Mainframe Reference Guide


This document provides some more detailed information about the objects and links that are stored in the Analysis Service. Other technical information may also be available.

Because the Mainframe analyzer can handle Cobol, JCL, IMS and CICS, this Reference Guide will contain information valid for all languages:

Cobol Object Types

Cobol objects detected by the analyzer are summarized in the following table:

IconObject TypeDescription
ProgramCobol code that can be executed by a process. The program contains a "procedure division" that consists of various sections or paragraphs.
Copy BookFile written in Cobol included in a program or another copy book. A copy book often contains declarations that are common to several Cobol programs.
ParagraphPiece of Cobol code located in a program. It can be executed inside a program if the resolution rules described below are respected.
SectionPiece of Cobol code located in a program or a group of paragraphs. It can be executed inside a program if the resolution rules described below are respected.
DivisionA Program consists of several Divisions that group together specific instructions (e.g.: program identification, execution environment, data declaration, processes etc.). A division can be divided into sections (e.g.: the DATA DIVISION can contain a FILE SECTION, WORKING-STORAGE SECTION, LINKAGE SECTION etc.).
File Link (Sequential, Partitioned, VSAM)This a logical file specific to the program. It is used to read/write data.
Data LinkFile used to implement a sort
ClassCobol files containing the implementation of a class (please note that classes are detected but not analyzed).
Directory/Root DirectoryFolder/directory located on the hard driver containing the analyzed files.
Entry PointEntry point for executing Cobol programs
InterfaceCobol files containing the implementation of an interface.
Program Specification BlockPSB specifications for handling IMS databases
Database DefinitionIMS database for mainframe
IMS SegmentSegments for an IMS database
Cobol conditional testConditional values of a field in a Cobol variable
Cobol dataField in a Cobol variable
Cobol literalLiteral
Cobol structure dataStructure data containing several fields
Cobol constant dataConstant data
External FileCICS files not resolved
TransactionCICS Transaction not resolved
Screen MapCICS Screen Map not resolved
Transient DataCICS TD Queue not resolved
ProjectTop level item
JCL Object Types

JCL objects detected by the analyzer are summarized in the following table:

IconTypeDescription
Catalogued JobA batch file written in JCL that executes JCL programs or procedures.
Catalogued ProcedureJCL file that can be executed by another JCL file
StepA section of a job or procedure that contains an execution order for a procedure or for a program.
Instream ProcedureA JCL procedure (a piece of JCL code) that can be executed within the file in which the code is stored.
Dataset (Sequential, Partitioned, VSAM)Data file used by a job, procedure or program.
External ProgramProgram called by a JCL job
Included FileFile included in a job or a JCL procedure.
IndexObject used to class JCL datasets in alphabetical order to facilitate navigation
ProjectTop level item
Directory/Root DirectoryContainer item
Program Specification BlockPSB specifications for handling IMS databases
IMS Object Types

IMS objects detected by the analyzer are summarized in the following table:

IconType
Directory/Root Directory
IMS Database
IMS Field
IMS Alternate PC Block
IMS PC Block type Database
IMS PC Block type GSAM
IMS Project
IMS PS Block
IMS Segment
IMS GSAM File
CICS Object Types

CICS objects detected by the analyzer are summarized in the following table:

IconType
CICS Basic Mapping Support

CICS System Definition file

CICS System Definition group
CICS Dataset
Directory/Root Directory
CICS Map
CICS Mapset
CICS Project
CICS TD Queue
CICS Transaction
CICS TS Model
Cobol Link Types

The following table describes Cobol references that are detected by the analyzer and the context in which corresponding links are traced and stored in the Analysis Service:

Link TypeLinked ObjectsCode Example
CallingCalled
CALLPROGProgram, section or copybookProgram or entrypoint
TRANSAC
PERFORMProgram,  section or sub-objectSection or paragraph
GOTOProgramFirst  executed section or paragraph
SectionFirst executed paragraph in section
ParagraphNext executed paragraph  in same section
INCLUDEProgram or CopybookCopybook
USECalls to matched character stringsDisplay "a string"
  • Cobol Program
  • Cobol Section
  • Cobol Paragraph
Program Specification Block
ACCESSOPEN
  • Cobol Program or sub-object
  • Cobol File Link
  • Cobol Data Link
         

            

              CALL 'CBLTDLI' USING GU                                                       CICSDLI-PCB
                                                      CICSDLI-SEGM                                                       CICSDLI-QSSA

CLOSE
READ
  • Cobol Program or sub-object
  • Cobol Section
  • Cobol Paragraph
  • Cobol File Link
  • Cobol Data Link
  • Constant Data
  • Structured Data
  • Data
  • Conditional Test
  • Program Communication Block (IMS PCB)
  • IMS Segment
WRITE

For Embedded SQL links, the following are valid for all servers.

USESELECTThis type is reserved for server side object referencing
UPDATE
INSERT
DELETE
CALL

For link types CALL PROG and CALL TRANSAC, two limitations exist when the call is in "string" form:

  • If the string is constant and declared in the "data-division" section, the entry point will be resolved in the normal way.
  • If the string is dynamic, the program may be found by the Dynamic Link Manager.

In addition, the following Embedded SQL links are valid for DB2 only:

DEPEND ONThis type is reserved for server side object referencing on structured or distinct UDTs.-
DDLCREATEThis type is reserved for server side object referencing on Tables-
DDLDROP

JCL Link Types

The following table describes JCL references that are detected by the analyzer and the context in which corresponding links are traced and stored in the Analysis Service:

TypeLinked Objects
CallingCalled
ACCESSWRITEJCL StepJCL Data Set
READ
EXECUTE
PROTOTYPECobol File LinkJCL Data Set
Cobol Data LinkJCL Data Set
JCL Data SetCobol JCL Program
CALLJCL StepCobol JCL Program
USEJCL StepIMS DBD

IMS Link Types

The following table describes IMS references that are detected by the analyzer and the context in which corresponding links are traced and stored in the Analysis Service:

TypeLinked Objects
CallingCalled
ACCESSWRITEIMS PC BlockIMS Segment
USEIMS PC BlockIMS DBD or IMS GSAM File

CICS Link Types

The following table describes CICS references that are detected by the analyzer and the context in which corresponding links are traced and stored in the Analysis Service:

TypeLinked Objects
CallingCalled
CALLTRANSACCICS TransidClient/Cobol Program

For Transactional Code, the following are valid:

TypeLinked ObjectsWhen does this link occur?
CallingCalled
CALLTRANSACClient/Cobol Program or its Sub objectClient/Cobol Program


or

EXEC CICS LINK  PROGRAM(TEST)
END EXEC

CALLTRANSACClient/Cobol Program or its Sub objectCICS Transaction


or


MONITORClient/Cobol Program or its Sub objectCICS Map

or


ACCESSOPEN

CLOSE

READ

WRITE

Client/Cobol Program or its Sub objectCICS Dataset

ex:


READ

WRITE

Client/Cobol Program or its Sub objectCICS Transient Data

ex: 

EXEC CICS DELETEQ TD QUEUE (W-CIC-TSQ-LNOM)

Miscellaneous Cobol information

Rules for resolving Paragraph names in a Section

The Mainframe Analyzer (Cobol) uses the following rules when resolving Paragraph names defined in Sections:

  1. If the referenced Paragraph is located in the current Section, Cobol Analyzer will link the calling Paragraph to the called Paragraph
  2. If the referenced Paragraph is not located in the current section, Cobol Analyzer will issue a syntax error
  3. If the referenced Paragraph has a unique declaration outside the Section, Cobol Analyzer will create a link to this Paragraph.
  4. The following syntax is also resolved: "Paragraph Name IN/OF Section Name". A link will be created to the correct Paragraph (which will be outside the current Section).

Access type links

Access type links are created when your Cobol program calls an external file (Data Set).

  1. The instructions that manage classic files ('File Link' type) are:

    Instructions for opening a file: OPEN Reading data: READ Writing data: WRITE, REWRITE Closing the file: CLOSE

  2. Sorting operations on data set files (Data Link type) are carried out via the instructions MERGE and/or SORT. These instructions should generate CALL + PERFORM type links on paragraphs or sections. OPEN and CLOSE instructions are also used.
  3. Access (Read/Write) links to "Cobol Constants" and "Cobol Data":
    • Variables used in the flow control: IF, PERFORM, EVALUATE, SEARCH.
    • Inclusion of the instructions: MOVE, INITIALIZE, SET, CALL, OPEN, CLOSE, READ, WRITE, REWRITE, MERGE, SORT.
    • The following instructions are not yet included: MULTIPLY, SUBTRACT, ADD, DIVIDE, EXHIBIT.
  4. CICS files read via CICS instructions in an EXEC CICS ... END-EXEC
    • Opening of file - Instructions: STARTBR -- Acesse(Open) on the file
    • Data reading - Instructions: DELETE, WRITE, REWRITE -- Access(Write)
    • Closing of file - Instruction: ENDBR -- Access(Close)
  5. Access to the segment in the IMS databases:
    • Links to the segment (Access + Write/Read)
    • Links to the Program Specification Block

File Selection

Logical Files are declared in the "File Section" part of the program with the FD or SD tag.

  • FD: declaration of  'file link' type
  • SD: declaration of 'data link' type

Example declaration of a logical file called MAIL-XREF (type FILE-LINK) in the Cobol program:

004600 FILE SECTION.                                                 00015900004700                                                               00016000009000 FD MAIL-XREF                                                  00020700009100    LABEL RECORDS ARE STANDARD                                 00020800009200    BLOCK CONTAINS 0 RECORDS.                                  00020900009300 01 MAIL-XREF-REC.                                             00021000009400    03 MAIL-XREF-KEY.                                          00021100009500       07 MAIL-XREF-ADDRESS.                                   00021200009600          11 MAIL-XREF-ZIP-PRE PIC X(05).                      00021300009700          11 MAIL-XREF-ZIP-SUF PIC X(04).                      00021400009800       07 MAIL-XREF-STATE PIC X(03).                           00021500009900       07 MAIL-XREF-CITY PIC X(25).                            00021600010000       07 MAIL-XREF-POSTAL-CODE PIC X(02).                     00021700010100    03 MAIL-XREF-DATA PIC X(324).                              00021800

Replacement used in COPY REPLACING directives

  • Replacements can be applied to words or parts of words
  • Patterns used to replace parts of words must be delimited by the following characters:  :, (, ), \ or "
  • Patterns that are not delimited by the above characters are considered as being used to replace entire words
  • LEADING and TRAILING clauses mean that the replacement will be applied on parts of words and as such, patterns must respect rule two (first character and last character will be removed from the pattern).
Miscellaneous JCL Information

JCL is a command language used to execute programs on large systems - primarily Cobol oriented. CAST's Mainframe Analyzer (JCL) is targeted at IBM's JCL language for 3090 systems used in conjunction with Cobol projects.

Display in CAST Enlighten

In CAST Enlighten, a full Mainframe Analysis (i.e. including COBOL, JCL, CICS and IMS) may be represented as follows:

COBOL Objects branch - if the data has NOT been saved in the Analysis Service (Data Structure > Save Data Only option in the Mainframe Technology options is not activated). Note that the Cobol Copybooks and its sub-heading Data in the Source file folders heading will only be visible if the Save data found in copy books option in the Mainframe Technology options is activated):

COBOL Objects branch - if the data has been saved in the Analysis Service (Data Structure > Save Data Only option in the Mainframe Technology options is activated). Note that the Cobol Copybooks and its sub-heading Data in the Source file folders heading will only be visible if the Save data found in copy books option in the Mainframe Technology options is activated):

JCL Objects branch

CICS Objects branch

IMS Objects branch


CAST Website