Function
The ASSIGN clause assigns an external device to a file of the COBOL program. One ASSIGN clause is required for each file in the program.
Format 1 for sequential file organization
ASSIGN { TO { PRINTER [literal-1] | implementor-name-1 | literal-2 }...
| USING data-name-1 }
Format 2 for relative and indexed file organization
ASSIGN {TO literal-1... | USING data-name-1}
Format 3 for sort files
ASSIGN TO {implementor-name-1 | literal}
Syntax rules
The following applies only to sequentially organized files:
PRINTER specified without literal-1 refers to the logical system file SYSLST.
PRINTER literal-1 refers to a print file.
In both cases, the compiler reserves the feed control character, which is not accessible to the user.
implementor-name-1 refers to devices which are named and assigned as follows:
Device name Assigned system file PRINTER01 - PRINTER99 SYSLST01 - SYSLST99 SYSIPT SYSIPT SYSOPT SYSOPT Files assigned by means of PRINTER or implementor-name-1 must not be external files.
The following applies for sequential, relative and indexed file organization:literal-1, literal-2 must be alphanumeric literals and may not be figurative constants. dataname-1 must be alphanumeric.
literal-1, literal-2 or the content of data-name-1 specify the line name for the file.
When a literal is specified, the link name is formed from the first 8 characters. These must be unique within the program. If the last character of the link name thus formed is a hyphen (-), then it is replaced by a # character.
data-name-1 must not be qualified.
data-name-1 must be defined as an alphanumeric data item in the WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION or LINKAGE SECTION.
The following applies to sort files:implementor-name is DISC
literal is SORTWK.
General rules
The type of file organization must be specified in the ORGANIZATION clause (see section "ORGANIZATION clause").
Only the first entry in the ASSIGN clause is evaluated; all other entries are ignored (PRINTER literal-1 is regarded as one entry).
If the ASSIGN clause refers to an external file, the ASSIGN clause must be used in the same form in all programs that describe this external file. The contents of the literal or data-name may, however, be different.