I want to acheive the below
a string of pic X(5) contains A1992 and is incremented to A9999 , after it reaches A9999 , the A should be replaced by B and the other characters should be reinitialized to 0000 ie B0000 , this should happen until Z9999 , is it possible somehow ?
or if you could show me how to increment A till Z that would be suffice
You will need to do some manual character manipulation on this one. There are several parts, first, you need to handle the simple addition of the numeric portion, then you need to handle the rollover of that to increment the alpha portion.
Data structures similar to this might be helpful:
01 Some-Work-Area.
02 Odometer-Char-Vals pic x(27) value 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'.
02 Odometer-Char occurs 27 pic x.
02 Odo-Char-Ndx pic s9(8) binary.
01 My-Odometer.
88 End-Odometer-Value value 'Z9999'.
02 My-Odometer-X pic X.
02 My-Odometer-9 pic 9999.
88 Carry-Is-True value 9999.
This would be used with a simple perform loop like so:
Move 0 to My-Odometer-9
Move 1 to Odo-Char-Ndx
Move Odometer-Char-Vals (Odo-Char-Ndx) to My-Odometer-X
Perform until End-Odometer-Value
Add 1 to My-Odometer-9
Display My-Odometer
If Carry-Is-True
Move 0 to My-Odometer-9
Add 1 to Odo-Char-Ndx
Move Odometer-Char-Vals (Odo-Char-Ndx) to My-Odometer-X
End-If
End-Perform
That is one way you could do it.
Please note, the code above took some shortcuts (aka skanky hacks) -- like putting a pad cell in the Odometer-Char array so I don't have to range check it. You wouldn't want to use this for anything but examples and ideas.
I'd probably do this with a nested perform loop.
Storage:
01 ws-counter-def
03 ws-counter-def-alpha-list pic x(27) value 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'.
03 ws-counter-def-num pic 9(4) comp-3.
01 ws-counter redefines ws-counter-def
03 ws-counter-alpha occurs 27 times indexed by counter-idx pic x.
03 ws-counter-num pic 9(4) comp-3.
01 ws-variable
03 ws-variable-alpha pic X
03 ws-variable-num pic X(4).
Procedure:
Initialize counter-idx.
Move 1992 to ws-counter-num.
Perform varying counter-idx from 1 by 1 until counter-idx > 26
move ws-counter-alpha(counter-idx) to ws-variable-alpha
perform until ws-counter-num = 9999
add 1 to ws-counter-
move ws-counter-num to ws-variable-num.
*do whatever it is you need to do to the pic X(5) value in ws-variable*
end-perform
move zeros to ws-counter-num
end-perform.
Just can't help myself... How about this...
IDENTIFICATION DIVISION.
PROGRAM-ID. EXAMPLE.
DATA DIVISION.
WORKING-STORAGE SECTION.
01.
02 ALL-LETTERS PIC X(26) VALUE 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'.
02 LETTERS REDEFINES ALL-LETTERS.
03 LETTER PIC X OCCURS 26 INDEXED BY I.
01 START-NUMBER PIC 9(4).
01 COUNTER.
02 COUNTER-LETTER PIC X.
02 COUNTER-NUMBER PIC 9(4).
PROCEDURE DIVISION.
MOVE 1992 TO START-NUMBER
PERFORM VARYING I FROM 1 BY 1 UNTIL I > LENGTH OF ALL-LETTERS
MOVE LETTER (I) TO COUNTER-LETTER
PERFORM TEST AFTER VARYING COUNTER-NUMBER FROM START-NUMBER BY 1
UNTIL COUNTER-NUMBER = 9999
DISPLAY COUNTER - or whatever else you need to do with the counter...
END-PERFORM
MOVE ZERO TO START-NUMBER
END-PERFORM
GOBACK
.
This will print all the "numbers" beginning with A1992 through to Z9999.
Basically stole Marcus_33's code and twiked it a tiny bit more. If you feel so inclined please upvote his answer, not mine
For lovers of obfuscated COBOL, here's the shortest (portable) version I can think of (assuming a compiler with Intrinsic Functions):
IDENTIFICATION DIVISION.
PROGRAM-ID. so.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ws-counter value "A00".
03 ws-alpha pic x.
03 ws-number pic 99.
PROCEDURE DIVISION.
1.
Perform with test after until ws-counter > "Z99"
Display ws-counter, " " with no advancing
Add 1 To ws-number
On size error
Move zero to ws-number
perform with test after until ws-alpha is alphabetic-upper or > "Z"
Move Function Char (Function Ord( ws-alpha ) + 1) to ws-alpha
end-perform
End-add
End-perform.
END PROGRAM so.
Tested on OpenVMS/COBOL. I shorten the value to X(3) since it's boring to watch run. A non-portable version (if you are aware of the Endianness of your platform) is to redefined the prefix as a S9(4) COMP and increment the low-order bits directly. But that solution wouldn't be any shorter...
Related
We have to find more than one way to get the ascii value of a character.
On top of that we also need to get the sum of all the characters's ascii values.
I currently have the below and works alright for the first section where you need individual values
.
I just need to know if there is an easier way or a function to do this in Cobol?
DATA DIVISION.
FILE SECTION.
WORKING-STORAGE SECTION.
01 WS-COUNTERS.
03 WS-COUNTER PIC 9(05).
03 WS-INPUT PIC X(01).
03 WS-DISPLAY PIC 9(03).
01 W1-ARRAY.
03 ALPHABETIC-CHARS OCCURS 26 TIMES PIC X.
01 W3-ARRAY.
03 NUMERIC-CHARS OCCURS 26 TIMES PIC X.
PROCEDURE DIVISION.
A000-MAIN SECTION.
BEGIN.
PERFORM B000-INITIALIZE.
PERFORM C000-PROCESS UNTIL WS-COUNTER > 26.
PERFORM D000-END.
A099-EXIT.
STOP RUN.
B000-INITIALIZE SECTION.
ACCEPT WS-INPUT.
MOVE "ABCDEFGHIJKLMNOPQRSTUVWXYZ" TO W1-ARRAY.
MOVE "01234567890000000000000000" TO W3-ARRAY.
MOVE 1 TO WS-COUNTER.
MOVE 0 TO WS-DISPLAY.
B099-EXIT.
EXIT.
C000-PROCESS SECTION.
C001-BEGIN.
IF WS-INPUT IS NUMERIC
IF NUMERIC-CHARS(WS-COUNTER) = WS-INPUT
COMPUTE WS-DISPLAY = WS-COUNTER + 48 - 1
END-IF
ELSE
IF ALPHABETIC-CHARS(WS-COUNTER) = WS-INPUT
COMPUTE WS-DISPLAY = WS-COUNTER + 65 - 1
END-IF
END-IF.
ADD 1 TO WS-COUNTER.
C099-EXIT.
EXIT.
Have a look at FUNCTION ORD and keep in mind that you will get the ordinal number in the program's collating sequence (which may be EBCDIC or not the full ASCII).
As this function was introduced in the COBOL85 standard it should be available in most compilers (your question misses the compiler/machine you use).
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 a field containing article-numbers (PIC X(25)).
Example article number: 12345-6789.
The problem is the "-", I need to delete the "-" and put together the 5 and 6, result example: 123456789
Using Micro Focus Net Express 5.1 running on a UNIX server. The position of the dash is not fixed.
Take this code for a spin.
Update: Good catch, Bill. I just wanted to give options, depending what the needs and demands truly were.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
* ClassIncludeList and ClassExcludeList can now be referenced much like NUMERIC
CLASS ClassIncludeList IS '0123456789'
CLASS ClassExcludeList IS '-'
.
WORKING-STORAGE SECTION.
01 InputStringText PIC X(1000).
01 InputStringLength PIC 9(04) COMP.
01 OutputStringText PIC X(1000).
01 OutputStringLength PIC 9(04) COMP.
01 ByteSubscript PIC 9(04) COMP.
PROCEDURE DIVISION.
MOVE article-numbers TO InputStringText.
MOVE FUNCTION LENGTH(article-numbers) TO InputStringLength.
PERFORM IncludeCharacters.
* Use OutputStringText(OutputStringLength)
PERFORM ExcludeCharacters.
* Use OutputStringText(OutputStringLength)
IncludeCharacters.
MOVE SPACES TO OutputStringText
MOVE ZERO TO OutputStringLength
PERFORM
VARYING ByteSubscript FROM 1 BY 1
UNTIL ByteSubscript > InputStringLength
IF (InputStringText(ByteSubscript:1) IS ClassIncludeList)
ADD 1 TO OutputStringLength
MOVE InputStringText(ByteSubscript:1)
TO OutputStringText(OutputStringLength:1)
END-IF
END-PERFORM
.
ExcludeCharacters.
MOVE SPACES TO OutputStringText
MOVE ZERO TO OutputStringLength
PERFORM
VARYING ByteSubscript FROM 1 BY 1
UNTIL ByteSubscript > InputStringLength
IF (InputStringText(ByteSubscript:1) IS ClassExcludeList)
CONTINUE
ELSE
ADD 1 TO OutputStringLength
MOVE InputStringText(ByteSubscript:1)
TO OutputStringText(OutputStringLength:1)
END-IF
END-PERFORM
.
There's always UNSTRING and STRING if your Cobol supports them, and if there is a limit to how many 'parts' there are going to be in the text.
01 ARTICLE-NUMBER PIC X(25).
01 PARTS.
05 PART1 PIC X(25).
05 PART2 PIC X(25).
05 PART3 PIC X(25).
05 PART4 PIC X(25).
01 RESULT PIC X(25).
........
INITIALIZE PARTS, RESULT.
UNSTRING ARTICLE-NUMBER
DELIMITED BY '-'
INTO PART1, PART2, PART3, PART4
ON OVERFLOW
DISPLAY "Too many parts!!!"
END-UNSTRING.
STRING PART1, PART2, PART3, PART4
DELIMITED BY SPACE INTO RESULT.
Hope this helps.
The following should work on any modern COBOL:
01 INPUT-STRING PIC X(25).
01 OUTPUT-STRING PIC X(25).
01 IX PIC S9(8) COMP SYNC.
01 OX PIC S9(8) COMP SYNC.
...
MOVE +1 TO OX.
MOVE ALL ' ' TO OUTPUT-STRING.
PERFORM VARYING IX FROM 1 BY 1
UNTIL IX > 25
IF NOT INPUT-STRING(IX:1) = '-'
THEN
MOVE INPUT-STRING(IX:1) TO OUTPUT-STRING(OX:1)
ADD +1 TO OX
END-IF
END-PERFORM.
I need help on some COBOL homework. I've made a few attempts and they don't seem to be working as I would hope.
I need to make a program that reads an input file with some student info, then output it to the terminal and an output file.
I also need to calculate the GPA based on the hours and quality points earned.
I am currently having issues with creating column headers, and also adding values to get the cumulative values to get the GPA, among some other things. I have the input file and the code I have so far attached.
IDENTIFICATION DIVISION.
PROGRAM-ID. TEST3.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT StudentFile ASSIGN TO "P2In.dat"
ORGANIZATION IS LINE SEQUENTIAL.
SELECT OutputFile ASSIGN TO "Report.dat"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD StudentFile.
*>Student details will only be printed once
01 StudentDetails.
05 STUDENT-NAME PIC X(16).
05 STUDENT-ID PIC X(9).
*>Semester info that will be on one line and not repeated
01 SemesterDetails.
05 SEMESTER PIC X(9).
*> Details in the class that need to be seperate
01 ClassDetails.
05 CLASS-NAME PIC X(32).
05 GRADE PIC X(2).
05 HOURS PIC X(4).
05 POINTS PIC X(2).
*>values that need to be calculated
01 CalculatedValues.
05 CUMULATIVE-GPA-IN PIC 99v99 VALUE ZERO.
05 CUMULATIVE-QP-IN PIC 99v99 VALUE ZERO.
05 CUMULATIVE-HOURS-IN PIC 99v99 VALUE ZERO.
FD OutputFile.
01 PrintLine PIC X(70).
WORKING-STORAGE SECTION.
01 SWITCHES.
05 EOF-SWITCH PIC X VALUE "N".
01 COUNTERS.
05 REC-COUNTER PIC 9(3) VALUE 0.
01 CUMULATIVE.
05 CUMULATIVE-QP PIC ZZ.99.
PROCEDURE DIVISION.
*>main paragraph, everything starts here
Main.
PERFORM Begin.
PERFORM ProcessData.
PERFORM PrintLines
UNTIL EOF-SWITCH = "Y".
*>opening read
Begin.
OPEN INPUT StudentFile
OPEN OUTPUT OutputFile
READ StudentFile
AT END
MOVE "Y" TO EOF-SWITCH
NOT AT END
COMPUTE REC-COUNTER = REC-COUNTER + 1
END-READ.
ProcessData.
READ StudentFile
AT END
MOVE "Y" TO EOF-SWITCH
NOT AT END
IF GRADE = 'A'
COMPUTE CUMULATIVE-QP = CUMULATIVE-QP + 4
ELSE
IF GRADE = 'B'
COMPUTE CUMULATIVE-QP = CUMULATIVE-QP + 3
ELSE
IF GRADE = 'C'
COMPUTE CUMULATIVE-QP = CUMULATIVE-QP + 2
ELSE
IF GRADE = 'D'
COMPUTE CUMULATIVE-QP = CUMULATIVE-QP + 1
END-IF.
*>printing out our lines to terminal
PrintLines.
READ StudentFile
AT END
MOVE "Y" TO EOF-SWITCH
NOT AT END
DISPLAY CUMULATIVE-QP
END-READ.
And the input file looks like this
TERRY ETHELBERT W1234567 FALL2014 CMPS161 ALGORITHM DSGN/IMPLMNT A 3.00 12.00
TERRY ETHELBERT W1234567 FALL2014 CMPS280 ALGORITHM DSGN/IMPLMNTII B 3.00 9.00
TERRY ETHELBERT W1234567 FALL2014 CMPS431 OPERATING SYSTEMS C 3.00 6.00
TERRY ETHELBERT W1234567 FALL2014 ENG322 TECHNICAL WRITING A 3.00 12.00
TERRY ETHELBERT W1234567 SPNG2015 MATH380 STATISTICS B 3.00 9.00
TERRY ETHELBERT W1234567 SPNG2015 HIST202 HISTORY B 3.00 9.00
TERRY ETHELBERT W1234567 SPNG2015 BIOL152 GENERAL BIOLOGY A 3.00 12.00
TERRY ETHELBERT W1234567 SPNG2015 MATH200 CALCULUS I C 5.00 10.00
A place to start would be nice.
First issue is to get your input record correct. The FD must match the line layout, so it should be something like
01 StudentDetails.
05 STUDENT-NAME PIC X(16).
05 STUDENT-ID PIC X(9).
*> Details in the class that need to be seperate
*01 ClassDetails.
05 CLASS-NAME PIC X(32).
05 GRADE PIC X(1).
05 FILLER PIC X(1).
05 HOURS.
07 HOURS-9 PIC 9.99.
05 FILLER PIC X(2).
05 POINTS.
07 POINTS-X PIC X(1) OCCURS 5.
05 POINTS-9-99 REDEFINES POINTS.
07 POINTS-9-99 PIC 9.99.
05 POINTS-99-99 REDEFINES POINTS.
07 POINTS-99-99 PIC 99.99.
Note that GRADE is an X(1) and is followed by a FILLER also X(1) to represent the space that follows the grade-letter.
HOURS is implicitly a X(4); HOURS-9 allows that field to be read as a 9.99
Then there are 2 spaces - another filler
Finally, there are POINTS. This is a 5-character field with 2 layouts. We van determine which of the layouts to use (POINTS-9-99 or POINTS-99-99) by looking at POINTS-X(2) - a dot means use POINTS-9-99, otherwise use POINTS-99-99.
I've no idea what Semesterdetails are.
Your Calculatedvalues are supposed to be in WORKING-STORAGE; you can't have a VALUE clause in an FD.
Next, you should think through your process. Think Michael Jackson. Seriously. Oh - not the singer, the computer scientist.
Your process:
Start with a CURRENT-STUDENT containing SPACES.
Read each record. If the STUDENT-NAME is not equal to CURRENT-STUDENT, (and also AT END) then (produce a report line, zero your accumulators and store STUDENT-NAME into CURRENT-STUDENT.) and use the fields in the current record to accumulate the required data.
Note that producing your report line is simply a matter of building the various accumulated fields into the output record and doing a little mathematical gymnastics to calculate averages. Naturally, don't bother if the CURRENT-STUDENT contains SPACES.
So, the essentials are
READ studentfile
at end perform write-report-line
not at end
if student-name is not equal to current-student
perform write-report-line
end-if
perform accumulate-data.
and the write-report-line paragraph is
if current-student is not equal to spaces
calculate and move name, average, etc. to output-record
and write it
end-if
move student-name to current-student
move zero to rec-counter etc, etc.
As Magoo has pointed out, you need to get your record-definition straight. You defined separate records when you defined each logical block as a separate 01-level. This does not match your data (which for the moment we assume is correct). It is unclear what POINTS is, but your definition doesn't match the data.
01 RecordDetails.
03 StudentDetails.
05 STUDENT-NAME PIC X(16).
05 STUDENT-ID PIC X(9).
03 SemesterDetails.
05 SEMESTER PIC X(9).
03 ClassDetails.
05 CLASS-NAME PIC X(32).
05 GRADE PIC X(2).
05 HOURS PIC X(4).
05 POINTS PIC X(2).
This you've define subordinate to the FD, so it as a record on your file:
01 CalculatedValues.
05 CUMULATIVE-GPA-IN PIC 99v99 VALUE ZERO.
05 CUMULATIVE-QP-IN PIC 99v99 VALUE ZERO.
05 CUMULATIVE-HOURS-IN PIC 99v99 VALUE ZERO.
That is probably not what you want.
Look at the documentation and understand what using FILE STATUS on the SELECT gets you. Every IO should have it's (separate per file) FILE STATUS field checked. You can then use the FILE STATUS field (via an 88-level with a value of "10") to check for end-of-file, cutting the tortuous use of READ ... AT END ... NOT AT END ....
88's are good for your grades as well, rather than literals. Note that if adding "4" it is better to add a well-named field with a VALUE of 4, so that the reader knows what is being added (what the 4 means).
Unless you have a complex calculation, you may want to prefer ADD 1 TO field-name over COMPUTE field-name = field-name + 1.
If you have your grade tests, you'll find EVALUATE much clearer to use than nested- or sequential-IFs.
You don't have any output yet, either file or screen. Look around here and elsewhere for examples and see how that goes. Best to ask a new question if you get stuck with that, else the answers become too complex. One thing at a time.
OK so I'm doing assignment but then I found that I was asked to add page numbers and change pages for each 4 records. Since it's an online course and I don't think there is anything about page numbers in lecture videos. So the main problems are
To add a heading that contains date and page number,
Print 4 records per page, which means page needs to be changed after printing 4 records.
I really have no idea how to do this.
Here is the code I have finished:
ENVIRONMENT DIVISION.
FILE-CONTROL. SELECT STOCK-IN ASSIGN TO 'F:/CS201S13/PROJECT2.TXT'
ORGANIZATION IS LINE SEQUENTIAL.
SELECT STOCK-OUT ASSIGN TO 'F:/CS201S13/PROJECT2OUTPUT.TXT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD STOCK-IN.
01 STOCK-RECORD.
05 ST-TRANSACTION-INFORMATION.
10 ST-TRANSACTION-SHARES PIC 9(3).
10 ST-TRANSACTION-STOCK PIC X(14).
05 ST-PURCHASE-INFORMATION.
10 ST-PURCHASE-PRICE PIC 9(5)V99.
10 ST-PURCHASE-DATE.
15 ST-PURCHASE-YEAR PIC 99.
15 ST-PURCHASE-MONTH PIC 99.
15 ST-PURCHASE-DAY PIC 99.
05 ST-SALE-INFORMATION.
10 ST-SALE-PRICE PIC 9(5)V99.
10 ST-SALE-DATE.
15 ST-SALE-YEAR PIC 99.
15 ST-SALE-MONTH PIC 99.
15 ST-SALE-DAY PIC 99.
FD STOCK-OUT.
01 STOCK-RECORD-OUT.
05 ST-TRANSACTION-INFORMATION-OUT.
10 ST-TRANSACTION-SHARES-OUT PIC 9(3).
10 ST-TRANSACTION-STOCK-OUT PIC X(14).
05 TOTAL-PURCHASE PIC 9(8)V99.
05 PIC X(4).
05 TOTAL-SALE PIC 9(8)V99.
05 PIC X(4).
05 TOTAL-PROFIT PIC 9(8)V99.
05 PIC X(4).
05 ST-PURCHASE-DATE-OUT.
10 ST-PURCHASE-YEAR-OUT PIC 99.
10 PIC X VALUE '/'.
10 ST-PURCHASE-MONTH-OUT PIC 99.
10 PIC X VALUE '/'.
10 ST-PURCHASE-DAY-OUT PIC 99.
05 PIC X(4).
05 ST-SALE-DATE-OUT.
10 ST-SALE-YEAR-OUT PIC 99.
10 PIC X VALUE '/'.
10 ST-SALE-MONTH-OUT PIC 99.
10 PIC X VALUE '/'.
10 ST-SALE-DAY-OUT PIC 99.
05 PIC X(4).
05 RECORD-OUT PIC 9 VALUE 0.
05 PAGE-OUT PIC 9.
WORKING-STORAGE SECTION.
01 ARE-THERE-MORE-RECORDS PIC XXX VALUE 'YES'.
01 IS-THIS-PAGE-FULL PIC XXX VALUE 'NO '.
PROCEDURE DIVISION.
100-MAIN-PROCESS.
OPEN INPUT STOCK-IN
OUTPUT STOCK-OUT
MOVE ST-TRANSACTION-INFORMATION TO ST-TRANSACTION-INFORMATION-OUT
PERFORM UNTIL ARE-THERE-MORE-RECORDS = 'NO '
READ STOCK-IN
AT END
MOVE 'NO ' TO ARE-THERE-MORE-RECORDS
NOT AT END
PERFORM 200-PROCEDURE-RTN
ADD 1 TO RECORD-OUT
END-READ
END-PERFORM
CLOSE STOCK-IN
STOCK-OUT
STOP RUN.
200-PROCEDURE-RTN.
IF RECORD-OUT = 4
MOVE 'YES' TO IS-THIS-PAGE-FULL
MOVE 0 TO RECORD-OUT
MOVE 'NO ' TO IS-THIS-PAGE-FULL
ADD 1 TO PAGE-OUT
END-IF
MULTIPLY ST-PURCHASE-PRICE BY ST-TRANSACTION-SHARES GIVING TOTAL-PURCHASE
MULTIPLY ST-SALE-PRICE BY ST-TRANSACTION-SHARES GIVING TOTAL-SALE
SUBTRACT TOTAL-PURCHASE FROM TOTAL-SALE GIVING TOTAL-PROFIT
WRITE STOCK-RECORD-OUT.
You are both close, and far away.
"Close" because you need a little bit of code in between setting IS-THIS-PAGE-FULL to YES and NO.
"Far away" as you have quite a lot to do rather than just "patch up" what you have.
Is the program writing an output file (STOCK-OUT) and a report, or is STOCK-OUT the report? If it is a report, change the names so that it is clear that it is a report, not an output file.
Don't worry if this seems a lot. You should be learning how to Program in Cobol, as well as learning Cobol. Doesn't happen overnight.
In no particular order:
Include FILE-STATUS checking for all IO operations on all files, always. At the moment, if your input fails to open and the system does not fail the program (even if yours does, you are presumably learning Cobol to be able to work with any system, not just the one you have) then no records will be read, your "end of file test" will never be YES and you'll have a BFL (Big Fat Loop). With the FILE-STATUS checking, produce useful messages, including key/reference/record number as appropriate for failed READ or WRITE.
You may feel that this is a lot of work. However, put together some "template" files with all the stuff in, and then paste (or even COPY) those into your program each time.
You have VALUE clause in the FD. These will not do what you think.
You have single digit for your page count, which is unlikely to have general application.
Why use YES and NO as literals? Look at the SET verb, in relation to "condition names", use 88's for tests and "flags/switches".
You have "MOVE ST-TRANSACTION-INFORMATION" after the input is opened but before a record is read, and only have one reference to it in the program. This is not going to work.
For reading files, have a look at the "priming read" approach.
read input
loop until end-of-file (88 on file-status)
process data
read input
end-loop
This avoids the AT END/NOT AT END, allows processing of headers (if present) and "empty files" without clogging-up the main logic. The code "expands" with headers/trailers (including the correct number of them), sequence-checking of keys, etc, but you only need to code it once then "template" it.
According to your VALUE clauses in your FD, you expect RECORD-OUT to be zero, so the test for 4 will actually get you five on the first page, and four thereafter.
You always assume there will be a "profit" (a positive amount), which is not realistic, yet you don't allow a signed value for the "profit".
Now, for the report.
For your report FD, just make it a simple thing, length of your print line.
In WORKING-STORAGE, define data for the headings and titles that you need. Define data for a print line. Since you're in the WORKING-STORAGE, put VALUEs for everything which will not have data MOVEd to it in the PROCEDURE DIVISION.
When you have written four items (or when your program tells you this) and you have a fifth, write the headings and titles, remembering to update the page number.
I say "or when your program tells you this" because you can set your original value of "records written" to 4. Comment it, so that it is clear that it is what you want, and why you want it. The reason is, you don't have to then deal with "first time" headings and othe things. For first time, or on a "contol break" (I guess you'll get to those soon) set the " done on a page already" to the maximum for a page, and the headings will pop out when you want.
Format the print line. PERFORM a para to print it (which is where the "page full" test will be).
Note: You can use VALUEs for your "/"s in the dates, or you can use the "/" editing character in the PICture, like this:
05 an-input-date PIC X(8) (can be other definitions).
...
05 date-to-print PIC X(4)/XX/XX.
...
MOVE an-input-date TO date-to-print
I like to see that you are using "minimal full-stops/periods". You can go a little further.
MOVE an-input-date TO date-to-print
.
Then you get your final full-stop/period in a paragraph, without having it "attached" to any particular line of code, which makes "tossing code around" easier, as you don't have to think "do I need/not need that full-stop/period there".
You could also look through some of the Cobol questions here, and get a handle on some general tips and advice.
This may or may not help, if LINAGE is not supported you'll have to do some explicit counting.
*****************************************************************
* Example of LINAGE File Descriptor
* Author: Brian Tiffin
* Date: 10-July-2008
* Tectonics: $ cobc -x linage.cob
* $ ./linage <filename ["linage.cob"]>
* $ cat -n mini-report
*****************************************************************
IDENTIFICATION DIVISION.
PROGRAM-ID. linage-demo.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
select optional data-file assign to file-name
organization is line sequential
file status is data-file-status.
select mini-report assign to "mini-report".
DATA DIVISION.
FILE SECTION.
FD data-file.
01 data-record.
88 endofdata value high-values.
02 data-line pic x(80).
FD mini-report
linage is 16 lines
with footing at 15
lines at top 2
lines at bottom 2.
01 report-line pic x(80).
WORKING-STORAGE SECTION.
01 command-arguments pic x(1024).
01 file-name pic x(160).
01 data-file-status pic 99.
01 lc pic 99.
01 report-line-blank.
02 filler pic x(18) value all "*".
02 filler pic x(05) value spaces.
02 filler pic x(34)
VALUE "THIS PAGE INTENTIONALLY LEFT BLANK".
02 filler pic x(05) value spaces.
02 filler pic x(18) value all "*".
01 report-line-data.
02 body-tag pic 9(6).
02 line-3 pic x(74).
01 report-line-header.
02 filler pic x(6) VALUE "PAGE: ".
02 page-no pic 9999.
02 filler pic x(24).
02 filler pic x(5) VALUE " LC: ".
02 header-tag pic 9(6).
02 filler pic x(23).
02 filler pic x(6) VALUE "DATE: ".
02 page-date pic x(6).
01 page-count pic 9999.
PROCEDURE DIVISION.
accept command-arguments from command-line end-accept.
string
command-arguments delimited by space
into file-name
end-string.
if file-name equal spaces
move "linage.cob" to file-name
end-if.
open input data-file.
read data-file
at end
display
"File: " function trim(file-name)
" open error or empty"
end-display
go to early-exit
end-read.
open output mini-report.
write report-line
from report-line-blank
end-write.
move 1 to page-count.
accept page-date from date end-accept.
move page-count to page-no.
write report-line
from report-line-header
after advancing page
end-write.
perform readwrite-loop until endofdata.
display
"Normal termination, file name: "
function trim(file-name)
" ending status: "
data-file-status
end-display.
close mini-report.
* Goto considered harmful? Bah! :)
early-exit.
close data-file.
exit program.
stop run.
****************************************************************
readwrite-loop.
move data-record to report-line-data
move linage-counter to body-tag
write report-line from report-line-data
end-of-page
add 1 to page-count end-add
move page-count to page-no
move linage-counter to header-tag
write report-line from report-line-header
after advancing page
end-write
end-write
read data-file
at end set endofdata to true
end-read
.
*****************************************************************
* Commentary
* LINAGE is set at a 20 line logical page
* 16 body lines
* 2 top lines
* A footer line at 15 (inside the body count)
* 2 bottom lines
* Build with:
* $ cobc -x -Wall -Wtruncate linage.cob
* Evaluate with:
* $ ./linage
* This will read in linage.cob and produce a useless mini-report
* $ cat -n mini-report
*****************************************************************
END PROGRAM linage-demo.