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

Getting File Creation Date


IBM Mainframe Forums -> JCL & VSAM
Post new topic   This topic is locked: you cannot edit posts or make replies.
View previous topic :: View next topic  
Author Message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Fri May 15, 2009 12:18 pm
Reply with quote

Hi All,

Can you please help me if we can get file creation date and file name in a output file?

EX:-
DSN : X.Y.Z >>> Creation date 20090515
DSN : A.B.C >>> Creation date 20090513

I need to get these dataset names as well creation dates in a output dataset...

//IN DD DSN=X.Y.Z,DISP=SHR
// DD DSN=A.B.C,DISP=SHR

//OUT DD DSN=M.N.Q,DISP=(NEW,CATLG)

M.N.Q SHOULD HAVE THE RECORD

X.Y.Z20090515A.B.C20090513 >>> RECORD
Back to top
View user's profile Send private message
expat

Global Moderator


Joined: 14 Mar 2007
Posts: 8797
Location: Welsh Wales

PostPosted: Fri May 15, 2009 3:31 pm
Reply with quote

I've probably got a REXX code archived somewhere
Back to top
View user's profile Send private message
expat

Global Moderator


Joined: 14 Mar 2007
Posts: 8797
Location: Welsh Wales

PostPosted: Fri May 15, 2009 6:10 pm
Reply with quote

This is for batch mode, you will need a CATIN DD * statement to select the HLQ etc.
You can use full * ** % %% functionality in the CATIN DD *.
Code:

/* REXX **                                                           */
 "EXECIO * DISKR CATIN ( STEM CAT. FINIS"
 DO KCNT = 1 TO CAT.0
 KEY = SUBSTR(CAT.KCNT,1,44)
MODRSNRC = SUBSTR(' ',1,4)
CSIFILTK = SUBSTR(KEY,1,44)
CSICATNM = SUBSTR(' ',1,44)
CSIRESNM = SUBSTR(' ',1,44)
CSIDTYPS = SUBSTR(' ',1,16)
CSICLDI  = SUBSTR('Y',1,1)
CSIRESUM = SUBSTR(' ',1,1)
CSIS1CAT = SUBSTR(' ',1,1)
CSIRESRV = SUBSTR(' ',1,1)
CSINUMEN = '0001'X
CSIFLD1  = 'DSCRDT2 '
CSIOPTS  = CSICLDI || CSIRESUM || CSIS1CAT || CSIRESRV
CSIFIELD = CSIFILTK || CSICATNM || CSIRESNM || CSIDTYPS || CSIOPTS
CSIFIELD = CSIFIELD || CSINUMEN || CSIFLD1
WORKLEN = 64000
DWORK = '0000FA00'X || COPIES('00'X,WORKLEN-4)
RESUME = 'Y'
CATNAMET = SUBSTR(' ',1,44)
DNAMET = SUBSTR(' ',1,44)
DO WHILE RESUME = 'Y'
 ADDRESS LINKPGM 'IGGCSI00  MODRSNRC  CSIFIELD  DWORK'
 RESUME = SUBSTR(CSIFIELD,150,1)
 USEDLEN = C2D(SUBSTR(DWORK,9,4))
 POS1=15
 DO WHILE POS1 < USEDLEN
   IF SUBSTR(DWORK,POS1+1,1) = '0'
    THEN DO
         CATNAME=SUBSTR(DWORK,POS1+2,44)
         IF CATNAME ^= CATNAMET THEN
          DO
           SAY 'CATALOG ' CATNAME
           SAY ' '
           CATNAMET = CATNAME
          END
         POS1 = POS1 + 50
         END
   DNAME = SUBSTR(DWORK,POS1+2,44)
   IF SUBSTR(DWORK,POS1+1,1) = 'C' THEN DTYPE = 'CLUSTER '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'D' THEN DTYPE = 'DATA    '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'I' THEN DTYPE = 'INDEX   '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'A' THEN DTYPE = 'NONVSAM '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'H' THEN DTYPE = 'GDS     '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'B' THEN DTYPE = 'GDG     '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'R' THEN DTYPE = 'PATH    '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'G' THEN DTYPE = 'AIX     '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'X' THEN DTYPE = 'ALIAS   '
   ELSE IF SUBSTR(DWORK,POS1+1,1) = 'U' THEN DTYPE = 'UCAT    '
   ELSE DTYPE = '        '
    POS1 = POS1 + 46
    POS2 = POS1 +  6
    TES01   = C2X(SUBSTR(DWORK,POS2,4))
    EXCENT  = SUBSTR(TES01,7,2)
    EXYEAR  = SUBSTR(TES01,1,2)
    EXDATE  = SUBSTR(TES01,3,3)
    IF DNAMET <> DNAME THEN DO
     DNAMET=DNAME
     IF DTYPE <> 'GDG     ' & DTYPE <> 'ALIAS   ' THEN DO
      IF EXYEAR <> 0 | EXDATE /= 0 THEN DO
       IF EXCENT = 0 THEN DO
        EXYEAR = EXYEAR + 1900
        SAY COPIES(' ',8) DTYPE DNAME  EXYEAR"/"EXDATE
       END
       ELSE IF EXCENT = 1 THEN DO
        EXYEAR = EXYEAR + 2000
        SAY COPIES(' ',8) DTYPE DNAME  EXYEAR"/"EXDATE
       END
       ELSE DO
        EXYEAR = EXYEAR + (EXCENT * 100)
        SAY COPIES(' ',8) DTYPE DNAME  EXYEAR"/"EXDATE
       END
      END
     END
    END
    POS1 = POS1 + C2D(SUBSTR(DWORK,POS1,2))
  END
END
END
Back to top
View user's profile Send private message
Skolusu

Senior Member


Joined: 07 Dec 2007
Posts: 2205
Location: San Jose

PostPosted: Fri May 15, 2009 10:34 pm
Reply with quote

mazahar,

The following JCL will give you the desired results


Code:

//STEP0100 EXEC PGM=IKJEFT01                       
//SYSTSPRT DD DSN=&&L,                             
//            DISP=(,PASS),                       
//            SPACE=(CYL,(1,1),RLSE),             
//            DCB=(LRECL=80,RECFM=FB,BLKSIZE=0)   
//SYSTSIN  DD *                                   
  LISTCAT ENT('X.Y.Z') ALL           
  LISTCAT ENT('A.B.C') ALL       
//*
//STEP0200 EXEC PGM=SORT                                         
//SYSOUT   DD SYSOUT=*                                           
//SORTIN   DD DSN=&&L,DISP=(OLD,PASS)                             
//SORTOUT  DD SYSOUT=*                                           
//SYSIN    DD *                                                   
  INCLUDE COND=(01,7,CH,EQ,C'NONVSAM',OR,                         
                37,8,CH,EQ,C'CREATION')                           
                                                                 
  INREC IFTHEN=(WHEN=(1,7,CH,EQ,C'NONVSAM'),                     
  BUILD=(17,44,+0,TO=PD,LENGTH=4,81:SEQNUM,4,ZD)),               
  IFTHEN=(WHEN=(37,8,CH,EQ,C'CREATION'),                         
  BUILD=(44X,X'01',55,6,UFF,PD,LENGTH=3,81:SEQNUM,4,ZD))         
                                                                 
  SORT FIELDS=(81,4,CH,A),EQUALS                                 
  SUM FIELDS=(45,4,PD) 
                                         
  OUTREC IFTHEN=(WHEN=INIT,OVERLAY=(45:45,4,DT1,EDIT=(TTTTTTTT))),
  IFTHEN=(WHEN=GROUP,BEGIN=(81,4,ZD,EQ,1),PUSH=(54:1,52))         
                                                                 
  OUTFIL REMOVECC,NODETAIL,BUILD=(114X),                         
  TRAILER1=(54,52,1,52,C'>>> RECORD')                             
/*
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Mon May 18, 2009 4:54 pm
Reply with quote

Skolusu Thanks a lot,

But i dont think we can use IFTHEN in our org, because i am getting the below error when i submit it.

wer251a Include/Omit invalid self def term
wer268a Inrec statement : syntax error
wer275a No Keywords found on control statement


As well, we are passing dataset names in SYSIN in the job which you have provided, actually my job needs to run in prod, i cant edit sysin daily, can i pass the names of datasets to sysin in any other way? i mean my input data sets are GDG's which will get created by my upstream, once GDG version is created, that latest version needs to be processed and same ones NAME and Creation date needs to be printed on a report.
Back to top
View user's profile Send private message
expat

Global Moderator


Joined: 14 Mar 2007
Posts: 8797
Location: Welsh Wales

PostPosted: Mon May 18, 2009 5:05 pm
Reply with quote

Skolusu has given a DFsORT solution, your product is SYNCSORT. Although similar products, there will be differences between syntax and functionality.
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Mon May 18, 2009 6:40 pm
Reply with quote

Expat,

Please can you give me Syncsort sntax for the same.
Back to top
View user's profile Send private message
expat

Global Moderator


Joined: 14 Mar 2007
Posts: 8797
Location: Welsh Wales

PostPosted: Mon May 18, 2009 7:07 pm
Reply with quote

Mazahar wrote:
Expat,
Please can you give me Syncsort sntax for the same.

DFSORT installed here, but the REXX code works perfectly well.
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Mon May 18, 2009 11:39 pm
Reply with quote

Hello,

Quote:
Please can you give me Syncsort sntax for the same.
I believe that is correct syntax for Syncsort. . .

I suspect your system is not running the current version of Syncsort.

You need to post the complete informational output from the failed run.
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Wed May 20, 2009 7:16 pm
Reply with quote

Dick,

thanks for your reply, those aer only the messages i am getting when i submit.

thanks
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Wed May 20, 2009 8:06 pm
Reply with quote

Dick, Skolusu

I made a stupid mistake, now its fine. It gave me what exactly i require.

Thanks a lot.

And one more thing,

I am giving dataset names in LISTCAT ENT manually, Cant we make it with a symobolic or something else to pick my job input data sets automatically?
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Wed May 20, 2009 10:23 pm
Reply with quote

Hello,

Good to hear it is working icon_smile.gif

Quote:
those aer only the messages i am getting when i submit.
For future reference, i'll wager there is more in the sysout than only those 3 messages. . . Your control statements will be repeated and at the top of the page is almost surely the version release information.

When we ask for the complete info, we really do mean the complete info, not just some subset you choose. . .
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Wed May 20, 2009 10:32 pm
Reply with quote

Dick,

Understood :-)

I am giving dataset names in LISTCAT ENT manually, Cant we make it with a symobolic or something else to pick my job input data sets automatically?
Back to top
View user's profile Send private message
Douglas Wilder

Active User


Joined: 28 Nov 2006
Posts: 305
Location: Deerfield IL

PostPosted: Wed May 20, 2009 10:56 pm
Reply with quote

Would you mean something like this?
Code:

//  SET HLQ=X                               
//  SET NODE2=Y                         
//  SET NODE3=Z
//STEP10 EXEC PGM=IKJEFT01,                   
//   PARM='LISTCAT ENT(''&HLQ..&NODE2..&NODE3'') ALL'
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Wed May 20, 2009 10:59 pm
Reply with quote

douglas

Yes, thanks a lot.
Back to top
View user's profile Send private message
Bill Dennis

Active Member


Joined: 17 Aug 2007
Posts: 562
Location: Iowa, USA

PostPosted: Thu May 21, 2009 2:30 am
Reply with quote

Just to clarify, the date returned from LISTCAT is the date the catalog entry was created. This may not be the same as when the dataset was created. An uncatalog/recatalog process could alter the date.
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Thu May 21, 2009 2:47 pm
Reply with quote

Douglas,

When i give
// SET FILE1=X.Y.Z
// SET FILE2=A.B.C
PARM='LISTCAT ENT(''&FILE1..&FILE2'') ALL'

its taking file names as X.Y.Z.A.B.C and giving me Invalid file name

if i give

PARM='LISTCAT ENT(''&FILE1&FILE2'') ALL'

its taking file names as X.Y.ZA.B.C and giving me Invalid file name

if i give

PARM='LISTCAT ENT(''&FILE1 &FILE2'') ALL'

its taking file names as X.Y.Z A.B.C and giving me Invalid file name

Can you please tell me exact PARM for IKJEFT
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Thu May 21, 2009 7:57 pm
Reply with quote

Hello,

Quote:
Can you please tell me exact PARM for IKJEFT

You need 2 separate executions. . . .
Back to top
View user's profile Send private message
Mazahar

New User


Joined: 11 Dec 2007
Posts: 82
Location: hyderabad

PostPosted: Fri May 22, 2009 11:55 pm
Reply with quote

Hi All,

Just wanted to update you guys that I made it like this and it has worked for me.

// SET FILE1=X.Y.Z,
// FILE2=A.B.C
//STEP0100 EXEC PGM=IKJEFT01,
// PARM='LISTCAT ENT(''&FILE1'') ALL'
//SYSTSPRT DD DSN=&&L,
// DISP=(NEW,PASS),
// SPACE=(CYL,(1,1),RLSE),
// DCB=(LRECL=80,RECFM=FB,BLKSIZE=0)
//SYSTSIN DD *
/*
//STEP0200 EXEC PGM=IKJEFT01
//SYSTSPRT DD DSN=&&L,
// PARM='LISTCAT ENT(''&FILE2'') ALL'
// DISP=(MOD,PASS),
// SPACE=(CYL,(1,1),RLSE),
// DCB=(LRECL=80,RECFM=FB,BLKSIZE=0)
//SYSTSIN DD *
//*
//STEP0200 EXEC PGM=SORT
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=&&L,DISP=(OLD,PASS)
//SORTOUT DD SYSOUT=*
//SYSIN DD *
INCLUDE COND=(01,7,CH,EQ,C'NONVSAM',OR,
37,8,CH,EQ,C'CREATION')

INREC IFTHEN=(WHEN=(1,7,CH,EQ,C'NONVSAM'),
BUILD=(17,44,+0,TO=PD,LENGTH=4,81:SEQNUM,4,ZD)),
IFTHEN=(WHEN=(37,8,CH,EQ,C'CREATION'),
BUILD=(44X,X'01',55,6,UFF,PD,LENGTH=3,81:SEQNUM,4,ZD))

SORT FIELDS=(81,4,CH,A),EQUALS
SUM FIELDS=(45,4,PD)

OUTREC IFTHEN=(WHEN=INIT,OVERLAY=(45:45,4,DT1,EDIT=(TTTTTTTT))),
IFTHEN=(WHEN=GROUP,BEGIN=(81,4,ZD,EQ,1),PUSH=(54:1,52))

OUTFIL REMOVECC,NODETAIL,BUILD=(114X),
TRAILER1=(54,52,1,52,C'>>> RECORD')
/*
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Sat May 23, 2009 12:16 am
Reply with quote

Good to hear it is working - thanks for letting us know icon_smile.gif

d
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   This topic is locked: you cannot edit posts or make replies. View Bookmarks
All times are GMT + 6 Hours
Forum Index -> JCL & VSAM

 


Similar Topics
Topic Forum Replies
No new posts How to split large record length file... DFSORT/ICETOOL 10
No new posts Extracting Variable decimal numbers f... DFSORT/ICETOOL 17
No new posts SFTP Issue - destination file record ... All Other Mainframe Topics 2
No new posts Modifying Date Format Using DFSORT DFSORT/ICETOOL 9
No new posts Access to non cataloged VSAM file JCL & VSAM 18
Search our Forums:

Back to Top