View previous topic :: View next topic
Author
Message
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
Hi All,
I have a PS file with LRECL 80. In that I have records within a common tags. Opening tag : Original(1-8) Ending Tag: ENDMSG(1-6). i have unique keys Acct Num(PIC 9(10)) and Emp num(PIC 9(9)). I need to remove entire set of records which occurs multiple times.
Input file:
Code:
Original: xxxyyy
Acct num: 1234567890
Emp Num: 098789076
.
.
.
ENDMSG;
Original: xxxyyy
Acct num: 1234567890
Emp Num: 098789076
.
.
.
ENDMSG;
Original: Yabcyyy
Acct num: 8736450987
Emp Num: 098720987
.
.
.
ENDMSG;
output file:
Code:
Original: xxxyyy
Acct num: 1234567890
Emp Num: 098789076
.
.
.
ENDMSG;
Original: Yabcyyy
Acct num: 8736450987
Emp Num: 098720987
.
.
.
ENDMSG;
My output file LRECL is the same 80.
I have to use SYNCSORT utility for achieving this. Kindly help me.
Back to top
xknight Active User Joined: 22 Jan 2008Posts: 117 Location: Liberty city
Hello,
Try the below snippet,
Code:
//STEP01 EXEC PGM=SYNCTOOL
//DFSMSG DD SYSOUT=*
//TOOLMSG DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//IN1 DD *
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
/*
//OUT1 DD DSN=&TMP1,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT2 DD DSN=&TMP2,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT3 DD DSN=&TMP3,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT4 DD DSN=&TMP4,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//TOOLIN DD *
COPY FROM(IN1) TO(OUT4) USING(CTL1)
COPY FROM(OUT4) TO(OUT1) USING(CTL2)
SELECT FROM(OUT1) TO(OUT2) ON(90,10,ZD) FIRSTDUP
COPY FROM(OUT2) TO(OUT3) USING(CTL3)
/*
//CTL1CNTL DD *
INREC IFTHEN=(WHEN=INIT,
OVERLAY=(90:SEQNUM,10,ZD)),
IFTHEN=(WHEN=(1,4,CH,EQ,C'ACCT'),OVERLAY=(90:11,10))
/*
//CTL2CNTL DD *
INREC IFTHEN=(WHEN=GROUP,
BEGIN=(1,8,CH,EQ,C'ORIGINAL'),
END=(1,6,CH,EQ,C'ENDMSG'),
PUSH=(81:ID=5))
/*
//CTL3CNTL DD *
OUTREC FIELDS=(1:81,5)
/*
//*
//STEP00 EXEC PGM=SORT
//SYSOUT DD SYSOUT=*
//SORTOUT DD SYSOUT=*
//SORTJNF1 DD DSN=&TMP1,DISP=SHR
//SORTJNF2 DD DSN=&TMP3,DISP=SHR
//SYSIN DD *
JOINKEYS FILE=F1,FIELDS=(81,5,A)
JOINKEYS FILE=F2,FIELDS=(1,5,A)
SORT FIELDS=COPY
JOIN UNPAIRED,F1,ONLY
REFORMAT FIELDS=(F1:1,80)
Input:
Code:
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
Output:
Code:
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
Is the value on Original relevant to your matching.
Are EMP NUMs unique within the file, or only unique (subject to being duplicate) with the ACCT NUMs?
Back to top
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
Hi,
xknight, thanks for the info. But is the same possible in SYNCSORT?
Quote:
Are EMP NUMs unique within the file, or only unique (subject to being duplicate) with the ACCT NUMs
Acct Num and Emp Num are two different values.
If it is like,
Code:
ACCT NUM: 1234567890
EMP NUM: 0987890C6
ACCT NUM: 1234567890
EMP NUM: 0987890C6
ACCT NUM: 1234567800
EMP NUM: 098789076
ACCT NUM: 1234567800
EMP NUM: 098789076
output should be:
Code:
ACCT NUM: 1234567890
EMP NUM: 0987890C6
ACCT NUM: 1234567800
EMP NUM: 098789076
I have to compare both the Acct Num and EMP Num. If both Acct num and Emp num together occur multiple times i have to remove the entire set of records.
Note: EMP NUM is PIC x(9). Sorry for the inconvinence.
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
Quote:
Quote:
Are EMP NUMs unique within the file, or only unique (subject to being duplicate) with the ACCT NUMs
Acct Num and Emp Num are two different values.
Goodness me, the quantity of my stunnedness is without bounds :-)
It is not the question I asked. It was kind of obvious from the different names that they were different things.
Can an Emp Num exist under more than one Acct Num?
Any answer to the question about Original?
If you want to try Xavier's solution, why don't you? Are you saying it has to be with PGM=SORT and nothing else?
Back to top
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
Bill,
Quote:
Can an Emp Num exist under more than one Acct Num
Yes, it can be.
Quote:
Any answer to the question about Original?
Orginal is just a Header value it may vary after the 9th position.
I was allowed to use only syncsort. Pls let me know if you need further info on this.
Back to top
dick scherrer Moderator Emeritus Joined: 23 Nov 2006Posts: 19243 Location: Inside the Matrix
Hello,
Suggest you submit the provided code and post back here what happens. . .
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
OK, with Syncsort you are looking at multiple steps.
I see you are a programmer, so if you need it in one step, it'll have to be a program.
First step:
Add GROUP ID to main file. Create KEY file with ACCT/EMP/GROUP ID.
Second step:
De-duplicate Keys (you may be able to do this in the first step)
Third step:
Join on ID from Main and Key, ignoring mismatches.
The GROUP ID for the Main and Key should start with the "Original".
To get the key, you'll need a second GROUP to PUSH the ACCT.
When you get the EMP, you'll have the ACCT to go with it and can create your key of ACCT, EMP and ID (from Original).
Back to top
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
Thanks for the suggestion Bill.
Xavier's solution removes the duplicate at the first occurance. I may have multiple occurance in the input file. Like,
Code:
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
My output should be:
Code:
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
i tried like using NODUPS,ALLDUPS option but it didnt work well.
Also i removed the JOIN UNPAIRED COND but it throws ABENDU0016 since REFORMAT FIELDS are mandatory.
Can you please suggest how to remove multiple occurance of duplicates.
Similar to SUM FIELDS=NONE.
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
These questions are all connected to each other? The same data? Or different?
Did you try the sorting solution? If the data is the same, just add the SUM FIELDS=NONE. If the data is different, modify the sorting solution and add SUM FIELDS=NONE.
If this is all the same data, can you try to put the whole requirement together all at once. I'm sort of loosing track of what is what with the similar data.
Back to top
xknight Active User Joined: 22 Jan 2008Posts: 117 Location: Liberty city
Hello,
Quote:
Also i removed the JOIN UNPAIRED COND but it throws ABENDU0016 since REFORMAT FIELDS are mandatory.
I dont understand why are you making this complicated.
Just remember, REFORMAT field is mandatory not the UNPAIRED option.
Quote:
solution removes the duplicate at the first occurance
And your requirement keep on changing,
Try the below (untested) snippet
Code:
//STEP01 EXEC PGM=ICETOOL
//DFSMSG DD SYSOUT=*
//TOOLMSG DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//IN1 DD *
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
/*
//OUT1 DD DSN=&TMP1,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT2 DD DSN=&TMP2,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT3 DD DSN=&TMP3,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT4 DD DSN=&TMP4,
// DISP=(MOD,PASS,DELETE),
// RECFM=FB,LRECL=100,BLKSIZE=0,
// SPACE=(CYL,(10,10),RLSE),UNIT=SYSDA
//OUT8 DD SYSOUT=*
//TOOLIN DD *
COPY FROM(IN1) TO(OUT1) USING(CTL1)
COPY FROM(OUT1) TO(OUT2) USING(CTL2)
SORT FROM(OUT2) TO(OUT3) USING(CTL4)
COPY FROM(OUT3) TO(OUT4) USING(CTL3)
/*
//CTL1CNTL DD *
INREC IFTHEN=(WHEN=INIT,
OVERLAY=(90:C'0000000000')),
IFTHEN=(WHEN=(1,4,CH,EQ,C'ACCT'),OVERLAY=(90:11,10))
/*
//CTL2CNTL DD *
INREC IFTHEN=(WHEN=GROUP,
BEGIN=(1,8,CH,EQ,C'ORIGINAL'),
END=(1,6,CH,EQ,C'ENDMSG'),
PUSH=(81:ID=5))
/*
//CTL3CNTL DD *
OUTREC FIELDS=(1:81,5)
/*
//CTL4CNTL DD *
SORT FIELDS=(90,10,CH,A)
SUM FIELDS=NONE
OMIT COND=(90,10,CH,EQ,C'0000000000')
/*
//*
//STEP00 EXEC PGM=SORT
//SYSOUT DD SYSOUT=*
//SORTOUT DD SYSOUT=*
//SORTJNF1 DD DSN=&TMP2,DISP=SHR
//SORTJNF2 DD DSN=&TMP4,DISP=SHR
//SYSIN DD *
JOINKEYS FILE=F1,FIELDS=(81,5,A)
JOINKEYS FILE=F2,FIELDS=(1,5,A)
SORT FIELDS=COPY
REFORMAT FIELDS=(F1:1,80)
If my assumption is correct, you might need to tweak it to sort it again based on A/c no or Original message, unless if you wish to retain in un-sorted order, this might work.
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
Sab,
As I understood it, Acct Num and Emp Num together make a unique key (subject to duplicates existing).
We know an Emp Num can appear under more than one Acct Num. I don't know, but have assumed an Acct Num can have more than one Emp Num. Can it?
Back to top
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
xknight you are great. The code worked without any issues. Thanks again..!!
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
Bill Woodger wrote:
Sab,
As I understood it, Acct Num and Emp Num together make a unique key (subject to duplicates existing).
We know an Emp Num can appear under more than one Acct Num. I don't know, but have assumed an Acct Num can have more than one Emp Num. Can it?
I'll take that as a NO then... which makes Acct Num unique (subject to duplicates).
Back to top
sabarikanth New User Joined: 07 Jun 2010Posts: 59 Location: coimbatore
sorry Bill missed you conversation.
to answer your query,
Quote:
We know an Emp Num can appear under more than one Acct Num. I don't know, but have assumed an Acct Num can have more than one Emp Num. Can it?
Yes it can have multiple Emp Num for an Acct Num.
Back to top
Bill Woodger Moderator Emeritus Joined: 09 Mar 2011Posts: 7309 Location: Inside the Matrix
Did you test Xavier's with that?
Just in case, here's another one to test. One pass of the data. I've included two Emp Num for the same Acct Num.
Code:
//SDDMULTR EXEC PGM=SORT
//SYSOUT DD SYSOUT=*
//SORTOUT DD SYSOUT=*
//SYSIN DD *
INREC IFTHEN=(WHEN=GROUP,BEGIN=(1,9,CH,EQ,C'ORIGINAL:'),
PUSH=(081:1,80)),
IFTHEN=(WHEN=GROUP,BEGIN=(1,9,CH,EQ,C'ACCT NUM:'),
END=(1,9,CH,EQ,C'ORIGINAL:'),
PUSH=(161:1,80)),
IFTHEN=(WHEN=GROUP,BEGIN=(1,7,CH,EQ,C'EMP NUM:'),
END=(1,9,CH,EQ,C'ORIGINAL:'),
PUSH=(241:1,80))
SORT FIELDS=(171,10,CH,A,249,10,CH,A),EQUALS
OUTREC IFTHEN=(WHEN=INIT,OVERLAY=(321:171,10,249,10,
SEQNUM,5,ZD,RESTART=(321,20))),
IFTHEN=(WHEN=GROUP,BEGIN=(1,7,CH,EQ,C'EMP NUM:'),
END=(1,9,CH,EQ,C'ORIGINAL:'),
PUSH=(341:341,5))
OUTFIL OMIT=(1,9,CH,EQ,C'ORIGINAL:',
OR,1,9,CH,EQ,C'ACCT NUM:',
OR,341,5,ZD,NE,1),
IFOUTLEN=80,
IFTHEN=(WHEN=(1,7,CH,EQ,C'EMP NUM:'),
BUILD=(081,80,/,
161,80,/,
001,80))
//SORTIN DD *
ORIGINAL: AAAYYY
ACCT NUM: 1234567890
EMP NUM: 111111111
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
Gives this output:
Code:
ORIGINAL: XXXYYY
ACCT NUM: 1234567890
EMP NUM: 098789076
.
.
.
ENDMSG;
ORIGINAL: AAAYYY
ACCT NUM: 1234567890
EMP NUM: 111111111
.
.
.
ENDMSG;
ORIGINAL: YABCYYY
ACCT NUM: 8736450987
EMP NUM: 098720987
.
.
.
ENDMSG;
Try that test data through Xavier's please.
It did take a bit more than "just add sum fields=none" as I previously suggested :-), but not much. There could be some dead wood in it if you want to poke around.
Back to top
Please enable JavaScript!