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

Matching files using DFSORT


IBM Mainframe Forums -> DFSORT/ICETOOL
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
guptae

Moderator


Joined: 14 Oct 2005
Posts: 1208
Location: Bangalore,India

PostPosted: Tue Jun 05, 2007 11:19 pm
Reply with quote

Hi There,

I have two files lets Take file A & B. I want to put match record of these two file in third file let take the name C & Unmatch record in File D.

Length of fileA & B is 80 Bytes

Copybook for fileA:
Code:
01  DOCUMENTUM-COPYBOOK
      05 CLAIM-NUMBER         PIC X(12)
      05 EVENT-NUMBER         PIC X(5)
      05 SOURCE_IMAGE_ID      PIC X(11)
      05 SCAN-DATE         PIC X(8)
      05 COLLECTION-NAME      PIC X(20)
      05 DOCUMENTUM-IMAGE-ID      PIC X(16)
      05 USER-IDENTIFIER      PIC X(8)

In FileA I have all the field populated except DOCUMENTUM-IMAGE-ID
which we need to take from file B for matching Claim Number & Event number

File B Layout:
Code:
01  DOCUMENTUM-COPYBOOKb
      05 CLAIM-NUMBER         PIC X(12)
      05 EVENT-NUMBER         PIC X(5)
      05 DOCUMENTUM-IMAGE-ID      PIC X(16)


Eg:
Code:
FILEA
000000DM62HL00011CPNA164V02120020522
000000DM62HL00015CPNA164W87120020605


Code:
FileB
000000DE07QY000010900077780390122
000000DE07QY000020900077780390123
000000DM62HL000110900077780390124
000000DM62HL000150900077780390125


O/p Should be
Code:
000000DM62HL00011CPNA164V02120020522                         0900077780390124
000000DM62HL00015CPNA164W87120020605                   0900077780390125

Files does not contain any duplicates on CLAIM NUMBER, EVENT NUMBER
Hope I explain it clearly.-)
Back to top
View user's profile Send private message
Frank Yaeger

DFSORT Developer


Joined: 15 Feb 2005
Posts: 7129
Location: San Jose, CA

PostPosted: Tue Jun 05, 2007 11:40 pm
Reply with quote

Have you tried using a variation of the technique discussed in the "Create files with matching and non-matching records" Smart DFSORT Trick at:

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

I've posted hundreds of SPLICE examples on this board. Have you tried to find one similar to what you want to do?
Back to top
View user's profile Send private message
guptae

Moderator


Joined: 14 Oct 2005
Posts: 1208
Location: Bangalore,India

PostPosted: Tue Jun 05, 2007 11:54 pm
Reply with quote

Hi Frank,

I have run the following job

Code:
//REMDUPS  EXEC PGM=ICETOOL                                     
//TOOLMSG  DD SYSOUT=*                                         
//DFSMSG   DD SYSOUT=*                                         
//T1       DD DISP=SHR,DSN=A40661.?SCCS.IMAGE.DOCUMNT1.FILE     
//T2       DD DISP=SHR,DSN=A40661.MN.TXT3.TEXT                 
//OUT      DD DSN=40661.?SCCS.IMAGE.DOCUMNT3.FILE,             
//            DISP=(NEW,CATLG,CATLG),                           
//            DCB=(RECFM=FB,LRECL=80),SPACE=(CYL,(100,100),RLSE)
//TOOLIN   DD *                                                 
  COPY FROM(IN1) TO(T1) USING(CTL1)                             
  COPY FROM(IN2) TO(T1) USING(CTL2)                             
  SPLICE FROM(T1) TO(T2) ON(1,17,CH) WITH(57,16)               
  SORT FROM(T2) TO(OUT) USING(CTL3)                             
/*                                                             
//CTL1CNTL DD *                                                 
  INREC OVERLAY=(81:SEQNUM,8,ZD)                               
/*                                                             
//CTL2CNTL DD *                                                 
  INREC BUILD=(1,80,88:X)                                       
/*                                                             
//CTL3CNTL DD *                                                 
  SORT FIELDS=(81,8,ZD,A)                                       
  OUTREC BUILD=(1,80)                                           
/*             


Please let me know whether its correct or not

I have changed the second file format to
01 DOCUMENTUM-COPYBOOKb
05 CLAIM-NUMBER PIC X(12)
05 EVENT-NUMBER PIC X(5)
05 SOURCE_IMAGE_ID PIC X(11)
05 SCAN-DATE PIC X(8)
05 COLLECTION-NAME PIC X(20)
05 DOCUMENTUM-IMAGE-ID PIC X(16)
05 USER-IDENTIFIER PIC X(8)

Hope it is clear
Back to top
View user's profile Send private message
Frank Yaeger

DFSORT Developer


Joined: 15 Feb 2005
Posts: 7129
Location: San Jose, CA

PostPosted: Wed Jun 06, 2007 12:47 am
Reply with quote

Quote:
Please let me know whether its correct or not


Just look at the output and see if it's what you want. If not, correct the job until you get the output you want.
Back to top
View user's profile Send private message
guptae

Moderator


Joined: 14 Oct 2005
Posts: 1208
Location: Bangalore,India

PostPosted: Wed Jun 06, 2007 1:43 pm
Reply with quote

Hi Frank,

Its taking FILEB record also for which its not finding matching key in FILEA
Back to top
View user's profile Send private message
krisprems

Active Member


Joined: 27 Nov 2006
Posts: 649
Location: India

PostPosted: Wed Jun 06, 2007 4:03 pm
Reply with quote

guptae

As per your initial requierement i tried this sort. Please check this
Code:
//*******************************************************               
//STEP001  EXEC PGM=ICETOOL                                             
//TOOLMSG  DD SYSOUT=*                                                 
//DFSMSG   DD SYSOUT=*                                                 
//IN1      DD *                                                         
000000DM62HL00011CPNA164V02120020522                                          000000DM62HL00015CPNA164W87120020605                                   
/*                                                                     
//IN2      DD *                                                         
000000DE07QY000010900077780390122                                       
000000DE07QY000020900077780390123                                       
000000DM62HL000110900077780390124                                       
000000DM62HL000150900077780390125                                       
/*                                                                     
//TMP1     DD DSN=&&TEMP1,DISP=(MOD,PASS),SPACE=(TRK,(5,5)),UNIT=SYSDA 
//MATCH    DD SYSOUT=*                                                 
//UNMATCH  DD SYSOUT=*                                                 
//TOOLIN   DD *                                                         
 COPY FROM(IN1)  TO(TMP1) USING(CP01)                                   
 COPY FROM(IN2)  TO(TMP1) USING(CP02)                                   
 SPLICE FROM(TMP1) TO(MATCH) ON(1,17,CH) WITH(76,1) WITH(57,16) -       
                            USING(CP03) KEEPNODUPS                     
/*                                                                     
//CP01CNTL DD   *                                                       
  OUTREC BUILD=(1,36,75:C'11')                                         
/*                                                                     
//CP02CNTL DD   *                                                       
  INREC  FIELDS=(1:1,17,57:18,16,75:C'22')                             
/*                                                                     
//CP03CNTL DD   *                                                       
  OUTFIL FNAMES=MATCH,INCLUDE=(75,2,CH,EQ,C'12'),BUILD=(1,73)           
    OUTFIL FNAMES=UNMATCH,INCLUDE=(75,2,CH,EQ,C'11',OR,                   
                                 75,2,CH,EQ,C'22'),BUILD=(1,36)         
/*                                                                     


Now the o/p contains
Match:
Code:
000000DM62HL00011CPNA164V02120020522                    0900077780390124       
000000DM62HL00015CPNA164W87120020605                    0900077780390125       


UNMATCH:
Code:
000000DE07QY00001                                                               
000000DE07QY00002                                                               


Please let me know if this is what you wanted icon_exclaim.gif
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 -> DFSORT/ICETOOL

 


Similar Topics
Topic Forum Replies
No new posts Modifying Date Format Using DFSORT DFSORT/ICETOOL 9
No new posts Write line by line from two files DFSORT/ICETOOL 7
No new posts Compare only first records of the fil... SYNCSORT 7
No new posts Replace Multiple Field values to Othe... DFSORT/ICETOOL 12
No new posts Calling DFSORT from Cobol, using OUTF... DFSORT/ICETOOL 5
Search our Forums:

Back to Top