Hey all, got one mountain of a problem here. I have completed a program I had to do for college homework, but when I run it the output shows almost nothing it is suppose to. This only happens when I RUN it though. If I hold F11 to STEP through the whole thing it shows the results as it is suppose to be. Normally I would not ask about something this big but I am stumped. Here is my code:
   ENVIRONMENT DIVISION.
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.
       SELECT SALESAMT-FILE-IN
           ASSIGN TO 'SALESAMT.SEQ'
           ORGANIZATION IS LINE SEQUENTIAL.
       SELECT SALESMAN-FILE-IN
           ASSIGN TO 'SALESMAN.SEQ'
           ORGANIZATION IS LINE SEQUENTIAL.
       SELECT SALESQTR-FILE-IN
           ASSIGN TO 'SALESQTR.SEQ'
           ORGANIZATION IS LINE SEQUENTIAL.
       SELECT SALESAMT-FILE-OUT
           ASSIGN TO 'SALESAMT.RPT'
           ORGANIZATION IS LINE SEQUENTIAL.
   DATA DIVISION.
   FILE SECTION.
   FD  SALESMAN-FILE-IN.
   01  SALESMAN-RECORD-IN.
       05  SM-NUMBER-IN                    PIC 99.
       05  SM-NAME-IN                      PIC X(20).
   FD  SALESQTR-FILE-IN.
   01  SALESQTR-RECORD-IN.
       05  QUARTER-YEAR                    PIC X.
   FD  SALESAMT-FILE-IN.
   01  SALESAMT-RECORD-IN.
       05  SM-NUMBER                       PIC 99.
       05                                  PIC X.
       05  MONTH-NUMBER                    PIC 9.
       05                                  PIC X.
       05  SALES-AMOUNT                    PIC 9(5).
   FD  SALESAMT-FILE-OUT.
   01  SALESAMT-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  QUARTER-CHECK                       PIC X.
   01  ROUTINE-CHECK                       PIC 99    VALUE ZEROS.
   01  SALESMAN-MATH                       PIC 9(5)  VALUE ZEROS.
   01  SALESMAN-TOTAL                      PIC 9(6)  VALUE ZEROS.
   01  FINAL-M-TOTAL-1                     PIC 9(7)  VALUE ZEROS.
   01  FINAL-M-TOTAL-3                     PIC 9(7)  VALUE ZEROS.
   01  FINAL-M-TOTAL-2                     PIC 9(7)  VALUE ZEROS.
   01  FINAL-TOTAL                         PIC 9(7)  VALUE ZEROS.
   01  SM-NUM-M                           PIC 99    VALUE ZEROS.
   01  MORE-TABLE-RECS                     PIC X     VALUE 'Y'.
   01  SPACE-LINE                          PIC X     VALUE SPACE.
   01  MONTH-NAMES
           VALUE 'JANFEBMARAPRMAYJUNJULAUGSEPOCTNOVDEC'.
       05  MONTH-TITLES OCCURS 12 TIMES    PIC X(3).
   01  MONTH-ARRAY.
       05  THREE-MONTHS OCCURS 3 TIMES.
           10 MONTH-TOTAL OCCURS 99 TIMES  PIC 9(7)  VALUE ZEROS.
   01  SALESMAN-TABLE.
       05  TABLE-ENTRIES OCCURS 99 TIMES
               INDEXED BY IND-TABLE-ENTRIES.
           10 SALESMAN-NUMBER              PIC 99    VALUE ZEROS.
           10 SALESMAN-NAME                PIC X(20) VALUE SPACES.
   01  SALESMAN-COUNT                      PIC 9(3)  VALUE ZEROS.
   01  WS-DATE.
       05  RUN-YEAR                        PIC XX.
       05  RUN-MONTH                       PIC XX.
       05  RUN-DAY                         PIC XX.
   01  HEADING-LINE-1.
       05                                  PIC X(17) VALUE SPACES.
       05                                  PIC X(35)
           VALUE 'SALES AMOUNTS BY SALESMAN AND MONTH'.
       05                                  PIC X(10)  VALUE SPACES.
       05  HL-1-DATE.
           10  MONTH-2                     PIC XX.
           10                              PIC X      VALUE '/'.
           10  DAY-2                       PIC XX.
           10                              PIC X      VALUE '/'.
           10  YEAR-2                      PIC XX.
       05                                  PIC X(3)   VALUE SPACES.
       05  PAGE-1                          PIC X(4)   VALUE 'PAGE'.
       05                                  PIC X(1)   VALUE SPACES.
       05  NUMBER-PAGE                     PIC Z9.
   01  HEADING-LINE-2.
       05  HL-NUM                          PIC X(3)   VALUE 'NUM'.
       05  HL-BLANK-A                      PIC XX     VALUE SPACES.
       05  HL-NAME                         PIC X(4)   VALUE 'NAME'.
       05  HL-BLANK-B                      PIC X(20)  VALUE SPACES.
       05  HL-MONTH-1                      PIC X(3)   VALUE SPACES.
       05  HL-BLANK-C                      PIC X(8)   VALUE SPACES.
       05  HL-MONTH-2                      PIC X(3)   VALUE SPACES.
       05  HL-BLANK-D                      PIC X(8)   VALUE SPACES.
       05  HL-MONTH-3                      PIC X(3)   VALUE SPACES.
       05  HL-BLANK-E                      PIC X(10)  VALUE SPACES.
       05  HL-TOTAL                        PIC X(5)   VALUE 'TOTAL'.
   01  DETAIL-LINE.
       05  DL-BLANK-A                      PIC X      VALUE SPACES.
       05  DL-NUM-COLUMN                   PIC 99.
       05  DL-BLANK-B                      PIC XX     VALUE SPACES.
       05  DL-NAME-COLUMN                  PIC X(17).
       05  DL-BLANK-C                      PIC X(4)   VALUE SPACES.
       05  DL-MONTH-1                      PIC ZZ,Z(3).
       05  DL-BLANK-D                      PIC X(5)   VALUE SPACES.
       05  DL-MONTH-2                      PIC ZZ,Z(3).
       05  DL-BLANK-E                      PIC X(5)   VALUE SPACES.
       05  DL-MONTH-3                      PIC ZZ,Z(3).
       05  DL-BLANK-F                      PIC X(8)   VALUE SPACES.
       05  DL-TOTAL                        PIC Z(3),Z(3).
   01 TOTALS-LINE.
       05  TL-WORDS                        PIC X(12)
           VALUE 'Final Totals'.
       05  TL-BLANK-A                      PIC X(12)   VALUE SPACES.
       05  MONTH-1-TOTAL                   PIC Z,Z(3),Z(3).
       05  TL-BLANK-A                      PIC X(2)   VALUE SPACES.
       05  MONTH-2-TOTAL                   PIC Z,Z(3),Z(3).
       05  TL-BLANK-A                      PIC X(2)   VALUE SPACES.
       05  MONTH-3-TOTAL                   PIC Z,Z(3),Z(3).
       05  TL-BLANK-A                      PIC X(5)   VALUE SPACES.
       05  MONTH-FINAL-TOTAL               PIC Z,Z(3),Z(3).
   PROCEDURE DIVISION.
   100-MAIN.
       OPEN INPUT SALESAMT-FILE-IN, SALESMAN-FILE-IN,
           SALESQTR-FILE-IN
       OPEN OUTPUT SALESAMT-FILE-OUT
       ACCEPT WS-DATE FROM DATE
       MOVE RUN-MONTH TO MONTH-2
       MOVE RUN-DAY TO DAY-2
       MOVE RUN-YEAR TO YEAR-2
       PERFORM 200-NEXT-PAGE
       PERFORM 300-SALES-ARRAY
       PERFORM 400-SALESMAN-NAME
       PERFORM 500-PROCESS-FILE
       PERFORM 600-FINAL-TOTALS
       CLOSE SALESAMT-FILE-IN, SALESMAN-FILE-IN, SALESQTR-FILE-IN
       CLOSE SALESAMT-FILE-OUT
       STOP RUN.
   200-NEXT-PAGE.
       ADD 1 TO PAGE-NUMBER
       MOVE PAGE-NUMBER TO NUMBER-PAGE
       MOVE HEADING-LINE-1 TO SALESAMT-RECORD-OUT
       IF REPORT-START = 'N'
           WRITE SALESAMT-RECORD-OUT
               AFTER ADVANCING PAGE
       ELSE
           MOVE 'N' TO REPORT-START
           WRITE SALESAMT-RECORD-OUT
               AFTER ADVANCING 1 LINE
           PERFORM 210-MONTH-CHECK
       END-IF.
       MOVE HEADING-LINE-2 TO SALESAMT-RECORD-OUT
       WRITE SALESAMT-RECORD-OUT
           AFTER ADVANCING 2 LINES
       MOVE ZEROS TO LINE-COUNT.
   210-MONTH-CHECK.
       READ SALESQTR-FILE-IN
           AT END
               CONTINUE
           NOT AT END
               PERFORM 220-MONTH-NAME
       END-READ.
   220-MONTH-NAME.
           EVALUATE QUARTER-YEAR
               WHEN = 1       MOVE MONTH-TITLES(1) TO HL-MONTH-1
                              MOVE MONTH-TITLES(2) TO HL-MONTH-2
                              MOVE MONTH-TITLES(3) TO HL-MONTH-3
               WHEN = 2       MOVE MONTH-TITLES(4) TO HL-MONTH-1
                              MOVE MONTH-TITLES(5) TO HL-MONTH-2
                              MOVE MONTH-TITLES(6) TO HL-MONTH-3
               WHEN = 3       MOVE MONTH-TITLES(7) TO HL-MONTH-1
                              MOVE MONTH-TITLES(8) TO HL-MONTH-2
                              MOVE MONTH-TITLES(9) TO HL-MONTH-3
               WHEN = 4       MOVE MONTH-TITLES(10) TO HL-MONTH-1
                              MOVE MONTH-TITLES(11) TO HL-MONTH-2
                              MOVE MONTH-TITLES(12) TO HL-MONTH-3
           END-EVALUATE.
   300-SALES-ARRAY.
       PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
           READ SALESAMT-FILE-IN
               AT END
                   MOVE 'NO ' TO ARE-THERE-MORE-RECORDS
               NOT AT END
                   PERFORM 310-STORE-DATA
           END-READ
       END-PERFORM.
   310-STORE-DATA.
       MOVE SM-NUMBER TO SM-NUM-M
       EVALUATE MONTH-NUMBER
           WHEN 1                  PERFORM 320-FIRST-MONTH
           WHEN 2                  PERFORM 330-SECOND-MONTH
           WHEN 3                  PERFORM 340-THIRD-MONTH
       END-EVALUATE.
   320-FIRST-MONTH.
       ADD SALES-AMOUNT TO
           MONTH-TOTAL OF MONTH-ARRAY (1, SM-NUM-M).
   330-SECOND-MONTH.
       ADD SALES-AMOUNT TO
           MONTH-TOTAL OF MONTH-ARRAY (2, SM-NUM-M).
   340-THIRD-MONTH.
       ADD SALES-AMOUNT TO
           MONTH-TOTAL OF MONTH-ARRAY (3, SM-NUM-M).
   400-SALESMAN-NAME.
       PERFORM UNTIL MORE-TABLE-RECS = 'N'
           READ SALESMAN-FILE-IN
               AT END
                   MOVE 'N' TO MORE-TABLE-RECS
               NOT AT END
                   PERFORM 450-TABLE-LOAD
           END-READ
       END-PERFORM.
   450-TABLE-LOAD.
       MOVE SM-NUMBER-IN TO SALESMAN-COUNT
       MOVE SM-NUMBER-IN TO SALESMAN-NUMBER (SALESMAN-COUNT)
       MOVE SM-NAME-IN TO SALESMAN-NAME (SALESMAN-COUNT).
   500-PROCESS-FILE.
       PERFORM UNTIL ROUTINE-CHECK = 99
           ADD 1 TO ROUTINE-CHECK
           PERFORM 510-TABLE-SEARCH
       END-PERFORM.
   510-TABLE-SEARCH.
       SEARCH TABLE-ENTRIES
           WHEN SALESMAN-NUMBER (ROUTINE-CHECK) = ROUTINE-CHECK
               PERFORM 520-WRITE-FILE
           WHEN SALESMAN-NUMBER (ROUTINE-CHECK) = 0
               CONTINUE
       END-SEARCH.
   520-WRITE-FILE.
       MOVE SALESMAN-NAME (ROUTINE-CHECK) TO DL-NAME-COLUMN
       IF DL-NAME-COLUMN = SPACES
           MOVE '*** Not Found ***' TO DL-NAME-COLUMN
       END-IF
       MOVE ROUTINE-CHECK TO DL-NUM-COLUMN
       MOVE ROUTINE-CHECK TO SM-NUM-M
       MOVE MONTH-TOTAL (1, SM-NUM-M) TO DL-MONTH-1
       MOVE DL-MONTH-1 TO SALESMAN-MATH
       ADD SALESMAN-MATH TO SALESMAN-TOTAL
       ADD SALESMAN-MATH TO FINAL-M-TOTAL-1
       ADD SALESMAN-MATH TO FINAL-TOTAL
       MOVE MONTH-TOTAL (2, SM-NUM-M) TO DL-MONTH-2
       MOVE DL-MONTH-2 TO SALESMAN-MATH
       ADD SALESMAN-MATH TO SALESMAN-TOTAL
       ADD SALESMAN-MATH TO FINAL-M-TOTAL-2
       ADD SALESMAN-MATH TO FINAL-TOTAL
       MOVE MONTH-TOTAL (3, SM-NUM-M) TO DL-MONTH-3
       MOVE DL-MONTH-3 TO SALESMAN-MATH
       ADD SALESMAN-MATH TO SALESMAN-TOTAL
       ADD SALESMAN-MATH TO FINAL-M-TOTAL-3
       ADD SALESMAN-MATH TO FINAL-TOTAL
       IF SALESMAN-TOTAL > 0
           MOVE SALESMAN-TOTAL TO DL-TOTAL
           MOVE DETAIL-LINE TO SALESAMT-RECORD-OUT
           WRITE SALESAMT-RECORD-OUT
               AFTER ADVANCING 2 LINES
       END-IF
       MOVE ZEROS TO SALESMAN-TOTAL.
   600-FINAL-TOTALS.
       MOVE FINAL-M-TOTAL-1 TO MONTH-1-TOTAL
       MOVE FINAL-M-TOTAL-2 TO MONTH-2-TOTAL
       MOVE FINAL-M-TOTAL-3 TO MONTH-3-TOTAL
       MOVE FINAL-TOTAL TO MONTH-FINAL-TOTAL
       MOVE TOTALS-LINE TO SALESAMT-RECORD-OUT
       WRITE SALESAMT-RECORD-OUT
           AFTER ADVANCING 3 LINES.
To me it seems that the logic is right as it does work, but for some reason it (in my mind when i see the results) jumps completely over 520-WRITE-FILE when it runs. With this I do leave a few notes.
I know 510-TABLE-SEARCH makes little sense and I intend to change it later, but I need to fix this first and it works for the moment. Unless it is the main problem please don't harass me over it.
I will be willing to add the data in the SEQ files if someone asks me for it.
My code might be a bit complex and I admit to that, but I am doing the best I can with the teacher I have (I mostly have to learn this stuff on my own).
I appreciate any help I receive and thank anyone who tries to help in advance.
edit: I am using a compiler called Micro Focus, Net Express 5.1 Academic Edition and my OS is Windows Vista. As for what the program does show when I run it, it just shows my two heading lines and then my totals-line without anything but the first field showing. I hope that helps.
I don't know for certain if this is the problem, but I can see a logic flow that isn't going to work very well...
First: 400-SALESMAN-NAME reads salesmen records from a file into working storage table SALESMAN-TABLE. 
The file probably looks something like:
01Sales Guy One   
02Lance Winslow   
03Scott Peterson   
04Willy Loman   
When the read loop is done, SALESMAN-NUMBER will equal the table index because of
the way you load the table (using SM-NUMBER-IN to set the table subscript). No problem so far...
Next: 500-PROCESS-FILE loops through all rows in the SALESMAN-TABLE by running subscript ROUTINE-CHECK from 1 to 99 and performing 510-TABLE-SEARCH to write out the report for the salesman where the subscript equals SALESMAN-NUMBER...
Next: The SEARCH statement. This is where it all goes strange and never performs 520-WRITE-FILE. 
This is why.
The SEARCH statement implements a linear search (SEARCH ALL is a binary search). SEARCH just increments the index associated with the searched table and then runs through a bunch of WHEN tests until one of them "fires" or the index runs off the end of the table. The index for your TABLE-ENTRIES table is IND-TABLE-ENTRIES. But you never set or reference it (this is the root of the problem). I will explain in a moment...
Notice that the WHEN part of your SEARCH is using subscript ROUTINE-CHECK. ROUTINE-CHECK was set in 500-PROCESS-FILE. Also notice that you only get to 520-WRITE-FILE if the SALESMAN-NUMBER matches the value of ROUTINE-CHECK - which it will do if a salesman with that number was read from the input file. This could work because you loaded the table such that the row number equals the salesman number back in 450-TABLE-LOAD.
Now, what happens if the input file does not contain a salesman where SM-NUMBER-IN equals 01?
Lets go through it, blow by blow...
ROUTINE-CHECK is set to 1, SEARCH is invoked and because the IND-TABLE-ENTRIES index associated with the searched table is less than the number of occurs in the table (it got initialized to zero on program load), the WHEN clauses are executed. 
The first test is WHEN SALESMAN-NUMBER (ROUTINE-CHECK) = ROUTINE-CHECK. Since Salesman 1 doesn't exist, the SALESMAN-NUMBER will be zero and the test fails (0<>1). 
The next WHEN clause is tried and it succeeds because (0=0); but this is a 'do nothing' option so another cycle of SEARCH is entered after IND-TABLE-ENTRIES is incremented. 
Same results on this and all subsequent iterations through the SEARCHed WHEN list (none of the clauses match)... Repeat this loop until IND-TABLE-ENTRIES is incremented beyond the end of the table. 
At this point the SEARCH terminates and control flows back to the next loop in 500-PROCESS-FILE. Nothing has been printed.
500-PROCESS-FILE then increments ROUTINE-CHECK by 1 (now it is 2). We have a salesman with a SALESMAN-NUMBER of 02 so we should get some output - right? Wrong! But why?
If you read up on the SEARCH verb you will find it does not reset the table index (in this case: IND-TABLE-ENTRIES). It starts using whatever value it has when the SEARCH is entered.  You never reset it so it is already set beyond the end of the table. SEARCH just terminates and nothing gets printed - ever again. 
Fixing the problem
Given that you have loaded TABLE-ENTRIES by salesman number in the first place, I don't see the purpose of using SEARCH. Just do something like:
500-PROCESS-FILE.   
    PERFORM VARYING ROUTINE-CHECK FROM 1 BY 1  
              UNTIL ROUTINE-CHECK > 99   
        IF SALESMAN-NUMBER (ROUTINE-CHECK) = ZERO   
           CONTINUE   
        ELSE   
           PERFORM 520-WRITE-FILE   
        END-IF   
    END-PERFORM.    
Might also be a good idea to have an initialization loop for the table so that every SALESMAN-NUMBER is explicitly set to zero before you read the salesman file.
If you must use SEARCH in this program, then don't forget to set and use the associated table index variable when referencing the table being searched.
I've added this as a second answer, which I think is correct !
520-WRITE-FILE is not being performed because the SEARCH to call it is failing.
In 510-TABLE-SEARCH, I believe you need to search on the index declared for the table, IND-TABLE-ENTRIES. You will probably need to re-code 500-PROCESS-FILE and 510-TABLE-SEARCH.
In another question, you asked about the SEARCH verb. fmartin gave a link describing how it works, with examples.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With