Cobol programs have multiple ways to make links to other programs, copybooks, datasets, etc. In addition, depending on the compiler and the Cobol flavor (Ansi, Tandem, OpenVMS…), the list of statements may change. AWS Blu Insights dependencies engine handles a large list of statements (see below) and can rapidly be extended to support new ones.
There are two way to identify a Cobol program from the file name without the extension and from the identification division at the start the source file, like the following example.
IDENTIFICATION DIVISION.
PROGRAM-ID. CBACT02C.
AUTHOR. AWS.ENVIRONMENT DIVISION.
Sometimes, the file name and the program id are different but both can be used to address a Cobol program. The dependencies analysis handle that. So when a link does to a Cobol file, “file named” can be resolve by a “program id” and vice versa. If two different Cobol files have the same file name or program id, both will be considered.
Some Cobol program can declare entry points, like follows.
PROCEDURE DIVISION.
DISPLAY ‘BEGINIING OF THE PROGRAM’.
ENTRY ‘POINT1’.
These entry points are treated like an alternative program id.
The call on ++INCLUDE / -INC and ?SOURCE implies dependencies on copybook files :
The list below uses only the CALL
keywords but the dependencies will be the same with CALL PROC
or CALL PROCEDURE
. We expect to find dependencies of any extension :
CALL 'PROGRAM'
implies a dependency on a file named “PROGRAM”CALL "PROGRAM"
implies a dependency on a file named “PROGRAM”CALL PROGRAM_VAR
implies a dynamic dependency involving PROGRAM_VAR
variable, refers to the dedicated paragraph.Those statements can also address an ENTRY
defined in an ASM or Cobol file.
The CALL ... USING ...
implies a dependency on a program file. We expect to find dependencies of any extension. We also handle dynamic code execution with those statements:
CALL "PROGRAM" USING MY_STRING_VAR
implies a dependency on a file named “PROGRAM” and if MY_STRING_VAR is a string containing dynamic source code, we will also analyze this source codeMY_STRING_VAR can be set using a STRING ... END-STRING
statement for string concatenation. We don’t handle cases where those String concatenations depend on each other.
For instance the code below will not generate an EXEC CICS PROGRAM dependency:
MOVE “” TO STR_COMMAND
STRING
“EXEC CICS LINK PROGRAM”
DELIMITED BY SIZE
INTO STR_COMMAND
END-STRING.STRING
“(MY_FILE) END-EXEC.”
DELIMITED BY SIZE
INTO STR_COMMAND
END-STRING.
The call on COPY
, +COPY
or $COPY
implies dependencies on copybook files or a record object declared in a PF or DSPF file :
COPY 'COPYBOOK'
implies a dependency on a copybook file named “COPYBOOK”COPY 'folder:COBCOP.cobcop'
implies a dependency on a cobcop file named “COBCOP”. The .cobcop
in the string is optional.COPY "COPYBOOK"
implies a dependency on a copybook file named “COPYBOOK”COPY "folder:COBCOP.cobcop"
implies a dependency on a cobcop file named “COBCOP”. The .cobcop
in the string is optional.COPY COPYBOOK
implies a dependency on a copybook file named “COPYBOOK”COPY PREFIXED-ID OF FILE
or COPY PREFIXED-ID IN FILE
implies a dependency on a file named “FILE” and implies a dependency on a record. The record name is found by removing prefix and suffix from PREFIXED-ID.
DD-
DDS-
DDR-
DDSR-
-O
-I
-I-O
-INDICATORS
For example, DDR-RECORD-I-INDICATOR
is transformed into RECORD
.
Copybook named ALL-FORMATS
will not made a dependency.
If a COPY statement is followed by REPLACING ... BY the content of the targeted copybook will be replaced according to the parameter of this statement:
COPY MYCOPYBOOK REPLACING VAR1 BY VALUE VAR2 BY VALUE2
When the replacing name and value are between "==" any character can compose the name and value.
COPY MYCOPYBOOK REPLACING ==:VAR1:== BY ==VALUE==
The replacing statements can be chained like the following:
COPY MYCOPYBOOK REPLACING ==:VAR1:== BY ==VALUE== ==:VAR2:== BY ==VALUE2==
In this last example, all occurrences of :VAR1:
and :VAR2:
in the copy file MYCOPYBOOK
will be replaced by VALUE
and VALUE2
.
All the dependencies from the replaced content of the copybook are directly added to the original copybook's dependencies as a "Copy Replacing" dependency.
EXEC CICS exec-cics-verb DATASET(“file-definition-name”) ... END-EXEC
implies a dependency on a “CICS_FILE” or “DATASET” object named “file-definition-name”EXEC CICS exec-cics-verb DATASET('file-definition-name') ... END-EXEC
implies a dependency on a “CICS_FILE” or “DATASET” object named “file-definition-name”EXEC CICS exec-cics-verb DATASET(variable-name) ... END-EXEC
implies a dependency on all “CICS_FILE” or “DATASET” objects referenced by the variable “variable-name”“exec-cics-verb” can be one of the following
Refer to the paragraph dedicated to file definitions.
EXEC CICS exec-cics-verb FILE(“file-definition-name”) ... END-EXEC
implies a dependency on a “CICS_FILE” object named “file-definition-name”EXEC CICS exec-cics-verb FILE('file-definition-name') ... END-EXEC
implies a dependency on a “CICS_FILE” object named “file-definition-name”EXEC CICS exec-cics-verb FILE(variable-name) ... END-EXEC
implies a dependency on all “CICS_FILE” objects referenced by the variable “variable-name”“exec-cics-verb” can be one of the following
We support several calls on LINK PROGRAM
, the call itself could be on multiple lines or not. We expect to find dependencies of any extension :
EXEC CICS LINK / LOAD / XCTL PROGRAM(“PROGRAM”) ... END-EXEC
implies a dependency on a file named “PROGRAM”EXEC CICS LINK / LOAD / XCTL PROGRAM('PROGRAM') ... END-EXEC
implies a dependency on a file named “PROGRAM”EXEC CICS LINK / LOAD / XCTL PROGRAM(PROGRAM_VAR) ... END-EXEC
implies a dynamic dependency involving PROGRAM_VAR
variable, refer to the dedicated paragraph.We support several calls on RECEIVE MAP
, the call itself could be on multiple lines or not. We expect to find dependencies of any extension but .CBL, .COB and .CPY :
EXEC CICS RECEIVE MAP(“MAP”) ... END-EXEC
implies a dependency on a file named “MAP”EXEC CICS RECEIVE MAP('MAP') ... END-EXEC
implies a dependency on a file named “MAP”EXEC CICS RECEIVE MAP(MAP_VAR) ... END-EXEC
implies a dynamic dependency involving MAP_VAR
variable, refer to the dedicated paragraph.We support several calls on RECEIVE MAPSET
, the call itself could be on multiple lines or not. We expect to find dependencies of any extension but .CBL, .COB and .CPY :
EXEC CICS RECEIVE MAPSET(“MAPSET”) ... END-EXEC
implies a dependency on a file named “MAPSET”EXEC CICS RECEIVE MAPSET('MAPSET') ... END-EXEC
implies a dependency on a file named “MAPSET”EXEC CICS RECEIVE MAPSET(MAPSET_VAR) ... END-EXEC
implies a dynamic dependency involving MAPSET_VAR
variable, refer to the dedicated paragraph.We support several calls on SEND MAP
, the call itself could be on multiple lines or not. We expect to find dependencies of any extension but .CBL, .COB and .CPY :
EXEC CICS SEND MAP(“MAP”) ... END-EXEC
implies a dependency on a file named “MAP”EXEC CICS SEND MAP('MAP') ... END-EXEC
implies a dependency on a file named “MAP”EXEC CICS SEND MAP(MAP_VAR) ... END-EXEC
implies a dynamic dependency involving MAP_VAR
variable, refer to the dedicated paragraph.We support several calls on SEND MAPSET
, the call itself could be on multiple lines or not. We expect to find dependencies of any extension but .CBL, .COB and .CPY :
EXEC CICS SEND MAPSET(“MAPSET”) ... END-EXEC
implies a dependency on a file named “MAPSET”EXEC CICS SEND MAPSET('MAPSET') ... END-EXEC
implies a dependency on a file named “MAPSET”EXEC CICS SEND MAPSET(MAPSET_VAR) ... END-EXEC
implies a dynamic dependency involving MAPSET_VAR
variable, refer to the dedicated paragraph.Refer to the paragraph dedicated to file definitions.
EXEC CICS exec-cics-verb TRANSID(“transaction-name”) ... END-EXEC
implies a dependency on a “TRANSACTION” object named “transaction-name”EXEC CICS exec-cics-verb TRANSID('transaction-name'”) ... END-EXEC
implies a dependency on a “TRANSACTION” object named “transaction-name”EXEC CICS exec-cics-verb TRANSID(variable-name) ... END-EXEC
implies a dependency on all “TRANSACTION” objects referenced by the variable “variable-name”“exec-cics-verb” can be one of the following
We support several calls on EXEC SQL
, the call itself could be on multiple lines or not. We expect to find the dependencies of any extension. The dependencies are detected for the following operations in the request :
EXEC SQL ... FROM TABLE1, TABLE2 ... END-EXEC
where TABLE1
and TABLE2
are files corresponding to SQL tables. TABLE2
is optional and if there are only two tables, commas aren’t needed.EXEC SQL ... INSERT INTO TABLE1 ... END-EXEC
where TABLE1
is a file corresponding to a SQL table.EXEC SQL ... JOIN TABLE1 T1 ON ... END-EXEC
where TABLE1
is a file corresponding to a SQL table and T1 is an optional alias for TABLE1
used in the rest of the request.EXEC SQL ... UPDATE TABLE1 SET ... END-EXEC
where TABLE1
is a file corresponding to a SQL table.The call on EXEC SQL CALL
implies dependencies on SQL files :
EXEC SQL CALL SQLFILE(...) END-EXEC.
implies a dependency on a SQL file named “SQLFILE”.The call on EXEC SQL INCLUDE
implies dependencies on copybook files :
EXEC SQL INCLUDE 'COPYBOOK' ... END-EXEC
implies a dependency on a copybook file named “COPYBOOK”EXEC SQL INCLUDE "COPYBOOK" ... END-EXEC
implies a dependency on a copybook file named “COPYBOOK”EXEC SQL INCLUDE COPYBOOK ... END-EXEC
implies a dependency on a copybook file named “COPYBOOK”The call on EXEC SQL SOURCE
implies dependencies on copybook files :
EXEC SQL SOURCE = 'COPYBOOK'
implies a dependency on a copybook file named “COPYBOOK”EXEC SQL SOURCE = "COPYBOOK"
implies a dependency on a copybook file named “COPYBOOK”EXEC SQL SOURCE = COPYBOOK
implies a dependency on a copybook file named “COPYBOOK”The call on NNCOPY
can be found in a COBOL comment and implies dependencies on copybook files :
*01 NNCOPY COPYBOOK(SEGMENT)
implies a dependency on a copybook file named “COPYBOOK”The call on SELECT ... ASSIGN TO
implies a dependency on a file and/or an SQL table:
SELECT filename ASSIGN TO varname
implies a dependency on “filename” that can be a SQL table or a cobol file. “filename” can also be a FileDefinition (FD filename
) and in that case, “varname’ becomes an alias of “filename”.The call on SWCOPY
implies dependencies on copybook files :
SWCOPY 'COPYBOOK'
implies a dependency on a copybook file named “COPYBOOK”SWCOPY "COPYBOOK"
implies a dependency on a copybook file named “COPYBOOK”SWCOPY COPYBOOK
implies a dependency on a copybook file named “COPYBOOK”In Cobol, file definitions are declared into the “FILE SECTION” like 000000 FD file-definition-name
LABEL RECORDS ARE STANDARD.
000000 01 file-definition-record.
A link from the Cobol file to an object named ‘file-definition-name’ typed ‘FILE_DEFINTION’ will be created. ‘file-definition-record’ is an alias of ‘file-definition-name’.
In Cobol, sort descriptions are declared like000000 SD sort-description-name
Then the Sort Description can be used in a SQL statement likeSELECT sort-description-name ASSIGN TO ...
A link from the Cobol file containing the SQL statement to an object named ‘sort-description-name’ typed ‘SORT_DESCRIPTION’ will be created.
OPEN (INPUT|OUTPUT|EXTEND|I-O) file-definition-name
implies a dependency on a “FILE_DEFINITION” object typed “FILE_DEFINTION” and named “file-definition-name”
READ file-definition-name
implies a dependency on a “FILE_DEFINITION” object named “file-definition-name”READ SUBFILE file-definition-name
implies a dependency on a “FILE_DEFINITION” object named “file-definition-name”WRITE file-definition-record
implies a dependency on a “FILE_DEFINITION” aliased object with an alias named “file-definition-record”WRITE SUBFILE file-definition-record
implies a dependency on a “FILE_DEFINITION” aliased object with an alias named “file-definition-record”REWRITE file-definition-record
implies a dependency on a “FILE_DEFINITION” aliased object with an alias named “file-definition-record”REWRITE SUBFILE file-definition-record
implies a dependency on a “FILE_DEFINITION” aliased object with an alias named “file-definition-record”DELETE file-definition-name
implies a dependency on a “FILE_DEFINITION” object named “file-definition-name”START file-definition-name
implies a dependency on a “FILE_DEFINITION” object named “file-definition-name”CLOSE file-definition-name
implies a dependency on a “FILE_DEFINITION” object named “file-definition-name”A dynamical dependency is when a dependency target is only known at runtime. In COBOL, the name of the program to call is stored in a variable that is used in some statements seen in the previous paragraph. Static analysis of COBOL source can detect some variable values.
01 ATTRIBUTE PIC X(8) VALUE 'PROGRAM '.
This is an initialization of a field named ATTRIBUTE
with the value 'PROGRAM '
. If ATTRIBUTE
is used in a statement implying a dependency, it means that 'PROGRAM '
maybe a program name.
MOVE 'PROGRAM' TO ATTRIBUTE ATTRIBUTE2
MOVE ATTRIBUTE TO ATTRIBUTE3
If either ATTRIBUTE
, ATTRIBUTE2
or ATTRIBUTE3
is used in a statement implying a dependency, which means that 'PROGRAM'
maybe a program name.
All default values and MOVE
defined in a copybook are reported to any program using this copybook. In addition, any dynamic call found in a copybook will be transformed into a dynamic call from any program using this copybook.
If a move statement set a variable's value just before a dynamic call using the same variable, the dependency analysis will consider it like a direct call.
MOVE "PROGA" TO VAR.
CALL VAR.