How to delete 2 GDG member in different steps - mainframe

I defined a Generation Data Group (GDG) with limit parameter as 5, and let's put (1,2,3,4,5) as members(suppose 5 is current position).
I use a job which has 2 steps each will try to delete a member using IEFBR14 utility.
//STEP10 EXEC PGM=IEFBR14
//SYSOUT DD SYSOUT=*
//SYSDEL DD DSN=DATA.TEST.GDG(-1),
// DISP=(MOD,DELETE,DELETE)
//****************************************
//STEP20 EXEC PGM=IEFBR14
//SYSOUT DD SYSOUT=*
//SYSDEL DD DSN=DATA.TEST.GDG(-2),
// DISP=(MOD,DELETE,DELETE)
I wish I can get result as (1,2,5), but in fact (1,3,5) was left, member 2 and member 4 was deleted ? it seems after step 1, there is a commit operation, can anybody can help me with this?
But on the other hand, if I try to delete member (0), and member (-2), the result is as what I expected.
//STEP10 EXEC PGM=IEFBR14
//SYSOUT DD SYSOUT=*
//SYSDEL DD DSN=DATA.TEST.GDG(0),
// DISP=(MOD,DELETE,DELETE)
//****************************************
//STEP20 EXEC PGM=IEFBR14
//SYSOUT DD SYSOUT=*
//SYSDEL DD DSN=DATA.TEST.GDG(-2),
// DISP=(MOD,DELETE,DELETE)
I get the result (1,2,4), member 3 and member 5 were deleted.

JOB1 deletes the Members 2 and 4. Here is how it works.
enter code here
//STEP1 EXEC PGM=IEFBR14
//DD1 DD DSN=DATA.GDG.TEST(-1),DISP=(MOD,DELETE,DELETE)
//*
//STEP2 EXEC PGM=SORT <==note:i added this step for TEST purpose only
//SORTIN DD DSN=DATA.GDG.TEST(-1),DISP=SHR
//SORTOUT DD DUMMY
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
OPTION COPY
/*
//STEP3 EXEC PGM=IEFBR14
//DD2 DD DSN=DATA.GDG.TEST(-2),DISP=(MOD,DELETE,DELETE)
if we have a look at the JESYMSG, we can find the messages as below:
IEF142I GDGTST STEP1 - STEP WAS EXECUTED - COND CODE 0000
IGD105I DATA.GDG.TEST.G0004V00 DELETED, DDNAME=DD1 <==(-1) to 5
**please note here in STEP2 the GDG member refered is 03 not 04 as expected**
IEF142I GDGTST STEP2 - STEP WAS EXECUTED - COND CODE 0000
IGD104I DATA.GDG.TEST.G0003V00 RETAINED, DDNAME=SORTIN <==(-1) to 4
IEF142I GDGTST STEP3 - STEP WAS EXECUTED - COND CODE 0000
IGD105I DATA.GDG.TEST.G0002V00 DELETED, DDNAME=DD2 <==(-2) to 4
The first time you use a relative generation number for a generation data group within a job, the system establishes the relationship between the relative generation number and the absolute generation number. The system maintains this relationship throughout the job.(reference: z/OS MVS JCL user's guide-APPENDIX B)
For example, if you create a generation data set with a relative generation number of (+1), the system recognizes any subsequent reference to (+1) throughout the job as having the same absolute generation number.
(+1)--> adding a member raltive to most recently added member(i.e.,(0))
(+2)-->(+1) to (+1)
(+3)--> (+1) to (+2)
likewise, in the JOB1 that you posted the reference is set to (-1) i.e, G0004V00 at the starting of the job. This (-1) relationship is maintained throughout the job. result of STEP2 in the job psosted by me proves this point.
so to achieve the result (1,3,5) give (-1) in both the steps(STEP10 and STEP20) of JOB1. that will work.
above results are for JES2, not sure about JES3
and for JOB2 in Main question:
//STEP1 EXEC PGM=IEFBR14
//DD1 DD DSN=DATA.GDG.TEST(0),DISP=(MOD,DELETE,DELETE)
//SYSOUT DD SYSOUT=*
//STEP2 EXEC PGM=SORT
//SORTIN DD DSN=DATA.GDG.TEST(-1),DISP=SHR
//SORTOUT DD DUMMY
//SYSOUT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
OPTION COPY
/*
//STEP3 EXEC PGM=IEFBR14
//DD2 DD DSN=DATA.GDG.TEST(-2),DISP=(MOD,DELETE)
//SYSOUT DD SYSOUT=*
//STEP4 EXEC PGM=IEFBR14
//MODEL1 DD DSN=DATA.GDG.TEST(-1),DISP=(MOD,DELETE)
the JESYMSG is as below:
IEF142I GDGTST STEP1 - STEP WAS EXECUTED - COND CODE 0000
IGD105I DATA.GDG.TEST.G0005V00 DELETED, DDNAME=DD1
IEF142I GDGTST STEP2 - STEP WAS EXECUTED - COND CODE 0000
IGD104I DATA.GDG.TEST.G0004V00 RETAINED, DDNAME=SORTIN
IEF142I GDGTST STEP3 - STEP WAS EXECUTED - COND CODE 0000
IGD105I DATA.GDG.TEST.G0003V00 DELETED, DDNAME=DD2
IEF142I GDGTST STEP4 - STEP WAS EXECUTED - COND CODE 0000
IGD105I DATA.GDG.TEST.G0004V00 DELETED, DDNAME=MODEL1
as I have explained earlier, the relationship between absolute and relative GDG is established when the job encounters the RELATIVE referencing for the FIRST time. so here in this job, it encounters(0) for the first time. so when the initiator issues ENQ at each step, the generation numbers will be resolved with reference to (0) in JOB2.
if we Observe here it deleted(0,3,4)--> for(0),(-2),(-1) in STEP1, STEP3,STEP4. that means, it didn't commit after the execution of eachstep. Reference to (-1) in STEP4 is resolved in relation to (0), which is established in STEP1.
lets consider one more example as below: if I add one morestep STEP5 like below to above job
//STEP1 EXEC PGM=IEFBR14
//DD1 DD DSN=DATA.GDG.TEST(-0),DISP=(MOD,DELETE,DELETE)
//SYSOUT DD SYSOUT=*
//STEP2 EXEC PGM=SORT
//SORTIN DD DSN=DATA.GDG.TEST(-1),DISP=SHR
//SORTOUT DD DUMMY
//SYSOUT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
OPTION COPY
/*
//STEP3 EXEC PGM=IEFBR14
//DD2 DD DSN=DATA.GDG.TEST(-2),DISP=(MOD,DELETE,DELETE)
//SYSOUT DD SYSOUT=*
//STEP4 EXEC PGM=IEFBR14
//MODEL1 DD DSN=DATA.GDG.TEST(-2),DISP=(MOD,DELETE)
//STEP5 EXEC PGM=IEFBR14
//DD2 DD DSN=DATA.GDG.TEST(-1),DISP=(MOD,DELETE,DELETE)
//STEP6 EXEC PGM=IEFBR14
//DD2 DD DSN=DATA.GDG.TEST(-2),DISP=(MOD,DELETE,DELETE)
it deletes(0,3,2,4)--> because at the starting of STEP4 it encountered a Ambiguity, so it resolved the reference against the catologue. For STEP6, again it has ambiguity so again it tries to resolve the reference according to the catologue, now as there are not enough generation members present(as we have created only 5 members and deleted 4 already),it throws the message like below:
IEF286I GDGTST STEP6 DD2 - DISP FIELD INCOMPATIBLE WITH DSNAME
IEF272I GDGTST STEP6 - STEP WAS NOT EXECUTED.

Related

Remove duplicates on specific record type using JCL sort

can you please help me to achieve below goal JCL sort ?
I have input file with different set if records. I need to remove the duplicates only specific record type based on 10,04 position. There should not be any change in other types of records.
I need to remove duplicates oly for P4 on position 10,4.
iNPUT:
P1AAAAAAA0101xxxxxxx
P2AAAAAAA0101xxxxxxx
P4AAAAAAA0101xxxxxxx
P4AAAAAAA0101xxxxxxx
P4AAAAAAA0102xxxxxxx
P4AAAAAAA0103xxxxxxx
P4AAAAAAA0104xxxxxxx
P5AAAAAAA0101xxxxxxx
P7AAAAAAA0101xxxxxxx
P9AAAAAAA0101xxxxxxx
EXPECTED OUTPUT:
P1AAAAAAA0101xxxxxxx
P2AAAAAAA0101xxxxxxx
P4AAAAAAA0101xxxxxxx
P4AAAAAAA0102xxxxxxx
P4AAAAAAA0103xxxxxxx
P4AAAAAAA0104xxxxxxx
P5AAAAAAA0101xxxxxxx
P7AAAAAAA0101xxxxxxx
P9AAAAAAA0101xxxxxxx
I would like to present you a small solution, a Little complicated but it works, maybe someone will have another one, more compact than mine:
//S1 EXEC PGM=ICETOOL
//TOOLMSG DD SYSOUT=*
//DFSMSG DD SYSOUT=*
//IN DD *
P1AAAAAAA0101xxxxxxx
P2AAAAAAA0101xxxxxxx
P4AAAAAAA0101xxxxxxx
P4AAAAAAA0101xxxxxxx
P4AAAAAAA0102xxxxxxx
P4AAAAAAA0103xxxxxxx
P4AAAAAAA0104xxxxxxx
P5AAAAAAA0101xxxxxxx
P7AAAAAAA0101xxxxxxx
P7AAAAAAA0101xxxxxxx
P9AAAAAAA0101xxxxxxx
//T1 DD DSN=&&T1,UNIT=SYSDA,SPACE=(CYL,(5,5)),DISP=(,PASS)
//T2 DD DSN=&&T2,UNIT=SYSDA,SPACE=(CYL,(5,5)),DISP=(,PASS)
//T3 DD DSN=&&T3,UNIT=SYSDA,SPACE=(CYL,(5,5)),DISP=(,PASS)
//OUT DD SYSOUT=*
//TOOLIN DD *
COPY FROM(IN) TO(T1) USING(AST1)
COPY FROM(IN) TO(T2) USING(AST2)
SELECT FROM(T1) TO(T3) ON(10,4,CH) NODUPS
MERGE FROM(T2,T3) TO(OUT) USING(AST3)
//AST1CNTL DD *
INCLUDE COND=(1,2,CH,EQ,C'P4')
//AST2CNTL DD *
INCLUDE COND=(1,2,CH,NE,C'P4')
//AST3CNTL DD *
MERGE FIELDS=(1,14,CH,A)
Regards,
Andreas
Here you go.
//JOBNAME JOB 1,NOTIFY=&SYSUID
//STEP1 EXEC PGM=SORT
//SORTIN DD *
P1AAAAAAA0101XXXXXXX
P2AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0102XXXXXXX
P4AAAAAAA0103XXXXXXX
P4AAAAAAA0104XXXXXXX
P5AAAAAAA0101XXXXXXX
P7AAAAAAA0101XXXXXXX
P9AAAAAAA0101XXXXXXX
//SORTOUT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SYSIN DD *
INREC IFTHEN=(WHEN=INIT,BUILD=(1:1,20,21:SEQNUM,2,ZD)),
IFTHEN=(WHEN=(1,2,CH,EQ,C'P4'),OVERLAY=(21:C'01'))
SORT FIELDS=(1,2,CH,A,10,4,CH,A,21,2,CH,A)
SUM FIELDS=NONE
OUTREC FIELDS=(1:1,20)
I've used INREC IFTHEN to set sequence numbers at the end of the
record. Sequence numbers are set to 1 for records with first 2 bytes
as P4.
Control fields included in the SORT FIELDS statement are first 2
bytes, col 10 thru 4 bytes and col 21 thru 2 bytes (sequence number).
Note that sequence numbers for duplicate records in P4 will be 1. So
SUM FIELDS=NONE would remove just those records.
Output:
P1AAAAAAA0101XXXXXXX
P1AAAAAAA0101XXXXXXX
P2AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0102XXXXXXX
P4AAAAAAA0103XXXXXXX
P4AAAAAAA0104XXXXXXX
P5AAAAAAA0101XXXXXXX
P7AAAAAAA0101XXXXXXX
P9AAAAAAA0101XXXXXXX
Let's run the same set of SORT statements with following input. Note that first 2 records (P1) are duplicates along with P4.
//JOBNAME JOB 1,NOTIFY=&SYSUID
//STEP1 EXEC PGM=SORT
//SORTIN DD *
P1AAAAAAA0101XXXXXXX
P1AAAAAAA0101XXXXXXX
P2AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0102XXXXXXX
P4AAAAAAA0103XXXXXXX
P4AAAAAAA0104XXXXXXX
P5AAAAAAA0101XXXXXXX
P7AAAAAAA0101XXXXXXX
P9AAAAAAA0101XXXXXXX
//SORTOUT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SYSIN DD *
INREC IFTHEN=(WHEN=INIT,BUILD=(1:1,20,21:SEQNUM,2,ZD)),
IFTHEN=(WHEN=(1,2,CH,EQ,C'P4'),OVERLAY=(21:C'01'))
SORT FIELDS=(1,2,CH,A,10,4,CH,A,21,2,CH,A)
SUM FIELDS=NONE
OUTREC FIELDS=(1:1,20)
Output after running the job is shown below. Note that duplicate P1 record are preserved and duplicate records with specific record type (P4) is only removed.
P1AAAAAAA0101XXXXXXX
P1AAAAAAA0101XXXXXXX
P2AAAAAAA0101XXXXXXX
P4AAAAAAA0101XXXXXXX
P4AAAAAAA0102XXXXXXX
P4AAAAAAA0103XXXXXXX
P4AAAAAAA0104XXXXXXX
P5AAAAAAA0101XXXXXXX
P7AAAAAAA0101XXXXXXX
P9AAAAAAA0101XXXXXXX
Hope this helps.

JCL SEVERE MESSAGES

I am getting these error messages when I try to compile my program:
IEW2747S D90C ABEND 013-18 OCCURRED WHILE PROCESSING SEQUENTIAL DATA SET WITH DD
IEW2230S 0414 MODULE HAS NO TEXT.
IEW2677S 5130 A VALID ENTRY POINT COULD NOT BE DETERMINED.
IEW2008I 0F03 PROCESSING COMPLETED. RETURN CODE = 12.
Here is the JCL:
000100 //IBMP5 JOB (COMPILE),USERID,MSGCLASS=H,REGION=0M,
000200 // MSGLEVEL=(1,1),CLASS=A,NOTIFY=&SYSUID
000300 //*******************************************************************
000400 //* *
000401 //* THIS JCL WILL COMPILE, LINK-EDIT (BIND) AND RUN A PROGRAM *
000402 //* *
000410 //*******************************************************************
000420 //* COMPILATION STEP
000430 //*
001100 //STEP1 EXEC PGM=IBMZPLI,REGION=1M,PARM=('MACRO,OBJECT,INSOURCE')
001200 //STEPLIB DD DSNAME=IEL380.SIBMZPRC,DISP=SHR
001201 // DD DSNAME=IEL380.SIBMZCMP,DISP=SHR
001204 //SYSUT1 DD UNIT=SYSDA,SPACE=(CYL,(2,1))
002000 //SYSPRINT DD SYSOUT=*
002010 //SYSOUT DD SYSOUT=*
002100 //*
002510 //* SOURCE CODE MEMBER
002520 //*
002530 //PLI.SYSIN DD DSN=INVAT.SOURCE(PROG5),DISP=SHR
002531 //*
002532 //* TARGET FOR OBJECT FILE
002535 //*
002536 //SYSLIN DD DSN=INVAT.OBJ(PROG5),DISP=(OLD,PASS),UNIT=SYSALLDA,
002537 // SPACE=(CYL,(1,1)),DCB=(LRECL=80,BLKSIZE=800)
002540 //*
002541 //* LINKAGE (BIND) STEP
002542 //*
002550 //STEP2 EXEC PGM=IEWL,REGION=0M
002560 //SYSLIB DD DSNAME=SYS1.LINKLIB,DISP=SHR
002570 // DD DSNAME=CEE.SCEELKED,DISP=SHR
002580 //SYSLIN DD DSN=INVAT.OBJ(PROG5),DISP=SHR
002590 //LKED.SYSLMOD DD DSN=INVAT.LOAD(PROG5),DISP=SHR
002600 //SYSUT1 DD UNIT=SYSALLDA,SPACE=(TRK,(10,10))
002700 //SYSPRINT DD SYSOUT=*
002800 //*
002900 //* EXECUTION STEP
003000 //*
003100 //STEP3 EXEC PGM=PROG5
003200 //STEPLIB DD DSN=INVAT.LOAD(PROG5),DISP=SHR
003300 //SYSPRINT DD SYSOUT=*
003400 //SYSIN DD *
003800 /*
003900 //
normally (in all of the compile JCL I have ever looked at) the SYSLMOD, does not specify the member. So you that line would look something like this:
//SYSLMOD DD DSN=INVAT.LOAD,DISP=SHR
and then underneath that, you would include the member in the sysin:
//LKED.SYSIN DD *
ENTRY PROG5
NAME PROG5(R)
/*
all that together would give you something like this:
000100 //IBMP5 JOB (COMPILE),USERID,MSGCLASS=H,REGION=0M,
000200 // MSGLEVEL=(1,1),CLASS=A,NOTIFY=&SYSUID
000300 //*******************************************************************
000400 //* *
000401 //* THIS JCL WILL COMPILE, LINK-EDIT (BIND) AND RUN A PROGRAM *
000402 //* *
000410 //*******************************************************************
000420 //* COMPILATION STEP
000430 //*
001100 //STEP1 EXEC PGM=IBMZPLI,REGION=1M,PARM=('MACRO,OBJECT,INSOURCE')
001200 //STEPLIB DD DSNAME=IEL380.SIBMZPRC,DISP=SHR
001201 // DD DSNAME=IEL380.SIBMZCMP,DISP=SHR
001204 //SYSUT1 DD UNIT=SYSDA,SPACE=(CYL,(2,1))
002000 //SYSPRINT DD SYSOUT=*
002010 //SYSOUT DD SYSOUT=*
002100 //*
002510 //* SOURCE CODE MEMBER
002520 //*
002530 //PLI.SYSIN DD DSN=INVAT.SOURCE(PROG5),DISP=SHR
002531 //*
002532 //* TARGET FOR OBJECT FILE
002535 //*
002536 //SYSLIN DD DSN=INVAT.OBJ(PROG5),DISP=(OLD,PASS),UNIT=SYSALLDA,
002537 // SPACE=(CYL,(1,1)),DCB=(LRECL=80,BLKSIZE=800)
002540 //*
002541 //* LINKAGE (BIND) STEP
002542 //*
002550 //STEP2 EXEC PGM=IEWL,REGION=0M
002560 //SYSLIB DD DSNAME=SYS1.LINKLIB,DISP=SHR
002570 // DD DSNAME=CEE.SCEELKED,DISP=SHR
002580 //SYSLIN DD DSN=INVAT.OBJ(PROG5),DISP=SHR
002590 //SYSLMOD DD DSN=INVAT.LOAD,DISP=SHR
002600 //SYSUT1 DD UNIT=SYSALLDA,SPACE=(TRK,(10,10))
002700 //SYSPRINT DD SYSOUT=*
//LKED.SYSIN DD *
ENTRY PROG5
NAME PROG5(R)
/*
002800 //*
002900 //* EXECUTION STEP
003000 //*
003100 //STEP3 EXEC PGM=PROG5
003200 //STEPLIB DD DSN=INVAT.LOAD(PROG5),DISP=SHR
003300 //SYSPRINT DD SYSOUT=*
003400 //SYSIN DD *
003800 /*
003900 //
give that a try and see if that helps.
EDIT:
What you were missing and ultimately fixed this JCL was the SYSIN lines that I added to the link edit (LKED) step (one line for ENTRY and one line for NAME). Basically what was happening the link edit step (which is the last step in the compile and is responsible for copying the compiled code to the loadlib) did not know the entry name or the name of the program you were trying to compile. You had specified a SYSIN, but because the SYSIN was empty, you received the error saying the module had not text.

JCL what is wrong with this?

I am trying to crack this JCL and wonder what is wrong.
This is my code :
000001 //SORTJCL JOB
000002 //SORTSTEP EXEC PGM=SORT
000003 //SYSOUT DD SYSOUT=*
000004 //SORTOUT DD SYSOUT=*
000005 //SORTWK01 DD SPACE=(CYL,(1,1))
000006 //SORTIN DD DISP=SHR,DSN=Y2015.PUBLIC.DATA(AREACODE)
000007 //SYSIN DD *
000008 SORT FIELDS=(6,10,CH,A)
000009 // IF RC = 0 THEN
000010 //COPYSTEP EXEC PGM=ICEGENER
000011 //SYSUT1 DD DISP=SHR,DSN=Y2015.PUBLIC.DATA($005)
000012 //SYSUT2 DD DISP=SHR,DSN=&SYSUID..P2.OUTPUT($005)
000013 //SYSOUT DD SYSOUT=*
000014 //SYSPRINT DD SYSOUT=*
000015 //SYSIN DD DUMMY
000016 // ELSE
000017 // ENDIF
The purpose of this code - to read and sort Y2015.PUBLIC.DATA(AREACODE) and copy and write the output into MYID.P2.OUTPUT($005)
Can anyone explain to me what am I missing?
To "read and sort Y2015.PUBLIC.DATA(AREACODE)", you already use the correct //SORTIN in your first jobstep, in line 000006. The result of that read and sort gets written to //SORTOUT, which in your JCL seems to be written to SYSOUT=* (the spool), in line 000003.
But that's NOT what you should do (as per your "copy and write the output into MYID.P2.OUTPUT($005)"). So therefor you must modify that line 000003 like so:
000003 //SYSOUT DD DISP=SHR,DSN=&SYSUID..P2.OUTPUT($005)
After you applied this change, you also have to remove everything related to the 2nd jobstep (so starting from line 000009 and everything following that line).
If for whatever reason you still want all those lines to continue to be included in this JCL, just insert a new line in front of line 000009 that looks like so:
000009 //
This will cause all remaining JCL lines following it to just be ignored.

Incude the year from last month's date in the DSN using JCL

I have a request similar to the "JCL for previous month-year in dataset name" question. The answer to that question used an ALTER statement, which assumes knowledge of the date. I have JCL to append the year to the DSN, however in January, I need the previous year. I think this is possible with the help of SYNCSORT or DFSORT, but am not experienced with either of these. Any assistance is appreciated.
Here is the current JCL:
//B999999X JOB (80594,XXX),'MAKE DATE',
// CLASS=C,MSGCLASS=C,NOTIFY=&SYSUID
//STEP0100 EXEC PGM=EZACFSM1
//SYSOUT DD SYSOUT=(*,INTRDR)
//SYSIN DD DATA,DLM=##
//B8025501 JOB (,9999),'TESTING',
// CLASS=A,MSGCLASS=C,MSGLEVEL=(1,1),NOTIFY=&SYSUID
//STEP01 EXEC PGM=IEFBR14
//FILE01 DD DSN=B999999.TEST.MYFILE.FUEL&YR2,
// DISP=(NEW,CATLG,DELETE),
// UNIT=SYSDA,
// SPACE=(CYL,(10,10),RLSE),
// DCB=(LRECL=80,RECFM=FB,BLKSIZE=0)
/*
##
Actually, the answer to the question you reference first states "The best solution for this is to use the features of your job scheduler." That remains the best answer. That I showed how something could be done was not intended to imply I thought it was the best or most maintainable method.
You could do this with Rexx, or a Unix System Services shell script, or an awk script, or Perl, again constructing an ALTER statement to be used in a subsequent step to rename a statically-named dataset to one containing the date qualifier you desire.
There are some other techniques here.
But, if you have a job scheduler package available, you really should be using its capabilities.
Examples of the above proposed solutions follow.
Rexx program MKALTR
dsn = Arg(1)
Parse Value Date('O') With yy '/' mm '/' dd
If mm = 1 Then
If yy > 0 Then
yy = yy - 1
Else
yy = 99
outLine.1 = ' ALTER ' || dsn || ' - '
outLine.2 = ' NEWNAME(' || dsn || yy || ')'
outLine.0 = 2
Address TSO 'EXECIO * DISKW OUTPUT01 ( STEM' outLine. 'FINIS )'
Exit
JCL to run Rexx program MKALTR
//*
// SET &DS=MY.DATASET.NAME
//*
//CATLG EXEC PGM=IEFBR14
//STDOUT DD DISP=(,CATLG),
// DSN=&DS,
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(1,1))
//*
//MKALTER EXEC PGM=IKJEFT1B,PARM='MKALTR &DS'
//SYSEXEC DD DISP=SHR,DSN=dataset.where.rexx.code.resides
//SYSTSPRT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSTSIN DD DUMMY
//OUTPUT01 DD DISP=(,PASS),
// AVGREC=K,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(2,1))
//*
//DOALTER EXEC PGM=IDCAMS
//SYSIN DD DISP=(OLD,DELETE),DSN=*.MKALTER.OUTPUT01
//SYSPRINT DD SYSOUT=*
//*
Shell script mkaltr
let "mon=`date +'%m'`"
let "yr=`date +'%y'`"
if [ $mon -eq 01 ]
then
let "outyr=$yr-1"
fi
echo \ ALTER $1 -
echo \ \ NEWNAME\($1$outyr\)
JCL to run shell script mkaltr
//*
// SET &DS=MY.DATASET.NAME
//*
//CATLG EXEC PGM=IEFBR14
//STDOUT DD DISP=(,CATLG),
// DSN=&DS,
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(1,1))
//*
//MKALTER EXEC PGM=BPXBATCH,
// PARM='SH /path/to/script/mkaltr &DS'
//STDOUT DD DISP=(,PASS),
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(2,1))
//STDERR DD SYSOUT=*
//*
//DOALTER EXEC PGM=IDCAMS
//SYSIN DD DISP=(OLD,DELETE),DSN=*.MKALTER.STDOUT
//SYSPRINT DD SYSOUT=*
//*
Shell script mkaltr using awk
date +"$1 %m %y" | awk '
{
yr = $3
if ( $2 = 1 ) yr -= 1
if ( yr > 100 ) yr -= 100
printf( " ALTER %s -\n NEWNAME(%s%2d)\n", $1, $1, yr )
}'
JCL to run shell script mkaltr
//*
// SET &DS=MY.DATASET.NAME
//*
//CATLG EXEC PGM=IEFBR14
//STDOUT DD DISP=(,CATLG),
// DSN=&DS,
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(1,1))
//*
//MKALTER EXEC PGM=BPXBATCH,
// PARM='SH /path/to/script/mkaltr &DS'
//STDOUT DD DISP=(,PASS),
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(2,1))
//STDERR DD SYSOUT=*
//*
//DOALTER EXEC PGM=IDCAMS
//SYSIN DD DISP=(OLD,DELETE),DSN=*.MKALTER.STDOUT
//SYSPRINT DD SYSOUT=*
//*
Perl program mkaltr
if ( #ARGV ) {
$dsn = shift( #ARGV );
} else {
die "dataset name required";
}
($sec,$min,$hour,$mday,$mon,$year,$wday,$yday,$isdst) = localtime(time);
if ($mon == 0) {
$year -= 1
}
if ($year >= 100) {
$year -= 100;
}
printf (" ALTER %s -\n NEWNAME(%s%2d)\n", $dsn, $dsn, $year);
JCL to run Perl program mkaltr
//*
// SET &DS=MY.DATASET.NAME
//*
//CATLG EXEC PGM=IEFBR14
//STDOUT DD DISP=(,CATLG),
// DSN=&DS,
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(1,1))
//*
//MKALTER EXEC PGM=BPXBATCH,
// PARM='SH perl /path/to/perl/program/mkaltr &DS'
//STDOUT DD DISP=(,PASS),
// AVGREC=U,
// LRECL=80,
// RECFM=FB,
// SPACE=(80,(2,1))
//STDERR DD SYSOUT=*
//*
//DOALTER EXEC PGM=IDCAMS
//SYSIN DD DISP=(OLD,DELETE),DSN=*.MKALTER.STDOUT
//SYSPRINT DD SYSOUT=*
//*

How to run dymanic SQL through IKJEFT01 Utility?

How can we pass parameters in SQL query while executing IKJEFT01? Example:
//UNLOAD EXEC PGM=IKJEFT01
//SYSTSPRT DD SYSOUT=*
//SYSTSIN DD * DSN SYSTEM(DB2X) RETRY(120)
RUN PROGRAM(DSNTIAUL)
PLAN(DSNTIAUL) -
PARM('SQL')
END
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=D
//SYSREC00 DD DSN=FCSTN.AK.XXXXXX,
// DISP=(NEW,CATLG,DELETE),
//SYSPUNCH DD SYSOUT=*
//SYSIN DD *
SELECT * FROM ABC.DEF WHERE XYZ='999'
/*
Instead of giving value in sql query as '999' i want to pass the value through a variable.
How this can be done? Plz help...!
Have a separate step, prior to your UNLOAD step, that writes the variable line(s) of SQL to a temporary file. Then concatenate that temporary file with the unchanging lines of SQL.
Freehand...
//SETVAR EXEC PGM=PRM2FILE,PARM='WHERE XYZ=''&VAL'''
//SYSPRINT DD SYSOUT=*
//OUTPUT01 DD DISP=(NEW,PASS,DELETE),
// LRECL=80,
// AVGREC=U,
// RECFM=FB,
// SPACE=(80,(1,1),RLSE)
//*
//UNLOAD EXEC PGM=IKJEFT01
//SYSTSPRT DD SYSOUT=*
//SYSTSIN DD * DSN SYSTEM(DB2X) RETRY(120)
RUN PROGRAM(DSNTIAUL)
PLAN(DSNTIAUL) -
PARM('SQL')
END
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=D
//SYSREC00 DD DSN=FCSTN.AK.XXXXXX,
// DISP=(NEW,CATLG,DELETE),
//SYSPUNCH DD SYSOUT=*
//SYSIN DD *
SELECT * FROM ABC.DEF
// DD DISP=(OLD,PASS),DSN=*.SETVAR.OUTPUT01
//*
...where PRM2FILE is a program you write to take whatever is in the parm field and write it to the OUTPUT01 DD.
We do this a lot to accomplish the same goal you are trying to achieve.

Resources