Extract records by first letter of name - cobol

I am trying to make the program below to pull out records that have customer names beginning with letter the "M" and write the records to a temporary file. The program runs but it won't write records to the output file. I debugged the code, and it seems like the code line "WRITE MAST2-RECORD" never runs. It skips this line of code.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT MAST-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-1\OVERDUE.IND.TXT'
ORGANIZATION IS INDEXED
ACCESS IS RANDOM
RECORD KEY IS M-ACCT-NUM.
SELECT MAST2-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-1\OVERDUE2.IND.TXT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD MAST-FILE
LABEL RECORDS ARE STANDARD.
01 MAST-RECORD.
05 M-ACCT-NUM PIC X(4).
05 M-CUSTOMER-NAME PIC X(15).
05 M-DAYS-OVERDUE PIC 99.
05 M-BALANCE-DUE PIC 999V99.
FD MAST2-FILE
LABEL RECORDS ARE STANDARD.
01 MAST2-RECORD PIC X(50).
WORKING-STORAGE SECTION.
01 COUNTER PIC 9.
01 PROGRAM-DATA-ITEMS.
05 WRITE-OK PIC X VALUE 'Y'.
PROCEDURE DIVISION.
10-MAINLINE.
OPEN OUTPUT MAST-FILE
OUTPUT MAST2-FILE
PERFORM 20-LOAD-MAST-FILE
CLOSE MAST-FILE
MAST2-FILE
STOP RUN.
20-LOAD-MAST-FILE.
PERFORM 30-INPUT-INDEX
PERFORM UNTIL M-ACCT-NUM = 0 OR WRITE-OK = 'N'
PERFORM 40-WRITE-FILE
PERFORM 50-FIND-CUSTOMER-START-WITH-M
PERFORM 30-INPUT-INDEX
END-PERFORM.
30-INPUT-INDEX.
DISPLAY 'ENTER ACCOUNT NUMBER (0 TO QUIT): ' WITH NO ADVANCING
ACCEPT M-ACCT-NUM.
40-WRITE-FILE.
DISPLAY ' ENTER CUSTOMER NAME: ' WITH NO ADVANCING
ACCEPT M-CUSTOMER-NAME
DISPLAY ' ENTER DAYS OVERDUE: ' WITH NO ADVANCING
ACCEPT M-DAYS-OVERDUE
DISPLAY ' ENTER BALANCE DUE: ' WITH NO ADVANCING
ACCEPT M-BALANCE-DUE
WRITE MAST-RECORD
INVALID KEY
MOVE 'N' TO WRITE-OK
DISPLAY 'ERROR ' MAST-RECORD
END-WRITE.
50-FIND-CUSTOMER-START-WITH-M.
MOVE 0 TO COUNTER
INSPECT MAST-RECORD TALLYING COUNTER FOR ALL ' M '
IF COUNTER > 0
WRITE MAST2-RECORD
END-IF.
end program Program1.

You are looking for blank-M-blank, across the entire record.
What you say you want to do is fine customer-names which begin with M.
05 M-CUSTOMER-NAME.
10 M-CUSTOMER-NAME-FIST-CHARACTER PIC X.
88 M-CUSTOMER-NAME-START-M VALUE "M".
If you use that definition in place of what you have, and use the 88 in the test for your write, you should get what you want.
Eg replace:
50-FIND-CUSTOMER-START-WITH-M.
MOVE 0 TO COUNTER
INSPECT MAST-RECORD TALLYING COUNTER FOR ALL ' M '
IF COUNTER > 0
WRITE MAST2-RECORD
END-IF.
By:
50-FIND-CUSTOMER-START-WITH-M.
IF M-CUSTOMER-NAME-START-M
WRITE MAST2-RECORD
END-IF
.
Simpler, easier to understand, so easier to maintain.
You should consider the possible "validity" of your names. In a good system, there will be no leading blanks. In a poor system there may be.
To deal with that, test the first byte of the customer-name for being space as well, if so, test the customer-name for entirely space. If not entirely space, loop until you find the first non-blank. Test that first non-blank for M. So in this case you have two tests.
You can assess the quality of your data separately by copying and cutting-down this program and reporting/outputting where the first byte of the customer-name is blank.
Once you know that, you go to the analyst (tutor) and ask if you need to deal with possible leading blanks. If you don't, keep the test for blank in your actual program, and crash in that case :-)

Related

COBOL error with numeric variable, not numeric

problem
I'm a beginner in COBOL and I'm running into this annoying problem which I can not find a solution for.
I want to add the value of the amount of sales to another numeric variable so that I can use it as a condition for a perform loop but when it tries to add that value to this new variable it triggers this error:
"libcob: PROG-PAGOS-F.cbl: 57: 'WS-CANTIDAD-VENTAS' not numeric: '2 '
WARNING - Implicit CLOSE of REG-VENDEDORES ('REG-MAESTRO.DAT')"
and I can not find a way around it; I'm stuck.
current code (not finished)
What this program is supposed to do is output data of employees' salary, sells, price of each sell into a file and then do some other operations with them but I can't do any progress because of this error, I'd love some help, and perhaps some advices to makes this code better. Thank you!
My variables are in Spanish because I'm Argentinian, sorry if it's hard to understand.
IDENTIFICATION DIVISION.
PROGRAM-ID. PROG-PAGOS-F.
AUTHOR. LUCAS GALEANO.
DATE-WRITTEN. 1/2/2023.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT REG-VENDEDORES ASSIGN TO "REG-MAESTRO.DAT"
ORGANIZATION IS LINE SEQUENTIAL.
SELECT REG-VENTAS ASSIGN TO "REG-VENTAS-MAESTRO.DAT"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD REG-VENDEDORES.
01 VENDEDORES PIC 9(11).
FD REG-VENTAS.
01 COBRO-VENTAS PIC 9(5).
WORKING-STORAGE SECTION.
01 WS-VENDEDORES.
05 WS-EMPLEADO PIC 999.
05 WS-SUELDO-BASE PIC 9(5).
05 WS-CANTIDAD-VENTAS PIC 999.
77 WS-COBROS PIC 9(5).
77 WS-SUM-VENTAS PIC 99.
77 WS-CONTADOR PIC 99 VALUE ZEROS.
01 WS-TABLAS.
05 WS-REGISTRO-COBROS PIC 9(5)
OCCURS 100 TIMES.
PROCEDURE DIVISION.
BEGIN-OUTPUT.
OPEN OUTPUT REG-VENDEDORES.
DISPLAY "INGRESE DATOS SOLICITADOS".
PERFORM INGRESO-DATOS-EMPLEADOS.
PERFORM UNTIL WS-VENDEDORES EQUALS SPACES
WRITE VENDEDORES FROM WS-VENDEDORES
PERFORM INGRESO-DATOS-EMPLEADOS
END-PERFORM.
DISPLAY "INGRESE COBROS DE CADA VENTA:".
PERFORM INGRESO-VENTAS WITH TEST AFTER
UNTIL WS-CONTADOR EQUALS WS-SUM-VENTAS
MOVE WS-COBROS TO WS-REGISTRO-COBROS(1)
CLOSE REG-VENDEDORES.
STOP RUN.
INGRESO-DATOS-EMPLEADOS.
DISPLAY "EEE$$$$$VVV".
ACCEPT WS-VENDEDORES.
ADD WS-CANTIDAD-VENTAS TO WS-SUM-VENTAS.
INGRESO-VENTAS.
ADD 1 TO WS-CONTADOR.
DISPLAY "$$$$$".
ACCEPT WS-COBROS.
example input data
INGRESE DATOS SOLICITADOS
EEE$$$$$VVV
1 400002
There is no implicit conversion in ACCEPT data-item, so you need to convert - and validate it on your own (or switch to "extended" screenio with ACCEPT data-item AT / SCREEN SECTION, but then the result would be depending on the actual COBOL environment).
The easiest option to convert (will sip leading/trailing spaces and invalid data) is something like the following:
ACCEPT WS-VENDEDORES. *> all data may now be invalid
MOVE FUNCTION NUMVAL (WS-EMPLEADO) TO WS-EMPLEADO
MOVE FUNCTION NUMVAL (WS-SUELDO-BASE) TO WS-SUELDO-BASE
MOVE FUNCTION NUMVAL (WS-CANTIDAD-VENTAS) TO WS-CANTIDAD-VENTAS
*> all data is now valid
For validation you may want to use FUNCITON TEST-NUMVAL (data-to-verify).
In any case I'd suggest to check out SCREEN SECTION, as this would allow you to input the data in three separate fields and commonly would do validation and conversion "on the fly".

Cobol Treating Multiple Lines as One Line When it Should Not

Trying to code a cobol program and it keeps treating multiple lines as one line when compiling with opencobol (have to use opencobol, I've heard GNU is better), giving errors
The code is
IDENTIFICATION DIVISION.
PROGRAM-ID. InteractiveProcessing.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT INVENTORY-FILE
ASSIGN TO "C:\COBOL\INVENTORY-FILE.DAT"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD INVENTORY-FILE.
01 FILE-OUTPUT.
05 PART-NO PIC X(5).
05 PART-DESC PIC X(15).
05 QTY-ON-HAND PIC 9(5).
05 UNIT-PRICE PIC 999V99.
WORKING-STORAGE SECTION.
01 MORE-DATA PIC X(3) VALUE 'YES'.
PROCEDURE DIVISION.
100-MAIN-MODULE.
OPEN OUTPUT INVENTORY-FILE
PERFORM UNTIL MORE-DATA = 'NO '
PERFORM 200-INVENTORY-MODULE
DISPLAY 'ENTER MORE DATA? (YES/NO)'
ACCEPT MORE-DATA
END-PERFORM
CLOSE INVENTORY-FILE
STOP RUN.
200-INVENTORY-MODULE.
DISPLAY 'ENTER PART NUM (5 CHARACTERS)'
ACCEPT PART-NO
DISPLAY 'ENTER PART DESCRIPTION (15 CHARACTERS)'
ACCEPT PART-DESC
DISPLAY 'ENTER QUANTITY ON HAND(INTEGER, UP TO 5 DIGITS)'
ACCEPT QTY-ON-HAND
DISPLAY 'ENTER UNIT PRICE (5 DIGITS, 2 AFTER DECIMAL)'
ACCEPT UNIT-PRICE
WRITE FILE-OUTPUT.
The errors I keep getting say
'ENTER' undefined
and
syntax error, unexpected UNIT
The line the errors are appearing on is
DISPLAY 'ENTER QUANTITY ON HAND(INTEGER, UP TO 5 DIGITS)'
The errors are from ENTER and UNIT from two lines down and I can't figure out why this is happening. Changing the quotation marks from single to double on just that line then gives an unexpected end of file error as well.
The problem was that I used tab to align the PIC clauses. Had the same issue in another program. Solved by backspacing the tabs then just using the spacebar to get the clauses to the right spot. Looks the same in the end but actually ran this way.

COBOL: Can a GDG file descriptor (FD) reference multiple generations?

I have a program which reads a GDG file and moves data to working storage. I am interested to know if it can be made to repeat this process for multiple generations of the GDG using a reference to the file definition. Perhaps there is a way to use subscripts on the file definition? My thought is there must be a method to move different file definitions into a reference variable from which to access the files.
Code Sample based on suggested, setenv solution
FILE-CONTROL.
SELECT DATAIN ASSIGN TO UT-S-DATAIN.
DATA DIVISION.
FILE-SECTION.
FD DATAIN
BLOCK CONTAINS 0 RECORDS
RECORD CONTAINS 133 CHARACTERS
LABEL RECORDS ARE STANDARD
DATA RECORD IS DATA-REC.
01 DATA-REC PIC X(133).
WORKING-STORAGE SECTION.
01 ENV-VARS.
02 ENV-NAME PIC X(9).
02 ENV-VALUE PIC X(100).
02 ENV-OVERWRITE PIC S9(8) COMPUTATIONAL VALUE 1.
PROCEDURE DIVISION.
MOVE Z"DATAIN" TO ENV-NAME
MOVE Z"DSN(PROGRAMMER.TEST.GDGFILE(-1)),SHR" TO ENV-VALUE
MOVE 1 TO ENV-OVERWRITE
CALL "setenv" USING ENV-NAME ENV-VALUE ENV-OVERWRITE.
Notes
Pay special attention when moving DSN value to ENV-VALUE. On my first swing I left out the closing parentheses, most likely because of JCL muscle memory.
Be sure to empty out your DD statement in JCL/Step.
In mainframe COBOL, the FD refers to a SELECT which refers to a DD statement attached to the EXEC PGM statement for your program in the invoking JCL. The DD statement may refer to one or many GDGs. This is determined at compile time.
What I think you are asking for is dynamic allocation of a file at runtime. There are a couple of ways to accomplish that, one is BPXWDYN.
Identification Division.
Program-ID. SOMETEST.
Environment Division.
Input-Output Section.
File-Control.
Select MY-FILE Assign SYSUT1A.
Data Division.
File Section.
FD MY-FILE
Record 80
Block 0
Recording F.
01 MY-FILE-REC PIC X(080).
Working-Storage Section.
01 CONSTANTS.
05 BPXWDYN-PGM PIC X(008) VALUE 'BPXWDYN '.
05 ALCT-LIT-PROC PIC X(035)
VALUE 'ALLOC FI(SYSUT1A) SHR MSG(WTP) DSN('.
05 FREE-LIT-PROC PIC X(016)
VALUE 'FREE FI(SYSUT1A)'.
05 A-QUOTE PIC X(001) VALUE "'".
01 WORK-AREAS.
05 WS-DSN PIC X(044) VALUE 'MY.GDG.BASE'.
05 WS-GDG-NB PIC 999 VALUE ZEROS.
05 BPXWDYN-PARM.
10 PIC S9(004) COMP-5 VALUE +100.
10 BPXWDYN-PARM-TXT PIC X(100).
Procedure Division.
* Construct the allocation string for BPXWDYN.
MOVE SPACES TO BPXWDYN-PARM-TXT
STRING
ALCT-LIT-PROC
DELIMITED SIZE
WS-DSN
DELIMITED SPACE
'(-'
DELIMITED SIZE
WS-GDG-NB
DELIMITED SIZE
')'
DELIMITED SIZE
INTO
BPXWDYN-PARM-TXT
END-STRING
CALL BPXWDYN-PGM USING
BPXWDYN-PARM
END-CALL
IF RETURN-CODE = 0
CONTINUE
ELSE
[error handling]
END-IF
[file I/O with MY-FILE]
MOVE SPACES TO BPXWDYN-PARM-TXT
MOVE FREE-LIT-PROC TO BPXWDYN-PARM-TXT
CALL BPXWDYN-PGM USING
BPXWDYN-PARM
END-CALL
IF RETURN-CODE = 0
CONTINUE
ELSE
[error handling]
END-IF
GOBACK.
This is just freehand, so there may be a syntax error, but I hope I've made the idea clear.
There is another technique, using the C RTL function setenv, documented by IBM here. It looks like it might be simpler but I've never done it that way.

Trouble with ACCEPT "ESC-CODE FROM ESCAPE KEY"

With Microsoft COBOL Compiler version 2.2 and I have this code that completely worked fine.
IDENTIFICATION DIVISION.
PROGRAM-ID. COCENTRY.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT COC-FILE
ASSIGN TO DISK
ORGANIZATION IS INDEXED
ACCESS MODE IS RANDOM
RECORD KEY IS COCNO
FILE STATUS IS FILE-STATUS.
DATA DIVISION.
FILE SECTION.
FD COC-FILE LABEL RECORD IS STANDARD
VALUE OF FILE-ID IS "COC.DAT".
01 COC-RECORD.
03 COCNO PIC 9(5).
03 COCDESC PIC X(40).
WORKING-STORAGE SECTION.
01 FILE-STATUS PIC XX.
01 ESC-CODE PIC 99 VALUE 0.
88 ESC-KEY VALUE 1.
88 F2 VALUE 3.
88 F10 VALUE 11.
01 ERRMSG PIC X(70) VALUE SPACES.
01 ERR PIC 9 VALUE 0.
SCREEN SECTION.
01 FORM1.
03 BLANK SCREEN BACKGROUND-COLOR 1.
03 LINE 1 COLUMN 1 'COCNO'.
03 LINE 2 COLUMN 1 'COCDESC'.
03 LINE 24 COLUMN 1 "Esc=Exit F2=Save F10=Cancel".
03 LINE 25 COLUMN 1 PIC X(70) FROM ERRMSG HIGHLIGHT.
01 FORM2.
03 LINE 1 COLUMN 14 PIC 9(5)
USING COCNO REVERSE-VIDEO.
03 LINE 2 COLUMN 14 PIC X(40)
USING COCDESC REVERSE-VIDEO.
03 LINE 24 COLUMN 1 PIC 99
USING ESC-CODE.
PROCEDURE DIVISION.
MAIN.
OPEN I-O COC-FILE.
IF FILE-STATUS NOT = '00'
OPEN OUTPUT COC-FILE
CLOSE COC-FILE
OPEN I-O COC-FILE.
PERFORM ENTRY1 THRU ENTRYX UNTIL ESC-KEY.
CLOSE COC-FILE.
STOP RUN.
ENTRY1.
MOVE SPACES TO COC-RECORD.
MOVE ZEROES TO COCNO.
ENTRY2.
DISPLAY FORM1 FORM2.
ACCEPT FORM2.
ACCEPT ESC-CODE FROM ESCAPE KEY.
IF F10
MOVE 'Entries canceled...' TO ERRMSG
GO ENTRY1
ELSE IF F2
GO ENTRY3
ELSE IF ESC-KEY
GO ENTRYX
ELSE
GO ENTRY2.
ENTRY3.
MOVE 0 TO ERR.
WRITE COC-RECORD INVALID KEY MOVE 1 TO ERR.
IF ERR = 1
MOVE 'Duplicate key not allowed...' TO ERRMSG
GO ENTRY2
ELSE
MOVE 'Entries recorded...' TO ERRMSG
GO ENTRY1.
ENTRYX.
EXIT.
Now I am using OpenCobol IDE 4.3.0 having GNUCobol version 1.1.0 and I am being prompted with this lines of
syntax error, unexpected "Literal", expecting LEADING or TRAILING
03 LINE 1 COLUMN 1 'COCNO'.
03 LINE 2 COLUMN 1 'COCDESC'.
03 LINE 24 COLUMN 1 "Esc=Exit F2=Save F10=Cancel".
So I fix them by adding VALUE keyword:
03 LINE 1 COLUMN 1 VALUE 'COCNO'.
03 LINE 2 COLUMN 1 VALUE 'COCDESC'.
03 LINE 24 COLUMN 1 VALUE "Esc=Exit F2=Save F10=Cancel".
but as soon as I do this I get a another prompt of
'ACCEPT .. FROM ESCAPE KEY' not implemented
on this line
ACCEPT ESC-CODE FROM ESCAPE KEY.
What could be the possible cause of this? And what could be the fix for this?
Your actual answer is here, https://sourceforge.net/p/open-cobol/discussion/help/thread/26a01c5f/, on the GnuCOBOL part of SourceForge. With minor changes your code will "completely work" with the change you've already made to include the VALUE clause, and if you use release 2.0 or higher of the GnuCOBOL compiler.
Your code may "completely work" but it is spaghetti code.
The term comes from the old days, and relates to the use of many branches in programs, a common practice at that time, but which made trying to follow the logic a process like trying to follow one strand of cooked spaghetti which is part of a pile of cooked spaghetti.
If you change this:
PERFORM ENTRY1 THRU ENTRYX UNTIL ESC-KEY.
To this:
PERFORM ENTRY1 THRU ENTRYX.
Your program will still work. Confused? Yes, because you have spaghetti. Your program flow will only ever get to ENTRYX once. The value when it arrives at ENTRYX is ESC-KEY, but that is superfluous, because it can only ever get there once, when it is ESC-KEY. Clear? No? Because you have spaghetti.
Here is your logic, re-written:
PROCEDURE DIVISION.
OPEN I-O COC-FILE
IF FILE-STATUS NOT = '00'
[the following code is a horror. Deal with this outside the
program. Crash for an unexpected FILE STATUS on OPEN]
OPEN OUTPUT COC-FILE
CLOSE COC-FILE
OPEN I-O COC-FILE
END-IF
PERFORM PROCESS-USER-INPUT
UNTIL ESC-KEY
CLOSE COC-FILE
IF FILE-STATUS NOT = '00'
[something bad has happened, so don't go quietly]
END-IF
GOBACK
.
PROCESS-USER-INPUT.
PERFORM BLANK-OUTPUT-RECORD
PERFORM PROCESS-COC
UNTIL ESC-KEY
.
PROCESS-COC.
DISPLAY FORM1 FORM2
ACCEPT FORM2
ACCEPT ESC-CODE FROM ESCAPE KEY
EVALUATE TRUE
WHEN F10
MOVE 'Entries canceled...' TO ERRMSG
WHEN F2
PERFORM CREATE-OUTPUT
END-EVALUATE
.
CREATE-OUTPUT.
WRITE COC-RECORD
IF ATTEMPT-TO-WRITE-DUPLICATE [22 on the FILE STATUS field]
MOVE 'Duplicate key not allowed...' TO ERRMSG
ELSE
MOVE 'Entries recorded...' TO ERRMSG
PERFORM BLANK-OUTPUT-RECORD
END-IF
.
BLANK-OUTPUT-RECORD.
MOVE SPACES TO COC-RECORD
MOVE ZEROES TO COCNO
.
Does that make your program look simpler? Easier to follow, change, understand what it does when someone else looks at it (or when you do in two weeks time)?
There are other things, like why set COC-RECORD to space, and then COCNO to zero? Move the spaces to COCDESC.
Make your data/procedure names good and descriptive. FILE STATUS having a good name (don't call it FILE-STATUS) and one per file when you have more than one file. Use full-stops/periods only where you have to, and use scope-delimiters for all conditional constructs that you use. Use FILE STATUS checking for all IO, and don't use the tortuous AT on IO.
If you look now the first code in your program is quite long, executes only once, and is (should be) irrelevant to the business function of your program. So stick all that in a paragraph, and PERFORM that. Same for the close. Then you can have as much code as you need when starting up and closing down, without making your program more difficult to follow.
The screen and keyboard I/O was a MicroSoft Cobol specific flavor. You will likely need to tweak that a bit to make it work with OpenCobol.
PROCEDURE DIVISION.
SET ENVIRONMENT 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
SET ENVIRONMENT 'COB_SCREEN_ESC' TO 'Y'.
Escape: IF cob-crt-status = 2005......
Enter: IF cob-crt-status = 0........
F1: IF cob-crt-status = 1001......
F2: IF cob-crt-status = 1002......

Cobol, Code 65 File Locked

I am trying to access the same file to do two certain tasks. The first task is to update, add, and delete records. Access has to be random. The second task is to display all records on console. Access has to be sequential. I receive code 65 File locked from COBOL because the program is trying to access the same file twice the same time. Is there any way to fix this error? Or is there an different way to do this? Or do I have to write a separate program to display the record on console? I am stuck!
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT MAST-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-5\SALES.IND.TXT'
ORGANIZATION IS INDEXED
ACCESS IS RANDOM
RECORD KEY M-SALESPERSON-NUM.
SELECT MAST2-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-5\SALES.IND.TXT'
ORGANIZATION IS INDEXED
ACCESS IS SEQUENTIAL
RECORD KEY M2-SALESPERSON-NUM.
DATA DIVISION.
FILE SECTION.
FD MAST-FILE
LABEL RECORDS ARE STANDARD.
01 MAST-RECORD.
05 M-SALESPERSON-NUM PIC XXX.
05 M-CUSTOMER-NAME PIC X(15).
05 M-TOTAL-SALES PIC 9(5)V99.
05 M-COST-OF-SALES PIC 9(4)V99.
FD MAST2-FILE
LABEL RECORDS ARE STANDARD.
01 MAST2-RECORD.
05 M2-SALESPERSON-NUM PIC X(3).
05 M2-SALESPERSON-NAME PIC X(15).
05 M2-TOTAL-SALES PIC 9(5)V99.
05 M2-COST-OF-SALES PIC 9(4)V99.
WORKING-STORAGE SECTION.
01 SALES-DATA.
05 SALESPERSON-NUM PIC X(3).
05 SALESPERSON-NAME PIC X(15).
05 TOTAL-SALES PIC 9(5)V99.
05 COST-OF-SALES PIC 9(4)V99.
01 OUTPUT-RECORD.
05 PIC X(1) VALUE SPACES.
05 O-SALESPERSON-NUM PIC X(3).
05 PIC X(3) VALUE SPACES.
05 O-SALESPERSON-NAME PIC X(3).
05 PIC X(3) VALUE SPACES.
05 O-TOTAL-SALES PIC 9(5)V99.
05 PIC X(3) VALUE SPACES.
05 O-COST-OF-SALES PIC 9(4)V99.
01 PROGRAM-DATA-ITEMS.
05 I-SALESPERSON-NUM PIC XXX.
05 WAIT-OK PIC X.
05 CHOICE PIC 9 VALUE 0.
05 READ-OK PIC X.
05 REWRITE-OK PIC X.
05 DELETE-OK PIC X.
PROCEDURE DIVISION.
10-MAINLINE.
OPEN I-O MAST-FILE
OPEN INPUT MAST2-FILE
PERFORM 20-PROCESS-LOOP
CLOSE MAST-FILE
MAST2-FILE
STOP RUN.
20-PROCESS-LOOP.
PERFORM UNTIL CHOICE = 5
PERFORM 30-DISPLAY-MENU
EVALUATE CHOICE
WHEN 1
PERFORM 40-UPD-SALES
WHEN 2
PERFORM 90-ADD-SALES
WHEN 3
PERFORM 110-DELETE-SALES
WHEN 4
PERFORM 120-DISPLAY-SALES
END-EVALUATE
END-PERFORM.
30-DISPLAY-MENU.
DISPLAY 'SALES MAINTENANCE SYSTEM'
DISPLAY ' '
DISPLAY ' SELECT ONE:'
DISPLAY ' '
DISPLAY ' 1. UPDATE SALES RECORD'
DISPLAY ' 2. ADD SALES RECORD'
DISPLAY ' 3. DELETE SALES RECORD'
DISPLAY ' 4. DISPLAY SALES RECORD'
DISPLAY ' 5. QUIT'
DISPLAY ' '
DISPLAY 'ENTER CHOICE (1 - 5): ' WITH NO ADVANCING
ACCEPT CHOICE
PERFORM UNTIL CHOICE >= 1 AND <= 5
DISPLAY ' '
DISPLAY 'ERROR: ENTER CHOICE (1 - 5): ' WITH NO ADVANCING
ACCEPT CHOICE
END-PERFORM.
40-UPD-SALES.
DISPLAY 'UPDATE SALES: ENTER SALESPERSON NUMBER: ' WITH NO ADVANCING
ACCEPT SALESPERSON-NUM
MOVE SALESPERSON-NUM TO M-SALESPERSON-NUM
PERFORM 50-READ-RECORD
IF READ-OK = 'N'
DISPLAY 'RECORD DOES NOT EXIST - PRESS ENTER'
ACCEPT WAIT-OK
ELSE
DISPLAY SALES-DATA
PERFORM 100-INPUT-NEW-RECORD
PERFORM 60-REWRITE-RECORD
END-IF.
50-READ-RECORD.
MOVE 'Y' TO READ-OK
READ MAST-FILE INTO SALES-DATA
INVALID KEY
MOVE 'N' TO READ-OK
END-READ.
60-REWRITE-RECORD.
REWRITE MAST-RECORD FROM SALES-DATA
INVALID KEY
DISPLAY 'REWRITE ERROR: SALESPERSON NUMBER ' SALESPERSON-NUM
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-REWRITE.
70-WRITE-RECORD.
MOVE 'Y' TO REWRITE-OK
WRITE MAST-RECORD FROM SALES-DATA
INVALID KEY
MOVE 'N' TO REWRITE-OK
END-WRITE
IF REWRITE-OK = 'N'
DISPLAY 'WRITE ERROR: SALESPERSON NUMBER ' SALESPERSON-NUM
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-IF.
80-DELETE-RECORD.
MOVE 'Y' TO DELETE-OK
DELETE MAST-FILE
INVALID KEY
MOVE 'N' TO DELETE-OK
END-DELETE
IF REWRITE-OK = 'N'
DISPLAY 'WRITE ERROR: SALESPERSON NUMBER ' SALESPERSON-NUM
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-IF.
90-ADD-SALES.
DISPLAY 'ADD SALES RECORD: ENTER SALESPERSON NUMBER: ' WITH NO ADVANCING
ACCEPT SALESPERSON-NUM
MOVE SALESPERSON-NUM TO M-SALESPERSON-NUM
PERFORM 50-READ-RECORD
IF READ-OK = 'Y'
DISPLAY 'RECORD ALREADY EXISTS - PRESS ENTER'
ACCEPT WAIT-OK
ELSE
PERFORM 100-INPUT-NEW-RECORD
PERFORM 70-WRITE-RECORD
IF REWRITE-OK = 'Y'
DISPLAY 'RECORD ' SALESPERSON-NUM ' ADDED TO FILE'
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-IF
END-IF.
100-INPUT-NEW-RECORD.
MOVE SALESPERSON-NUM TO M-SALESPERSON-NUM
DISPLAY ' ENTER SALESPERSON NAME: ' WITH NO ADVANCING
ACCEPT SALESPERSON-NAME
DISPLAY ' ENTER TOTAL SALES: ' WITH NO ADVANCING
ACCEPT TOTAL-SALES
DISPLAY ' ENTER COST OF SALES: ' WITH NO ADVANCING
ACCEPT COST-OF-SALES.
110-DELETE-SALES.
DISPLAY 'DELETE SALES RECORD: ENTER SALESPERSON NUMBER: ' WITH NO ADVANCING
ACCEPT SALESPERSON-NUM
MOVE SALESPERSON-NUM TO M-SALESPERSON-NUM
PERFORM 50-READ-RECORD
IF READ-OK = 'N'
DISPLAY 'RECORD DOES NOT EXIST - PRESS ENTER'
ACCEPT WAIT-OK
ELSE
PERFORM 80-DELETE-RECORD
IF DELETE-OK = 'Y'
DISPLAY 'RECORD DELETED - PRESS ENTER'
ACCEPT WAIT-OK
END-IF
END-IF.
120-DISPLAY-SALES.
MOVE SALESPERSON-NUM TO M2-SALESPERSON-NUM
MOVE SALESPERSON-NAME TO M2-SALESPERSON-NAME
MOVE TOTAL-SALES TO M2-TOTAL-SALES
MOVE COST-OF-SALES TO M2-COST-OF-SALES
READ MAST2-FILE
AT END MOVE HIGH-VALUES TO M2-SALESPERSON-NUM
END-READ
PERFORM UNTIL M2-SALESPERSON-NUM = HIGH-VALUES
MOVE M2-SALESPERSON-NUM TO O-SALESPERSON-NUM
MOVE M2-SALESPERSON-NAME TO O-SALESPERSON-NAME
MOVE M2-TOTAL-SALES TO O-TOTAL-SALES
MOVE M2-COST-OF-SALES TO O-COST-OF-SALES
DISPLAY OUTPUT-RECORD
READ MAST2-FILE
AT END MOVE HIGH-VALUES TO M2-SALESPERSON-NUM
END-READ
END-PERFORM.
end program Program1.
When you open a file I-O, that means you open it for Input and Output. Get rid of your second file.
To position your file for displaying the data, you can READ with a KEY and then READ ... NEXT ..., or you can use START ... and then READ ... NEXT.
Always use the FILE STATUS in the ASSIGN. Then use the file-status field you tell COBOL to put the file status in to, to check the previous IO. Use it for end-of-file (value of "10"). Use 88s. You don't then need the INVALID KEY and AT END and all the END- statements associated with IO can go, because you then don't have a built-in condition with the IO. Which will simplify things.
Your structure is very good for a beginner. Refreshing to see no PERFORM ... THRU ....
I'd suggest you try the effect of a single full-stop/period in column 12 on a line of its own. You'll then be able to move the last line of code from a paragraph without having to think about the full-stop/period attached to it (because it isn't attached to it).
Use more PERFORMs. OPEN and CLOSE are not vital to the logic of the program. Hide them away in paragraphs, do the FILE STATUS checking on them. Same with the READ/WRITE/DELETE and any other IO statements you end up with. Hide them in well-named procedures which you PERFORM.
Consider the size (number of lines) of some of your IFs. Put the code in a well-named procedure, and the code can be "read" at a high level by a human, with the detail only being looked at if needed.
Do not, do not, do not, mess around with two files. Do not, do not, do not OPEN the same file twice (I've written a few COBOL programs in my time, and I've never, ever, considered that a reasonable way to achieve anything, let alone the simple task you have).
You may want to consider DYNAMIC instead of RANDOM (this is what it is for). You use RANDOM if you are only doing random access. You actually want to do sequential access as well (look for references to skip-sequential access for further discussion).
SELECT MAST-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-5\SALES.IND.TXT'
ORGANIZATION IS INDEXED
ACCESS IS RANDOMREWRITE-OK = 'N'
RECORD KEY M-SALESPERSON-NUM
FILE STATUS IS W-MAST-FILE-STATUS.
...
01 W-MAST-FILE-STATUS PIC XX.
88 W-MAST-FILE-LAST-IO-OK VALUE "00".
88 W-MAST-FILE-EOF VALUE "10".
88 W-MAST-FILE-REC-NOT-FOUND VALUE "23".
88 W-MAST-FILE-OR-OR-NOT-FOUND VALUE "00" "23".
...
50-READ-RECORD.
MOVE 'Y' TO READ-OK
READ MAST-FILE INTO SALES-DATA
INVALID KEY
MOVE 'N' TO READ-OK
END-READ.
Becomes:
50-READ-RECORD.
READ MAST-FILE KEY key-name INTO SALES-DATA
IF NOT ( W-MAST-FILE-OR-OR-NOT-FOUND )
some code to deal with the pickle, which is nothing to do with
business-logic, so hide it away
END-IF
.
80-DELETE-RECORD.
MOVE 'Y' TO DELETE-OK
DELETE MAST-FILE
INVALID KEY
MOVE 'N' TO DELETE-OK
END-DELETE
IF REWRITE-OK = 'N'
DISPLAY 'WRITE ERROR: SALESPERSON NUMBER ' SALESPERSON-NUM
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-IF.
Becomes:
80-DELETE-RECORD.
DELETE MAST-FILE
IF NOT W-MAST-FILE-LAST-IO-OK
DISPLAY 'WRITE ERROR: SALESPERSON NUMBER ' SALESPERSON-NUM
DISPLAY 'PRESS ENTER TO CONTINUE'
ACCEPT WAIT-OK
END-IF
.
Each IO paragraph becomes self-contained, self-verifying, and the FILE STATUS field naturally bears only good conditions when you are in your business logic. The "can't happen" (but will, one day) you deal with in these paragraphs.
You code elsewhere simplifies. Your number of "flags" is reduced (the value of the FILE STATUS field replaces the need for the flags) your IOs have no conditional part, so don't need the END- scope delimiter.
A tip about numbering paragraphs. Don't do it until you have tested sufficiently that you are happy with the structure of the logic. Once you are happy with that, rearrange the paragraphs so that the paragraph is always physically after the PERFORM of it. Then put the numbers on. The physical layout of your code then represents the structure of your program logic.
If you number first, you'll end up with the situation you have - you have numbers, but they infer nothing. It is much more tedious to "renumber" paragraphs than it is to add paragraph numbers where there were none (use the power of the editor/utilities available to you to do this numbering).

Resources