Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

INITIALIZE statement

Function

The INITIALIZE statement enables selected data items to be supplied with specific values.

Format


INITIALIZE {identifier-1} ... [WITH FILLER]

[{ ALL | category-name...} TO VALUE  ]

THEN REPLACING {category-name DATA BY {identifier-2 | literal-1}}... ]

[THEN TO DEFAULT ]


category-name stands for:

{  ALPHABETIC
 | ALPHANUMERIC
 | ALPHANUMERIC-EDITED
 | DATA-POINTER
 | NATIONAL
 | NUMERIC
 | NUMERIC-EDITED
 | OBJECT-REFERENCE
 | PROGRAM-POINTER
}


Syntax rules

  1. identifier-1 is the receiving item of the INITIALIZE statement. literal-1 and identifier-2 are sending items.

  2. The following applies for the sending items:

    • If DATA-POINTER is named in the REPLACING phrase, identifier-2 must be a valid sending item of a SET statement whose receiving item belongs to the category "data pointer".

    • If PROGRAM-POINTER is named in the REPLACING phrase, identifier-2 must be a valid sending item of a SET statement whose receiving item belongs to the category "program pointer".

    • If OBJECT-REFERENCE is named in the REPLACING phrase, identifier-2 must be a valid sending item of a SET statement whose receiving item belongs to the category "object reference".

    • Any other data category specified in the REPLACING phrase must be permitted as a data category for a receiving item in a MOVE statement in which identifier-2 or literal-1 represent the sending field.

  3. Each data category may only be named once in the VALUE phrase and in the REPLACING phrase.

  4. The data description entry of identifier-1 or a data item subordinate to identifier-1 may not contain the DEPENDING phrase of the OCCURS clause.

  5. An index data item may not occur as the operand of an INITIALIZE statement.

  6. The data description entry of identifier-1 may not contain the RENAMES clause.

  7. If identifier-1 is a table element or if it contains tables, the VALUE phrases for the table elements are ignored. However, if the INITIALIZE statement contains REPLACING or DEFAULT phrases, these are effective instead.

General rules

  1. If identifier-1 is a national group, it is processed like a group. If identifier-2 is a national group, it is processed like an elementary item.

  2. The keywords in category-name correspond to the data categories (see "data categories" in section "Concept of computer-independent data description"). The word ALL in the VALUE phrase means the same as if every category from category-name had been specified.

  3. If more than one identifier-1 is specified, this has the same effect as if a separate INITIALIZE statement had been issued in the specified sequence for each identifier-1.
    If the exceptional condition EC-DATA-CONVERSION arises from one of these implicit INITIALIZE statements, the program run is stopped after a USE procedure which is exited with RESUME AT NEXT STATEMENT has been executed, and it is resumed at the next implicit INITIALIZE statement, if one is issued.

  4. Regardless of whether identifier-1 represents an elementary item or a group item, all move operations are performed as though a sequence of MOVE or SET statements had been specified, each of them with an elementary item as receiving item. The receiving item of these implicit statements are determined in rule 3, the sending items in rule 4.

    Initialization is performed as follows:

    • If the category is "data pointer", "program pointer" or "object reference", then identifier-2 acts as the sending item of an implicit SET statement whose receiving item in each case is an elementary receiving item that is subordinate to identifier-1.

    • If the category is not "data pointer", "program pointer" or "object reference", then identifier-2 or literal-1 acts as the sending item of an implicit MOVE statement whose receiving item in each case is an elementary receiving item that is subordinate to identifier-1.

  5. The receiving item in each implicit MOVE or SET statement is determined by the use of the following steps in the defined order:

    1. To determine the elementary receiving items the following elementary items are first of all excluded:

      1. Index data items.

      2. Data items that are subordinate to an identifier-1 and whose data description entry contains the REDEFINES clause, and data items that are subordinate to such an item.

      3. Data items that are subordinate to an identifier-1 and whose data description entry contains the RENAMES clause.

      4. Elementary FILLER data items if the WITH FILLER phrase is omitted.

      Note:
      The data description entry of identifier-1 itself, however, may contain the REDEFINES clause or be subordinate to a data item with a REDEFINES clause.

    2. An elementary item is a potential receiving item if:

      1. identifier-1 is an elementary item,

      2. or if it is subordinate to identifier-1. If the elementary item is a table element, it is a potential receiving item each time it occurs.

    3. In fact each potential receiving item is really a receiving field if at least one of the following conditions applies in this order:

      1. The INITIALIZE statement contains the VALUE phrase, the category of the elementary item is explicitly or implicitly contained in the VALUE phrase and one of the following conditions is satisfied:

        1. The category of the elementary item is "data pointer", "object reference" or "program pointer", or

        2. a VALUE clause (defined by format 1) is contained in the data description of the elementary item.

      2. The INITIALIZE statement contains the REPLACING phrase and the category of the elementary item is one of the categories from the REPLACING phrase, or

      3. the INITIALIZE statement contains the DEFAULT phrase, or

      4. The INITIALIZE statement contains neither the VALUE phrase nor the REPLACING phrase.

      The first condition which applies for an elementary item takes effect - the subsequent conditions are then no longer evaluated for this elementary item.

  6. The following rules apply when determining the elementary sending items:

    1. If the receiving item qualifies itself as a result of the VALUE phrase, the following applies:

      1. If the receiving item is of the category "data pointer" or "program pointer", the sending item is the predefined address NULL.

      2. If the receiving item is of the category "object reference", the sending item is the predefined object reference NULL.

      3. In all other cases the sending item is the literal which is specified in the VALUE clause in the definition of the receiving item (see the section "VALUE clause" format 1 or format 3).

    2. If the receiving item qualifies iteself as a result of the REPLACING phrase, the sending item is literal-1 or identifier-2 which are allocated to the category of the receiving item in the REPLACING phrarse.

    3. If neither rule a) nor rule b) apply for the receiving item, the value of the sending item depends on the category of the receiving item as shown in the table below:

      Category of the receiving itemSend operand
      alphabeticFigurative constant alphanumeric SPACES
      alphanumericFigurative constant alphanumeric SPACES
      alphanumeric-editedFigurative constant alphanumeric SPACES
      nationalFigurative constant national SPACES
      numericFigurative constant ZEROES
      numeric-editedFigurative constant ZEROES
      data-pointerPredefined address NULL
      program-pointerPredefined address NULL
      object-referencePredefined object reference NULL
  7. The elementary items represented by identifier-1 are initialized from left to right in the order in which they occur in the INITIALIZE statement. If identifier-1 is a group, the relevant elementary itemswithin this group are initialized in the order in which they were defined in the group.

  8. If identifier-1 and identifier-2 occupy the same storage space, the result of the execution of this statement will be undefined (see "Overlapping operands").

Example 8-46

IDENTIFICATION DIVISION.
PROGRAM-ID. INIT1.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  WAGE-RATE.
    02  SURNAME    PIC X(30).
    02  NAME       PIC X(30).
    02  ADDRESS    PIC X(30).
    02  DATE-OF-BIRTH.
        03  BDAY   PIC 99.
        03  MONTH  PIC 99.
        03  YEAR   PIC 99.
    02  HIRING-DATE.
        03  HDAY    PIC 99.
        03  MONTH   PIC 99.
        03  YEAR    PIC 99.
    02  NO-OF-HOURS   PIC 9(3).
    02  HOURLY-RATE   PIC 9(2)V99.
PROCEDURE DIVISION.
MAIN SECTION.
P1.
    INITIALIZE WAGE-RATE.
    DISPLAY WAGE-RATE UPON T.
    STOP RUN.

The statement INITIALIZE WAGE-RATE means:

MOVE SPACE TO SURNAME NAME ADDRESS
MOVE ZERO TO BDAY OF DATE-OF-BIRTH
             MONTH OF DATE-OF-BIRTH
             YEAR OF DATE-OF-BIRTH
             HDAY OF HIRING-DATE
             MONTH OF HIRING-DATE
             YEAR OF HIRING-DATE
             NO-OF-HOURS, HOURLY-RATE

Example 8-47

01 Data-structure. 
   02 alphaItem       PIC X(20). 
   02 numItem         PIC 9(15).
   02 pointerA        POINTER.
   02 FILLER          PIC 9(5).99.
INITIALIZE Data-structure FILLER
      REPLACING ALPHANUMERIC BY HIGH VALUE
                  NUMERIC BY 5
      DEFAULT

The statement INITIALIZE means:

MOVE HIGH-VALUE TO AlphaItem
MOVE 5 TO NumItem
SET PointerA TO NULL                (1)
MOVE ZERO TO <FILLER-data-item>     (2)

(1) Because of the “Default” specification

(2) Because of the FILLER specification and the “Default” specification

Example 8-48

01 Data-structure. 
   02 alphaitem      PIC X(20). 
   02 numItem        PIC 9(15) value 1860.
   02 pointerA       POINTER.
   02 FILLER         PIC 9(5).99.
   02 objref         OBJECT REFERENCE.
INITIALIZE Data-structure FILLER
     ALL TO VALUE
     REPLACING ALPHANUMERIC BY LOW-VALUE
                  NUMERIC BY 5
     DEFAULT.


The statement INITIALIZE means:

MOVE LOW-VALUE TO alphaitem
MOVE 1860 TO numItem               (1)
SET pointerA TO NULL               (2) 
MOVE ZERO TO <FILLER-data-item>    (3)
SET objref TO NULL                 (2)

(1)

Because of the VALUE phrase; 
the REPLACING phrase for NUMERIC is not used in this case

(2)

Because of the VALUE phrase

(3)

Because of the FILLER phrase and the DEFAULT phrase

Example 8-49

01 Data-structure. 
   02 alphaitem      PIC X(20). 
   02 numItem        PIC 9(15) value 1860. 
   02 pointerA       POINTER.
   02 FILLER         PIC 9(5).99.
   02 objref         OBJECT REFERENCE.
 
INITIALIZE Data-structure
     DATA-POINTER TO VALUE
     REPLACING ALPHANUMERIC BY HIGH-VALUE
           NUMERIC BY 5
     DEFAULT.


The statement INITIALIZE means:

MOVE HIGH-VALUE TO alphaitem
MOVE 5 TO numItem
SET pointerA TO NULL             (1)
SET objref TO NULL               (2)

(1)

Because of the VALUE phrase 

(2)

Because of the DEFAULT phrase

Example 8-50

01 PTR USAGE POINTER.
...
INITIALIZE PTR DATA-POINTER TO VALUE

 

is a more complicated way of writing:

SET PTR TO NULL.

Example 8-51

01 Datastructure VALUE "XXXX1234".
   02 alphaitem         PIC X(4). 
   02 numItem           PIC 9(4).
 
INITIALIZE Data-structure ALL TO VALUE DEFAULT


The statement INITIALIZE means:

MOVE SPACE TO alphaitem
MOVE ZERO TO numItem

The VALUE phrase in the INITIALIZE statement has no effect because the VALUE clause is specified at the group item level and not at the level of the elementary items.