I am in the last course I will have for COBOL in college, and I have to write interacting programs that are supposed to keep track of inventory for a business. I have reached a few parts that I am having problems with. The first is verifying that the date is between the years 2011 and 2012, and the second is that the month and day numbers are between 1-12 and 1-31, respectively. When I run my program, it always says in the error report that the year is wrong, even when I put it in right. Here is my code for that part:
   WORKING-STORAGE SECTION.
       05  POLI-DATE-REQUESTED-S.
           10 POLI-DATE-REQUESTED-S-1  PIC XX.
           10 POLI-DATE-REQUESTED-S-2  PIC XX.
           10 POLI-DATE-REQUESTED-S-3  PIC XX.
           10 POLI-DATE-REQUESTED-S-4  PIC XX.
   SCREEN SECTION.
   01  SCREEN-IMAGE.
       05  BLANK SCREEN
           BACKGROUND-COLOR 0.
       05  LINE 02  COLUMN 02          PIC X(8)
               FROM TIME-HHMMSSXX-COLONS
               FOREGROUND-COLOR 15.
       05  LINE 02  COLUMN 25
               VALUE 'Purchase Order Line Item Maintenance'
               FOREGROUND-COLOR 14.
       05  LINE 02  COLUMN 70          PIC X(8)
               FROM DATE-MMDDYY-SLASHES
               FOREGROUND-COLOR 15.
       05  LINE 04  COLUMN 02  VALUE 'FUNCTION CODE:'
               FOREGROUND-COLOR 10.
       05  LINE 04  COLUMN 18          PIC X(3)
               USING FUNCTION-CODE-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 04  COLUMN 23  VALUE '(ADD, CHG, DEL, INQ, END)'
               FOREGROUND-COLOR 11.
       05  LINE 07  COLUMN 23  VALUE 'NUMBER:'
               FOREGROUND-COLOR 10.
       05  LINE 07  COLUMN 50          PIC X(4)
               USING POLI-VEND-NUMBER-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 08  COLUMN 23  VALUE 'ORDER ID:'
               FOREGROUND-COLOR 10.
       05  LINE 08  COLUMN 50          PIC X(8)
               USING POLI-ORDER-ID-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 09  COLUMN 23  VALUE 'LINE ITEM:'
               FOREGROUND-COLOR 10.
       05  LINE 09  COLUMN 50          PIC X(4)
               USING POLI-LINE-ITEM-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 10  COLUMN 23  VALUE 'ITEM ID:'
               FOREGROUND-COLOR 10.
       05  LINE 10  COLUMN 50          PIC X(10)
               USING POLI-ITEM-ID-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 11  COLUMN 23  VALUE 'QUANTITY:'
               FOREGROUND-COLOR 10.
       05  LINE 11  COLUMN 50          PIC X(5)
               USING POLI-QUANTITY-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 12  COLUMN 23  VALUE 'DATE REQUESTED (YYYYMMDD):'
               FOREGROUND-COLOR 10.
       05  LINE 12  COLUMN 50          PIC X(8)
               USING POLI-DATE-REQUESTED-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 13  COLUMN 23  VALUE 'QUOTED COST:'
               FOREGROUND-COLOR 10.
       05  LINE 13  COLUMN 50          PIC X(7)
               USING POLI-QUOTED-COST-S
               FOREGROUND-COLOR 15 AUTO.
       05  LINE 17  COLUMN 23  VALUE 'DATE ADDED:'
               FOREGROUND-COLOR 10.
       05  LINE 17  COLUMN 40  PIC X(10)
               USING POLI-DATE-ADDED-S
               FOREGROUND-COLOR 15.
       05  LINE 18  COLUMN 23  VALUE 'DATE-CHANGED:'
               FOREGROUND-COLOR 10.
       05  LINE 18  COLUMN 40  PIC X(10)
               USING POLI-DATE-CHANGED-S
               FOREGROUND-COLOR 15.
       05  LINE 23  COLUMN 23  PIC X(55)
               FROM ERROR-MESSAGE-S
               FOREGROUND-COLOR 12.
   PROCEDURE DIVISION.
   900-VALIDATE-THE-FIELDS.
       IF POLI-DATE-REQUESTED-S-1 IS NOT = 20
           MOVE 'Year must be 2011 OR 2012' TO ERROR-MESSAGE-S
           GO TO 999-EXIT
       END-IF
       IF POLI-DATE-REQUESTED-S-2 IS NOT = 11 OR 12
           MOVE 'Year Must Be 2011 Or 2012' TO ERROR-MESSAGE-S
           GO TO 999-EXIT
       END-IF
     开发者_运维技巧  IF POLI-DATE-REQUESTED-S-3 IS < 1 OR > 12
           MOVE 'Month Must Be 1 Through 12' TO ERROR-MESSAGE-S
           GO TO 999-EXIT
       END-IF
       IF POLI-DATE-REQUESTED-S-4 IS < 1 OR > 31
           MOVE 'Day Must Be 1 Through 31' TO ERROR-MESSAGE-S
           GO TO 999-EXIT
       END-IF.
Also, I have to make sure that a record in a field called POLI-ITEM-ID already exists in another indexed file called ITEM-MASTER. I am not exactly sure how to do this, but I assume that it involves temporarily opening the file and searching it. If anyone could show me how to do this I would be grateful, as these two things seem to be the only things holding me back today. I thank everyone for all the help in advance.
Edit: The input data is written on a screen image that is part of the program. Thus I know that what I put in in correct at the time of entry. If it helps, I have put the SCREEN SELECTION in the code, but I do not think it has any bearing on why my date entry is considered an error (i.e. I put in "2011" and it tells me on the screen "Year must be 2011 OR 2012").
   05  POLI-DATE-REQUESTED-S.
       10 POLI-DATE-REQUESTED-S-1  PIC 9999.
          88 Year-Valid            value 2011 thru 2012.
       10 POLI-DATE-REQUESTED-S-2  PIC 99.
          88 Month-Valid           value 01 thru 12.
       10 POLI-DATE-REQUESTED-S-4  PIC 99.              
          88 Day-Valid             value 01 thru 31.
Try redefining your fields like this. Then you can do a simple test of the fields with:
  IF not Year-Valid
       MOVE 'Year must be 2011 OR 2012' TO ERROR-MESSAGE-S
  Else
       IF not Month-Valid
          MOVE 'Month Must Be 1 Through 12' TO ERROR-MESSAGE-S
       Else
          IF not Day-Valid
              MOVE 'Day Must Be 1 Through 31' TO ERROR-MESSAGE-S
          END-IF
       END-IF
  END-IF
To deal with your lookup, do a direct read on the ITEM-MASTER file. That will involve something like this:
   SELECT ITEM-MASTER ASSIGN TO "fname.txt"
      ORGANIZATION IS INDEXED
      ACCESS MODE IS DYNAMIC
      RECORD KEY IS ITEM-MASTER-KEY.
and then do a direct read:
  READ ITEM-MASTER
     KEY IS POLI-ITEM-ID
     INVALID KEY  DISPLAY "error or something"
  END-READ
Be careful - the accepted solution does not guarantee numeric values. The following program illustrates the point:
   PROGRAM-ID. EXAMPLE.                       
   DATA DIVISION.                             
   WORKING-STORAGE SECTION.                   
   01  TXT-VALUE        PIC X(4).             
   01  NUM-VALUE        PIC 9(4).             
       88 WS-VALID-NUM  VALUE  2000 THRU 2999.
   PROCEDURE DIVISION.                        
       MOVE '21b1' TO TXT-VALUE               
       MOVE TXT-VALUE TO NUM-VALUE            
       DISPLAY 'NUM-VALUE: ' NUM-VALUE        
       IF WS-VALID-NUM                        
          DISPLAY 'passed the range test.'    
       END-IF                                 
       IF NUM-VALUE IS NUMERIC                
          DISPLAY 'passed numeric test.'      
       ELSE                                   
          DISPLAY 'failed numeric test.'      
       END-IF                                 
Which results in the following output:
NUM-VALUE: 21b1       
passed the range test.
failed numeric test.  
Lesson: Always validate numeric fields with an IS NUMERIC test and then a range test.
Furthermore, unless input data have been pre-edited for validity, 
it is not a good idea to read external data directly into numeric
data types. Reading '1b' from an
input file directly into a PIC 9(2) data item yields the value 12 (in an ebcdic based
environment). This will now pass an IS NUMERIC test as well as range tests even though
the actual input data were not numeric. The reasons for the "automatic" conversion are
a bit beyond this discussion - lets just say data movement rules in COBOL are
much more complex than most people appreciate.
Joe Zitzelberger's post is the recommended and 'clean' way to do this.
I would just point out that the error in your original code was to mix up XX and numeric types. You should either have used character literals in your tests:
IF POLI-DATE-REQUESTED-S-1 IS NOT = '20'
or, better, defined your data values as numbers:
 10 POLI-DATE-REQUESTED-S-1  PIC 99.
01  FILLER. 
05  POLI-DATE-REQUESTED-S. 
    10  POLI-DATE-REQUESTED-S-1  PIC XXXX. 
        88  YEAR-VALID            VALUE "2011" THRU "2012". 
    10  POLI-DATE-REQUESTED-S-2  PIC XX. 
        88  MONTH-VALID           VALUE "01" THRU "12". 
        88  MONTH-IS-FEB          VALUE "02". 
        88  MONTH-IS-30-DAYS      VALUE "04" "06" "09" "11".
    10  POLI-DATE-REQUESTED-S-4  PIC XX. 
        88  DAY-MAY-BE-VALID      VALUE "01" THRU "31". 
        88  VALID-FEB-DAYS        VALUE "01" THRU "28". 
        88  VALID-30-DAYS         VALUE "01" THRU "30". 
Then the "first cut", with a student who doesn't have to worry about the actual number of days a month has:
MOVE SPACE                   TO ERROR-MESSAGE-S
EVALUATE TRUE 
  WHEN NOT POLI-DATE-REQUESTED-S NUMERIC 
      MOVE 'DATE MUST ONLY BE NUMBERS' 
                             TO ERROR-MESSAGE-S
  WHEN NOT YEAR-VALID 
    MOVE 'YEAR MUST BE 2011 OR 2012' 
                             TO ERROR-MESSAGE-S
  WHEN NOT MONTH-VALID 
    MOVE 'MONTH MUST BE 01 THROUGH 12' 
                             TO ERROR-MESSAGE-S
  WHEN NOT DAY-MAY-BE-VALID 
    MOVE "DAY IS ZERO OR MORE THAN 31" 
                             TO ERROR-MESSAGE-S
END-EVALUATE 
And then amended later for the actual number of days.
MOVE SPACE                   TO ERROR-MESSAGE-S
EVALUATE TRUE 
  WHEN NOT POLI-DATE-REQUESTED-S NUMERIC 
      MOVE 'DATE MUST ONLY BE NUMBERS' 
                             TO ERROR-MESSAGE-S
  WHEN NOT YEAR-VALID 
    MOVE 'YEAR MUST BE 2011 OR 2012' 
                             TO ERROR-MESSAGE-S
  WHEN NOT MONTH-VALID 
    MOVE 'MONTH MUST BE 01 THROUGH 12' 
                             TO ERROR-MESSAGE-S
  WHEN NOT DAY-MAY-BE-VALID 
    MOVE "DAY IS ZERO OR MORE THAN 31" 
                             TO ERROR-MESSAGE-S
  WHEN ( MONTH-IS-FEB 
       AND NOT VALID-FEB-DAYS ) 
   MOVE 'TOO MANY DAYS FOR FEBRUARY' 
                             TO ERROR-MESSAGE-S
  WHEN ( MONTH-IS-30-DAYS 
       AND NOT VALID-30-DAYS ) 
   MOVE 'NO 31ST THIS MONTH' 
                             TO ERROR-MESSAGE-S
END-EVALUATE 
 
         
                                         
                                         
                                         
                                        ![Interactive visualization of a graph in python [closed]](https://www.devze.com/res/2023/04-10/09/92d32fe8c0d22fb96bd6f6e8b7d1f457.gif) 
                                         
                                         
                                         
                                         加载中,请稍侯......
 加载中,请稍侯......
      
精彩评论