Dynamic File Names in COBOL

Often times we Cobol programmers take the “lazy” way out when accessing files within a program. Other than the record size, which is implicitly defined by the FD statement, we let MPE default the remaining parameters. We also use file equations to override some of these defaults.

Many new MPE programmers and veterans alike are intimidated by the FOPEN intrinsic. I think this is due to several factors including the myriad of parameters used by FOPEN. Moreover, the file open options (FOPTIONS) and access options (AOPTIONS) are coded as bitmaps, and typically passed as octal numbers in the FOPEN call. Compilers like Cobol and Fortran handle all of the dirty work for you, and file equations are much easier to understand than bitmaps, so we naturally use them to our advantage.

Nevertheless, there are times when you must explicitly define the characteristics of a file within the program. In Cobol, the combined parameters of the SELECT statement and the FD statement control how the compiler generates the FOPEN parameters. The following program overrides the default of 10,000 records per file that Cobol uses with 80,000. It also assigns the file name dynamically using a WORKING-STORAGE value. Since the file name is determined at run time instead of compile time, a file equation is not feasible. Even generating the file name using command interpreter (CI) programming isn’t necessarily practical.

As an example consider the following commonly used JCL statements:

!setvar fname,"GL"+rht("0!hpyear",2)+rht("0!hpmonth",2)+rht("0!hpdate",2)
!file file1=!fname;rec=-80,,f,ascii;disc=80000

>Result:

:listeq

FILE FILE1=GL000201;REC=-80,,F,ASCII;DISC=80000

Now, if your program was written using the highlighted statements in the following Cobol source, the above commands would be redundant

$CONTROL USLINIT,NOSOURCE,NOLIST,BOUNDS,POST85
 IDENTIFICATION DIVISION.
 PROGRAM-ID. COBTEST.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SPECIAL-NAMES.
     CONDITION-CODE IS C-C.
 INPUT-OUTPUT SECTION.

 FILE-CONTROL.
     SELECT FILE1 ASSIGN TO "TEST,,,,80000" USING DYNAMIC-NAME.
 I-O-CONTROL.
 DATA DIVISION.
 FILE SECTION.
 FD FILE1.
 01 FILE1-RECORD PIC X(80).

 WORKING-STORAGE SECTION.
 01 PROGRAM-NAME PIC X(26) VALUE SPACES.

 01 DYNAMIC-NAME     PIC X(16) VALUE "FILENAME".
 01 TODAY-DATE       PIC X(06) VALUE SPACES.
 PROCEDURE DIVISION.
 0000-CONTROL-PROCESS.
     ACCEPT TODAY-DATE FROM DATE.
     STRING "LG", TODAY-DATE, DELIMITED BY SIZE,
            INTO DYNAMIC-NAME.
     OPEN OUTPUT FILE1.
     CLOSE FILE1.
     STOP RUN.

:run cobtest
:listftemp myfile,2

TEMPORARY FILES FOR DOUG.WERTH,SOURCE
ACCOUNT=  WERTH       GROUP=  SOURCE

FILENAME  CODE  ------------LOGICAL RECORD-----------  ----SPACE----
                  SIZE  TYP        EOF      LIMIT R/B  SECTORS #X MX

LG000727           80B  FA           0      80000   3        0  0  * (TEMP)

This technique is useful for generating audit trails with file names based upon the input data which is not known at compile time, or even run time when file equations are set. Another place this is advantageous is in web application development where all processes are running underneath the same job rendering file equations ineffective because they apply to the entire job, not just the current process.