This sample program uses the MVSCASPB API to retrieve various subsets of data, and writes the returned data to an output file.
identification division. program-id. Program1. environment division. configuration section. input-output section. file-control. SELECT ASCII-FILE ASSIGN TO ASCII-DSN ORGANIZATION IS LINE SEQUENTIAL FILE STATUS ASCII-FILE-STATUS. data division. FILE SECTION. FD ASCII-FILE LABEL RECORDS STANDARD. 01 ASCII-DATA PIC X(80). working-storage section. 01 ascii-file-status pic xx. 01 ascii-dsn pic x(250). 01 disp-rc pic 9999. 01 disp-rsn pic 9999. 01 disp-type pic Z9. 01 disp-job-nbr pic 9(9). *> Increased to allow for *> 7 digit numbers 01 disp-cc. 03 disp-cc-type pic x(01). 03 disp-cc-nbr pic 9(04). 01 save-job-name pic x(8). 01 save-job-nbr pic x(4) comp-x. 01 ws-pb-get-version pic 9(04). 01 ws-pubcas-spl-format pic x(01) comp-x. 88 ws-SPL-FORMAT-1 VALUE 1. *> 5 digit casspool.dat 88 ws-SPL-FORMAT-2 VALUE 2. *> unused 88 ws-SPL-FORMAT-3 VALUE 3. *> restructed spljob 88 ws-SPL-FORMAT-4 VALUE 4. 88 ws-SPL-FORMAT-5 VALUE 5. 01 ws-idx1 pic x(04) comp-5. 01 pubcas-area. copy "mfpubcas.cpy" replacing ==()== by ==pubcas==. procedure division. *> specify were the output should be written move '$outdir/output.txt' to ASCII-DSN open output ascii-file if ascii-file-status <> '00' display 'open output failed ' ascii-file-status goback end-if perform get-messages *> type 6 perform get-o-hold *> type 7 perform get-ds-hold *> type 9 perform get-ds-out *> type 10 *> With the new spool control files (ws-SPL-FORMAT-3) *> there aren't any type 7 or 8 records. *> So next 4 methods will not return any records. *> Use type 9 and 10 (as above) perform get-o-hold-type-jobname *> type 7 by job name perform get-o-hold-type-create-date *> type 7 by date perform o-spool-files-jobname *> type 8 and associated *> type 10s perform o-held-spool-files-jobname *> type 7 and associated *> type 9s if ws-SPL-FORMAT-3 *> we are using the new spool control file format *> so we can ask for completed jobs perform get-completed-jobs *> type 20 end-if display 'test prog ended ' goback. o-held-spool-files-jobname section. move spaces to ascii-data perform write-outfile move 'By Jobs with held output spool files ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas *> loop through the type output records to find jobs with *> output spool files perform until pubcas-retcode <> 0 or pubcas-type <> pubcas-o-hold-78 *> for each o-hold record *> print details *> save key *> get associated output spool records (ds-hold) *> reposition for next o-hold record move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move pubcas-job-name to save-job-name move pubcas-job-nbr to save-job-nbr move low-values to pubcas-area move 78-KEY-IS-job-NUMBER to pubcas-key-id move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode <> 0 or pubcas-job-nbr <> save-job-nbr *> all the output spool files for this job if pubcas-type = pubcas-ds-hold-78 move spaces to ascii-data string ' ' delimited by size pubcas-SYSOT-STEP-NAME delimited by size ',' delimited by size pubcas-SYSOT-PSTP-NAME delimited by size ',' delimited by size pubcas-SYSOT-DD-NAME delimited by size into ascii-data perform write-outfile end-if perform call-pubcas end-perform *> reposition on the next job name that has a type 8 record move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move pubcas-o-hold-78 to pubcas-type move save-job-name to pubcas-job-name move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas *> get next next job move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas if pubcas-job-name = save-job-name and pubcas-job-nbr = save-job-nbr *> STGT and GN gets the same type 8 *> record ( duplicate keys allowed ) *> so need a second GN to get the next record move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-if end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. o-spool-files-jobname section. move spaces to ascii-data perform write-outfile move 'By Jobs with output spool files ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-out-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas *> loop through the type output records to find jobs with *> output spool files perform until pubcas-retcode > 4 or pubcas-type <> pubcas-out-78 or pubcas-rsncode = 78-EOF *> for each o-hold record *> print details *> save key *> get associated output spool records (ds-hold) *> reposition for next o-hold record move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move pubcas-job-name to save-job-name move pubcas-job-nbr to save-job-nbr move low-values to pubcas-area move 78-KEY-IS-job-NUMBER to pubcas-key-id move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode <> 0 or pubcas-job-nbr <> save-job-nbr *> all the output spool files for this job if pubcas-type = pubcas-ds-out-78 move spaces to ascii-data string ' ' delimited by size pubcas-SYSOT-STEP-NAME delimited by size ',' delimited by size pubcas-SYSOT-PSTP-NAME delimited by size ',' delimited by size pubcas-SYSOT-DD-NAME delimited by size into ascii-data perform write-outfile end-if perform call-pubcas end-perform *> reposition on the next job name that has a type 8 record move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move pubcas-out-78 to pubcas-type move save-job-name to pubcas-job-name move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas *> get next next job move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas if pubcas-job-name = save-job-name and pubcas-job-nbr = save-job-nbr *> STGT and GN gets the same type 8 *> record ( duplicate keys allowed ) *> so need a second GN to get the next record move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-if end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold-type-create-date section. move spaces to ascii-data perform write-outfile move 'By Type and Date - hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-date to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode <> 0 or pubcas-type <> pubcas-o-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold-type-jobname section. move spaces to ascii-data perform write-outfile move 'By Type and Job Name - o-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 4 or pubcas-type <> pubcas-o-hold-78 or pubcas-rsncode = 78-EOF move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-ds-out section. move spaces to ascii-data perform write-outfile move 'By Type - ds-out ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-ds-out-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 4 or pubcas-type <> pubcas-ds-out-78 or pubcas-rsncode = 78-EOF move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-sysot-job-name delimited by size ',' delimited by size pubcas-sysot-step-name delimited by size ',' delimited by size pubcas-sysot-pstp-name delimited by size ',' delimited by size pubcas-sysot-dd-name delimited by size ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold section. move spaces to ascii-data perform write-outfile move 'By Type - o-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 4 or pubcas-type <> pubcas-o-hold-78 or pubcas-rsncode = 78-EOF move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-ds-hold section. move spaces to ascii-data perform write-outfile move 'By Type - ds-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-ds-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 4 or pubcas-type <> pubcas-ds-hold-78 or pubcas-rsncode = 78-EOF move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-sysot-job-name delimited by size ',' delimited by size pubcas-sysot-step-name delimited by size ',' delimited by size pubcas-sysot-pstp-name delimited by size ',' delimited by size pubcas-sysot-dd-name delimited by size ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-messages section. move 'Messages ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-mesg-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode <> 0 or pubcas-type > pubcas-mesg-78 move pubcas-type to disp-type if pubcas-msglg-mesg-length > 256 move 256 to pubcas-msglg-mesg-length end-if move spaces to ascii-data string disp-type delimited by size ',' delimited by size pubcas-msglg-mesg(1:pubcas-msglg-mesg-length) delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-completed-jobs section. move spaces to ascii-data perform write-outfile move 'Completed Jobs' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-JOB-COMPLETED-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas IF pubcas-RETCODE > ZERO EXIT SECTION END-IF move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 4 or pubcas-type <> pubcas-JOB-COMPLETED-78 or pubcas-rsncode = 78-EOF move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data move 1 to ws-idx1 string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-JOB-NAME delimited by size ',' delimited by size pubcas-REC-CLASS delimited by size into ascii-data with pointer ws-idx1 *> If the COND-CODE value has a type indicator *> and exceeds 3 digits in value, e.g. U2052 *> then, because of the limitation in space in the *> pubcas-INPUT-COND-CODE field, the *> pubcas-INPUT-CC-TYPE and pubcas-INPUT-CC-NUM *> format is used. if pubcas-rec-type-input-88 if pubcas-INPUT-CC-TYPE > x'f0' evaluate true when pubcas-INPUT-CC-TYPE-ERR-88 string ',' delimited by size 'ERR' delimited by size into ascii-data with pointer ws-idx1 when pubcas-INPUT-CC-TYPE-SYS-88 string ',' delimited by size 'SYS' delimited by size into ascii-data with pointer ws-idx1 when pubcas-INPUT-CC-TYPE-RTS-88 string ',' delimited by size 'RTS' delimited by size into ascii-data with pointer ws-idx1 when pubcas-INPUT-CC-TYPE-USER-88 string ',' delimited by size 'USR' delimited by size into ascii-data with pointer ws-idx1 when pubcas-INPUT-CC-TYPE-RC-88 string ',' delimited by size 'RC ' delimited by size into ascii-data with pointer ws-idx1 when other string ',' delimited by size 'XXX' delimited by size into ascii-data with pointer ws-idx1 end-evaluate move pubcas-INPUT-CC-NUM to disp-cc-nbr string ',' delimited by size disp-cc delimited by size into ascii-data with pointer ws-idx1 else move pubcas-INPUT-COND-CODE to disp-cc string ',' delimited by size 'CC:' delimited by size disp-cc delimited by size into ascii-data with pointer ws-idx1 end-if end-if if pubcas-REC-TYPE-SYSOT-88 if pubcas-sysot-create-date is numeric string ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data with pointer ws-idx1 end-if string ',' delimited by size pubcas-sysot-step-name delimited by size ',' delimited by size pubcas-sysot-pstp-name delimited by size ',' delimited by size pubcas-sysot-dd-name delimited by size into ascii-data with pointer ws-idx1 *> If 7 digit job numbering is active then *> the SYSOT JOB Number will be a COMP-X item if pubcas-SYSOT-JOB-NBR-2 is numeric *> 5 digit move pubcas-SYSOT-JOB-JOBNUM-5 to disp-job-nbr else *> 7 digit move pubcas-SYSOT-JOB-JOBNUM-COMPX to disp-job-nbr end-if string ",JN: " disp-job-nbr delimited by size into ascii-data with pointer ws-idx1 end-if perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. call-pubcas section. if pubcas-FUNC = 78-CAS-FUNC-OPEN *> Set the version to the current version if pubcas-VERSION <= spaces move CURR-VERSION to pubcas-VERSION end-if end-if call "mvscaspb" using pubcas-area if pubcas-retcode > 8 move pubcas-RETCODE to disp-rc move pubcas-RSNCODE to disp-rsn display 'call failed func ' pubcas-func ',' disp-rc ',' disp-rsn ',' pubcas-file-status goback end-if if pubcas-FUNC = 78-CAS-FUNC-OPEN if pubcas-VERSION is numeric move pubcas-VERSION to ws-pb-get-version else move 1 to ws-pb-get-version end-if if ws-pb-get-version >= 2 *> Store the type of spool control file *> were are using move pubcas-SPL-INFO-FILES-FORMAT to ws-pubcas-spl-format end-if end-if exit section. write-outfile section. write ASCII-DATA if ascii-file-status <> '00' display 'write output failed ' ascii-file-status goback end-if exit section end program Program1.
identification division. program-id. Program1. environment division. configuration section. input-output section. file-control. SELECT ASCII-FILE ASSIGN TO ASCII-DSN ORGANIZATION IS LINE SEQUENTIAL FILE STATUS ASCII-FILE-STATUS. data division. FILE SECTION. FD ASCII-FILE LABEL RECORDS STANDARD. 01 ASCII-DATA PIC X(80). working-storage section. 01 ascii-file-status pic xx. 01 ascii-dsn pic x(250). 01 disp-rc pic 9999. 01 disp-rsn pic 9999. 01 disp-type pic 9. 01 disp-job-nbr pic 9(6). 01 directory-name pic x(260). 01 flags pic x(4) comp-5. 01 name-length pic x(4) comp-5. 01 status-code pic x(2) comp-5. 01 save-job-name pic x(8). 01 save-job-nbr pic x(4) comp-x. 01 pubcas-area. copy "mfpubcas.cpy" replacing ==()== by ==pubcas==. procedure division. move '$outdir/output.txt' to ASCII-DSN open output ascii-file if ascii-file-status <> '00' display 'open output failed ' ascii-file-status goback end-if move 0 to flags call "CBL_GET_CURRENT_DIR" using by value flags by value name-length by reference directory-name returning status-code perform get-messages *> type 6 perform get-o-hold *> type 7 perform get-ds-hold *> type 8 perform get-o-hold-type-jobname *> type 7 by job name perform get-o-hold-type-create-date *> type 7 by date perform o-spool-files-jobname *> type 8 and associated *> type 10s perform o-held-spool-files-jobname *> type 7 and associated *> type 9s display 'test prog ended ' goback. o-held-spool-files-jobname section. move spaces to ascii-data perform write-outfile move 'By Jobs with held output spool files ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas *> loop through the type output records to find jobs with *> output spool files perform until pubcas-retcode > 8 or pubcas-type <> pubcas-o-hold-78 *> for each o-hold record *> print details *> save key *> get associated output spool records (ds-hold) *> reposition for next o-hold record move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move pubcas-job-name to save-job-name move pubcas-job-nbr to save-job-nbr move low-values to pubcas-area move 78-KEY-IS-job-NUMBER to pubcas-key-id move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-job-nbr <> save-job-nbr *> all the output spool files for this job if pubcas-type = pubcas-ds-hold-78 move spaces to ascii-data string ' ' delimited by size pubcas-SYSOT-STEP-NAME delimited by size ',' delimited by size pubcas-SYSOT-PSTP-NAME delimited by size ',' delimited by size pubcas-SYSOT-DD-NAME delimited by size into ascii-data perform write-outfile end-if perform call-pubcas end-perform *> reposition on the next job name that has a type 8 record move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move pubcas-o-hold-78 to pubcas-type move save-job-name to pubcas-job-name move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas *> get next next job move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas if pubcas-job-name = save-job-name and pubcas-job-nbr = save-job-nbr *> STGT and GN gets the same type 8 *> record ( duplicate keys allowed ) *> so need a second GN to get the next record move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-if end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. o-spool-files-jobname section. move spaces to ascii-data perform write-outfile move 'By Jobs with output spool files ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-out-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas *> loop through the type output records to find jobs with *> output spool files perform until pubcas-retcode > 8 or pubcas-type <> pubcas-out-78 *> for each o-hold record *> print details *> save key *> get associated output spool records (ds-hold) *> reposition for next o-hold record move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move pubcas-job-name to save-job-name move pubcas-job-nbr to save-job-nbr move low-values to pubcas-area move 78-KEY-IS-job-NUMBER to pubcas-key-id move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-job-nbr <> save-job-nbr *> all the output spool files for this job if pubcas-type = pubcas-ds-out-78 move spaces to ascii-data string ' ' delimited by size pubcas-SYSOT-STEP-NAME delimited by size ',' delimited by size pubcas-SYSOT-PSTP-NAME delimited by size ',' delimited by size pubcas-SYSOT-DD-NAME delimited by size into ascii-data perform write-outfile end-if perform call-pubcas end-perform *> reposition on the next job name that has a type 8 record move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move pubcas-out-78 to pubcas-type move save-job-name to pubcas-job-name move save-job-nbr to pubcas-job-nbr move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas *> get next next job move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas if pubcas-job-name = save-job-name and pubcas-job-nbr = save-job-nbr *> STGT and GN gets the same type 8 *> record ( duplicate keys allowed ) *> so need a second GN to get the next record move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-if end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold-type-create-date section. move spaces to ascii-data perform write-outfile move 'By Type and Date - hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-date to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-type <> pubcas-o-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold-type-jobname section. move spaces to ascii-data perform write-outfile move 'By Type and Job Name - o-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type-job-name to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-type <> pubcas-o-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-dat-time delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-ds-out section. move spaces to ascii-data perform write-outfile move 'By Type - ds-out ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-ds-out-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-type <> pubcas-o-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-o-hold section. move spaces to ascii-data perform write-outfile move 'By Type - o-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-o-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-type <> pubcas-o-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-job-name delimited by size ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-ds-hold section. move spaces to ascii-data perform write-outfile move 'By Type - ds-hold ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-ds-hold-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode > 8 or pubcas-type <> pubcas-ds-hold-78 move pubcas-type to disp-type move pubcas-job-nbr to disp-job-nbr move spaces to ascii-data string disp-type delimited by size ',' delimited by size disp-job-nbr delimited by size ',' delimited by size pubcas-sysot-job-name delimited by size ',' delimited by size pubcas-sysot-step-name delimited by size ',' delimited by size pubcas-sysot-pstp-name delimited by size ',' delimited by size pubcas-sysot-dd-name delimited by size ',' delimited by size pubcas-sysot-create-date delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. get-messages section. move 'Messages ' to ascii-data perform write-outfile move low-values to pubcas-area move 78-KEY-IS-type to pubcas-key-id move 78-CAS-FUNC-OPEN to pubcas-func perform call-pubcas move pubcas-mesg-78 to pubcas-type move 78-CAS-FUNC-STGT to pubcas-func perform call-pubcas move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas perform until pubcas-retcode <> 0 or pubcas-type > pubcas-mesg-78 move pubcas-type to disp-type if pubcas-msglg-mesg-length > 256 move 256 to pubcas-msglg-mesg-length end-if move spaces to ascii-data string disp-type delimited by size ',' delimited by size pubcas-msglg-mesg(1:pubcas-msglg-mesg-length) delimited by size into ascii-data perform write-outfile move 78-CAS-FUNC-GN to pubcas-func perform call-pubcas end-perform move 78-CAS-FUNC-CLOS to pubcas-func perform call-pubcas exit section. call-pubcas section. call "mvscaspb" using pubcas-area if pubcas-retcode > 8 move pubcas-RETCODE to disp-rc move pubcas-RSNCODE to disp-rsn display 'call failed func ' pubcas-func ',' disp-rc ',' disp-rsn ',' pubcas-file-status goback end-if exit section. write-outfile section. write ASCII-DATA if ascii-file-status <> '00' display 'write output failed ' ascii-file-status goback end-if exit section end program Program1.