Running the COBOL Conversion Utility

This section discusses the COBOL conversion utility.

As delivered, PeopleSoft COBOL programs are configured to run only on non-Unicode databases. To run the PeopleSoft-delivered COBOL on a Unicode database, it first must be converted by using the PeopleTools COBOL conversion utility. This utility is typically called automatically by the PeopleSoft installation process; however in certain circumstances, such as when you adapt COBOL code or apply a PeopleSoft-provided patch to a COBOL program, you may need to run the COBOL conversion utility manually.

Moving to a COBOL Unicode environment means that character data can potentially require three times the storage space that is required in a single-character environment. To allow for this, all internal data definitions for character-type data in COBOL programs must be expanded to allow for three times as many bytes.

Adapt and apply patches to only one set of COBOL source code—non-Unicode source. It is much easier to write COBOL programs without having to remember to triple the size of your working storage as you go. Once your adaptation or patch is complete and you are ready to compile the program, first run it through the COBOL conversion utility, then compile it. This approach has several benefits over customizing the converted code:

  • You maintain a single source tree for all of your COBOL—the non-Unicode source.

    This way you don’t run the risk of accidentally adapting both the non-Unicode COBOL programs and the Unicode-converted COBOL programs and potentially losing the modifications to the converted programs the next time you run the converter.

  • Although PeopleSoft developers test all delivered COBOL programs and patches in both Unicode and non-Unicode environments, only non-Unicode versions of the source are delivered.

    Therefore, any time you apply a PeopleSoft COBOL patch to a Unicode system, the patched source code must be run through the COBOL converter. If you had already modified the post-converted source, the reconversion would obliterate your modifications.

If the COBOL conversion utility makes modifications to your code that are undesirable, instead of modifying the postconverted code, the PeopleSoft system provides a series of directives to the utility that can tell it how specific lines of code should (or should not be) converted. This enables you to limit your changes only to the nonconverted code and to make the conversion completely automated.

In a non-Unicode (also known as ANSI) implementation, 1 character typically occupies one byte of storage. So for a 10-character field, you can define a PICTURE clause of PIC X(10). In a Unicode implementation, however, you must allow for the maximum number of storage bytes that are required for any character field. Therefore, in the Unicode environment, you must define this same 10-character field with a PICTURE clause of PIC X(30).

To accommodate the number of bytes in the UTF-8 encoding scheme, the PeopleSoft system provides a COBOL conversion utility to expand the character fields in the working storage.

Use the following command syntax to run the COBOL conversion utility:

PS_HOME\bin\client\winx86\pscblucvrt.exe  -s:Source_Directory -t:Destination_Directory  [-r:TEMP_Directory]

Command

Description

-s:Source_Directory

Specify the source directory where the non-Unicode version of COBOL resides. For the directory, you must specify where the COBOL subdirectories reside (\BASE, \WIN32, \Unix, and so on).

Example: -s:d:\PT8\SRC\CBL

-t:Destination_Directory

Specify where you want to place the expanded version of COBOL. The utility puts the modified source file in the same COBOL subdirectory in which it was found.

Example: -t:d:\PT8\SRC\CBLUNICODE

-r or -rd:Temp_directory

See Viewing Error Logs.

-r generates only the summary log file; -rd generates all of the log files.

The utility produces a new source file for each .CBL file that is found. These new files are placed in the PS_HOME\src\ directory.

As delivered, the PeopleSoft batch utilities that compile your COBOL programs include logic to convert all programs and copybooks before compiling. This logic is triggered only when the Unicode version of PeopleTools is installed.

Compiling COBOL in Microsoft Windows

Use the PS_HOME\setup\cbl2uni.bat command to convert all of the COBOL programs and copybooks that are found in the PS_HOME\src\cbl directory. After the conversion, PS_HOME\src\cbl Unicode contains the expanded COBOL source codes.

Compiling COBOL in Unix/Linux

Use the PS_HOME/install/pscbl.mak command to trigger the conversion before any COBOL programs are compiled. This utility stores all converted programs in the PS_HOME/src/cblunicode directory.

When the COBOL conversion utility runs, it places a comment at the beginning of each COBOL program that it converts:

This comment line identifies converted programs in two ways:

  • A person looking at the program can tell whether it has been converted.

  • If you attempt to convert the COBOL source file again, this comment line prevents the conversion utility program from expanding the working storage of this COBOL source file again.

For the utility to recognize when it is appropriate to expand data, strict adherence to the PeopleSoft COBOL coding standards is required. The utility looks for certain code-style patterns to make these decisions.

The conversion utility expands all PIC X[(N)] data fields to triple their original size, with the following exceptions:

  • Exception 1: SQL buffer setup data.

  • Exception 2: Redefined character fields.

  • Exception 3: Fields that appear to be dates.

  • Exception 4: Arrays comprising a single character.

The utility also converts copybooks on the fly: the first time that a copybook is referenced inside a code module, it is expanded 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.

Note: The COBOL conversion utility ensures that edited lines do not go past the 72nd column. If the conversion would normally cause a line to exceed that limitation, the utility removes some of the blank spaces between the field name and the PIC X string so that the line fits in the allowed area.

Exception 1: SQL Buffer Setup Data

SQL buffer setup data that refers to the numeric or date data types of SELECT-SETUP or BIND-SETUP is not expanded.

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 these descriptors represent the lengths of the associated data fields in the corresponding SELECT-DATA and BIND-DATA structures, the utility adjusts only the length of the descriptors that are representing character-type data.

Example 1: In the following code, the select list contains two character fields (EMPLID and NAME), a small integer (EMPL_RCD), and a date (EFFDT):

SELECT-SETUP.
02  FILLER   PIC X(60)   VALUE ALL 'C'.
02  FILLER   PIC X(2)   VALUE ALL 'S'.
02  FILLER   PIC X(10)   VALUE ALL 'D'.
02  FILLER   PIC X(90)   VALUE ALL 'C'.
SELECT-DATA.
02  EMPLID   PIC X(60).
02  EMPL_RCD   PIC 99   COMP.
02  EFFDT   PIC X(10).
02  NAME      PIC X(90).

In Unicode, the only fields that should be expanded are the two character fields (EMPLID and NAME). Numeric data is never affected by Unicode, and (according to the PeopleTools definition), dates are not affected either: they are treated as numeric strings and cannot have special characters.

Thus, the utility converts this code as follows:

SELECT-SETUP.
02  FILLER  PIC X(60)  VALUE ALL ‘C’.
02  FILLER  PIC X(2)  VALUE ALL ‘S’.
02  FILLER  PIC X(10)  VALUE ALL ‘D’.
02  FILLER  PIC X(90)  VALUE ALL ‘C’.
 
SELECT-DATA.
02  EMPLID  PIC X(60).
02  EMPL_RCD  PIC 99  COMP.
02  EFFDT  PIC X(10).
02  NAME    PIC X(90).

Example 2: The following code represents non-Unicode COBOL (COBOL that has not yet been expanded):

01  I-ERRL.
           05  SQL-STMT            PIC X(18)   VALUE
                                               'INPXPROC_I_ERRL'.
           05  BIND-SETUP.
               10  FILLER          PIC X(10)   VALUE ALL 'C'.
               10  FILLER          PIC X(6)    VALUE '0PPPPP'.
               10  FILLER          PIC X(4)    VALUE ALL 'I'.
               10  FILLER          PIC X       VALUE 'H'.
               10  FILLER          PIC X(18)   VALUE ALL 'C'.
               10  FILLER          PIC X(4)    VALUE ALL 'I'.
               10  FILLER          PIC X(4)    VALUE ALL 'N'.
               10  FILLER          PIC X(30)   VALUE ALL 'H'.
               10  FILLER          PIC X(30)   VALUE ALL 'C'.
               10  FILLER          PIC X(30)   VALUE ALL 'H'.
               10  FILLER          PIC X(10)   VALUE ALL 'C'.
               10  FILLER          PIC X(6)    VALUE '0PPPPP'.
               10  FILLER          PIC X(8)    VALUE '0PPPPPPP'.
               10  FILLER          PIC X       VALUE 'Z'.
           05  BIND-DATA.
               10  TSE-JOBID       PIC X(10)   VALUE SPACES.
               10  TSE-PROC-INSTANCE PIC 9(10) VALUE ZERO  COMP-3.
               10  TSE-SET-NBR     PIC 9(6)    VALUE ZERO  COMP.
               10  TSE-EDIT-TYPE   PIC X       VALUE SPACE.
               10  TSE-FIELDNAME   PIC X(18)   VALUE SPACES.
               10  MESSAGE-SET-NBR PIC 9(5)    VALUE ZERO  COMP.
               10  MESSAGE-NBR     PIC 9(5)    VALUE ZERO  COMP.
               10  MESSAGE-PARM    PIC X(30)   VALUE SPACES.
               10  MESSAGE-PARM2   PIC X(30)   VALUE SPACES.
               10  MESSAGE-PARM3   PIC X(30)   VALUE SPACES.
               10  BUSINESS-UNIT   PIC X(10)   VALUE SPACES.
               10  TRANSACTION-NBR PIC 9(10)   VALUE ZERO  COMP-3.
               10  SEQ-NBR         PIC 9(15)   VALUE ZERO  COMP-3.
               10  FILLER          PIC X       VALUE 'Z'.

The utility converts this code as follows:

01  I-ERRL.
           05  SQL-STMT            PIC X(54)   VALUE
                                               'INPXPROC_I_ERRL'.
           05  BIND-SETUP.
               10  FILLER          PIC X(30)   VALUE ALL 'C'.
               10  FILLER          PIC X(6)    VALUE '0PPPPP'.
               10  FILLER          PIC X(4)    VALUE ALL 'I'.
               10  FILLER          PIC X(3)   VALUE  ALL 'H'.
               10  FILLER          PIC X(54)   VALUE ALL 'C'.
               10  FILLER          PIC X(4)    VALUE ALL 'I'.
               10  FILLER          PIC X(4)    VALUE ALL 'N'.
               10  FILLER          PIC X(90)   VALUE ALL 'H'.
               10  FILLER          PIC X(90)   VALUE ALL 'C'.
               10  FILLER          PIC X(90)   VALUE ALL 'H'.
               10  FILLER          PIC X(30)   VALUE ALL 'C'.
               10  FILLER          PIC X(6)    VALUE '0PPPPP'.
               10  FILLER          PIC X(8)    VALUE '0PPPPPPP'.
               10  FILLER          PIC X       VALUE 'Z'.
           05  BIND-DATA.
               10  TSE-JOBID       PIC X(30)   VALUE SPACES.
               10  TSE-PROC-INSTANCE PIC 9(10) VALUE ZERO  COMP-3.
               10  TSE-SET-NBR     PIC 9(6)    VALUE ZERO  COMP.
               10  TSE-EDIT-TYPE   PIC X(3)    VALUE SPACES.
               10  TSE-FIELDNAME   PIC X(54)   VALUE SPACES.
               10  MESSAGE-SET-NBR PIC 9(5)    VALUE ZERO  COMP.
               10  MESSAGE-NBR     PIC 9(5)    VALUE ZERO  COMP.
               10  MESSAGE-PARM    PIC X(90)   VALUE SPACES.
               10  MESSAGE-PARM2   PIC X(90)   VALUE SPACES.
               10  MESSAGE-PARM3   PIC X(90)   VALUE SPACES.
               10  BUSINESS-UNIT   PIC X(30)   VALUE SPACES.
               10  TRANSACTION-NBR PIC 9(10)   VALUE ZERO  COMP-3.
               10  SEQ-NBR         PIC 9(15)   VALUE ZERO  COMP-3.
               10  FILLER          PIC X       VALUE 'Z'.

Exception 2: Redefined Character Fields

Character fields that are redefined to a numeric field (and group-level fields that contain such character fields) are not expanded. In instances where the redefined field is also redefined as a character field, the original character field and the redefinition that is a character field are expanded.

Example 1: In this example, the DB-PIC-PRECIS-CHAR is not expanded:

07  DB-PIC-PRECIS-CHAR  PIC X(2).
07  DB-PIC-PRECIS-NUM   REDEFINES
     DB-PIC-PRECIS-CHAR PIC 9(2).

Example 2: In this example, the I-REMIT-ADDR-SEQ is not expanded:

02  I-REMIT-ADDR-SEQ        PIC 9(04).
02  I-REMIT-ADDR-SEQ-C REDEFINES
    I-REMIT-ADDR-SEQ        PIC X(04).

Example 3: In this example, the original definition is a character-type field. Although some of the redefined fields are numeric fields, all of the character fields, including the original definition, are expanded.

02  MSGDATA1                PIC X(30)   VALUE SPACES.
02  FILLER       REDEFINES MSGDATA1.
    03  MSGDATA1-INT        PIC Z(9)9-.
    03  INT-FILL1           PIC X(19).
02  FILLER       REDEFINES MSGDATA1.
    03  MSGDATA1-DOL        PIC Z(9)9.99-.
    03  DOL-FILL1           PIC X(16).
02  FILLER       REDEFINES MSGDATA1.
    03  MSGDATA1-DEC        PIC Z(9)9.9(5)-.
    03  DEC-FILL1           PIC X(13).

Exception 3: Fields That Appear to Be Dates

Fields and group-level fields that appear to be dates are not expanded, unless the EXPAND directive is specified for this field or group-level field.

The following table describes the criteria that are used to determine fields or group-level fields as dates:

DATE Data Type

Field or Group-Level Field Name

Field Length or Total Length of a Group-Level Field*

Date

Contains -DT or DATE

10

Time

Contains -TM or TIME

15

Date-Time

Contains -DTTM, DATE, or TIME

26

* When calculating the total length, the utility considers that a group-level field may contain REDEFINE fields. The length of the REDEFINE field is not included when determining the total length of the group field.

Example 1: The field in this example is not expanded:

10  START-DATE          PIC X(10)   VALUE SPACES.

Example 2: The fields in this example are not expanded:

02  W-EMP-BIRTHDATE.
03 YEAR             PIC 9(4).
03 FILLER           PIC X(1).
03 MONTH            PIC 99.
03 FILLER           PIC X(1).
03 DAYS             PIC 99.

Example 3: The fields in this example are not expanded:

03  PAY-DATE-TIME.
04  PAY-DTTM-DATE   PIC X(10).
04  PAY-DTTM-DELIM1 PIC X         VALUE '-'.
04  PAY-DTTM-TIME   PIC X(15).

Example 4: The fields in this example are not expanded:

05  BEGIN-DTTM-TIME.
07  SYS-HOUR        PIC 99      VALUE ZERO.
07  FILLER          PIC X       VALUE SPACE.
07  SYS-MINUTE      PIC 99      VALUE ZERO.
07  FILLER          PIC X       VALUE SPACE.
07  SYS-SECOND      PIC 99      VALUE ZERO.
07  FILLER          PIC X       VALUE SPACE.
07  SYS-MICRO-SECOND  PIC 9(6)  VALUE ZERO.

Example 5: In this example, the group field contains REDEFINE fields. The conversion utility expands the fields because the group field meets the criteria for expansion: it has a total length of 10 and the field name includes the -DT string.

02  END-DT.
03  END-DT-YY           PIC X(4).
03  END-DT-YY-NUM       REDEFINES END-DT-YY
PIC 9999.
03  FILLER              PIC X.
03  END-DT-MM           PIC XX.
03  END-DT-MM-NUM       REDEFINES END-DT-MM
PIC 99.
03  FILLER              PIC X.
03  END-DT-DD           PIC XX.
03  END-DT-DD-NUM       REDEFINES END-DT-DD
PIC 99.

Exception 4: Arrays Comprising a Single Character

For arrays that comprise a single character, the PIC clause is expanded for character data, but the OCCURS clause is not expanded. However, if the data name ends with -POS, -CHAR, or -BYTE, the OCCURS clause is expanded, instead of the element size.

Example 1: In this example, the field is expanded:

  01  CHAR-ARRAY  PIC X    OCCURS 80 TIMES.
    Is expanded to:
  01  CHAR-ARRAY  PIC X(3)  OCCURS 80 TIMES.

Example 2: In this example, the data name ends with -POS; therefore, the OCCURS clause is expanded, instead of the element size:

  01  CHAR-POS  PIC X    OCCURS 80 TIMES.
    Is expanded to:
  01  CHAR-POS  PIC X    OCCURS 240 TIMES.

The COBOL conversion utility accepts various directives in the first six columns of COBOL code. Use these directives to override the utility’s normal mode of processing for a single source code line or for a block of lines.

Directive

Description

Purpose

NOCBGN

No conversion: begin

Starting with this line, do not perform expansions.

NOCEND

No conversion: end

End the NOCBGN directive following this line (the directive line is not expanded).

NOCLN

No conversion: line

Do not perform expansions in this single line.

COCCUR

Convert occurrence

Expand the OCCURS clause instead of the PIC clause in this line.

EXPEOF

Expand end of field

Expand a group item by increasing the length of the last field in the group.

EXPAND

Instruct utility to expand field

Force expansion of fields that would normally not be expanded because they appear to be date, time, or datetime fields.

The following examples use existing PeopleSoft COBOL programs to illustrate possible uses for the utility directives.

NOCBGN, NOCEND, and NOCLN Directives

One of the COBOL programs for PeopleSoft Human Resources has a unique way of setting the PAY-PERIODS group field. The program defines an 88-level definition based on the concatenated value of the five, one-column, character-type fields. If the conversion utility were to convert the program without the special directives, none of the cases that are defined in the 88-level field would ever be true.


               NOCBGN         03  PAY-PERIODS.
                   88  PAY-PERIODS-ALL             VALUE 'YYYYY'.
                   88  PAY-PERIODS-ALL-BIWEEKLY    VALUE 'YYYNN'.
                   88  PAY-PERIODS-ALL-SEMIMONTHLY VALUE 'YYNNN'.
                   88  PAY-PERIODS-NONE            VALUE 'NNNNN'.
                   04  PAY-PERIOD1     PIC X.
                   04  PAY-PERIOD2     PIC X.
                   04  PAY-PERIOD3     PIC X.
                   04  PAY-PERIOD4     PIC X.
                   04  PAY-PERIOD5     PIC X.
               03  FILLER REDEFINES PAY-PERIODS.
                   04  PAY-PERIOD      PIC X       OCCURS 5.
                       88  PAY-PERIOD-YES          VALUE 'Y'.
NOCEND                   88  PAY-PERIOD-NO           VALUE 'N'.
       01  S-DEDPDS.
           02  SQL-STMT                PIC X(18)   VALUE
                                                   'PSPDCFSA_S_DEDPDS'.
           02  BIND-SETUP.
               03  FILLER              PIC X(10)   VALUE ALL 'C'.
               03  FILLER              PIC X(10)   VALUE ALL 'H'.
               03  FILLER              PIC X(10)   VALUE ALL 'D'.
               03  FILLER              PIC X(10)   VALUE ALL 'A'.
NOCBGN                  03  FILLER              PIC X       VALUE ALL 'C'.
               03  FILLER              PIC X       VALUE ALL 'H'.
               03  FILLER              PIC X       VALUE ALL 'C'.
               03  FILLER              PIC X       VALUE ALL 'H'.
NOCEND                  03  FILLER              PIC X       VALUE ALL 'C'.
               03  FILLER              PIC X       VALUE 'Z'.
           02  BIND-DATA.
               03  COMPANY             PIC X(10).
               03  PAYGROUP            PIC X(10).
               03  PAY-END-DT          PIC X(10).
               03  YEAR-END-DT         PIC X(10).
NOCLN                   03  PAY-PERIODS         PIC X(5).
               03  FILLER              PIC X       VALUE 'Z'.

COCCUR Directive

The conversion utility doesn't normally expand the size of the array in this line from one of the PeopleTools COBOL programs. Using the COCCUR directive ensures that the OCCURS clause is expanded:

    02  PARM.
COCCUR      05  PARM-CH             OCCURS 30 TIMES
                          PIC X.

EXPEOF Directive

In the following example, the FIELDNAME group-level field is broken down to check the first 4 characters of the string. In this instance, it makes more sense to adjust the length of the FILLER field. By using the EXPEOF directive, you direct the utility to expand the FILLER field to a length of 50:


               EXPEOF   02  FIELDNAME.
    03  FIELDNAME4          PIC X(4)    VALUE SPACE.
    88  FIELDNAME-TSE               VALUE 'TSE_'.
    03  FILLER              PIC X(14)   VALUE SPACE.

The COBOL conversion utility produces a set of error and warning logs with messages that identify nonstandard code styles and inconsistencies. The utility also logs expansion actions that may require manual review.

The utility produces the following logs:

Field or Control

Definition

Exception log

This log contains warnings that occurred because of ambiguous working storage definitions. You may need to modify code or add utility directives to resolve the issues logged.

Exception BIND/SELECT log

This log contains warnings and errors that occurred because of ambiguous BIND and SETUP definitions.

Exception date log

This log lists all group-level date fields that are detected by the utility.

Summary log

This log provides general statistics regarding the number of programs that are processed.

When you specify the -4 flag, you see only the summary log. Set the -rd flag on the conversion utility command line if you want the utility to produce all of the detail logs: exception, BIND/SELECT, and exception date.

Messages from the Exception Log

The following tables summarize all of the messages that can appear in the three exception log files. Errors indicate problems that are encountered by the conversion utility.

Message

Type

Note

Non-matching conversion block found in line line number.

Error

Detected the NOCBGN directive, but couldn’t find the corresponding NOCEND.

Error in determining numeric length in line line number.

Error

Couldn’t decipher the numeric PICTURE clause.

The size of the one character array will be expanded in line line number.

Warning

Detected a one-character array where the field contains the string -BYTE, -POS, or -CHAR.

A one-character array is found in line number. The conversion routine will expand this to PIC X(3).

Warning

None.

Unable to find the copy library copy library name.

Error

Couldn't locate the copy library file that the program references.

Messages from the Exception BIND/SELECT Log

The following table lists messages from the BIND/SELECT log:

Message

Type

Note

Didn't find the corresponding DATA section for DATA field name in line line number.

Error

Detected either a BIND-DATA or a SELECT-DATA, but cannot find the SETUP group field.

No delimiter found on group field name section in line line number.

Warning

Didn’t find a FILLER field with a value Z in a DATA or SETUP group field.

Unable to convert the group field name section due to problems reading the Copylib.

Error

Couldn't locate a copy library that DATA or SETUP references.

The group field name found in line line number has a mismatch count.

Warning and error

The number of columns in DATA doesn’t match the count for the corresponding SETUP.

Incompatible date type match for field in lineline number.

Error

The data type definition in SETUP doesn’t correspond to the data type in DATA.

Messages from the Exception Date Log

The following table lists messages from the exception date log:

Message

Type

Note

Date/time/datetime detected and will not be expanded in line.

Warning

None.

Verify if a date/time/datetime field in line number: line number.

Warning

Found a character-type field or group field with a total length of 10, 15, or 26 that could be a date, time, or datetime.