You are on page 1of 14

---

* User Defined words -


* Paragraph-name and Section name need not contain aphabetic character
* Other user defined words must have alphabetic
* Maximum size of COBOL word is 30 characters

* Reserved Words Types -


* Figurative constants are ZERO, SPACES, HIGH-VALUES, LOW-VALUES, QUOTE, NULL
* Special character words - +, -, <, >, =
* Keywords are ACCEPT, ADD, SUBTRACT, ALPHABETIC, NUMERIC, ASCENDING, AUTHOR
* Optional words are SKIP1, ROUNDED
* Special registers are ADDRESS OF, LENGTH OF, RETURN-CODE

---

* Numeric Literal - ex. +123.3 max length is 18 digits


* Max length of Numeric literal can be increased by coding - PARM='ARITH(EXTEND)'
in EXEC statement in COMPILE JCL or in 1st line before IDENTIFICATION DIVISION.

* Non Numeric Literal - ex. "123", "HELLO" max length is 256 characters
* " is converted to ' when " is written as delimiter - ex. 'THIS ISN"T WRONG' is
converted to THIS ISN'T WRONG

---

* Contant types - Numeric(Ex. 123), Alphanumeric(Ex. 'HELLO') and Figurative(Ex.


ZEROS, QUOTE, ALL)

---

* PICTURE SYMBOL is the letter used to specify picture clause -


Alphabetic - A ex. PIC A(5) Input(HELLO) Output(HELLO)
Alphanumeric - X ex. PIC X(5) Input(HELLO)
Output(HELLO)
Numeric - 9 ex. PIC 9(5) Input(12345)
Output(12345)
Implied decimal - V ex. PIC 9V99 Input(12.34) Output(234)
- . is NOT COUNTED in size of data
Actual Decimal - . ex PIC 9(3).9(2) Input(123.45/12.34/12.345/123)
Output(123.45/012.34/012.34/123.00) - . is COUNTED in size of data
Operational sign S ex. PIC S999 Input(-123/+123)
Output(12L/12C) - not counted in size of data - unless 'SIGN IS LEADING/TRAILING

SEPERATE CHARACTER' is coded


Sign - - ex. PIC -9(3) Input(-123/+1234) Output(-
123/ 123) - counted in size of data
Sign - - ex. PIC -(4) Input(-123/+1234) Output(-
123/1234) - not counted in size of data
CR - CR ex. PIC 9(3)CR Input(+123/-123) Output(123
/123CR) - Credit editing control char
DB - DB ex. PIC 9(5)DB Input(+123/-123) Output(123
/123DB) - Debit editing control char
Zero suppresser - Z ex. PIC Z(5) Input(0000123)
Output( 123)
ZERO insertion - 0 ex. PIC 990099 Input(1234)
Output(120034)
SPACE insertion - B ex. PIC 99B99B9999 Input(09101993) Output(09 10
1993)
Decimal scaling - P ex. PIC 9999P Input(1234) Output(1234)
- not counted in size of data - similarly , / + - and $

---

* PIC $**,**9. Input(12.34) Output($**12) - Zero suppression editing with * (other


zero supression done by Z)
* PIC $**,*** Input(00000) Output(*******) - Zero suppressed with * when passed
zeroes will not even display $ and ,

---

* Comments in COBOL
using * in column 7
using / in column 7
using *> in any column (for COBOL 5.1 and above only)

---

IDENTIFICATION DIVISION.
PROGRAM-ID. MYPROG.
AUTHOR. SHYLENDRA.
DATE-WRITTEN. 22-SEP-2021.
DATE-COMPILED. 22-SEP-2021.

---

ENVIRONMENT DIVISION.

CONFIGURATION SECTION. (only coded in main program and not in nested program)
SOURCE-COMPUTER. IBM1. [WITH DEBUGGING MODE - used when debug lines added in
program - debug lines are those having 'D' in column 7]
OBJECT-COMPUTER. IBM1.

INPUT-OUTPUT SECTION. (To specify file organization and access method)


FILE-CONTROL.
SELECT FILE1 [OPTIONAL] ASSIGN TO INFILE (optional is used when file opened
in I-O mode or when file is not present like in DD DUMMY)
ORGANIZATION IS SEQUENTIAL [INDEXED/RELATIVE]
ACCESS MODE IS SEQUENCTIAL [RANDOM/DUNAMIC]
[RECORD KEY IS WS-FILE1-KEY/ RELATIVE KEY IS WS-FILE1-REL-KEY]
[ALTERNATE RECORD KEY IS WS-FILE1-ALT-KEY]
FILE STATUS IS WS-FS1.

---

DATA DIVISION.

FILE SECTION.
FD[SD] FILE1 [IS GLOBAL/ IS EXTERNAL]
RECORD CONTAINS 80 CHARACTERS
BLOCK CONTAINS 800 CHARCATERS [RECORDS]
RECORDING MODE IS F
DATA RECORD IS FILE1-REC.
01 FILE1-REC PIC X(80).

WORKING-STORAGE SECTION.
01 WS-GROUP.
05 WS-VAR-A PIC X(10) VALUE SPACES.
05 WS-VAR-B PIC 9(10) VALUE ZEROES.

LOCAL-STORAGE SETION.
01 LS-GROUP.
05 LS-VAR-A PIC X(10) VALUE SPACES.
05 LS-VAR-B PIC 9(10) VALUE ZEROES.

LINKAGE SECTION.
[ (declaration for called pgm ; Data items must be
declared in level 01/77, max length allowed is 64K)
01 LN-NUM-A PIC 9(05).
01 LN-NUM-B PIC 9(05).
01 LN-RESULT PIC 9(10).
]
[ (declaration to receive data from JCL PARM ; max
length allowed is 100 bytes)
01 LN-DATA.
05 LN-LENGTH PIC S9(4) COMP.
05 LN-PARM PIC X(10).
]

---

* == is a pseudo-text delimiter used with COPY statement REPLACING


Ex. COPY <copybook name here> REPLACING ==:WS:== BY ==WS1== (here char length
between "==" can be of 322 bytes)

---

* If 01 WS-GROUP-VAR.
02 WS-GRP.
05 WS-VAR1 PIC X(01) VALUE 'Y'.
05 WS-VAR2 PIC X(01) VALUE 'N'.
66 WS-GRP-2 RENAMES WS-VAR1 THRU WS-VAR2.
01 WS-IND-VAR PIC X(01) VALUE 'N'.

Then WS-GROUP-VAR and WS-GRP variables are group variables


WS-VAR1 and WS-VAR2 are elementary variables
WS-IND-VAR is a Individual variable

* This is valid
01 WS-GRP1.
05 WS-VAR1 PIC X(05).
01 WS-GRP-BACKUP.
05 WS-VAR1 PIC X(05). - Duplicate WS-VAR1 but under different group
variaable
They can be refered like below - WS-VAR1 of WS-GRP1 ; WS-VAR1 of WS-GRP-
BACKUP

---

* Level 49 is used for declaring VARCHAR in DB2 - is a group variable of level 01


should have a 49 level length variable and a 49 level data variable

* Level 66 can only be used for RENAME clause


* RENAME clause is used to regroup the elementary items of a group item
* Can not RENAME if elementary items(within group variable) contains OCCURS clause
* Can not RENAME Level 01, Level 77, Level 88 or Level 66

* Level 77 reduce usage of memory during run time.

* Sample 88 level declaration -


01 STD-MARKS PIC 9(03).
88 FIRST-CLASS VALUE 060 THRU 100.
88 SEC-CLASS VALUE 050 THRU 059.
88 JUST-PASS VALUE 035 THRU 049.
88 FAIL VALUE 000 THRU 034.

---

* REDEFINES Clause used to store different data items in same storage area
(Technically address of starting byte will be same).
* Ex. 01 WS-VAR-A PIC X(20) VALUE SPACES.
01 WS-VAR-B REDEFINES WS-VAR-A PIC 9(8).
01 WS-VAR-C REDEFINES WS-VAR-A PIC X(23).

---

* SIGN CLAUSE ex.


01 WS-VAR.
05 WS-NUM-SIG PIC S9(03) VALUE +125
SIGN IS LEADING SEPERATE CHARACTER.
Output(+125) total size will be 4

---

* OCCURES can not be given to 01 LEVEL. Below ex. for 60 students studying 6
subjects.
* Ex. 01 WS-STUDENT.
02 WS-NAME PIC X(35) OCCURES 60 TIMES.
05 WS-MARKS PIC 9(03) OCCURES 06 TIMES.
DISPLAY WS-MARKS(1,1) will access 1st instance of WS-MARKS in 1st instance of
WS-NAME; here (1, 1) is (idx of WS-NAME, idx of WS-MARKS)
* 6 nested level OCCURES and one outermost OCCURES clause allowed.
* SUBSCRIPT need to be declared sperately in working storage where as INDEX can
just be mentioned in OCCURES class
* Move can be used to initialize and increment SUBSCRIPT, but we need to use SET if
it is INDEX.

---

* USAGE clause specifies how data is stored in memory, and is used to reduce
storage space and increase efficiency of program.
* USAGE can be specied for al levels exccept 66 and 88.
* USAGE DISPLAY is default and applicable to all data items. Data stored in CHAR
form (1char/1digit = 1 byte)
* USAGE COMP/BINARY applicable to only numeric. 9 to 9(4) = 2 bytes half word ,
9(5) to 9(9) = 4 bytes word , 9(10) to 9(18) = 8 bytesdouble word
* USAGE COMP-1 for single precision floating point number. 4 bytes length (sign in
left most nibble).
* USAGE COMP-2 for double precision floating point number. 8 bytes length (sign in
left most nibble).
* USAGE COMP-3/PACKED DECIMAL for internal decimal items. n digits = (n+1)/2 byte
(sign stored in right most nibble)

---
* JUST clause not applicable for numeric. JUST can be used to right justify
alpanumeric values while displaying
* JUST can be appplied only at elementary level.
* data in VALUE clause not affected by JUST.
* WS-VAR1 PIC X(10) JUST [JUSTIFIED] RIGHT.

---

* SYNC clause specifies allignment of elementary item on natural boundary in


storgae. Used to improve performance of binary items in arthmetic.
* SLACK Bytes - leftover bytes.
* Ex. 01 WS-STUDENT.
05 WS-ID PIC 9(02).
[05 SLACK-BYTES PIC XX. INSERTED BY COMPILER]
05 WS-NAME PIC X(12) SYNC.

---------------
---------------

* Comments in IDENTIFICATION DIVISION - ex. AUTHOR, DATE-WRITTEN, DATE-COMPILED,


SECURITY, INSTALLATION
* Note continuation char(-) in colummn 7 is not required for identification
division comments
* '*' is for comments, '-' is for continuation and '/' is for form feed -- can be
coded in any division
* '*>' is inline comments (also called floating comment indicator) -- can be coded
in any division, but supported only in COBOL5.1 and above

---

* In FILE-CONTROL para, RECORD KEY and ALTERNATE RECORD KEY clause(specified if


Organization is INDEXED) the value is treated as alphanumeric regardless of the
data type of record key.
* RELATIVE KEY is always required if ACCESS method is RANDOM/DYNAMIC, and not
required for SEQUENCTIAL

---

* WS-VAR (in PROCEDURE DIVISION USING WS-VAR) must be declared in 01 77 level in


linkage section of called pgm but can be of any level in data division in calling
program.
* Procedure/PARA names can not exceed 30 char.

---------------
---------------

* EXAMINE statement can be coded similar to INSPECT. This is an addition by HP.

---

* EXIT PROGRAM only for called program and STOP RUN is only for main program.
* EXIT PROGRAM gives control back to calling program and STOP RUN gives control
back to OS.
* GOBACK based on where it is coded gives control back to either OS or to calling
program.

---
* INITIALIZE sets the data item to predefined values based on data type. FILLERS
are not affected by INITIALIZE.

---

* INSPECT WS-DATA TALLYING WS-CNT FOR ALL 'A' BEFORE INITIAL 'B' (similarly FOR
LEADING SPACES)
* INSPECT WS-DATA REPLACING ALL '-' BY '~' BEFORE INITIAL 'B'
* INSPECT WS-DATA TALLYING WS-CNT FOR ALL 'A' BEFORE INITIAL 'B' REPLACING ALL
'A' BY '*' BEFORE INITIAL 'B'
* INSPECT WS-DATA REPLACING 'ABC' BY '123' - Will replace string 'ABC' by '123'
* INSPECT WS-DATA CONVERTING 'ABC' TO '123' - Will A by 1, B by 2 and C by
3.

---

* NEXT SENTENCE will transfers the control to next cobol SENTENCE after the PERIOD.
* CONTINUE on the other hand will tranfer control to next STATEMENT.

---

* SET statement for initializarion - SET WS-VAR TO 1.


* SET stetment for increasing index - SET WS-VAR UP BY(or DOWN BY) 1.
* SET statement for setting flag/conditional variables - SET WS-PASS TO TRUE.

---

* STRING WS-DATA, WS-DATA-2 DELIMITED BY SPACE


INTO WS-OUTPUT
ON OVERFLOW DISPLAY 'ERROR OCCURED'
NOT ON OVERFLOW DISPLAY 'NO ERROR'
END-STRING.

* UNSTRING WS-OUTPUT DELIMITED BY SPACE


INTO WS-DATA, WS-DATA-2
END-UNSTRING.

---

* INCLUDE statement is used to insert a piece of cobol code (or DB2 stored
procedures) into source program.
* INCLUDE is also used to include DCLGENs

---

* EVALUATE using mutiple conditions -


EVALUATE TRUE ALSO TRUE
WHEN WS-AGE > 18 AND WS-GENDER = 'M'

---

* PERFORM will come out of the loop as soon as condition is satisfied

* PERFORM BUILD-PARA
THRU BUILD-PARA-EXIT
WITH TEST BEFORE UNTIL I > 5
END-PERFORM

* PERFORM VERYING I FROM 1 BY 1 UNTIL I > 5


<Code here>
END-PERFORM

---

* ADD ex.
ADD A B TO C D [ROUNDED] (C=A+B+C and D=A+B+D)
ADD A B C TO D GIVING E [ROUNDED] (E=A+B+C+D)
ADD CORR WS-GROUP1 TO WS-GROUP2 [ROUNDED] (Adds elementary item in
GROUP1 to corr elementary item in GROUP2, store value in GROUP2) - CORR is only for
+ and - and MOVE

* SUBTRACT ex.
SUBTRACT A B FROM C D [ROUNDED] (C=C-(A+B) and D=D-(A+B))
SUBTRACT A B C FROM D GIVING E [ROUNDED] (D=D-(A+B+C))
SUBTRACT CORR WS-GROUP1 FROM WS-GROUP2 [ROUNDED] (Subtract elementary item in
GROUP1 to corr elementary item in GROUP2, store value in GROUP2)

* MULTIPLY ex.
MULTIPLY A BY B C [ROUNDED] (B=A*B and C=A*C)
MULTIPLY A BY B GIVING E [ROUNDED] (E=A*B)

* DEVIDE ex.
DIVIDE A INTO B [ROUNDED] (B=B/A)
DIVIDE A BY B GIVING C REMAINDER R [ROUNDED] (C=A/B)

---

* File handling life cycle = Declare a File > Open a File > Read a File > Write to
a File > Close a File

* OPEN INPUT to read existing file


OUTPUT to write to newly created file (if already has data then data is
replaced, not use for DUMMY)
I-O used only for files stored in DASD
EXTEND allowed only for QSAMs/FLAT files

* In FILE-CONTROL, SELECT OPTIONAL ASSIGN TO INPUT1 - OPTIONAL can be used for


openning file in I-O or EXTEND mode when file does not exist - a temp file will be
created and at end of pgm it is deleted.

* READ file-name NEXT RECORD INTO ws-file-structure


[KEY IS rec-key - when access mode is random]
AT END DISPLAY 'End of File'
NOT AT END DISPLAY 'Record Details:' ws-file-structure
END-READ.

* WRITE record-buffer [FROM ws-file-structure]


[INVALID KEY DISPLAY 'Invalid Key' - when access mode is random]
END-WRITE.

* REWRITE record-buffer [FROM ws-file-structure]


[INVALID KEY DISPLAY 'Invalid Key' - when access mode is random]
END-REWRITE.

* DELETE file-name RECORD


INVALID KEY DISPLAY 'Invalid Key'
NOT INVALID KEY DISPLAY 'Record Deleted'
END-DELETE.
* START file-name KEY IS [=, >, <, NOT, <= or >=] rec-key
INVALID KEY DISPLAY 'Invalid Key'
NOT INVALID KEY DISPLAY 'File Pointer Updated'
END-START.

---

* SEARCH - Linear Search; index needs initialization; Can be used in multi


dimentional array; table need not be sorted; multiple WHEN and operators can be
coded in condition
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-TABLE.
05 WS-A PIC X(1) OCCURS 18 TIMES INDEXED BY I.
01 WS-SRCH PIC A(1) VALUE 'M'.

PROCEDURE DIVISION.
MOVE 'ABCDEFGHIJKLMNOPQR' TO WS-TABLE.

SET I TO 1.

SEARCH WS-A
AT END DISPLAY 'M NOT FOUND IN TABLE'
NOT AT END
WHEN WS-A(I) = WS-SRCH
DISPLAY 'LETTER M FOUND IN TABLE'
END-SEARCH.

* SEARCH ALL - Binary Search; index needs no initialization; not used in multi
dimentional array; table need to be sorted; single WHEN condition allowed
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-TABLE.
05 WS-RECORD OCCURS 10 TIMES ASCENDING KEY IS WS-NUM INDEXED BY I.
10 WS-NUM PIC 9(2).
10 WS-NAME PIC A(3).

PROCEDURE DIVISION.
MOVE '12ABC56DEF34GHI78JKL93MNO11PQR' TO WS-TABLE.

SEARCH ALL WS-RECORD


AT END DISPLAY 'RECORD NOT FOUND'
NOT AT END
WHEN WS-NUM(I) = 93
DISPLAY 'RECORD FOUND '
END-SEARCH.

---

* INTERNAL SORT and MERGE:

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT INPUT ASSIGN TO IN.
SELECT INPUT2 ASSIGN TO IN2.
SELECT OUTPUT ASSIGN TO OUT.
SELECT WORK ASSIGN TO WRK.

DATA DIVISION.
FILE SECTION.
FD INPUT.
01 INPUT-STUDENT.
05 STUDENT-ID-I PIC 9(5).
05 STUDENT-NAME-I PIC A(25).
FD INPUT2.
01 INPUT2-STUDENT.
05 STUDENT-ID-I2 PIC 9(5).
05 STUDENT-NAME-I2 PIC A(25).
FD OUTPUT.
01 OUTPUT-STUDENT.
05 STUDENT-ID-O PIC 9(5).
05 STUDENT-NAME-O PIC A(25).
SD WORK.
01 WORK-STUDENT.
05 STUDENT-ID-W PIC 9(5).
05 STUDENT-NAME-W PIC A(25).

PROCEDURE DIVISION.

SORT WORK ON ASCENDING KEY STUDENT-ID-O


USING INPUT GIVING OUTPUT.

MERGE WORK ON ASCENDING KEY STUDENT-ID-O


USING INPUT, INPUT2 GIVING OUTPUT.

---

00 - Successful
10 - End of file
35 - Try to open OPEN but file not present
39 - File attribute mismatch
33 - All files in concatination are not having same specifications
04 - Invalid fixed length record
41 - Tried to OPEN which is already OPEN
42 - Tried to CLOSE which is not OPEN
47,48,49 - Read/Write/ReWrite performed on file not oppened in proper input mode

02 - AIX duplicate key found in KSDS/RRDS files


20 - Invalid key for KSDS/RRDS
22 - Duplicate Primary key
23 - Key not found in KSDS/RRDS

-----------------------------------------------------------------------------------
--------------------
-----------------------------------------------------------------------------------
--------------------

ACCENTURE history -
Irish based company, headquarters in Dublin, Ireland. Founded by Arthur Andersen.
Employed about 5L+ employees.
CEO JULIE SWEET.
LET THERE BE CHANGE.
Latest VERSIONS -
JCL V1
Enterprise COBOL V5 R2
DB2 V11
CICS/MVS V2 R2
DFSORT V2 R2

COBOL Questions -
1. 4 Sections in Data Division -
File Section(describe externally stored data) ,
Working Storage Section(describe internal data),
Local Storage Section(describe inernal data that is pre-invocation details)
and
Linkage Section(describe data made available by anathor PGM)
2. Difference b/w INCLUDE and COPY
INCLUDE is used for expanding at pre-compiler time and COPY is used for
expanding at compiler time
3. FOREIGN KEYs are attributes of a particular table that have matching entries to
the primary key in another table. Foreign keys are used to build a relation between
any two tables. When two tables related using foreign keys then they are called
DELTE-CONNECTED TABLES, as when primary key deleted will affect foreign key.
4. REFERENTIAL INTEGRITY rule states that consistency needs to be maintained
between primary and foreign keys. In other words, each foreign key needs to have a
primary key.
5. SELF-REFRAINING CONSTRAINT is used to restrict the changes that can be made to
the primary key through a foreign key. To implement this, the foreign key must
define the DELETE CASCADE rule.
6. DEADLOCK in DB2 - When two separate processes are fighting for the same
resources, or the resource reserved for each other, the situation is called a
deadlock. SQL code for a deadlock are -911 and -913.
7. Program abends while processing 30th reccord, how to restart it from 31st
record?
Keep a new file and update counter for every record read
When program abends fetch last counter from above file
Skip those number of records or just perform read
Start processing from next record
8. Error handling in COBOL -
While string and unstring - ON OVERFLOW
While doing Add, Subtract - ON SIZE ERROR
I/P O/P operations on file - know EOF by using AT END, Use file status, use
INVALID KEY
9. SOC4
Description - Protection Exception
Reason -
1. Missing DD statement (Identify using file status in SYSOUT, it will
be 35)
2. File attribute mismatch between DD statement and COBOL (Identify
using file status in SYSOUT, it will be 39)
3. Tried to refer the file record before OPEN statement
4. Missmatch in parameter between calling and called program
5. Index or Subscript is out of range
Analysis -
1. We use ABEND-AID to analyse and solve this
Know which statement casuing error?
Tracing variabeles of the data source
2. Open ABEND-AID and the recent job abend
It will directly show you which statement and para the error is
3. Go to grogram and trace back the source variables in that statement
How to solve -
1. Corrrect the data and re-run - ask SME or data owner for correcting
the data
2. remove the bad record and re-run - copy the original data in a
backup dataset and change the file and re-run
SOC7
Description - Data Exception
Reason -
1. Passing non numeric data into COMP field
2. Performing numeric operations on fields declared as numeric but data
is non numeric
Analysis -
1. We use ABEND-AID to analyse and solve this
Know which statement casuing error?
Tracing variabeles of the data source
2. Open ABEND-AID and the recent job abend
It will directly show you which statement and para the error is
3. Go to grogram and trace back the source variables in that statement
How to solve -
1. Corrrect the data and re-run - ask SME or data owner for correcting
the data
2. remove the bad record and re-run - copy the original data in a
backup dataset and change the file and re-run
IF THERE IS NO TOLL THEN -
1. Try recreating the abened in TEST
2. Add display statements
3. Give O/P DISP=(NEW,CATLG,CATLG) so that when abended o/p file can be
checked for last processed rec

-----------------------------------------------------------------------------------
--------------------
-----------------------------------------------------------------------------------
--------------------

DB2

12. Which utility is used to load data from file into DB2?

//STEP01 EXEC PGM=DB2LOAD,DB2=SSID <==


DB2LOAD load utility
//LOAD.SYSREC00 DD DSN=TEST.TABLE.LOAD,DISP=SHR
<== input file to be loaded
//LOAD.SYSIN DD * <==
file structure input
LOAD DATA INDDN SYSREC00
INTO TABLE EBANK.PHONE
(FULLPHONE POSITION(1:10) CHAR(10)
EXTENSION POSITION(11:5) CHAR(5)
LINENUMBER POSITION(16:5) CHAR(5))
/*
===============
//STEP02 EXEC PGM=IKJEFT01 <== IKJEFT01
unload utility
//SYSTSPRT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSTSIN DD * <== DB2 info
DSN SYSTEM(SSID)
RUN PROGRAM(DSNTIAUL) -
PLAN(DSNTIAUL) -
LIB('TEST.DB2.LOAD') -
PARMS('SQL')
/*
//SYSPUNCH DD DSN=TEST.TABLE.STRTCTURE, <==
File structure output file
// DISP=(NEW,CATLG,DELETE),
// UNIT=DISK,SPACE=(CYL,(1,1),RLSE)
//SYSREC00 DD DSN=TEST.TABLE.LOAD, <==
Data unloaded output file
// DISP=(,CATLG,DELETE),
// UNIT=DISK,SPACE=(CYL,(1,1),RLSE)
//SYSIN DD * <== SQL
query input
SELECT * FROM TST.CLIENT ;
/*
================
//STEP1 EXEC PGM=DSNUTILB,
<== DSNUTILB load utility
// PARM=(SSID,'SHYLENDRA') <==
SSID for DB2
//STEPLIB DD DSN=TEST.PROCLIB,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SYSREC DD DSN=SAMPLE.DATA.FILE,DISP=SHR <==
Input file to be loaded
//SYSCOPY DD DSN=&&SYSCOPY,DISP=(,DELETE,DELETE),SPACE=(CYL,(10,5))
//SORTOUT DD DSN=&&SORTOUT,DISP=(,DELETE,DELETE),SPACE=(CYL,(10,5))
//SYSUT1 DD DSN=&&SYSUT1,DISP=(,DELETE,DELETE),SPACE=(CYL,(10,5))
//SYSMAP DD DSN=&&SYSMAP,DISP=(,DELETE,DELETE),SPACE=(CYL,(10,5))
//SYSIN DD * <==
file structure
LOAD DATA
RESUME YES
INTO TABLE EBANK.PHONE
(FULLPHONE POSITION(1:10) CHAR(10)
EXTENSION POSITION(11:5) CHAR(5)
LINENUMBER POSITION(16:5) CHAR(5))
/*

-----------------------------------------------------------------------------------
--------------------
-----------------------------------------------------------------------------------
--------------------

CICS

13. Common control tables in CICS and their usage?


PCT - Program Control Table
Defines each transaction with TRANID
Contains pair of TRANID and Program
PPT - Program Processing Table
List of valid Programs or Maps
FCT - File Control Table
List of files and their status - open/closed/enabled/disabled
TCT - Terminals Control Table
List of terminals
14. What tables must be updated when adding a new TRANSACTION and PROGRAM?
PCT and PPT must be updated

15. Significance of SYNCPOINT command?


It will end the logical unit of work
to rollback changes using ROLLBACK option of SYNCPOINT command
But when it is not used sync point occurs when task ends

16. Significance of MAPONLY or DATAONLY?


MAPONLY sends only constant data from physical map so no FROM area is used
DATAONLY sends only data from FROM area
If both not used then both contand data from physical data and data from FROM
area are sent

17. CICS commands for Temporary storage queue processing?


WRITEQ TS, READQ TS, DELETEQ TS

18. Difference between EXEC CICS XCTL and EXEC CICS START and EXEC CICS LINK?
XCTL will pass the control to another application having same transaction ID
- continue the task in same terminal
START will initiate new transaction - create new terminal
LINK will pass the control to an application program in lower logical level
and expects control back

CICS - Consumer Information Control System


online OLTP system which allows user to interact with system

CECI - Cics Execute Command Interface


CECI SEND MAP(TR001) MAPSET(TST001) FREEKB,ERASE

EDF - Execution Diagnostic Facility

CEMT - Cics Empty Master Terminal

EIB - Execute Interface Block


It will store Cursor Pos in Map, Trans ID, Terminal ID, Task Number, Length
of Commarea, Current date, time etc

MAPSET > MAPS > FIELDS

DFHMSD - Define Mapset


DFHMDI - Define Maps - size, line, column
DFHMDF - Define Fields - pos, length, initial, attrib, color

-----------------------------------------------------------------------------------
--------------------
-----------------------------------------------------------------------------------
--------------------

12. Questions related to one program calling multiple programs


14. Questions related to SQL statement for selecting 3rd highest, top 10, and self
referencing tables

-------
-------
To reset values of variables in called program (from first call) for second call -
Its sufficient if while compiling link edit option 'RENT' is used.
But if 'REUS' is used then either called program should be coded with 'IS
INITIAL' in PROGRAM_ID or CANCEL issued after first call.
To retain values of variables in called program (from first call) for second call -

Called program should not have 'IS INITIAL' in PROGRAM-ID.


While compiling link edit option 'REUS' must be used.
CANCEL should not be coded after the first call.
-------
-------
How to decide whether sub program called statically or dynamically
If compiled as NODYNAM:
CALL 'literal' is a static call
CALL WS-identifier is a dynamic call

If compiled as DYNAM:
CALL 'literal' is a dynamic call
CALL WS-identifier is a dynamic call

Note: NODYM is default compiler option.


Note: STATIC call is prefered when program functionality does not involve
frequent changes
STATIC call is prefered when speed is a contraint
DYNAMIC call is prefered when frequent changes are involved
DYNAMIC call is prefered when runtime storage space is a contraint
Note: Suppose 1 program called 100 times then STATIC call makes sense and if
100 programs are being called 1 each time then DYNAMIC call makes sense

Note: How To know if PGM calls are STATIC or DYNAMIC?


1. Check source program and list out all CALL statements and note down called
PGM names
2. Follow step 2.1 or step 2.2 to find out list of called programs with
STATIC call
2.1 Use AMBLIST
//STEP0100 EXEC PGM=AMBLIST
//SYSPRINT DD SYSOUT=*
//SYSLIB DD DSN=YOUR LOADLIB,
// DISP=SHR
//SYSIN DD *
LISTIDR DDN=SYSLIB,MEMBER=YOUR PGM NAME
/*
2.2 Use FILEAID
Main Menu > Option 3 - UTILITIES > Option 1 - LIBRARY > Option A
or N - Map CSECT (here specify your load library and member name)
3. Check if there is a CSECT for each of the called PGMs, if present then
that called PGM is STATIC
4. To get list of PGM with Dynamic calls - Remove all static called PGM from
list obtained in step 1
-------
-------

You might also like