SlideShare una empresa de Scribd logo
1 de 39
SORT




       by RK
Agenda

SORT FLOW
INCLUDE / OMIT
INREC
JOIN
SUM / DUPKEYS
EXIT Routines (MODS)
OUTREC
OUTFIL
OUTFIL Reports
DATE Operations
Basic Points

 The first byte of every fixed-length record is position 1, the second byte position 2, and so on.

 Bytes 1 through 4 of variable-length records are reserved for the Record Descriptor Word
 (RDW). For these records, the first byte of the data portion is position 5.

 When proper processing depends on data format, the format of the field must be specified.

 The format of the field must be appropriate to the task. For example, only numeric fields can
  be SUMmed.

 When all the fields have the same format, the format value can be specified just once through
  the FORMAT=f subparameter. The FORMAT=f subparameter cannot be used when the
  INCLUDE/OMIT parameter is specified on the OUTFIL control statement.

Identify a comment card image by placing an asterisk (*) in column 1. Comments can
 extend through column 80.

 To add a comment to a control statement card image, leave one or more blanks after the
  last parameter or comma on the image and follow with the comment, which can extend
  through column 71.
Basic Points Contd…


 Comment lines can be inserted between a control statement and its continuation by
  coding an asterisk (*) in column one.

                                                                COL. 72
                                                                   ↓
SORT FIELDS=(1,10,A,20,5,A,45,7,A),FORMAT=CH,STOPAFT=100, *COMMENT
       EQUALS

In the above example, no continuation character is required. The control statement is
interrupted after a parameter-comma combination before column 72.

         COL. 16                                      COL.72
            ↓                                            ↓
OUTFIL OUTREC=(1:10,8,30:40,10),HEADER2=(1:'CUSTOMER NUMBX
            ER',30:'ITEM NUMBER')

In this example, a continuation character is necessary because the literal string in the
HEADER2 specification would extend beyond column 71. The 'X' in column 72 is the
continuation character. The literal string is continued in column 16 of the next card image.
SORT JCL


    //SORT     EXEC PGM=SORT
    //SORTIN   DD DISP=SHR,DSN=INPUT.FILE
    //SORTOUT DD DSN=OUTPUT.FILE,
    //            DISP=(,CATLG,DELETE),
    //            UNIT=SYSDA,SPACE=(TRKS,(40,20),RLSE)
    //SYSOUT   DD SYSOUT=*
    //SYSPRINT DD SYSOUT=*
    //SYSIN    DD *
     SORT FIELDS=COPY
    /*

SORTIN                                    SORTOUT
ACCOUNT# MOBILE# STATUS   DATE   AMOUNT   ACCOUNT# MOBILE# STATUS   DATE   AMOUNT
----+----+----+----+----+----+----+----   ----+----+----+----+----+----+----+----
10000001 5000001   0     011511 100.50    10000001 5000001   0     011511 100.50
10000001 5000002   1     021512 050.50    10000001 5000002   1     021512 050.50
10000001 5000003   2     011512 000.50    10000001 5000003   2     011512 000.50
10000002 5100001   2     021512 111.50    10000002 5100001   2     021512 111.50
10000002 5200002   1     021512 120.50    10000002 5200002   1     021512 120.50
10000006 5600001   0     021512 100.50    10000006 5600001   0     021512 100.50
10000003 5300001   0     021512 020.50    10000003 5300001   0     021512 020.50
SORT FLOW


BEFORE SORT         SORT     AFTER SORT


    SORTIN

                             SUM / DUPKEYS
   SKIPREC


      E15                       OUTREC


     JOIN            SORT         E35



  INCLUDE/OMIT                  OUTFIL


                               SORTOUT
   STOPAFT


     INREC
STOPAFT


STOPAFT Parm
STOPAFT=n

 STOPAFT=n (a decimal number) sorts/copies at most n records.

These will be the first n records after any input processing due to an E15, an
INCLUDE/OMIT statement, or the SKIPREC parameter.

 If STOPAFT=n has been specified on the SORT control statement as well as
in the PARM field, the PARM specification will take precedence.

//SORT EXEC PGM=SORT,PARM=‘STOPAFT=100'
                 or
  SORT FIELDS=COPY,STOPAFT=100

 First 100 records will be taken and remaining records will be skipped. These
100 will be send to next control of SORT for processing.
SKIPREC


SKIPREC Parm
SKIPREC=n

 SKIPREC=n instructs the sort to skip a decimal number n of records before
sorting/copying the input file.

 The records skipped are deleted from the input file before E15 and
INCLUDE/OMIT processing is begun.

 If SKIPREC=n has been specified on the SORT control statement as well as
in the PARM field, the PARM specification will take precedence.

//SORT EXEC PGM=SORT,PARM='SKIPREC=100'
                 or
  SORT FIELDS=COPY,SKIPREC=100

 First 100 records will be skipped and remaining records will be send to
SORT for processing.
STOPAFT /SKIPREC

//SORTCHK1 EXEC PGM=SORT
//SORTIN   DD *
111 1 0001 1
111 2 0001 2
111 3 0001 3
222 1 0001 1
333 1 0001 1
444 3 0001 2
444 4 0001 4
444 2 0001 2
//SORTOUT DD SYSOUT=*
//SYSOUT   DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSIN    DD *
 SORT FIELDS=(1,3,CH,A),SKIPREC=02,STOPAFT=5
/*

SORTOUT
------------
111 3 0001 3
222 1 0001 1
333 1 0001 1
444 3 0001 2
444 4 0001 4
INCLUDE / OMIT


INCLUDE/OMIT COND=ALL / NONE /COMPARISION

INCLUDE COND=((1,4,CH,EQ,C'1995',OR,1,4,CH,EQ,C'1996‘),AND,5,5,CH,EQ,C'PARIS')

INCLUDE COND=(1,4,CH,EQ,10,4,CH) OR (1,4,EQ,10,4),FORMAT=CH

INCLUDE COND=(15,3,ZD,EQ,100,AND,20,1,CH,NE,X'40')

INCLUDE COND=(35,8,ZD,LE,&DATE1,AND,45,8,ZD,GT,&DATE1-14)

 If you have multiple strings to search:
 (1,4,CH,EQ,L(C'1995',C'1996‘) OR (1,40,SS,EQ,L(C'1995',C'1996‘))

 Numeric Check
INCLUDE COND=(35,8,ZD,EQ,NUM)


SORTIN (FB RECORD)
----+----1----+----2----+----3----+----4----+----5----+
1995PARIS1997 100 R
1996LONDN1996       ANYTOWN
1997CINCI1998 200           ANYTOWN
1999INDIA1999                       20120220 20120218

Options vlscomp
INREC

The INREC control statement reformats the input records.

 Use the INREC control statement to add, delete, or reformat fields before the records are sorted or
merged.

 Except for CONVERT, all the functions performed by the OUTREC control statement, such as
inserting character strings or changing the data format of a numeric field, can also be performed by
the INREC control statement.

Note: that INREC is performed after E15 exit processing and INCLUDE/OMIT control statement
processing.

INREC FIELDS=(1,15,20,5)

SORTIN                                   SORTOUT
----+----1----+----2----+----3           ----+----1----+----2
ABCDEFGHIJKLMNOPQRSTUVWXYZ               ABCDEFGHIJKLMNOTUVWX

INREC FIELDS=(1,4,5,9,ZD,PD,X,20,5)             Variable Block (1,4 RECORD LENGTH)

SORTIN                                   SORTOUT (HEX ON)
----+----1----+----2----+----3           ----+----1----+
    123456789RAMA ABCDEFGHI                    î̤ ABCDE
                                             135794CCCCC
                                             2468F012345
INREC contd…


INREC IFTHEN=(WHEN=INIT,BUILD=(1,15,C’CVG’,19,27)),
      IFTHEN=(WHEN=(1,2,CH,EQ,C’NJ’),
                        BUILD=(1,30,C’NEW JERSEY’)),
      IFTHEN=(WHEN=(1,2,CH,EQ,C’NY’),
                        OVERLAY=(31:C’NEW YORK ‘)),
      IFTHEN=(WHEN=NONE,OVERLAY=(31:C’NO MATCH ‘))


SORTIN
----+----1----+----2----+----3----+----4----+----5----+
HYDERABAD                     INDIA
NJ                            USA
NY                            USA
PARIS


SORTOUT
----+----1----+----2----+----3----+----4----+
HYDERABAD      CVG            NO MATCH
NJ             CVG            NEW JERSEY
NY             CVG            NEW YORK
PARIS          CVG            NO MATCH
INREC contd…

 INREC FIELDS=(1,7,SFF,TO=ZD,9,7,UFF,TO=PD)       * SIGNED FREE FORM FORMAT
                                                  * UNSIGNED FREE FORM FORMAT
 SORTIN                               SORTOUT (HEX ON)
 ----+----1----+----2----+----3       ----+----1-
  -19.85 +20.05                       000198L
                                      FFFFFFD0005
                                      0001985020F

INREC PARSE=(%1=(ENDBEFR=C',',FIXLEN=4),            *   STOCK SYMBOL (MAX LEN 4)
             %2=(ENDBEFR=C',',FIXLEN=6),            *   CURRENT PRICE (MAX LEN 6)
             %3=(FIXLEN=1),                         *   SIGN OF TODAY'S CHANGE
             %4=(ENDBEFR=C' ',FIXLEN=5)),           *   CHANGE AMOUNT (MAX LEN 5)
BUILD=(01:%1,                                       *   STOCK SYMBOL
       07:%2,JFY=(SHIFT=RIGHT),                     *   CURRENT PRICE
       15:%3,                                       *   SIGN OF TODAY'S CHANGE
       16:%4,JFY=(SHIFT=RIGHT))                     *   CHANGE AMOUNT
SORT FIELDS=(1,4,CH,A)                              *   SORT BY STOCK SYMBOL

SORTIN                           SORTOUT
----+----1----+---               ----+----1----+-----
DIS,34.56,+1.09                  DIS     34.56 + 1.09
T,37.05,-.42                     GOOG 449.12 -11.62
GOOG,449.12,-11.62               T       37.05 - .42

** If you don’t want to store just say % in PARSE
JOIN


 Using JOIN you can extract and sort data from two different files. One file point to
SORTJNF1 other point to SORTJNF2.

The join files do not need to be presorted on the fields specified on the
JOINKEYS statement. By default, SyncSort will sort the records to the proper
sequence before performing the join operation.

 The FIELDS parameter is required. It describes the fields to be used to match records
from the two files, SORTJNF1 and SORTJNF2.

 The number of JOINKEYS fields and their lengths and sorted order (A or D) must be
the same for both files, although their starting positions need not be the same.

 Each JOINKEYS field may be anywhere within the record through column 32750,
the maximum length of a field is 4080 bytes, and the sum of all fields on a JOINKEYS
statement cannot exceed 4080 bytes.

 For variable-length records, any JOINKEYS fields that are completely or partially
missing will be padded with binary zeros when performing the comparison.
JOIN Cntd..

//SORTJNF1 DD *                              //SORTJNF2 DD *
----+----1----+----2----+----3-              ----+----1----+----2----+----3-
000001 0310.00 12/01/2002 2178I              7454C JOSEPH SMITH NY
000002 8055.22 12/02/2002 2123D              2111A JAMES JONES   NJ
000003 0310.00 12/05/2002 2178I              2178I JOHN JACKSON DE
000004 0020.00 12/06/2002 2111A              2123D MARY LEE      FL


JOINKEYS FILE=F1,FIELDS=(27,5,A)
JOINKEYS FILE=F2,FIELDS=(1,5,A)
REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3)        File1              File2
SORT FIELDS=COPY
OUTFIL FILES=01,HEADER2=('DATE       ','TRANS# ','TRANAMT ',
            'CUST# ','CUSTOMER NAME ','ADD')


DATE         TRANS#   TRANAMT   CUST#   CUSTOMER NAME   ADD
12/06/2002   000004   0020.00   2111A   JAMES JONES     NJ
12/02/2002   000002   8055.22   2123D   MARY LEE        FL
12/05/2002   000003   0310.00   2178I   JOHN JACKSON    DE
12/01/2002   000001   0310.00   2178I   JOHN JACKSON    DE
JOIN Cntd..

//SORTJNF1 DD *                              //SORTJNF2 DD *
----+----1----+----2----+----3-              ----+----1----+----2----+----3-
000001 0310.00 12/01/2002 2178I              7454C JOSEPH SMITH NY
000002 8055.22 12/02/2002 2123D              2111A JAMES JONES   NJ
000003 0310.00 12/05/2002 2178I              2178I JOHN JACKSON DE
000004 0020.00 12/06/2002 2111A              2123D MARY LEE      FL


JOINKEYS FILE=F1,FIELDS=(27,5,A)                            File1              File2
JOINKEYS FILE=F2,FIELDS=(1,5,A)
JOIN UNPAIRED,F2
REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3),FILL=C’ ‘
SORT FIELDS=COPY
OUTFIL FILES=01,HEADER2=('DATE       ','TRANS# ','TRANAMT ',
            'CUST# ','CUSTOMER NAME ','ADD')


DATE         TRANS#   TRANAMT   CUST#   CUSTOMER NAME   ADD
12/06/2002   000004   0020.00   2111A   JAMES JONES     NJ
12/02/2002   000002   8055.22   2123D   MARY LEE        FL
12/05/2002   000003   0310.00   2178I   JOHN JACKSON    DE
12/01/2002   000001   0310.00   2178I   JOHN JACKSON    DE
                                        JOSEPH SMITH    NY
JOIN contd…



                                                                                               File1    File2
     File1      File2               File1        File2           File1         File2



   Left Outer Join                Right Outer Join               Full Outer Join
                                                                                             JOIN
   JOIN UNPAIRED,F1               JOIN UNPAIRED,F2               JOIN UNPAIRED               UNPAIRED,ONLY


JOIN         UNPAIRED [,F1] [,F2] [,ONLY]

 To retain unpaired records from SORTJNF1 (a “left outer join”) in addition to all joined records,
JOIN UNPAIRED,F1

 To retain unpaired records from SORTJNF2 (a “right outer join”) in addition to all joined records.
JOIN UNPAIRED,F2

 To retain unpaired records from both SORTJNF1 and SORTJNF2 (a “full outer join”) in addition to all joined records,
JOIN UNPAIRED,F1,F2

or simply:
JOIN UNPAIRED

You have the option of discarding the paired records from a join and keeping only the unpaired ones.
JOIN UNPAIRED,ONLY
SUM

 The SUM control statement specifies that, whenever two records are found with equal
sort control fields, the contents of their summary fields are to be added, the sum is to be
placed in one of the records and the other record is to be deleted.

 If the EQUALS option is in effect the first record of summed records is kept.

 If the NOEQUALS option is in effect, the record to be kept is unpredictable.

SORT FIELDS=(1,3,CH,A),EQUALS
SUM FIELDS=(7,4,ZD),XSUM
SUM FIELDS=NONE,XSUM

SORTIN:                 SORTOUT:              SORTXSUM:
----+----1--            ----+----1--          ----+----1--
111 1 0001 1            111 1 0003 1          111 2 0001 2
111 2 0001 2            222 1 0001 1          111 3 0001 3
111 3 0001 3            333 1 0001 1          444 4 0001 4
222 1 0001 1            444 3 0003 2          444 2 0001 2
333 1 0001 1
444 3 0001 2
444 4 0001 4
444 2 0001 2
DUPKEYS


 The DUPKEYS control statement deletes all records with duplicate SORT control
fields and optionally replaces specified numeric fields in the retained records with
calculated sum, minimum, maximum, or average values from all records with equal
control fields.

 The deleted records can optionally be written to a separate output file (using XDUP).


SORT FIELDS=(1,3,CH,A),EQUALS
DUPKEYS SUM=(7,4),MIN=(5,1),MAX=(12,1),FORMAT=ZD,XDUP
DUPKEYS FIELDS=NONE,XDUP

 SUM,MIN,MAX may not overlap each other.


 SORTIN:                  SORTOUT:               SORTXDUP:
 ----+----1--             ----+----1--           ----+----1--
 111 1 0001 1             111 1 0003 3           111 2 0001 2
 111 2 0001 2             222 1 0001 1           111 3 0001 3
 111 3 0001 3             333 1 0001 1           444 4 0001 4
 222 1 0001 1             444 2 0003 4           444 2 0001 2
 333 1 0001 1
 444 3 0001 2
 444 4 0001 4
 444 2 0001 2
MODS (EXIT module…)

MODS E15=(E15COBOL,9999,MODLIB,C), E35=(E35COBOL,999999,STEPLIB,C)

 An E15 exit is the first exit routine. E15COBOL is the member name of the routine,
which requires 9999 bytes in main storage and resides in a library referenced by the DD
statement named MODLIB. The routine does not require link-editing.

 An E35 exit is the third exit routine. E35COBOL is the member name of the routine,
which requires 999999 bytes in main storage and resides in a library referenced by the DD
statement named STEPLIB. This routine is a COBOL exit which has been link-edited
before execution time.

C The C value identifies a COBOL exit routine. COBOL exits must be link-edited before execution time.
Only COBOL E15 and E35 exits can be specified.

E The E value identifies a C exit routine. C exits must be link-edited before execution time.
Only C E15 and/or E35 exits can be specified.

X The X value identifies a REXX exit routine.
Only REXX E15 and E35 exits can be specified.


 You can name the referenced DD name as you wish (MODLIB / STEPLIB / RKLIB …)
MODS (EXIT module example…)


//COBOLSRT EXEC PGM=SORT
//STEPLIB DD DSN=PROD.LOADLIB.MCEL,DISP=SHR
//SORTIN    DD DISP=SHR,DSN=SORT.INPUT.FILE
//SORTOUT DD DSN=SORT.OUTPUT.FILE,
//              DISP=(,CATLG,DELETE),
//              SPACE=(CYL,(10,10),RLSE),
//              DCB=(SUP.ALL,RECFM=VB,LRECL=972),UNIT=SYSDA
//SYSIN    DD *
   SORT FIELDS=COPY
   MODS E35=(E35COBOL,999999,STEPLIB,C)
   OUTREC FIELDS=(01,250,47X)
//*

//REXXSORT EXEC PGM=SORT
//MODLIB     DD DSN=MCELD.R0009H1.CLIST,DISP=SHR
//SYSTSPRT DD SYSOUT=*,DCB=(RECFM=FB,LRECL=297)
//SYSOUT     DD SYSOUT=*
//SORTIN     DD DSN=MCELD.R0009H1.REC250,DISP=SHR
//SORTOUT    DD DSN=MCELD.R0009H1.REC297,DISP=(,CATLG,DELETE),
//          UNIT=SYSDA,SPACE=(CYL,(2,2),RLSE)
//SYSIN    DD *
   SORT FIELDS=COPY
   MODS E15=(E15COBOL,336000,MODLIB,C)
   OUTREC FIELDS=(01,250,47X)
//*
MODS
                 Cobol Exit module Example..
 NO SELECT STATEMENT FOR THE INPUT, HANDLED BY SYNCSORT

01   EXIT-STATUS                  PIC 9(08) COMP.
     88 FIRST-RECORD                        VALUE 00.
     88 NORMAL                              VALUE 04.
     88 LAST-RECORD                         VALUE 08.

01   RECORD-FROM-SORT.
     05 INPUT-RECORD OCCURS 1 TO 968 TIMES
                DEPENDING ON INPUT-LENGTH  PIC    X(01).
01   RECORD-TO-SORT.
     05 OUTPUT-RECORD OCCURS 1 TO 968 TIMES
                DEPENDING ON OUTPUT-LENGTH PIC    X(01).
01   IN-BUF                                 PIC   X(01).
01   DUMMY                                  PIC   X(01).
01   INPUT-LENGTH                           PIC   9(08) COMP.
01   OUTPUT-LENGTH                          PIC   9(08) COMP.

PROCEDURE DIVISION USING   EXIT-STATUS,
                           RECORD-FROM-SORT,
                           RECORD-TO-SORT,
                           IN-BUF,
                           DUMMY,
                           INPUT-LENGTH,
                           OUTPUT-LENGTH
OUTREC

The OUTREC control statement reformats the output records.

 Use the OUTREC control statement to add, delete, or reformat fields after the records are
sorted or merged.

Including CONVERT, all the functions performed by the INREC control statement, such as
inserting character strings or changing the data format of a numeric field, can also be
performed by the OUTREC control statement.

Note: that OUTREC is performed before E35 exit processing.

OUTREC FIELDS=(1,15,20,5)

SORTIN                                   SORTOUT
----+----1----+----2----+----3           ----+----1----+----2
ABCDEFGHIJKLMNOPQRSTUVWXYZ               ABCDEFGHIJKLMNOTUVWX

OUTREC FIELDS=(5,9,ZD,PD,X,20,5),CONVERT              * CONVERT FROM VB TO FB

SORTIN                                   SORTOUT (HEX ON)
----+----1----+----2----+----3           ----+----1-
    123456789RAMA ABCDEFGHI                î̤ ABCDE
                                         135794CCCCC
                                         2468F012345
OUTREC

  SORT FIELDS=COPY
* ENSURE A VALID POSITIVE ZD VALUE IN 4-8 HAS AN F SIGN.

  OUTREC IFTHEN=(WHEN=(4,5,ZD,EQ,NUM),
  OVERLAY=(4:4,5,ZD,TO=ZDF,LENGTH=5),HIT=NEXT),
* REPLACE AN INVALID ZD VALUE IN 4-8 WITH 00000.
  IFTHEN=(WHEN=(4,5,ZD,NE,NUM),
  OVERLAY=(4:C'00000'),HIT=NEXT),
* ENSURE A VALID POSITIVE ZD VALUE IN 10-14 HAS AN F SIGN.

  IFTHEN=(WHEN=(10,5,ZD,EQ,NUM),
  OVERLAY=(10:10,5,ZD,TO=ZDF,LENGTH=5),HIT=NEXT),
* REPLACE AN INVALID ZD VALUE IN 10-14 WITH 00000.
  IFTHEN=(WHEN=(10,5,ZD,NE,NUM),
  OVERLAY=(10:C'00000'))
  SORTIN                     SORTOUT
  ----+----1----             ----+----1----
  R1 1234E 862-3             R1 12345 00000
  R2 582B3 2832C             R2 00000 28323
  R3 0521L 87103             R3 0521L 87103
  R4 68200 9862S             R4 68200 00000
  R5 7123T 0032J             R5 00000 0032J
  R6 X0521 72013             R6 00000 72013
OUTREC

 Here's how you could change all low values (X'00') to spaces (X'40'),

ALTSEQ CODE=(0040)
OUTREC FIELDS=(1,2,TRAN=ALTSEQ,              CH - change zeros to spaces
              21,5,                          PD field - no change
              26,55,TRAN=ALTSEQ)             CH - change zeros to spaces

Note: By not using TRAN=ALTSEQ for the PD field, we avoid changing PD values
incorrectly, such as from X'000000001C' (P'1') to X'404040401C' (P'404040401').
OUTFIL


The OUTFIL control statement describes the output file(s). It is required to accomplish
these three tasks:

 Create multiple output files. The OUTFIL parameters associated with this task are
CONVERT, ENDREC, FILES, FNAMES, FTOV, INCLUDE/OMIT, NULLOFL,
OUTREC, REPEAT, SAMPLE, SAVE, SPLIT, SPLITBY, SPLIT1R, STARTREC,
VLFILL, and VLTRIM.

 Use the Sort Writer facility. The OUTFIL parameters associated with this task are
HEADER1, HEADER2, LINES, NODETAIL, REMOVECC, SECTIONS, TRAILER1,
and TRAILER2.

Reformat records after E35 processing. The OUTFIL parameter associated with this
task is OUTREC.
OUTFIL


 Convert VB file to FB file and return return-code 4 when no records

INCLUDE COND=(400,28,CH,EQ,C'ERROR SENDING TO ACT MANAGER',AND,
              291,6,Y2W,EQ,Y'DATE1'-1)
SORT FIELDS=COPY
OUTFIL FILES=01,VTOF,OUTREC=(01:192,14,15:C',',
                             16:400,28),NULLOFL=RC4

** VTOF/CONVERT are same , FTOV is for FB to VB

 Editing Masks for Zone Decimal / Pack Decimal

INCLUDE COND=(196,2,CH,EQ,C'G2')
SORT FIELDS=(196,2,CH,A,214,2,CH,A)
SUM FIELDS=(51,7,ZD,207,7,PD)
OUTFIL FILES=01,OUTREC=(01:196,2,3:C',',04:214,2,6:C',',

                              07:51,7,ZD,EDIT=(TTTTTTT.TT),17:C',',
                              18:207,7,PD,EDIT=(TTTTTTTTTT.TTT))
OUTFIL


//SORTIN DD DSN=Y897797.INPUT3,DISP=OLD
//OUT1 DD DSN=Y897797.SUBSET1,DISP=(NEW,CATLG)
//OUT2 DD DSN=Y897797.SUBSET2,DISP=(NEW,CATLG)
//OUT3 DD DSN=Y897797.SUBSET3,DISP=(NEW,CATLG)
//SYSIN DD *
  SORT FIELDS=COPY
  OUTFIL INCLUDE=(8,6,CH,EQ,C'ACCTNG'),FNAMES=OUT1
  OUTFIL INCLUDE=(8,6,CH,EQ,C'DVPMNT'),FNAMES=OUT2
  OUTFIL SAVE,FNAMES=OUT3
//*

Y897797.SUBSET1 (OUT1 DD)
J2 ACCTNG
X52 ACCTNG
...
Y897797.SUBSET2 (OUT2 DD)
P16 DVPMNT
A51 DVPMNT
...
Y897797.SUBSET3 (OUT3 DD)
R27 RESRCH
Q51 ADMIN
...
OUTFIL

OUTFIL FTOV,VLTRIM=C'*',OUTREC=(1,7,9:8,8)

This OUTFIL control statement uses FTOV to convert fixed-length records to
variable length records and VLTRIM to remove the specified type of trailing bytes
(in this case, asterisks).

Input                  Output                  Record Length
Records                Records                (with 4-byte RDW)
----+----1----+-       +----1----+----2
RECORD1 ABC*****       RECORD1 ABC                     15
RECORD2 ABCDEF**       RECORD2 ABCDEF                  18
RECORD3 ABC****Z       RECORD3 ABC****Z                20

OUTFIL VTOF,VLFILL=C'*‘,OUTREC=(5,16)

This OUTFIL control statement uses VTOF to convert variable-length records to
fixed length records and VLFILL to fill the specified type of trailing bytes
(in this case, asterisks).

Input                  Output                  Record Length
Records                Records
+----1----+----2       ----+----1----+-
RECORD1 ABC            RECORD1 ABC*****                16
RECORD2 ABCDEF         RECORD2 ABCDEF**                16
RECORD3 ABC****Z       RECORD3 ABC****Z                16
OUTFIL REPORTS

JOINKEYS FILE=F1,FIELDS=(27,5,A)
JOINKEYS FILE=F2,FIELDS=(1,5,A)
REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3)
SORT FIELDS=COPY
OUTFIL FILES=01,HEADER2=('DATE ','TRAN# ','TRANAMT ','CUST# ','CUSTOMER
NAME ','ADD')




SORT FIELDS=(7,13,CH,A)
OUTFIL HEADER2=('INACTIVE CUSTOMERS',2/,'CUST# ','CUSTOMER NAME','ADD')
REPORTS cntd…
REPORTS cntd…
OUTFIL …
DATE

  DATE1 – YYYYMMDD                                       5,Y2T C'yyddd' or Z'yyddd'
                                                         6,Y2T C'yymmdd' or Z'yymmdd'
  DATE2 – YYYYMM
                                                         7,Y4T C'ccyyddd' or Z'ccyyddd'
  DATE3 – YYYYDDD                                        8,Y4T C'ccyymmdd' or Z'ccyymmdd'
                                                         5,Y2W C'dddyy' or Z'dddyy'
  DATE4 – yyyy-mm-dd-hh.mm.ss
                                                         6,Y2W C'mmddyy' or Z'mmddyy'
  DT=(MDYor4)      DTNS=(MDY)                            7,Y4W C'dddccyy' or Z'dddccyy'
                                                         8,Y4W C'mmddccyy' or Z'mmddccyy'
  TOJUL, TOGREG                                          3,Y2U P'yyddd'
  WEEKDAY=CHAR3/CHAR9/DIGIT1                             4,Y2V P'yymmdd'
                                                         4,Y4U P'ccyyddd'
               CHAR3 – ‘SUN’                             5,Y4V P'ccyymmdd'
               CHAR9 – ‘SUNDAY ‘                         3,Y2X P'dddyy'
                                                         4,Y2Y P'mmddyy'
               DIGIT1 – 1                                4,Y4X P'dddccyy'
                                                         5,Y4Y P'mmddccyy'

 &DATEx and &DATEx(c) represent the current date as a character string (C'string') to which a field
can be compared.

 &DATExP represents the current date as a decimal number (+n) to which a field can be compared.

 Y'DATEx' represents the current date with a Y constant (Y'string') to which a field can be compared.
DATE contd…

* Convert a P'dddyy' input date to a C'ccyy/mm/dd' output date   *Convert P'dddccyy' date can be edited to a C'ccyy-ddd' date
INREC BUILD=(21,3,Y2X,TOGREG=Y4T(/),X,                           OUTFIL BUILD=(1,4,Y4X(-))

* Convert a C'ccyymmdd' input date to a P'ccyyddd' output date * Convert a P'dddyy' input date to C'ccyy/mm/dd'
42,8,Y4T,TOJUL=Y4U,X,                                          INREC BUILD=(21,3,Y2X,TOGREG=Y4T(/),X,

* Convert a C'mmddyy' input date to a C'yymmdd' output date      •Convert a C'ccyymmdd' input date to P'ccyyddd'
11,6,Y2W,TOGREG=Y2T)                                             42,8,Y4T,TOJUL=Y4U,X,

* Convert a C'yyddd' input date to a C'dd/mm/ccyy' output date   •Date Calculation
OUTFIL BUILD=(92,5,Y2T,DT=(DM4/),X,                              (5,8,ZD,LE,&DATE1P,AND,5,8,ZD,GT,&DATE1P-14)

* Convert a P'ccyyddd' input date to a C'mmddyy' output date     INREC BUILD=(
53:32,4,Y4U,DTNS=(MDY))                                          1,6,Y2W,TOJUL=Y4T,X,
                                                                 1,6,Y2W,WEEKDAY=CHAR3,X,
* Convert a C'mmddccyy' date to a C'mmddccyy' date.              9,7,Y4T,TOGREG=Y4T(/),X,
OUTFIL BUILD=(34,8,Y4W,X,                                        9,7,Y4T,WEEKDAY=DIGIT1)

* Convert a P'ccyymmdd' date to a C'ccyy-mm-dd' date.            The input records might be as follows:
13,5,Y4V,EDIT=(TTTT-TT-TT),X,                                    120409 1999014
                                                                 051895 2003235
* Convert a C'dddccyy' date to a 4-byte BI dddccyy value.        999999 0000000
61,7,Y4W,TO=BI,LENGTH=4)                                         013099 1992343

Convert a Z'dddccyy' date to a C'ddd/ccyy' date.                 The output records would be as follows:
OUTFIL BUILD=(19,7,Y4W(/),X,                                     2009338 FRI 1999/01/14 5
                                                                 2095138 WED 2003/08/23 7
* Convert a P'ccyymmdd' date to a C'ccyy-mm-dd' date.            9999999 999 0000/00/00 0
43,5,Y4V(-))                                                     1999030 SAT 1992/12/08 3
Accessing DB2 table


You can access DB2 tables using SORT. But you can issue only SELECT statement.


//SORT EXEC PGM=SYNCSORT,PARM='DB2=D2P2'
//STEPLIB DD DSN=SYS.DMSS.DB2D2P2.SDSNLOAD,DISP=SHR
//SORTOUT DD SYSOUT=*
//SORTDBIN DD *
 SELECT ACRONYM, TRANS_CD_CLASS,
    TRANS_CD_TYPE,
    TRANS_CD_SUBTYPE,
    TRANS_CD_PRORATE,
    REVENUE_CD,
    REVENUE_TEXT
 FROM    CSGDB2A.BTA3_TRANS_REV
 WHERE ACRONYM = 'CBP';
/*
//SYSIN DD *
   SORT FIELDS=COPY
/*
//SYSOUT DD SYSOUT=*
SORT FLOW
SORT FLOW
Questions ???

Más contenido relacionado

La actualidad más candente

20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview QuestionsSrinimf-Slides
 
Introduction of ISPF
Introduction of ISPFIntroduction of ISPF
Introduction of ISPFAnil Bharti
 
Jcl utilities iebgener
Jcl  utilities iebgenerJcl  utilities iebgener
Jcl utilities iebgenerjanaki ram
 
JCL UTILITIES IEBCOPY
JCL UTILITIES IEBCOPYJCL UTILITIES IEBCOPY
JCL UTILITIES IEBCOPYjanaki ram
 
DB2 Interview Questions - Part 1
DB2 Interview Questions - Part 1DB2 Interview Questions - Part 1
DB2 Interview Questions - Part 1ReKruiTIn.com
 
Mainframe refresher-part-1
Mainframe refresher-part-1Mainframe refresher-part-1
Mainframe refresher-part-1vishwas17
 
Z OS IBM Utilities
Z OS IBM UtilitiesZ OS IBM Utilities
Z OS IBM Utilitieskapa rohit
 
Dialog Programming Overview
Dialog Programming OverviewDialog Programming Overview
Dialog Programming Overviewsapdocs. info
 
IBM DB2 for z/OS Administration Basics
IBM DB2 for z/OS Administration BasicsIBM DB2 for z/OS Administration Basics
IBM DB2 for z/OS Administration BasicsIBM
 
Top jcl interview questions and answers job interview tips
Top jcl interview questions and answers job interview tipsTop jcl interview questions and answers job interview tips
Top jcl interview questions and answers job interview tipsjcltutorial
 

La actualidad más candente (20)

DB2 utilities
DB2 utilitiesDB2 utilities
DB2 utilities
 
JCL SORT TOOL
JCL SORT TOOLJCL SORT TOOL
JCL SORT TOOL
 
20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions
 
Introduction of ISPF
Introduction of ISPFIntroduction of ISPF
Introduction of ISPF
 
Jcl utilities iebgener
Jcl  utilities iebgenerJcl  utilities iebgener
Jcl utilities iebgener
 
Skillwise JCL
Skillwise JCLSkillwise JCL
Skillwise JCL
 
MVS ABEND CODES
MVS ABEND CODESMVS ABEND CODES
MVS ABEND CODES
 
JCL UTILITIES IEBCOPY
JCL UTILITIES IEBCOPYJCL UTILITIES IEBCOPY
JCL UTILITIES IEBCOPY
 
DB2 Interview Questions - Part 1
DB2 Interview Questions - Part 1DB2 Interview Questions - Part 1
DB2 Interview Questions - Part 1
 
Vsam
VsamVsam
Vsam
 
Mainframe refresher-part-1
Mainframe refresher-part-1Mainframe refresher-part-1
Mainframe refresher-part-1
 
JCL DFSORT
JCL DFSORTJCL DFSORT
JCL DFSORT
 
Z OS IBM Utilities
Z OS IBM UtilitiesZ OS IBM Utilities
Z OS IBM Utilities
 
Mainframe
MainframeMainframe
Mainframe
 
Dialog Programming Overview
Dialog Programming OverviewDialog Programming Overview
Dialog Programming Overview
 
Basic VSAM
Basic VSAMBasic VSAM
Basic VSAM
 
Tso and ispf
Tso and ispfTso and ispf
Tso and ispf
 
IBM DB2 for z/OS Administration Basics
IBM DB2 for z/OS Administration BasicsIBM DB2 for z/OS Administration Basics
IBM DB2 for z/OS Administration Basics
 
Top jcl interview questions and answers job interview tips
Top jcl interview questions and answers job interview tipsTop jcl interview questions and answers job interview tips
Top jcl interview questions and answers job interview tips
 
Mvs commands
Mvs commandsMvs commands
Mvs commands
 

Destacado

Training presentation vlookup - what it is, and when to use it
Training presentation   vlookup - what it is, and when to use itTraining presentation   vlookup - what it is, and when to use it
Training presentation vlookup - what it is, and when to use ithayat25in
 
How to Suceed in Hadoop
How to Suceed in HadoopHow to Suceed in Hadoop
How to Suceed in HadoopPrecisely
 
Writing command macro in stratus cobol
Writing command macro in stratus cobolWriting command macro in stratus cobol
Writing command macro in stratus cobolSrinimf-Slides
 
The Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfThe Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfSrinimf-Slides
 
PL/SQL Interview Questions
PL/SQL Interview QuestionsPL/SQL Interview Questions
PL/SQL Interview QuestionsSrinimf-Slides
 
PLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersPLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersSrinimf-Slides
 
Oracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideOracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideSrinimf-Slides
 
Assembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersAssembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersSrinimf-Slides
 
IMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialIMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialSrinimf-Slides
 
101 Reasons To Go Vegetarian
101 Reasons To Go Vegetarian101 Reasons To Go Vegetarian
101 Reasons To Go VegetarianAntoine Tinawi
 
Assembly Language Basics
Assembly Language BasicsAssembly Language Basics
Assembly Language BasicsEducation Front
 

Destacado (17)

Training presentation vlookup - what it is, and when to use it
Training presentation   vlookup - what it is, and when to use itTraining presentation   vlookup - what it is, and when to use it
Training presentation vlookup - what it is, and when to use it
 
How to Suceed in Hadoop
How to Suceed in HadoopHow to Suceed in Hadoop
How to Suceed in Hadoop
 
Rexx
RexxRexx
Rexx
 
Writing command macro in stratus cobol
Writing command macro in stratus cobolWriting command macro in stratus cobol
Writing command macro in stratus cobol
 
The Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfThe Easytrieve Presention by Srinimf
The Easytrieve Presention by Srinimf
 
Rexx Shih
Rexx ShihRexx Shih
Rexx Shih
 
Macro teradata
Macro teradataMacro teradata
Macro teradata
 
DB2-SQL Part-2
DB2-SQL Part-2DB2-SQL Part-2
DB2-SQL Part-2
 
PL/SQL Interview Questions
PL/SQL Interview QuestionsPL/SQL Interview Questions
PL/SQL Interview Questions
 
PLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersPLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe Programmers
 
Oracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideOracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step Guide
 
Assembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersAssembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe Programmers
 
Assembler
AssemblerAssembler
Assembler
 
IMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialIMS DC Self Study Complete Tutorial
IMS DC Self Study Complete Tutorial
 
100 sql queries
100 sql queries100 sql queries
100 sql queries
 
101 Reasons To Go Vegetarian
101 Reasons To Go Vegetarian101 Reasons To Go Vegetarian
101 Reasons To Go Vegetarian
 
Assembly Language Basics
Assembly Language BasicsAssembly Language Basics
Assembly Language Basics
 

Similar a Sort presentation

Stack_Application_Infix_Prefix.pptx
Stack_Application_Infix_Prefix.pptxStack_Application_Infix_Prefix.pptx
Stack_Application_Infix_Prefix.pptxsandeep54552
 
[FT-11][suhorng] “Poor Man's” Undergraduate Compilers
[FT-11][suhorng] “Poor Man's” Undergraduate Compilers[FT-11][suhorng] “Poor Man's” Undergraduate Compilers
[FT-11][suhorng] “Poor Man's” Undergraduate CompilersFunctional Thursday
 
Combine the keypad and LCD codes in compliance to the following requ.pdf
Combine the keypad and LCD codes in compliance to the following requ.pdfCombine the keypad and LCD codes in compliance to the following requ.pdf
Combine the keypad and LCD codes in compliance to the following requ.pdfforwardcom41
 
Answers To Selected Exercises For Fortran 90 95 For Scientists And Engineers
Answers To Selected Exercises For Fortran 90 95 For Scientists And EngineersAnswers To Selected Exercises For Fortran 90 95 For Scientists And Engineers
Answers To Selected Exercises For Fortran 90 95 For Scientists And EngineersSheila Sinclair
 
New SQL features in latest MySQL releases
New SQL features in latest MySQL releasesNew SQL features in latest MySQL releases
New SQL features in latest MySQL releasesGeorgi Sotirov
 
The Ring programming language version 1.5 book - Part 2 of 31
The Ring programming language version 1.5 book - Part 2 of 31The Ring programming language version 1.5 book - Part 2 of 31
The Ring programming language version 1.5 book - Part 2 of 31Mahmoud Samir Fayed
 
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CSAAKASH KUMAR
 
3.ASSEMBLERS.pptx
3.ASSEMBLERS.pptx3.ASSEMBLERS.pptx
3.ASSEMBLERS.pptxGaganaP13
 
8086-instruction-set-ppt
 8086-instruction-set-ppt 8086-instruction-set-ppt
8086-instruction-set-pptjemimajerome
 
a) In the code, board is initialized by reading an input file. But y.pdf
a) In the code, board is initialized by reading an input file. But y.pdfa) In the code, board is initialized by reading an input file. But y.pdf
a) In the code, board is initialized by reading an input file. But y.pdfanuradhasilks
 
Concepts of C [Module 2]
Concepts of C [Module 2]Concepts of C [Module 2]
Concepts of C [Module 2]Abhishek Sinha
 
PBL1-v1-002j.pptx
PBL1-v1-002j.pptxPBL1-v1-002j.pptx
PBL1-v1-002j.pptxNAIST
 
Sap script system_symbol
Sap script system_symbolSap script system_symbol
Sap script system_symbolmoderngladiator
 

Similar a Sort presentation (20)

Stack_Application_Infix_Prefix.pptx
Stack_Application_Infix_Prefix.pptxStack_Application_Infix_Prefix.pptx
Stack_Application_Infix_Prefix.pptx
 
[FT-11][suhorng] “Poor Man's” Undergraduate Compilers
[FT-11][suhorng] “Poor Man's” Undergraduate Compilers[FT-11][suhorng] “Poor Man's” Undergraduate Compilers
[FT-11][suhorng] “Poor Man's” Undergraduate Compilers
 
Combine the keypad and LCD codes in compliance to the following requ.pdf
Combine the keypad and LCD codes in compliance to the following requ.pdfCombine the keypad and LCD codes in compliance to the following requ.pdf
Combine the keypad and LCD codes in compliance to the following requ.pdf
 
Answers To Selected Exercises For Fortran 90 95 For Scientists And Engineers
Answers To Selected Exercises For Fortran 90 95 For Scientists And EngineersAnswers To Selected Exercises For Fortran 90 95 For Scientists And Engineers
Answers To Selected Exercises For Fortran 90 95 For Scientists And Engineers
 
New SQL features in latest MySQL releases
New SQL features in latest MySQL releasesNew SQL features in latest MySQL releases
New SQL features in latest MySQL releases
 
pointers 1
pointers 1pointers 1
pointers 1
 
The Ring programming language version 1.5 book - Part 2 of 31
The Ring programming language version 1.5 book - Part 2 of 31The Ring programming language version 1.5 book - Part 2 of 31
The Ring programming language version 1.5 book - Part 2 of 31
 
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS
2 d array(part 1) || 2D ARRAY FUNCTION WRITING || GET 100% MARKS IN CBSE CS
 
3.ASSEMBLERS.pptx
3.ASSEMBLERS.pptx3.ASSEMBLERS.pptx
3.ASSEMBLERS.pptx
 
Vcs16
Vcs16Vcs16
Vcs16
 
Experiment 16 x2 parallel lcd
Experiment   16 x2 parallel lcdExperiment   16 x2 parallel lcd
Experiment 16 x2 parallel lcd
 
5.stack
5.stack5.stack
5.stack
 
8086-instruction-set-ppt
 8086-instruction-set-ppt 8086-instruction-set-ppt
8086-instruction-set-ppt
 
To excel or not?
To excel or not?To excel or not?
To excel or not?
 
Lập trình C
Lập trình CLập trình C
Lập trình C
 
a) In the code, board is initialized by reading an input file. But y.pdf
a) In the code, board is initialized by reading an input file. But y.pdfa) In the code, board is initialized by reading an input file. But y.pdf
a) In the code, board is initialized by reading an input file. But y.pdf
 
Macro
MacroMacro
Macro
 
Concepts of C [Module 2]
Concepts of C [Module 2]Concepts of C [Module 2]
Concepts of C [Module 2]
 
PBL1-v1-002j.pptx
PBL1-v1-002j.pptxPBL1-v1-002j.pptx
PBL1-v1-002j.pptx
 
Sap script system_symbol
Sap script system_symbolSap script system_symbol
Sap script system_symbol
 

Último

Gen AI in Business - Global Trends Report 2024.pdf
Gen AI in Business - Global Trends Report 2024.pdfGen AI in Business - Global Trends Report 2024.pdf
Gen AI in Business - Global Trends Report 2024.pdfAddepto
 
Generative AI for Technical Writer or Information Developers
Generative AI for Technical Writer or Information DevelopersGenerative AI for Technical Writer or Information Developers
Generative AI for Technical Writer or Information DevelopersRaghuram Pandurangan
 
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptx
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptxMerck Moving Beyond Passwords: FIDO Paris Seminar.pptx
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptxLoriGlavin3
 
Advanced Computer Architecture – An Introduction
Advanced Computer Architecture – An IntroductionAdvanced Computer Architecture – An Introduction
Advanced Computer Architecture – An IntroductionDilum Bandara
 
Sample pptx for embedding into website for demo
Sample pptx for embedding into website for demoSample pptx for embedding into website for demo
Sample pptx for embedding into website for demoHarshalMandlekar2
 
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptx
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptxPasskey Providers and Enabling Portability: FIDO Paris Seminar.pptx
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptxLoriGlavin3
 
Dev Dives: Streamline document processing with UiPath Studio Web
Dev Dives: Streamline document processing with UiPath Studio WebDev Dives: Streamline document processing with UiPath Studio Web
Dev Dives: Streamline document processing with UiPath Studio WebUiPathCommunity
 
DSPy a system for AI to Write Prompts and Do Fine Tuning
DSPy a system for AI to Write Prompts and Do Fine TuningDSPy a system for AI to Write Prompts and Do Fine Tuning
DSPy a system for AI to Write Prompts and Do Fine TuningLars Bell
 
The State of Passkeys with FIDO Alliance.pptx
The State of Passkeys with FIDO Alliance.pptxThe State of Passkeys with FIDO Alliance.pptx
The State of Passkeys with FIDO Alliance.pptxLoriGlavin3
 
SALESFORCE EDUCATION CLOUD | FEXLE SERVICES
SALESFORCE EDUCATION CLOUD | FEXLE SERVICESSALESFORCE EDUCATION CLOUD | FEXLE SERVICES
SALESFORCE EDUCATION CLOUD | FEXLE SERVICESmohitsingh558521
 
Nell’iperspazio con Rocket: il Framework Web di Rust!
Nell’iperspazio con Rocket: il Framework Web di Rust!Nell’iperspazio con Rocket: il Framework Web di Rust!
Nell’iperspazio con Rocket: il Framework Web di Rust!Commit University
 
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptx
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptxThe Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptx
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptxLoriGlavin3
 
Artificial intelligence in cctv survelliance.pptx
Artificial intelligence in cctv survelliance.pptxArtificial intelligence in cctv survelliance.pptx
Artificial intelligence in cctv survelliance.pptxhariprasad279825
 
Anypoint Exchange: It’s Not Just a Repo!
Anypoint Exchange: It’s Not Just a Repo!Anypoint Exchange: It’s Not Just a Repo!
Anypoint Exchange: It’s Not Just a Repo!Manik S Magar
 
What is Artificial Intelligence?????????
What is Artificial Intelligence?????????What is Artificial Intelligence?????????
What is Artificial Intelligence?????????blackmambaettijean
 
Take control of your SAP testing with UiPath Test Suite
Take control of your SAP testing with UiPath Test SuiteTake control of your SAP testing with UiPath Test Suite
Take control of your SAP testing with UiPath Test SuiteDianaGray10
 
The Ultimate Guide to Choosing WordPress Pros and Cons
The Ultimate Guide to Choosing WordPress Pros and ConsThe Ultimate Guide to Choosing WordPress Pros and Cons
The Ultimate Guide to Choosing WordPress Pros and ConsPixlogix Infotech
 
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptx
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptxThe Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptx
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptxLoriGlavin3
 
How to write a Business Continuity Plan
How to write a Business Continuity PlanHow to write a Business Continuity Plan
How to write a Business Continuity PlanDatabarracks
 
TrustArc Webinar - How to Build Consumer Trust Through Data Privacy
TrustArc Webinar - How to Build Consumer Trust Through Data PrivacyTrustArc Webinar - How to Build Consumer Trust Through Data Privacy
TrustArc Webinar - How to Build Consumer Trust Through Data PrivacyTrustArc
 

Último (20)

Gen AI in Business - Global Trends Report 2024.pdf
Gen AI in Business - Global Trends Report 2024.pdfGen AI in Business - Global Trends Report 2024.pdf
Gen AI in Business - Global Trends Report 2024.pdf
 
Generative AI for Technical Writer or Information Developers
Generative AI for Technical Writer or Information DevelopersGenerative AI for Technical Writer or Information Developers
Generative AI for Technical Writer or Information Developers
 
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptx
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptxMerck Moving Beyond Passwords: FIDO Paris Seminar.pptx
Merck Moving Beyond Passwords: FIDO Paris Seminar.pptx
 
Advanced Computer Architecture – An Introduction
Advanced Computer Architecture – An IntroductionAdvanced Computer Architecture – An Introduction
Advanced Computer Architecture – An Introduction
 
Sample pptx for embedding into website for demo
Sample pptx for embedding into website for demoSample pptx for embedding into website for demo
Sample pptx for embedding into website for demo
 
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptx
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptxPasskey Providers and Enabling Portability: FIDO Paris Seminar.pptx
Passkey Providers and Enabling Portability: FIDO Paris Seminar.pptx
 
Dev Dives: Streamline document processing with UiPath Studio Web
Dev Dives: Streamline document processing with UiPath Studio WebDev Dives: Streamline document processing with UiPath Studio Web
Dev Dives: Streamline document processing with UiPath Studio Web
 
DSPy a system for AI to Write Prompts and Do Fine Tuning
DSPy a system for AI to Write Prompts and Do Fine TuningDSPy a system for AI to Write Prompts and Do Fine Tuning
DSPy a system for AI to Write Prompts and Do Fine Tuning
 
The State of Passkeys with FIDO Alliance.pptx
The State of Passkeys with FIDO Alliance.pptxThe State of Passkeys with FIDO Alliance.pptx
The State of Passkeys with FIDO Alliance.pptx
 
SALESFORCE EDUCATION CLOUD | FEXLE SERVICES
SALESFORCE EDUCATION CLOUD | FEXLE SERVICESSALESFORCE EDUCATION CLOUD | FEXLE SERVICES
SALESFORCE EDUCATION CLOUD | FEXLE SERVICES
 
Nell’iperspazio con Rocket: il Framework Web di Rust!
Nell’iperspazio con Rocket: il Framework Web di Rust!Nell’iperspazio con Rocket: il Framework Web di Rust!
Nell’iperspazio con Rocket: il Framework Web di Rust!
 
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptx
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptxThe Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptx
The Fit for Passkeys for Employee and Consumer Sign-ins: FIDO Paris Seminar.pptx
 
Artificial intelligence in cctv survelliance.pptx
Artificial intelligence in cctv survelliance.pptxArtificial intelligence in cctv survelliance.pptx
Artificial intelligence in cctv survelliance.pptx
 
Anypoint Exchange: It’s Not Just a Repo!
Anypoint Exchange: It’s Not Just a Repo!Anypoint Exchange: It’s Not Just a Repo!
Anypoint Exchange: It’s Not Just a Repo!
 
What is Artificial Intelligence?????????
What is Artificial Intelligence?????????What is Artificial Intelligence?????????
What is Artificial Intelligence?????????
 
Take control of your SAP testing with UiPath Test Suite
Take control of your SAP testing with UiPath Test SuiteTake control of your SAP testing with UiPath Test Suite
Take control of your SAP testing with UiPath Test Suite
 
The Ultimate Guide to Choosing WordPress Pros and Cons
The Ultimate Guide to Choosing WordPress Pros and ConsThe Ultimate Guide to Choosing WordPress Pros and Cons
The Ultimate Guide to Choosing WordPress Pros and Cons
 
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptx
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptxThe Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptx
The Role of FIDO in a Cyber Secure Netherlands: FIDO Paris Seminar.pptx
 
How to write a Business Continuity Plan
How to write a Business Continuity PlanHow to write a Business Continuity Plan
How to write a Business Continuity Plan
 
TrustArc Webinar - How to Build Consumer Trust Through Data Privacy
TrustArc Webinar - How to Build Consumer Trust Through Data PrivacyTrustArc Webinar - How to Build Consumer Trust Through Data Privacy
TrustArc Webinar - How to Build Consumer Trust Through Data Privacy
 

Sort presentation

  • 1. SORT by RK
  • 2. Agenda SORT FLOW INCLUDE / OMIT INREC JOIN SUM / DUPKEYS EXIT Routines (MODS) OUTREC OUTFIL OUTFIL Reports DATE Operations
  • 3. Basic Points  The first byte of every fixed-length record is position 1, the second byte position 2, and so on.  Bytes 1 through 4 of variable-length records are reserved for the Record Descriptor Word (RDW). For these records, the first byte of the data portion is position 5.  When proper processing depends on data format, the format of the field must be specified.  The format of the field must be appropriate to the task. For example, only numeric fields can be SUMmed.  When all the fields have the same format, the format value can be specified just once through the FORMAT=f subparameter. The FORMAT=f subparameter cannot be used when the INCLUDE/OMIT parameter is specified on the OUTFIL control statement. Identify a comment card image by placing an asterisk (*) in column 1. Comments can extend through column 80.  To add a comment to a control statement card image, leave one or more blanks after the last parameter or comma on the image and follow with the comment, which can extend through column 71.
  • 4. Basic Points Contd…  Comment lines can be inserted between a control statement and its continuation by coding an asterisk (*) in column one. COL. 72 ↓ SORT FIELDS=(1,10,A,20,5,A,45,7,A),FORMAT=CH,STOPAFT=100, *COMMENT EQUALS In the above example, no continuation character is required. The control statement is interrupted after a parameter-comma combination before column 72. COL. 16 COL.72 ↓ ↓ OUTFIL OUTREC=(1:10,8,30:40,10),HEADER2=(1:'CUSTOMER NUMBX ER',30:'ITEM NUMBER') In this example, a continuation character is necessary because the literal string in the HEADER2 specification would extend beyond column 71. The 'X' in column 72 is the continuation character. The literal string is continued in column 16 of the next card image.
  • 5. SORT JCL //SORT EXEC PGM=SORT //SORTIN DD DISP=SHR,DSN=INPUT.FILE //SORTOUT DD DSN=OUTPUT.FILE, // DISP=(,CATLG,DELETE), // UNIT=SYSDA,SPACE=(TRKS,(40,20),RLSE) //SYSOUT DD SYSOUT=* //SYSPRINT DD SYSOUT=* //SYSIN DD * SORT FIELDS=COPY /* SORTIN SORTOUT ACCOUNT# MOBILE# STATUS DATE AMOUNT ACCOUNT# MOBILE# STATUS DATE AMOUNT ----+----+----+----+----+----+----+---- ----+----+----+----+----+----+----+---- 10000001 5000001 0 011511 100.50 10000001 5000001 0 011511 100.50 10000001 5000002 1 021512 050.50 10000001 5000002 1 021512 050.50 10000001 5000003 2 011512 000.50 10000001 5000003 2 011512 000.50 10000002 5100001 2 021512 111.50 10000002 5100001 2 021512 111.50 10000002 5200002 1 021512 120.50 10000002 5200002 1 021512 120.50 10000006 5600001 0 021512 100.50 10000006 5600001 0 021512 100.50 10000003 5300001 0 021512 020.50 10000003 5300001 0 021512 020.50
  • 6. SORT FLOW BEFORE SORT SORT AFTER SORT SORTIN SUM / DUPKEYS SKIPREC E15 OUTREC JOIN SORT E35 INCLUDE/OMIT OUTFIL SORTOUT STOPAFT INREC
  • 7. STOPAFT STOPAFT Parm STOPAFT=n  STOPAFT=n (a decimal number) sorts/copies at most n records. These will be the first n records after any input processing due to an E15, an INCLUDE/OMIT statement, or the SKIPREC parameter.  If STOPAFT=n has been specified on the SORT control statement as well as in the PARM field, the PARM specification will take precedence. //SORT EXEC PGM=SORT,PARM=‘STOPAFT=100' or SORT FIELDS=COPY,STOPAFT=100  First 100 records will be taken and remaining records will be skipped. These 100 will be send to next control of SORT for processing.
  • 8. SKIPREC SKIPREC Parm SKIPREC=n  SKIPREC=n instructs the sort to skip a decimal number n of records before sorting/copying the input file.  The records skipped are deleted from the input file before E15 and INCLUDE/OMIT processing is begun.  If SKIPREC=n has been specified on the SORT control statement as well as in the PARM field, the PARM specification will take precedence. //SORT EXEC PGM=SORT,PARM='SKIPREC=100' or SORT FIELDS=COPY,SKIPREC=100  First 100 records will be skipped and remaining records will be send to SORT for processing.
  • 9. STOPAFT /SKIPREC //SORTCHK1 EXEC PGM=SORT //SORTIN DD * 111 1 0001 1 111 2 0001 2 111 3 0001 3 222 1 0001 1 333 1 0001 1 444 3 0001 2 444 4 0001 4 444 2 0001 2 //SORTOUT DD SYSOUT=* //SYSOUT DD SYSOUT=* //SYSPRINT DD SYSOUT=* //SYSIN DD * SORT FIELDS=(1,3,CH,A),SKIPREC=02,STOPAFT=5 /* SORTOUT ------------ 111 3 0001 3 222 1 0001 1 333 1 0001 1 444 3 0001 2 444 4 0001 4
  • 10. INCLUDE / OMIT INCLUDE/OMIT COND=ALL / NONE /COMPARISION INCLUDE COND=((1,4,CH,EQ,C'1995',OR,1,4,CH,EQ,C'1996‘),AND,5,5,CH,EQ,C'PARIS') INCLUDE COND=(1,4,CH,EQ,10,4,CH) OR (1,4,EQ,10,4),FORMAT=CH INCLUDE COND=(15,3,ZD,EQ,100,AND,20,1,CH,NE,X'40') INCLUDE COND=(35,8,ZD,LE,&DATE1,AND,45,8,ZD,GT,&DATE1-14)  If you have multiple strings to search: (1,4,CH,EQ,L(C'1995',C'1996‘) OR (1,40,SS,EQ,L(C'1995',C'1996‘))  Numeric Check INCLUDE COND=(35,8,ZD,EQ,NUM) SORTIN (FB RECORD) ----+----1----+----2----+----3----+----4----+----5----+ 1995PARIS1997 100 R 1996LONDN1996 ANYTOWN 1997CINCI1998 200 ANYTOWN 1999INDIA1999 20120220 20120218 Options vlscomp
  • 11. INREC The INREC control statement reformats the input records.  Use the INREC control statement to add, delete, or reformat fields before the records are sorted or merged.  Except for CONVERT, all the functions performed by the OUTREC control statement, such as inserting character strings or changing the data format of a numeric field, can also be performed by the INREC control statement. Note: that INREC is performed after E15 exit processing and INCLUDE/OMIT control statement processing. INREC FIELDS=(1,15,20,5) SORTIN SORTOUT ----+----1----+----2----+----3 ----+----1----+----2 ABCDEFGHIJKLMNOPQRSTUVWXYZ ABCDEFGHIJKLMNOTUVWX INREC FIELDS=(1,4,5,9,ZD,PD,X,20,5)  Variable Block (1,4 RECORD LENGTH) SORTIN SORTOUT (HEX ON) ----+----1----+----2----+----3 ----+----1----+ 123456789RAMA ABCDEFGHI î̤ ABCDE 135794CCCCC 2468F012345
  • 12. INREC contd… INREC IFTHEN=(WHEN=INIT,BUILD=(1,15,C’CVG’,19,27)), IFTHEN=(WHEN=(1,2,CH,EQ,C’NJ’), BUILD=(1,30,C’NEW JERSEY’)), IFTHEN=(WHEN=(1,2,CH,EQ,C’NY’), OVERLAY=(31:C’NEW YORK ‘)), IFTHEN=(WHEN=NONE,OVERLAY=(31:C’NO MATCH ‘)) SORTIN ----+----1----+----2----+----3----+----4----+----5----+ HYDERABAD INDIA NJ USA NY USA PARIS SORTOUT ----+----1----+----2----+----3----+----4----+ HYDERABAD CVG NO MATCH NJ CVG NEW JERSEY NY CVG NEW YORK PARIS CVG NO MATCH
  • 13. INREC contd… INREC FIELDS=(1,7,SFF,TO=ZD,9,7,UFF,TO=PD) * SIGNED FREE FORM FORMAT * UNSIGNED FREE FORM FORMAT SORTIN SORTOUT (HEX ON) ----+----1----+----2----+----3 ----+----1- -19.85 +20.05 000198L FFFFFFD0005 0001985020F INREC PARSE=(%1=(ENDBEFR=C',',FIXLEN=4), * STOCK SYMBOL (MAX LEN 4) %2=(ENDBEFR=C',',FIXLEN=6), * CURRENT PRICE (MAX LEN 6) %3=(FIXLEN=1), * SIGN OF TODAY'S CHANGE %4=(ENDBEFR=C' ',FIXLEN=5)), * CHANGE AMOUNT (MAX LEN 5) BUILD=(01:%1, * STOCK SYMBOL 07:%2,JFY=(SHIFT=RIGHT), * CURRENT PRICE 15:%3, * SIGN OF TODAY'S CHANGE 16:%4,JFY=(SHIFT=RIGHT)) * CHANGE AMOUNT SORT FIELDS=(1,4,CH,A) * SORT BY STOCK SYMBOL SORTIN SORTOUT ----+----1----+--- ----+----1----+----- DIS,34.56,+1.09 DIS 34.56 + 1.09 T,37.05,-.42 GOOG 449.12 -11.62 GOOG,449.12,-11.62 T 37.05 - .42 ** If you don’t want to store just say % in PARSE
  • 14. JOIN  Using JOIN you can extract and sort data from two different files. One file point to SORTJNF1 other point to SORTJNF2. The join files do not need to be presorted on the fields specified on the JOINKEYS statement. By default, SyncSort will sort the records to the proper sequence before performing the join operation.  The FIELDS parameter is required. It describes the fields to be used to match records from the two files, SORTJNF1 and SORTJNF2.  The number of JOINKEYS fields and their lengths and sorted order (A or D) must be the same for both files, although their starting positions need not be the same.  Each JOINKEYS field may be anywhere within the record through column 32750, the maximum length of a field is 4080 bytes, and the sum of all fields on a JOINKEYS statement cannot exceed 4080 bytes.  For variable-length records, any JOINKEYS fields that are completely or partially missing will be padded with binary zeros when performing the comparison.
  • 15. JOIN Cntd.. //SORTJNF1 DD * //SORTJNF2 DD * ----+----1----+----2----+----3- ----+----1----+----2----+----3- 000001 0310.00 12/01/2002 2178I 7454C JOSEPH SMITH NY 000002 8055.22 12/02/2002 2123D 2111A JAMES JONES NJ 000003 0310.00 12/05/2002 2178I 2178I JOHN JACKSON DE 000004 0020.00 12/06/2002 2111A 2123D MARY LEE FL JOINKEYS FILE=F1,FIELDS=(27,5,A) JOINKEYS FILE=F2,FIELDS=(1,5,A) REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3) File1 File2 SORT FIELDS=COPY OUTFIL FILES=01,HEADER2=('DATE ','TRANS# ','TRANAMT ', 'CUST# ','CUSTOMER NAME ','ADD') DATE TRANS# TRANAMT CUST# CUSTOMER NAME ADD 12/06/2002 000004 0020.00 2111A JAMES JONES NJ 12/02/2002 000002 8055.22 2123D MARY LEE FL 12/05/2002 000003 0310.00 2178I JOHN JACKSON DE 12/01/2002 000001 0310.00 2178I JOHN JACKSON DE
  • 16. JOIN Cntd.. //SORTJNF1 DD * //SORTJNF2 DD * ----+----1----+----2----+----3- ----+----1----+----2----+----3- 000001 0310.00 12/01/2002 2178I 7454C JOSEPH SMITH NY 000002 8055.22 12/02/2002 2123D 2111A JAMES JONES NJ 000003 0310.00 12/05/2002 2178I 2178I JOHN JACKSON DE 000004 0020.00 12/06/2002 2111A 2123D MARY LEE FL JOINKEYS FILE=F1,FIELDS=(27,5,A) File1 File2 JOINKEYS FILE=F2,FIELDS=(1,5,A) JOIN UNPAIRED,F2 REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3),FILL=C’ ‘ SORT FIELDS=COPY OUTFIL FILES=01,HEADER2=('DATE ','TRANS# ','TRANAMT ', 'CUST# ','CUSTOMER NAME ','ADD') DATE TRANS# TRANAMT CUST# CUSTOMER NAME ADD 12/06/2002 000004 0020.00 2111A JAMES JONES NJ 12/02/2002 000002 8055.22 2123D MARY LEE FL 12/05/2002 000003 0310.00 2178I JOHN JACKSON DE 12/01/2002 000001 0310.00 2178I JOHN JACKSON DE JOSEPH SMITH NY
  • 17. JOIN contd… File1 File2 File1 File2 File1 File2 File1 File2 Left Outer Join Right Outer Join Full Outer Join JOIN JOIN UNPAIRED,F1 JOIN UNPAIRED,F2 JOIN UNPAIRED UNPAIRED,ONLY JOIN UNPAIRED [,F1] [,F2] [,ONLY]  To retain unpaired records from SORTJNF1 (a “left outer join”) in addition to all joined records, JOIN UNPAIRED,F1  To retain unpaired records from SORTJNF2 (a “right outer join”) in addition to all joined records. JOIN UNPAIRED,F2  To retain unpaired records from both SORTJNF1 and SORTJNF2 (a “full outer join”) in addition to all joined records, JOIN UNPAIRED,F1,F2 or simply: JOIN UNPAIRED You have the option of discarding the paired records from a join and keeping only the unpaired ones. JOIN UNPAIRED,ONLY
  • 18. SUM  The SUM control statement specifies that, whenever two records are found with equal sort control fields, the contents of their summary fields are to be added, the sum is to be placed in one of the records and the other record is to be deleted.  If the EQUALS option is in effect the first record of summed records is kept.  If the NOEQUALS option is in effect, the record to be kept is unpredictable. SORT FIELDS=(1,3,CH,A),EQUALS SUM FIELDS=(7,4,ZD),XSUM SUM FIELDS=NONE,XSUM SORTIN: SORTOUT: SORTXSUM: ----+----1-- ----+----1-- ----+----1-- 111 1 0001 1 111 1 0003 1 111 2 0001 2 111 2 0001 2 222 1 0001 1 111 3 0001 3 111 3 0001 3 333 1 0001 1 444 4 0001 4 222 1 0001 1 444 3 0003 2 444 2 0001 2 333 1 0001 1 444 3 0001 2 444 4 0001 4 444 2 0001 2
  • 19. DUPKEYS  The DUPKEYS control statement deletes all records with duplicate SORT control fields and optionally replaces specified numeric fields in the retained records with calculated sum, minimum, maximum, or average values from all records with equal control fields.  The deleted records can optionally be written to a separate output file (using XDUP). SORT FIELDS=(1,3,CH,A),EQUALS DUPKEYS SUM=(7,4),MIN=(5,1),MAX=(12,1),FORMAT=ZD,XDUP DUPKEYS FIELDS=NONE,XDUP  SUM,MIN,MAX may not overlap each other. SORTIN: SORTOUT: SORTXDUP: ----+----1-- ----+----1-- ----+----1-- 111 1 0001 1 111 1 0003 3 111 2 0001 2 111 2 0001 2 222 1 0001 1 111 3 0001 3 111 3 0001 3 333 1 0001 1 444 4 0001 4 222 1 0001 1 444 2 0003 4 444 2 0001 2 333 1 0001 1 444 3 0001 2 444 4 0001 4 444 2 0001 2
  • 20. MODS (EXIT module…) MODS E15=(E15COBOL,9999,MODLIB,C), E35=(E35COBOL,999999,STEPLIB,C)  An E15 exit is the first exit routine. E15COBOL is the member name of the routine, which requires 9999 bytes in main storage and resides in a library referenced by the DD statement named MODLIB. The routine does not require link-editing.  An E35 exit is the third exit routine. E35COBOL is the member name of the routine, which requires 999999 bytes in main storage and resides in a library referenced by the DD statement named STEPLIB. This routine is a COBOL exit which has been link-edited before execution time. C The C value identifies a COBOL exit routine. COBOL exits must be link-edited before execution time. Only COBOL E15 and E35 exits can be specified. E The E value identifies a C exit routine. C exits must be link-edited before execution time. Only C E15 and/or E35 exits can be specified. X The X value identifies a REXX exit routine. Only REXX E15 and E35 exits can be specified.  You can name the referenced DD name as you wish (MODLIB / STEPLIB / RKLIB …)
  • 21. MODS (EXIT module example…) //COBOLSRT EXEC PGM=SORT //STEPLIB DD DSN=PROD.LOADLIB.MCEL,DISP=SHR //SORTIN DD DISP=SHR,DSN=SORT.INPUT.FILE //SORTOUT DD DSN=SORT.OUTPUT.FILE, // DISP=(,CATLG,DELETE), // SPACE=(CYL,(10,10),RLSE), // DCB=(SUP.ALL,RECFM=VB,LRECL=972),UNIT=SYSDA //SYSIN DD * SORT FIELDS=COPY MODS E35=(E35COBOL,999999,STEPLIB,C) OUTREC FIELDS=(01,250,47X) //* //REXXSORT EXEC PGM=SORT //MODLIB DD DSN=MCELD.R0009H1.CLIST,DISP=SHR //SYSTSPRT DD SYSOUT=*,DCB=(RECFM=FB,LRECL=297) //SYSOUT DD SYSOUT=* //SORTIN DD DSN=MCELD.R0009H1.REC250,DISP=SHR //SORTOUT DD DSN=MCELD.R0009H1.REC297,DISP=(,CATLG,DELETE), // UNIT=SYSDA,SPACE=(CYL,(2,2),RLSE) //SYSIN DD * SORT FIELDS=COPY MODS E15=(E15COBOL,336000,MODLIB,C) OUTREC FIELDS=(01,250,47X) //*
  • 22. MODS Cobol Exit module Example..  NO SELECT STATEMENT FOR THE INPUT, HANDLED BY SYNCSORT 01 EXIT-STATUS PIC 9(08) COMP. 88 FIRST-RECORD VALUE 00. 88 NORMAL VALUE 04. 88 LAST-RECORD VALUE 08. 01 RECORD-FROM-SORT. 05 INPUT-RECORD OCCURS 1 TO 968 TIMES DEPENDING ON INPUT-LENGTH PIC X(01). 01 RECORD-TO-SORT. 05 OUTPUT-RECORD OCCURS 1 TO 968 TIMES DEPENDING ON OUTPUT-LENGTH PIC X(01). 01 IN-BUF PIC X(01). 01 DUMMY PIC X(01). 01 INPUT-LENGTH PIC 9(08) COMP. 01 OUTPUT-LENGTH PIC 9(08) COMP. PROCEDURE DIVISION USING EXIT-STATUS, RECORD-FROM-SORT, RECORD-TO-SORT, IN-BUF, DUMMY, INPUT-LENGTH, OUTPUT-LENGTH
  • 23. OUTREC The OUTREC control statement reformats the output records. Use the OUTREC control statement to add, delete, or reformat fields after the records are sorted or merged. Including CONVERT, all the functions performed by the INREC control statement, such as inserting character strings or changing the data format of a numeric field, can also be performed by the OUTREC control statement. Note: that OUTREC is performed before E35 exit processing. OUTREC FIELDS=(1,15,20,5) SORTIN SORTOUT ----+----1----+----2----+----3 ----+----1----+----2 ABCDEFGHIJKLMNOPQRSTUVWXYZ ABCDEFGHIJKLMNOTUVWX OUTREC FIELDS=(5,9,ZD,PD,X,20,5),CONVERT * CONVERT FROM VB TO FB SORTIN SORTOUT (HEX ON) ----+----1----+----2----+----3 ----+----1- 123456789RAMA ABCDEFGHI î̤ ABCDE 135794CCCCC 2468F012345
  • 24. OUTREC SORT FIELDS=COPY * ENSURE A VALID POSITIVE ZD VALUE IN 4-8 HAS AN F SIGN. OUTREC IFTHEN=(WHEN=(4,5,ZD,EQ,NUM), OVERLAY=(4:4,5,ZD,TO=ZDF,LENGTH=5),HIT=NEXT), * REPLACE AN INVALID ZD VALUE IN 4-8 WITH 00000. IFTHEN=(WHEN=(4,5,ZD,NE,NUM), OVERLAY=(4:C'00000'),HIT=NEXT), * ENSURE A VALID POSITIVE ZD VALUE IN 10-14 HAS AN F SIGN. IFTHEN=(WHEN=(10,5,ZD,EQ,NUM), OVERLAY=(10:10,5,ZD,TO=ZDF,LENGTH=5),HIT=NEXT), * REPLACE AN INVALID ZD VALUE IN 10-14 WITH 00000. IFTHEN=(WHEN=(10,5,ZD,NE,NUM), OVERLAY=(10:C'00000')) SORTIN SORTOUT ----+----1---- ----+----1---- R1 1234E 862-3 R1 12345 00000 R2 582B3 2832C R2 00000 28323 R3 0521L 87103 R3 0521L 87103 R4 68200 9862S R4 68200 00000 R5 7123T 0032J R5 00000 0032J R6 X0521 72013 R6 00000 72013
  • 25. OUTREC  Here's how you could change all low values (X'00') to spaces (X'40'), ALTSEQ CODE=(0040) OUTREC FIELDS=(1,2,TRAN=ALTSEQ, CH - change zeros to spaces 21,5, PD field - no change 26,55,TRAN=ALTSEQ) CH - change zeros to spaces Note: By not using TRAN=ALTSEQ for the PD field, we avoid changing PD values incorrectly, such as from X'000000001C' (P'1') to X'404040401C' (P'404040401').
  • 26. OUTFIL The OUTFIL control statement describes the output file(s). It is required to accomplish these three tasks:  Create multiple output files. The OUTFIL parameters associated with this task are CONVERT, ENDREC, FILES, FNAMES, FTOV, INCLUDE/OMIT, NULLOFL, OUTREC, REPEAT, SAMPLE, SAVE, SPLIT, SPLITBY, SPLIT1R, STARTREC, VLFILL, and VLTRIM.  Use the Sort Writer facility. The OUTFIL parameters associated with this task are HEADER1, HEADER2, LINES, NODETAIL, REMOVECC, SECTIONS, TRAILER1, and TRAILER2. Reformat records after E35 processing. The OUTFIL parameter associated with this task is OUTREC.
  • 27. OUTFIL  Convert VB file to FB file and return return-code 4 when no records INCLUDE COND=(400,28,CH,EQ,C'ERROR SENDING TO ACT MANAGER',AND, 291,6,Y2W,EQ,Y'DATE1'-1) SORT FIELDS=COPY OUTFIL FILES=01,VTOF,OUTREC=(01:192,14,15:C',', 16:400,28),NULLOFL=RC4 ** VTOF/CONVERT are same , FTOV is for FB to VB  Editing Masks for Zone Decimal / Pack Decimal INCLUDE COND=(196,2,CH,EQ,C'G2') SORT FIELDS=(196,2,CH,A,214,2,CH,A) SUM FIELDS=(51,7,ZD,207,7,PD) OUTFIL FILES=01,OUTREC=(01:196,2,3:C',',04:214,2,6:C',', 07:51,7,ZD,EDIT=(TTTTTTT.TT),17:C',', 18:207,7,PD,EDIT=(TTTTTTTTTT.TTT))
  • 28. OUTFIL //SORTIN DD DSN=Y897797.INPUT3,DISP=OLD //OUT1 DD DSN=Y897797.SUBSET1,DISP=(NEW,CATLG) //OUT2 DD DSN=Y897797.SUBSET2,DISP=(NEW,CATLG) //OUT3 DD DSN=Y897797.SUBSET3,DISP=(NEW,CATLG) //SYSIN DD * SORT FIELDS=COPY OUTFIL INCLUDE=(8,6,CH,EQ,C'ACCTNG'),FNAMES=OUT1 OUTFIL INCLUDE=(8,6,CH,EQ,C'DVPMNT'),FNAMES=OUT2 OUTFIL SAVE,FNAMES=OUT3 //* Y897797.SUBSET1 (OUT1 DD) J2 ACCTNG X52 ACCTNG ... Y897797.SUBSET2 (OUT2 DD) P16 DVPMNT A51 DVPMNT ... Y897797.SUBSET3 (OUT3 DD) R27 RESRCH Q51 ADMIN ...
  • 29. OUTFIL OUTFIL FTOV,VLTRIM=C'*',OUTREC=(1,7,9:8,8) This OUTFIL control statement uses FTOV to convert fixed-length records to variable length records and VLTRIM to remove the specified type of trailing bytes (in this case, asterisks). Input Output Record Length Records Records (with 4-byte RDW) ----+----1----+- +----1----+----2 RECORD1 ABC***** RECORD1 ABC 15 RECORD2 ABCDEF** RECORD2 ABCDEF 18 RECORD3 ABC****Z RECORD3 ABC****Z 20 OUTFIL VTOF,VLFILL=C'*‘,OUTREC=(5,16) This OUTFIL control statement uses VTOF to convert variable-length records to fixed length records and VLFILL to fill the specified type of trailing bytes (in this case, asterisks). Input Output Record Length Records Records +----1----+----2 ----+----1----+- RECORD1 ABC RECORD1 ABC***** 16 RECORD2 ABCDEF RECORD2 ABCDEF** 16 RECORD3 ABC****Z RECORD3 ABC****Z 16
  • 30. OUTFIL REPORTS JOINKEYS FILE=F1,FIELDS=(27,5,A) JOINKEYS FILE=F2,FIELDS=(1,5,A) REFORMAT FIELDS=(F1:16,11,1,7,8,8,27,6,F2:7,14,21,3) SORT FIELDS=COPY OUTFIL FILES=01,HEADER2=('DATE ','TRAN# ','TRANAMT ','CUST# ','CUSTOMER NAME ','ADD') SORT FIELDS=(7,13,CH,A) OUTFIL HEADER2=('INACTIVE CUSTOMERS',2/,'CUST# ','CUSTOMER NAME','ADD')
  • 34. DATE DATE1 – YYYYMMDD 5,Y2T C'yyddd' or Z'yyddd' 6,Y2T C'yymmdd' or Z'yymmdd' DATE2 – YYYYMM 7,Y4T C'ccyyddd' or Z'ccyyddd' DATE3 – YYYYDDD 8,Y4T C'ccyymmdd' or Z'ccyymmdd' 5,Y2W C'dddyy' or Z'dddyy' DATE4 – yyyy-mm-dd-hh.mm.ss 6,Y2W C'mmddyy' or Z'mmddyy' DT=(MDYor4) DTNS=(MDY) 7,Y4W C'dddccyy' or Z'dddccyy' 8,Y4W C'mmddccyy' or Z'mmddccyy' TOJUL, TOGREG 3,Y2U P'yyddd' WEEKDAY=CHAR3/CHAR9/DIGIT1 4,Y2V P'yymmdd' 4,Y4U P'ccyyddd' CHAR3 – ‘SUN’ 5,Y4V P'ccyymmdd' CHAR9 – ‘SUNDAY ‘ 3,Y2X P'dddyy' 4,Y2Y P'mmddyy' DIGIT1 – 1 4,Y4X P'dddccyy' 5,Y4Y P'mmddccyy'  &DATEx and &DATEx(c) represent the current date as a character string (C'string') to which a field can be compared.  &DATExP represents the current date as a decimal number (+n) to which a field can be compared.  Y'DATEx' represents the current date with a Y constant (Y'string') to which a field can be compared.
  • 35. DATE contd… * Convert a P'dddyy' input date to a C'ccyy/mm/dd' output date *Convert P'dddccyy' date can be edited to a C'ccyy-ddd' date INREC BUILD=(21,3,Y2X,TOGREG=Y4T(/),X, OUTFIL BUILD=(1,4,Y4X(-)) * Convert a C'ccyymmdd' input date to a P'ccyyddd' output date * Convert a P'dddyy' input date to C'ccyy/mm/dd' 42,8,Y4T,TOJUL=Y4U,X, INREC BUILD=(21,3,Y2X,TOGREG=Y4T(/),X, * Convert a C'mmddyy' input date to a C'yymmdd' output date •Convert a C'ccyymmdd' input date to P'ccyyddd' 11,6,Y2W,TOGREG=Y2T) 42,8,Y4T,TOJUL=Y4U,X, * Convert a C'yyddd' input date to a C'dd/mm/ccyy' output date •Date Calculation OUTFIL BUILD=(92,5,Y2T,DT=(DM4/),X, (5,8,ZD,LE,&DATE1P,AND,5,8,ZD,GT,&DATE1P-14) * Convert a P'ccyyddd' input date to a C'mmddyy' output date INREC BUILD=( 53:32,4,Y4U,DTNS=(MDY)) 1,6,Y2W,TOJUL=Y4T,X, 1,6,Y2W,WEEKDAY=CHAR3,X, * Convert a C'mmddccyy' date to a C'mmddccyy' date. 9,7,Y4T,TOGREG=Y4T(/),X, OUTFIL BUILD=(34,8,Y4W,X, 9,7,Y4T,WEEKDAY=DIGIT1) * Convert a P'ccyymmdd' date to a C'ccyy-mm-dd' date. The input records might be as follows: 13,5,Y4V,EDIT=(TTTT-TT-TT),X, 120409 1999014 051895 2003235 * Convert a C'dddccyy' date to a 4-byte BI dddccyy value. 999999 0000000 61,7,Y4W,TO=BI,LENGTH=4) 013099 1992343 Convert a Z'dddccyy' date to a C'ddd/ccyy' date. The output records would be as follows: OUTFIL BUILD=(19,7,Y4W(/),X, 2009338 FRI 1999/01/14 5 2095138 WED 2003/08/23 7 * Convert a P'ccyymmdd' date to a C'ccyy-mm-dd' date. 9999999 999 0000/00/00 0 43,5,Y4V(-)) 1999030 SAT 1992/12/08 3
  • 36. Accessing DB2 table You can access DB2 tables using SORT. But you can issue only SELECT statement. //SORT EXEC PGM=SYNCSORT,PARM='DB2=D2P2' //STEPLIB DD DSN=SYS.DMSS.DB2D2P2.SDSNLOAD,DISP=SHR //SORTOUT DD SYSOUT=* //SORTDBIN DD * SELECT ACRONYM, TRANS_CD_CLASS, TRANS_CD_TYPE, TRANS_CD_SUBTYPE, TRANS_CD_PRORATE, REVENUE_CD, REVENUE_TEXT FROM CSGDB2A.BTA3_TRANS_REV WHERE ACRONYM = 'CBP'; /* //SYSIN DD * SORT FIELDS=COPY /* //SYSOUT DD SYSOUT=*