MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Get the matching records from 2 diferent files
Goto page 1, 2, 3  Next
 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Utilities
View previous topic :: View next topic  
Author Message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12369
Topics: 75
Location: San Jose

PostPosted: Thu Nov 28, 2002 12:19 pm    Post subject: Get the matching records from 2 diferent files Reply with quote

Requirement:

I have 2 seperate files containing account information is provided,each Record has Unique Account values in fields.Both the files are FB with a LRECL of 80 bytes.The Processing should create 3 files with the following information:

A. Match accounts in File A & File B
B. Accounts in File A but not in File B
C. Accounts in File B but not in File A

Solution:

There are so many ways to get the desired results.I am just listing a few of them.

1. DFSORT/ICETOOL
2. EASYTRIEVE
3. COBOL

Change the pgm name to SYNCTOOL,if you have syncsort at your shop

Code:

//STEP0100 EXEC PGM=ICETOOL                                   
//*                                                           
//TOOLMSG   DD SYSOUT=*                                       
//DFSMSG    DD SYSOUT=*                                       
//IN1       DD *                                               
1234567890                                                     
2345678901                                                     
3456789012                                                     
4567890123                                                     
5678901234                                                     
6789012345                                                     
//IN2       DD *                                               
3456789012                                                     
7890123456                                                     
8901234567                                                     
//T1        DD DSN=&T1,SPACE=(CYL,(5,5),RLSE),DISP=(,PASS)     
//T2        DD DSN=&T2,SPACE=(CYL,(5,5),RLSE),DISP=(,PASS)     
//INT       DD DSN=*.T1,DISP=(OLD,PASS),VOL=REF=*.T1           
//          DD DSN=*.T2,DISP=(OLD,PASS),VOL=REF=*.T2           
//FILEA     DD SYSOUT=*                                       
//FILEB     DD SYSOUT=*                                       
//OUT       DD SYSOUT=*                                       
//TOOLIN    DD   *                                             
  COPY FROM(IN1) USING(CTL1)                                   
  COPY FROM(IN2) USING(CTL2)                                   
  SORT FROM(INT) USING(CTL3)                                   
//CTL1CNTL  DD *                                               
   OUTFIL FNAMES=T1,OUTREC=(1,80,C'1')                           
//CTL2CNTL  DD   *                                             
   OUTFIL FNAMES=T2,OUTREC=(1,80,C'2')                           
//CTL3CNTL  DD   *                                             
  OPTION EQUALS
  SORT FIELDS=(1,10,CH,A)                                       
  SUM FIELDS=(81,1,ZD)                                         
  OUTFIL FNAMES=OUT,INCLUDE=(81,1,ZD,EQ,3),OUTREC=(1,80)       
  OUTFIL FNAMES=FILEA,INCLUDE=(81,1,CH,EQ,C'1'),OUTREC=(1,80)   
  OUTFIL FNAMES=FILEB,INCLUDE=(81,1,CH,EQ,C'2'),OUTREC=(1,80)
/*


Easytrieve Solution:

Code:

//STEP0200 EXEC PGM=EZTPA00                       
//*                                               
//STEPLIB   DD DSN=EASYTREV.LOADLIB,     
//             DISP=SHR                           
//SYSPRINT  DD SYSOUT=*                           
//SYSOUT    DD SYSOUT=*                           
//IN1       DD *                                   
1234567890                                         
2345678901                                         
3456789012                                         
4567890123                                         
5678901234                                         
6789012345                                         
//IN2       DD *                                   
3456789012                                         
7890123456                                         
8901234567                                         
//MATCH     DD DSN=MATCH.FILE,                 
//             DISP=(NEW,CATLG,DELETE),           
//             UNIT=SYSDA,                         
//             SPACE=(CYL,(X,Y),RLSE),             
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=0)   
//*
//OUT1      DD DSN=ONLY.FILEA.RECORDS,             
//             DISP=(NEW,CATLG,DELETE),           
//             UNIT=SYSDA,                         
//             SPACE=(CYL,(X,Y),RLSE),             
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=0)   
//*
//OUT2      DD DSN=ONLY.FILEB.RECORDS,             
//             DISP=(NEW,CATLG,DELETE),           
//             UNIT=SYSDA,                         
//             SPACE=(CYL,(X,Y),RLSE),             
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=0)   
//SYSIN     DD *
                                   
 FILE IN1                           
  IN1-KEY             001 010 A     
                                   
 FILE IN2                           
  IN2-KEY             001 010 A     
                                   
 FILE MATCH FB(0 0)                 
 FILE OUT1  FB(0 0)                 
 FILE OUT2  FB(0 0)                 
                                   
 JOB INPUT (IN1 KEY (IN1-KEY)  +   
            IN2 KEY (IN2-KEY))     
                                   
     IF MATCHED                     
        PUT MATCH FROM IN1         
     ELSE-IF IN1                   
        PUT OUT1 FROM IN1           
     ELSE-IF IN2                   
        PUT OUT2 FROM IN2           
     END-IF                         
/*                                 


Cobol Code:

Code:

 IDENTIFICATION DIVISION.               
 PROGRAM-ID.    MANJU                   
 DATE-COMPILED.                         
 ENVIRONMENT DIVISION.                   
 CONFIGURATION SECTION.                 
 INPUT-OUTPUT SECTION.                   
 FILE-CONTROL.                           
                                         
      SELECT   IN1-FILE                 
      ASSIGN   TO IN1                   
      ORGANIZATION IS SEQUENTIAL.       
                                         
      SELECT   IN2-FILE                 
      ASSIGN   TO IN2                   
      ORGANIZATION IS SEQUENTIAL.       
                                         
      SELECT   MATCH-FILE               
      ASSIGN   TO MATCH                 
      ORGANIZATION IS SEQUENTIAL.       
                                         
      SELECT   OUT1-FILE                 
      ASSIGN   TO OUT1                   
      ORGANIZATION IS SEQUENTIAL.       
                                         
      SELECT   OUT2-FILE                 
      ASSIGN   TO OUT2                   
      ORGANIZATION IS SEQUENTIAL.       
                                         
 DATA DIVISION.                         
 FILE SECTION.                           
                                         
 FD IN1-FILE                             
    RECORDING MODE IS F                 
    LABEL RECORDS ARE STANDARD           
    BLOCK CONTAINS 0 RECORDS             
    DATA RECORD IS IN1-REC.             
                                         
 01 IN1-REC.                               
    05 IN1-KEY                  PIC X(10).
    05 FILLER                   PIC X(70).
                                           
 FD IN2-FILE                               
    RECORDING MODE IS F                   
    LABEL RECORDS ARE STANDARD             
    BLOCK CONTAINS 0 RECORDS               
    DATA RECORD IS IN2-REC.               
                                           
 01 IN2-REC.                               
    05 IN2-KEY                  PIC X(10).
    05 FILLER                   PIC X(70).
                                           
 FD MATCH-FILE                             
    RECORDING MODE IS F                   
    LABEL RECORDS ARE STANDARD             
    BLOCK CONTAINS 0 RECORDS               
    DATA RECORD IS MATCH-REC.             
                                           
 01 MATCH-REC                   PIC X(80).
                                           
 FD OUT1-FILE                             
    RECORDING MODE IS F                   
    LABEL RECORDS ARE STANDARD             
    BLOCK CONTAINS 0 RECORDS               
    DATA RECORD IS OUT1-REC.               
                                           
 01 OUT1-REC                    PIC X(80).
                                           
 FD OUT2-FILE                             
    RECORDING MODE IS F                   
    LABEL RECORDS ARE STANDARD             
    BLOCK CONTAINS 0 RECORDS               
    DATA RECORD IS OUT2-REC.               
                                           
 01 OUT2-REC                    PIC X(80).
                                           
 WORKING-STORAGE SECTION.
 01 S-IN1-FILE                  PIC X(01)  VALUE 'N'.
 01 S-IN2-FILE                  PIC X(01)  VALUE 'N'.
                                                             
 PROCEDURE DIVISION.                                       
                                                             
      PERFORM 1000-INITIALIZATION                           
                                                             
      PERFORM 2000-MAIN-PROCESS UNTIL                       
              S-IN1-FILE = 'Y' AND S-IN2-FILE = 'Y'         
                                                             
      PERFORM 3000-WRAPUP                                   
                                                             
      GOBACK                                                 
      .                                                     
                                                             
 1000-INITIALIZATION.                                       
*************************************************************
* THIS PARAGRAPH OPENS INPUT AND OUTPUT FILES AND DOES THE  *
* PRIME READ.                                               *
*************************************************************
                                                             
      OPEN INPUT  IN1-FILE                                   
                  IN2-FILE                                   
           OUTPUT MATCH-FILE                                 
                  OUT1-FILE                                 
                  OUT2-FILE                                 
                                                             
                                                             
      PERFORM 2100-READ-IN1-FILE                             
      PERFORM 2200-READ-IN2-FILE                             
      .                                                     
                                                             
 2000-MAIN-PROCESS.                                         
*************************************************************
* THIS PARAGRAPH PERFORMS THE MAIN LOGIC                    *
*************************************************************

      EVALUATE TRUE                                         
          WHEN IN1-KEY = IN2-KEY                             
               PERFORM 2300-WRITE-MATCH-FILE                 
               PERFORM 2100-READ-IN1-FILE                   
               PERFORM 2200-READ-IN2-FILE                   
          WHEN IN1-KEY < IN2-KEY                             
               PERFORM 2400-WRITE-OUT1-FILE                 
               PERFORM 2100-READ-IN1-FILE                   
          WHEN IN1-KEY > IN2-KEY                             
               PERFORM 2500-WRITE-OUT2-FILE                 
               PERFORM 2200-READ-IN2-FILE                   
      END-EVALUATE                                           
      .                                                     
                                                             
                                                             
 2100-READ-IN1-FILE.                                         
*************************************************************
* THIS PARAGRAPH READS THE IN1-FILE                         *
*************************************************************
                                                             
      READ IN1-FILE                                         
          AT END                                             
              MOVE 'Y'            TO S-IN1-FILE             
              MOVE  HIGH-VALUES   TO IN1-KEY                 
      END-READ                                               
      .                                                     
                                                             
 2200-READ-IN2-FILE.                                         
*************************************************************
* THIS PARAGRAPH READS THE IN2-FILE                         *
*************************************************************
                                                             
      READ IN2-FILE                                         
          AT END                                             
              MOVE 'Y'            TO S-IN2-FILE             
              MOVE  HIGH-VALUES   TO IN2-KEY                 
      END-READ
      .
                                                             
 2300-WRITE-MATCH-FILE.                                     
*************************************************************
* THIS PARAGRAPH WRITES RECORDS WHICH MATCHES ON BOTH FILES.*
*************************************************************
                                                             
      MOVE SPACES                 TO MATCH-REC               
      MOVE IN1-REC                TO MATCH-REC               
      WRITE MATCH-REC                                       
      .                                                     
                                                             
 2400-WRITE-OUT1-FILE.                                       
*************************************************************
* THIS PARAGRAPH WRITES RECORDS WHICH ARE ONLY IN IN1 FILE. *
*************************************************************
                                                             
      MOVE SPACES                 TO OUT1-REC               
      MOVE IN1-REC                TO OUT1-REC               
      WRITE OUT1-REC                                         
      .                                                     
                                                             
 2500-WRITE-OUT2-FILE.                                       
*************************************************************
* THIS PARAGRAPH WRITES RECORDS WHICH ARE ONLY IN IN2 FILE. *
*************************************************************
                                                             
      MOVE SPACES                 TO OUT2-REC               
      MOVE IN2-REC                TO OUT2-REC               
      WRITE OUT2-REC                                         
      .
 3000-WRAPUP.
*************************************************************
* THIS PARAGRAPH CLOSES THE INPUT & OUTPUT FILES.           *
*************************************************************
                                                             
      CLOSE  IN1-FILE                                       
             IN2-FILE                                       
             MATCH-FILE                                     
             OUT1-FILE                                       
             OUT2-FILE
      .
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Frank Yaeger
Sort Forum Moderator
Sort Forum Moderator


Joined: 02 Dec 2002
Posts: 1618
Topics: 31
Location: San Jose

PostPosted: Mon Mar 10, 2003 6:06 pm    Post subject: Reply with quote

If you have DFSORT R14 PTF UQ90053, you can use the new SPLICE operator of ICETOOL to produce the three files needed. For more information, see the "Create files with matching and non-matching records" Smart DFSORT Trick at:

http://www.ibm.com/servers/storage/support/software/sort/mvs/tricks/

Here's the DFSORT/ICETOOL job:

Code:

//STEP1    EXEC PGM=ICETOOL
//TOOLMSG  DD SYSOUT=*
//DFSMSG   DD SYSOUT=*
//IN1      DD *
1234567890
2345678901
3456789012
4567890123
5678901234
6789012345
/*
//IN2      DD *
3456789012
7890123456
8901234567
/*
//OUT      DD SYSOUT=*
//FILEA    DD SYSOUT=*
//FILEB    DD SYSOUT=*
//T1       DD DSN=&&T1,DISP=(MOD,PASS),UNIT=SYSDA,SPACE=(CYL,(5,5),RLSE)
//TOOLIN   DD *
* Add '11' id to IN1 records -> T1
  COPY FROM(IN1) TO(T1) USING(CTL1)
* Add '22' id to IN2 records -> T1
  COPY FROM(IN2) TO(T1) USING(CTL2)
* Splice records with matching key.
* Resulting output data sets are:
*  OUT - id is '12' for records in IN1 and IN2
*  FILEA -  id is '11' for records in IN1, but not in IN2
*  FILEB -  id is '22' for records in IN2, but not in IN1
  SPLICE FROM(T1) TO(OUT) ON(1,10,CH) WITH(82,1) USING(CTL3) -
    KEEPNODUPS
/*
//CTL1CNTL DD *
  OUTREC FIELDS=(1,80,C'11')
/*
//CTL2CNTL DD *
  OUTREC FIELDS=(1,80,C'22')
/*
//CTL3CNTL DD *
  OUTFIL FNAMES=OUT,INCLUDE=(81,2,CH,EQ,C'12'),OUTREC=(1,80)
  OUTFIL FNAMES=FILEA,INCLUDE=(81,2,CH,EQ,C'11'),OUTREC=(1,80)
  OUTFIL FNAMES=FILEB,INCLUDE=(81,2,CH,EQ,C'22'),OUTREC=(1,80)
/*

_________________
Frank Yaeger - DFSORT Development Team (IBM)
Specialties: JOINKEYS, FINDREP, WHEN=GROUP, ICETOOL, Symbols, Migration
DFSORT is on the Web at:
www.ibm.com/storage/dfsort


Last edited by Frank Yaeger on Tue Sep 19, 2006 12:36 pm; edited 2 times in total
Back to top
View user's profile Send private message Send e-mail Visit poster's website
rasprasads
Beginner


Joined: 10 Dec 2002
Posts: 59
Topics: 20
Location: Chennai

PostPosted: Sat Apr 12, 2003 8:54 am    Post subject: Reply with quote

Kolusu,

I tried the Easytrieve solution given. It worked well when both file had no duplicate keys. But when there were duplictae keys it did not work .

For example :

FILE A -

AA
BB
BB
BB
CC

FILE B -

AA
BB
BB
BB
CC

The OUT1 file had -

BB
BB

Why is this so? What should i do to correctl this problem...
_________________
Rasprasad S
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12369
Topics: 75
Location: San Jose

PostPosted: Sat Apr 12, 2003 10:41 am    Post subject: Reply with quote

Rasprasad,

Easytrieve MATCH logic(Syncronised file) processing does not work with duplicates(Many to Many Match) . It works only with one to many and many to one match.

So you need to write your own logic instead of using "if matched".

for ex:

Code:

GET FILEA
GET FILEB

IF KEYA = KEYB
   ....
END-IF


Hope this helps...

cheers

kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
rasprasads
Beginner


Joined: 10 Dec 2002
Posts: 59
Topics: 20
Location: Chennai

PostPosted: Sat Apr 12, 2003 4:21 pm    Post subject: Reply with quote

Thanks a lot Kolusu !!!

And one more doubt too...

In soln. FILE MATCH FB(0 0) is given i.e,(lrecl=0,blksize=0).
Why is it so when o/p LRECL=80?

Thanks again...
_________________
Rasprasad S
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12369
Topics: 75
Location: San Jose

PostPosted: Sun Apr 13, 2003 1:35 am    Post subject: Reply with quote

Rasprasad,

In easytrieve when you code FB (0 0) then the program expects the LRECL from the JCL.If you don't code the lrecl in jcl then the pgm will abend with S013.That is the reason why I coded the Lrecl as 80. Also I took the example of 80 byte input files.

Hope this helps...

cheers

kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Prayank
Beginner


Joined: 13 May 2003
Posts: 18
Topics: 9
Location: Indore,India

PostPosted: Thu Feb 19, 2004 4:48 pm    Post subject: Reply with quote

Just wanted to know the changes needed in the ICETOOL solution if the input files are Variable Block.

Thanks

Prayank
Back to top
View user's profile Send private message
Frank Yaeger
Sort Forum Moderator
Sort Forum Moderator


Joined: 02 Dec 2002
Posts: 1618
Topics: 31
Location: San Jose

PostPosted: Thu Feb 19, 2004 6:48 pm    Post subject: Reply with quote

For VB, you would have the RDW in positions 1-4, the data would start in position 5 (instead of in position 1) and the records can be variable. So we need to put the id ('11' or '22') in positions 5-6 after the RDW which moves the starting position of the data to position 7:

Code:

| RDW|id|data....


Then we just change all of the statements to reflect that. Here's the DFSORT/ICETOOL job (remember that the data starts in position 5 in the input records):

Code:

//STEP1    EXEC PGM=ICETOOL
//TOOLMSG  DD SYSOUT=*
//DFSMSG   DD SYSOUT=*
//IN1      DD DSN=...  input file1
//IN2      DD DSN=...  input file2
//OUT      DD SYSOUT=*
//FILEA    DD SYSOUT=*
//FILEB    DD SYSOUT=*
//T1       DD DSN=&&T1,DISP=(MOD,PASS),UNIT=SYSDA,SPACE=(CYL,(5,5),RLSE)
//TOOLIN   DD *
* Add '11' id to IN1 records -> T1
  COPY FROM(IN1) TO(T1) USING(CTL1)
* Add '22' id to IN2 records -> T1
  COPY FROM(IN2) TO(T1) USING(CTL2)
* Splice records with matching key.
* Resulting output data sets are:
*  OUT - id is '12' for records in IN1 and IN2
*  FILEA -  id is '11' for records in IN1, but not in IN2
*  FILEB -  id is '22' for records in IN2, but not in IN1
  SPLICE FROM(T1) TO(OUT) ON(7,10,CH) WITH(6,1) USING(CTL3) -
    KEEPNODUPS
/*
//CTL1CNTL DD *
  OUTREC FIELDS=(1,4,5:C'11',7:5)
/*
//CTL2CNTL DD *
  OUTREC FIELDS=(1,4,5:C'22',7:5)
/*
//CTL3CNTL DD *
  OUTFIL FNAMES=OUT,INCLUDE=(5,2,CH,EQ,C'12'),OUTREC=(1,4,7)
  OUTFIL FNAMES=FILEA,INCLUDE=(5,2,CH,EQ,C'11'),OUTREC=(1,4,7)
  OUTFIL FNAMES=FILEB,INCLUDE=(5,2,CH,EQ,C'22'),OUTREC=(1,4,7)
/*

_________________
Frank Yaeger - DFSORT Development Team (IBM)
Specialties: JOINKEYS, FINDREP, WHEN=GROUP, ICETOOL, Symbols, Migration
DFSORT is on the Web at:
www.ibm.com/storage/dfsort


Last edited by Frank Yaeger on Tue Jul 12, 2005 10:28 am; edited 1 time in total
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vallishar
Beginner


Joined: 17 Dec 2002
Posts: 53
Topics: 14
Location: BengaLuru

PostPosted: Tue Mar 02, 2004 6:41 pm    Post subject: Reply with quote

I am trying to make use of the SYNCTOOL utility to achieve the the same as the original requirement in this post.

On executing the job, I get this message with a return code of 12.

Code:
SYT000I  SYNCTOOL RELEASE 1.4A - COPYRIGHT 2001  SYNCSORT INC.
SYT001I  INITIAL PROCESSING MODE IS "STOP"
SYT002I  "TOOLIN" INTERFACE BEING USED

              SORT FORM(IN1) USING(CTL1)
SYT050E  INVALID OPERAND ON "SORT" STATEMENT
SYT030I  OPERATION COMPLETED WITH RETURN CODE 12

SYT015I  PROCESSING MODE CHANGED FROM "STOP" TO "SCAN" DUE TO OPERATION FAILURE

              SORT FROM(IN2) USING(CTL2)
SYT019I  STATEMENT VALID; NOT PROCESSED DUE TO "SCAN" PROCESSING MODE

              SORT FROM(INT) USING(CTL3)
SYT019I  STATEMENT VALID; NOT PROCESSED DUE TO "SCAN" PROCESSING MODE

SYT004I  SYNCTOOL PROCESSING COMPLETED WITH RETURN CODE 12


Any help ?
_________________
If you're not failing every now and again, it's a sign you're not doing anything very innovative.
Back to top
View user's profile Send private message Yahoo Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12369
Topics: 75
Location: San Jose

PostPosted: Tue Mar 02, 2004 6:59 pm    Post subject: Reply with quote

vallishar,


If you look at the TOOLMSG messages you will find that you have spelled FROM as FORM. Very Happy

i.e
Code:

SORT FORM(IN1) USING(CTL1)


change it to
Code:

SORT FROM(IN1) USING(CTL1)


Hope this helps...

Cheers

Kolusu
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vallishar
Beginner


Joined: 17 Dec 2002
Posts: 53
Topics: 14
Location: BengaLuru

PostPosted: Tue Mar 02, 2004 7:48 pm    Post subject: Reply with quote

Thanks Kolusu.

I should better get my eyes tested Laughing
_________________
If you're not failing every now and again, it's a sign you're not doing anything very innovative.
Back to top
View user's profile Send private message Yahoo Messenger
infoman123
Beginner


Joined: 02 Nov 2004
Posts: 57
Topics: 20

PostPosted: Fri Dec 10, 2004 5:42 am    Post subject: Reply with quote

Kolusu,

Will the below code help in ezy for many to many matching
Code:

JOB INPUT (FILE1 KEY (FILE1-A) +
          (FILE2 KEY (FILE2-A)) +
IF FIRST-DUP FILE2               
  DISPLAY ' FIRST-DUP '
ELSE                             
 IF LAST-DUP FILE2               
  DISPLAY 'LAST-DUP '
  GO TO JOB                       
 ELSE                             
   IF DUPLICATE FILE2             
    DISPLAY 'DUP'
    GO TO JOB                     
   END-IF                         
 END-IF                           
END-IF                           

IF MATCHED
 DISPLAY 'MATCH'
ELSE
IF FILE1
 DISPLAY 'FILE1'
ELSE
 DISPLAY 'FILE2 '
END-IF
END-IF
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12369
Topics: 75
Location: San Jose

PostPosted: Fri Dec 10, 2004 8:33 am    Post subject: Reply with quote

Infoman123,

I don't think that logic is going to work. The only way to use Easytrieve's syncronised file processing to match many to many is using internal tables. Normally, Synchronized File Processing would process the first FILEA key A against all of the FILEB key A records and the second key A record from FILEA would be presented as NOT MATCHED. The above code will read the first key A record from FILEA and the first Key A record from FILEB and present that as a MATCH, it will then read FILEB record 2 and present that as a match with the first record from FILEA. While this processing is going on, the FILEB records are being stored in the array. Once we read the fourth record in FILEB and encounter an unmatched key we then read ahead in FILEA, since the key of FILEA matches the SAVE-KEY we will process the second record from FILEA against the array of FILEB records. Record two from FILEA is the last duplicate which causes the array to be emptied. Processing continues to the next record in FILEA which now matches the current key of FILEB, another MATCH condition.

check this sample code

Code:

JOB INPUT (FILEA KEY(FLDA) FILEB KEY (FLDB))

      IF MATCHED
         IF FIRST-DUP FILEA
            ARRAY-CNT = ARRAY-CNT + 1
            IF ARRAY-CNT GT 10
               DISPLAY 'OVERFLOW ON INTERNAL TABLE - CHANGE OCCURS VALUE'
               STOP EXECUTE
               END-IF
               WSB-ARRAY (ARRAY-CNT) = RECB
            END-IF
            .
            . other program logic
            .
            SAVE-KEY = FLDA
       END-IF

       IF NOT MATCHED AND FILEA AND FLDA = SAVE-KEY
          ARRAY-SUB = 1
          DO WHILE ARRAY-SUB LE ARRAY-CNT
             WS-RECB = WSB-ARRAY (ARRAY-SUB)
             .
             . other program logic
             .
             ARRAY-SUB = ARRAY-SUB + 1
          END-DO
            IF LAST-DUP FILEA
               MOVE SPACES TO ENTIRE-ARRAY
               ARRAY-CNT = 0
            END-IF
       END-IF



Hope this helps...

Cheers

Kolusu
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
e_thani
Beginner


Joined: 26 Jul 2004
Posts: 4
Topics: 1

PostPosted: Thu Dec 16, 2004 7:14 am    Post subject: Reply with quote

Hi Kolusu,

I have a small doubt on cited topic using Synctool(JCL),
In above example the matched record i.e., 3456789012 is not displayed in the OUT Output Queue

Only the records that found in InputA NOT in inputB is displayed in FILEA and Vice versa.
I like to see both matched records and non-matched record in the output Queue


SDSF
JESMSGLG JES2 2 TSOTEKA X LOCAL
JESJCL JES2 3 TSOTEKA X LOCAL
JESYSMSG JES2 4 TSOTEKA X LOCAL
TOOLMSG STEP0100 107 TSOTEKA X LOCAL
DFSMSG STEP0100 108 TSOTEKA X LOCAL
OUT ????
FILEA STEP0100 109 TSOTEKA X LOCAL
FILEB STEP0100 110 TSOTEKA X LOCAL

I hope you understood my Question.
Back to top
View user's profile Send private message
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Thu Dec 16, 2004 7:40 am    Post subject: Reply with quote

e thani,

Could you please post your complete JCL. Kolusu's JCL works fine for me.

Thanks,
Phantom
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Utilities All times are GMT - 5 Hours
Goto page 1, 2, 3  Next
Page 1 of 3

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group