Compaq COBOL
Reference Manual
Examples 
The examples assume these Data Division entries:
  
    
       
      
01  CUSTOMER-REC. 
    03  CUSTOMER-USPS-STATE  PIC XX. 
    03  CUSTOMER-REGION      PIC X. 
    03  CUSTOMER-NAME        PIC X(15). 
01  STATE-TAB. 
    03  FILLER  PIC X(153) 
          VALUE 
          "AK3AL5AR5AZ4CA4CO4CT1DC1DE1FL5GA5HI3 
-         "IA2ID3IL2IN2KS2KY5LA5MA1MD1ME1MI2MN2 
-         "MO5MS5MT3NC5ND3NE2NH1NJ1NM4NV4NY1OH2 
-         "OK4OR3PA1RI1SC5SD3TN5TX4UT4VA5VT1WA3 
-         "WI2WV5WY4". 
01  STATE-TABLE REDEFINES STATE-TAB. 
    03  STATES OCCURS 51 TIMES 
        ASCENDING KEY IS STATE-USPS-CODE 
        INDEXED BY STATE-INDEX. 
        05  STATE-USPS-CODE  PIC XX. 
        05  STATE-REGION     PIC X. 
01  STATE-NUM   PIC 99. 
01  STATE-ERROR PIC 9. 
01  NAME-TABLE VALUE SPACES. 
    03  NAME-ENTRY OCCURS 8 TIMES 
        INDEXED BY NAME-INDEX. 
        05  LAST-NAME    PIC X(15). 
        05  NAME-COUNT   PIC 999. 
 | 
  - Binary search: 
(The correctness of this statement's operation 
  depends on the ascending order of key values in the source table.)
  
    
       
      
INITIALIZE-SEARCH. 
    MOVE "NH" TO CUSTOMER-USPS-STATE. 
 
    SEARCH ALL STATES 
       AT END 
              MOVE 1 TO STATE-ERROR 
              GO TO SEARCH-END 
       WHEN STATE-USPS-CODE (STATE-INDEX) = CUSTOMER-USPS-STATE 
              MOVE 0 TO STATE-ERROR 
              MOVE STATE-REGION (STATE-INDEX) TO CUSTOMER-REGION. 
 
SEARCH-END. 
    DISPLAY " ". 
    DISPLAY "Customer State index number = " STATE-INDEX WITH CONVERSION 
     "   Region = " STATE-REGION (STATE-INDEX) 
     "   State Error Code = " STATE-ERROR. 
 | 
    
Following are the results of the binary search:
  
    
       
      
Customer State index number = 31   Region = 1   State Error Code = 0 
 
 | 
   - Serial search with WHEN phrase:
  
    
       
      
INITIALIZE-SEARCH. 
    MOVE "2" TO CUSTOMER-REGION. 
SEARCH-LOOP. 
    SEARCH STATES 
       AT END 
              MOVE 1 TO STATE-ERROR 
              GO TO SEARCH-END 
       WHEN STATE-REGION (STATE-INDEX) = CUSTOMER-REGION 
              MOVE 0 TO STATE-ERROR 
              DISPLAY STATE-USPS-CODE (STATE-INDEX) 
                  " " STATE-INDEX WITH CONVERSION 
                  " " STATE-ERROR. 
    SET STATE-INDEX UP BY 1. 
    GO TO SEARCH-LOOP. 
 
SEARCH-END. 
 | 
    
The following lists the results of this serial search:
  
    
       
      
IA 13 0 
IL 15 0 
IN 16 0 
KS 17 0 
MI 23 0 
MN 24 0 
NE 30 0 
OH 36 0 
WI 49 0 
 
 | 
  
 - Serial search with two WHEN phrases:
  
    
       
      
INITIALIZE-SEARCH. 
    MOVE 1 TO CUSTOMER-REGION. 
    MOVE "NH" TO CUSTOMER-USPS-STATE. 
 
    DISPLAY "States in customer's region:". 
 
SEARCH-LOOP. 
     SEARCH STATES 
        AT END 
                 GO TO SEARCH-END 
        WHEN STATE-USPS-CODE (STATE-INDEX) = CUSTOMER-USPS-STATE 
                 SET STATE-NUM TO STATE-INDEX 
        WHEN STATE-REGION (STATE-INDEX) = CUSTOMER-REGION 
                 DISPLAY STATE-USPS-CODE (STATE-INDEX) 
                         " " WITH NO ADVANCING. 
    SET STATE-INDEX UP BY 1. 
    GO TO SEARCH-LOOP. 
 
SEARCH-END. 
    DISPLAY " " 
    DISPLAY "Customer state index number = " STATE-NUM. 
 | 
    
The following lists the results of the serial search with two WHEN 
    phrases:
  
    
       
      
States in customer's region: 
CT DC DE MA MD ME NJ NY PA RI VT 
 
Customer state index number = 31 
 
 | 
   - Updating a table in a SEARCH statement:
  
    
       
      
GET-NAME. 
    DISPLAY "Enter name: " NO ADVANCING. 
    ACCEPT CUSTOMER-NAME. 
    SET NAME-INDEX TO 1. 
    SEARCH NAME-ENTRY 
      AT END 
        DISPLAY "   Table full" 
        SET NAME-INDEX TO 1 
        PERFORM SHOW-TABLE 8 TIMES 
        STOP RUN 
      WHEN LAST-NAME (NAME-INDEX) = CUSTOMER-NAME 
        ADD 1 TO NAME-COUNT (NAME-INDEX) 
      WHEN LAST-NAME (NAME-INDEX) = SPACES 
        MOVE CUSTOMER-NAME TO LAST-NAME (NAME-INDEX) 
        MOVE 1 TO NAME-COUNT (NAME-INDEX). 
    GO TO GET-NAME. 
SHOW-TABLE. 
    DISPLAY LAST-NAME (NAME-INDEX) " " NAME-COUNT (NAME-INDEX). 
    SET NAME-INDEX UP BY 1. 
 | 
    
The following lists the results of updating a table in a SEARCH 
    statement:
  
    Enter name: CRONKITE
    
Enter name: GEORGE
    
Enter name: PHARES
    
Enter name: CRONKITE
    
Enter name: BELL
    
Enter name: SMITH
    
Enter name: FRANKLIN
    
Enter name: HENRY
    
Enter name: GEORGE
    
Enter name: ROBBINS
    
Enter name: BELL
    
Enter name: FRANKLIN
    
Enter name: SMITH
    
Enter name: BELL
    
Enter name: SMITH
Table full
    
CRONKITE 002
    
GEORGE 002
    
PHARES 001
    
BELL 003
    
SMITH 003
    
FRANKLIN 002
    
HENRY 001
    
ROBBINS 001
  
 
6.8.32 SET
Function 
The SET statement sets values of indexes associated with table 
elements. It can also change the value of a conditional variable, 
change the status of an external switch, and store the address of a 
COBOL identifier reference at run time.
rsult
is an index-name, the identifier of an index data item, or an 
elementary numeric data item described as an integer.
val
is a positive integer, which can be signed. It can also be an 
index-name (or the identifier of an index data item) or an elementary 
numeric data item described as an integer.
indx
is an index-name.
increm
is an integer, which can be signed. It can also be the identifier of an 
elementary numeric data item described as an integer.
cond-name
is a condition-name that must be associated with a conditional variable.
switch-name
is the name of an external switch defined in the SPECIAL-NAMES 
paragraph.
pointer-id
is a data-name whose data description entry must contain the USAGE IS 
POINTER clause.
identifier
is a data item in the File, Working-Storage, Linkage, or Subschema 
Section.
status-code-id
is a word or longword integer data item represented by PIC S9(1) to 
S9(9) COMP or PIC 9(1) to 9(9) COMP.
Syntax Rule 
No two occurrences of cond-name can refer to the same 
conditional variable.
General Rules 
Formats 1 and 2 
  - Index-names are associated with a table in the table's OCCURS 
  clause INDEXED BY phrase.
  
 - If rsult is an index-name, its value after SET statement 
  execution must correspond to an occurrence number of an element in the 
  associated table.
  
 - If val is an index-name, its value before SET statement 
  execution must correspond to an occurrence number of an element in the 
  table associated with rsult.
  
 - The value of indx, both before and after SET statement 
  execution, must correspond to an occurrence number of an element in the 
  table associated with indx.
 
Format 1 
  - The SET statement sets the value of rsult to refer to the 
  table element whose occurrence number corresponds to the table element 
  referred to by val. If val is an index data item, no 
  conversion occurs.
  
 - If rsult is an index data item, val cannot be an 
  integer. No conversion occurs when rsult is set to the value 
  of val.
  
 - If rsult is not an index data item or an index-name, 
  val can only be an index-name.
  
 - When there is more than one rsult, SET uses the original 
  value of val in each operation. Subscript or index evaluation 
  for rsult occurs immediately before its value changes.
  
 - Table 6-18 shows the validity of operand combinations. An 
  asterisk (*) means that no conversion occurs during the SET operation.
 
  Table 6-18 Validity of Operand Combinations in Format 1 SET Statements
  
    | Sending Item  | 
    Receiving Item  | 
  
  
    |   | 
    Integer Data Item  | 
    Index  | 
    Index Data Item  | 
  
  
    | 
      Integer Literal
     | 
    
      Invalid/Rule 7
     | 
    
      Valid/Rule 5
     | 
    
      Invalid/Rule 6
     | 
  
  
    | 
      Integer Data Item
     | 
    
      Invalid/Rule 7
     | 
    
      Valid/Rule 5
     | 
    
      Invalid/Rule 6
     | 
  
  
    | 
      Index
     | 
    
      Valid/Rule 7
     | 
    
      Valid/Rule 5
     | 
    
      Valid/Rule 6*
     | 
  
  
    | 
      Index Data Item
     | 
    
      Invalid/Rule 7
     | 
    
      Valid/Rule 5*
     | 
    
      Valid/Rule 6*
     | 
  
Format 2 
  - The SET statement increments (UP) or decrements (DOWN) 
  indx by a value that corresponds to the number of occurrences 
  increm represents.
  
 - When there is more than one indx, SET uses the original 
  value of increm in each operation.
 
Format 3 
  - SET moves the literal in the VALUE clause for cond-name to 
  its associated conditional variable. The transfer occurs according to 
  the rules for elementary moves. If the VALUE clause contains more than 
  one literal, the first is moved.
 
Format 4 
  - SET changes the status of each switch-name in the 
  statement.
  
 - The ON phrase changes the status of switch-name to on.
  
 - The OFF phrase changes the status of switch-name to off.
  
 - The SET statement changes the switch status only for the image in 
  which it executes. When the image terminates, the status of each 
  external switch is the same as when the image began.
 
Format 5 
  - The address of identifier is evaluated and stored in 
  pointer-id.
 
Format 6 
  - Specifying the SUCCESS option sets status-code-id to the 
  SUCCESS state (the low-bit of status-code-id is set to 1).
  
 - Specifying the FAILURE option sets status-code-id to the 
  FAILURE state (the low-bit of status-code-id is set to 0).
 
Additional References 
Examples 
The examples assume these Environment and Data Division entries:
  
    
       
      
 SPECIAL-NAMES. 
    SWITCH 1 UPDATE-RUN ON STATUS IS DO-UPDATE 
    SWITCH 3 REPORT-RUN ON STATUS IS DO-REPORT 
        OFF STATUS IS SKIP-REPORT 
    SWITCH 4 IS NEW-YEAR ON STATUS IS BEGIN-YEAR 
        OFF IS CONTINUE-YEAR. 
DATA DIVISION. 
WORKING-STORAGE SECTION. 
01    YEAR-LEVEL            PIC 99. 
    88    FRESHMAN VALUE 1. 
    88    SOPHOMORE VALUE 2. 
    88    JUNIOR VALUE 3. 
    88    SENIOR VALUE 4. 
    88    FIRST-MASTERS VALUE 5. 
    88    MASTERS VALUE 5,6. 
    88    FIRST-DOCTORAL VALUE 7. 
    88    DOCTORAL VALUE 7,8. 
    88    NON-DEGREE-UNDERGRAD VALUE 9. 
    88    NON-DEGREE-GRAD VALUE 10. 
    88    UNDERGRAD VALUE 9, 1 THROUGH 4. 
    88    GRAD VALUE 10, 5 THROUGH 8. 
01    COURSES-AVAILABLE. 
    02    OCCURS 100 TIMES INDEXED BY COURSE-INDEX. 
        03    COURSE-NAME             PIC X(10). 
        03    COURSE-INSTRUCTOR       PIC X(20). 
        03    COURSE-LOCATION         PIC X(10). 
        03    COURSE-CODE             PIC 9(5). 
01    POINTER-VAL USAGE IS POINTER. 
01    THREE-DIMENSIONAL-TABLE. 
    02    X OCCURS 5 TIMES INDEXED BY I. 
        03    Y OCCURS 7 TIMES INDEXED BY J. 
            04    Z     PIC X(17) OCCURS 3 TIMES. 
01    K                 PIC S9(9) COMP. 
01    RETURN-STATUS     PIC S9(9) COMP. 
01    DECREMENT-VALUE   PIC 9 VALUE 1. 
 | 
  - Format 1---Initializing COURSE-INDEX.
   - Format 2---Adding to or subtracting from the index-name 
  COURSE-INDEX.
  
    
       
      
SET COURSE-INDEX UP BY 1. 
 
SET COURSE-INDEX DOWN BY DECREMENT-VALUE. 
 
 | 
   - Format 3---Initializing a conditional variable: 
 YEAR-LEVEL
  
    
       
      
SET SOPHOMORE TO TRUE                               02 
SET MASTERS TO TRUE                                 05 
SET GRAD TO TRUE                                    10 
SET NON-DEGREE-GRAD TO TRUE                         10 
 
 | 
   - Format 4---Setting external switches. The truth value shows the 
  result of the IF statements:
    
 TRUTH VALUE
  
    
       
      
SET UPDATE-RUN TO ON. 
SET REPORT-RUN TO OFF. 
SET NEW-YEAR TO ON. 
IF DO-UPDATE ...                                   true 
IF DO-REPORT ...                                   false 
IF CONTINUE-YEAR...                                false 
SET REPORT-RUN TO ON. 
IF DO-REPORT ...                                   true 
IF SKIP-REPORT ...                                 false 
 
 | 
   - Format 5---Setting POINTER-VAR to the address of the subscripted 
  table item named Z(I,J,K).
  
    
       
      
SET POINTER-VAR TO REFERENCE OF Z(I,J,K). 
 
 | 
   - Format 6---On OpenVMS, initializing RETURN-STATUS to FAILURE before 
  calling subprogram SUBPROGA and a Run-Time Library Procedure, then 
  checking for SUCCESS from each.
  
    
       
      
     . 
     . 
     . 
    SET RETURN-STATUS TO FAILURE. 
    CALL "SUBPROGA" GIVING RETURN-STATUS. 
    IF RETURN-STATUS IS SUCCESS 
        THEN 
            GO TO A0200-PARA 
        ELSE 
            DISPLAY "SUBPROGA failed" 
            STOP RUN. 
A0200-PARA. 
    SET RETURN-STATUS TO FAILURE. 
    CALL "SCR$SET_CURSOR" USING BY VALUE 4, 22 GIVING RETURN-STATUS. 
    IF RETURN-STATUS IS SUCCESS 
        THEN 
            DISPLAY "UPDATE ROUTINE COMPLETED" 
        ELSE 
            DISPLAY "Cursor positioning failed" 
            STOP RUN. 
     . 
     . 
     . 
 
IDENTIFICATION DIVISION. 
PROGRAM-ID. SUBPROGA. 
     . 
     . 
     . 
01    PROGRAM-STATUS    PIC S9(9) COMP. 
     . 
     . 
     . 
PROCEDURE DIVISION GIVING PROGRAM-STATUS. 
A000-BEGIN. 
     . 
     . 
     . 
 
    IF ... SET PROGRAM-STATUS TO SUCCESS 
      ELSE SET PROGRAM-STATUS TO FAILURE. 
    EXIT PROGRAM.    <>
 | 
 
6.8.33 SORT
Function 
The SORT statement (Format 1) creates a sort file by executing input 
procedures or transferring records from an input file. It sorts the 
records in the sort file using one or more keys that you specify. 
Finally, it returns each record from the sort file, in sorted order, to 
output procedures or an output file.
 SORT (Format 2) orders the elements in a table. This is especially 
 useful for tables used with SEARCH ALL. The table elements are sorted 
 based on the keys as specified in the OCCURS for the table unless you 
 override them by specifying keys in the SORT statement. If no key is 
 specified, the table elements are the SORT keys.
sortfile
is a file-name described in a sort-merge file description (SD) entry in 
the Data Division.
sortkey
(Format 1) is the data-name of a data item in a record associated with 
sortfile.
(Format 2) is the data-name of a data item in the table-name 
table.
first-proc
is the section-name or paragraph-name of the first (or only) section or 
paragraph of the INPUT or OUTPUT procedure range.
end-proc
is the section-name or paragraph-name of the last section or paragraph 
of the INPUT or OUTPUT procedure range.
infile
is the file-name of the input file. It must be described in a file 
description (FD) entry in the Data Division.
outfile
is the file-name of the output file. It must be described in a file 
description (FD) entry in the Data Division.
table-name
is a table described with OCCURS in the Data Division.
alpha
is an alphabet-name defined in the SPECIAL-NAMES paragraph of the 
Environment Division.
Syntax Rules 
All Formats
  - You can use SORT statements anywhere in the Procedure Division 
  except in:
  
    - Declaratives (Format 1)
    
 - SORT or MERGE statement input or output procedures
  
 
   - sortkey can be qualified.
  
 - sortkey cannot be in a group item that contains variable 
  occurrence data items.
  
 - The sortkey description cannot contain an OCCURS clause or 
  be subordinate to a data description entry that does.
 
Format 1
  - If sortfile contains variable-length records, 
  infile records must not be smaller than the smallest in 
  sortfile nor larger than the largest.
  
 - If sortfile contains fixed-length records, infile 
  records must not be larger than the largest record described for 
  sortfile.
  
 - If outfile contains variable-length records, 
  sortfile records must not be smaller than the smallest in 
  outfile nor larger than the largest.
  
 - If outfile contains fixed-length records, 
  sortfile records must not be larger than the largest record 
  described for outfile.
  
 - sortfile can have more than one record description. 
  However, sortkey needs to be described in only one of the 
  record descriptions. The character positions referenced by sortkey 
  are used as the key for all the file's records.
  
 - The words THRU and THROUGH are equivalent.
  
 - If outfile is an indexed file, the first sortkey 
  must be in the ASCENDING phrase. It must specify the same character 
  positions in its record as the prime record key for outfile.
 
Format 2
  -  table-name may be qualified and must have an OCCURS 
  clause in its data description entry. If table-name is subject 
  to more than one level of OCCURS clauses, subscripts must be specified 
  for all levels with OCCURS INDEXED BY.
  
 -  table-name is a key data-name, subject to the following 
  rules:
  
    - The data item identified by a key data-name must be the same as, or 
    subordinate to, the data item referenced by table-name.
    
 -  Key data items may be qualified.
    
 -  The data items identified by key data-names must not be 
    variable-length data items.
    
 -  If the data item identified by a key data-name is subordinate to 
    table-name, it must not be described with an OCCURS clause, 
    and it must not be subordinate to an entry that is also subordinate to 
    table-name and contains an OCCURS clause.
  
 
   -  The KEY phrase may be omitted only if the description of the table 
  referenced by table-name contains a KEY phrase.
 
General Rules 
All Formats
  - The first sortkey you specify is the major key, the next 
  sortkey you specify is the next most significant key, and so 
  forth. The significance of sortkey data items is not affected 
  by how you divide them into KEY phrases. Only first-to-last order 
  determines significance.
  
 - The ASCENDING phrase causes the sorted sequence to be from the 
  lowest to highest sortkey value.
  
 - The DESCENDING phrase causes the sorted sequence to be from the 
  highest to the lowest sortkey value.
  
 - Sort sequence follows the rules for relation condition comparisons.
  
 - The DUPLICATES phrase affects the return order of records or table 
  elements whose corresponding sortkey values are equal.
  
    - When there is a USING phrase, return order is the same as the order 
    of appearance of infile names in the SORT statement.
    
 - When there is an INPUT PROCEDURE, return order is the same as the 
    order in which the records were released.
    
 - When table elements are returned, the order is the relative order 
    of the contents of these table elements before sorting.
  
 
   - If there is no DUPLICATES phrase, the return order for records or 
  table elements with equal corresponding sortkey values is 
  unpredictable.
  
 - The SORT statement determines the comparison collating sequence for 
  nonnumeric sortkey items when it begins execution. If there is 
  a COLLATING SEQUENCE phrase in the SORT statement, SORT uses that 
  sequence. Otherwise, it uses the program collating sequence described 
  in the OBJECT-COMPUTER paragraph.
 
Format 1
  - If sortfile contains fixed-length records, any shorter 
  infile records are space-filled on the right, following the 
  last character. Space-filling occurs before the infile record 
  is released to sortfile.
  
 - The INPUT PROCEDURE range consists of one or more sections or 
  paragraphs that:
  
    - Appear contiguously in the source program
    
 - Do not form a part of an OUTPUT PROCEDURE range
  
 
   - The statements in the INPUT PROCEDURE range must include at least 
  one RELEASE statement to transfer records to sortfile.
  
 - The INPUT PROCEDURE range can consist of any procedure needed to 
  select, modify, or copy the next record made available by the RELEASE 
  statement to the file referenced by sortfile.
  
 - The range of the INPUT PROCEDURE additionally includes all 
  statements executed as a result of a CALL, EXIT, GO TO, or PERFORM 
  statement. The range of the INPUT PROCEDURE also includes all 
  statements in the Declaratives Section that can be executed if control 
  is transferred from statements in the range of the INPUT PROCEDURE.
  
 - The INPUT PROCEDURE range must not contain MERGE, RETURN, or SORT 
  statements.
  
 - If there is an INPUT PROCEDURE phrase, control transfers to the 
  first statement in its range before the SORT statement sequences the 
  sortfile records. When control passes the last statement in 
  the INPUT PROCEDURE range, the records released to sortfile 
  are sorted.
  
 - During execution of the INPUT or OUTPUT procedures, or any USE 
  AFTER EXCEPTION procedure implicitly invoked during the SORT statement, 
  no outside statement can manipulate the files or record areas 
  associated with infile or outfile.
  
 - If there is a USING phrase, the SORT statement transfers all 
  records in infile to sortfile. This transfer is an 
  implied SORT statement input procedure. When the SORT statement 
  executes, infile must not be open.
  
 - For each infile, the SORT statement:
  
    - Initiates file processing as if the program had executed an OPEN 
    statement with the INPUT phrase.
    
 - Gets the logical records and releases them to the sort operation. 
    SORT obtains each record as if the program had executed a READ 
    statement with the NEXT and AT END phrases.
    
 - Terminates file processing as if the program had executed a CLOSE 
    statement with no optional phrases. The SORT statement ends file 
    processing before it executes any output procedure.
  
 
    
These implicit OPEN, READ, and CLOSE operations cause associated 
    USE procedures to execute when an exception condition occurs.
   - OUTPUT PROCEDURE consists of one or more sections or paragraphs 
  that:
  
    - Appear contiguously in the source program
    
 - Do not form part of an INPUT PROCEDURE range
  
 
   - When the SORT statement begins the OUTPUT PROCEDURE phrase, it is 
  ready to select the next record in sorted order. The statements in the 
  OUTPUT PROCEDURE range must include at least one RETURN statement to 
  make records available for processing.
  
 - When the MERGE statement enters the OUTPUT PROCEDURE range, it is 
  ready to select the next record in merged order. Statements in the 
  OUTPUT PROCEDURE range must execute at least one RETURN statement to 
  make records available for processing.
  
 - The OUTPUT PROCEDURE can consist of any procedure needed to select, 
  modify, or copy the next record made available by the RETURN statement 
  in sorted order from the file referenced by sortfile.
  
 - The range of the OUTPUT PROCEDURE additionally includes all 
  statements executed as a result of a CALL, EXIT, GO TO, or PERFORM 
  statement. The range of the OUTPUT PROCEDURE also includes all 
  statements in the Declarative USE procedures that can be executed if 
  control is transferred from statements in the range of the OUTPUT 
  PROCEDURE.
  
 - The OUTPUT PROCEDURE range must not include MERGE, RELEASE, or SORT 
  statements.
  
 - If there is an OUTPUT PROCEDURE phrase, control passes to the first 
  statement in its range after the SORT statement sequences the records 
  in sortfile. When control passes the last statement in the 
  OUTPUT PROCEDURE range, the SORT statement ends. Control then transfers 
  to the next executable statement after the SORT statement.
  
 - If there is a GIVING phrase, the SORT statement writes all sorted 
  records to each outfile. This transfer is an implied SORT 
  output procedure. When the SORT statement executes, outfile 
  must not be open.
  
 - The SORT statement initiates outfile processing as if the 
  program had executed an OPEN statement with the OUTPUT phrase. The SORT 
  statement does not initiate outfile processing until after 
  INPUT PROCEDURE execution.
  
 - The SORT statement obtains the sorted logical records and writes 
  them to each outfile. SORT writes each record as if the 
  program had executed a WRITE statement with no optional phrases. 
  
For relative files, the value of the relative key data item is 1 
  for the first returned record, 2 for the second, and so on. When the 
  SORT statement ends, the value of the relative key data item indicates 
  the number of outfile records.
   - The SORT statement terminates outfile processing as if the 
  program had executed a CLOSE statement with no optional phrases.
  
 - These implicit OPEN, WRITE, and CLOSE operations can cause 
  associated USE procedures to execute if they are present. If a USE 
  procedure is present, processing terminates after the USE procedure has 
  completed execution. If a USE procedure is not present, processing 
  terminates as if the program had executed a CLOSE statement with no 
  optional phrases.
  
 - If outfile contains fixed-length records, any shorter 
  sortfile records are space-filled on the right, after the last 
  character. Space-filling occurs before the sortfile record is 
  released to outfile.
  
 - If the SORT statement is in a fixed segment, its input and 
  output procedures must be completely in either:
  
    - Fixed segments
    
 - One independent segment
  
 
   - If the SORT statement is in an independent segment, its 
  input and output procedures must be completely in either:
  
    - Fixed segments
    
 - The same independent segment as the SORT statement itself