Skip to main content

SORT collating sequence of EBCDIC with DIALECT(ENTCOBOL) CHARSET(ASCII)

  • November 1, 2017
  • 0 replies
  • 0 views

Problem:
 We have been using MFSORT with the SORT-EBCDIC parameter to provide sort results similar to that of the EBCDIC sort order on the mainframe in order to match output file and report results for comparison with mainframe baselines. Is there anything similar for an internal COBOL sort routine to specify an EBCDIC collating sequence as the sort order when we have set CHARSET(ASCII)?

Resolution:
 The mfsort.exe module can process an EBCDIC collating sequence with ASCII data, but so can a Cobol program or a SORT being called from JCL.
 To start, please re-compile your user program and create a compiler listing with these additional directives:
    setting(col) rawlist copylistcomment(7) list()
 Check the compiler listing file for the setting of these directives:  
  DIALECT
  CHARSET
  NATIVE
  SIGN
 It is the setting of NATIVE that we want to examine, but it is affected by the other directives. Please reference our online Help at this url and navigate to this topic:  
 
 http://documentation.microfocus.com/help/index.jsp
 Enterprise > Micro Focus Enterprise Developer 3.0 for Eclipse > General Reference > Compiler Directives > Compiler Directives - Alphabetical List, NATIVE
 
 The Help says:  Set to NATIVE"EBCDIC" at end by CHARSET"EBCDIC".
 
 The 'at end' is saying that as compiler gathers its list of directives and we are using CHARSET(EBCDIC) then NATIVE(EBCDIC) will be set. So if we pick up one directive and then find the same directive but with a different option, we will use the last one found. After gathering directives from all possible inputs (command line, .DIR files, IDE settings), the last setting found will be used. So that means if you want a DIALECT of ENTCOBOL with a character set of ASCII, you need to make sure the last CHARSET directive passed is CHARSET(ASCII) and then pass NATIVE(EBCDIC) after it. The compiler listing will confirm the final composite list of directives used.
 Here is an IBM reference for the expected output for an EBCDIC and ASCII collating sequences:
 
 Enterprise COBOL for z/OS 6.1.0>Language Reference>Appendixes>EBCDIC and ASCII collating sequences
 https://www.ibm.com/support/knowledgecenter/SS6SG3_6.1.0/com.ibm.cobol61.ent.doc/PGandLR/ref/rlebc.html
 
 And from the Micro Focus Help
 Enterprise > Micro Focus Enterprise Developer 3.0 for Eclipse > General Reference > COBOL Language Reference > Part 4: Appendices, Character Sets and Collating Sequences
 
 And here is a useful web site: http://www.simotime.com/cblclt01.htm  Search for ' sorted output '

 The following sample JCL uses a program compiled with Dialect(Entcobol) Charset(Ascii) Native(Ebcdic):  
 
//MFSRTA1S JOB (MFIUVE),'LORINCE',CLASS=A,MSGCLASS=D,
//       REGION=0M,NOTIFY=MFIUVE TYPRUN=SCAN
//*--------------------------------------------------------*
//*  Clean Up Old Datasets                                 *
//*--------------------------------------------------------*
//DELOLD1  EXEC PGM=IEFBR14
//DD1      DD DSN=MFIUVE.LORINCE.SORTIN,
//            SPACE=(TRK,(1,1)),DISP=(MOD,DELETE)
//DD2      DD DSN=MFIUVE.LORINCE.SORTOUT.COBA,
//            SPACE=(TRK,(1,1)),DISP=(MOD,DELETE)
//SYSOUT   DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
/*
//*--------------------------------------------------------*
//*  Create New Datasets                                   *
//*--------------------------------------------------------*
//MAKENEW1 EXEC PGM=IEFBR14
//DD1      DD DSN=MFIUVE.LORINCE.SORTIN,
//            DISP=(NEW,CATLG,KEEP),
//            UNIT=SYSDA,SPACE=(TRK,(1,1)),
//            DCB=(DSORG=PS,RECFM=FB,LRECL=80,BLKSIZE=0)
//DD2      DD DSN=MFIUVE.LORINCE.SORTOUT.COBA,
//            DISP=(NEW,CATLG,KEEP),
//            UNIT=SYSDA,SPACE=(TRK,(1,1)),
//            DCB=(DSORG=PS,RECFM=FB,LRECL=80,BLKSIZE=0)
//SYSOUT   DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
/*
//*--------------------------------------------------------*
//*  Copy Data Into Sortin Dataset                         *
//*--------------------------------------------------------*
//COPYIN   EXEC PGM=IDCAMS
//SYSIN    DD *
   REPRO INFILE(IN1) OUTFILE(OUT1)
//IN1      DD *
  00000001  x
9999999999  dupe
0000000001  x
( )0000003  x
0000000005  x
abc123d4e5  LetNum
0000000003  x
abcdefghij  l
0000000001  dupe
9999999999  x
0000000000  x
ABCDEFGHIJ  U
123abc4d5e  NumLet
/*
//OUT1     DD DSN=MFIUVE.LORINCE.SORTIN,DISP=SHR
//SYSPRINT DD SYSOUT=*
/*
//*--------------------------------------------------------*
//*  Cobol Sort Input Output Procedure Ascending           *
//*--------------------------------------------------------*
//GOCOBA   EXEC PGM=SORTA
//STEPLIB  DD DSN=CEE.SCEERUN,DISP=SHR
//         DD DSN=MFIUVE.PGMLIB,DISP=SHR
//INA      DD DSN=MFIUVE.LORINCE.SORTIN,DISP=SHR
//OUTA     DD DSN=MFIUVE.LORINCE.SORTOUT.COBA,DISP=SHR
//CEEDUMP  DD SYSOUT=*
//SORTA1   DD UNIT=SYSDA,SPACE=(CYL,(1),,CONTIG)
//SORTWK01 DD UNIT=SYSDA,SPACE=(CYL,(1),,CONTIG)
//SORTWK02 DD UNIT=SYSDA,SPACE=(CYL,(1),,CONTIG)
//SORTWK03 DD UNIT=SYSDA,SPACE=(CYL,(1),,CONTIG)
//SYSOUT   DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
/*
 
As you can see, the input is instream and will be cataloged as ASCII data because the ES Server being used for this case is set to use mf_charset=a (it is not case sensitive and can sometimes be seen as MF_CHARSET=A). So that setting will match the compiler directive of CHARSET(ASCII).
 
 Here is the expected output:
 
  00000001  x                                                                   
( )0000003  x                                                                   
abcdefghij  l                                                                   
abc123d4e5  LetNum                                                              
ABCDEFGHIJ  U                                                                   
0000000000  x                                                                   
0000000001  x                                                                   
0000000001  dupe                                                                
0000000003  x                                                                   
0000000005  x                                                                   
123abc4d5e  NumLet                                                              
9999999999  dupe                                                                
9999999999  x                                                                   
 
Since the sorting sequence for EBCDIC data is Space, Special Characters, Lower Case Letters, Upper Case Letters and then Numbers, you will see the output matches this order. The duplicate records are shown in the order in which they were read in. That is because the Cobol program used 'SORT ... ON ASCENDING KEY ... WITH DUPLICATES IN ORDER'. Be sure you create a compiler listing to check the final list of directives and that the NATIVE directive is set to use EBCDIC.
 Here is the sample Cobol program:
 
       IDENTIFICATION DIVISION.
       PROGRAM-ID.  SORTA.
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT SFILE ASSIGN SFILEA.
           SELECT SIN1  ASSIGN INA  FILE STATUS IS STAT1.
           SELECT SOUT1 ASSIGN OUTA FILE STATUS IS STAT2.
       DATA DIVISION.
       FILE SECTION.
       SD  SFILE.
       1   SORT-SD.
        2   SORT-S1-KEY      PIC X(10).
        2                    PIC X(70).
       FD  SIN1
           RECORDING MODE IS F.
       1   SORT-REC-FD1.
        2   SORT-F1-KEY      PIC X(10).
        2                    PIC X(70).
       FD  SOUT1
           RECORDING MODE IS F.
       1   SORT-REC-FD2.
        2   SORT-F2-KEY      PIC X(10).
        2                    PIC X(70).
       WORKING-STORAGE SECTION.
       1   WS-1.
        2   DUMP-CODE        PIC S9(8) BINARY.
        2   CLEANUP-SW       PIC S9(8) BINARY.
        2   WS-SWITCH        PIC X(1).
             88 END-INPUT    VALUE '1'.
             88 END-OUTPUT   VALUE '2'.
       1   STAT1             PIC X(2).
       1   STAT2             PIC X(2).
       PROCEDURE DIVISION.
       P1 SECTION.
       INITIAL-VALUES.
           MOVE ZERO TO DUMP-CODE WS-SWITCH STAT1 STAT2
           MOVE 1 TO CLEANUP-SW.
       S01-OPEN SECTION.
       OPEN-OUTPUT.
           OPEN OUTPUT SOUT1.
       SORT-RECORDS-CLOSE-GOBACK.
           SORT SFILE ON ASCENDING KEY SORT-S1-KEY
                WITH DUPLICATES IN ORDER
      *         USING IN1 GIVING OUT1.
                INPUT  PROCEDURE IS S02-IN
                OUTPUT PROCEDURE IS S03-OUT.
           IF SORT-RETURN NOT = 0
                DISPLAY 'SORT-RETURN = ' SORT-RETURN
                DISPLAY 'SORTIN FILE STATUS = ' STAT1
                DISPLAY 'SORTOUT FILE STATUS = ' STAT2
                MOVE SORT-RETURN TO DUMP-CODE
                CALL 'CEE3ABD' USING
                     BY REFERENCE DUMP-CODE
                     BY REFERENCE CLEANUP-SW
                END-CALL
            ELSE
              CLOSE SIN1 SOUT1
               GOBACK.
       S02-IN SECTION.
       IN-PROC.
           OPEN INPUT SIN1
           READ SIN1 AT END
                SET END-INPUT TO TRUE
           END-READ
           PERFORM UNTIL END-INPUT
               MOVE SORT-REC-FD1 TO SORT-SD
               RELEASE SORT-SD FROM SORT-REC-FD1
               READ SIN1 AT END
                    MOVE '1' TO WS-SWITCH
               END-READ
           END-PERFORM.
       S03-OUT SECTION.
       OUT-PROC.
               RETURN SFILE AT END
                      SET END-OUTPUT TO TRUE
               END-RETURN
           PERFORM UNTIL END-OUTPUT
               WRITE SORT-REC-FD2 FROM SORT-SD
               RETURN SFILE AT END
                      SET END-OUTPUT TO TRUE
               END-RETURN
           END-PERFORM.


#MFDS
#EnterpriseDeveloper

0 replies

Be the first to reply!