首页 > 解决方案 > 有没有办法更好地管理我的 COBOL 程序中的数据使用情况

问题描述

我目前正在编写一个程序,该程序在 COBOL 中找到最大的素因子或数字。这是我所拥有的:

IDENTIFICATION DIVISION.
PROGRAM-ID. EULER2.
DATA DIVISION.
WORKING-STORAGE SECTION.
    01 num1 PIC 9(12) VALUE 600851475143.
    01 num2 PIC 9(6) VALUE 2.
    01 smallest PIC 9(6) VALUE 0. 
    01 num3 PIC 9(6). 
PROCEDURE DIVISION.
MAIN-PROCEDURE. 

PERFORM whileLoop UNTIL num1 <= num2.
DISPLAY "Greatest prime of large number " smallest. 
STOP RUN.

whileLoop.
    IF FUNCTION MOD(num1, num2) = 0
        DIVIDE num2 INTO num1.
        IF(smallest LESS THAN num2)
            SET smallest TO num2
            ADD 1 TO smallest
    ELSE
        ADD 1 TO num2
    END-IF.  

此代码有效。但是为了得到正确的答案,我必须将 1 添加到最小,因为它会返回小于 1 的最大素数。此外,当我检查诸如最小之类的东西时,输出比我运行这个要多得多用另一种语言编写程序。我想知道这里是否存在内存问题,或者我是否可以深入了解 COBOL 是如何运行它的。

标签: memorycobol

解决方案


There is no memory usage issue. The run time is affected by the use of display values rather than binary values (I used comp-5) and that all even numbers are tested despite these not being possible primes.

As originally written, the loop was terminating when num1 <= num2. After adding 1 to num2, num2 became equal to num1, but smallest had a value that was one less than num1. By changing the loop termination to num1 < num2, the final value was saved in smallest. This removed the need to add the final 1.

In the code, I added statements to display num2. The numbers displayed are the prime factors than comprise the original number. I also replaced all separator periods, after statements, to a separate line at the end of their paragraphs.

I changes to address a comment and for other concerns.

If num1 is prime or has a factor, where either gives a result of more than 6 digits, there will be an overflow of num2 that will result in a "divide by zero" exception. That is to say that the PICTURE clause for num2 should never be smaller than that for num1. I made the PICTURE clauses 18 digits, which, in most cases, will be 64-bits.

I added some display formatting to make it "neater".

I changed the SET statement to a MOVE statement. Be aware that using a SET statement for assignment between two numeric data items is a syntax error in both the 1985 and 2002 standards.

ISO/IEC 1989:2002
SET statement
14.8.35.2 Syntax rules
4) If identifier-1 references a numeric data item, index-name-2 shall be specified.

Additional changes address speed. num2 is checked for 2, then for the odd numbers 3 and above. The search for the next factor is terminated when num2 is greater than the square root of num1. The largest 18-digit prime, 999,999,999,999,999,991, may still take several minutes, but is about a billion times faster than without these changes.

Code:

   IDENTIFICATION DIVISION.
   PROGRAM-ID. EULER2.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01 num1 comp-5 PIC S9(18) VALUE 600851475143.
   01 num2 comp-5 PIC S9(18) VALUE 2.
   01 smallest comp-5 PIC S9(18) VALUE 1.
   01 temp comp-5 PIC S9(18).
   01 rem comp-5 PIC S9(18).
   01 sqrt-num1 comp-5 PIC S9(18).
   01 num-display PIC BZZZ,ZZZ,ZZZ,ZZZ,ZZZ,ZZ9.
   01 trimmed-display PIC X(23).
   PROCEDURE DIVISION.
   MAIN-PROCEDURE. 
       PERFORM get-sqrt-num1
       DISPLAY "Factors:"
       PERFORM whileLoop UNTIL num1 < num2
       MOVE smallest TO num-display
       PERFORM trim-num
       DISPLAY SPACE
       DISPLAY "Greatest prime of large number: "
           trimmed-display
       STOP RUN
       .

   whileLoop.
       DIVIDE num2 INTO num1 GIVING temp REMAINDER rem
       IF rem = 0
           MOVE temp TO num1
           PERFORM get-sqrt-num1
           IF(smallest LESS THAN num2)
               MOVE num2 TO smallest
           end-if
           MOVE num2 TO num-display
           PERFORM trim-num
           DISPLAY trimmed-display
       ELSE
           IF num2 > 2
               ADD 2 TO num2
           ELSE
               ADD 1 TO num2
           END-IF
           IF num2 > sqrt-num1
               MOVE num1 TO num2
           END-IF
       END-IF
       .

   get-sqrt-num1.
       COMPUTE sqrt-num1 = FUNCTION SQRT (num1)
       .

   trim-num.
       UNSTRING num-display DELIMITED ALL SPACE
           INTO trimmed-display (1:1) trimmed-display
       .

Output:

Factors:
71
839
1,471
6,857

Greatest prime of large number: 6,857

推荐阅读