As part of an assignment I need to create a "shipping" program that checks a certain field which tells the date an item is to be shipped. Any record with a date greater than 6 months away is to be omitted while sorting the rest of the data.
The problem is no matter what I try I get bad results. I figured an EVALUATE
statement would be the best route to go, but I just can't seem to get it right. This is what I have down:
DATA DIVISION.
FILE SECTION.
COPY ORDERS-FILE-NEW-IN.COP.
FD ORDERS-FILE-NEW-IN.
01 ORDERS-RECORD-NEW-IN.
05 PART-NUMBER-N-IN PIC X(8).
05 QUANTITY-N-IN PIC 9(4).
05 REQUEST-DATE-N-IN.
10 REQUEST-YEAR-N-IN PIC X(4).
10 REQUEST-MONTH-N-IN PIC XX.
10 REQUEST-DAY-N-IN PIC XX.
05 CUST-NUMBER-N-IN PIC X(5).
05 CUST-ORDER-NUMBER-N-IN PIC X(10).
05 STOCK-AVAILABLE-N-IN PIC X.
COPY ORDERS-FILE-PRIOR-IN.COP.
FD ORDERS-FILE-PRIOR-IN.
01 ORDERS-RECORD-PRIOR-IN.
05 PART-NUMBER-P-IN PIC X(8).
05 QUANTITY-P-IN PIC 9(4).
05 REQUEST-DATE-P-IN.
10 REQUEST-YEAR-P-IN PIC X(4).
10 REQUEST-MONTH-P-IN PIC XX.
10 REQUEST-DAY-P-IN PIC XX.
05 CUST-NUMBER-P-IN PIC X(5).
05 CUST-ORDER-NUMBER-P-IN PIC X(10).
05 STOCK-AVAILABLE-P-IN PIC X.
COPY ORDERS-FILE-SORT.COP.
SD ORDERS-FILE-SORT.
01 ORDERS-RECORD-SORT.
05 PART-NUMBER-S PIC X(8).
05 QUANTITY-S PIC 9(4).
05 REQUEST-DATE-S.
10 REQUEST-YEAR-S PIC X(4).
10 REQUEST-MONTH-S PIC XX.
10 REQUEST-DAY-S PIC XX.
05 CUST-NUMBER-S PIC X(5).
05 CUST-ORDER-NUMBER-S PIC X(10).
05 STOCK-AVAILABLE-S PIC X.
FD ORDERS-FILE-OUT.
01 ORDERS-RECORD-OUT PIC X(80).
WORKING-STORAGE SECTION.
01 ARE-THERE-MORE-RECORDS PIC X(3) VALUE 'YES'.
01 REPORT-START PIC X VALUE 'Y'.
01 LINE-COUNT PIC 99 VALUE ZEROS.
01 LINE-JUMP PIC X VALUE 'Y'.
01 PAGE-NUMBER PIC 99 VALUE ZEROS.
01 MONTH-TOTAL PIC 99 VALUE ZEROS.
01 YEAR-TOTAL PIC 99 VALUE ZEROS.
01 YEAR-CHECK PIC 99 VALUE ZEROS.
01 SPACE-LINE PIC X VALUE SPACE.
01 WS-DATE.
05 RUN-MONTH PIC XX.
05 RUN-DAY PIC XX.
05 RUN-YEAR PIC XX.
01 HEADING-LINE-1.
05 PIC X(15) VALUE SPACES.
05 PIC X(43)
VALUE 'OPEN ORDERS REPORT - NEXT SIX MONTHS'.
05 HL-1-DATE.
10 MONTH-1 PIC 99.
10 PIC X VALUE '/'.
10 DAY-1 PIC 99.
10 PIC X VALUE '/'.
10 YEAR-1 PIC 99.
05 PIC X(3) VALUE SPACES.
05 PAGE-1 PIC X(5) VALUE 'PAGE'.
05 NUMBER-PAGE PIC Z9.
01 HEADING-LINE-2.
05 PIC X(14)
VALUE 'REQUEST DATE'.
05 PIC X(12)
VALUE 'CUSTOMER #'.
05 PIC X(16)
VALUE 'CUSTOMER ORD #'.
05 PIC X(10)
VALUE 'PART #'.
05 PIC X(11)
VALUE 'QUANTITY'.
05 PIC X(8)
VALUE 'AVAIL'.
05 PIC X(5)
VALUE 'SHIP?'.
01 DETAIL-LINE.
05 REQUEST-DATE.
10 REQUEST-MONTH PIC XX.
10 PIC X VALUE '/'.
10 REQUEST-DAY PIC XX.
10 PIC X VALUE '/'.
10 REQUEST-YEAR PIC X(4).
05 PIC X(4) VALUE SPACES.
05 CUST-NUMBER PIC X(5).
05 PIC X(7) VALUE SPACES.
05 CUST-ORDER-NUMBER PIC X(10).
05 PIC X(6) VALUE SPACES.
05 PART-NUMBER PIC X(8).
05 PIC X(5) VALUE SPACES.
05 QUANTITY PIC Z,ZZZ.
05 PIC X(3) VALUE SPACES.
05 STOCK-AVAILABLE PIC X(3).
05 PIC X(5) VALUE SPACES.
05 SHIP-MESSAGE PIC X(4).
PROCEDURE DIVISION.
100-MAIN.
SORT ORDERS-FILE-SORT
ON ASCENDING KEY REQUEST-DATE-S
ON ASCENDING KEY CUST-NUMBER-S
ON ASCENDING KEY CUST-ORDER-NUMBER-S
ON ASCENDING KEY PART-NUMBER-S
INPUT PROCEDURE 200-SORT-SELECTION
OUTPUT PROCEDURE 300-FILE-START
STOP RUN.
200-SORT-SELECTION.
OPEN INPUT ORDERS-FILE-NEW-IN
ORDERS-FILE-PRIOR-IN
ACCEPT WS-DATE FROM DATE
MOVE RUN-MONTH TO MONTH-1
MOVE RUN-DAY TO DAY-1
MOVE RUN-YEAR TO YEAR-1
PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
READ ORDERS-FILE-PRIOR-IN
AT END
MOVE 'NO' TO ARE-THERE-MORE-RECORDS
NOT AT END
PERFORM 210-SORT-ADD-PRIOR
END-READ
END-PERFORM
MOVE 'YES' TO ARE-THERE-MORE-RECORDS
PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
READ ORDERS-FILE-NEW-IN
AT END
MOVE 'NO' TO ARE-THERE-MORE-RECORDS
NOT AT END
PERFORM 220-SORT开发者_开发知识库-ADD-NEW
END-READ
END-PERFORM
MOVE 'YES' TO ARE-THERE-MORE-RECORDS
CLOSE ORDERS-FILE-NEW-IN
ORDERS-FILE-PRIOR-IN.
210-SORT-ADD-PRIOR.
MOVE ORDERS-RECORD-PRIOR-IN TO ORDERS-RECORD-SORT
MOVE MONTH-1 TO MONTH-TOTAL
MOVE YEAR-1 TO YEAR-TOTAL
MOVE REQUEST-YEAR-P-IN TO YEAR-CHECK
ADD 6 TO MONTH-TOTAL
IF MONTH-TOTAL > 12
SUBTRACT 12 FROM MONTH-TOTAL
END-IF
EVALUATE REQUEST-MONTH-P-IN
WHEN 01 IF MONTH-TOTAL = 1 OR
(MONTH-TOTAL > 6 AND < 13)
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 02 IF (MONTH-TOTAL = 1 OR 2) OR
(MONTH-TOTAL > 7 AND < 13)
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 03 IF (MONTH-TOTAL > 0 AND < 4) OR
(MONTH-TOTAL > 8 AND < 13)
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 04 IF (MONTH-TOTAL > 0 AND < 5) OR
(MONTH-TOTAL > 9 AND < 13)
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 05 IF (MONTH-TOTAL > 0 AND < 6) OR
(MONTH-TOTAL = 11 OR 12)
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 06 IF (MONTH-TOTAL > 0 AND < 7) OR
MONTH-TOTAL = 12
IF YEAR-CHECK - YEAR-1 = 0 OR 1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 07 IF MONTH-TOTAL > 1 AND < 8
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 08 IF MONTH-TOTAL > 2 AND < 9
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 09 IF MONTH-TOTAL > 3 AND < 10
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 10 IF MONTH-TOTAL > 4 AND < 11
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 11 IF MONTH-TOTAL > 5 AND < 12
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
WHEN 12 IF MONTH-TOTAL > 6 AND < 13
IF YEAR-CHECK = YEAR-1
RELEASE ORDERS-RECORD-SORT
END-IF
END-IF
END-EVALUATE.
One of the first things you should learn as a programmer, COBOL or otherwise, is to nail down what your requirements really are. Your assignment is asking to compare two dates and perform certain actions if one is 6 months or less after another. Exactly what is the meaning of 6 months? Would it be: 183 days; would it be the month number plus 6, in such case, the dates 2011-01-31 and 2011-07-01 would be 6 months apart – but 33 days short of the 183 day alternative definition; other definitions are possible too. Dates, and date arithmetic in particular, can be confusing.
Next, beware of varying date formats: YYMMDD; YYYYMMDD; MMDDYYYY; DDMMYYYY and may more. The ACCEPT WS-DATE FROM DATE
statement could be giving you a date format different from the one you are expecting (compile time options and/ or compiler installation defaults may affect the format). It is generally better form to request an explicit date format as in ACCEPT WS-YYYYMMDD FROM DATE YYYYMMDD
. One of the problems in your program is related to this. You are mixing up 2 and 4 digit years, as in:
MOVE REQUEST-YEAR-P-IN TO YEAR-CHECK
Moves a 4 digit year to a two digit year. What do you suppose got truncated there? That in turn messes up your entire EVALUATE
statement (which I recommend not using the way you have in this program).
Next I think you would be better off taking advantage of the way dates are presented to you in the input file. They are in YYYYMMDD format. All you need to do is calculate a date a date 6 months into the future from the current date and compare it directly to the date from the input file. If the input date is numerically less than the calculated date, keep the record.
Try something like:
10 WS-YYYYMMDD.
15 WS-YYYY PIC 9(4).
15 WS-MM PIC 9(2).
15 WS-DD PIC 9(2).
100-MAIN.
*
* Calculate a reference date 6 months into the future.
*
ACCEPT WS-YYYYMMDD FROM DATE YYYYMMDD
COMPUTE WS-MM = WS-MM + 6 END-COMPUTE
IF WS-MM > 12
COMPUTE WS-MM = WS-MM - 12 END-COMPUTE
COMPUTE WS-YYYY = WS-YYYY + 1 END-COMPUTE
END-IF
....
210-SORT-ADD-PRIOR.
IF REQUEST-DATE-P-IN < WS-YYYYMMDD
MOVE ORDERS-RECORD-PRIOR-IN TO ORDERS-RECORD-SORT
RELEASE ORDERS-RECORD-SORT
END-IF
.
Or something along these lines... but get rid of that huge EVALUATE
.
If you want to know if a date is 6 months ahead I think it's easier to calculate just months
Compare
Year-today * 12 + month-Today + 6
With
Year-Shipping * 12 + month-Shipping
and you are done.
I can only assume this is too late to help with the homework, but compares of future dates may be easier with the intrinsic FUNCTION INTEGER-OF-DATE. You simply need integer compares after that. Assuming the dates are within the range of 16010101 and 99991231 you should be good to go (Gregorian).
IF MONTH-TOTAL > 12
SUBTRACT 12 FROM MONTH-TOTAL
END-IF
Maybe you need to add 1 to the year inside that IF?
I won't even try to write it in COBOL
I would suggest at the start of the program
- you calculate the date 6 months in the future (and store in YYYYMMDD format).
- You can then compare REQUEST-DATE-P-IN > Calculated-date
To calculate the future date:
Add 6 to month
if month > 12
Sub 12 from month
Add 1 to year
end-if
This is much simpler than the Evaluate
精彩评论