Understanding Converted Data

The PeopleTools COBOL Unicode conversion utility for z/OS reads COBOL sources under the source directory, analyzes their structures and statements, and applies a set of conversion rules to each statement.

The utility converts copybooks on the fly: the first time that a copybook is referenced inside data division or procedure division of any program, it is processed immediately. The utility processes an entire set of COBOL modules in a single run. It maintains a record of what it has converted to avoid converting copybooks twice.

The utility assumes that the COBOL programs are using PeopleSoft-standard COBOL program naming conventions, including that program sources are named “??P?????.cbl” and copybook sources are named “??C?????.cbl” The convention ? means any single character.

Note: The PeopleTools COBOL Unicode conversion utility for z/OS is designed to process an entire set of COBOL modules, including all programs and copybooks. The utility processes the COBOL COPY statement and checks for the existence of a copybook called from the program. If a copybook called from a program cannot be found in the source directory, the conversion process stops with an error, since the content of the copybook may affect the conversion result of the calling program.

All data field declarations with usage DISPLAY are converted to usage NATIONAL.

  • A PIC X field is converted to a PIC N field.

  • A string literal in the context of PIC N field is prefixed with N symbol.

  • A PIC 9 field whose usage is DISPLAY is added USAGE NATIONAL clause to make its usage NATIONAL.

  • A group that all of its members can be converted to usage NATIONAL is added GROUP USAGE NATIONAL clause to make the group NATIONAL item.

Example 1: PIC X Field Converted to PIC N and String Literal Prefixed with N Symbol

The following example shows the PIC X field converted to PIC N. In addition the prefix N is added to the VALUE clause.

02  RECNAME-TBLB            PIC X(9)    VALUE 'APPL_TBLB'

Is converted to:

02  RECNAME-TBLB            PIC N(9)    VALUE N'APPL_TBLB'

Example 2: Usage NATIONAL clause added to PIC 9 Field

The following example shows the Usage NATIONAL clause added to the PIC 9 field.

02  CURR-COUNT              PIC 9(4)

Is converted to:

02  CURR-COUNT              PIC 9(4) USAGE NATIONAL

Example 3: GROUP-USAGE NATIONAL Clause Added to Group W-LIT

The utility adds the GROUP-USAGE NATIONAL clause to the group W-LIT, because all the members of the group can be converted to the national data type. W-CALC-FIELDS is not added GROUP-USAGE NATIONAL because it includes item that cannot be converted to national data type. Packed decimal, binary, pointer items are not converted to national type, and groups including these data types are not added GROUP-USAGE NATIONAL.

01  W-LIT GROUP-USAGE NATIONAL .
02  PROGRAM-NAME            PIC N(8)    VALUE N'PTPDEC31'.
02  JOBID                   PIC N(10)   VALUE N'PTPDEC31'.
02  DESCR                   PIC N(16)   VALUE
N'TEST DEC31'.
01  W-CALC-FIELDS.
02  INIT-CHAR-DEF           PIC N(10).
02  COMP-REDEF-OF-CHAR REDEFINES INIT-CHAR-DEF
PIC S9(8) COMP.

There are a few exceptions to the data division rules to make the program compile and work correctly. For the utility to recognize these exceptional cases, strict adherence to the PeopleSoft COBOL coding standards is required. The utility looks for certain code-style patterns to make these decisions.

This section discusses the following areas where there are exceptions to data division rules:

  • SQL buffer setup area.

  • SQL buffer data area.

  • File status field.

  • FD entry in file section.

SQL Buffer Setup Area

For the interface to PTPSQLRT a COBOL program passes a SELECT list (SELECT-DATA) and a descriptor area (SELECT-SETUP). The program also passes similar data and setup areas for bind variables. The descriptors that are passed are always character-type data with embedded values that signal the actual data type and length of the data fields.

Because PTPSQLRT is designed to process the descriptors as alphanumeric character arrays (instead of national character arrays), the conversion utility does not convert the data type of the descriptor fields. However, it doubles the size of the descriptor field that is representing character-type data. Each data field in the descriptor area has associated field in SELECT-DATA or BIND-DATA field, and the byte size of the corresponding field in –DATA area doubles because of the change from PIC X to PIC N. Because of this implicit field size expansion, the corresponding field in –SETUP area should be doubled in size. Example: The following BIND-SETUP area is converted to match with BIND-DATA in byte size. Character fields are converted to double of the original size, to match with the size of the field in BIND-DATA area. Numeric and delimiter (‘Z’) items are not converted.

05  BIND-SETUP.
10  FILLER              PIC X(22)   VALUE ALL 'C'.
10  FILLER              PIC X(8)    VALUE ALL 'H'.
10  FILLER              PIC X(02)   VALUE ALL 'S'.
10  FILLER              PIC X(01)   VALUE 'Z'.

05  BIND-DATA.
10  EMPLID              PIC N(11).
10  ACAD-CAREER         PIC N(04).
10  STDNT-CAR-NBR-REAL  PIC S9(04)              COMP.
10  FILLER              PIC N(01)   VALUE N'Z'.

SQL Buffer Data Area

In the SQL buffer data area the conversion utility does not convert character data that is redefining numeric data. By convention in PeopleSoft application COBOL programs, this type of redefinition is used only for the purpose of using one data area for different number of variables. This type of character field can be in PIC X type that the conversion utility will not change the data type to PIC N.Example: PAGE-NO-FILLER, which is redefining binary field and in SQL buffer data area, is not converted to PIC N.02 BIND-DATA.

03  COMPANY             PIC N(10).
03  PAYGROUP            PIC N(10).
03  PAY-END-DT          PIC N(10).
03  OFF-CYCLE           PIC N.
03  PAGE-NO             PIC 9999                COMP.
03  PAGE-NO-FILLER REDEFINES PAGE-NO
                        PIC XX.
03  FILLER              PIC N       VALUE N'Z'.

File Status Field

The conversion utility does not convert a file status field (that includes “FILE-STAT” in name), because file status field (specified in FILE STATUS clause of FILE-CONTROL paragraph) must have the form of two-character alphanumeric or numeric item. It cannot be two-character national item.

Example: FILE-STAT-CTLFILE is not converted because it is file status field.

INPUT-OUTPUT SECTION.

FILE-CONTROL.

     SELECT CTLFILE  ASSIGN TO UT-S-CTLFILE
     FILE STATUS IS FILE-STAT-CTLFILE.


DATA DIVISION.




WORKING-STORAGE SECTION.

01  PROGRAM-IDENTITY       PIC N(8)    VALUE N'PTPCTL'.
01  FILE-STAT-CTLFILE      PIC XX      VALUE '00'.
01  MORE-INPUT             PIC N(1)    VALUE SPACES.

FD Entry in File Section

A line containing the RECORD CONTAINS clause in the FD data field will be commented out. If this line is not commented out, the program may cause an error at compile time because the record field is normally converted to a PIC N field and the record size will not match with the size specified in RECORD CONTAINS clause.

Note: This conversion eliminates compile errors. To read and write files either in Unicode or in EBCDIC, you may need to further modify the program manually to guarantee the correct file operation.

Example: Line containing “RECORD CONTAINS” clause is commented out in FD field declaration.

FD  TESTFILE
*   RECORD CONTAINS 80 CHARACTERS
     RECORDING MODE IS F
     LABEL RECORDS OMITTED.
01   TESTFILE-RECORD              PIC N(80).

In procedure division, the COBOL Unicode conversion utility for z/OS applies the following conversion rules to ensure that the correct operations on data fields convert to usage NATIONAL. These conversion rules are based on statement type.

Statement(s)

Conversion Rule Description

  • ADD

  • DIVIDE

  • EVALUATE

  • WHEN

  • ENTRY

  • IF

  • INITIALIZE

  • INSPECT

  • INVOKE

  • MULTIPLY

  • PERFORM

  • SEARCH

  • SET

  • STOP

  • STRING

  • SUBTRACT

  • UNSTRING

  • EXEC

Add “N” in front of every literal in the context of these statements.

DISPLAY

Surround each national data item in its context with FUNCTION DISPLAY-OF(), so that EBCIDIC data is printed on the log. If the data item is national numeric item (PIC 9 USAGE NATIONAL), add FUNCTION DISPLAY-OF() and reference modification to the item.

  • CALL

  • CANCEL

Add FUNCTION DISPLAY-OF() if the first parameter is NATIONAL data field.

COMPUTE

Add FUNCTION DISPLAY-OF() to the parameter of FUNCTION NUMVAL().

Example 1: Prefix “N” Added to Literals in the Context of STRING Statements

IBM Enterprise COBOL compiler complains if both national and non-national items are contained in the context of some statements, including STRING, UNSTRING, and INSPECT. Since SQL-STMT of ICST-DYSQL is a national character field, the statement cannot be compiled unless we add “N” prefix to the literals.

STRING
     N'%ROUND(TLP_COST,2), ' DELIMITED BY SIZEN'%ROUND(LLP_COST,2), ' DELIMITED BY SIZE
     INTO SQL-STMT OF ICST-DYSQL
     WITH POINTER SQL-STMT-LEN OF ICST-DYSQL
     ON OVERFLOW PERFORM ZS000-STRING-ERROR
END-STRING

Example 2: Insert DISPLAY-OF() Intrinsic Function Around National Data Items

The conversion utility inserts DISPLAY-OF() intrinsic function around national data items in the context of DISPLAY statements, so that the data is converted to EBCDIC.

The DISPLAY-OF() function only accepts the PIC N parameter. To convert the PIC 9 USAGE NATIONAL item to non-Unicode using the DISPLAY-OF() function, you must add a reference modification (in the following example (1:)) to the PIC 9 USAGE NATIONAL ITEM, so that the item is first converted to a PIC N item.

DISPLAY 'RUNID= ' FUNCTION DISPLAY-OF(RUNID OF KBDPR)
DISPLAY 'OPRID= '  FUNCTION DISPLAY-OF(OPRIDX OF KBDPR)
DISPLAY 'RUNID OF SQLRT=' FUNCTION DISPLAY-OF(BATCH-RUN-ID OF SQLRT)
DISPLAY 'PROCESS-INSTANCE = ' FUNCTION
DISPLAY-OF(PROCESS-INSTANCE OF KBDPR(1:))

Example 3: Add FUNCTION DISPLAY-OF() if the First Parameter is National Data Field

If the first parameter of a CALL statement, which specifies the called subprogram, is a national data item, the conversion utility adds the DISPLAY-OF() function to the parameter, because the national data item cannot be used for the CALL parameter.

CALL FUNCTION DISPLAY-OF(COBOL-PROG OF W-WK) USING SQLRT
                                         LOGMS
                                         BMSET
                                         DYSQL
                                         SPARM
                                         SBIND
                                         SCACH
                                         ECURS

Example 4: Add FUNCTION DISPLAY-OF() to the Parameter of FUNCTION NUMVAL()

If the data field passed to function NUMVAL() is national data type, the conversion utility adds function DISPLAY-OF() to convert the data item to EBCDIC data, as NUMVAL() function cannot process national data.

COMPUTE W-COMPARE-GPA =
            FUNCTION NUMVAL ( FUNCTION DISPLAY-OF(W-CONDITION-DATA
))

The COBOL Unicode conversion utility ensures that edited lines do not go past the column 72. If the conversion would normally cause a line to exceed column 72, the utility inserts a line break before column 72 to make the long line into two separate lines.

The COBOL Unicode conversion utility for Microsoft Windows and Unix environments accepts various directives in the first six columns of COBOL code to that COBOL programs can use to tailor the conversion for specific code. The COBOL Unicode conversion utility for z/OS does not use any directive, therefore, the above rules applies to all the COBOL code.