Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Help with my coding 2

Status
Not open for further replies.

scurf

Programmer
Feb 5, 2002
19
0
0
GB
I seem to get only a blank output with headings on my coding. The program reads my data file which I have on floppy disk and is supposed to print invalid data items on a printed error report.
Valid data is supposed to save back to disk as a validated file to be used in a further program.
Could anyone please suggest some additional coding or suggest where I am going wrong befor I tear my last remaining hair out. Sorry about the layout, I am unsure how to attach the file to my thread!!!!

Cheers GAZ Sausages@scurfield.fsnet.co.uk

IDENTIFICATION DIVISION.
PROGRAM-ID. 495955P1.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT TRANSACTION-FILE ASSIGN TO "495955TD.DAT"
ORGANIZATION LINE SEQUENTIAL.
SELECT VALID-FILE ASSIGN TO "495955VF.DAT"
ORGANIZATION LINE SEQUENTIAL.
SELECT INVALID-FILE ASSIGN TO PRINTER.
DATA DIVISION.
FILE SECTION.
FD TRANSACTION-FILE.
01 I-R-RECORD.
03 RECORD-TYPE PIC X.
88 VALID-TYPE VALUES "I" "R" "D" "C".
03 IN-CUSTCODE.
05 INCODE-DIGIT.
07 INCODE-DGT PIC 9 OCCURS 4.
05 INCODE-CHKDGT PIC X.
03 IN-PARTNO.
05 INPART-DIGIT.
07 INPART-DGT PIC 9 OCCURS 5.
05 INPART-CHKDGT PIC X.
03 IN-QUANTITY.
05 IN-QUANT PIC X(4).
01 DELETION.
03 PIC X(6).
01 CREATION.
03 PIC X(6).
03 CUST-NAME PIC X(20).
03 CUST-ADDRESS PIC X(60).
03 CUST-BAL.
05 CUST-BALANCE PIC X(9).
03 CREDIT-LIM.
05 CREDIT-LIMIT PIC X(7).
FD VALID-FILE.
01 VALID-REC PIC X(102).
FD INVALID-FILE
LINAGE IS 60 LINES
WITH FOOTING AT 56
LINES AT TOP 2
LINES AT BOTTOM 4.
01 PRINT-RECORD PIC X(120).
WORKING-STORAGE SECTION.
01 W-REC-COUNT PIC 999 VALUE 0.
01 W-PAGENO PIC 99 VALUE 0.
01 W-LINENO PIC 99.
01 W-DOS-DATE.
03 W-DOS-YEAR PIC 99.
03 W-DOS-MONTH PIC 99.
03 W-DOS-DAY PIC 99.
01 W-IN-DATE.
03 W-IN-YEAR PIC 99.
03 W-IN-MONTH PIC 99.
03 W-IN-YEAR PIC 99.
*WS SECTION FOR BREAKING THE CUSTOMER CODE INTO *PARTS FOR
*MODULUS 11 CHECK
01 W-CUSTCODE-WEIGHTS VALUE "5432".
03 W-C-WT PIC 9 OCCURS 4.
01 W-C-SUB PIC 9.
01 W-C-PRODUCT PIC 99.
01 W-C-SUM PIC 999.
01 W-C-MOD PIC 99 VALUE 11.
01 W-C-REM PIC 99.
01 W-C-CHK.
03 W-C-CHK-NUM PIC 9.
*BREAK THE PART NUMBER DOWN FOR MODULUS 11 CHECK
01 W-PARTNO-WEIGHTS VALUE "65432".
03 W-P-WT PIC 9 OCCURS 5.
01 W-P-SUB PIC 9.
01 W-P-PRODUCT PIC 99.
01 W-P-SUM PIC 999.
01 W-P-MOD PIC 99 VALUE 11.
01 W-P-REM PIC 99.
01 W-P-CHK.
03 W-P-CHK-NUM PIC 9.
01 W-ERROR-REC-FLAG PIC X VALUE "N".
88 VALID-RECORD VALUE "Y".
01 END-TRANSACTION-FILE-FLAG PIC X VALUE "N".
88 END-OF-TRANSACTION-FILE VALUE "Y".
01 P-HDG.
03 PIC X(4) VALUE
"DATE".
03 PIC X VALUE SPACES.
03 PIC X(10) VALUE SPACES.
03 P-HDG-DAY PIC 99.
03 PIC X VALUE "/".
03 P-HDG-MONTH PIC 99.
03 PIC X VALUE "/".
03 P-HDG-YEAR PIC 99.
03 PIC X(36) VALUE
"ZENITH-PAINTS-INVALID-RECORDS-REPORT".
03 PIC X(31) VALUE
"PAGE.".
03 P-PAGENO PIC Z9.
01 P-SUB-HDG.
03 PIC X(11) VALUE
"RECORD-TYPE".
03 PIC X(13) VALUE
"CUSTOMER-CODE".
03 PIC X(15) VALUE
"PART-NUMBER".
03 PIC X(16) VALUE
"QUANTITY".
03 PIC X(16) VALUE
"REJECTION REASON".
01 P-DETAIL-LINE.
03 PIC X(15) VALUE SPACES.
03 P-RECORD-TYPE PIC X.
03 PIC X(15) VALUE SPACES.
03 P-CUST-CODE PIC 9(5).
03 PIC X(23) VALUE SPACES.
03 P-PART-NO PIC 9(6).
03 PIC X(20) VALUE SPACES.
03 P-IR-QUANT PIC 9(4).
03 PIC X(12) VALUE SPACES.
03 P-REJECTION-REASON PIC X(21).
01 P-FILE-EMPTY-LINE.
03 PIC X(35) VALUE
"NO RECORDS ON THIS FILE".
01 P-FINAL-LINE.
03 PIC X(35) VALUE
"*NO MORE INVALID RECORDS*".
PROCEDURE DIVISION.
CONTROL-PARAGRAPH.
PERFORM INITIAL-PROCESS
PERFORM MAIN-PROCESS UNTIL END-OF-TRANSACTION-FILE
PERFORM TERMINATION
STOP RUN.
INITIAL-PROCESS.
OPEN INPUT TRANSACTION-FILE
OUTPUT INVALID-FILE
VALID-FILE
ACCEPT W-DOS-DATE FROM DATE
*DOS stores the date in YYMMDD format.
*Adjustment is needed for DDMMYY format in the heading.
MOVE W-DOS-YEAR TO P-HDG-YEAR
MOVE W-DOS-MONTH TO P-HDG-MONTH
MOVE W-DOS-DAY TO P-HDG-DAY
PERFORM PRINT-HEADINGS
READ TRANSACTION-FILE AT END
DISPLAY "FILE CONTAINS NO RECORDS*"
MOVE "Y" TO END-TRANSACTION-FILE-FLAG
END-READ.
PRINT-HEADINGS.
MOVE 0 TO W-LINENO
ADD 1 TO W-PAGENO
MOVE W-PAGENO TO P-PAGENO
WRITE PRINT-RECORD FROM P-HDG AFTER PAGE
WRITE PRINT-RECORD FROM P-SUB-HDG AFTER 1
MOVE SPACES TO PRINT-RECORD
WRITE PRINT-RECORD AFTER 1.
MAIN-PROCESS.
IF RECORD-TYPE = "I" OR "R" THEN
PERFORM VALIDATE-CUSTCODE
PERFORM VALIDATE-PARTNO
PERFORM VALIDATE-QUANTITY
WRITE VALID-REC
ELSE
IF RECORD-TYPE = "D" THEN
PERFORM VALIDATE-CUSTCODE
WRITE VALID-REC
ELSE
IF RECORD-TYPE = "C" THEN
PERFORM VALIDATE-CUSTCODE
PERFORM VALIDATE-CUST-NAME
PERFORM VALIDATE-CUST-BALANCE
PERFORM VALIDATE-CREDIT-LIMIT
WRITE VALID-REC
ELSE
IF W-REC-COUNT = 0 THEN
PERFORM PRINT-HEADINGS
WRITE PRINT-RECORD FROM
P-FILE-EMPTY-LINE AFTER 2
END-IF
END-IF
END-IF
MOVE "Y" TO W-ERROR-REC-FLAG
MOVE "INVALID RECORD TYPE" TO P-REJECTION-REASON.
END-IF.
VALIDATE-CUSTCODE.
*this procedure will validate the Customer Code using Modul us 11
*the 5th digit is the check digit
IF INCODE-DIGIT NOT NUMERIC THEN
MOVE "Y" TO W-ERROR-REC-FLAG
MOVE "CUSTOMER CODE NOT NUMERIC" TO P-REJECTION-REASON
ELSE
MOVE ZERO TO W-C-SUM
PERFORM VARYING W-C-SUB FROM 1 BY 1
UNTIL W-C-SUB > 4
MULTIPLY INCODE-DGT (W-C-SUB) BY W-C-WT (W-C-SUB)
GIVING W-C-PRODUCT
ADD W-C-PRODUCT TO W-C-SUM
END-PERFORM
END-IF
DIVIDE W-C-SUM BY W-C-MOD GIVING W-C-SUM
REMAINDER W-C-REM
IF W-C-REM > 1 THEN
SUBTRACT W-C-REM FROM W-C-MOD GIVING W-C-CHK-NUM
ELSE
IF W-C-REM = 1 THEN
MOVE ZERO TO W-C-CHK
ELSE
MOVE "X" TO W-C-CHK
END-IF
END-IF
IF INCODE-CHKDGT NOT = W-C-CHK THEN
MOVE "INVALID CUSTOMER CODE" TO P-REJECTION-REASON
END-IF.
VALIDATE-PARTNO.
*this procedure will validate the part number using Modulus
*11 the 6th digit is the check digit.
IF INPART-DIGIT NOT NUMERIC THEN
MOVE "Y" TO W-ERROR-REC-FLAG
MOVE "PART NUMBER NOT NUMERIC" TO P-REJECTION-REASON
ELSE
MOVE ZERO TO W-P-SUM
PERFORM VARYING W-P-SUB FROM 1 BY 1
UNTIL W-P-SUB > 5
MULTIPLY INPART-DGT (W-P-SUB) BY W-P-WT (W-P-SUB)
GIVING W-P-PRODUCT
ADD W-P-PRODUCT TO W-P-SUM
END-PERFORM
END-IF
DIVIDE W-P-SUM BY W-P-MOD GIVING W-P-SUM
REMAINDER W-P-REM
IF W-P-REM > 1 THEN
SUBTRACT W-P-REM FROM W-P-MOD GIVING W-P-CHK-NUM
ELSE
IF W-P-REM = 1 THEN
MOVE ZERO TO W-P-CHK
ELSE
MOVE "X" TO W-P-CHK
END-IF
END-IF
IF INPART-CHKDGT NOT = W-C-CHK THEN
MOVE "INVALID CUSTOMER CODE" TO P-REJECTION-REASON
END-IF
IF W-P-CHK-NUM NOT = W-P-CHK THEN
MOVE "INVALID PART NUMBER" TO P-REJECTION-REASON
MOVE "Y" TO W-ERROR-REC-FLAG
END-IF.
VALIDATE-QUANTITY.
IF IN-QUANT NOT NUMERIC THEN
MOVE "QUANTITY INVALID" TO P-REJECTION-REASON
MOVE "Y" TO W-ERROR-REC-FLAG
END-IF.
VALIDATE-CUST-NAME.
IF CUST-NAME = SPACES THEN
MOVE "NO CUSTOMER NAME" TO P-REJECTION-REASON
MOVE "Y" TO W-ERROR-REC-FLAG
END-IF.
VALIDATE-CUST-BALANCE.
IF CUST-BALANCE NOT NUMERIC THEN
MOVE "NON NUMERIC BALANCE" TO P-REJECTION-REASON
MOVE "Y" TO W-ERROR-REC-FLAG
END-IF.
VALIDATE-CREDIT-LIMIT.
IF CREDIT-LIMIT NOT NUMERIC THEN
MOVE "NON NUMERIC CREDIT LIMIT" TO P-REJECTION-REASON
MOVE "Y" TO W-ERROR-REC-FLAG
END-IF.
WRITE VALID-REC FROM CREATION.
TERMINATION.
CLOSE TRANSACTION-FILE
CLOSE INVALID-FILE
CLOSE VALID-FILE
STOP RUN.


 
Hi GAZ,

The general rule, when a program doesn't abend, but gives improper o/p, is to insert display stmts (usually after pgraph heads and/or at decision points. That is, if you're not lucky enough to have debugging tools like Expediter or ReadyTrace.

One usually has an idea of how a pgm should execute given its i/p data. If the pgm deviates from the expected path, as evidenced by the display o/p, insert displays of the data and/or the paths taken (or not taken), as a result of the pgm testing the data, to home in on the logic error.

Of course, you can peruse the code to solve the problem, but, as you've noticed, it plays havoc w/the hairline.

Regards, Jack.
 
Well, scurf, you've got a ways to go on this assignment.

I can suggest several ways to go about solving the problem you pose:

1. Code walk through. Take the first few (invalid) records of your input file and walk through the code with each of them. Are you sure each transaction follows the logic path that you expect it should? E.g. what happens if the RECORD-CODE is SPACES? Consider a flowchart to help analyze what's going on.

2. Where is the WRITE PRINT-RECORD statement that will be writing out the error records to the report? Why is it not being executed when you expect it to?

3. It would seem that the valid record file contains both valid and invalid records. Why are invalid records being written to the valid record file? Back track from there.

4. Next time consider using a "top-down" development approach. For example, write no more than 1 paragraph at a time and test after each paragraph is done. If you need to perform a paragraph that isn't written yet, simply provide a stub that is either empty or performs some simple action like setting a switch(e.g. you might have a paragraph to read a record from a file and do something with it; you could stub it out by simply having the paragraph set the file's EOF switch to simulate reading an empty file.), or performing a DISPLAY.

5. As a style issue, I'd suggest dropping the THEN's on the IFs and lining up the ELSE or ELSE IFs with their respective IFs/END-IFs. Of course, that's just a suggestion; others will have strong feelings otherwise, I'm sure. In any event, try to pick a way of laying out your code and be CONSISTENT about it.

Good luck.

3gm
 
Through a quick scan, I think no moves are happening to VALID-REC, which is being written.

Please check.

Sorry, if I am wrong.
 
Thanks for all the help, I will put a couple of hours aside this weekend to scan my coding..Must remember to buy some black ink for the printer!!..
The reason some of my coding may look daft is because I did not have a compiler when I started it, I just recently purchased MicroFocus Cobol and I am still learning how to make best use of it.....

Thanks.



GAZ
 
I didn't know you can put an 88 in an FD record??

Is that an add-on or in the standard or what? If you do not like my post feel free to point out your opinion or my errors.
 
Been standard for a long time. Tom Morrison
 
88-levels are not used nearly as much or as well as they should be. They can be used in the FILE, WORKING-STORAGE, and LINKAGE sections. They can be used on group items, elementary items, even un-named filler, e.g.:

Code:
01  WS-SWITCHES VALUE ALL "N".
    05                            PIC X.
         88  EOF-INPUT-FILE       VALUE "Y".
    05                            PIC X.
         88  SOME-OTHER-SWITCH    VALUE "Y".
[\CODE]

They can also have multiple values and ranges:

[code]
     88  VALID-PRODUCT-TYPE       VALUES 1 
                                         2
                                         7 THRU 9
                                         11.
[\CODE]

I find they make my code much more readable and maintainable.

Glenn
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top