IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Unmatched records from 1st file needs to be write in output


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
mallem_ravi
Warnings : 1

New User


Joined: 29 Mar 2007
Posts: 10
Location: India

PostPosted: Thu May 31, 2007 1:02 pm
Reply with quote

I had a requirement, that I had 2 similar files having same length and which i need to write the unique records from 1st file, for that i read the 1st file as master file and reading the second file for the unmatched records, in this i am getting status code 46 for the 2nd file, can anybody please let me know if any change need in the below logic in reading the 2nd file, to write the Unique records from the 1st file to output file.

ex:
file1
456
487
586
259

file2:
487
586

Output file:

456
259





Code:

 IDENTIFICATION DIVISION.                                   
 PROGRAM-ID.    APXDIFF1.                                   
*------------------------------------------------------------
/                                                           
 ENVIRONMENT DIVISION.                                       
 CONFIGURATION SECTION.                                     
 INPUT-OUTPUT SECTION.                                       
 FILE-CONTROL.                                               
     SELECT  BNC-DUE-FILE            ASSIGN TO UT-S-ISEQL01.
     SELECT  BNC-COR-DUE-FILE        ASSIGN TO UT-S-ISEQL02.
     SELECT  BNC-DIFF-FILE           ASSIGN TO UT-S-OSEQL01.
 DATA DIVISION.                                 
 FILE SECTION.                                   
                                                 
 FD  BNC-DUE-FILE                               
     BLOCK CONTAINS 0 RECORDS                   
     RECORDING MODE IS F.                       
                                                 
 01  BNC-DUE-FILE-REC.                           
     05 FILLER                     PIC X(10).   
     05 PT-CONTRACT-DUE-NR         PIC X(8).     
     05 FILLER                     PIC X(537).   
     05 PT-POLICY-DUE-NR           PIC X(15).   
     05 FILLER                     PIC X(7430). 
/                                               
 FD  BNC-COR-DUE-FILE                           
     BLOCK CONTAINS 0 RECORDS                   
     RECORDING MODE IS F.                       
                                                         
 01  BNC-COR-DUE-FILE-REC.                               
     05 FILLER                     PIC X(10).           
     05 PT-CONTRACT-COR-NR         PIC X(8).             
     05 FILLER                     PIC X(537).           
     05 PT-POLICY-COR-NR           PIC X(15).           
     05 FILLER                     PIC X(7430).         
/                                                       
 FD  BNC-DIFF-FILE                                       
     BLOCK CONTAINS 0 RECORDS                           
     RECORDING MODE IS F.                               
                                                         
 01  BNC-DIFF-FILE-REC         PIC X(8000).             
 WORKING-STORAGE SECTION.                             
                                                     
     COPY BCF924TS.                                   
/                                                     
/                                                             
 PROCEDURE DIVISION.                                         
 0000-MAINLINE.                                               
**************************************************************
*                                                            *
**************************************************************
                                                             
     PERFORM 0100-INITIALIZE.                                 
                                                             
     IF ERROR-NOT-FOUND                                       
         PERFORM 1000-MAIN-PROCESSING                         
     END-IF.                                                 
                                                             
     PERFORM 9500-PROGRAM-TERMINATION.                       
                                                             
     MOVE RETURN-CODE-SA         TO RETURN-CODE.             
     STOP RUN.                                               
**************************************************************

 0100-INITIALIZE.                                             
**************************************************************
*                                                            *
     MOVE 'N'                       TO ERROR-FOUND-SW.         
                                                               
     OPEN  INPUT   BNC-DUE-FILE                               
                   BNC-COR-DUE-FILE                           
           OUTPUT  BNC-DIFF-FILE.     
 ************************************************************* 1000-MAIN-PROCESSING.                                       
*************************************************************                                                           
     PERFORM 1500-BNC-DUE-FILE.                               
                                                             
     PERFORM 1100-PROCESS-BNC-DUE-FILE UNTIL                 
         (BNC-DUE-FILE-EOF = 'Y' ) OR                         
         ERROR-FOUND.       
     IF ERROR-NOT-FOUND                         
         PERFORM 3000-WRITE-BNC-DIFF-FILE       
     END-IF.                                     
 ************************************************************* 1100-PROCESS-BNC-DUE-FILE.                                   
*************************************************************
     INITIALIZE BNC-DIFF-FILE-REC                             
     INITIALIZE BCF924-DUE-REC                               
     MOVE SPACES TO  BNC-DIFF-FILE-REC                       
     MOVE SPACES TO  BCF924-DUE-REC                           
     PERFORM 1600-BNC-COR-DUE-FILE UNTIL                     
           ((BNC-COR-DUE-FILE-EOF = 'Y') OR                 
             ((PT-CONTRACT-DUE-NR = PT-CONTRACT-COR-NR) AND   
              (PT-POLICY-DUE-NR = PT-POLICY-COR-NR))).         
     IF (( PT-CONTRACT-DUE-NR NOT =  PT-CONTRACT-COR-NR) AND 
        (PT-POLICY-DUE-NR NOT = PT-POLICY-COR-NR ))           
         PERFORM 3000-WRITE-BNC-DIFF-FILE                     
     END-IF.                                                 
     PERFORM 1500-BNC-DUE-FILE.                               

     MOVE SPACES TO    PT-CONTRACT-COR-NR                         
                     PT-POLICY-COR-NR.                           
                                                             
*************************************************************
 1500-BNC-DUE-FILE.                                               
*************************************************************                                                       
     READ BNC-DUE-FILE                                           
         AT END MOVE 'Y'            TO BNC-DUE-FILE-EOF.         
     IF BNC-DUE-FILE-EOF = 'N'                                   
         ADD 1 TO BNC-DUE-FILE-READ-AA                           
         MOVE 'N' TO BNC-COR-DUE-FILE-EOF                         
     END-IF.                                                     
/                                                                 
*                                                                 
*************************************************************
 1600-BNC-COR-DUE-FILE.                                       
*************************************************************
      READ BNC-COR-DUE-FILE INTO BCF924-DUE-REC                 
        AT END MOVE 'Y'            TO BNC-COR-DUE-FILE-EOF.             

************************************************************* 3000-WRITE-BNC-DIFF-FILE.                                   
*************************************************************     MOVE BNC-DUE-FILE-REC           TO BNC-DIFF-FILE-REC     
     WRITE BNC-DIFF-FILE-REC.                                 
                         
**************************************************************
 9500-PROGRAM-TERMINATION.                                     
**************************************************************----CLOSE ALL FILES.                                         
                                                               
                                                               
     CLOSE BNC-DUE-FILE                                       
           BNC-COR-DUE-FILE                                   
           BNC-DIFF-FILE.
Back to top
View user's profile Send private message
mallem_ravi
Warnings : 1

New User


Joined: 29 Mar 2007
Posts: 10
Location: India

PostPosted: Thu May 31, 2007 1:08 pm
Reply with quote

I had a requirement, that I had 2 similar files having same length and which i need to write the unique records from 1st file, for that i read the 1st file as master file and reading the second file for the unmatched records, in this i am getting status code 46 for the 2nd file, can anybody please let me know if any change need in the below logic in reading the 2nd file, to write the Unique records from the 1st file to output file.

ex:
file1
456
487
586
259

file2:
487
586

Output file:

456
259






IDENTIFICATION DIVISION.
PROGRAM-ID. APXDIFF1.
*------------------------------------------------------------
/
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT BNC-DUE-FILE ASSIGN TO UT-S-ISEQL01.
SELECT BNC-COR-DUE-FILE ASSIGN TO UT-S-ISEQL02.
SELECT BNC-DIFF-FILE ASSIGN TO UT-S-OSEQL01.
DATA DIVISION.
FILE SECTION.

FD BNC-DUE-FILE
BLOCK CONTAINS 0 RECORDS
RECORDING MODE IS F.

01 BNC-DUE-FILE-REC.
05 FILLER PIC X(10).
05 PT-CONTRACT-DUE-NR PIC X(8).
05 FILLER PIC X(537).
05 PT-POLICY-DUE-NR PIC X(15).
05 FILLER PIC X(7430).
/
FD BNC-COR-DUE-FILE
BLOCK CONTAINS 0 RECORDS
RECORDING MODE IS F.

01 BNC-COR-DUE-FILE-REC.
05 FILLER PIC X(10).
05 PT-CONTRACT-COR-NR PIC X(8).
05 FILLER PIC X(537).
05 PT-POLICY-COR-NR PIC X(15).
05 FILLER PIC X(7430).
/
FD BNC-DIFF-FILE
BLOCK CONTAINS 0 RECORDS
RECORDING MODE IS F.

01 BNC-DIFF-FILE-REC PIC X(8000).
WORKING-STORAGE SECTION.

COPY BCF924TS.
/
/
PROCEDURE DIVISION.
0000-MAINLINE.
**************************************************************
* *
**************************************************************

PERFORM 0100-INITIALIZE.

IF ERROR-NOT-FOUND
PERFORM 1000-MAIN-PROCESSING
END-IF.

PERFORM 9500-PROGRAM-TERMINATION.

MOVE RETURN-CODE-SA TO RETURN-CODE.
STOP RUN.
**************************************************************
0100-INITIALIZE.
**************************************************************
* *
MOVE 'N' TO ERROR-FOUND-SW.

OPEN INPUT BNC-DUE-FILE
BNC-COR-DUE-FILE
OUTPUT BNC-DIFF-FILE.
*************************************************************


1000-MAIN-PROCESSING.

*************************************************************
PERFORM 1500-BNC-DUE-FILE.

PERFORM 1100-PROCESS-BNC-DUE-FILE UNTIL
(BNC-DUE-FILE-EOF = 'Y' ) OR
ERROR-FOUND.
IF ERROR-NOT-FOUND
PERFORM 3000-WRITE-BNC-DIFF-FILE
END-IF.
*************************************************************
1100-PROCESS-BNC-DUE-FILE.

*************************************************************
INITIALIZE BNC-DIFF-FILE-REC
INITIALIZE BCF924-DUE-REC
MOVE SPACES TO BNC-DIFF-FILE-REC
MOVE SPACES TO BCF924-DUE-REC
PERFORM 1600-BNC-COR-DUE-FILE UNTIL
((BNC-COR-DUE-FILE-EOF = 'Y') OR
((PT-CONTRACT-DUE-NR = PT-CONTRACT-COR-NR) AND
(PT-POLICY-DUE-NR = PT-POLICY-COR-NR))).
IF (( PT-CONTRACT-DUE-NR NOT = PT-CONTRACT-COR-NR) AND
(PT-POLICY-DUE-NR NOT = PT-POLICY-COR-NR ))
PERFORM 3000-WRITE-BNC-DIFF-FILE
END-IF.
PERFORM 1500-BNC-DUE-FILE.

MOVE SPACES TO PT-CONTRACT-COR-NR
PT-POLICY-COR-NR.

*************************************************************
1500-BNC-DUE-FILE.
*************************************************************
READ BNC-DUE-FILE
AT END MOVE 'Y' TO BNC-DUE-FILE-EOF.
IF BNC-DUE-FILE-EOF = 'N'
ADD 1 TO BNC-DUE-FILE-READ-AA
MOVE 'N' TO BNC-COR-DUE-FILE-EOF
END-IF.
/
*
*************************************************************

1600-BNC-COR-DUE-FILE.

*************************************************************
READ BNC-COR-DUE-FILE INTO BCF924-DUE-REC
AT END MOVE 'Y' TO BNC-COR-DUE-FILE-EOF.

*************************************************************

3000-WRITE-BNC-DIFF-FILE.

*************************************************************
MOVE BNC-DUE-FILE-REC TO BNC-DIFF-FILE-REC
WRITE BNC-DIFF-FILE-REC.

**************************************************************
9500-PROGRAM-TERMINATION.
**************************************************************
----CLOSE ALL FILES.


CLOSE BNC-DUE-FILE
BNC-COR-DUE-FILE
BNC-DIFF-FILE.
Back to top
View user's profile Send private message
pingte

Active User


Joined: 03 Dec 2005
Posts: 120
Location: india

PostPosted: Thu May 31, 2007 1:34 pm
Reply with quote

Status code 46 means:
A sequential READ statement was attempted on a file open in the input or I-O mode and no valid next record had been established because:
1. The preceding READ statement was unsuccessful but did not cause an at end condition
2. The preceding READ statement caused an at end condition.

Logic should be some what like this icon_idea.gif
Step1: Read record from Master File
Step2: Search 2nd file with record/key from master file
As soon as record is found, move 'Y' to EOF flag for second file i.e. set AT END condition to true.
If not found then also when EOF is reached set AT END condition to true.
Step 3: If no matching record is found, write the Unique record to master file.
Step 4: Before you start processing second record from master file, set EOF flag for 2nd file to 'N' i.e. set AT END condition to false

Hope this will solve ur prob
Back to top
View user's profile Send private message
pingte

Active User


Joined: 03 Dec 2005
Posts: 120
Location: india

PostPosted: Thu May 31, 2007 1:36 pm
Reply with quote

U can refer this link for all file status codes
www.simotime.com/vsmfsk01.htm
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Thu May 31, 2007 9:31 pm
Reply with quote

Hello,

I'd suggest you "step away from the code" and map out the logic for your "match" on paper. As these are sequential files, you will process them sequentially with no "searching" in either file (the 2 files do need to be sorted in the same order before your process runs).

Your process needs to handle the conditions where there are entries in one file and not the other as well as possibly duplicates in one file or the other. This means that (other than the first time thru the code), your process must decide whther to read one file, the other file, or both. There need be only one READ statement for each file, if the code is properly structured.

This (match/merge) is also referred to as a "balance line" process - the code needs to balance back and forth between the files to keep the sort-keys in sync. When proper balance and eof testing is not done, your type of error occurs. The code (when properly implemented) will accomodate one file reaching eof before the other.

We're here when you have questions.
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts FTP VB File from Mainframe retaining ... JCL & VSAM 1
No new posts Extract the file name from another fi... DFSORT/ICETOOL 6
No new posts How to split large record length file... DFSORT/ICETOOL 10
No new posts Extracting Variable decimal numbers f... DFSORT/ICETOOL 17
No new posts SFTP Issue - destination file record ... All Other Mainframe Topics 2
Search our Forums:

Back to Top