Mainframe Utility: ESFRECD

Return to Mainframe Utilities Page

Module


/**********************************************************************
/* UTILITY: ESFRECD                                                   *
/* AUTHOR: DAVID LEIGH                                                *
/* FUNCTION: THIS UTILITY PROMPTS FOR INPUT OF A DB2 TABLE NAME AND AN*
/*           ASSOCIATED CSP RECORD NAME, AN ENDEVOR CCID, AND AN      *
/*           ENDEVOR COMMENT.  IT THEN CREATES JCL WHICH:             *
/*           1. RETRIEVES A RECORD FROM ENDEVOR                       *
/*           2. EXTRACTS THAT TABLE/VIEW'S INFORMATION FROM DB2       *
/*           3. CREATES AN ESF FORMAT RECORD FROM THE DB2 INFO.       *
/*           4. ADDS THAT BACK INTO ENDEVOR                           *
/**********************************************************************
PROC 0 TABLE() +
       CREATOR(USSTRD00) +
       RECORD() +
       CCID() +
       COMMENT() +
       ENVIRON(QUAL) +
       STAGE(D) +
       TYPE(RECD) +
       SYSTEM(STR) +
       SUBSYS(UNIPAC) +
       XRFILE('DUSC1.STR.DOCLIB(CSPDB2XR)') +
       TEMPJCL('&SYSUID..TEMP.ESFRECD.JCL') +
       JCLREVEW(N) +
       HELP +
       DEBUG

/*** CHECK THE DEBUG SWITCH ***/
IF &DEBUG = DEBUG THEN +
    CONTROL MSG LIST CONLIST SYMLIST NOFLUSH NOPROMPT ASIS
ELSE +
    CONTROL NOMSG NOLIST NOFLUSH NOPROMPT ASIS

IF &HELP = HELP THEN GOTO HELPSEC
                                                                              02
/**********************************************************************
/* GET THE USER'S FULL NAME                                           *
/**********************************************************************
SET SYSOUTTRAP = 1000
ACF
LIST *
END
SET SYSOUTTRAP = 0
SET SYSDVAL = &STR(&SYSNSUB(1,&SYSOUTLINE1))
READDVAL A B NAME1 NAME2 NAME3 NAME4 NAME5
SET FULLNAME = &STR(&NAME1 &NAME2 &NAME3 &NAME4 &NAME5)
                                                                              02
/**********************************************************************
/* ESTABLISH SOME PROCESSING VARIABLES                                *
/**********************************************************************
CALL 'SYS2.USC1.LINKLIB(USERINFO)' '&SYSUID '
SET TEMPJCL = &STR(&TEMPJCL)
SET LP = &STR((
SET RP = &STR()

/**********************************************************************
/* DISPLAY THE PANEL IF NO INPUT WAS PASSED                           *
/**********************************************************************
IF &STR(&TABLE)   >    AND +
   &STR(&RECORD)  >    AND +
   &STR(&CCID)    >    AND +
   &STR(&COMMENT) >    THEN GOTO PROCESS

ISPEXEC VGET (TABLE RECORD CCID COMMENT) SHARED

REDISPLAY: +
SET GENERATE =
ISPEXEC DISPLAY PANEL(ESFRECD)
IF &LASTCC > 7 THEN +
    DO
        IF &STR(&GENERATE) = Y THEN +
            DO
                SET ZEDSMSG =
                SET ZEDLMSG = &STR(*** SET GENERATE TO "N" BEFORE +
                                   QUITTING OR PRESS  TO +
                                   GENERATE ***)
                ISPEXEC SETMSG MSG(UTLZ001W)
                GOTO REDISPLAY
            END
        GOTO FINISH
    END
ELSE +
    DO
        /**************************************************************
        /* PERMIT DYNAMIC DEBUG TOGGLEING                             *
        /**************************************************************
        IF &ZCMD = &STR(DEBUG ON) THEN +
            DO
                SET DEBUG = DEBUG
                SET ZEDSMSG = &STR(DEBUG ON)
                SET ZEDLMSG = &STR(THE DEBUG SWITCH HAS BEEN SET ON)
                ISPEXEC SETMSG MSG(UTLZ000)
                GOTO REDISPLAY
            END
        IF &ZCMD = &STR(DEBUG OFF) THEN +
            DO
                SET DEBUG = DEBUG
                SET ZEDSMSG = &STR(DEBUG OFF)
                SET ZEDLMSG = &STR(THE DEBUG SWITCH HAS BEEN SET OFF)
                ISPEXEC SETMSG MSG(UTLZ000)
                GOTO REDISPLAY
            END
        /**************************************************************
        /* GET A TABLE/VIEW LIST FROM DB2                             *
        /**************************************************************
        IF &SYSINDEX(&STR(%),&STR(&TABLE)) > 0 THEN +
            SYSCALL GET_TABLE TABLE CREATOR DEBUG
        /**************************************************************
        /* GET A CSP RECORD NAME FROM THE CROSS REFERENCE FILE        *
        /**************************************************************
        IF &STR(&RECORD) = &STR(?) AND +
           &STR(&TABLE) >         THEN +
            DO
                ISPEXEC CONTROL DISPLAY LOCK
                ISPEXEC DISPLAY PANEL(ESFRECD)
                ISPEXEC SELECT +
                        CMD(%ESFRECD2 TABLE(&TABLE) XRFILE(&XRFILE))
                IF &LASTCC = 2000 THEN +
                    DO
                        SET ZEDSMSG =
                        SET ZEDLMSG = &STR(*** COULD NOT FIND A +
                                           CSP RECORD IN THE CROSS +
                                           REFERENCE FILE FOR THIS +
                                           TABLE ***)
                        ISPEXEC SETMSG MSG(UTLZ001W)
                        SET RECORD =
                        GOTO REDISPLAY
                    END
                ELSE ISPEXEC VGET RECORD SHARED
            END
        /**************************************************************
        /* PROCESS THE PROLOGUE OVERRIDE FLAG IF SET                  *
        /**************************************************************
        ISPEXEC CONTROL DISPLAY LOCK
        ISPEXEC DISPLAY PANEL(ESFRECD)
        SELECT (&STR(&PROLOVRD))
            /**********************************************************
            /* REFRESH THE PROLOGUE OVERRIDE FROM THE CROSS REFERENCE *
            /**********************************************************
            WHEN (R) DO
                ISPEXEC SELECT CMD(%ESFRECD4 XRFILE(&XRFILE) +
                                             RECORD(&RECORD) +
                                             &DEBUG)
                IF &LASTCC = 2000 THEN +
                    DO
                        SET ZEDSMSG =
                        SET ZEDLMSG = &STR(*** COULD NOT FIND A +
                                           CSP RECORD IN THE CROSS +
                                           REFERENCE FILE FOR THIS +
                                           TABLE ***)
                        ISPEXEC SETMSG MSG(UTLZ001W)
                        SET PROLOVRD = N
                        ISPEXEC VGET PROVRDSN SHARED
                        GOTO REDISPLAY
                    END
                ELSE +
                    SET PROLOVRD = Y
                ISPEXEC VGET PROVRDSN SHARED
            END
            /**********************************************************
            /* EDIT THE PROLOGUE OVERRIDE (BUILD FIRST IF NECESSARY)  *
            /**********************************************************
            WHEN (E) DO
                LISTDSI '&PROVRDSN'
                IF &LASTCC ¬= 0 THEN +
                    DO
                        ISPEXEC SELECT CMD(%ESFRECD4 XRFILE(&XRFILE) +
                                                     RECORD(&RECORD) +
                                                     &DEBUG)
                        ISPEXEC VGET PROVRDSN SHARED
                    END
                ISPEXEC EDIT DATASET('&PROVRDSN')
                SET PROLOVRD = Y
                ISPEXEC VGET PROVRDSN SHARED
            END
            /**********************************************************
            /* SELECT THE PROLOGUE OVERRIDE (BUILD 1ST IF NECESSARY)  *
            /**********************************************************
            WHEN (Y) DO
                ISPEXEC VGET PROVRDSN SHARED
                LISTDSI '&PROVRDSN'
                IF &LASTCC ¬= 0 THEN +
                    DO
                        ISPEXEC SELECT CMD(%ESFRECD4 XRFILE(&XRFILE) +
                                           RECORD(&RECORD) +
                                           &DEBUG)
                        IF &LASTCC = 2000 THEN +
                            DO
                                SET ZEDSMSG =
                                SET ZEDLMSG = &STR(*** COULD NOT FIND +
                                                   A CSP RECORD IN THE +
                                                   CROSS REFERENCE +
                                                   FILE FOR THIS TABLE +
                                                   ***)
                                ISPEXEC SETMSG MSG(UTLZ001W)
                                SET PROLOVRD = N
                                GOTO REDISPLAY
                            END
                    END
            END
        END
        /**************************************************************
        /* GO BACK TO REDISPLAY IF THE USER'S NOT READY TO GENERATE   *
        /**************************************************************
        IF &STR(&GENERATE) ¬= Y THEN GOTO REDISPLAY
    END

/**********************************************************************
/* PROCESS THE INPUT REQUEST                                          *
/**********************************************************************
PROCESS: +
SET ZEDSMSG =
SET ZEDLMSG = &STR(*** CREATING THE JCL ***)
ISPEXEC CONTROL DISPLAY LOCK
ISPEXEC DISPLAY MSG(UTLZ000W)

DELETE '&TEMPJCL'
FREE DDNAME(ISPFILE)

ALLOCATE DDNAME(ISPFILE) DSN('&TEMPJCL') +
         NEW CATALOG +
         UNIT(SYSDA) VOLUME(WRK$$$) +
         SPACE(1,1) TRACKS RELEASE +
         RECFM(F B) LRECL(80) BLKSIZE(23440) DSORG(PS)

ISPEXEC FTOPEN
ISPEXEC FTINCL ESFRECD
SET SAVECC = &LASTCC
ISPEXEC FTCLOSE

FREE DDNAME(ISPFILE)

IF &SAVECC > 0 THEN +
    DO
        ISPEXEC VGET ZERRLM
        SET ZEDSMSG = &STR(JCL CREATION ERROR)
        SET ZEDLMSG = &STR(&ZERRLM)
        ISPEXEC SETMSG MSG(UTLZ001)
    END

IF &JCLREVEW = &STR(Y) THEN +
    DO
        SET ZEDLMSG = &STR(*** NOTE:  YOU MUST SUBMIT THIS +
                           JCL YOURSELF ***)
        ISPEXEC SETMSG MSG(UTLZ000W)
        ISPEXEC EDIT DATASET('&TEMPJCL')
    END
ELSE +
    DO
        SUBMIT '&TEMPJCL'
        SET ZEDSMSG = &STR(JOB SUBMITTED)
        SET ZEDLMSG = &STR(*** THE CREATED JCL WAS SUBMITTED ***)
        ISPEXEC SETMSG MSG(UTLZ000)
    END

GOTO REDISPLAY

/**********************************************************************
/* GET OUT!                                                           *
/**********************************************************************
FINISH: EXIT

/**********************************************************************
/* QUERY DB2 TO GET A LIST OF TABLE NAMES                             *
/**********************************************************************
GET_TABLE: PROC 3 TABLE CREATOR DEBUG
SYSREF &TABLE &CREATOR &DEBUG

CONTROL END(END@)

SET ZEDSMSG =
SET ZEDLMSG = &STR(*** CREATING A DB2 TABLE LIST FROM THE CATALOG ***)
ISPEXEC CONTROL DISPLAY LOCK
ISPEXEC DISPLAY MSG(UTLZ000W)

FREE DD(SYSREC00 SYSIN SYSPRINT SYSPUNCH)
IF &DEBUG = DEBUG THEN +
    DO
        ALLOC DD(SYSPRINT) DA(*)
        ALLOC DD(SYSPUNCH) DA(*)
    END@
ELSE +
    DO
        ALLOC DD(SYSPRINT) DUMMY
        ALLOC DD(SYSPUNCH) DUMMY
    END@

SET DB2DSN = &STR(&SYSUID..TEMP.ESFRECD.TABLES)
DELETE '&DB2DSN'
ALLOC DD(SYSREC00) DSN('&DB2DSN') +
      NEW CATALOG +
      UNIT(SYSDA) VOLUME(WRK$$$) +
      SPACE(1,1) TRACKS RELEASE

ALLOC DD(SYSIN) +
      NEW +
      UNIT(SYSDA) VOLUME(WRK$$$) +
      SPACE(1,1) TRACKS RELEASE +
      RECFM(F B) LRECL(80) BLKSIZE(23440) DSORG(PS)

OPENFILE SYSIN OUTPUT
SET SYSIN = &STR(ESFRECD WHERE NAME LIKE '&TABLE' +
                           AND CREATOR LIKE '&CREATOR')
PUTFILE SYSIN
CLOSFILE SYSIN

DSN SYSTEM(DSNT)
    RUN  PROGRAM(DSNTIAUL) PLAN(DSNTIAUL) -
         LIB('SYS4.DSN.DSNT.RUNLIB.LOAD')
END

FREE DD(SYSREC00 SYSIN SYSPRINT SYSPUNCH)

ISPEXEC EDIT DATASET('&DB2DSN') MACRO(ESFRECDM)
ISPEXEC VGET COUNT SHARED
IF &COUNT = 1 THEN +
    DO
        SET ZTDSELS = 1
        ISPEXEC VGET (CREATOR TABLE) SHARED
        GOTO SELECT_SECTION
    END@

/**********************************************************************
/* SHOW THE LIST ON A SCREEN SO THE USER CAN CHOOSE ONE               *
/**********************************************************************
DISPLAY_TABLES: +
SET ZTDMARK = &STR(*** END OF DB2 TABLES/VIEWS LIKE "&TABLE" ***)
ISPEXEC TBDISPL TEMPESFR PANEL(ESFRECD2)

SET PANELCC = &LASTCC

IF &PANELCC > 8 THEN +
    DO
        SET ZEDLMSG = &STR(PROBABLE ERROR IN ESFRECD2 PANEL. +
                           TBDISPL RC = &PANELCC)
        ISPEXEC SETMSG MSG(UTLZ001W)
        GOTO FINISH_PROC
    END@

/**********************************************************************
/* SEE HOW MANY THE USER SELECTED.  THEY CAN ONLY DO ONE!             *
/**********************************************************************
SELECT_SECTION: +
SELECT (&ZTDSELS)
    WHEN (0) DO
        SET TABLE =
        SET CREATOR =
        IF &PANELCC > 7 THEN GOTO FINISH_PROC
        GOTO DISPLAY_TABLES
    END@
    WHEN (1) GOTO FINISH_PROC
    OTHERWISE DO
        SET ZEDSMSG = &STR(SELECT ONLY 1)
        SET ZEDLMSG = &STR(YOU MAY SELECT ONLY 1 TABLE ON THIS SCREEN)
        ISPEXEC SETMSG MSG(UTLZ001)
        SET SEL =
        SET ZTDSELS =
        GOTO DISPLAY_TABLES
    END@
END@

FINISH_PROC: RETURN
END@
            


Documentation


 ESFRECD is a utility design to streamline the process of reflecting changes in
 DB2 data structures in the CSP records which point to those data structures.

 It's initial premise or raison detre is that DBA's typically only deal with CSP
 and ENDEVOR in the area of CSP records.  The process of logging into CSP in
 CICS and ENDEVOR in TSO if one is not usually in these environments and will
 only be there briefly can be tedious.  Additionally, the issue of MSL
 maintenance is unnecessarily added to the equation.  Since the DB2 catalog
 contained everything needed to update the CSP record and DB2, CSP and ENDEVOR
 all can be updated in batch, this utility was created to automate those steps
 into a batch job.

 ESFRECD performs this CSP record update process in the following steps:

  1. Create a temporary MSL and EZEWORK dataset.  This insures that no conflict
     will arise with the user's own MSL and EZEWORK dataset.  It also insures
     that "stray" CSP ITEMs will not mess things up unexpectedly.

  2. Initialize the temporary MSL with batch CSP so that ENDEVOR can write to
     it.

  3. Retrieve the record element from ENDEVOR into the temporary MSL.

  4. Export the record from the temporary MSL into a sequential file in ESF
     format.

  5. Extract the column information from DB2 which is necessary to refresh
     (actually rebuild) the CSP record.

  6. Sort this information in column sequence order and remove some special HEX
     characters which will give subsequent batch TSO steps some problems.

  7. Invoke batch TSO/ISPF to create an ISPF table of the DB2 table information
     and an ISPF table of the prologue information for the record from either:

     A. The prologue "override" dataset created by using a "Y", "E", or "R" in
        the "CSP Prologue Override" field.
     B. The ESF CSP record prologue from step #4 above.
     C. If not present, from the DB2 REMARKS column for that table/view.

     Once these ISPF tables are built, they are used in ISPF file tailoring
     services to create the new CSP record in ESF format.

  8. Delete/Define the temporary MSL again to insure you are starting with a
     clean MSL.

  9. Import the newly created ESF CSP record into the temporary MSL.

 10. Invoke ENDEVOR to ADD/UPDATE the CSP record back into ENDEVOR.

 When you invoke ESFRECD, you are presented with a screen on which you can type
 in the necessary information.  The data needed is as follows:

  1. A DB2 table or view name.  This name (unqualified) will the CSP record will
     point to.

  2. A DB2 CREATOR.  Even though the record will be unqualified in CSP, the
     qualification is needed to access the appropriate information in the DB2
     catalog table SYSCOLUMNS.
1
  3. A CSP record name.

  4. An ENDEVOR CCID.  Required for the ENDEVOR steps.

  5. An ENDEVOR comment.  Required for the ENDEVOR steps.

  7. A value in the "CSP Prologue Override" field.  This value must be one of
     the following:

     "N" - This indicates that the prologue from ENDEVOR or from DB2 should not
           be overridden in favor of a user-developed prologue.  This is the
           default value.

     "Y" - This indicates that the prologue from ENDEVOR or from DB2 should be
           overridden in favor of a user-developed prologue.  When this option
           is selected, ESFRECD determines if a prologue override dataset with
           the name userid.TEMP.ESFRECD.PROVRDSN exists.  If it does exist,
           nothing is done and the flag is just set to "Y".  If it does not
           exist, it is created (always on work packs) , and the prologue for
           the record is extracted from the CSP to DB2 cross reference file and
           placed in the file just created.

     "R" - This value indicates that the prologue override dataset is to be
           deleted and recreated using the same processing as an initial "Y"
           value described above.  After the refresh has taken place, the value
           of the flag becomes "Y".

     "E" - This indicates that the user wants to edit the override dataset to
           either view its contents and/or to change the contents.  If the
           prologue override dataset does not exist, it will be created and
           populated like the Refresh or initial "Y" instance described above,
           and then edited.  If it does exist, it will just be edited
           immediately.  When the edit session ends, the flag value becomes "Y".

  8. A Y/N flag to trigger ESFRECD to generate the batch job.

  9. A Y/N flag to indicate whether the generated job should be edited, or not
     edited and submitted automatically.

 Two special features are supported from the panel to present a list of DB2
 tables/views to choose from and to access a CSP/DB2 cross reference file to
 populate the CSP record field if this is an existing record.

 If you can't remember how to spell a given table/view or just which one you
 want to choose, specify the table name (and/or the CREATOR) with a '%' at the
 end of the string you DO know, and ESFRECD will query the DB2 catalog using a
 "LIKE" WHERE predicate and bring up a panel with a list of tables/views to
 choose from.  On this panel, type an "S" next to the table/view name you wish
 to choose and press ENTER.  You are returned to the main ESFRECD panel and the
 TABLE and CREATOR fields are populated with your choice.
1
 If this is an existing CSP record, you now need to know which record name is
 associated with this DB2 object.  On UNISTAR, we have been maintaining a
 cross-reference file of CSP record names and DB2 table/view names.  It is in
 'DUSC1.STR.DOCLIB(CSPDB2XR)' and is recreated each time the CSPDB2XR utility is
 executed.  Since its format is consistant, ESFRECD can reference it and extract
 the information it needs.  To use the cross reference to determine the CSP
 record name, you must have the DB2 table/view name field populated with a full
 name and a "?" in the CSP record name.  When you press  with these
 fields set in this manner ESFRECD will access the cross-reference file and
 return the name of the CSP record into the CSP record field on the panel.

 Now you're ready to generate a job to actually do the work!

 To do this, just change the "N" to a "Y" in the "Generate JCL Now?" field and
 press .  If the "Review JCL Prior To Submit ?" field value is "N", the
 generated job will be submitted automatically.  If the value is "Y", however,
 you will be taken into an edit session on the JCL.  You must submit the JCL
 yourself if you choose this route.
            


Leave a Reply

This site uses Akismet to reduce spam. Learn how your comment data is processed.