I'm writing a program that converts international account numbers into the standard IBAN structure.
I have so far managed to write a program that checks the input for validity, strings said input together without embedded spaces or zeroes, converts the alphabetic characters into numbers corresponding with their position in the alphabet and creates a string with those numbers.
Now all I have to do is calculate the Mod 97 on the number and subtract the remainder from 98. If the result is a single digit then I have to insert a leading zero.
What I have right now is this:
Note: I used a pointer to get the numbers into the string before this step, so the pointer (after subtracting 1 from it) contains the total length of the string.
WORKING STORAGE SECTION.
01 WORK-FIELDS.
05 HELP FIELDS.
10 POINTER PIC S9(04) COMP.
10 DIGITIZED-STRING PIC X(66).
10 STRING-FOR-CALCULATION PIC 9(31).
05 IBAN.
10 COUNTRY-CODE PIC X(02).
10 CHECK-DIGITS PIC 9(02).
10 BANK-CODE PIC X(10).
10 BRANCH-CODE PIC X(10).
10 ACCOUNT-NUMBER PIC X(28).
10 OUTPUT-IBAN PIC X(34).
PROCEDURE DIVISION.
SUBTRACT 1 FROM POINTER
STRING DIGITIZED-STRING(1:POINTER)
DELIMITED BY SIZE
INTO STRING-FOR-CALCULATION
EVALUATE TRUE
WHEN POINTER < 32
COMPUTE IBAN-CHECK-DIGITS = 98
- FUNCTION MOD(STRING-FOR-CALCULATION, 97)
END-EVALUATE
.
I have 2 problems:
Even with the ARITH(EXTEND) option in the compiler, COBOL can't handle numeric fields larger than 31 digits, which my program will be dealing with. There is a reason my DIGITIZED-STRING field has a length of 66. When I compile my program, I get this message:
"Truncation of high-order digit positions may occur due to precision
of intermediate results exceeding 31 digits."
When the length of my STRING-FOR-CALCULATION field (as seen above) is longer than the content I move to it from the DIGITIZED-STRING, the gap is filled by trailing zeroes. This affects the calculation. When I manually adjust the STRING-FOR-CALCULATION field to be exactly as long as the content of the DIGITIZED-STRING, the calculation goes well.
I just don't know how to make sure it works when I'm dealing with shorter and longer numbers, which I have to split up in parts.
Additional info:
I'm using this document as a guide: www.bpfi.ie/wp-content/uploads/2014/10/MOD-97-Final-May-2013.pdf
But I have no clue how to do this in COBOL.
Also, for those who have kindly read and answered my previous questions, the reason these fields aren't National is because my project manager changed his mind about it. Now all I have to do is use a MOVE FUNCTION NATIONAL-OF to move the IBAN-OUTPUT field to the copybook.
UPDATE
I'm using a COBOL/390 COMPILER.
Below is the code I ended up using:
WORKING-STORAGE SECTION.
01 DIGITIZED-STRING PIC X(66).
01 POINTER PIC S9(04) COMP.
01 TEST-FIELDS.
05 VERY-LONG-NUMBER.
10 VLN-FIRST-PART PIC 9(11).
10 VLN-SECOND-PART PIC 9(11).
10 VLN-THIRD-PART PIC 9(11).
10 VLN-FOURTH-PART PIC 9(11).
10 VLN-FIFTH-PART PIC 9(11).
10 VLN-SIXTH-PART PIC 9(11).
05 EXPANDED-DIVIDEND PIC 9(13).
05 FILLER
REDEFINES EXPANDED-DIVIDEND.
10 ED-REMAINDER PIC 99.
10 ED-PART PIC 9(11).
05 IRRELEVANT-ANSWER PIC 9(12).
PROCEDURE DIVISION.
MOVE SPACES TO TEST-FIELDS
MOVE ZEROES TO TEST-FLDS
MOVE DIGITIZED-STRING(1:POINTER)
TO VERY-LONG-NUMBER(66 - POINTER + 1:POINTER)
MOVE ZERO TO ED-REMAINDER
MOVE VLN-FIRST-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-SECOND-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-THIRD-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-FOURTH-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-FIFTH-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-SIXTH-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY 97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
COMPUTE CHECK-DIGITS = 98
- ED-REMAINDER
.
You do it like "long division".
1234 divided by 97 =
123 divided by 97, which gives x (doesn't matter for you) remainder 26
264 divided by 97, gives x, remainder 70
70 is the mod 97 of 1234.
Here's an example program:
ID DIVISION.
PROGRAM-ID. STAB22.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 VERY-LONG-NUMBER PIC 9(8).
01 FILLER
REDEFINES VERY-LONG-NUMBER.
05 VLN-FIRST-PART PIC 9(4).
05 VLN-SECOND-PART PIC 9(4).
01 EXPANDED-DIVIDEND PIC 9(6).
01 FILLER
REDEFINES EXPANDED-DIVIDEND.
05 ED-REMAINDER PIC 99.
05 ED-PART PIC 9(4).
01 IRRELEVANT-ANSWER PIC 9(5).
01 VALUE-FOR-MOD-97 PACKED-DECIMAL PIC 99 VALUE 97.
PROCEDURE DIVISION.
MOVE 1234 TO VERY-LONG-NUMBER
MOVE ZERO TO ED-REMAINDER
MOVE VLN-FIRST-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY VALUE-FOR-MOD-97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-SECOND-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY VALUE-FOR-MOD-97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
DISPLAY ED-REMAINDER
MOVE 12345678 TO VERY-LONG-NUMBER
MOVE ZERO TO ED-REMAINDER
MOVE VLN-FIRST-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY VALUE-FOR-MOD-97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
MOVE VLN-SECOND-PART TO ED-PART
DIVIDE EXPANDED-DIVIDEND BY VALUE-FOR-MOD-97
GIVING IRRELEVANT-ANSWER
REMAINDER ED-REMAINDER
DISPLAY ED-REMAINDER
GOBACK
.
That gives 70 and 03 as the results.
You extrapolate. I'd suggest you have six parts of 11 digits, making a 13-digit dividend each time. That will be more efficient than trying to use longer numbers with less code, using compiler option ARITH(EXTEND).
Related
I have Alphanumeric value = '86' and its length is defined as PIC x(02). I need to convert it into hex x'86' and its length is defined as PIC 9(01) comp-3.
example:
01 WS-ALPHANUMERIC PIC X(02) VALUE '86'.
01 WS-HEX PIC 9(01) COMP-3.
PROCEDURE DIVISION.
MOVE WS-ALPHANUMERIC TO WS-HEX.
DISPLAY WS-HEX.
STOP RUN
I am getting x'FF' in my spool. But I am expecting x'86'.
Why your code doesn't produce the output you're expecting
It is just guessing from my part for on my computer it doesn't work that way.
When you MOVE from WS-ALPHANUMERIC to WS-HEX, the string '86' in transformed in the decimal number 86.
However WS-HEX is only one byte long and in the COMP-3 format. This format can only store one decimal digit and the sign.
I'm guessing that on your environment when you move a bigger number than the capacity to a COMP-3 it take the biggest hexadecimal value it can hold : 0xF.
In my environment it would just take the digit 6 of the number 86.
So when you display, it is converted to a usage display so you have your firt 0xF for the usage formatting and then your 0xF for the "overflow" I guess.
On my computer you would just get a 0xF6.
A solution to produce the expected output
Disclaimer : I originally thought that your input would only be decimals, like '87596', '12' or '88'. This solution does not work for hexadecimals input like 'F1' ou '99F'. I built more complete solutions below in items 3 and 4 by improving this one
The solution I propose can take up to 16 digits in the input string if your system is 64bit because it takes 4 bits to store a hexadecimal digit.
Therefore if you want a larger input you'll have to use more than one result variable.
If you want to have it in only one byte, you just have to make Result a PIC 9(1) instead of PIC 9(18)
IDENTIFICATION DIVISION.
PROGRAM-ID. CNVRSN.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RawInput PIC X(02) VALUE '86'.
01 FormattedInput PIC 9(16).
01 FractionedInput REDEFINES FormattedInput
05 Digit PIC 9 OCCURS 16.
01 Shifting PIC 9(18) COMP-5 VALUE 1.
01 I PIC 99 COMP-5.
01 Result PIC 9(18) COMP-5 VALUE 0.
01 DisplayResult REDEFINES Result PIC X(8).
PROCEDURE DIVISION.
MOVE RawInput TO FormattedInput.
PERFORM VARYING I FROM LENGTH OF FractionedInput
BY -1 UNTIL I < 1
COMPUTE Result = Result + Digit(I)*Shifting
MULTIPLY 16 BY Shifting
END-PERFORM
DISPLAY 'DisplayResult : ' DisplayResult
.
END PROGRAM CNVRSN.
The code works by transforming the string in a number of USAGE DISPLAY with the first move MOVE RawInput to FormattedInput.
We use the fact that each digit has the same format as a number of just one digit (PIC 9). This allows us to split the number in elements of an array with the REDEFINES of FomattedInput inFractionedInput
As you can see I traverse the array from the end to start because the least significant byte is at the end of the array (highest address in memory), not at the start (lowest address in memory).
Then we place each the hexadecimal digit in the correct place by shifting them to the left by 2^4 (a nibble, which is the size of a hexadecimal digit) as many times as required.
A solution that accepts the full hexadecimal input range (memory intensive)
Here is the code :
IDENTIFICATION DIVISION.
PROGRAM-ID. CNVRSN.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RawInput PIC X(02) VALUE '86'.
01 FormattedInput PIC X(16).
01 FractionedInput REDEFINES FormattedInput
05 Digit PIC X OCCURS 16.
01 I PIC 99 COMP-5.
01 ConversionTableInitializer.
05 FILLER PIC X(192).
05 TenToFifteen PIC X(06) VALUE X'0A0B0C0D0E0F'.
05 FILLER PIC X(41).
05 ZeroToNine PIC X(10) VALUE X'00010203040506070809'.
01 ConversionTable Redefines ConversionTableInitializer.
05 DigitConverter PIC 99 COMP-5 OCCURS 249.
01 Result PIC 9(18) COMP-5 VALUE 0.
01 DisplayResult REDEFINES Result PIC X(8).
PROCEDURE DIVISION.
MOVE RawInput TO FormattedInput.
PERFORM VARYING I FROM 1 BY 1
UNTIL I > LENGTH OF FractionedInput
OR Digit(I) = SPACE
COMPUTE Result = Result*16 + DigitConverter(Digit(I))
END-PERFORM
DISPLAY 'DisplayResult : ' DisplayResult
.
END PROGRAM CNVRSN.
The idea in this solution is to convert each character (0,1...,E,F) to its value in hexadecimal. For this we use the value of their encoding as a string (0xC1 = 0d193 for A for instance) as the index of an array.
This is very wasteful of memory for we allocate 249 bytes to store only 16 nibbles of information. However to access the element of an array is a very fast operation: We are trading the memory usage for cpu efficiency.
The underlying idea in this solution is a hashtable. This solution is nothing but a very primitive hash table where the hash function is the identity function (A very, very bad hash function).
Another solution that accepts the full hexadecimal input range (CPU intensive)
Disclaimer : This solution was proposed by #Jim Castro in the comments.
IDENTIFICATION DIVISION.
PROGRAM-ID. CNVRSN.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RawInput PIC X(02) VALUE '86'.
01 FormattedInput PIC X(16).
01 FractionedInput REDEFINES FormattedInput
05 Digit PIC 9 OCCURS 16.
01 ConversionString PIC X(16) VALUE '0123456789ABCDEF'.
01 ConversionTable REDEFINES ConversionString.
05 ConversionEntry OCCURS 16 INDEXED BY Idx.
10 HexDigit PIC X.
01 I PIC 99 COMP-5.
01 Result PIC 9(18) COMP-5 VALUE 0.
01 DisplayResult REDEFINES Result PIC X(8).
PROCEDURE DIVISION.
MOVE RawInput TO FormattedInput.
PERFORM VARYING I FROM 1 BY 1
UNTIL I > LENGTH OF FractionedInput
OR Digit(I) = SPACE
SET Idx To 1
SEARCH ConversionEntry
WHEN HexDigit(Idx) = Digit(I)
COMPUTE Result = Result*16 + Idx - 1
END-SEARCH
END-PERFORM
DISPLAY 'DisplayResult : ' DisplayResult
.
END PROGRAM CNVRSN.
Here the idea is still to convert the string digit to its value. However instead of trading off memory efficiency for cpu efficiency we are doing the converse.
We have a ConversionTable where each character string is located at the index that convey the value they are supposed to convey + 1 (because in COBOL arrays are 0 based). We juste have to find the matching character and then the index of the matching character is equal to the value in hexadecimal.
Conclusion
There are several ways to do what you want. The fundamental idea is to :
Implement a way to convert a character to its hexadecimal value
Traverse all the characters of the input string and use their position to give them the correct weight.
Your solution will always be a trade off between memory efficiency and time efficiency. Sometimes you want to preserve your memory, sometimes you want the execution to be real fast. Sometimes you wand to find a middle ground.
To go in this direction we could improve the solution of the item 3 in terms of memory at the expense of the cpu. This would be a compromise between item 3 and 4.
To do it we could use a modulo operation to restrict the number of possibilities to store. Going this way would mean implementing a real hashtable.
I don't have access to an IBM mainframe to test this code.
When I run the code on an online GnuCOBOL v2.2 compiler, I'm stuck with ASCII instead of EBCDIC.
I've posted the code. Here's what you have to do.
Make sure the top byte comes out to 8 and the bottom byte comes out to 6. You're converting the EBCDIC values to intager values. Values A - F hex will have different EBCDIC values than values 0 - 9.
Make sure the multiply and add are correct
Here's the code. You'll have to fix it to work with EBCDIC.
IDENTIFICATION DIVISION.
PROGRAM-ID. CONVERSION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-ALPHANUMERIC PIC X(02) VALUE '86'.
01 WS-WORK-FIELDS.
05 WS-INPUT.
10 WS-ONE.
15 WS-TOP-BYTE PIC 99 COMP.
10 WS-TWO.
15 WS-BOTTOM-BYTE PIC 99 COMP.
05 WS-ACCUMULATOR PIC S9(4) COMP.
05 FILLER REDEFINES WS-ACCUMULATOR.
10 FILLER PIC X.
10 WS-HEX PIC X.
PROCEDURE DIVISION.
0000-BEGIN.
MOVE WS-ALPHANUMERIC TO WS-INPUT
DISPLAY WS-INPUT
COMPUTE WS-TOP-BYTE = WS-TOP-BYTE - 183
COMPUTE WS-BOTTOM-BYTE = WS-BOTTOM-BYTE - 183
IF WS-TOP-BYTE NOT LESS THAN 16
COMPUTE WS-TOP-BYTE = WS-TOP-BYTE - 57
END-IF
IF WS-BOTTOM-BYTE NOT LESS THAN 16
COMPUTE WS-BOTTOM-BYTE = WS-BOTTOM-BYTE - 57
END-IF
DISPLAY WS-TOP-BYTE
DISPLAY WS-BOTTOM-BYTE
MOVE WS-TOP-BYTE TO WS-ACCUMULATOR
MULTIPLY 16 BY WS-ACUMULATOR
ADD WS-BOTTOM-BYTE TO WS-ACCUMULATOR
DISPLAY WS-ACCUMULATOR
DISPLAY WS-HEX
GOBACK.
I was working on a brute-force implementation of this RosettaCode challenge. I wanted to be able to handle numbers bigger than USAGE BINARY-DOUBLE so I wrote a dead simple bignum routine for adding.
If I want to limit myself to a certain number of iterations and that number is greater than 9(18) then that's tricky. So I hit upon the idea of an 88 on a particular element of the array, thus the code below.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
03 FILLER REDEFINES DIGITS1.
05 FILLER pic 9999999999.
05 FILLER pic 999999999.
05 filler pic 9.
88 EOR value 1.
05 filler pic 9999999999.
05 filler pic 9999999999.
So I'm still wondering if this is the only way to go or is there some other way of handling when I get to 10^20.
This is the full "solution". It's a mess but it almost working.
identification division.
program-id. Program1.
data division.
working-storage section.
01 COUNTER.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
03 FILLER REDEFINES DIGITS1.
05 filler pic 9999999999.
05 FILLER pic 9999999999.
05 filler pic 9999999999.
05 filler pic 999.
05 filler pic 9.
88 EOR value 1.
05 filler pic 999999.
01 INCREMENTOR.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
01 ACCUMULATOR.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
01 IN-NUMBER usage binary-double unsigned.
01 I USAGE BINARY-DOUBLE UNSIGNED.
01 N USAGE BINARY-DOUBLE UNSIGNED.
01 THREE-COUNTER USAGE BINARY-CHAR value 1.
88 IS-THREE VALUE 3.
01 FIVE-COUNTER USAGE BINARY-CHAR value 1.
88 IS-FIVE VALUE 5.
01 ANSWER pic x(40).
procedure division.
initialize COUNTER ACCUMULATOR incrementor.
10-MAIN-PROCEDURE.
move 1 to IN-NUMBER.
call "MOVENUMTOBIGNUM" using by content in-number
by reference incrementor.
move 1 to IN-NUMBER.
call "MOVENUMTOBIGNUM" using by content in-number
by reference counter.
PERFORM 20-INNER-LOOP WITH TEST AFTER UNTIL eor.
move ACCUMULATOR to ANSWER.
inspect answer REPLACING LEADING '0'
by space.
DISPLAY answer.
STOP RUN.
20-INNER-LOOP.
IF IS-THREE OR IS-FIVE
call "ADDBIGNUMS" using by content counter
by reference accumulator
IF IS-THREE
MOVE 1 TO THREE-COUNTER
ELSE
ADD 1 TO THREE-COUNTER
END-IF
IF IS-FIVE
MOVE 1 TO FIVE-COUNTER
ELSE
ADD 1 TO FIVE-COUNTER
END-IF
ELSE
ADD 1 TO FIVE-COUNTER END-ADD
ADD 1 TO THREE-COUNTER END-ADD
END-IF.
call "ADDBIGNUMS" using by content INCREMENTOR
by reference counter.
EXIT.
end program Program1.
identification division.
PROGRAM-ID. MOVENUMTOBIGNUM.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 num-MOD usage binary-CHAR.
01 num-DIV usage binary-DOUBLE unsigned.
01 IN-COUNTER usage binary-char.
LINKAGE SECTION.
01 num usage binary-double.
01 BIGNUM.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
PROCEDURE DIVISION USING NUM BIGNUM.
10-MOVE.
move 40 to IN-COUNTER.
perform until num = 0
divide num by 10
giving num-DIV
REMAINDER num-MOD
end-divide
move num-MOD to DIGITS1 of BIGNUM(IN-COUNTER)
move NUM-DIV to NUM
subtract 1 from IN-COUNTER end-subtract
END-PERFORM.
GOBACK.
END PROGRAM MOVENUMTOBIGNUM.
*Add Bignum to Bignum, modifying second Bignum in situ
identification division.
program-id. ADDBIGNUMS.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 IN-COUNTER usage binary-char.
01 ADD-FLAG pic 9.
88 STILL-ADDING VALUE 0.
88 DONE-ADDING VALUE 9.
01 CARRIER usage binary-char.
01 REGISTER-A usage binary-char.
LINKAGE SECTION.
01 BIGNUM1.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
01 BIGNUM2.
03 DIGITS1 OCCURS 40 TIMES PIC 9.
PROCEDURE DIVISION USING BIGNUM1 BIGNUM2.
10-ADD-WITH-CARRY.
move zero to CARRIER.
move 40 to IN-COUNTER.
move zero to ADD-FLAG.
perform until DONE-ADDING
add DIGITS1 of BIGNUM1(IN-COUNTER)
DIGITS1 of BIGNUM2(IN-COUNTER)
CARRIER GIVING REGISTER-A
END-ADD
move zero to CARRIER
if REGISTER-A > 9
divide REGISTER-A by 10
giving CARRIER
remainder REGISTER-A
end-divide
else
if REGISTER-A = zero
move 9 to ADD-FLAG
END-IF
end-if
if STILL-ADDING
move REGISTER-A to DIGITS1 of BIGNUM2(IN-COUNTER)
subtract 1 from IN-COUNTER end-subtract
end-if
END-PERFORM.
goback.
END PROGRAM ADDBIGNUMS.
Although you already don't seem to like the structure, I'll stick to it. It will work with your structure as well. No need for the REDEFINES or those other FILLERs.
05 FILLER.
10 FILLER OCCURS 40 TIMES.
15 DIGITS1 PIC 9.
88 DIGITS1-MEANS-SOMETHING
VALUE 1.
01 NAME-THAT-REVEALS-INFORMATION BINARY PIC 9(4).
IF DIGITS1-MEANS-SOMETHING
( NAME-THAT-REVEALS-INFORMATION )
do some stuff
END-IF
I've changed you PIC 9 to PIC X. Unless you are doing calculations, there is never a need to define a field as 9 for "numeric". If a field happens to contain numbers, or happens to have the word number, or something like that in its name, don't be tricked into defining it as a number.
Extra (generated) code ensues and it carries the meaning "numeric stuff will be done with this", so misleads. If/when you need to do a "numeric edit" for output, there's always the REDEFINES at that point. Doesn't have to have these other costs to make that happen.
I've now reverted to your PIC 9, as, after your edit, I can see you are using it for calculations :-)
I have an error code 18 in COBOL when I'm trying to write the output to a file. I'm using Micro Focus VS 2012. I have tried everything but it seem doesn't print the output correctly at this time.
...
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT GRADE-FILE ASSIGN TO 'Grades.txt'.
SELECT PRINT-FILE ASSIGN TO 'Output.txt'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD GRADE-FILE
LABEL RECORDS ARE STANDARD.
01 GRADE-RECORD.
05 I-STUDENT PIC X(14).
05 I-GRADE1 PIC 999.
05 I-GRADE2 PIC 999.
05 I-GRADE3 PIC 999.
05 I-GRADE4 PIC 999.
05 I-GRADE5 PIC 999.
05 I-GRADE6 PIC 999.
FD PRINT-FILE
LABEL RECORDS ARE STANDARD.
01 PRINT-RECORD PIC X(80).
WORKING-STORAGE SECTION.
01 PROGRAM-VARIABLES.
05 W-AVERAGE PIC 999V99.
05 W-EOF-FLAG PIC X VALUE 'N'.
01 PAGE-TITLE.
05 PIC X(46) VALUE
' S I X W E E K G R A D E R E P O R T'.
01 HEADING-LINE1.
05 PIC X(51) VALUE
' Student T e s t S c o r e s Average'.
01 HEADING-LINE2.
05 PIC X(51) VALUE
'--------------------------------------------------'.
01 DETAIL-LINE.
05 PIC X VALUE SPACE.
05 O-STUDENT PIC X(14).
05 PIC X VALUE SPACE.
05 O-GRADE1 PIC ZZ9.
05 PIC X VALUE SPACE.
05 O-GRADE2 PIC ZZ9.
05 PIC X VALUE SPACE.
05 O-GRADE3 PIC ZZ9.
05 PIC X VALUE SPACE.
05 O-GRADE4 PIC ZZ9.
05 PIC X VALUE SPACE.
05 O-GRADE5 PIC ZZ9.
05 PIC X VALUE SPACE.
05 O-GRADE6 PIC ZZ9.
05 PIC X(4) VALUE SPACE.
05 O-AVERAGE PIC ZZ9.99.
PROCEDURE DIVISION.
10-MAINLINE.
OPEN INPUT GRADE-FILE
OUTPUT PRINT-FILE
PERFORM 20-PRINT-HEADINGS
PERFORM 30-PROCESS-LOOP
CLOSE GRADE-FILE
PRINT-FILE
STOP RUN.
20-PRINT-HEADINGS.
MOVE PAGE-TITLE TO PRINT-RECORD
WRITE PRINT-RECORD AFTER ADVANCING 1 LINE
MOVE HEADING-LINE1 TO PRINT-RECORD
WRITE PRINT-RECORD AFTER ADVANCING 3 LINES
MOVE HEADING-LINE2 TO PRINT-RECORD
WRITE PRINT-RECORD AFTER ADVANCING 1 LINE.
30-PROCESS-LOOP.
* PERFORM 40-READ-RECORD
READ GRADE-FILE
PERFORM UNTIL W-EOF-FLAG = 'Y'
PERFORM 50-COMPUTE-GRADE-AVERAGE
PERFORM 60-PRINT-DETAIL-LINE
READ GRADE-FILE
* PERFORM 40-READ-RECORD
END-PERFORM.
*40-READ-RECORD.
* READ GRADE-FILE
* AT END MOVE 'Y' TO W-EOF-FLAG.
50-COMPUTE-GRADE-AVERAGE.
COMPUTE W-AVERAGE ROUNDED = (I-GRADE1 + I-GRADE2 + I-GRADE3 + I-GRADE4 + I-GRADE5 + I-GRADE6 ) / 6.
60-PRINT-DETAIL-LINE.
MOVE SPACES TO DETAIL-LINE
MOVE I-STUDENT TO O-STUDENT
MOVE I-GRADE1 TO O-GRADE1
MOVE I-GRADE2 TO O-GRADE2
MOVE I-GRADE3 TO O-GRADE3
MOVE I-GRADE4 TO O-GRADE4
MOVE I-GRADE5 TO O-GRADE5
MOVE I-GRADE6 TO O-GRADE6
MOVE W-AVERAGE TO O-AVERAGE
WRITE PRINT-RECORD FROM DETAIL-LINE AFTER ADVANCING 1 LINE.
end program "GradeReport.Program1"
S I X W E E K G R A D E R E P O R T
Student T e s t S c o r e s Average
--------------------------------------------------
KellyAntonetz0 700 500 980 800 650 852 747.00
obertCain09708 207 907 309 406 2;1 25> 400.67
Dehaven0810870 940 850 930 892 122 981 785.83
rmon0760770800 810 750 92; 142 9>1 <1> 816.33
g0990930890830 940 901 =1> 41= ?82 65 872.50
06707108408809 6=9 ;52 565 <<0 900 870 924.33
78052076089Woo 493 9>4 520 760 760 830 734.50
Something prior to your COBOL program has pickled your file by removing all the spaces and shuffling the data to the left.
Your first student shows as KellyAntonetz but likely should be Kelly Antonetz. Since only one space was removed, the grade data has moved only one place to the left, so the numbers are still recognizable and although the average is a factor of 10 out, it is approximately correct.
It is not actually correct (except for the power of 10) because of that 2 following the 85. Where did that 2 come from?
It came from the next record, where the first-name should be Robert but you show as obertCain09708. The ASCII code for the letter R is X'82'. When treated as a number by COBOL the 8 will be ignored (or will cause a crash when in the trailing byte of a number). Your compiler doesn't cause the code to crash, but does treat the R as the number 2.
obertCain is only 9 bytes out of the 14 you have for the name. The five spaces/blanks which have been "lost" this time cause the numerics to be pulled-left by five bytes. From that point onward, explaining how the output you show fits the presumed input becomes an academic exercise only.
Further support is a reference for what would be a FILE STATUS code of 18 from a Micro Focus compiler, here: http://www.simotime.com/vsmfsk01.htm
Which says, for 18:
Read part record error: EOF before EOR or file open in wrong mode
(Micro Focus).
Your final record would "finish" before expected, with end-of-file being detected before 32 bytes have been read.
Note that the error is on your input file, not your output file.
Losing the spaces in that way can be done in many ways, so I can't guess what you are doing to the file before it gets to the COBOL program, but neither COBOL itself nor your code is doing that.
Take note of Emmad Kareem's comments. Use the FILE STATUS. Check the file-status field (define one per file) after each IO, so that you know when a problem occurs, and what the problem is.
Testing the file-status field for 10 on a file you are reading sequentially gives cleaner code than the AT END on the READ.
Note also that if your program had not crashed there, it would either loop infinitely or crash shortly afterwards. Probably in trying to fix your problem, you have commented-out your use of the "read paragraph" and in that paragraph is the only place you are setting end-of-file.
If you use the file-status instead of AT END, you don't need to define a flag/switch you can use an 88 on the file-status field and have the COBOL run-time set it for you directly, without you having to code it.
Just a couple of points about your DETAIL-LINE.
There is no need to MOVE SPACE to it, as you MOVE to each named field, and the (un-named) FILLERs have VALUE SPACE.
You don't necessarily need the (un-named) FILLERS. Try this:
01 DETAIL-LINE.
05 O-STUDENT PIC BX(14).
05 O-GRADE1 PIC ZZZ9.
05 O-GRADE2 PIC ZZZ9.
05 O-GRADE3 PIC ZZZ9.
05 O-GRADE4 PIC ZZZ9.
05 O-GRADE5 PIC ZZZ9.
05 O-GRADE6 PIC ZZZ9.
05 O-AVERAGE PIC Z(6)9.99.
If you work with COBOL, you may see this type of thing, so it is good to know. With massive amounts of output there is probably a small performance penalty. You may find it more convenient for "lining-up" output to headings.
Ah. Putting together you non-use of LINE SEQUENTIAL for your input file, I predict you have a "script" running some time before the COBOL program which is supposed to remove the record-terminators (whatever those are on your OS) at the end of each logical record, but that you have accidentally removed all whitespace from all positions of your record instead.
With LINE SEQUENTIAL you can have records of fixed-length which also happen to be "terminated". Unless the exercise specifically includes the removal of the record terminators, just use LINE SEQUENTIAL.
If you are supposed to remove the terminators, don't do so for whitespace which covers too much (be specific) and also "anchor" the change to the end of the record.
I'm working on an assignment for my class, and I'm having an issue with getting a percentage to show the proper value for my COBOL Lab.
My issue is with PERCENT-DISCOUNT / WS-PERCENT-WITH-DISCOUNT (at least, I believe it is).
When the program is run, I get the result 50.0. The result I should be getting (assuming I did the math correctly by hand) is 55.6. I'm not too sure where I'm going wrong.
Here is the code that I currently have written for the program.
*
IDENTIFICATION DIVISION.
PROGRAM-ID. LAB2.
AUTHOR. XXXXXXX XXXXXXXXXXX.
*
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT IPT-FILE ASSIGN TO 'LAB2.DAT'
ORGANIZATION IS LINE SEQUENTIAL.
SELECT PRT-FILE ASSIGN TO 'LAB2_OUTPUT.DAT'
ORGANIZATION IS LINE SEQUENTIAL.
*
DATA DIVISION.
FILE SECTION.
*
FD IPT-FILE
RECORD CONTAINS 80 CHARACTERS
RECORDING MODE IS F
DATA RECORD IS INPUT-RECORD.
01 IPT-RECORD.
05 IPT-INV-NUMBER PIC 9(04).
05 IPT-INV-QUANTITY PIC 9(03).
05 IPT-INV-DESCRIPTION PIC X(13).
05 IPT-INV-UNITPRICE PIC 9999V99.
05 IPT-INV-PROD-CLASS PIC 9(01).
*
FD PRT-FILE
RECORD CONTAINS 132 CHARACTERS
RECORDING MODE IS F
DATA RECORD IS PRT-LINE.
01 PRT-LINE.
05 FILLER PIC X(04).
05 PRT-INV-NUMBER PIC 9(04).
05 FILLER PIC X(02).
05 PRT-EXTENDED-PRICE PIC Z,ZZZ,ZZ9.99.
05 FILLER PIC X(04).
05 PRT-DISCOUNT-AMOUNT PIC ZZZ,ZZ9.99.
05 FILLER PIC X(03).
05 PRT-NET-PRICE PIC Z,ZZZ,ZZ9.99.
05 FILLER PIC X(10).
05 PRT-PRODUCT-CLASS PIC 9.
05 FILLER PIC X(07).
05 PRT-TRANS-PERCENT PIC Z9.9.
05 FILLER PIC X(05).
05 PRT-TRANS-CHARGE PIC ZZZ,ZZ9.99.
*
WORKING-STORAGE SECTION.
*
01 EOF-SWITCH PIC X VALUE 'N'.
*
01 WS-EXTENDED-COST PIC 9(07)V99.
01 WS-DISCOUNT-AMOUNT PIC 9(06)V99.
01 WS-NET-COST PIC 9(07)V99.
01 WS-TRANS-PERCENT PIC ZZ9V9.
01 WS-TRANS-COST PIC 9(06)V99.
*
01 WS-TOTAL-EXTENDED-COST PIC 9(09)V99 VALUE ZERO.
01 WS-TOTAL-NET-COST PIC 9(08)V99 VALUE ZERO.
01 WS-TOTAL-TRANS-COST PIC 9(08)V99 VALUE ZERO.
01 WS-TOTAL-WITH-DISCOUNT PIC 99V9 VALUE ZERO.
01 WS-TOTAL-ITEMS PIC 99V9 VALUE ZERO.
01 WS-PERCENT-WITH-DISCOUNT PIC 99V9.
01 WS-TOTAL-NO-DISCOUNT PIC 99V9 VALUE ZERO.
*
01 HEADING-NAME.
05 MY-NAME PIC X(20) VALUE
'XXXXX XXXXXXX, LAB 2'.
01 HEADING-COLUMN-1.
05 FILLER PIC X(05) VALUE SPACES.
05 COLUMN-1-INV-NUM PIC X(03) VALUE 'INV'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-EXT-PRC PIC X(08) VALUE 'EXTENDED'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-DISC-AMT PIC X(08) VALUE 'DISCOUNT'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-NET-PRC PIC X(09) VALUE 'NET PRICE'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-CLASS PIC X(05) VALUE 'CLASS'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-TRANS-P PIC X(05) VALUE 'TRANS'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-1-TRANS-C PIC X(14) VALUE 'TRANSPORTATION'.
01 HEADING-COLUMN-2.
05 FILLER PIC X(05) VALUE SPACES.
05 COLUMN-2-INV-NUM PIC X(03) VALUE 'NUM'.
05 FILLER PIC X(09) VALUE SPACES.
05 COLUMN-2-EXT-PRC PIC X(08) VALUE 'PRICE'.
05 FILLER PIC X(05) VALUE SPACES.
05 COLUMN-2-DISC-AMT PIC X(08) VALUE 'AMOUNT'.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-2-NET-PRC PIC X(09) VALUE SPACES.
05 FILLER PIC X(06) VALUE SPACES.
05 COLUMN-2-CLASS PIC X(05) VALUE SPACES.
05 FILLER PIC X(08) VALUE SPACES.
05 COLUMN-2-TRANS-P PIC X(05) VALUE '%'.
05 FILLER PIC X(05) VALUE SPACES.
05 COLUMN-2-TRANS-C PIC X(14) VALUE 'CHARGE'.
01 BLANK-LINE.
05 BLANK-SPACE PIC X VALUE SPACES.
01 TOTAL-FOOTER.
05 FILLER PIC X(07) VALUE SPACES.
05 TOTAL-EXTENDED-COST PIC $$$$,$$$,$$9.99.
05 FILLER PIC X(15) VALUE SPACES.
05 TOTAL-NET-COST PIC $$$,$$$,$$9.99.
05 FILLER PIC X(23) VALUE SPACES.
05 TOTAL-TRANS-COST PIC $$$,$$$,$$9.99.
01 TOTAL-NO-DISCOUNT-FOOTER.
05 TOTAL-SENTENCE PIC X(31) VALUE
'TOTAL ITEMS WITHOUT DISCOUNT = '.
05 TOTAL-NO-DISCOUNT PIC Z9.
01 PERCENT-DISCOUNT-FOOTER.
05 PERCENT-SENTENCE PIC X(44) VALUE
'PERCENT OF ITEMS THAT RECEIVED A DISCOUNT = '.
05 PERCENT-DISCOUNT PIC Z9.9.
*
PROCEDURE DIVISION.
*
OPEN INPUT IPT-FILE.
OPEN OUTPUT PRT-FILE.
*
WRITE PRT-LINE FROM HEADING-NAME AFTER ADVANCING 0 LINES.
WRITE PRT-LINE FROM HEADING-COLUMN-1 AFTER ADVANCING 3 LINES.
WRITE PRT-LINE FROM HEADING-COLUMN-2 AFTER ADVANCING 1 LINES.
WRITE PRT-LINE FROM BLANK-LINE AFTER ADVANCING 1 LINES.
*
READ IPT-FILE AT END MOVE 'Y' TO EOF-SWITCH.
*
PERFORM MAIN-LOOP UNTIL EOF-SWITCH EQUALS 'Y'.
*
DIVIDE WS-TOTAL-WITH-DISCOUNT BY WS-TOTAL-ITEMS
GIVING WS-PERCENT-WITH-DISCOUNT.
MULTIPLY WS-PERCENT-WITH-DISCOUNT BY 100
GIVING WS-PERCENT-WITH-DISCOUNT.
*
MOVE WS-TOTAL-EXTENDED-COST TO TOTAL-EXTENDED-COST.
MOVE WS-TOTAL-NET-COST TO TOTAL-NET-COST.
MOVE WS-TOTAL-TRANS-COST TO TOTAL-TRANS-COST.
MOVE WS-TOTAL-NO-DISCOUNT TO TOTAL-NO-DISCOUNT.
MOVE WS-PERCENT-WITH-DISCOUNT TO PERCENT-DISCOUNT.
*
WRITE PRT-LINE FROM TOTAL-FOOTER AFTER ADVANCING 3 LINES.
WRITE PRT-LINE FROM TOTAL-NO-DISCOUNT-FOOTER AFTER
ADVANCING 3 LINES.
WRITE PRT-LINE FROM BLANK-LINE AFTER ADVANCING 1 LINES.
WRITE PRT-LINE FROM PERCENT-DISCOUNT-FOOTER AFTER ADVANCING
1 LINES.
*
CLOSE IPT-FILE, PRT-FILE.
STOP RUN.
*
MAIN-LOOP.
MOVE SPACES TO PRT-LINE.
*
MULTIPLY IPT-INV-QUANTITY BY IPT-INV-UNITPRICE
GIVING WS-EXTENDED-COST ROUNDED.
MOVE WS-EXTENDED-COST TO PRT-EXTENDED-PRICE.
*
ADD 1 TO WS-TOTAL-ITEMS
*
IF WS-EXTENDED-COST IS GREATER THAN 200 THEN
MULTIPLY WS-EXTENDED-COST BY 0.11 GIVING
WS-DISCOUNT-AMOUNT ROUNDED
ADD 1 TO WS-TOTAL-WITH-DISCOUNT
*
ELSE
MOVE ZERO TO WS-DISCOUNT-AMOUNT
ADD 1 TO WS-TOTAL-NO-DISCOUNT
END-IF.
*
IF IPT-INV-PROD-CLASS IS EQUAL TO 1 THEN
MOVE 27.0 TO WS-TRANS-PERCENT
MULTIPLY WS-EXTENDED-COST BY 0.27 GIVING
WS-TRANS-COST ROUNDED
*
ELSE IF IPT-INV-PROD-CLASS IS EQUAL TO 2 THEN
MOVE 17.0 TO WS-TRANS-PERCENT
MULTIPLY WS-EXTENDED-COST BY 0.17 GIVING
WS-TRANS-COST ROUNDED
*
ELSE IF IPT-INV-QUANTITY IS GREATER THAN 100 THEN
MOVE 13.5 TO WS-TRANS-PERCENT
MULTIPLY WS-EXTENDED-COST BY 0.135 GIVING
WS-TRANS-COST ROUNDED
*
ELSE
MOVE ZERO TO WS-TRANS-PERCENT
MOVE 25.00 TO WS-TRANS-COST
END-IF.
*
SUBTRACT WS-EXTENDED-COST FROM WS-DISCOUNT-AMOUNT
GIVING WS-NET-COST.
ADD WS-EXTENDED-COST TO WS-TOTAL-EXTENDED-COST.
ADD WS-NET-COST TO WS-TOTAL-NET-COST.
ADD WS-TRANS-COST TO WS-TOTAL-TRANS-COST.
*
MOVE IPT-INV-NUMBER TO PRT-INV-NUMBER.
MOVE WS-EXTENDED-COST TO PRT-EXTENDED-PRICE.
MOVE WS-DISCOUNT-AMOUNT TO PRT-DISCOUNT-AMOUNT.
MOVE WS-NET-COST TO PRT-NET-PRICE.
MOVE IPT-INV-PROD-CLASS TO PRT-PRODUCT-CLASS.
MOVE WS-TRANS-PERCENT TO PRT-TRANS-PERCENT.
MOVE WS-TRANS-COST TO PRT-TRANS-CHARGE.
*
WRITE PRT-LINE AFTER ADVANCING 1 LINES.
*
READ IPT-FILE AT END MOVE 'Y' TO EOF-SWITCH.
Here is the information that the .dat file holds.
2047105TYPEWRITER 0800002
1742010HANDLE 0010001
2149150USB DRIVE 1200003
3761005TAPE 5000004
2791010BOLTS 0000751
3000100STAPLER 0002007
3001101OVERHEAD PROJ0099997
3002099PENCILS 0000097
4001184CANADIAN RUGS0150294
4003050CARPET 0040000
4005001WASTE BASKETS0003793
5001010HINGES 0010001
5003010PENS (GOLD) 0049992
5004400PENS (BLACK) 0002004
8888999HIGH CHAIR 9999991
8889412PLAY PEN 0074992
0001001LOW TEST 0000019
9999999LAST RECORD 0000011
Your problem is here:
01 WS-PERCENT-WITH-DISCOUNT PIC 99V9.
When you do your divide, you store the result in that field. If you expect it to be 0.556, what you are storing is 0.5, because you have only defined one decimal place, so the two low-order decimal places are simply truncated.
When you then multiply by 100, you make that 50.0.
If you define that field with three decimal places, your expected answer should appear (I've not checked your data).
However, a better way to do it is to define more integer digits, so that the field is large enough to hold your intermediate result and multiply by 100 first. Then you can divide (and you may want to consider ROUNDED on that, but it depends on the spec for the program).
There are a few questions here on problems with COMPUTE. Reading those questions and understanding the answers will help you get a good grasp on this. In COBOL, you define the accuracy you require, and you do that by supplying the correct number of integer and decimal digits.
You could also look through some of the other COBOL questions, where you'll find lots of advice on using FILE STATUS on your files, and checking the result of each IO. You can also use the file-status field you define to check for end-of-file, rather than using AT END/NOT AT END: you should find that it needs less code, and is more easy to understand.
Ditch as many full-stops/periods as you can. You need one at the end of the PROCEDURE DIVISION header, one at the end of a procedure-name, one at the end of a procedure, and one at the end of the program (if you have no procedure-names). All the others are superfluous. Commas in code tend to distract, you may find it clearer to use indentation and formatting of the statements.
Whilst it is well-constructed, your nested-IF would be better as an EVALUATE.
You have many constants in your program. It is better to define those as data-items, with a well-chosen name, so that the code "reads", and no-one has to wonder about the significance of 0.27. You also have examples where you have two constants which are obviously related, 27.0 and 0.27 for instance, which are better served by just being one thing. If someone "maintains" the program, they may only change one of the values without changing the other (not expecting there to be another).
Look also at the use of 88-level condition names. The "switch = y" can become "end-of-invoice-file" for instance, and that 88 can be on the file-status for that file, with a value of "10".
You should test your program with an empty input file, and see if you like the results.
As a beginner with COBOL, it is not a bad shot at all.
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.
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.
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.
--------------------------------------------------
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.