Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

Implementor-name

Syntax rules

  1. implementor-name is a system-name and must be a name from the left column of the following table. Implementor-names and their meanings:

    Implementor-nameMeaning
    CONSOLESystem or main console or subconsole
    TERMINALThe user' s data display unit
    SYSIPTSystem logical input file
    PRINTER
    PRINTER01-PRINTER99
    System logical printer file
    SYSOPTSystem logical output file
    C01 to C08Skip to channel 1 through 8
    C10 to C11Skip to channel 10 or 11
    JV-job-variable-nameJob variable describing the link name of a job variable (see below)
    TSW-0 to TSW-31Task switches
    USW-0 to USW-31User switches
    COMPILER-INFOCompiler information
    CPU-TIME,
    PROCESS-INFO,
    TERMINAL-INFO
    DATE-ISO4
    Operating system information

    Table 8: Implementor-names and their meanings

  2. job-variable-name indicates a BS2000 job variable. It is a COBOL word of up to 7 characters and is used to form the link name *job-variable-name and for accessing the job variable (see Example 6-1)

General rules

  1. If implementor-name is a user or task switch, at least one condition-name must be associated with it. The status of the switches is described under "Condition-names", and can be interrogated by testing the condition-name (see the section "Switch-status condition").

    The status of a switch may be altered by using a format 3 SET statement (see section "SET statement").

  2. C01 through C08, C10 and C11 will not be supported in the next version of the COBOL2000 compiler.
    If C01 through C08, C10 or C11 is specified as implementor-name, the associated mnemonic-name may be used only in a WRITE statement with ADVANCING phrase.

     

Example 6-1

Use of job variables:

IDENTIFICATION DIVISION.
PROGRAM-ID. JVTEST.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    JV-JV1 IS JOB-VAR-1.
    ...
PROCEDURE DIVISION.
    ...
    DISPLAY "xyz" UPON JOB-VAR-1.

Prior to the program call:

/SET-JV-LINK LINK-NAME=*JV1,JV-NAME=JV1TEST