Return to Mainframe Utilities Page
Module
/********************************************************************** /* UTILITY: LAYOUT * /* AUTHOR: DAVID LEIGH * /* FUNCTION: COMPILE A COPYBOOK AND BRING BACK THE LENGTH AND POSITION* /* INFORMATION INTO THE COPYBOOK FROM THE COMPILE LISTING. * /* CHANGE : DAVID SLEEMAN. * /* CHANGED CODE TO BE ABLE TO HANDLE THE OCCURS CLAUSE AND * /* PUT (1) AFTER TABLES ON THE SORT PARAMETER OPTIONS. * /********************************************************************** ISREDIT MACRO (OPT1 OPT2 OPT3 OPT4 OPT5 OPT6 OPT7 OPT8 OPT9 OPT10) ISPEXEC CONTROL ERRORS RETURN /**** SET MESSAGE DISPLAY ON/OFF BASED ON THE DEBUG SWITCH ***/ ISPEXEC VGET (DBGSWTCH) PROFILE IF &DBGSWTCH = &STR(ON) THEN + CONTROL MSG LIST CONLIST SYMLIST NOFLUSH ELSE + CONTROL NOMSG NOLIST NOFLUSH NOPROMPT /********************************************************************** /* NOTIFY THE USER * /********************************************************************** SET ZEDLMSG = &STR(*** PREPARING TO CALL THE COBOL COMPILER ***) ISPEXEC CONTROL DISPLAY LOCK ISPEXEC DISPLAY MSG(UTLZ000W) /********************************************************************** /* SET PROCESSING VARIABLES * /********************************************************************** DO &I = 1 TO 10 IF &STR(&SYSNSUB(2,&&OPT&I)) > THEN + DO SET X = &STR(&SYSNSUB(2,&&OPT&I)) SELECT (&STR(&X)) WHEN (SYNCSORT ¦ SORT) SET FORMAT = SYNCSORT WHEN (RDW) SET RDW = RDW WHEN (X) DO SET EXCLUDE = ON SET OPTIONS = &STR(&OPTIONS &X) END OTHERWISE SET OPTIONS = &STR(&OPTIONS &X) END END END SET COMPILER = IGYCRCTL /********************************************************************** /* ALLOCATE THE NECESSARY DD'S FOR THE COMPILE * /********************************************************************** FREE DD(SYSIN SYSLIB SYSPRINT SYSLIN + SYSUT1 SYSUT2 SYSUT3 SYSUT4 SYSUT5 SYSUT6 SYSUT7) ALLOC DD(SYSLIB) DATASET('PPROD.STR.COPYLIB') ALLOC DD(SYSLIN) DUMMY ALLOC DD(SYSUT1) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT2) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT3) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT4) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT5) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT6) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSUT7) UNIT(SYSDA) SPACE(1,1) CYLINDERS ALLOC DD(SYSPRINT) + NEW + UNIT(SYSDA) + SPACE(1,1) TRACKS RELEASE + RECFM(F B A) LRECL(133) BLKSIZE(23408) DSORG(PS) ALLOC DD(SYSIN) + NEW + UNIT(SYSDA) + SPACE(1,1) TRACKS RELEASE + RECFM(F B) LRECL(80) BLKSIZE(23440) DSORG(PS) /********************************************************************** /* UNIQUELY DEFINE "FILLER" * /********************************************************************** SET FILLNUM = 0 ISREDIT SEEK FIRST ' FILLER-1 ' &STR(&OPTIONS) DO WHILE &LASTCC = 0 SET FILLNUM = &FILLNUM + 1 ISREDIT CHANGE 'FILLER' 'FILLER-&FILLNUM' IF &LASTCC = 0 AND &EXCLUDE = ON THEN + DO ISREDIT EXCLUDE FIRST 'FILLER' .ZCSR .ZCSR ISREDIT SEEK LAST P'=' .ZCSR .ZCSR END ISREDIT SEEK NEXT ' FILLER-2 ' &STR(&OPTIONS) END /********************************************************************** /* MAKE A "PROGRAM" OUT OF THIS COPYBOOK * /********************************************************************** OPENFILE SYSIN OUTPUT SET SYSIN = &STR( IDENTIFICATION DIVISION.) PUTFILE SYSIN SET SYSIN = &STR( PROGRAM-ID. TESTPGM.) PUTFILE SYSIN SET SYSIN = &STR( DATE-COMPILED.) PUTFILE SYSIN SET SYSIN = &STR( ENVIRONMENT DIVISION.) PUTFILE SYSIN SET SYSIN = &STR( INPUT-OUTPUT SECTION.) PUTFILE SYSIN SET SYSIN = &STR( FILE-CONTROL.) PUTFILE SYSIN SET SYSIN = &STR( DATA DIVISION.) PUTFILE SYSIN SET SYSIN = &STR( FILE SECTION.) PUTFILE SYSIN SET SYSIN = &STR( WORKING-STORAGE SECTION.) PUTFILE SYSIN ISREDIT (X,Y) = NUMBER IF &X = ON AND &SYSINDEX(&STR( COBOL),&STR(&Y)) > 0 THEN + DO SET COL1 = 1 SET COL2 = 66 SET COL3 = 4 SET PREFIX = &STR( ) END ELSE + DO SET COL1 = 7 SET COL2 = 72 SET COL3 = 10 SET PREFIX = END /********************************************************************** /* LOOK FOR AN "01" LEVEL TO BEGIN THE DATA ELEMENT * /********************************************************************** ISREDIT CURSOR = 1 1 LOOP_01: + ISREDIT SEEK NEXT P' #' &COL1 &COL2 &STR(&OPTIONS) ISREDIT (LN1,CL1) = CURSOR ISREDIT SEEK NEXT ' ' .ZCSR .ZCSR ISREDIT (LN2,CL2) = CURSOR ISREDIT SEEK FIRST P'¬' &COL1 &COL1 .ZCSR .ZCSR IF &LASTCC = 0 THEN + DO ISREDIT SEEK LAST P'=' .ZCSR .ZCSR GOTO LOOP_01 END ISREDIT (NBR) = LINE .ZCSR SET NBR = &SUBSTR(&CL1:&CL2,&STR(&NBR)) SET NBR = &NBR IF &NBR > 1 THEN + DO SET SYSIN = &STR( 01 TEMP-LAYOUT-AREA.) PUTFILE SYSIN END ISREDIT SEEK FIRST P'=' &COL3 &STR(&OPTIONS) DO WHILE &LASTCC = 0 ISREDIT (SYSIN) = LINE .ZCSR SET SYSIN = &STR(&PREFIX&SYSNSUB(1,&SYSIN)) PUTFILE SYSIN ISREDIT SEEK NEXT P'=' &COL3 &STR(&OPTIONS) END SET SYSIN = &STR( PROCEDURE DIVISION.) PUTFILE SYSIN SET SYSIN = &STR( GOBACK.) PUTFILE SYSIN CLOSFILE SYSIN /********************************************************************** /* NOTIFY THE USER * /********************************************************************** SET ZEDLMSG = &STR(*** COMPILING THIS DATA ELEMENT DESCRIPTION ***) ISPEXEC CONTROL DISPLAY LOCK ISPEXEC DISPLAY MSG(UTLZ000W) /********************************************************************** /* COMPILE THE SUCKER ! * /********************************************************************** CALL 'SYS1.IGY.SIGYCOMP(&COMPILER)' /* ISPEXEC SELECT PGM(&COMPILER) */ SET SAVECC = &LASTCC IF &SAVECC > 4 THEN + DO SET ZEDLMSG = &STR(*** COMPILE UNSUCCESSFUL! RC=&SAVECC ***) ISPEXEC SETMSG MSG(UTLZ001W) ISPEXEC LMINIT DATAID(DID) DDNAME(SYSPRINT) ISPEXEC EDIT DATAID(&DID) ISPEXEC LMFREE DATAID(&DID) GOTO FINISH END /********************************************************************** /* NOTIFY THE USER * /********************************************************************** SET ZEDLMSG = &STR(*** EXTRACTING THE COMPILER LISTING OUTPUT ***) ISPEXEC CONTROL DISPLAY LOCK ISPEXEC DISPLAY MSG(UTLZ000W) /********************************************************************** /* EXTRACT THE DATA * /********************************************************************** FREE DD(SYSIN SYSLIB SYSLIN + SYSUT1 SYSUT2 SYSUT3 SYSUT4 SYSUT5 SYSUT6 SYSUT7) ISPEXEC LMINIT DATAID(DID) DDNAME(SYSPRINT) ISPEXEC EDIT DATAID(&DID) MACRO(LAYOUTMA) /********************************************************************** /* NOTIFY THE USER * /********************************************************************** IF &FORMAT = SYNCSORT THEN + SET ZEDLMSG = &STR(*** CONVERTING TO SYNCSORT FORMAT ***) ELSE + SET ZEDLMSG = &STR(*** INSERTING MESSAGE LINES ***) ISPEXEC CONTROL DISPLAY LOCK ISPEXEC DISPLAY MSG(UTLZ000W) /********************************************************************** /* INSERT THE INFORMATION AS MESSAGE LINES * /********************************************************************** ISPEXEC LMFREE DATAID(&DID) FREE DD(SYSPRINT) ISPEXEC VGET (CPINNUM CPIVAR CPIMAX) SHARED SET CPIMAX = &LENGTH(&CPIMAX) DO &I = 1 TO &CPIMAX SET ZEROPFX = &STR(0&ZEROPFX) SET QUESPFX = &STR(?&QUESPFX) END SET CPIMAX = &CPIMAX - 1 IF &CPIVAR = YES THEN + DO SET RDW = RDW IF &FORMAT = SYNCSORT THEN + SET RDWLINE = &SUBSTR(&LENGTH(&STR(&ZEROPFX.1))-&CPIMAX:+ &LENGTH(&STR(&ZEROPFX.1)),+ &STR(&ZEROPFX.1))+ &STR(,)+ &SUBSTR(&LENGTH(&STR(&ZEROPFX.4))-&CPIMAX:+ &LENGTH(&STR(&ZEROPFX.4)),+ &STR(&ZEROPFX.4))+ &STR(,CH,A,) END SET &OCCURSW = NO DO &I = 1 TO &CPINNUM SET ZEDSMSG = &STR(ON &I OF &CPINNUM) ISPEXEC CONTROL DISPLAY LOCK ISPEXEC DISPLAY MSG(UTLZ000) ISPEXEC VGET (CPID&I + CPIH&I + CPIP&I + CPIL&I + CPIF&I + CPIO&I + CPIR&I + CPIV&I) SHARED IF &STR(&SYSNSUB(2,&&CPIO&I)) = YES THEN + SET &HEX = YES IF &HEX = YES THEN + DO ISPEXEC SELECT PGM(HEX2DECP) PARM(&STR(&SYSNSUB(2,&&CPIH&I))) ISPEXEC VGET DECNUM SHARED SET DECNUM = &DECNUM + 1 SET POSITION = &DECNUM END ELSE + SET POSITION = &STR(&SYSNSUB(2,&&CPIP&I)) ISREDIT FIND FIRST ' &STR(&SYSNSUB(2,&&CPID&I)) ' &STR(&OPTIONS) IF &LASTCC ¬= 0 THEN + ISREDIT FIND FIRST ' &STR(&SYSNSUB(2,&&CPID&I)). ' &STR(&OPTIONS) IF &FORMAT = SYNCSORT THEN + DO SET &OCCUR = SET LEVEL = &STR(&SYSNSUB(2,&&CPIV&I)) SET LEVEL = &LEVEL - 13 + 35 IF &HLDLEVEL = &LEVEL OR &HLDLEVEL > &LEVEL THEN + SET OCCURSW = NO IF &OCCURSW = YES THEN SET OCCUR = &STR((1)) IF &POSITION = 1 AND &RDW = RDW THEN + DO SET CPIVAR = YES SET RDW = ISREDIT LINE_BEFORE .ZCSR = <15,(RDWLINE) + 32,' * RDW'> END IF &CPIVAR = YES THEN SET POSITION = &POSITION + 4 SET POSITION = &STR(&ZEROPFX&POSITION) SET L = &LENGTH(&STR(&POSITION)) IF &POSITIONS = OFF THEN SET POSITION = &STR(&QUESPFX) ELSE SET POSITION = &SUBSTR(&L-&CPIMAX:&L,&STR(&POSITION)) SET DATALEN = &STR(&ZEROPFX&SYSNSUB(2,&&CPIL&I)) SET L = &LENGTH(&STR(&DATALEN)) SET DATALEN = &SUBSTR(&L-&CPIMAX:&L,&STR(&DATALEN)) IF &STR(&SYSNSUB(2,&&CPIO&I)) = YES AND + &OCCURSW = NO THEN + DO SET OCCURSW = YES SET HLDLEVEL = &LEVEL END SET DATANAME = &STR(&SYSNSUB(2,&&CPID&I) &OCCUR) SET SORTFMT = &STR(&SYSNSUB(2,&&CPIF&I)) SET STRING = &STR(&POSITION,&DATALEN,&SORTFMT,A, * ) ISREDIT LINE .ZCSR = <15,(STRING) + (LEVEL),(DATANAME) + 72,' '> END ELSE + DO IF &POSITIONS = OFF THEN SET CPIP&I = &STR(?????) SET MESSAGE = &STR(POSITION=&POSITION )+ &STR(LENGTH=&SYSNSUB(2,&&CPIL&I )) /* &STR(HEX=&DECNUM) ISREDIT (LN,CL) = CURSOR IF &SLN = THEN SET SLN = &LN SET CL = &CL + 1 ISREDIT LINE_BEFORE .ZCSR = MSGLINE <(CL) (MESSAGE)> END /* SET MESSAGE = &STR(POSITION=&SYSNSUB(2,&&CPIP&I) )+ /* DO /* SET POSITIONS = OFF /* ISREDIT LINE_BEFORE .ZCSR = MSGLINE + /* '&STR(*** DEFINED WITH "OCCURS" *** + /* SUBSEQUENT "POSITIONS" ARE UNKNOWN ***)' /* END END /********************************************************************** /* CLEAN UP * /********************************************************************** IF &FORMAT = SYNCSORT THEN + DO ISREDIT EXCLUDE ALL .ZFIRST .ZLAST IF &POSITIONS = OFF THEN ISREDIT LOCATE FIRST SPECIAL SET STGPOS = &EVAL(((&CPIMAX+1)*2)+19) ISREDIT FIND ALL ',A, * ' &STGPOS ISREDIT LINE_BEFORE .ZFIRST = ' SORT FIELDS=(' ISREDIT DELETE EXCLUDED .ZFIRST .ZLAST END ELSE + ISREDIT RESET EXCLUDED /********************************************************************** /* CLEAN UP FILLERS * /********************************************************************** FINISH: + DO &I = 1 TO &FILLNUM ISREDIT CHANGE FIRST 'FILLER-&I ' 'FILLER ' END IF &FORMAT = SYNCSORT THEN + ISREDIT CURSOR = 1 1 ELSE + DO ISREDIT CURSOR = &SLN 1 ISREDIT FIND PREV P'=' 1 END EXIT
Documentation
LAYOUT is an edit macro which returns position and length information about a COBOL data element description, or converts a COBOL data element description into SYNCSORT SYSIN. The best way to describe the value of LAYOUT is to describe the common problems it solves. Have you ever wanted to know how big a print line definition is? Have you ever wanted to know if your RECORD CONTAINS matches your file layout in number of bytes (whether described in the FD or in WORKING-STORAGE)? This has usually meant tediously counting up the picture clauses (including COMP, COMP-3 conversions and numeric edited fields) and hoping you counted right until you abended or the compile did not work! There is an edit macro named ADDCOL which has provided some help up until now, but it requires all the picture clauses to be of the same digit precision, beginning in the same column, and the data elements must be display or numeric-display format. That's ok for a few things, but reality dictates that you're going to need to know the length of much more complex data element definitions than that. Let's use the following example of a data element layout and the results that the LAYOUT edit macro would return: ***************************************************************** * COPYBOOK: DATEFD * ***************************************************************** FD IN-DATE-CARD-FILE RECORDING MODE IS F RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS LABEL RECORDS ARE STANDARD DATA RECORD IS IN-DATE-CARD-RECORD. 01 IN-DATE-CARD-RECORD. 05 IN-RUN-DATE. 10 IN-DATE-YY PIC X(02). 10 IN-DATE-MM PIC X(02). 10 IN-DATE-DD PIC X(02). 05 FILLER PIC X(01). 05 IN-DSNQUAL PIC X(05). 05 FILLER PIC X(68). First we would "exclude" the lines we want to process: ***************************************************************** * COPYBOOK: DATEFD * ***************************************************************** FD IN-DATE-CARD-FILE RECORDING MODE IS F RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS LABEL RECORDS ARE STANDARD DATA RECORD IS IN-DATE-CARD-RECORD. - - - - - - - - - - - - - - - - 8 line(s) not displayed Then we would type the following on the command line: COMMAND ===> layout x 1 This means to execute the LAYOUT edit macro on the "excluded" lines. The results would look like the following: ***************************************************************** * COPYBOOK: DATEFD * ***************************************************************** FD IN-DATE-CARD-FILE RECORDING MODE IS F RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS LABEL RECORDS ARE STANDARD DATA RECORD IS IN-DATE-CARD-RECORD. ==MSG> POSITION=1 LENGTH=80 01 IN-DATE-CARD-RECORD. ==MSG> POSITION=1 LENGTH=6 05 IN-RUN-DATE. ==MSG> POSITION=1 LENGTH=2 10 IN-DATE-YY PIC X(02). ==MSG> POSITION=3 LENGTH=2 10 IN-DATE-MM PIC X(02). ==MSG> POSITION=5 LENGTH=2 10 IN-DATE-DD PIC X(02). ==MSG> POSITION=7 LENGTH=1 05 FILLER PIC X(01). ==MSG> POSITION=8 LENGTH=5 05 IN-DSNQUAL PIC X(05). ==MSG> POSITION=13 LENGTH=68 05 FILLER PIC X(68). The newly inserted lines are called edit "message" lines. They are not "real" data lines and are deleted via the RESET or RESET SPECIAL command. Additionally, if you have your terminal contrast set appropriately or have a color terminal, these lines are "highlighted" so they stand out more. Now would be a good time to discuss the philosopy of LAYOUT. LAYOUT works on the concept that, while I might be able programatically process the data element description myself, the task would be significant, and it's already been done for me.....it's call the compiler! What LAYOUT actually does is COMPILE the data element definition you identify and interrogate the compile listing to extract data element length information. From the length information, it derives "position" information within the data element structure as well. So, anyway, back to the task at hand. You want to know how big a data element definition is. LAYOUT will tell you automatically without the need for you to exercise a single synapse. Because the layout is determined by compiling the data element definition, you need to identify this definition to LAYOUT so that it can compile it. Let's start with some easy examples and move to harder ones. If you are in edit of a copybook and you want to find out the length and positions of each data element in the copybook, just type LAYOUT on the command line and press ENTER. LAYOUT will make a "program" around this copybook (non-destructive to the member you are editing) with the copybook as the WORKING-STORAGE. As in the example shown above, LAYOUT will compile the data element description, interrogate the compile listing and then insert the POSITION/LENGTH message lines. 1 In the example above, the data element description was part of the FD, but since LAYOUT is going to make "WORKING-STORAGE" out of your identified lines, you have to make sure that all you identify is valid working-storage lines (and comment lines are permissable as well). In the above example we did that by "excluding" the lines we wanted to process and then "telling" LAYOUT to process only the excluded lines. To paraphrase, LAYOUT can accept any data lines which would be valid in a COBOL WORKING-STORAGE section, including comment lines. If the file you are editing contains only that, then all you need to do is type "layout" on the command line and press ENTER. Otherwise, you need to isolate those lines which you want to process with LAYOUT and then "tell" LAYOUT which lines to process. In the previous example, we excluded the lines and then specified that only excluded lines were to be processed. Basically, lines to be processed by LAYOUT can be specified by the use of the excluded status of the lines, (which can mean excluded or "x" or non-excluded or "nx") user edit labels, system edit labels, or any combination of the three. For more information on the use of edit labels (a little known but EXTREMELY powerful facility of the ISPF editor), see the ISPF edit tutorial....only a PF-key away! Valid examples of how to invoke LAYOUT include the following (where ".a" and ".b" are "user" edit labels, and the edit labels beginning ".z" are "system" edit labels): COMMAND ===> layout .a .b COMMAND ===> layout .a .zlast COMMAND ===> layout .zcsr .a x COMMAND ===> layout nx COMMAND ===> layout x .a .b COMMAND ===> layout LAYOUT has another basic function and, consequently, a problem that it solves. I mentioned that LAYOUT not only tells you the length of the data element, it also indicates the position that data element begins in within the data structure being processed. Now, where in data processing is position and length of data used most frequently? External sorts of course! Have you ever wanted to use SYNCSORT to extract and/or report data on a file? Of course you have. Have you had to count bytes based on a COBOL layout definition of the file you are processing? Of course you have. have you wanted to deal with data that is hundreds of bytes past the first column and is in the middle of a forest of "flag" fields? Of course you have. Hopefully, LAYOUT can make this process a little easier for you. The other facility which LAYOUT performs is the conversion of a COBOL data element definition into "SORT FIELDS="-compatible format. The first item to emphasize in this discussion is CONVERT....this is a DESTRUCTIVE operation. Your COBOL definition is REPLACED in the file you are editing, with the SYNCSORT SYSIN, and the lines not processed by LAYOUT are deleted! When LAYOUT is operating in this mode, it is a conversion tool, not just an information tool! Ok, now that we have "the fear of God" in you, we can continue. LAYOUT uses the position and length information it knows as well as the data type information it has acquired from the compile listing, and the data name itself to create a documented SYNCSORT SYSIN. The impetus for this entire utility was the need to do some quick and dirty extract/reporting on the UNIPAC SLSS transaction file. So, we'll use it in our example. 1 Let's say, for example, that you needed to create a quick and dirty report from T100, T230, and T335 transactions with SYNCSORT. Here are the steps you would take using the LAYOUT utility: 1. Copy the copybooks TRANHEAD, TRAN100, TRAN230, TRAN335 and TRANAPPD (in that order) into a clean member. The result (without comment lines) would look like this (as of 8-20-92): 044900 01 TRANSACTION-RECORD. TRANHEA 045000 05 T-CODE PIC X(03) VALUE SPACES. TRANHEA 045100 05 T-ISAM-KEY. TRANHEA 045200 10 T-SSN. TRANHEA 045300 15 T-SSN1 PIC X(03) VALUE SPACES. TRANHEA 045400 15 T-SSN2 PIC X(02) VALUE SPACES. TRANHEA 045500 15 T-SSN3 PIC X(04) VALUE SPACES. TRANHEA 045600 10 T-LOAN-NUMBER PIC X(01) VALUE SPACES. TRANHEA 045700 05 T-LAST-NAME PIC X(15) VALUE SPACES. TRANHEA 045800 05 T-TRANS-DATE. TRANHEA 045900 10 T-DATE-YY PIC X(02) VALUE SPACES. TRANHEA 046000 10 T-DATE-MM PIC X(02) VALUE SPACES. TRANHEA 046100 10 T-DATE-DD PIC X(02) VALUE SPACES. TRANHEA 046200 05 T-TIME PIC X(06) VALUE SPACES. TRANHEA 046300 05 T-EFFECTIVE-DATE. TRANHEA 046400 10 T-EFFECTIVE-YY PIC X(02) VALUE SPACES. TRANHEA 046500 10 T-EFFECTIVE-MM PIC X(02) VALUE SPACES. TRANHEA 046600 10 T-EFFECTIVE-DD PIC X(02) VALUE SPACES. TRANHEA 046700 05 T-BATCH-NUMBER PIC X(06) VALUE SPACES. TRANHEA 046800 05 REST-OF-TRAN PIC X(207) VALUE SPACES. TRANHEA 120300 05 TRAN-100 REDEFINES REST-OF-TRAN. TRAN100 120400 10 T-PRIOR-PRINC-BAL-100-X. TRAN100 120500 15 T-PRIOR-PRINC-BAL-100 TRAN100 120600 PIC S9(05)V9(02). TRAN100 120700 10 T-CHECK-SUBNO PIC 9(01). TRAN100 120800 10 FILLER PIC X(06). TRAN100 120900 10 T-CHECK-AMT-X. TRAN100 121000 15 T-CHECK-AMT PIC S9(05)V9(02). TRAN100 121100 10 T-CHECK-MANIFEST-DATE. TRAN100 121200 15 T-CHECK-MAN-YY PIC X(02). TRAN100 121300 15 T-CHECK-MAN-MM PIC X(02). TRAN100 121400 15 T-CHECK-MAN-DD PIC X(02). TRAN100 121500 10 T-LOAN-PERIOD-BEGIN-DATE-100. TRAN100 121600 15 T-LOAN-BEGIN-100-YY TRAN100 121700 PIC X(02). TRAN100 121800 15 T-LOAN-BEGIN-100-MM TRAN100 121900 PIC X(02). TRAN100 122000 15 T-LOAN-BEGIN-100-DD TRAN100 122100 PIC X(02). TRAN100 122200 10 T-CHECK-INS-FEE-X. TRAN100 122300 15 T-CHECK-INS-FEE PIC S9(05)V9(02). TRAN100 122400 10 T-PRIOR-PRINC-NONSUB-100-X. TRAN100 122500 15 T-PRIOR-PRINC-NONSUB-100 TRAN100 122600 PIC S9(05)V9(02). TRAN100 122700 10 T-ORIG-FEE-DED-100 PIC S9(05)V9(02). TRAN100 122800 10 T-FIRST-NAME-100 PIC X(12). TRAN100 122900 10 T-MIDDLE-INITIAL-100 TRAN100 123000 PIC X(01). TRAN100 123100 10 T-CHECK-FLAG-100 PIC X(01). TRAN100 123200 10 T-END-DATE-FLAG-100 PIC X(01). TRAN100 123300 10 T-NOTE-ID-NO-100-X. TRAN100 123400 15 T-NOTE-ID-NO-100 TRAN100 123500 PIC S9(02). TRAN100 1 123600 10 T-GUARANTOR-ID-100 PIC X(04). TRAN100 123700 10 T-GRAM-RUDMAN-FLAG-100 TRAN100 123800 PIC X(01). TRAN100 123900 10 T-INTEREST-RATE-100-X. TRAN100 124000 15 T-INTEREST-RATE-100 TRAN100 124100 PIC SV9(05). TRAN100 124200 10 T-WINDFALL-FLAG-100 PIC X(01). TRAN100 124300 10 T-ACH-CODE PIC X(03). WWA1115 124400 10 T-LATE-DISB-FLAG-100 JGA1115 124401 PIC X(01). JGA1115 124402 10 FILLER PIC X(121). WWA1115 002700 05 TRAN-230 REDEFINES REST-OF-TRAN. TRAN230 002800 10 T-SECURITY-CODE PIC X(04). TRAN230 002900 10 T-PRIOR-PRINC-BAL-230-X. TRAN230 003000 15 T-PRIOR-PRINC-BAL-230 TRAN230 003100 PIC S9(05)V9(02). TRAN230 003200 10 T-PRIOR-PRINC-NONSUB-230-X. TRAN230 003300 15 T-PRIOR-PRINC-NONSUB-230 TRAN230 003400 PIC S9(05)V9(02). TRAN230 003500 10 T-PRINCIPAL-ADJ-AMT-X. TRAN230 003600 15 T-PRINCIPAL-ADJ-AMT TRAN230 003700 PIC S9(05)V9(02). TRAN230 003800 10 T-INTERIM-INT-ACCRUAL-AMT-X. TRAN230 003900 15 T-INTERIM-INT-ACCRUAL-AMT TRAN230 004000 PIC S9(05)V9(02). TRAN230 004100 10 FILLER PIC X(01). G1A0979 004200 10 T-NET-TOTAL-FLAG-230 G1A0979 004300 PIC X(01). G1A0979 004400 10 FILLER PIC X(05). G1A0979 004500 10 T-INTERIM-INT-RECIEVED-TD-X. TRAN230 004600 15 T-INTERIM-INT-RECIEVED-TD TRAN230 004700 PIC S9(05)V9(02). TRAN230 004800 10 T-GOVT-INT-ACCRUAL-AMT-X. TRAN230 004900 15 T-GOVT-INT-ACCRUAL-AMT TRAN230 005000 PIC S9(05)V9(02). TRAN230 005100 10 FILLER PIC X(07). TRAN230 005200 10 T-REPAYMENT-INT-ACCRUAL-AMT-X. TRAN230 005300 15 T-REPAYMENT-INT-ACCRUAL-AMT TRAN230 005400 PIC S9(05)V9(02). TRAN230 005500 10 FILLER PIC X(07). TRAN230 005600 10 T-REPAYMENT-INT-RECIEVED-TD-X. TRAN230 005700 15 T-REPAYMENT-INT-RECIEVED-TD TRAN230 005800 PIC S9(05)V9(02). TRAN230 005900 10 T-INTERIM-DATE-230. TRAN230 006000 15 T-INTERIM-YY PIC X(02). TRAN230 006100 15 T-INTERIM-MM PIC X(02). TRAN230 006200 15 T-INTERIM-DD PIC X(02). TRAN230 006300 10 T-REPAY-DATE-230. TRAN230 006400 15 T-REPAY-YY PIC X(02). TRAN230 006500 15 T-REPAY-MM PIC X(02). TRAN230 006600 15 T-REPAY-DD PIC X(02). TRAN230 006700 10 T-GOVT-DATE-230. TRAN230 006800 15 T-GOVT-YY PIC X(02). TRAN230 006900 15 T-GOVT-MM PIC X(02). TRAN230 007000 15 T-GOVT-DD PIC X(02). TRAN230 007100 10 T-ACTIVITY-CODE-230 PIC X(01). TRAN230 007200 10 T-NOTE-ID-NO-230-X. TRAN230 007300 15 T-NOTE-ID-NO-230 TRAN230 007400 PIC S9(02). TRAN230 007500 10 T-REASON-FOR-230 PIC X(03). TRAN230 1 007600 10 T-AMOUNT-OF-REASON-230-X. TRAN230 007700 15 T-AMOUNT-OF-REASON-230 TRAN230 007800 PIC S9(05)V9(02). TRAN230 007900 10 T-INTEREST-RATE-230-X. TRAN230 008000 15 T-INTEREST-RATE-230 TRAN230 008100 PIC SV9(05). TRAN230 008200 10 T-NON-CASH-230 PIC X(01). WWA0979 008300 10 T-ACCOUNT-NUM-230 PIC X(06). GMA0979 008400 10 T-PRINC-ADJ-AMT-MULTI-230-X. G1A0979 008500 15 T-PRINC-ADJ-AMT-MULTI-230 G1A0979 008600 PIC S9(05)V9(02). G1A0979 008700 10 T-REPAY-INT-ACCR-MULTI-230-X. G1A0979 008800 15 T-REPAY-INT-ACCR-MULTI-230 G1A0979 008900 PIC S9(05)V9(02). G1A0979 009000 10 T-REPAY-INT-RCVD-MULTI-230-X. G1A0979 009100 15 T-REPAY-INT-RCVD-MULTI-230 G1A0979 009200 PIC S9(05)V9(02). G1A0979 009300 10 T-INTRM-INT-ACCR-MULTI-230-X. G1A0979 009400 15 T-INTRM-INT-ACCR-MULTI-230 G1A0979 009500 PIC S9(05)V9(02). G1A0979 009600 10 T-INTRM-INT-RCVD-MULTI-230-X. G1A0979 009700 15 T-INTRM-INT-RCVD-MULTI-230 G1A0979 009800 PIC S9(05)V9(02). G1A0979 009900 10 T-GOVT-INT-ACCR-MULTI-230-X. G1A0979 010000 15 T-GOVT-INT-ACCR-MULTI-230 G1A0979 010100 PIC S9(05)V9(02). G1A0979 010200 10 FILLER PIC X(41). G1A0979 222300 05 TRAN-335 REDEFINES REST-OF-TRAN. TRAN335 222400 10 T-PRIOR-PRINC-BAL-335-X. TRAN335 222500 15 T-PRIOR-PRINC-BAL-335 TRAN335 222600 PIC S9(05)V9(02). TRAN335 222700 10 T-ACCRUAL-TYPE-335 PIC X(01). TRAN335 222800 10 T-AMT-INTEREST-ACCR-335-X. TRAN335 222900 15 T-AMT-INTEREST-ACCR-335 TRAN335 223000 PIC S9(05)V9(02). TRAN335 223100 10 T-AMT-PRINC-ADJ-335-X. TRAN335 223200 15 T-AMT-PRINC-ADJ-335 TRAN335 223300 PIC S9(05)V9(02). TRAN335 223400 10 T-AMT-INCOME-INT-335-X. TRAN335 223500 15 T-AMT-INCOME-INT-335 TRAN335 223600 PIC S9(05)V9(02). TRAN335 223700 10 T-PRIOR-PRINC-NONSUB-335-X. TRAN335 223800 15 T-PRIOR-PRINC-NONSUB-335 TRAN335 223900 PIC S9(05)V9(02). TRAN335 224000 10 T-SPECIAL-ALLW-PR-100180-335-X. TRAN335 224100 15 T-SPECIAL-ALLW-PR-100180-335 TRAN335 224200 PIC S9(07)V9(02). TRAN335 224300 10 T-SPECIAL-ALLW-100180-335-X. TRAN335 224400 15 T-SPECIAL-ALLW-100180-335 TRAN335 224500 PIC S9(07)V9(02). TRAN335 224600 10 T-SPECIAL-ALLW-100181-335-X. TRAN335 224700 15 T-SPECIAL-ALLW-100181-335 TRAN335 224800 PIC S9(07)V9(02). TRAN335 224900 10 T-SPECIAL-ALLW-030186-335-X. TRAN335 225000 15 T-SPECIAL-ALLW-030186-335 TRAN335 225100 PIC S9(07)V9(02). TRAN335 225200 10 T-SPECIAL-ALLW-111686-335-X. TRAN335 225300 15 T-SPECIAL-ALLW-111686-335 TRAN335 225400 PIC S9(07)V9(02). TRAN335 225500 10 T-INTEREST-RATE-335-X. TRAN335 225600 15 T-INTEREST-RATE-335 TRAN335 225700 PIC SV9(05). TRAN335 1 225800 10 T-REASON-335 PIC X(01). TRAN335 225900 10 FILLER PIC X(120). TRAN335 272300 05 INFO-APPENDED. TRANAPP 272400 10 SCHOOL-ID-APPEND PIC X(06) VALUE SPACES. TRANAPP 272500 10 CUSTOMER-APPEND PIC X(04) VALUE SPACES. TRANAPP 272600 10 LENDER-APPEND PIC X(06) VALUE SPACES. TRANAPP 272700 10 BORROWER-STATUS-APPEND TRANAPP 272800 PIC X(02) VALUE SPACES. TRANAPP 272900 10 AMT-APPLY-PRINC-APPEND TRANAPP 273000 PIC S9(05)V9(02) VALUE +0. TRANAPP 273100 10 CURRENT-PRINC-TOTAL-APPEND TRANAPP 273200 PIC S9(05)V9(02) VALUE +0. TRANAPP 273300 10 AMT-APPLY-REPAY-INT-APPEND TRANAPP 273400 PIC S9(05)V9(02) VALUE +0. TRANAPP 273500 10 REPAYMENT-INT-RCVD-TD-APPEND TRANAPP 273600 PIC S9(05)V9(02) VALUE +0. TRANAPP 273700 10 AMT-APPLY-INTERIM-INT-APPEND TRANAPP 273800 PIC S9(05)V9(02) VALUE +0. TRANAPP 273900 10 INTERIM-INT-RCVD-TD-APPEND TRANAPP 274000 PIC S9(05)V9(02) VALUE +0. TRANAPP 274100 10 INTERNALLY-GENERATED TRANAPP 274200 PIC X(01) VALUE SPACES. TRANAPP 274300 10 NOTE-NUMBER-APPEND PIC 9(02) VALUE 0. TRANAPP 274400 10 LOAN-TYPE-APPEND PIC X(01) VALUE SPACES. TRANAPP 274500 10 INITIALS-APPEND PIC X(03) VALUE SPACES. TRANAPP 274600 10 WRITE-PH-FLAG-APPEND TRANAPP 274700 PIC X(01) VALUE SPACES. TRANAPP 274800 10 TRANS-CODE-APPEND PIC X(03) VALUE SPACES. TRANAPP 274900 10 TERMINAL-ID-APPEND PIC X(04) VALUE SPACES. TRANAPP 275000 10 FILLER PIC X(08) VALUE SPACES. TRANAPP 275100 10 BOND-ID-APPEND PIC X(06) VALUE SPACES. TRANAPP 275200 10 GUARANTOR-ID-APPEND PIC X(04) VALUE SPACES. TRANAPP 275300 10 LOAN-ADD-FLAG-APPEND TRANAPP 275400 PIC X(01) VALUE SPACES. TRANAPP 270700 10 INSURED-FLAG-APPEND PIC X(01) VALUE SPACES. TRANAPP 270800 10 LOAN-INTEREST-TYPE-APPEND TDA0769 270800 PIC X(01) VALUE SPACES. TDA0769 272400 10 BRANCH-ID-APPEND PIC X(02) VALUE SPACES. JKA1112 270800 10 FILLER PIC X(03) VALUE SPACES. JKA1112 Identification of lines to be processed is exactly the same as when executing LAYOUT just to show informational message lines. It is probable, however, due to the "destructive" nature of the SYNCSORT conversion function of LAYOUT, that you'll not need to explicitly identify the lines to be processed because you'll already have placed just the lines you want into a clean file. The way you tell LAYOUT to create sort SYSIN out of your COBOL layout is to specify "sort" when you are invoking layout. Just like you would specify "X" or "NX", you can specify "SORT". So, using our transaction copybook example, you would type the following on the command line: COMMAND ===> layout sort 1 Using the above example, your file would be converted to the following: SORT FIELDS=( 001,360,CH,A, * TRANSACTION-RECORD 001,003,CH,A, * T-CODE 004,010,CH,A, * T-ISAM-KEY 004,009,CH,A, * T-SSN 004,003,CH,A, * T-SSN1 007,002,CH,A, * T-SSN2 009,004,CH,A, * T-SSN3 013,001,CH,A, * T-LOAN-NUMBER 014,015,CH,A, * T-LAST-NAME 029,006,CH,A, * T-TRANS-DATE 029,002,CH,A, * T-DATE-YY 031,002,CH,A, * T-DATE-MM 033,002,CH,A, * T-DATE-DD 035,006,CH,A, * T-TIME 041,006,CH,A, * T-EFFECTIVE-DATE 041,002,CH,A, * T-EFFECTIVE-YY 043,002,CH,A, * T-EFFECTIVE-MM 045,002,CH,A, * T-EFFECTIVE-DD 047,006,CH,A, * T-BATCH-NUMBER 053,207,CH,A, * REST-OF-TRAN 053,207,CH,A, * TRAN-100 053,007,ZD,A, * T-PRIOR-PRINC-BAL-100 060,001,ZD,A, * T-CHECK-SUBNO 061,006,CH,A, * FILLER 067,007,ZD,A, * T-CHECK-AMT 074,006,CH,A, * T-CHECK-MANIFEST-DATE 074,002,CH,A, * T-CHECK-MAN-YY 076,002,CH,A, * T-CHECK-MAN-MM 078,002,CH,A, * T-CHECK-MAN-DD 080,006,CH,A, * T-LOAN-PERIOD-BEGIN-DATE-100 080,002,CH,A, * T-LOAN-BEGIN-100-YY 082,002,CH,A, * T-LOAN-BEGIN-100-MM 084,002,CH,A, * T-LOAN-BEGIN-100-DD 086,007,ZD,A, * T-CHECK-INS-FEE 093,007,ZD,A, * T-PRIOR-PRINC-NONSUB-100 100,007,ZD,A, * T-ORIG-FEE-DED-100 107,012,CH,A, * T-FIRST-NAME-100 119,001,CH,A, * T-MIDDLE-INITIAL-100 120,001,CH,A, * T-CHECK-FLAG-100 121,001,CH,A, * T-END-DATE-FLAG-100 122,002,ZD,A, * T-NOTE-ID-NO-100 124,004,CH,A, * T-GUARANTOR-ID-100 128,001,CH,A, * T-GRAM-RUDMAN-FLAG-100 129,005,ZD,A, * T-INTEREST-RATE-100 134,001,CH,A, * T-WINDFALL-FLAG-100 135,003,CH,A, * T-ACH-CODE 138,001,CH,A, * T-LATE-DISB-FLAG-100 139,121,CH,A, * FILLER 053,207,CH,A, * TRAN-230 053,004,CH,A, * T-SECURITY-CODE 057,007,ZD,A, * T-PRIOR-PRINC-BAL-230 064,007,ZD,A, * T-PRIOR-PRINC-NONSUB-230 071,007,ZD,A, * T-PRINCIPAL-ADJ-AMT 078,007,ZD,A, * T-INTERIM-INT-ACCRUAL-AMT 085,001,CH,A, * FILLER 086,001,CH,A, * T-NET-TOTAL-FLAG-230 087,005,CH,A, * FILLER 1 092,007,ZD,A, * T-INTERIM-INT-RECIEVED-TD 099,007,ZD,A, * T-GOVT-INT-ACCRUAL-AMT 106,007,CH,A, * FILLER 113,007,ZD,A, * T-REPAYMENT-INT-ACCRUAL-AMT 120,007,CH,A, * FILLER 127,007,ZD,A, * T-REPAYMENT-INT-RECIEVED-TD 134,006,CH,A, * T-INTERIM-DATE-230 134,002,CH,A, * T-INTERIM-YY 136,002,CH,A, * T-INTERIM-MM 138,002,CH,A, * T-INTERIM-DD 140,006,CH,A, * T-REPAY-DATE-230 140,002,CH,A, * T-REPAY-YY 142,002,CH,A, * T-REPAY-MM 144,002,CH,A, * T-REPAY-DD 146,006,CH,A, * T-GOVT-DATE-230 146,002,CH,A, * T-GOVT-YY 148,002,CH,A, * T-GOVT-MM 150,002,CH,A, * T-GOVT-DD 152,001,CH,A, * T-ACTIVITY-CODE-230 153,002,ZD,A, * T-NOTE-ID-NO-230 155,003,CH,A, * T-REASON-FOR-230 158,007,ZD,A, * T-AMOUNT-OF-REASON-230 165,005,ZD,A, * T-INTEREST-RATE-230 170,001,CH,A, * T-NON-CASH-230 171,006,CH,A, * T-ACCOUNT-NUM-230 177,007,ZD,A, * T-PRINC-ADJ-AMT-MULTI-230 184,007,ZD,A, * T-REPAY-INT-ACCR-MULTI-230 191,007,ZD,A, * T-REPAY-INT-RCVD-MULTI-230 198,007,ZD,A, * T-INTRM-INT-ACCR-MULTI-230 205,007,ZD,A, * T-INTRM-INT-RCVD-MULTI-230 212,007,ZD,A, * T-GOVT-INT-ACCR-MULTI-230 219,041,CH,A, * FILLER 053,207,CH,A, * TRAN-335 053,007,ZD,A, * T-PRIOR-PRINC-BAL-335 060,001,CH,A, * T-ACCRUAL-TYPE-335 061,007,ZD,A, * T-AMT-INTEREST-ACCR-335 068,007,ZD,A, * T-AMT-PRINC-ADJ-335 075,007,ZD,A, * T-AMT-INCOME-INT-335 082,007,ZD,A, * T-PRIOR-PRINC-NONSUB-335 089,009,ZD,A, * T-SPECIAL-ALLW-PR-100180-335 098,009,ZD,A, * T-SPECIAL-ALLW-100180-335 107,009,ZD,A, * T-SPECIAL-ALLW-100181-335 116,009,ZD,A, * T-SPECIAL-ALLW-030186-335 125,009,ZD,A, * T-SPECIAL-ALLW-111686-335 134,005,ZD,A, * T-INTEREST-RATE-335 139,001,CH,A, * T-REASON-335 140,120,CH,A, * FILLER 260,101,CH,A, * INFO-APPENDED 260,006,CH,A, * SCHOOL-ID-APPEND 266,004,CH,A, * CUSTOMER-APPEND 270,006,CH,A, * LENDER-APPEND 276,002,CH,A, * BORROWER-STATUS-APPEND 278,007,ZD,A, * AMT-APPLY-PRINC-APPEND 285,007,ZD,A, * CURRENT-PRINC-TOTAL-APPEND 292,007,ZD,A, * AMT-APPLY-REPAY-INT-APPEND 299,007,ZD,A, * REPAYMENT-INT-RCVD-TD-APPEND 306,007,ZD,A, * AMT-APPLY-INTERIM-INT-APPEND 313,007,ZD,A, * INTERIM-INT-RCVD-TD-APPEND 320,001,CH,A, * INTERNALLY-GENERATED 321,002,ZD,A, * NOTE-NUMBER-APPEND 1 323,001,CH,A, * LOAN-TYPE-APPEND 324,003,CH,A, * INITIALS-APPEND 327,001,CH,A, * WRITE-PH-FLAG-APPEND 328,003,CH,A, * TRANS-CODE-APPEND 331,004,CH,A, * TERMINAL-ID-APPEND 335,008,CH,A, * FILLER 343,006,CH,A, * BOND-ID-APPEND 349,004,CH,A, * GUARANTOR-ID-APPEND 353,001,CH,A, * LOAN-ADD-FLAG-APPEND 354,001,CH,A, * INSURED-FLAG-APPEND 355,001,CH,A, * LOAN-INTEREST-TYPE-APPEND 356,002,CH,A, * BRANCH-ID-APPEND 358,003,CH,A, * FILLER You'll notice that the "SORT FIELDS=(" text is on a line by itself. This allows you to choose which line will be used for the primary sort field. You can then do a "M"ove "O"verlay to position the line where you want it. Each line is documented on the right with the field it defines. Keep in mind that group level fields are defined as well as elementary items. Consequently, you would not want to sort an elementary item as well as the group item it is a part of. SYNCSORT would not allow this. You can tell the hierarchy of group to elementary items by the number of characters the data name is indented. So, what do you do about VARIABLE files (e.g. the SLSS MASTER file) since their position (as far as SYNCSORT is concerned) is really their position + 4 bytes for the RDW. If the data element description has an OCCURS DEPENDING ON clause in it, LAYOUT will automatically take into account the 4 bytes of RDW when processing. You can, if you want, specify that LAYOUT is to create an RDW line for SYNCSORT conversion and bump the position of every item up by 4 bytes. You do this by specifying "RDW" when invoking LAYOUT. For example: COMMAND ===> layout sort rdw The mention of "OCCURS" just now brings up the issue of the current (as of 8-20-92) limitation of LAYOUT. If LAYOUT comes across an OCCURS clause, it will cease trying to determine position. It will still determine the length of both group and elementary items, but the compile listing does not contain the number of occurances in the area of the listing which LAYOUT interrogates. As of 4-21-93 the layout utility was changed to no longer have a problem with the occurs clause. In the sort format a '(1)' will be added to inform you about the occurs and positioning will be calculated for the first item of the table.