chkiran2
New User
Joined: 24 Jun 2004 Posts: 24 Location: Gurgoan
|
|
|
|
Hi
I got this done by 2 methods. One using only JCL and the other using COBOL program. I am giving both the methods so that it will be useful for some one in future.
Method 1: (USING JCL)
The following JCL creates a dataset with Current date & time at the time of creation of dataset and copies the data from a source dataset into the newly created dataset.
Code: |
//ABAB77V1 JOB (0400,PT,PES),'KIRAN',CLASS=C,MSGCLASS=X,
// MSGLEVEL=(1,1),NOTIFY=ABAB77,REGION=0008192K
//STEP0100 EXEC PGM=EZACFSM1
//SYSOUT DD SYSOUT=(*,INTRDR)
//SYSIN DD DATA,DLM=@@
//ABAB77V2 JOB (0400,PT,PES),
// 'VIJAY',
// CLASS=C,
// MSGCLASS=X,
// NOTIFY=&SYSUID
//STEPK1 EXEC PGM=IEBGENER
//SYSPRINT DD SYSOUT=*
//SYSUT1 DD DSN=ABAB.TX.SND.SQUS0001.SI,DISP=SHR
//SYSUT2 DD DSN=ABAB.TX.SND.SQUS0001.SI.D&LYYMMDD..T&LHHMMSS,
// DISP=(NEW,CATLG,DELETE),
// SPACE=(CYL,(2,2),RLSE),
// DCB=(LRECL=890,RECFM=FB)
//SYSIN DD DUMMY
@@
|
Method 2:
we can get the desired result using COBOL program. Here is the tested program which allocates/creates a new dataset and then copies the data from an file to the newly created file using IEBGENER.
I am sharing this so that it may be useful for some one later.
Code: |
COBOL PROGRAM:
IDENTIFICATION DIVISION.
PROGRAM-ID. DSDATE.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-DATE PIC X(06).
01 WS-TIME-IN PIC X(08).
01 WS-TIME PIC X(06).
*
PROCEDURE DIVISION.
*
000-MAIN.
ACCEPT WS-DATE FROM DATE.
ACCEPT WS-TIME-IN FROM TIME.
MOVE WS-TIME-IN (1:6) TO WS-TIME.
DISPLAY '//KIRAN1CD JOB (0400,XXX),''KIRAN CH'',CLASS=B,'
DISPLAY '// MSGLEVEL=(1,1),NOTIFY=MGPB16,REGION=4M,'
DISPLAY '// MSGCLASS=X'
DISPLAY '//GENER01 EXEC PGM=IEBGENER'
DISPLAY '//SYSIN DD DUMMY'
DISPLAY '//SYSPRINT DD SYSOUT=*'
DISPLAY '//SYSUT1 DD DSN=XYXYXY.TST.DATA,DISP=SHR'
DISPLAY '//SYSUT2 DD DSN=XYXYXY.D' WS-DATE '.'
'T' WS-TIME ','
DISPLAY '// DISP=(NEW,CATLG,DELETE),'
DISPLAY '// DCB=(LRECL=80,RECFM=FB,BLKSIZE=0,DSORG=PS),'
DISPLAY '// SPACE=(TRK,(09,03),RLSE),'
DISPLAY '// UNIT=DISK'
DISPLAY '/*EOF'
DISPLAY '//'.
000-EXIT.
STOP RUN.
Compile above program and use following JCL to execute this:
//KIRANCD JOB (0400,XXX),'KIRAN CH',CLASS=B,
// MSGLEVEL=(1,1),NOTIFY=MGPB16,REGION=4M,
// MSGCLASS=X
//STEP01 EXEC PGM=DSDATE
//STEPLIB DD DSN=XYXYXY.TEST.PRG,DISP=SHR
//SYSOUT DD SYSOUT=(*,INTRDR)
//SYSIN DD DUMMY
//
|
|
|