Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Assignment to compiler variables to control source text manipulation

Compiler directives allow the COBOL programmer to control the manipulation of the source text.

The following compiler directives are available:

  • DEFINE directive

  • EVALUATE directive

  • IF directive

The compiler directives are described in detail in the “COBOL2000 Reference Manual” [1].

The DEFINE directive allows the programmer to define compiler variables in the source program. It is also possible to use S variables to assign values to these compiler variables prior to compilation. To do this, the programmer must define the variables in the program with the suffix ASPARAMETER. Compiler variables are assigned to S variables via the variable name which must be formed as follows:

DEFINE directive

S variable

>>DEFINE variable AS PARAMETER

DECL-VAR SYSDIR-variable ...,SCOPE=*TASK

The S variables must be declared with SCOPE=*TASK.

If values are to be supplied externally to the compiler variables, two different types of S variable are available and these must be declared with the required TYPE:

  • numeric variables with TYPE=*INTEGER

  • alphanumeric variables with TYPE=*STRING

The two examples below demonstrate how compiler variables are used in BS2000/OSD. The use of compiler variables when the compiler is called under POSIX is described in subsection "Using compiler variables under POSIX" of section "Compiling".

Example 2-7

Passing a numeric value

IDENTIFICATION DIVISION.
PROGRAM-ID. PROG1
...
    >>DEFINE VLADIMIR AS PARAMETER. ——————————————————————————————— (1)
...

Assignment and linkage:

/DECLARE-VARIABLE SYSDIR-VLADIMIR(TYPE=*INTEGER),SCOPE=*TASK  ————— (2)
/SET-VARIABLE SYSDIR-VLADIMIR=1234 ———————————————————————————————— (3)

Call to compiler

(1)

The DEFINE directive specifies a compiler variable with a content which the COBOL compiler expects to find in an S variable.

(2)

The SDF-P command DECLARE-VARIABLE declares an S variable: VLADIMIR is the name of the numeric compiler variable in the source program. The associated S variable is declared as SYSDIR-VLADIMIR with TYPE=*INTEGER.

(3)

The SDF-P command SET-VARIABLE assigns the numeric value 1234 to the S variable SYSDIR-VLADIMIR.

Example 2-8

Passing an alphanumeric literal

IDENTIFICATION DIVISION.
PROGRAM-ID. PROG2
...
    >>DEFINE JERRY AS PARAMETER.——————————————————————————————————— (1)
...

Assignment and linkage:

/DECLARE-VARIABLE SYSDIR-JERRY (TYPE=*STRING),SCOPE=*TASK ————————— (2)
/SET-VARIABLE SYSDIR-JERRY='This is a string'—————————————————————— (3)

Call to compiler

(1)

The DEFINE directive specifies a compiler variable with a content which the COBOL compiler expects to find in an S variable.

(2)

The SDF-P command DECLARE-VARIABLE declares an S variable: JERRY is the name of the alphanumeric compiler variable in the source program. The associated S variable is declared as SYSDIR-JERRY with TYPE=*STRING.

(3)

The SDF-P command SET-VARIABLE assigns the alphanumeric value “This is a string” to the S variable SYSDIR-JERRY. The surrounding quotes do not form part of the literal.