Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

COBOL words

A word consists of 1-30 characters from the following set:

A-Z, a-z, 0-9, - (hyphen)

No distinction is made between uppercase and lowercase letters.

A word may neither begin nor end with a hyphen, must not contain space characters, and must contain at least one letter.

Words are divided into four categories:

  • user-defined words

  • system-names

  • reserved words

  • function-names

1. User-defined words

A user-defined word is a COBOL word to be supplied by the programmer according to the format for a clause or statement. It refers to particular units of data at object time. The following subsections describe the types of user-defined words employed in COBOL programs, and state the rules for writing these names.

The 17 types of user-defined words are listed and defined in table 4.

All user-defined words except segment-numbers and level-numbers must be made unique. Either there must be no other user-defined word in the compilation unit with the same sequence of characters and punctuation marks, or the word must be qualified.

With the exception of paragraph-name, section-name, level-number, and segment-number, all user-defined words must contain at least one alphabetic character. Segment-numbers or level-numbers may be identical to other segment-numbers or level-numbers, or to paragraph-names and section-names.

alphabet-name

An alphabetical name located in the SPECIAL-NAMES paragraph of the Environment Division and connected with a character set and/or collating sequence.

class-name
(object-oriented)

A user-defined word that identifies a class.

class-name

A name entered by the user in the CLASS clause of the SPECIAL-NAMES paragraph in the Environment Division to define a character set. This classname can be referenced in the class condition.

condition-name

The name assigned to a specific value, set of values, or range of values which an elementary data item may assume (hence, a condition of the data item). A condition-name is defined by an 88-level entry in the FILE SECTION, LINKAGE SECTION , WORKING-STORAGE SECTION or LOCAL-STORAGE SECTION.

data-name
 

A name identifying a data item in the Data Division. A data-name is defined by its appearance in a data description entry.

file-name

A name assigned to a set of input data or output data.
A file-name is defined by its appearance in the SELECT clause of the FILE CONTROL paragraph and its use as the name of an FD entry.
A special file-name is a sort-file-name that names a sort-file. A sort-file-name is defined by its appearance in the SELECT clause of the FILE CONTROL paragraph and its use to name an SD entry in the FILE SECTION.

index-name

A name of an index for a particular table. An index name is declared by its occurrence in the INDEXED BY phrase of the OCCURS clause.

interface-name

A user-defined word that identifies an interface.

level-number

A level-number indicates the position of a data item in the hierarchical structure of a record or indicates special properties of a data description entry.
Level-numbers are defined by their appearance in a data description entry.

library-name

A name of an entry in the COBOL compilation unit library, which may contain more than one text with various names.

method-name

A user-defined word that identifies a method. The method name is defined by its use in the METHOD-ID paragraph of the Identification Division.

mnemonic-name

A fixed name, provided the programmer associated it with a particular implementor-name in the SPECIAL-NAMES paragraph of the Environment Division.

paragraph-name

A paragraph-name is used to name a paragraph in the Procedure Division.
Paragraph-names are written starting at Area A.

parameter-name

A parameter-name identifies a formal parameter of a parameterized class or of a parameterized interface.

program-name

The name used to identify the program. The program-name is defined by its use in the PROGRAM-ID paragraph of the Identification Division. It may also appear in a CALL statement of a corresponding calling program.

program-proto-type-name

A user-defined word that identifies a program prototype.

record-name

The name of a record. A record is declared by a 01-level entry in the FILE SECTION, LINKAGE SECTION, WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION or in the SUB-SCHEMA SECTION.

report-name

The name of a report. A report-name is defined by its occurrence in the REPORT clause of an FD entry; it is used to name an RD entry in the REPORT SECTION.

section-name

A section-name is used to name a section in the Procedure Division. A section-name is written starting at Area A and is followed by the word SECTION.

segment-number

A number to classify sections in the Procedure Division for purposes of segmentation. It is defined by its use in a section header.

symbolic-character

A name for a figurative constant defined by the user character in the SYMBOLIC-CHARACTERS clause of the SPECIAL-NAMES paragraph.

text-name

Name of an entry in the COBOL compilation unit library.
The entry is copied from the library by the COPY statement.

type-name

A user-defined name to identify a type which is described in a data description entry of the DATA DIVISION.

Table 4: COBOL user-defined words

2. System-names

A system-name is a COBOL word which is used as an interface with the operating system environment. System-names are defined by the implementor and may vary from compiler to compiler. From the programmer’s point of view, the system-names of a specific compiler are treated as reserved words.

The system names for COBOL2000 are:

Computer-name

in the SOURCE-COMPUTER and OBJECT-COMPUTER paragraphs.

Implementor-name

in the SPECIAL-NAMES paragraph and the ASSIGN clause.

Call-convention

in the CALL-CONVENTION directive.

3. Reserved words

COBOL includes a fixed number of reserved words, the COBOL words.

A reserved word serves a specific purpose and must be used only in the context specified in the formats; it must not occur in the compilation unit as a user-defined word or system-name.

A complete list of reserved words is supplied on the pages below. All reserved words marked with an asterisk (*) in this list are treated as reserved words only if DML (Data Manipulation Language) statements are being used for compilation; otherwise they may be employed as user-defined words. Compilation with DML statements occurs when

SUB-SCHEMA SECTION

is specified in the Data Division of a program (see the "UDS/SQL Reference Manual" [6]).

There are three types of reserved words:

  • Required words

  • Optional words

  • Special purpose words


  • Required words

    A required word is a word whose presence is required when the format in which the word appears is used in a compilation unit.

    Required words are of two types:

    Keywords

    Within each format, such words are uppercase and underlined. Keywords are only allowed in the formats indicated. Keywords may be grouped as shown below:

    • Verbs such as ADD, READ and CALL.

    • Required words which are encountered in statement and entry formats.

    • Words which have a specific functional significance, such as NEGATIVE, SECTION, etc.

    Some keywords may be abbreviated (e.g. PIC for PICTURE).

    Special character words

    These are the arithmetic operators and relation characters (see section "Glossary").

  • Optional words

    Within each format, uppercase words which are not underscored are called "optional words". These words may be used at the option of the user. The presence or omission of an optional word has no effect on the meaning of the COBOL statement. However, an optional word must not be misspelled or replaced with another word.

  • Special purpose words

    There are two types of special purpose words:

    • special registers

    • figurative constants

    Special registers

    Special registers are data items in which information produced with the use of certain COBOL features is stored. The attributes of these registers are predefined, and each register has a fixed name. Thus, the programmer does not have to define these registers in the Data Division. The eleven special registers are listed in table 5.

Register name

Description

Use

TALLY

5-digit unsigned data item with COMPUTATIONAL phrase (see section "USAGE clause")

TALLY may be used wherever a data item with an integral value can occur. For example, if the current value of TALLY is 3, the following statements are equivalent:
ADD 3 TO ALPHA.
ADD TALLY TO ALPHA.

LINE-COUNTER
PAGE-COUNTER
PRINT-SWITCH
CBL-CTR

Used by the Report Writer (see chapter "Report Writer").

See section "Special registers of the Report Writer".

LINAGE-COUNTER

A 4-byte data item containing an unsigned integer whose value is less than or equal to integer-1 or the data item referenced by dataname-1 in the LINAGE clause

A LINAGE-COUNTER register is generated by the compiler for each file whose file description entry contains a LINAGE-clause (see section "LINAGE clause").

RETURN-CODE

8-digit signed data item with COMPUTATIONAL and SYNCHRONIZED phrase (corresponds to PIC S9(8) COMP-5 SYNC).

This data item exists only once for each run unit. The user can use this item to exchange information between COBOL modules which were compiled separately but linked into a single object program. This item can also be used to store the return value of a non-COBOL subprogram. When a COBOL subprogram terminates, the contents of the item can be made available to the calling non-COBOL program as a function value. If the contents of the RETURN-CODE special register are not 0 after the execution of STOP RUN, the operating system is informed that the program terminated abnormally.

SORT-RETURN
SORT-FILE-SIZE
SORT-CORE-SIZE
SORT-MODE-SIZE
SORT-EOW
SORT-CCSN

Used by the sort section (see section "Sorting records".

See section "Special registers for files: SORT".

XML-EVENT
XML-CODE
XML-TEXT
XML-NTEXT
XML-NAMESPACE
XML-NNAMESPACE
XML-NAMESPACE-PREFIX
XML-NNAMESPACE-PREFIX

Used by the XML part (see section "Language elements for processing XML").

See section "Special registers for the XML PARSE statement".

Table 5: COBOL special registers


Reserved words

The following table contains all the reserved words. All words marked with * are treated as reserved words only if DML (Data Manipulation Language) statements are being used for compilation; otherwise they may be employed as user-defined words. Compilation with DML statements occurs when SUB-SCHEMA SECTION is specified.

A ’#’ before the word means that this word is not treated as a reserved word if ENABLE-KEYWORDS = *COBOL85 is set in the SOURCE-PROPERTIES option.

<
<=
+
*
**
-
/
>
>=
:
=
ACCEPT
ACCESS
#ACTIVE-CLASS
ADD
#ADDRESS
ADVANCING
AFTER
ALL
#ALLOCATE
ALPHABET
ALPHABETIC
ALPHABETIC-LOWER
ALPHABETIC-UPPER
ALPHANUMERIC
ALPHANUMERIC-EDITED
ALSO
ALTER
ALTERNATE
AND
ANY
#ANYCASE
ARE
AREA
AREAS
#AS
ASCENDING
ASSIGN
AT
AUTHOR

#B-AND
#B-NOT
#B-OR
#B-XOR
#BASED
BEFORE
BEGINNING
BINARY
#BINARY-CHAR
#BINARY-DOUBLE
#BINARY-LONG
#BINARY-SHORT
#BIT
BLANK
BLOCK
#BOOLEAN
BOTTOM
BY
BYTE-LENGTH

CALL
CANCEL
*CASE
CBL-CTR
CF
CH
CHARACTER
CHARACTERS
CHECKING
CLASS
#CLASS-ID
CLOCK-UNITS
CLOSE
CODE
CODE-SET
#COL
COLLATING
#COLS
COLUMN
#COLUMNS
COMMA
COMMIT
COMMON

COMMUNICATION
COMP
COMP-1
COMP-2
COMP-3
COMP-5
COMPUTATIONAL
COMPUTATIONAL-1
COMPUTATIONAL-2
COMPUTATIONAL-3
COMPUTATIONAL-5
COMPUTE
#CONDITION
CONFIGURATION
*CONNECT
#CONSTANT
CONTAINS
CONTENT
CONTINUE
CONTROL
CONTROLS
CONVERTING
COPY
CORR
CORRESPONDING
COUNT
CREATING
#CRT
CURRENCY
*CURRENT
#CURSOR

DATA
#DATA-POINTER
*DATABASE-EXCEPTION
DATABASE-KEY
DATABASE-KEY-LONG
DATE
DATE-COMPILED
DATE-WRITTEN
DAY
DAY-OF-WEEK
*DB

DE
DEBUG-CONTENTS

DEBUG-ITEM
DEBUG-LINE
DEBUG-NAME
DEBUG-SUB-1
DEBUG-SUB-2
DEBUG-SUB-3
DEBUGGING
DECIMAL-POINT
DECLARATIVES
#DEFAULT
DELETE
DELIMITED
DELIMITER
DEPENDING
DESCENDING
DETAIL
DISABLE
DISC
*DISCONNECT
DISPLAY
DIVIDE
DIVISION
#DOCUMENT
DOWN
*DUPLICATE
DUPLICATES
DYNAMIC

EBCDIC
#EC
ELSE
*EMPTY
ENABLE
END
END-ACCEPT
END-ADD
END-CALL
END-COMPUTE
END-DELETE
END-DISPLAY
END-DIVIDE

END-EVALUATE
END-IF
#END-INVOKE
END-MULTIPLY
END-OF-PAGE
#END-OPEN
END-PERFORM
END-READ
END-RECEIVE
END-RETURN
END-REWRITE
END-SEARCH
END-START
END-STRING
END-SUBTRACT
END-UNSTRING
END-WRITE
#END-XML
ENDING
ENTRY
ENVIRONMENT
#EO
EOP
EQUAL
ERASE
ERROR
*ESCAPE
EVALUATE
EVERY
EXCEPTION
#EXCEPTION-OBJECT
*EXCLUSIVE
EXIT
EXTEND
EXTENDED
EXTERNAL

#FACTORY
FALSE
FD
*FETCH
FILE
FILE-CONTROL
FILLER
FINAL
*FIND
*FINISH

FIRST
#FLOAT-EXTENDED
#FLOAT-LONG
#FLOAT-SHORT
FOOTING
FOR
#FORMAT
FREE
FROM
FUNCTION
#FUNCTION-ID

GENERATE
GET
GIVING
GLOBAL
GO
GOBACK
GREATER
GROUP
#GROUP-USAGE

HEADING
HIGH-VALUE
HIGH-VALUES

I-O
I-O-CONTROL
ID
IDENTIFICATION
#IDENTIFIED
IF
IGNORING
IN
*INCLUDING
INDEX
INDEXED
INDICATE
#INHERITS
INITIAL
INITIALIZE
INITIATE
INPUT
INPUT-OUTPUT
INSPECT
INSTALLATION
#INTERFACE

#INTERFACE-ID
INTO
INVALID
#INVOKE
IS

JUST
JUSTIFIED

*KEEP
KEY

LABEL
LAST
LEADING
LEFT
LENGTH
LESS
LIMIT
*LIMITED
LIMITS
LINAGE
LINE
LINE-COUNTER
LINES
LINKAGE
#LOCAL-STORAGE
#LOCALE
LOCK
LOW-VALUE
LOW-VALUES

*MASK
*MATCHING
*MEMBER
*MEMBERS
*MEMBERSHIP
MEMORY
MERGE
MESSAGE
#METHOD
#METHOD-ID
#MINUS
MODE
*MODIFY
MODULES
MORE-LABELS

MOVE
MULTIPLE
MULTIPLY

#NATIONAL
#NATIONAL-EDITED
NATIVE
NEGATIVE
#NESTED
NEXT
NO
NOT
#NULL
NUMBER
NUMERIC
NUMERIC-EDITED

#OBJECT
OBJECT-COMPUTER
#OBJECT-REFERENCE
*OCCURENCE
OCCURS
OF
OFF
OMITTED
ON
OPEN
OPTIONAL
#OPTIONS
OR
ORDER
ORGANIZATION
OTHER
OUTPUT
OVERFLOW
#OVERRIDE
*OWNER

PACKED-DECIMAL
PADDING
PAGE
PAGE-COUNTER
PERFORM
*PERMANENT
PF
PH
PIC

PICTURE
PLUS
POINTER
POSITION
POSITIVE
#PRESENT
PRINT-SWITCH
PRINTING
*PRIOR
PROCEDURE
PROCEED
PROGRAM
PROGRAM-ID
#PROGRAM-POINTER
#PROPERTY
*PROTECTED
#PROTOTYPE
PURGE

QUOTE
QUOTES

#RAISE
#RAISING
RANDOM
RD
READ
*READY
*REALM
*REALM-NAME
RECEIVE
RECORD
RECORDING
RECORDS
REDEFINES
REEL
REFERENCE
RELATIVE
RELEASE
REMAINDER
REMOVAL
RENAMES
REPEATED
REPLACE
REPLACING
REPORT
REPORTING

REPORTS
#REPOSITORY
RERUN
RESERVE
RESET
*RESULT
#RESUME
*RETAINING
*RETRIEVAL
#RETRY
RETURN

#RETURNING
REVERSED
REWIND
REWRITE
RF
RH
RIGHT
ROLLBACK
ROUNDED
RUN

SAME
#SCREEN
SD
SEARCH
SECTION
SECURITY
SEGMENT-LIMIT
SELECT
*SELECTIVE
#SELF
SEND
SENTENCE
SEPARATE
SEQUENCE
SEQUENTIAL
SET
*SET-SELECTION
*SETS
#SHARING
SIGN
SIZE
SORT
SORT-MERGE
SORT-TAPE
SORT-TAPES

*SORTED
SOURCE
SOURCE-COMPUTER
#SOURCES
SPACE
SPACES
SPECIAL-NAMES
STANDARD
STANDARD-1
STANDARD-2
START
STATUS
STOP
*STORE
STRING
*SUB-SCHEMA
SUBTRACT
SUM
#SUPER
SUPPRESS
*SUPPRESSING
SYMBOLIC
SYNC
SYNCHRONIZED
*SYSTEM
#SYSTEM-DEFAULT

TABLE
TALLY
TALLYNG
TAPE
TAPES
*TENANT
TERMINAL
TERMINATE
TEST
THAN
THEN
THROUGH
THRU
TIME
TIMES
TO
TOP
TRAILING
TRUE
TRY

TYPE
#TYPEDEF

UNIT
UNITS
#UNIVERSAL
#UNLOCK
UNSTRING
UNTIL
UP
*UPDATE
UPON
USAGE
*USAGE-MODE
USE
#USER-DEFAULT
USING

#VAL-STATUS
#VALID
#VALIDATE
#VALIDATE-STATUS
VALUE
VALUES
VARYING
#VERSION-XML
*VIA

WHEN
WITH
*WITHIN
WORDS
WORKING-STORAGE
WRITE

#XML

ZERO
ZEROES
ZEROS

Reserved words for compiler directives

ALL
AND
AS

B-AND
B-NOT
B-OR
B-XOR
BYTE-LENGTH

CALL-CONVENTION
CHECKING
COBOL

DE-EDITING
DEFINE
DEFINED
DIVIDE

ELSE
END-IF
END-EVALUATE
EQUAL
EVALUATE

FIXED
FLAG-85
FLAG-NATIVE-ARITHMETIC
FORMAT
FREE
FUNCTION-ARGUMENT

GREATER

IF
IMP
IS

LEAP-SECOND
LESS
LISTING
LOCATION

MOVE

NOT
NUMVAL

OFF
ON
OR
OTHER
OVERRIDE

PAGE
PARAMETER
PROPAGATE

SET
SIZE
SOURCE

THAN
THROUGH
THRU
TO
TRUE
TURN

WHEN

ZERO-LENGTH

In addition, all the exception condition names from table 45 in section "Exception conditions and exception statuses" are reserved words for compiler directives.

 

Context-sensitive words

ALIGNED
ARITHMETIC
ATTRIBUTE
AUTO
AUTOMATIC

BACKGROUND-COLOR
BELL
BLINK

CENTER
CHECK
CLASSIFICATION
CYCLE

DISCARD
DTD

ELEMENT
ENTRY-CONVENTION
EOL
EOS
EXPANDS

FOREGROUND-COLOR
FOREVER
FULL

HIGHLIGHT

IMPLEMENTS
INITIALIZED
INTRINSIC

LINAGE-COUNTER
LOCALIZE
LOWLIGHT

MANUAL

NAMESPACE
NONE
NORMAL
NUMBERS

ONLY

PARAGRAPH
PARSE
PREVIOUS
PROCESSING
RAW
RECURSIVE
RELATION
REQUIRED
RETURN-CODE
REVERSE-VIDEO

SCHEMA
SECONDS
SECURE
SIGNED
SORT-CCSN
SORT-CORE-SIZE
SORT-EOW
SORT-FILE-SIZE
SORT-MODE-SIZE
SORT-RETURN
STACK
STATEMENT
STEP
STRONG
SYMBOL

UCS-2
UCS-4
UNDERLINE
UNSIGNED
UTF-16
UTF-8

VALIDITY

YYYYDDD
YYYYMMDD

4. Function-names

A function-name is a word that is one of a specified list of words which may be used in a COBOL program. The same word, in a different context, may appear in a program as a user-defined word (see section "General").

5. Exception-situation-names

An exception-situation-name is a COBOL word which identifies an exception condition (see table 45 in section "Exception conditions and exception statuses" ).

In other contexts these words can be used as user-defined names.