VMS Help  —  COBOL  PROCEDURE_DIVISION, miscellaneous_topics

1  –  arithmetic-expressions

  An arithmetic expression can be one of the following:

    1)  An identifier (including function-identifier)
        of a numeric elementary item
    2)  A numeric literal
    3)  Two or more of the above choices separated by arithmetic
        operators (+, -, *, /, **)
    4)  Two or more arithmetic expressions separated by an arithmetic
        operator (+, -, *, /, **)
    5)  An arithmetic expression enclosed in parentheses

  A unary operator (a sign) can precede any arithmetic expression.

  The identifiers and literals in an arithmetic expression must represent
  either: (1) numeric elementary items (including functions),
  or (2) numeric literals on which arithmetic can be performed.

2  –  conditional_expressions

  A conditional expression specifies a condition the program must
  evaluate to determine the path of program flow.

2.1  –  abbreviated

  When you combine simple or negated simple conditions in a consecutive
  sequence, you can abbreviate any of the relation conditions except
  the first.  You can do this by either:

    1)  Omitting the subject of the relation condition
    2)  Omitting both the subject and the relational operator of the
        condition

  A relation condition in the consecutive sequence must contain a
  subject (or subject and relational operator) that is common with the
  preceding relation condition.  There must be no parentheses in the
  consecutive sequence.

  Format -

  relation-condition { { AND } [NOT] [relational-operator] object } ...
                     { { OR  }                                    }

2.2  –  class

  The class condition tests whether the contents of an operand are
  numeric or alphabetic.  It also determines if an alphabetic operand
  contains only uppercase or only lowercase characters or if the
  operand is a class-name.

  Format -

                           { NUMERIC          }
   identifier-1 IS [ NOT ] { ALPHABETIC       }
                           { ALPHABETIC-LOWER }
                           { ALPHABETIC-UPPER }
                           { class-name       }

2.2.1  –  identifier-1

  Identifier-1 must reference a data item whose usage is explicitly
  or implicitly DISPLAY. If identifier-1 is a function-identifier,
  it must reference an alphanumeric function.

2.2.2  –  class-name

  is the user-defined word for a class. It always possesses the
  global attribute

2.3  –  combined_and_negated_combined

  A combined condition results from connecting conditions with one of
  the logical operators AND or OR.

  Format -

   condition { { AND } condition } ...
             { { OR  }           }

  condition
    can be
      1)  A simple condition
      2)  A negated simple condition
      3)  A combined condition
      4)  A negated combined condition
      5)  Valid combinations of the preceding conditions

2.4  –  condition-name

  The condition-name condition determines if a data item contains a
  value assigned to one of that item's condition-names.  The term
  conditional variable refers to the data item.  Condition-name refers
  to a level 88 entry associated with that item.

  Format -

   condition-name

2.5  –  database_key_condition

  Database conditions allow alternate paths of control depending on the
  truth value of a test involving conditions peculiar to the database
  environment.  The database conditions are the tenancy, member, and
  database key conditions.

  The database key condition determines whether: (1) two database key
  values identify the same database record, (2) a database key value
  is null, or (3) a database key value is identical to any database
  key value in a keeplist.

  Format -

                           { ALSO database-key    }
   database-key IS [ NOT ] { NULL                 }
                           { WITHIN keeplist-name }

  database-key
   references a currency indicator or a keeplist entry in the
   Sub-Schema Section.

2.6  –  member_database_condition

  Database conditions allow alternate paths of control depending on the
  truth value of a test involving conditions peculiar to the database
  environment.  The database conditions are the tenancy, member, and
  database key conditions.

  The member condition determines whether member records are present
  in one or more sets.  Only member record types defined in the
  Sub-Schema Section are considered in determining the truth value of
  the condition.

  Format -

   [ set-name IS ]   [ NOT ]   EMPTY

  set-name is a subschema set name.

2.7  –  negated_simple

  The logical operator NOT negates a simple condition.  The truth value
  of a negated simple condition is the opposite of the simple
  condition's truth value.  Thus, the truth value of a negated simple
  condition is true only if the simple condition's truth value is
  false.  It is false only if the simple condition's truth value is
  true.

  Format -

   NOT simple-condition

2.8  –  relation

  A relation condition states a relation between two operands.  The
  program compares the operands to determine whether the stated
  relation is true or false.  The first operand is called the
  condition's subject.  The second operand is called its object.
  Either operand can be: (1) an identifier, (2) a literal, or (3) the
  value of an arithmetic expression.  The set of words that specifies
  the type of comparison is called the relational operator.

  Format -

                    {IS [NOT] GREATER THAN      }
                    {IS [NOT] >                 }
                    {IS [NOT] LESS THAN         }
  {identifier-1   } {IS [NOT] <                 } {identifier-2   }
  {literal-1      } {IS [NOT] EQUAL TO          } {literal-2      }
  {arith-express-1} {IS [NOT] =                 } {arith-express-2}
                    {IS GREATER THAN OR EQUAL TO}
                    {IS >=                      }
                    {IS LESS THAN OR EQUAL TO   }
                    {IS <=                      }

2.9  –  sign

  The sign condition determines if the algebraic value of an arithmetic
  expression is less than, greater than, or equal to zero.

  Format -

                                    { POSITIVE }
   arithmetic-expression IS [ NOT ] { NEGATIVE }
                                    { ZERO     }

2.10  –  success-failure

  This condition tests the return status codes of COBOL and non-COBOL
  procedures for success or failure conditions.

  Format -

   status-code-id IS { SUCCESS }
                     { FAILURE }

  status-code-id
   must be a word or longword COMP integer as represented by
   PIC S9(1 to 9) COMP.

2.11  –  switch-status

  The switch-status condition tests the "on" or "off" setting of an
  external logical program switch.

  Format -

   condition-name

2.12  –  tenancy_database_condition

  Database conditions allow alternate paths of control depending on the
  truth value of a test involving conditions peculiar to the database
  environment.  The database conditions are the tenancy, member, and
  database key conditions.

  The tenancy conditions determine whether a record in the database is
  an owner, or member, or a tenant in one or more sets.

  Format -

                        { OWNER  }
   [ NOT ] [ set-name ] { MEMBER }
                        { TENANT }

  set-name is a subschema set name.

3  –  database_key_identifiers

  Database key identifiers are in Record Selection Expressions.

  If a database exception condition occurs during the execution of a
  FETCH or FIND statement, the Database Control System (DBCS) places a
  database exception condition code in the special register
  DB-CONDITION.  This code identifies the condition.  The DBCS also
  places the record name of database-record in the special register
  DB-CURRENT-RECORD-NAME and its UID in DB-CURRENT-RECORD-ID.

  Format 1 - Currency Indicator Access

            [        { record-name } ]
    CURRENT [ WITHIN { set-name    } ]
            [        { realm-name  } ]

  Format 2 - Keeplist Access

    { OFFSET integer-exp }
    { FIRST              } WITHIN keeplist-name
    { LAST               }

4  –  declaratives

  Declaratives specify procedures to be executed only when certain
  conditions occur.  You must write declarative procedures at the
  beginning of the Procedure Division in consecutive sections.  The key
  word DECLARATIVES begins the declaratives part of the Procedure
  Division; the pair of key words END DECLARATIVES ends it.  Each of
  these reserved word phrases must: (1) be on a line by itself, starting
  in Area A; and (2) be followed by a separator period.

  When you use declarative procedures, you must divide the remainder of
  the Procedure Division into sections.

  Format -

   [ DECLARATIVES.

   { section-name SECTION [ segment-number ] . declarative-sentence

   [ paragraph-name. [sentence] ... ] ... } ...

     END DECLARATIVES. ]

5  –  I-O status

  If a file description entry has a FILE STATUS clause, a value is placed
  in the two-character FILE STATUS data item during execution of a CLOSE,
  DELETE, OPEN, READ, REWRITE, START, UNLOCK, or WRITE statement.  Two
  "keys" combine to form this value.  Status Key 1 occupies the leftmost
  character position in the item and Status Key 2 occupies the rightmost
  position.  In combination, the keys indicate the status of the
  input-output operation.

6  –  identifiers

  In Procedure Division rules, the term identifier means the
  complete specification of a data item. The term refers to
  all words required to make your reference to the item
  unique.  To reference a data item that is a function, a
  function-identifier is used.

  Format 1 -

   data-name [qualification] [subscripting] [reference modification]

  Format 2 -

   data-name [qualification] [indexing] [reference modification]

  Format 3 -

   FUNCTION function-name [ ({argument}...) ] [reference modification]

7  –  functions

  A function (synonymous with intrinsic function) is a temporary data
  item that represents a value to be determined at the time the
  function is referenced during the execution of a statement.  The
  value can be alphanumeric, numeric, or integer.

  A function-identifier is a syntactically correct combination of
  character strings and separators that uniquely references the data
  item resulting from the evaluation of a function.   Functions are
  treated as elementary data items, but cannot be  receiving operands. A
  function-identifier that references an alphanumeric function can be
  specified wherever an identifier is permitted and where a reference to
  a function is not specifically prohibited by general-format rules. An
  integer or numeric function can be used anywhere an arithmetic
  expression can be used, subject to certain restrictions.

  The general format of a function-identifier is as follows:

  FUNCTION function-name [({argument}... )] [reference-modifier]

  A function-name is one of the names listed below. Most function-names
  are key words but not reserved words (the exceptions are LENGTH,
  RANDOM, and SUM, which are reserved words, as is FUNCTION), and  can
  be used in a program outside the context of a function.

  An argument is an identifier (including a function-identifier),  a
  literal an arithmetic expression, or a table that complies with the
  specific rules governing the number, class, and category of arguments
  for the function.   The arguments in an argument list may be separated
  by a comma; they are evaluated individually, from left to right.

  A reference-modifier can be specified only for alphanumeric functions.
  It specifies the beginning character position and optionally the
  length of the resulting data item.

  The functions are listed below.  For a complete description of the
  functions, including their formats, see the chapter on Intrinsic
  Functions in the COBOL Reference Manual.

  ACOS               LENGTH         ORD-MIN*
  ANNUITY            LOG            PRESENT-VALUE*
  ARGCOUNT           LOG10          RANDOM
  ASIN               LOWER-CASE     RANGE*
  ATAN               MAX*           REM
  CHAR               MEAN*          REVERSE
  COS                MEDIAN*        SIN
  CURRENT-DATE       MIDRANGE*      SQRT
  DATE-OF-INTEGER    MIN*           STANDARD-DEVIATION*
  DAY-OF-INTEGER     MOD            SUM*
  FACTORIAL          NUMVAL         TAN
  INTEGER            NUMVAL-C       UPPER-CASE
  INTEGER-OF-DATE    ORD            VARIANCE*
  INTEGER-OF-DAY     ORD-MAX*       WHEN-COMPILED
  INTEGER-PART

  *Functions which permit a variable number of arguments which may
  include occurring items subscripted by "ALL" for one or more of
  its dimensions.

  In addition, five new Y2K functions are documented in the release notes:

  YEAR-TO-YYYY
  DATE-TO-YYYYMMDD
  DAY-TO-YYYYDDD
  TEST-DATE-YYYYMMDD
  TEST-DAY-YYYYMMDD

8  –  indexing

  Indexing is a special subscripting procedure.  In indexing, you use the
  INDEXED BY phrase of the OCCURS clause to assign an index-name to each
  table level.  You then refer to a table element using the index-name as
  a subscript.

  Format -

   { data-name      } ( { , index-name [ { + } literal-2 ] }     )
   { condition-name } ( {              [ { - }           ] } ... )
                      ( { , literal-1                      }     )

9  –  phrases

9.1  –  AT_END

  The AT END phrase specifies the action your program takes when the AT
  END condition occurs.

  Format -

   AT END stment

9.2  –  AT_END-OF-PAGE

  The AT END-OF-PAGE phrase specifies the action your program takes
  when the AT END-OF-PAGE condition occurs.

  Format -

   AT END-OF-PAGE stment

9.3  –  CORRESPONDING

  The CORRESPONDING option allows you to specify group items as
  operands in order to use their corresponding subordinate items in an
  operation.

9.4  –  FROM

  Format 1 -

   record-name FROM identifier

  Format 2 -

   FROM { keeplist-name } ...

  Keeplist-name refers to a user-defined keeplist in the Sub-Schema
  Section.

  Record-name and identifier must not refer to the same storage area.

  After statement execution ends, the data in the area referenced by
  identifier is available to the program.  The data is not available in
  the area referenced by record-name, unless there is an applicable
  SAME clause.

9.5  –  INTO

  The INTO phrase implicitly moves a current record from the record
  storage area into an identifier.

  Format -

   file-name INTO identifier

9.6  –  INVALID_KEY

  The INVALID KEY phrase specifies the action your program takes when
  an invalid key condition is detected for the file being processed.

  Format -

   INVALID KEY stment

9.7  –  NOT_AT_END

  The NOT AT END phrase specifies the action your program takes when
  the AT END condition does not occur.

  Format -

   NOT AT END stment

9.8  –  NOT_AT_END-OF-PAGE

  The NOT AT END-OF-PAGE phrase specifies the action your program takes
  when the AT END-OF-PAGE condition does not occur.

  Format -

   NOT AT END-OF-PAGE stment

9.9  –  NOT_INVALID_KEY

  The NOT INVALID KEY phrase specifies the action your program takes
  when an invalid key condition is not detected for the file being
  processed.

  Format -

   NOT INVALID KEY stment

9.10  –  NOT ON ERROR database

  The database on error exception condition occurs when the Database
  Control System (DBCS) encounters any database exception condition for
  any Data Manipulation Language (DML) statement.

  The NOT ON ERROR phrase in a DML statement allows the selection of an
  imperative statement sequence when any database exception condition
  does not occur.

  Format -

   NOT ON ERROR stment

9.11  –  NOT_ON_EXCEPTION

  The NOT ON EXCEPTION phrase allows execution of an imperative
  statement when an exception (or error) condition does not occur.

  Format -

   NOT ON EXCEPTION stment

9.12  –  NOT_ON_OVERFLOW

  The NOT ON OVERFLOW phrase allows you to specify an action for your
  program to take when an overflow condition does not exist.

  Format -

   NOT ON OVERFLOW stment

9.13  –  NOT_ON_SIZE_ERROR

  The NOT ON SIZE ERROR phrase allows you to specify an action for your
  program to take when a size error condition does not exist.

  Format -

   NOT ON SIZE ERROR stment

9.14  –  ON ERROR database

  The database on error exception condition occurs when the Database
  Control System (DBCS) encounters any database exception condition for
  any Data Manipulation Language (DML) statement.

  The ON ERROR phrase in a DML statement allows the selection of an
  imperative statement sequence when any database exception condition
  occurs.

  Format -

   ON ERROR stment

9.15  –  ON_EXCEPTION

  The ON EXCEPTION phrase allows execution of an imperative statement
  when an exception (or error) condition occurs.

  The ON EXCEPTION option of the CALL statement prevents control
  transfer of the CALL and triggers the execution of the imperative
  statement related to the CALL.

  The ON EXCEPTION option of the ACCEPT statement allows you to handle
  data entry errors when ACCEPTing into a numeric data field WITH
  CONVERSION.

  Format -

   ON EXCEPTION stment

9.16  –  ON_OVERFLOW

  The ON OVERFLOW phrase allows you to specify an action for your
  program to take when an overflow condition exists.

  Format -

   ON OVERFLOW stment

9.17  –  ON_SIZE_ERROR

  The ON SIZE ERROR phrase allows you to specify an action for your
  program to take when a size error condition exists.

  Format -

   ON SIZE ERROR stment

9.18  –  RETAINING

  The RETAINING clause specifies which currency indicators are not
  updated during the execution of the CONNECT, FETCH, FIND, MODIFY,
  RECONNECT, and STORE statements.

  Format -

   [           [ {|   REALM                  |} ]          ]
   [ RETAINING [ {|   RECORD                 |} ] CURRENCY ]
   [           [ {| { SET [ set-name ] ... } |} ]          ]
   [           [ {| { { set-name } ...     } |} ]          ]

  set-name is a subschema set name.

9.19  –  ROUNDED

  The rounding operation adds 1 to the absolute value of the low-order
  digit of the resultant identifier if the absolute value of the next
  least significant (lower-valued) digit of the intermediate data item
  is greater than or equal to 5.

  If you do not use the ROUNDED phrase, any excess low-order digits in
  the arithmetic result are truncated when the result is moved to the
  resultant identifier(s).

10  –  qualification

  A reference to a user-defined word is unique if:

    1)  no other name has the same spelling, including hyphenation,
    2)  it is a part of a REDEFINES clause (the reference following the
        word REDEFINES is unique because of clause placement), or
    3)  scoping rules make it unique.

  A name in a hierarchy of names can occur in more than one place in your
  program.  Unless you are redefining it, you must refer to this
  nonunique name using one or more higher-level names in the hierarchy.
  These higher-level names are called qualifiers.  Using them to achieve
  uniqueness of reference is called qualification.

  To make your reference unique, you need not specify all available
  qualifiers for a name, only the one(s) necessary to avoid ambiguity.

  You cannot use the same data-name as:

    1)  The name of an external record and as the name of any other
        external data item in any program contained within or containing
        the program describing the external data record.

    2)  The name of an item possessing the global attribute and as the
        name of any other data item in the program describing the global
        data item.

10.1  –  1format_file

  Format 1 -

                    { { { IN } data-name-2 } ... [ { IN } file-name ] }
  { data-name-1    }{ { { OF }             }     [ { OF }           ] }
  { condition-name }{    { IN } file-name                             }
                    {    { OF }                                       }

10.2  –  2format_paragraph

  Format 2 -

   paragraph-name { IN } section-name
                  { OF }

10.3  –  3format_text

  Format 3 -

   text-name { IN } library-name
             { OF }

10.4  –  4format LINAGE

  Format 4 -

   LINAGE-COUNTER { IN } file-name
                  { OF }

10.5  –  5format PAGE LINE

  Format 5 -

   { PAGE-COUNTER } { IN } report-name
   { LINE-COUNTER } { OF }

10.6  –  6format_report

  Format 6 -

               { { IN } data-name-4 [ { IN } report-name ] }
   data-name-3 { { OF }             [ { OF }             ] }
               {  { IN } report-name                       }
               {  { OF }                                   }

10.7  –  7format_screens

  Format 7 -

   screen-name-1 { { OF } screen-name-2 } ...
                 { { IN }               }

10.8  –  8format RMS

  Format 8 -

   { RMS-STS      } { IN } file-name
   { RMS-STV      } { OF }
   { RMS-FILENAME }

11  –  record_selection_expressions

  A record selection expression is used to select a record in the
  database.  It can be used in a FETCH or FIND statement.  The record
  thus selected becomes the current record of the run unit upon which
  subsequent statements may operate when accessing the database.

11.1  –  1format_database_key_identifier_access

  This format selects a record by a database key value held by the
  Database Control System (DBCS) in a currency indicator or a keeplist
  entry.

  Format 1 - Database Key Identifier Access

   database-key-identifier

11.1.1  –  database-key-identifier

  identifies a record according to the rules of Database Key
  Identifiers.

11.2  –  2format_set_owner_access

  This format selects the record that owns a set.

  Format 2 - Set Owner Access

   OWNER WITHIN set-name

11.2.1  –  set-name

  is a subschema set name.  The Database Control System (DBCS) uses
  the currency indicator for set-name to choose the owner record of
  that set occurrence.  A database exception condition occurs if
  set-name is a singular set (DB-CONDITION is set to DBM$_SINGTYP) or
  if the currency indicator for the set type is null (DB-CONDITION is
  set to DBM$_CSTYP_NULL).

11.3  –  3format_record_search_access

  This format selects a record by its position within a collection of
  records and optionally by its record type and contents.

  Format 3 - Record Search Access

  { FIRST                }
  { LAST                 }
  { NEXT                 }
  { PRIOR                }
  { ANY                  }
  { DUPLICATE            }
  { [ RELATIVE ] int-exp }

    [record-name] [ WITHIN { realm-name } ] [ USING { rec-key } ... ]
                  [        { set-name   } ] [ WHERE { bool-expres } ]

11.3.1  –  int-exp

  is an integer or arithmetic expression resulting in a longword
  integer value.  It cannot be zero.

11.3.2  –  realm-name

  is a subschema realm name.

11.3.3  –  record-name

  is a subschema record name.

11.3.4  –  set-name

  is a subschema set name.

11.3.5  –  rec-key

  is a key data item within the subschema record occurrence.  The
  same rec-key can appear only once in a given USING phrase.

11.3.6  –  bool-expres

  is a conditional expression that involves data items of the object
  record.  It is used to specify additional requirements of a
  qualifying record.

    bool-expres:
      { bool-alt [ OR bool-alt ] ... }
    bool-alt:
      { simp-bool-rel [ AND simp-bool-rel ] ... }
    simp-bool-rel:
      { bool-condit     }
      { NOT bool-expres }
    bool-condit:
      {          {         {[ NOT ] EQUAL TO          } }         }
      {          {         {[ NOT ] =                 } }         }
      {          {         {[ NOT ] LESS THAN         } }         }
      {          { IS      {[ NOT ] <                 } }         }
      {          {         {[ NOT ] GREATER THAN      } }         }
      {          {         {[ NOT ] >                 } }         }
      { { id  }  {         { GREATER THAN OR EQUAL TO } } { id  } }
      { { lit }  {         { >=                       } } { lit } }
      {          {         { LESS THAN OR EQUAL TO    } }         }
      {          {         { <=                       } }         }
      {          { DOES    {[ NOT ] CONTAIN           } }         }
      {          {         {[ NOT ] CONTAINS          } }         }
      {          {         {[ NOT ] MATCH             } }         }
      {          {         {[ NOT ] MATCHES           } }         }

11.3.6.1  –  bool-alt

  is one or more sub-expressions (simp-bool-rel).  Pairs of
  sub-expressions are joined by the logical operator AND.

11.3.6.2  –  simp-bool-rel

  is a simple-condition (bool-condit), an expression, or the
  negation of either.

11.3.6.3  –  bool-condit

  a simple-condition is a relation involving two operands joined by
  a relational operator.  At least one operand in each relation
  must be an item in the record being found or fetched.

11.4  –  4format_database_key_access

  This format selects the record that is referred to by the database
  key value contained in the special register DB-KEY.

  Format 4 - Database Key Access

    DBKEY

12  –  reference_modification

  Reference modification defines a subset of a data item by specifying
  its leftmost character and length.

  Format 1 -

   data-name ( leftmost-character-position : [ length ] )

  Format 2 -

   FUNCTION function-name [ ({argument}...) ]

      ( leftmost-character-position : [ length ] )

13  –  segmentation

  VSI COBOL programs execute in a virtual memory environment.  Therefore,
  programs need not manage physical memory by overlaying Procedure
  Division code.

  In VSI COBOL, segmentation controls the assignment of Procedure
  Division sections to fixed or independent segments.  The optional
  segment-number in the section header specifies the type of segment.

  Format -

   section-name SECTION [ segment-number ] .

13.1  –  section-name

  names a Procedure Division section.

13.2  –  segment-number

  must be an integer in the range 0 through 99.  If there is no
  segment-number in a section header, the implied segment-number is 0.

13.3  –  fixed_segments

  Fixed segments appear to reside in memory at all times.  A fixed
  segment is in its initial state the first time the program calls it.
  On later calls, the fixed segment is in its last-used state.

13.4  –  independent_segments

  The state of an independent segment depends on how and when it
  receives control.

14  –  subscripting

  Subscripts can appear only in references to individual elements in a
  list, or table, of like elements that do not have individual
  data-names.

  Format 1 -

   { data-name      } ( { arithmetic-expression } ... )
   { condition-name }

   Format 2 -

                 { ALL                            }
      argument ( { integer-1                      }
                 { data-name  [ {+|-} integer-2 ] } ... )
                 { index-name [ {+|-} integer-3 ] }

   In Format 2,  argument is  an  intrinsic function  argument  that is
   allowed to be repeated a variable number of times.  Note that Format
   1 may also be used for intrinsic function  arguments  when  ALL sub-
   scripts are not specified.  In Format 2,  when ALL is specified as a
   subscript, the effect is as if  each  table element  associated with
   that  subscript position were specified.
Close Help