user1364920
user1364920

Reputation: 21

Can't get proper file output

This is a homework assignment that involves reading in an input file, doing some processing, and printing the processed data to an output file in a neat and readable format.

The first record prints to the output file perfectly. Every record after that, it seems like when the record was read-in from the input file, it was read in with an added space; shifting the position of all of my input data and making it useless. Every line it seems like another space is being added.

I suspect that A.) Despite my best efforts I do not fully understand the READ verb and/or B.) There may be a problem with my compiler.

Any help is appreciated.

IDENTIFICATION DIVISION.
        PROGRAM-ID.            
                payroll.

ENVIRONMENT DIVISION.
        INPUT-OUTPUT SECTION.
                FILE-CONTROL.
                        SELECT payroll-in-file  ASSIGN TO 'input.txt'.
                        SELECT payroll-out-file ASSIGN TO 'output.txt'.

DATA DIVISION.
        FILE SECTION.
                FD payroll-in-file
                        LABEL RECORDS ARE STANDARD.  
                01 payroll-in-record.  
                        05 i-unused-01          PIC X.  
                        05 i-emp-num            PIC X(5).
                        05 i-dpt-num            PIC X(5).
                        05 1-unused-02          PIC X(6).
                        05 i-hrs-wkd            PIC 9(4).  
                        05 i-base-pay-rt        PIC 9(2)v99.  
                        05 i-mncpl-code         PIC X(2).

                FD payroll-out-file
                        LABEL RECORDS ARE STANDARD.
                01 payroll-out-record.
                        05 o-emp-num            PIC X(5).
                        05 FILLER               PIC XX.
                        05 o-hrs-wkd            PIC 9(5).
                        05 FILLER               PIC XX.
                        05 o-base-pay-rt        PIC 9(3).99.
                        05 FILLER               PIC XX.  
                        05 o-grs-pay            PIC 9(5).99.
                        05 FILLER               PIC XX.
                        05 o-fed-tax            PIC 9(5).99.  
                        05 FILLER               PIC XX.  
                        05 o-state-tax          PIC 9(4).99.
                        05 FILLER               PIC XX.
                        05 o-city-tax           PIC 9(4).99.
                        05 FILLER               PIC XX.
                        05 o-net-pay            PIC 9(5).99.

        WORKING-STORAGE SECTION.
                01 w-out-of-data-flag           PIC X.
                01 w-grs-pay                    PIC 99999V99.
                01 w-fed-tax                    PIC 99999V99.
                01 w-state-tax                  PIC 9999V99.
                01 w-city-tax                   PIC 9999V99.

PROCEDURE DIVISION.
        A000-main-line-routine.
                OPEN INPUT payroll-in-file
                        OUTPUT payroll-out-file.
                MOVE 'N' TO w-out-of-data-flag.
                READ payroll-in-file
                        AT END MOVE 'Y' TO w-out-of-data-flag.
                PERFORM B010-process-payroll
                        UNTIL w-out-of-data-flag = 'Y'.
                CLOSE payroll-in-file
                        payroll-out-file.
                STOP RUN.

        B010-process-payroll.
                MOVE SPACES TO payroll-out-record.
                IF i-hrs-wkd IS NOT GREATER THAN 37.5
                        MULTIPLY i-hrs-wkd BY i-base-pay-rt GIVING w-grs-pay ROUNDED
                ELSE
                        COMPUTE w-grs-pay ROUNDED =
                                        (i-base-pay-rt * 37.5) + (1.5 * (i-base-pay-rt) * (i-hrs-wkd - 37.5))
                END-IF.
                MULTIPLY w-grs-pay BY 0.25
                        GIVING w-fed-tax ROUNDED.
                MULTIPLY w-grs-pay BY 0.05
                        GIVING w-state-tax ROUNDED.  
                IF              i-mncpl-code = 03
                        MULTIPLY w-grs-pay BY 0.015 GIVING w-city-tax ROUNDED
                ELSE IF         i-mncpl-code = 07
                        MULTIPLY w-grs-pay BY 0.02 GIVING w-city-tax ROUNDED
                ELSE IF         i-mncpl-code = 15
                        MULTIPLY w-grs-pay BY 0.0525 GIVING w-city-tax ROUNDED
                ELSE IF         i-mncpl-code = 23
                        MULTIPLY w-grs-pay BY 0.0375 GIVING w-city-tax ROUNDED
                ELSE IF         i-mncpl-code = 77
                        MULTIPLY w-grs-pay BY 0.025 GIVING w-city-tax ROUNDED

                    END-IF.

input file:

 AA34511ASD      0037115003
 AA45611WER      0055120007
 BB98722TYU      0025075015
 BB15933HUJ      0080200023
 FF35799CGB      0040145077

(each line begins with 1 space, which corresponds to "i-unused-01" in the code)

output file (so far):

AA345  00037  011.50  00425.50  00106.38  0021.28  0006.38  00291.46 AA45  0 005  051.20  00425.50  00106.38  0021.28  0006.38  00291.46
 BB9  0  00  025.07  00425.50  00106.38  0021.28  0006.38  00291.465
 BB  0   0  008.02  00425.50  00106.38  0021.28  0006.38  00291.4623
 F  0      000.40  10673.10  02668.28  0533.66  0006.38  07464.78

^it prints just like that!

Using OpenCOBOL compiler in Linux.

Upvotes: 2

Views: 3257

Answers (3)

cobp
cobp

Reputation: 772

This might be due to the Mingw Open COBOL version you use. As it is documented here

ORGANIZATION IS LINE SEQUENTIAL These are files with the simplest of all internal structures. Their contents are structured simply as a series of data records, each terminated by a special end-of-record delimiter character. An ASCII line-feed character (hexadecimal 0A) is the end-of-record delimiter character used by any UNIX or pseudo-UNIX (MinGW, Cygwin, MacOS) OpenCOBOL build. A truly native Windows build would use a carriage-return, line-feed (hexadecimal 0D0A) sequence.

Upvotes: 1

Bruce Martin
Bruce Martin

Reputation: 10543

As colemanj said, you need to change the output file to line sequential

But you also need to change the input file / input file definition. The 2 options are 1) change the Input file to line sequential (bring the definition into line with the file 2) Remove carraige returns from the input file to (all on one line):

AA34511ASD      0037115003 AA45611WER      0055120007 BB98722TYU      0025075015 BB15933HUJ      0080200023 FF35799CGB      0040145077

The current input file definition indicates there is no carriage returns in the file.

--------------------------------------------------

Upvotes: 1

colemanj
colemanj

Reputation: 499

I didn't look at the code in detail, but two things are worth looking at.

Firstly, the output file should probably be "line sequential", as this will insert a delimiter (carraige return/newline), which means that the output file will print as one record per line.

Also, there may be a difference of one character, between the number of characters in your input record, i.e. your actual data, and the the number of characters defined in your input FD.

Upvotes: 2

Related Questions