310 likes | 332 Vues
Tutorial – Basic Introduction. 02 January 2020. Nick Jones Jim Evans. Compute (Bridgend) Ltd 8 Merthyr Mawr Road BRIDGEND CF31 3NH +44 (0)1656 652222 http://www.cbl.com. SELCOPY Uses. Simple one-off jobs or complex applications. Copy between datasets of different RECFM.
E N D
Tutorial – Basic Introduction 02 January 2020 Nick Jones Jim Evans Compute(Bridgend) Ltd 8 Merthyr Mawr Road BRIDGEND CF31 3NH +44 (0)1656 652222 http://www.cbl.com
SELCOPY Uses • Simple one-off jobs or complex applications. • Copy between datasets of different RECFM. • Filter/Modify/Merge data using selection criteria. • Update/Delete/Insert data records. • Generate/Extract test data from production. • Print input data and reports in different formats. • Search and update PDS library members. • Load/Modify DB2 tables and IMS databases. • Execute DB2 SQL statements. Compute(Bridgend) Ltd
Running SELCOPY (1/2) • Batch JCL • EXEC statement with optional PARM string. • SYSPRINT • SYSIN • Input/Output dataset DDnames //NBJJOB JOB ,,CLASS=A,MSGCLASS=X,MSGLEVEL=(1,1),NOTIFY=&SYSUID //SELC001 EXEC PGM=SELCOPY //SYSPRINT DD DISP=SHR,DSN=NBJ.SELCOPY.SYSPRINT(SELC001) //CORRUPT DD DISP=(NEW,CATLG),DSN=NBJ.SELC001.CORRUPT, // UNIT=SYSDA,VOL=SER=CBLM05,SPACE=(TRK,(1,5)), // DCB=(DSORG=PS,RECFM=VB,BLKSIZE=0,LRECL=256) //SYSIN DD * OPTION NORDW * WORKLEN=65536 READ MYDDNAME DSN='CBL.INST.CBL15112.SZZSSAM2.ZZSDATSA' STOPAFT=5000 IF LRECL = 58 THENIF POS 7 = 'C' OR POS 7 = 'D' THEN IF POS 15 = ' ' THEN PRINT TYPE=B STOPAFT=5 THEN WRITE CORRUPT /* Compute(Bridgend) Ltd
Running SELCOPY (2/2) • TSO/E • REXX procedures • See also member STERM in the installation SZZSEXEC library. • SELCOPYi - RUNSELC utility • SELCOPYi - IDE/Debug utility /* REXX */ parse argctl address TSO “allocddname(SYSIN) dsn(‘”ctl”’) shr reuse” /* SYSIN */ “allocddname(SYSPRINT) dsn(*) shr reuse” /* SYSPRINT to terminal. */ “SELCOPY”; rr = rc /* Execute SELCOPY and save return code. */ “free ddname(SYSIN)” “free ddname(SYSPRINT)” return rr Compute(Bridgend) Ltd
SELCOPY Control Statements • RECFM=V (variable) or F (fixed) SYSIN input • RECFM=F => last 8 characters ignored. • Terminated by end of SYSIN record by default • Continuation character – ‘\’ (backslash) • Separation character – ‘!’ (exclamation mark) • OPTION SEP=x or SEP=NO to change/disable • Mixed case - unquoted identifiers upper-cased • Comment text – ‘*’ or ‘*>’ • Comment text ignoring SEP chars – ‘*<‘ in column 1 Compute(Bridgend) Ltd
SELCOPY Control Statements ** NBJ.CTL.F80(SSAMP01) *** L=001 --- 2016/06/17 15:48:47 (NBJ) 00001000 *<alloc f(cblsqlog) da('CBL.SSC.LOG.S340(SSAMP01)') shr reuse 00002000 *<runselc 00003000 00004000 OPTION Worklen 5120 * 5K work buffer. 00005000 Option SSN=CBLA * Default DB2 Sub-system name. 00006000 OPTION DATAWIDTH=80 * Printed data width. 00007000 00008000 READ INDB SQL=" \ 00009000 select f.funcname, p.parmno, p.parmname, p.parmtype \ 00010000 from cblazos.cbl.zzsfunc f \ 00011000 inner join cblazos.cbl.zzsparm p \ 00012000 on f.apilib = p.apilib \ 00013000 and f.funcname = p.funcname \ 00014000 where f.funcname like 'C2%' \ 00015000 order by f.funcname, p.parmno \ 00016000 " CHAR SEP * Printable character + separators. 00017000 00018000 IF POS 1 = 'C2D ' !THEN POS 78 = '*#*' *> ## Flag Function ##\ 00019000 - This is an important function. 00020000 00021000 00022000 PRINT LENGTH=80 STOPAFT=20 00023000 *<LOG 'Important function found.' !LOG '-------------------------' 00024000 00025000 Compute(Bridgend) Ltd
SELCOPY Processing • Control Statement Analysis • Statement identification (Continuation/Separation) • Assign Prime Input • Open each Input and Output file (unless explicitly deferred) • Execute EQU, OPTION and END operations • Establish labels • Assign selection Ids • Selection Time Processing • Logical statement selection and execution • End of Job Processing • Close data sets • Write SYSPRINT diagnostics Compute(Bridgend) Ltd
Input / Output • Input operation • READ (or IMS/DL1 GN, GHN, GU, etc.) • CAT • Output operations • WRITE, UPDATE (REPL), DELETE, INSERT (ISRT) • PRINT, LOG, PLOG • Input/Output objects • Sequential data sets or PDS/PDSE library members • VSAM data sets - KSDS, ESDS or RRDS • HFS/ZFS files (DD PATH, PATHOPTS, PATHMODE, FILEDATA) • IMS/DL1 data bases • ADABAS data bases • DB2 tables READ DDIN1 * Input data from one object. WRITE DDOUT * Output the same data to another. Compute(Bridgend) Ltd
Input Methods • Sequential Input • Sequential data sets & library members (QSAM) • KSDS, ESDS, RRDS data sets - FWD and BWD (VSAM) • PDS/PDSE library directories - DIR (QSAM) • PDS/PDSE library directory and member data - DIRDATA (QSAM/BPAM) • IMS database segment - GN, GNP, GU, GHN, GHNP, GHU • DB2 table - SQL SELECT query • Direct input and filtered input • KSDS, ESDS, RRDS data sets – KEY, RBA, REC, STARTKEY, etc. • IMS database segment - SSA or SEG SEARCH • DB2 table - SQL SELECT WHERE query Compute(Bridgend) Ltd
Prime Input Object READ DDIN1 * Prime Input (DDIN1). WRITE DDOUT * Output last record read from DDIN1. READ DDIN2 * WRITE DDOUT * Output last record read from DDIN2. First input object identified during control statement analysis processing. • Implies a logical loop on selection control statements. • Loop ends at prime input end-of-file. • Default object for IF DIR/DATA/EOF/INCOUNT tests. DO GETIN1 * Sub-routine. READ DDIN2 * Prime Input (DDIN2). WRITE DDOUT * Output last record read from DDIN2. GOTO GET ==GETIN1== READ DDIN1 * WRITE DDOUT * Output last record read from DDIN1. =RETURN= Compute(Bridgend) Ltd
Work Area • WORKLEN on OPTION or firstREAD operation. • Buffer for manipulating data. • Required for fields outside limits of the last input record. READ DDIN1 INTO 1 WORKLEN=200 * 200-byte work area. READ DDIN2 INTO 81 * Join nth record from DDIN2 with... * ... nth record from DDIN1. WRITE DDOUT FROM 1 LENGTH=160 * Output joined input records. • Clear residual data if variable length input. OPTION WORKLEN=1000 * 1000-byte work area. READ DDINV INTO 1 NORDW * Suppress RECFM=V 4-byte RDW. POS 1+LRECL, 500 = ' ' * Clear residue left by a longer record. WRITE DDOUTF FROM 1 * RECFM=F output. Compute(Bridgend) Ltd
Field Definitions • Used for Source and Target of SELCOPY operations. • Location, length and data type. • Data type implied by SELCOPY operation. • CVBC (Binary to Character) • MOVE (Character only) • ADD, SUB, MULT, DIV TYPE=B/P(Binary / Packed Decimal) • Specification: • POS p1 LENGTH n • POS p1(Length implied by the operation or another field.) • POS p1, p2 • n AT p1 • Literal constant - ABC, ‘Abc', X'C1,82,83' Compute(Bridgend) Ltd
Field Data Type • Numeric fields. Numeric values are used for arithmetic (ADD, SUB, MULT, DIV) and arithmetic compare (IF) operations. Field data type Binary (TYPE=B) or Packed Decimal (TYPE=P) must be specified. • Character Numeric fields. Character fields are treated as Zoned Decimal when converted to numeric data types or when numeric fields converted to character without FORMAT. • Hexadecimal Floating Point fields. Source and target field data types supported for conversion to and from printable character only. (CVFC and CVCF) POS 1 = '12L' * POS 1 = '12L' (-123 in Zoned Decimal) CVCP 3 AT 1 TO 2 AT 4 * POS 4 = x'123D' (-123 in Packed Decimal) ADD 14 TO 2 AT 4 * POS 4 = x'109D' (-109 in Packed Decimal) CVPC 2 AT 4 TO 4 AT 6 * POS 6 = '010R' (-109 in Zoned Decimal) CVPC 2 AT 4 TO 11 FMT 'szz9' * POS 11 = '-109' (-109 in Printable Char) Compute(Bridgend) Ltd
EQUated Symbols • EQU operation - control statement analysis. • Give meaningful names to values. • Nesting EQU names. • Map fields in Work Area. EQU IREC1 1 * DDIN1 input record field position. EQU IREC1_L 80 * DDIN1 input record field length. EQU IREC2 IREC1+IREC1_L * DDIN2 input record field position. EQU IREC2_L IREC1_L * DDIN2 input record field length OPTION WORKLEN=IREC2+IREC2_L * Work area length = 1+80+80. READ DDIN1 INTO IREC1 READ DDIN2 INTO IREC2 WRITE DDOUT FROM IREC1 LENGTH=IREC1_L+IREC2_L Compute(Bridgend) Ltd
Conditional Selections (1/2) • Based on condition tests: IF/AND/OR ... • True condition selections: THEN... !THEN... • False condition selections: ELSE... !THEN... • Conditional condition tests: THENIF... !ELSEIF... • Nested conditions. IF POS 1 = 'A' OR POS 1 = 'B' THEN MOD POS 101 = 'Y' THEN PRINT 'A or B found in position 1.' THENIF POS 2 = 'C' * Same as THEN IF. OR POS 2 = 'D' THEN PRINT 'C or D found in position 2.' ELSEIF POS 2 > 'D' < 'H' * Same as ELSE IF. AND POS 3 = '#' THEN PRINT 'E#, F# or G# in position 2.' ELSE PRINT 'Failed to find match following A or B' THEN MOD POS 101 = 'N' ELSE PRINT 'No match for A or B found in position 1.' THEN GOTO CANCEL * Unexpected condition. Compute(Bridgend) Ltd
Conditional Selections (2/2) IF POS 1 LENGTH 100 = '#' FILL='#' • Character compare of single field. Compare a field of length 100 located at position 1 for equality with a literal field '#' of length 1 padded to the length of the longer field using the '#' character. i.e. test for 100 '#' characters at position 1. • Character compare of multiple fields. (Range test) Find the first match for 'ABC' in 100, 3-byte character fields located at ascending positions starting from position 1. Note that POS 1,100 is not a field definition. • Arithmetic compare. (Numeric field interpretation) Test the numeric value in a binary field value for being greater than 100. • Special conditions. Other specials: DIR, DATA, EOF, INCOUNT, LINE, LRECL, RETCODE IF POS 1, 100 = 'ABC' IF 4 at 11 TYPE=B > 100 IF INCOUNT >= 35 * Prime input record count. Compute(Bridgend) Ltd
Selection Operations • Data object open / close / input / output. READ, WRITE, UPDATE, INSERT, DELETE, PRINT, LOG, PLOG, PUNCH, OPEN, CLOSE • Field value assignment and copy. MOD, MOVE, GENERATE, XV • Field value data type conversion. CVxx, TRAN, UPPER, LOWER, CVDATE • Field value arithmetic. ADD, SUB, MULT, DIV • Internal and external routine processing. CALL, DO (GOSUB/PERFORM), RETURN • Logic operations. GOTO, FLAG, DUMMY, SPACE, START, SUSP Compute(Bridgend) Ltd
SELect and COPY Simple file filter program: Same program using EQUates: READ DDIN WORKLEN=1000 IF POS 21 = POS 36 LENGTH=4 AND POS 8 LENGTH=4 TYPE=B > 256 THEN ADD 1 TO POS 8 LENGTH=4 TYPE=B THEN WRITE DDOUT1 ELSE WRITE DDOUT2 THEN PRINT EQU INREC 1 EQU UID 7 !EQU UID_L 4 EQU NAM1 20 !EQU NAM1_L 4 EQU NAM2 35 !EQU NAM2_L 8 EQU INREC_L 1000 READ DDIN WORKLEN=INREC+INREC_L IF POS INREC+NAM1 = POS INREC+NAM2 LENGTH=NAM1_L AND POS INREC+UID LENGTH=UID_L TYPE=B > 256 THEN ADD 1 TO POS INREC+UID LENGTH=UID_L TYPE=B THEN WRITE DDOUT1 ELSE WRITE DDOUT2 THEN PRINT Compute(Bridgend) Ltd
Internal Variables (1/3) • LRECL • Automatically assigned the length of the last input record read. (READ) • Default length of output data. (WRITE, UPDATE, PRINT) • May be updated directly by an assignment operation. e.g. LRECL=22 • Used as an integer value in a simple expression. e.g. LRECL=LRECL-4 • Value stored in 4-byte binary (TYPE=B) internal field: POS UXLRECL • Different to LRECL parameter specified on READ or WRITE. OPTION WORKLEN=2048 * 2048-byte work area. READ DDIN1 INTO 1 NORDW * DDIN1 RECFM=V (suppress RDW). @RLEN = LRECL * Save last input record length. READ DDIN2 INTO 1+@RLEN NORDW * DDIN2 into byte following. LRECL = LRECL+@RLEN * Combined length of both records. WRITE DDOUT * LRECL = default output record length. Compute(Bridgend) Ltd
Internal Variables (2/3) • @ pointers • Address locations in storage. • Automatically assigned to the first matching field in a range test. • Up to 16 named @ pointers (@xxxx) plus 1 default (@). • Named @ pointers defined by assignment or via PTR= on a range test. • May be directly assigned to an integer value work area position. • Used as an integer value in a simple expression. e.g. @a=@a+@b+@c-1 • Default pointer (@) address stored in 4-byte field: POS UXATPTR READ CARD * In-line record data following END statement. @FLD = 1 * Initialise @FLD (1st field position) pointer. ==LOOP== IF POS @FLD, LRECL = ',' PTR=@CMMA * Scan record for comma. THEN PRINT FROM @FLD, @CMMA-1 * Print the individual field. THEN @FLD = @CMMA+1 * @FLD -> start of next field. THEN GOTO LOOP * Loop to search for next comma. ELSE PRINT FROM @FLD, LRECL * Comma not found so print remainder. THEN SPACE 1 * Skip a line in SYSPRINT. END * CARD input records follow... Mary,had,a,little,lamb Shall,I,compare,thee,to,a,"summer's",day. Compute(Bridgend) Ltd
Internal Variables (3/3) • DIFF • Following a single field character compare operation, DIFF is automatically assigned to the position within the first field at which a difference is found. • May be assigned to an integer value corresponding to a work area position. • May be used as an integer value in a simple expression. e.g. @x=DIFF-10 • RC / RETCODE • The current, highest return code value set by the SELCOPY execution. • May be updated directly by an assignment operation. e.g. RETCODE=901 • LINE • The next SYSPRINT output line number within the current print page. • May be updated directly by an assignment operation. e.g. LINE=35 • If the assigned line number is lower than the current value of LINE or greater than the page depth (OPTION PAGEDEPTH), a new page will be started and the value reset to 1. MOD POS 1 = 'zaefr0g3LKEFiwhc;UHV29' IF POS 1 <> 'zaefrOg3LKEFiwhc;UHV29' THEN PRINT FROM DIFF LENGTH=10 * Print from the 1st difference. Compute(Bridgend) Ltd
SYSPRINT Output (1/2) • Pages (PAGEWIDTH / PAGEDEPTH) with page headers. • Diagnostic Output • Control statements with assigned selection ids. • Control statement analysis error messages follow individual statements in error. • Selection time error messages follow the control statements. • Selection Summary block: • Execution count for each selection id. • Data object information (BLKSIZE, LRECL, etc.) • Warning messages follow individual selection id entries to which they apply. • Return code warning message (if RC<>0) • SELCOPY standard footer with product expiry date. • Program PRINT output • Occurs before the Selection Summary block. • Selection of PRINT types (including Character, Hex, Dump, Report and System) • Print block for all types except REPORT and TYPE=S (System) Compute(Bridgend) Ltd
SYSPRINT Output (2/2) 1SELCOPY REL 3.30 AT CBL - Bridgend UK (Internal Only) 2016/06/21 11:43 PAGE 1 ----------------------------------------------------- ---------------- -------- OPTION DATAWIDTH=60 PAGEWIDTH=90 1. READ CARD * In-line record data following END statement. 2. @FLD = 1 * Initialise @FLD (1st field position) pointer. ==LOOP== ---- IF POS @FLD, LRECL = ',' PTR=@CMMA * Scan record for comma. 3. THEN PRINT FROM @FLD, @CMMA-1 * Print the individual field. 4. THEN @FLD = @CMMA+1 * @FLD -> start of next field. 5. THEN GOTO LOOP * Loop to search for next comma. 6. ELSE PRINT FROM @FLD, LRECL * Comma not found so print remainder. END * CARD input records follow... INPUT SEL SEL RECORD RECNO TOT ID. 1 2 3 4 5 6 LENGTH ----- --- --- ....,....0....,....0....,....0....,....0....,....0....,....0 ------ 1 1 3 Mary 13 1 2 3 had 13 1 1 6 lamb 13 ....,....1....,....2....,....3....,....4....,....5....,....6 SUMMARY.. SEL-ID SELTOT FILE BLKSIZE LRECL FSIZE CI DSN ------ ------ ---- ------- ----- ----- -- --- 1 1 READ SYSIN 27998 17 VB 1 2 1 3----5 2 6 1 ** SELCOPY IS LICENSED BY COMPUTE (BRIDGEND) LTD +44 (1656) 652222 & 656466 ** ** EXPIRY DATE -- 2017/07/13 ** Compute(Bridgend) Ltd
SELCOPY Sample 1 READ INDD * Read a record. IF POS 10 = ‘CR’ * Select records with CR in column 10. THEN PRINT STOPAFT=10 * Print only first 10. THEN WRITE CRFILE * Write all of them to CRFILE. IF POS ANY = ‘PICK ME’ * Scan whole record for string PICK ME. THEN POS @ = ‘PICKED ’ * Where found change it to PICKED. THEN WRITE PKFILE * Create file of picked records. ELSE WRITE NOTPK * Else write file of not picked. Simple Select and Change program: This program demonstrates only use of: IF THEN ELSE Condition testing may be enhanced to include use of: AND OR THENIF ELSEIF Compute(Bridgend) Ltd
SELCOPY Sample 2 EQU INREC 1 * Buffer Input record position. EQU OUTREC 5001 * Buffer Output record position. OPTION WORKLEN=10000 * Define a work buffer. READ INFILE INTO INREC NORDW * Input record data. MOVE 1729 FROM INREC+0000 TO OUTREC+0000 * Start building the output record. POS OUTREC+1729, OUTREC+1773 = X'40' * 45 blanks. MOVE 271 FROM INREC+1730 TO OUTREC+1774 MOVE 448 FROM INREC+2003 TO OUTREC+2045 MOVE 248 FROM INREC+2457 TO OUTREC+2493 MOVE 030 FROM INREC+3101 TO OUTREC+2741 MOVE 001 FROM INREC+3213 TO OUTREC+2771 MOVE 018 FROM INREC+3336 TO OUTREC+2772 MOVE 015 FROM INREC+3427 TO OUTREC+2790 WRITE OUTFILE FROM OUTREC, OUTREC+2804 * Write the output record. Re-format data records: Use EQU names to identify the input and output areas within the work area. Compute(Bridgend) Ltd
SELCOPY Sample 3 EQU DIRIN 1 * Input directory record position. EQU DIRIN_L 256 * Input directory record max length. EQU XDSN DIRIN+DIRIN_L * Current input PDS data set name. EQU XDSN_L 44 * DSN max length. OPTION WORKLEN=XDSN+XDSN_L PAGEDEPTH=99999 * Suppress new pages. READ INPDS1 DSN='CBL.JCL' DIR INTO DIRIN * 1st input PDS directory. CAT INPDS2 DSN='NBJ.JCL' DIR * 2nd " CAT INPDS3 DSN='JGE.JCL' DIR * 3rd " IF POS DSN <> XDSN_L AT XDSN * If next concatenated PDS. THEN SPACE 2 * Skip 2 SYSPRINT lines. THEN MOD XDSN_L AT XDSN = POS DSN * Copy new PDS data set name. THEN PRINT "### Next Library ###" * Print eye-catcher. THEN PRINT FROM XDSN_L AT XDSN * Print the new PDS DSN. IF POS DIRIN = 'SQ' * If member name begins "SQ"... OR POS DIRIN, DIRIN+7 = '£' * ...or contains "£". THEN PRINT FROM DIRIN TYPE=MC * Print the directory record. * TYPE=MC => mixed character and hex. Concatenated PDS (or PDSE library) directory input: • Dynamic allocation of static library DSN. • Internal field at POS DSN changes when next concatenated data set object is read. • PRINT TYPE=MC will print non-printable characters as up/down hex. Compute(Bridgend) Ltd
SELCOPY Sample 4 OPTION NOPRINT * Suppress diagnostic output. EQU IREC 1 * Input dir + data records position. EQU IREC_L 80 * Input dir + data records max length. EQU OREC IREC+IREC_L * Output report record position. EQU OREC_L 132 * Output report record max length. OPTION WORKLEN=OREC+OREC_L PAGEDEPTH=100 * Report page depth. OPTION REPORT HEAD='COBOL Copybook 01 Groups' * Report header. READ INPDS1 DSN='CBL.CBLI340.COB' DIRDATA * COBOL Copybook members. IF DIR INPDS1 * If a directory record. THEN MOVE 8 AT IREC TO OREC * Member name. THEN MOD POS OREC+8 = ':' * Colon separator. THEN GOTO GET * No further DIR record processing. ** Process member DATA records. ** IF POS IREC+07, IREC+10 = '01 ' PTR=@BEG * "01" must start in area A. AND POS @BEG+03, IREC+LRECL-1 <> ' ' PTR=@BEG * Start of group name. AND POS @BEG+01, IREC+LRECL-1 = '.' PTR=@END * "01" sentence end.(Note 2) THEN MOVE POS @BEG, @END-1 TO OREC+10 * Copy to output record. THEN PRINT FROM OREC, OREC+10+@END-@BEG-1 * Report output record. PDS (or PDSE library) directory and member data input: • Dynamic allocation of static library DSN. • Assumes sentence ends on same record. Extra statements required for a more generic approach. • OPTION REPORT will output SELCOPY report format print lines and headers. Compute(Bridgend) Ltd
SELCOPY Sample 5 READ INKS DSN="NBJ.SSDEMO07.KSDS" UPDATE * Indicate update intention. IF POS 16 < '2015/10/26' * Date at pos 16 of input. THEN DELETE INKS * Delete this record. THEN GOTO GET * Return to start of input loop. IF POS ANY = 'CBLM05' * Test all input positions for 'CBLM05' THEN POS @ = 'XXXXXX' * Overwrite with 'X' characters. THEN UPDATE INKS * Update the record. VSAM KSDS cluster sequential input, update and delete: • UPDATE required on READ to indicate open for update. • VSAM KSDS cluster data records read sequentially. • POS ANY is a range test on the length of the input record starting at POS 1. • @pointer (default @) is set following a successful POS ANY range test. Compute(Bridgend) Ltd
SELCOPY Sample 6 EQU INREC 1 * Input KSDS record position. EQU INREC_L 1024 * Input KSDS record maximum length. EQU INCRD INREC+INREC_L * Input card record position. EQU INKEY 0 * Key value offset. EQU INKEY_L 7 * Key value length. EQU INCRD_L 256 * Input card record maximum length. OPTION WORKLEN=INCRD+INCRD_L * Work Area buffer. READ CARD INTO INCRD NORDW READ INKS DSN="NBJ.SSDEMO07.KSDS" KSDS \ INTO INREC KEY=INKEY_L AT INCRD+INKEY * Direct input by key. IF POS INREC = "--- KEY/REC NOT FOUND ---" THEN MOD POS INREC = "VSAM GET Return code = x' ', Reason code = x' '." THEN CVCH 1 AT RETVSAM+1 TO INREC+25 * VSAM GET return code. THEN CVCH 1 AT RETVSAM+3 TO INREC+46 * VSAM GET reason code. THEN LRECL = 50 * Output length. THEN RC = 912 * Set high SELCOPY return code. PRINT FROM INREC * Default length LRECL. END 0000045 1st input key. 0000025 2nd input key. 0000022 This key is not found. 0000060 4th input key. VSAM KSDS cluster keyed input: • POS RETVSAM +1 points to the RPL single byte return, component and reason codes. • “--- KEY/REC NOT FOUND ---” returned at input position if key lookup fails to find a record. Compute(Bridgend) Ltd
SELCOPY IDE (SELCOPYi) • Source from JCL or from SYSIN input • Step through SELCOPY control statements • Set break points • Display Hex Dump window - Work Area and POS x • Track positions in storage based on POS expressions • Track @pointer and LRECL values • SYSIN/SYSPRINT and SQL Log windows • Trace/WTO console output windows Compute(Bridgend) Ltd
SELCOPYi (Interactive) • SELCOPYi is a separate presentation topic • Features include: • Windows like desktop inside 3270 screen. • Data Editor - COBOL/PL1/HLASM copybooks. • Text Editor. • DB2 Table Edit, SQL execution & Object management. • Dataset Utilities – Compare, Search, Copy. • XML/CSV generation. • Point-and-shoot command execution. Compute(Bridgend) Ltd