nboz75
nboz75

Reputation: 55

COBOL Only Reading From One Line of Input File

Having an issue with a Cobol batch program where it is only reading one line from an input file, and the line that's being read isn't the first line either. Records for the input file are fixed length. The code is:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. AverageGPA. 
       ENVIRONMENT DIVISION. 
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
          SELECT STUDENT-DATA
             ASSIGN TO "C:\COBOL\CH0708.DAT"
             ORGANIZATION IS LINE SEQUENTIAL.        
          SELECT OUTPUT-FILE
             ASSIGN TO "C:\COBOL\STUDENT_GPA.DAT"
             ORGANIZATION IS LINE SEQUENTIAL. 
       DATA DIVISION. 
       FILE SECTION.
       FD  STUDENT-DATA.
       01  EMPLOYEE-RECORD.
           05  SSN-IN                PICTURE X(9).
           05  NAME-IN               PICTURE X(21). 
           05  CLASS-IN              PICTURE 9.    
           05  SCHOOL-IN             PICTURE 9.
           05  GPA-IN                PICTURE 9V99.
           05  CREDITS-IN            PICTURE 999.
       FD  OUTPUT-FILE. 
       01  OUTPUT-DATA. 
           05  SSN-OUT               PICTURE X(9).  
           05                        PICTURE X(5).
           05  NAME-OUT              PICTURE X(21).
           05  CLASS-OUT             PICTURE X(9).
           05                        PICTURE X(5).
           05  SCHOOL-OUT            PICTURE X(15).
           05                        PICTURE X(5).
           05  GPA-OUT               PICTURE 9.99.
           05                        PICTURE X(5).
           05  CREDITS-OUT           PICTURE Z99.
       WORKING-STORAGE SECTION.
       01  OUTPUT-HEADING.
           05 SSN-HEADING            PICTURE X(9) 
                                        VALUE 'SSN'.
           05                        PICTURE X(5).
           05 NAME-HEADING           PICTURE X(21) 
                                        VALUE 'STUDENT NAME'.
           05 CLASS-HEADING          PICTURE X(9) VALUE 'CLASS'.
           05                        PICTURE X(5).
           05 SCHOOL-HEADING         PICTURE X(15) VALUE 'SCHOOL'.
           05                        PICTURE X(5).
           05 GPA-HEADING            PICTURE X(3) VALUE 'GPA'.
           05                        PICTURE X(5).
           05 CREDITS-HEADING        PICTURE X(7) VALUE 'CREDITS'.
       01  GPA-COUNT                 PICTURE 9 VALUE 0.
       01  GPA-SUM                   PICTURE 9V99 VALUE 0.
       01  AVERAGE-GPA               PICTURE 9.99.
       01  AVERAGE-GPA-LINE          PICTURE X(16)
                                VALUE 'AVERAGE GPA IS '.
       01  ARE-THERE-MORE-RECORDS    PICTURE XXX VALUE 'YES'.
       PROCEDURE DIVISION.
       100-MAIN-MODULE.
           OPEN INPUT STUDENT-DATA
                OUTPUT OUTPUT-FILE
           WRITE OUTPUT-DATA FROM OUTPUT-HEADING
           PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
              READ STUDENT-DATA
                  AT END
                      MOVE 'NO' TO ARE-THERE-MORE-RECORDS
                  NOT AT END
                      PERFORM 200-WRITE-GPA
                      
                 END-READ
           END-PERFORM
           DIVIDE GPA-SUM BY GPA-COUNT GIVING AVERAGE-GPA
           WRITE OUTPUT-DATA FROM AVERAGE-GPA-LINE
           WRITE OUTPUT-DATA FROM AVERAGE-GPA
           CLOSE STUDENT-DATA
                 OUTPUT-FILE
           STOP RUN.
       200-WRITE-GPA.
           MOVE SPACES TO OUTPUT-DATA.
           MOVE SSN-IN TO SSN-OUT
           MOVE NAME-IN TO NAME-OUT
           IF CLASS-IN = 1
              MOVE 'FRESHMAN' TO CLASS-OUT
           ELSE IF CLASS-IN = 2
              MOVE 'SOPHOMORE' TO CLASS-OUT
           ELSE IF CLASS-IN = 3
              MOVE 'JUNIOR' TO CLASS-OUT
           ELSE IF CLASS-IN = 4 
              MOVE 'SENIOR' TO CLASS-OUT
           ELSE
              MOVE CLASS-IN TO CLASS-OUT
           END-IF
           IF SCHOOL-IN = 1
              MOVE 'BUSINESS' TO SCHOOL-OUT
           ELSE IF SCHOOL-IN = 2
              MOVE 'LIBERAL ARTS' TO SCHOOL-OUT
           ELSE IF SCHOOL-IN = 3
              MOVE 'ENGINEERING' TO SCHOOL-OUT
           ELSE
              MOVE 'INVALID' TO SCHOOL-OUT
           END-IF
           MOVE GPA-IN TO GPA-OUT
           ADD  GPA-IN TO GPA-SUM
           MOVE CREDITS-IN TO CREDITS-OUT
           ADD 1 TO GPA-COUNT
           WRITE OUTPUT-DATA.
           STOP RUN.

The input file is:

125997600R. HENDERSON         11379011
234789543P. MARTINSON         11250011
276888003M. JACKSON           22394020
332557267B. BRUHANSKY         21314020
235654654K. THOMPSON          23279021
336221180F. SMITH             21304019
332557845D. MIKA              33217024
377000854A. ABRAMS            31379027
399000002L. NAIRN             33375029
211311411P. BUTTRAM           41397035
122886567F. DARK              41297034
224257889S. SMITH             41397038
125654334C. HAYES             41400040
345345669J. FISHER            42200036
432234543S. JONES             43291033
488345612M. PILLION           41255034

The output given is

SSN           STUDENT NAME         CLASS         SCHOOL              GPA     CRED
432234543     S. JONES             SENIOR        ENGINEERING         2.91      33
AVERAGE GPA IS
2.91

Also, have two more questions. How come the credits header is not showing all letters? How would I do the line for average GPA? Right now it's on two lines but I want it to be on one.

Upvotes: 3

Views: 1174

Answers (1)

Bruce Martin
Bruce Martin

Reputation: 10543

  • How come the credits header is not showing all letters - the ouput record is not long enough to hold the full header, see expanded section
  • How would I do the a line for average GPA - read the whole file sum the the GPA and divide by the record number.

credits header problem

The output record is defined as


       01  OUTPUT-DATA. 
           05  SSN-OUT               PICTURE X(9).  
           05                        PICTURE X(5).
           05  NAME-OUT              PICTURE X(21).
           05  CLASS-OUT             PICTURE X(9).
           05                        PICTURE X(5).
           05  SCHOOL-OUT            PICTURE X(15).
           05                        PICTURE X(5).
           05  GPA-OUT               PICTURE 9.99.
           05                        PICTURE X(5).
           05  CREDITS-OUT           PICTURE Z99.

All you have to do is to add a filler at the end.

       01  OUTPUT-DATA. 
           05  SSN-OUT               PICTURE X(9).  
           05                        PICTURE X(5).
           05  NAME-OUT              PICTURE X(21).
           05  CLASS-OUT             PICTURE X(9).
           05                        PICTURE X(5).
           05  SCHOOL-OUT            PICTURE X(15).
           05                        PICTURE X(5).
           05  GPA-OUT               PICTURE 9.99.
           05                        PICTURE X(5).
           05  CREDITS-OUT           PICTURE Z99.
           05                        picture X(2).

personally I would

  • move the output record definition to Working storage
  • define output-data as a single picture

i.e.

       01  OUTPUT-DATA               pic x(73).
       
       Woring storage.
       
       01  report-record.       
           05  SSN-OUT               PICTURE X(9).  
           05                        PICTURE X(5).
           05  NAME-OUT              PICTURE X(21).
           05  CLASS-OUT             PICTURE X(9).
           05                        PICTURE X(5).
           05  SCHOOL-OUT            PICTURE X(15).
           05                        PICTURE X(5).
           05  GPA-OUT               PICTURE 9.99.
           05                        PICTURE X(5).
           05  CREDITS-OUT           PICTURE Z99.
           05                        picture X(2).

Other issue

I would change

          ADD 1 TO GPA-COUNT
           WRITE OUTPUT-DATA.
           STOP RUN.

to

           ADD 1 TO GPA-COUNT
           WRITE OUTPUT-DATA.
       299-exit.
           exit.

Single line output

Just create a record like

      01  Summary-line
          03               PICTURE X(16)
                                VALUE 'AVERAGE GPA IS '.
          03  everage-gpa  picture 9.99.

Only one record written

The problem is you are not ending your if statements

         IF SCHOOL-IN = 1
              MOVE 'BUSINESS' TO SCHOOL-OUT
           ELSE IF SCHOOL-IN = 2
              MOVE 'LIBERAL ARTS' TO SCHOOL-OUT
           ELSE IF SCHOOL-IN = 3
              MOVE 'ENGINEERING' TO SCHOOL-OUT
           ELSE
              MOVE 'INVALID' TO SCHOOL-OUT
           END-IF
           MOVE GPA-IN TO GPA-OUT
           ADD  GPA-IN TO GPA-SUM
           MOVE CREDITS-IN TO CREDITS-OUT
           ADD 1 TO GPA-COUNT
           WRITE OUTPUT-DATA.

The end-if ends one if i.e. it actually means

         IF SCHOOL-IN = 1
              MOVE 'BUSINESS' TO SCHOOL-OUT
         ELSE
           IF SCHOOL-IN = 2
              MOVE 'LIBERAL ARTS' TO SCHOOL-OUT
           ELSE 
              IF SCHOOL-IN = 3
                 MOVE 'ENGINEERING' TO SCHOOL-OUT
              ELSE
                 MOVE 'INVALID' TO SCHOOL-OUT
              END-IF
              MOVE GPA-IN TO GPA-OUT
              ADD  GPA-IN TO GPA-SUM
              MOVE CREDITS-IN TO CREDITS-OUT
              ADD 1 TO GPA-COUNT
              WRITE OUTPUT-DATA.

The WRITE OUTPUT-DATA. ends all the nested if's

use Evaluate

         evaluate true
         when SCHOOL-IN = 1
              MOVE 'BUSINESS' TO SCHOOL-OUT
         when SCHOOL-IN = 2
              MOVE 'LIBERAL ARTS' TO SCHOOL-OUT
         when SCHOOL-IN = 3
              MOVE 'ENGINEERING' TO SCHOOL-OUT
         when other
              MOVE 'INVALID' TO SCHOOL-OUT
         END-evaluate
         MOVE GPA-IN TO GPA-OUT
         ADD  GPA-IN TO GPA-SUM
         MOVE CREDITS-IN TO CREDITS-OUT
         ADD 1 TO GPA-COUNT
         WRITE OUTPUT-DATA.

The same applies to the other if end-if block as well

Upvotes: 5

Related Questions