SlideShare ist ein Scribd-Unternehmen logo
1 von 21
Downloaden Sie, um offline zu lesen
CICS - Application Programming
DAY 1 – SESSION 2
Updated in Nov 2004
Session 2 : ObjectivesTo understand
The languages that support CICS
CICS Command format and Argument Values
CICS Embedding in COBOL Application program
The CICS Control block EIB
The DFHCOMMAREA
Program preparation and execution
The Task flow
Host Languages
COBOL
Assembler
PL/1
C and C++
Java
CICS Command Format
EXEC CICS function
[option ( argument value)]
[option ( argument value)]
...
[RESP ( argument value)]
END-EXEC
Argument values
Data Value
Data Area
Name
Label
Time in hhmmss format
Pointer Reference
CICS Commands - Examples
EXEC CICS RECEIVE
INTO(WS-INPUT)
LENGTH(WS-IN-LENGTH)
RESP(WS-CICS-RESP-CODE)
END-EXEC.
EXEC CICS SEND
FROM(WS-OUTPUT)
LENGTH(WS-OUT-LENGTH)
RESP(WS-CICS-RESP-CODE)
END-EXEC.
EXEC CICS
RETURN
TRANSID(WS-NXT-TRANSID)
COMMAREA(WS-COMM-AREA)
END-EXEC.
COMMAREAA COMMAREA is a CICS maintained unit of storage for
passing and receiving data between CICS programs
Any changes to the COMMAREA in the linked program,
will be available to the linking program after RETURN
Coded as DFHCOMMAREA in the Linkage Section
Transaction Execution -
COMMAREA
WORKING STORAGE SECTION
01 WS-COMM-AREA
LINKAGE SECTION
01 DFHCOMMAREA
PROCEDURE DIVISION.
……...…...…….
...Processing…
EXEC CICS RETURN TRANSID(‘TXN1’)
COMMAREA(WS-COMM-AREA)
END-EXEC.
First Execution - TXN1
WORKING STORAGE SECTION
01 WS-COMM-AREA
LINKAGE SECTION
01 DFHCOMMAREA
Next Execution - TXN1
Communication Area -
Maintained by CICS
Between Executions
Structure of CICS Application program -
COBOL
IDENTIFICATION DIVISION.
PROGRAM-ID . XXXXXXXX.
ENVIRONMENT DIVISION. <=== THIS DIVISION MUST BE EMPTY
DATA DIVISION. <=== FILE SECTION IS OMITTED
WORKING- STORAGE SECTION.
77 --------------------- .
01 --------------------- .
05 ---------------- .
LINKAGE SECTION. <=== LINKAGE SECTION IS MANDATORY
01 DFHCOMMAREA. <=== COMMUNICATION AREA required for
05 -----------------. passing data for subsequent execs.
PROCEDURE DIVISION .
( COBOL STATEMENTS) + <=== CICS statements mixed with COBOL
( CICS STATEMENTS) statements. Some COBOL verbs not
. allowed.
GOBACK.
Structure of CICS Application
program – COBOL (Contd.)
The following COBOL statements cannot be issued in a CICS
application program.
- ACCEPT - DATE - DISPLAY - EXHIBIT
- RELEASE - SORT - STOP RUN - TRACE
- Any I/O statements ( OPEN ,CLOSE, READ, WRITE,
REWRITE, DELETE , START)
The Execute Interface Block (EIB)
A CICS area that contains information related to the current Task –
data, time, transaction-id
The definition is automatically inserted into the LINKAGE SECTION of
the program before the DFHCOMMAREA at the time of program
translation
EIB variables are available in the copy book DFHEIBLK
Information in the EIB fields can be used for
◦ Handling error/exceptions (EIBRESP, EIBRESP2)
◦ Checking the length of data passed to the program through its DFHCOMMAREA
(EIBCALEN)
◦ Identifying the function key pressed
EIB : ExampleEVALUATE TRUE
WHEN EIBCALEN = ZERO
MOVE LOW-VALUE TO INQMAP10
……..
……..
PERFORM 1400-SEND-CUSTOMER-MAP
WHEN EIBAID = DFHCLEAR
MOVE LOW-VALUE TO INQMAP10
……..
……..
PERFORM 1400-SEND-CUSTOMER-MAP
WHEN EIBAID = DFHPA1 OR DFHPA2 OR DFHPA3
CONTINUE
WHEN EIBAID = DFHPF3 OR DFHPF12
EXEC CICS
……
Sample CICS Program –
COBOL
IDENTIFICATION DIVISION.
PROGRAM-ID . SAMPPROG.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING STORAGE SECTION.
77 WS-LENGTH PIC S9(4) COMP.
77 WS-RESP PIC S9(4) COMP.
01 WS-INPUT.
05 WS-TRAN-IDPIC X(4) .
05 FILLER PIC X.
05 WS-IN-DATA PIC X(15).
01 WS-OUTPUT.
05 WS-MSG_DESC PIC X(17).
05 FILLER PIC X .
05 WS-OUT-DATA PIC X(15).
LINKAGE SECTION.
01 DFHCOMMAREA.
05 LS-COMMAREA PIC X.
PROCEDURE DIVISION.
MOVE 40 TO WS-LENGTH.
MOVE LOW-VALUES TO WS-INPUT
EXEC CICS RECEIVE INTO (WS-INPUT)
LENGTH (WS-LENGTH)
RESP(WS-RESP)
END-EXEC.
IF WS-RESP = DFHRESP(NORMAL)
MOVE LOW-VALUES TO WS-OUTPUT
MOVE WS-IN-DATA TO WS-OUT-DATA
MOVE ‘MSG RECEIVED IS :’
TO WS-MSG-DESC
MOVE 53 TO WS-LENGTH
ELSE
MOVE LOW-VALUES TO WS-OUTPUT
MOVE WS-IN-DATA TO WS-OUT-DATA
MOVE ‘ERROR IN TXN : ’
TO WS-MSG-DESC
MOVE 53 TO WS-LENGTH
END-IF.
EXEC CICS SEND
FROM (WS-OUTPUT)
LENGTH(WS-LENGTH)
END-EXEC.
EXEC CICS
RETURN
END-EXEC .
CICS Program Preparation
Compile
Object
ModuleLink-Edit
Load
Module
Translator
Listing
Compiler
Listing
Translated
Source
Source
Program
Translate
CICS - DB2 Program Preparation
Compile
Object
Module
Link-Edit
Load
Module
Compiler
Listing
Translated
Source
Source
Program
Translator
Listing
Translate
Precompile
Listing
Pre-Compile
Application
Plan
DBRM
Bind
CICS Program Preparation
(Contd.)
COBOL-CICS programs should be compiled with RENT
option to make it Re-entrant.
A CICS-DB2-COBOL program would require a few
more additional steps like a Pre-compile and a Bind.
The pre-compiler would generate a DBRM (Database
Request Module) and the bind will generate a plan
or package using the DBRM.
CICS Security - Sign-on, Sign-
off
Security for accessing CICS system
Until CICS 2.2 users required to be defined as
resources in CICS System Table - Signon Table
(SNT). But with higher releases the SNT has
become obsolete and RACF is used as the External
Security manager.
CESN or CSSN for signon, CESF or CSSF for signoff
CICS Program Execution
Register the transaction in PCT
Register the Programs and Maps in PPT
Sign on to CICS
Enter transaction identifier
Starting a TASK
TXN1 Trans. Program
TXC1 MAPPGC1
TXC2 MAPPGC2
TXN1 TXNPGM1TXN1 TXNPGM1
TXN2 TXNPGM2
PCT
Program. Location
MAPPGC1 In Storage
MAPPGC2 On Disk
TXNPGM1 In StorageTXNPGM1 In Storage
TXNPGM2 On Disk
PPT
Load Module Library
MAPPGC1 MAPLIB
MAPPGC2 MAPLIB
TXNPGM1 PGMLIBTXNPGM1 PGMLIB
TXNPGM2 PGMLIB
CICS Address Space
TXNPGM1
MAPPGC1
CICS Statements after
Translation
Original Source Code :
EXEC CICS
READ DATASET(ACCMSTR) INTO(ACCT-MSTR-DTLS)
RIDFLD(ACCT-NO) RESP(RESP-CODE)
END-EXEC.
Translated Source
* EXEC CICS
* READ DATASET(‘ACCMSTR’) INTO(ACCT-MSTR-DTLS)
* RIDFLD(ACCT-NO) RESP(RESP-CODE)
* END-EXEC.
MOVE ‘..0……00061 ‘ TO DFHEIV0
MOVE ‘ACCMSTR’ TO DFHC0080
MOVE LENGTH OF ACCT-MSTR-DTLS TO DFHB0020
CALL ‘DFHEI1’ USING DFHEIV0 DFHC0080 ACCT-MSTR-DTLS
DFHB0020 ACCT-NO
MOVE EIBRESP TO RESP-CODE.
Session 2 : Summary
Language support and Embedding in COBOL
Command syntax & Argument values
Structure of a CICS application program
Control Block and Common Area to pass data across
programs
Program preparation and Program execution - PCT, PPT
Task flow diagram

Weitere ähnliche Inhalte

Was ist angesagt?

Was ist angesagt? (20)

Skillwise cics part 1
Skillwise cics part 1Skillwise cics part 1
Skillwise cics part 1
 
Parallel Sysplex Implement2
Parallel Sysplex Implement2Parallel Sysplex Implement2
Parallel Sysplex Implement2
 
TCP/IP Stack Configuration with Configuration Assistant for IBM z/OS CS
TCP/IP Stack Configuration with Configuration Assistant for IBM z/OS CSTCP/IP Stack Configuration with Configuration Assistant for IBM z/OS CS
TCP/IP Stack Configuration with Configuration Assistant for IBM z/OS CS
 
Vsam interview questions and answers.
Vsam interview questions and answers.Vsam interview questions and answers.
Vsam interview questions and answers.
 
TN3270 Access to Mainframe SNA Applications
TN3270 Access to Mainframe SNA ApplicationsTN3270 Access to Mainframe SNA Applications
TN3270 Access to Mainframe SNA Applications
 
Networking on z/OS
Networking on z/OSNetworking on z/OS
Networking on z/OS
 
DB2 and storage management
DB2 and storage managementDB2 and storage management
DB2 and storage management
 
IBM SMP/E
IBM SMP/EIBM SMP/E
IBM SMP/E
 
Smpe
SmpeSmpe
Smpe
 
Job Control Language
Job Control LanguageJob Control Language
Job Control Language
 
Mainframe Architecture & Product Overview
Mainframe Architecture & Product OverviewMainframe Architecture & Product Overview
Mainframe Architecture & Product Overview
 
Mvs commands
Mvs commandsMvs commands
Mvs commands
 
z/OS Communications Server Overview
z/OS Communications Server Overviewz/OS Communications Server Overview
z/OS Communications Server Overview
 
MVS ABEND CODES
MVS ABEND CODESMVS ABEND CODES
MVS ABEND CODES
 
Cics cheat sheet
Cics cheat sheetCics cheat sheet
Cics cheat sheet
 
Cics Connectivity
Cics ConnectivityCics Connectivity
Cics Connectivity
 
Ipl process
Ipl processIpl process
Ipl process
 
DB2 Basic Commands - UDB
DB2 Basic Commands - UDBDB2 Basic Commands - UDB
DB2 Basic Commands - UDB
 
Mainframe interview
Mainframe interviewMainframe interview
Mainframe interview
 
Jcl
JclJcl
Jcl
 

Ähnlich wie Cics application programming - session 2

Blue Phoenix Idms Migration
Blue Phoenix Idms MigrationBlue Phoenix Idms Migration
Blue Phoenix Idms MigrationGilShalit
 
Mainframe Technology Overview
Mainframe Technology OverviewMainframe Technology Overview
Mainframe Technology OverviewHaim Ben Zagmi
 
MongoDB.local DC 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local DC 2018: MongoDB Ops Manager + KubernetesMongoDB.local DC 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local DC 2018: MongoDB Ops Manager + KubernetesMongoDB
 
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...Christopher Diamantopoulos
 
DACHSview++features
DACHSview++featuresDACHSview++features
DACHSview++featuresA. Steinhoff
 
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...Faster, more Secure Application Modernization and Replatforming with PKS - Ku...
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...VMware Tanzu
 
MongoDB.local Austin 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local Austin 2018: MongoDB Ops Manager + KubernetesMongoDB.local Austin 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local Austin 2018: MongoDB Ops Manager + KubernetesMongoDB
 
"Wie passen Serverless & Autonomous zusammen?"
"Wie passen Serverless & Autonomous zusammen?""Wie passen Serverless & Autonomous zusammen?"
"Wie passen Serverless & Autonomous zusammen?"Volker Linz
 
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0Thomas Conté
 
WAVV 2009 - Migration to CICS TS for VSE/ESA
WAVV 2009 - Migration to CICS TS for VSE/ESAWAVV 2009 - Migration to CICS TS for VSE/ESA
WAVV 2009 - Migration to CICS TS for VSE/ESAillustrosystems
 
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...Talk Python To Me: Stream Processing in your favourite Language with Beam on ...
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...Aljoscha Krettek
 
Impact2014 session #1317 you have got a friend on z - tales from cics tran...
Impact2014  session #1317   you have got a friend on z - tales from cics tran...Impact2014  session #1317   you have got a friend on z - tales from cics tran...
Impact2014 session #1317 you have got a friend on z - tales from cics tran...Elena Nanos
 
Track A-Compilation guiding and adjusting - IBM
Track A-Compilation guiding and adjusting - IBMTrack A-Compilation guiding and adjusting - IBM
Track A-Compilation guiding and adjusting - IBMchiportal
 
Application Modernisation with PKS
Application Modernisation with PKSApplication Modernisation with PKS
Application Modernisation with PKSPhil Reay
 
Application Modernisation with PKS
Application Modernisation with PKSApplication Modernisation with PKS
Application Modernisation with PKSPhil Reay
 
Logic synthesis with synopsys design compiler
Logic synthesis with synopsys design compilerLogic synthesis with synopsys design compiler
Logic synthesis with synopsys design compilernaeemtayyab
 
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019corehard_by
 
cbmanual
cbmanualcbmanual
cbmanualMatt D
 

Ähnlich wie Cics application programming - session 2 (20)

Blue Phoenix Idms Migration
Blue Phoenix Idms MigrationBlue Phoenix Idms Migration
Blue Phoenix Idms Migration
 
Mainframe Technology Overview
Mainframe Technology OverviewMainframe Technology Overview
Mainframe Technology Overview
 
Model_Driven_Development_SDR
Model_Driven_Development_SDRModel_Driven_Development_SDR
Model_Driven_Development_SDR
 
MongoDB.local DC 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local DC 2018: MongoDB Ops Manager + KubernetesMongoDB.local DC 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local DC 2018: MongoDB Ops Manager + Kubernetes
 
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...
IMAGE CAPTURE, PROCESSING AND TRANSFER VIA ETHERNET UNDER CONTROL OF MATLAB G...
 
DACHSview++features
DACHSview++featuresDACHSview++features
DACHSview++features
 
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...Faster, more Secure Application Modernization and Replatforming with PKS - Ku...
Faster, more Secure Application Modernization and Replatforming with PKS - Ku...
 
MongoDB.local Austin 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local Austin 2018: MongoDB Ops Manager + KubernetesMongoDB.local Austin 2018: MongoDB Ops Manager + Kubernetes
MongoDB.local Austin 2018: MongoDB Ops Manager + Kubernetes
 
"Wie passen Serverless & Autonomous zusammen?"
"Wie passen Serverless & Autonomous zusammen?""Wie passen Serverless & Autonomous zusammen?"
"Wie passen Serverless & Autonomous zusammen?"
 
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0
MS Day EPITA 2010: Visual Studio 2010 et Framework .NET 4.0
 
WAVV 2009 - Migration to CICS TS for VSE/ESA
WAVV 2009 - Migration to CICS TS for VSE/ESAWAVV 2009 - Migration to CICS TS for VSE/ESA
WAVV 2009 - Migration to CICS TS for VSE/ESA
 
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...Talk Python To Me: Stream Processing in your favourite Language with Beam on ...
Talk Python To Me: Stream Processing in your favourite Language with Beam on ...
 
Impact2014 session #1317 you have got a friend on z - tales from cics tran...
Impact2014  session #1317   you have got a friend on z - tales from cics tran...Impact2014  session #1317   you have got a friend on z - tales from cics tran...
Impact2014 session #1317 you have got a friend on z - tales from cics tran...
 
Track A-Compilation guiding and adjusting - IBM
Track A-Compilation guiding and adjusting - IBMTrack A-Compilation guiding and adjusting - IBM
Track A-Compilation guiding and adjusting - IBM
 
Application Modernisation with PKS
Application Modernisation with PKSApplication Modernisation with PKS
Application Modernisation with PKS
 
Application Modernisation with PKS
Application Modernisation with PKSApplication Modernisation with PKS
Application Modernisation with PKS
 
Cobol
CobolCobol
Cobol
 
Logic synthesis with synopsys design compiler
Logic synthesis with synopsys design compilerLogic synthesis with synopsys design compiler
Logic synthesis with synopsys design compiler
 
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019
The Hitchhiker's Guide to Faster Builds. Viktor Kirilov. CoreHard Spring 2019
 
cbmanual
cbmanualcbmanual
cbmanual
 

Mehr von Srinimf-Slides

software-life-cycle.pptx
software-life-cycle.pptxsoftware-life-cycle.pptx
software-life-cycle.pptxSrinimf-Slides
 
Python Tutorial Questions part-1
Python Tutorial Questions part-1Python Tutorial Questions part-1
Python Tutorial Questions part-1Srinimf-Slides
 
Cics data access-session 4
Cics data access-session 4Cics data access-session 4
Cics data access-session 4Srinimf-Slides
 
The best Teradata RDBMS introduction a quick refresher
The best Teradata RDBMS introduction a quick refresherThe best Teradata RDBMS introduction a quick refresher
The best Teradata RDBMS introduction a quick refresherSrinimf-Slides
 
The best ETL questions in a nut shell
The best ETL questions in a nut shellThe best ETL questions in a nut shell
The best ETL questions in a nut shellSrinimf-Slides
 
IMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialIMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialSrinimf-Slides
 
How To Master PACBASE For Mainframe In Only Seven Days
How To Master PACBASE For Mainframe In Only Seven DaysHow To Master PACBASE For Mainframe In Only Seven Days
How To Master PACBASE For Mainframe In Only Seven DaysSrinimf-Slides
 
Assembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersAssembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersSrinimf-Slides
 
The Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfThe Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfSrinimf-Slides
 
Writing command macro in stratus cobol
Writing command macro in stratus cobolWriting command macro in stratus cobol
Writing command macro in stratus cobolSrinimf-Slides
 
PLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersPLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersSrinimf-Slides
 
PL/SQL Interview Questions
PL/SQL Interview QuestionsPL/SQL Interview Questions
PL/SQL Interview QuestionsSrinimf-Slides
 
Oracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideOracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideSrinimf-Slides
 
20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview QuestionsSrinimf-Slides
 

Mehr von Srinimf-Slides (20)

software-life-cycle.pptx
software-life-cycle.pptxsoftware-life-cycle.pptx
software-life-cycle.pptx
 
Python Tutorial Questions part-1
Python Tutorial Questions part-1Python Tutorial Questions part-1
Python Tutorial Questions part-1
 
Cics data access-session 4
Cics data access-session 4Cics data access-session 4
Cics data access-session 4
 
100 sql queries
100 sql queries100 sql queries
100 sql queries
 
The best Teradata RDBMS introduction a quick refresher
The best Teradata RDBMS introduction a quick refresherThe best Teradata RDBMS introduction a quick refresher
The best Teradata RDBMS introduction a quick refresher
 
The best ETL questions in a nut shell
The best ETL questions in a nut shellThe best ETL questions in a nut shell
The best ETL questions in a nut shell
 
IMS DC Self Study Complete Tutorial
IMS DC Self Study Complete TutorialIMS DC Self Study Complete Tutorial
IMS DC Self Study Complete Tutorial
 
How To Master PACBASE For Mainframe In Only Seven Days
How To Master PACBASE For Mainframe In Only Seven DaysHow To Master PACBASE For Mainframe In Only Seven Days
How To Master PACBASE For Mainframe In Only Seven Days
 
Assembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe ProgrammersAssembler Language Tutorial for Mainframe Programmers
Assembler Language Tutorial for Mainframe Programmers
 
The Easytrieve Presention by Srinimf
The Easytrieve Presention by SrinimfThe Easytrieve Presention by Srinimf
The Easytrieve Presention by Srinimf
 
Writing command macro in stratus cobol
Writing command macro in stratus cobolWriting command macro in stratus cobol
Writing command macro in stratus cobol
 
PLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe ProgrammersPLI Presentation for Mainframe Programmers
PLI Presentation for Mainframe Programmers
 
PL/SQL Interview Questions
PL/SQL Interview QuestionsPL/SQL Interview Questions
PL/SQL Interview Questions
 
Macro teradata
Macro teradataMacro teradata
Macro teradata
 
DB2-SQL Part-2
DB2-SQL Part-2DB2-SQL Part-2
DB2-SQL Part-2
 
DB2 SQL-Part-1
DB2 SQL-Part-1DB2 SQL-Part-1
DB2 SQL-Part-1
 
Teradata - Utilities
Teradata - UtilitiesTeradata - Utilities
Teradata - Utilities
 
Oracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step GuideOracle PLSQL Step By Step Guide
Oracle PLSQL Step By Step Guide
 
Hirarchical vs RDBMS
Hirarchical vs RDBMSHirarchical vs RDBMS
Hirarchical vs RDBMS
 
20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions20 DFSORT Tricks For Zos Users - Interview Questions
20 DFSORT Tricks For Zos Users - Interview Questions
 

Kürzlich hochgeladen

Videogame localization & technology_ how to enhance the power of translation.pdf
Videogame localization & technology_ how to enhance the power of translation.pdfVideogame localization & technology_ how to enhance the power of translation.pdf
Videogame localization & technology_ how to enhance the power of translation.pdfinfogdgmi
 
Designing A Time bound resource download URL
Designing A Time bound resource download URLDesigning A Time bound resource download URL
Designing A Time bound resource download URLRuncy Oommen
 
UiPath Studio Web workshop series - Day 7
UiPath Studio Web workshop series - Day 7UiPath Studio Web workshop series - Day 7
UiPath Studio Web workshop series - Day 7DianaGray10
 
Cybersecurity Workshop #1.pptx
Cybersecurity Workshop #1.pptxCybersecurity Workshop #1.pptx
Cybersecurity Workshop #1.pptxGDSC PJATK
 
UiPath Platform: The Backend Engine Powering Your Automation - Session 1
UiPath Platform: The Backend Engine Powering Your Automation - Session 1UiPath Platform: The Backend Engine Powering Your Automation - Session 1
UiPath Platform: The Backend Engine Powering Your Automation - Session 1DianaGray10
 
How Accurate are Carbon Emissions Projections?
How Accurate are Carbon Emissions Projections?How Accurate are Carbon Emissions Projections?
How Accurate are Carbon Emissions Projections?IES VE
 
Linked Data in Production: Moving Beyond Ontologies
Linked Data in Production: Moving Beyond OntologiesLinked Data in Production: Moving Beyond Ontologies
Linked Data in Production: Moving Beyond OntologiesDavid Newbury
 
Salesforce Miami User Group Event - 1st Quarter 2024
Salesforce Miami User Group Event - 1st Quarter 2024Salesforce Miami User Group Event - 1st Quarter 2024
Salesforce Miami User Group Event - 1st Quarter 2024SkyPlanner
 
Building AI-Driven Apps Using Semantic Kernel.pptx
Building AI-Driven Apps Using Semantic Kernel.pptxBuilding AI-Driven Apps Using Semantic Kernel.pptx
Building AI-Driven Apps Using Semantic Kernel.pptxUdaiappa Ramachandran
 
Computer 10: Lesson 10 - Online Crimes and Hazards
Computer 10: Lesson 10 - Online Crimes and HazardsComputer 10: Lesson 10 - Online Crimes and Hazards
Computer 10: Lesson 10 - Online Crimes and HazardsSeth Reyes
 
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdf
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdfUiPath Solutions Management Preview - Northern CA Chapter - March 22.pdf
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdfDianaGray10
 
9 Steps For Building Winning Founding Team
9 Steps For Building Winning Founding Team9 Steps For Building Winning Founding Team
9 Steps For Building Winning Founding TeamAdam Moalla
 
Machine Learning Model Validation (Aijun Zhang 2024).pdf
Machine Learning Model Validation (Aijun Zhang 2024).pdfMachine Learning Model Validation (Aijun Zhang 2024).pdf
Machine Learning Model Validation (Aijun Zhang 2024).pdfAijun Zhang
 
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...DianaGray10
 
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPA
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPAAnypoint Code Builder , Google Pub sub connector and MuleSoft RPA
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPAshyamraj55
 
Bird eye's view on Camunda open source ecosystem
Bird eye's view on Camunda open source ecosystemBird eye's view on Camunda open source ecosystem
Bird eye's view on Camunda open source ecosystemAsko Soukka
 
Comparing Sidecar-less Service Mesh from Cilium and Istio
Comparing Sidecar-less Service Mesh from Cilium and IstioComparing Sidecar-less Service Mesh from Cilium and Istio
Comparing Sidecar-less Service Mesh from Cilium and IstioChristian Posta
 
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdf
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdfIaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdf
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdfDaniel Santiago Silva Capera
 

Kürzlich hochgeladen (20)

Videogame localization & technology_ how to enhance the power of translation.pdf
Videogame localization & technology_ how to enhance the power of translation.pdfVideogame localization & technology_ how to enhance the power of translation.pdf
Videogame localization & technology_ how to enhance the power of translation.pdf
 
Designing A Time bound resource download URL
Designing A Time bound resource download URLDesigning A Time bound resource download URL
Designing A Time bound resource download URL
 
UiPath Studio Web workshop series - Day 7
UiPath Studio Web workshop series - Day 7UiPath Studio Web workshop series - Day 7
UiPath Studio Web workshop series - Day 7
 
Cybersecurity Workshop #1.pptx
Cybersecurity Workshop #1.pptxCybersecurity Workshop #1.pptx
Cybersecurity Workshop #1.pptx
 
UiPath Platform: The Backend Engine Powering Your Automation - Session 1
UiPath Platform: The Backend Engine Powering Your Automation - Session 1UiPath Platform: The Backend Engine Powering Your Automation - Session 1
UiPath Platform: The Backend Engine Powering Your Automation - Session 1
 
201610817 - edge part1
201610817 - edge part1201610817 - edge part1
201610817 - edge part1
 
How Accurate are Carbon Emissions Projections?
How Accurate are Carbon Emissions Projections?How Accurate are Carbon Emissions Projections?
How Accurate are Carbon Emissions Projections?
 
Linked Data in Production: Moving Beyond Ontologies
Linked Data in Production: Moving Beyond OntologiesLinked Data in Production: Moving Beyond Ontologies
Linked Data in Production: Moving Beyond Ontologies
 
Salesforce Miami User Group Event - 1st Quarter 2024
Salesforce Miami User Group Event - 1st Quarter 2024Salesforce Miami User Group Event - 1st Quarter 2024
Salesforce Miami User Group Event - 1st Quarter 2024
 
Building AI-Driven Apps Using Semantic Kernel.pptx
Building AI-Driven Apps Using Semantic Kernel.pptxBuilding AI-Driven Apps Using Semantic Kernel.pptx
Building AI-Driven Apps Using Semantic Kernel.pptx
 
Computer 10: Lesson 10 - Online Crimes and Hazards
Computer 10: Lesson 10 - Online Crimes and HazardsComputer 10: Lesson 10 - Online Crimes and Hazards
Computer 10: Lesson 10 - Online Crimes and Hazards
 
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdf
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdfUiPath Solutions Management Preview - Northern CA Chapter - March 22.pdf
UiPath Solutions Management Preview - Northern CA Chapter - March 22.pdf
 
9 Steps For Building Winning Founding Team
9 Steps For Building Winning Founding Team9 Steps For Building Winning Founding Team
9 Steps For Building Winning Founding Team
 
Machine Learning Model Validation (Aijun Zhang 2024).pdf
Machine Learning Model Validation (Aijun Zhang 2024).pdfMachine Learning Model Validation (Aijun Zhang 2024).pdf
Machine Learning Model Validation (Aijun Zhang 2024).pdf
 
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...
Connector Corner: Extending LLM automation use cases with UiPath GenAI connec...
 
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPA
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPAAnypoint Code Builder , Google Pub sub connector and MuleSoft RPA
Anypoint Code Builder , Google Pub sub connector and MuleSoft RPA
 
Bird eye's view on Camunda open source ecosystem
Bird eye's view on Camunda open source ecosystemBird eye's view on Camunda open source ecosystem
Bird eye's view on Camunda open source ecosystem
 
Comparing Sidecar-less Service Mesh from Cilium and Istio
Comparing Sidecar-less Service Mesh from Cilium and IstioComparing Sidecar-less Service Mesh from Cilium and Istio
Comparing Sidecar-less Service Mesh from Cilium and Istio
 
20230104 - machine vision
20230104 - machine vision20230104 - machine vision
20230104 - machine vision
 
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdf
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdfIaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdf
IaC & GitOps in a Nutshell - a FridayInANuthshell Episode.pdf
 

Cics application programming - session 2

  • 1. CICS - Application Programming DAY 1 – SESSION 2 Updated in Nov 2004
  • 2. Session 2 : ObjectivesTo understand The languages that support CICS CICS Command format and Argument Values CICS Embedding in COBOL Application program The CICS Control block EIB The DFHCOMMAREA Program preparation and execution The Task flow
  • 4. CICS Command Format EXEC CICS function [option ( argument value)] [option ( argument value)] ... [RESP ( argument value)] END-EXEC
  • 5. Argument values Data Value Data Area Name Label Time in hhmmss format Pointer Reference
  • 6. CICS Commands - Examples EXEC CICS RECEIVE INTO(WS-INPUT) LENGTH(WS-IN-LENGTH) RESP(WS-CICS-RESP-CODE) END-EXEC. EXEC CICS SEND FROM(WS-OUTPUT) LENGTH(WS-OUT-LENGTH) RESP(WS-CICS-RESP-CODE) END-EXEC. EXEC CICS RETURN TRANSID(WS-NXT-TRANSID) COMMAREA(WS-COMM-AREA) END-EXEC.
  • 7. COMMAREAA COMMAREA is a CICS maintained unit of storage for passing and receiving data between CICS programs Any changes to the COMMAREA in the linked program, will be available to the linking program after RETURN Coded as DFHCOMMAREA in the Linkage Section
  • 8. Transaction Execution - COMMAREA WORKING STORAGE SECTION 01 WS-COMM-AREA LINKAGE SECTION 01 DFHCOMMAREA PROCEDURE DIVISION. ……...…...……. ...Processing… EXEC CICS RETURN TRANSID(‘TXN1’) COMMAREA(WS-COMM-AREA) END-EXEC. First Execution - TXN1 WORKING STORAGE SECTION 01 WS-COMM-AREA LINKAGE SECTION 01 DFHCOMMAREA Next Execution - TXN1 Communication Area - Maintained by CICS Between Executions
  • 9. Structure of CICS Application program - COBOL IDENTIFICATION DIVISION. PROGRAM-ID . XXXXXXXX. ENVIRONMENT DIVISION. <=== THIS DIVISION MUST BE EMPTY DATA DIVISION. <=== FILE SECTION IS OMITTED WORKING- STORAGE SECTION. 77 --------------------- . 01 --------------------- . 05 ---------------- . LINKAGE SECTION. <=== LINKAGE SECTION IS MANDATORY 01 DFHCOMMAREA. <=== COMMUNICATION AREA required for 05 -----------------. passing data for subsequent execs. PROCEDURE DIVISION . ( COBOL STATEMENTS) + <=== CICS statements mixed with COBOL ( CICS STATEMENTS) statements. Some COBOL verbs not . allowed. GOBACK.
  • 10. Structure of CICS Application program – COBOL (Contd.) The following COBOL statements cannot be issued in a CICS application program. - ACCEPT - DATE - DISPLAY - EXHIBIT - RELEASE - SORT - STOP RUN - TRACE - Any I/O statements ( OPEN ,CLOSE, READ, WRITE, REWRITE, DELETE , START)
  • 11. The Execute Interface Block (EIB) A CICS area that contains information related to the current Task – data, time, transaction-id The definition is automatically inserted into the LINKAGE SECTION of the program before the DFHCOMMAREA at the time of program translation EIB variables are available in the copy book DFHEIBLK Information in the EIB fields can be used for ◦ Handling error/exceptions (EIBRESP, EIBRESP2) ◦ Checking the length of data passed to the program through its DFHCOMMAREA (EIBCALEN) ◦ Identifying the function key pressed
  • 12. EIB : ExampleEVALUATE TRUE WHEN EIBCALEN = ZERO MOVE LOW-VALUE TO INQMAP10 …….. …….. PERFORM 1400-SEND-CUSTOMER-MAP WHEN EIBAID = DFHCLEAR MOVE LOW-VALUE TO INQMAP10 …….. …….. PERFORM 1400-SEND-CUSTOMER-MAP WHEN EIBAID = DFHPA1 OR DFHPA2 OR DFHPA3 CONTINUE WHEN EIBAID = DFHPF3 OR DFHPF12 EXEC CICS ……
  • 13. Sample CICS Program – COBOL IDENTIFICATION DIVISION. PROGRAM-ID . SAMPPROG. ENVIRONMENT DIVISION. DATA DIVISION. WORKING STORAGE SECTION. 77 WS-LENGTH PIC S9(4) COMP. 77 WS-RESP PIC S9(4) COMP. 01 WS-INPUT. 05 WS-TRAN-IDPIC X(4) . 05 FILLER PIC X. 05 WS-IN-DATA PIC X(15). 01 WS-OUTPUT. 05 WS-MSG_DESC PIC X(17). 05 FILLER PIC X . 05 WS-OUT-DATA PIC X(15). LINKAGE SECTION. 01 DFHCOMMAREA. 05 LS-COMMAREA PIC X. PROCEDURE DIVISION. MOVE 40 TO WS-LENGTH. MOVE LOW-VALUES TO WS-INPUT EXEC CICS RECEIVE INTO (WS-INPUT) LENGTH (WS-LENGTH) RESP(WS-RESP) END-EXEC. IF WS-RESP = DFHRESP(NORMAL) MOVE LOW-VALUES TO WS-OUTPUT MOVE WS-IN-DATA TO WS-OUT-DATA MOVE ‘MSG RECEIVED IS :’ TO WS-MSG-DESC MOVE 53 TO WS-LENGTH ELSE MOVE LOW-VALUES TO WS-OUTPUT MOVE WS-IN-DATA TO WS-OUT-DATA MOVE ‘ERROR IN TXN : ’ TO WS-MSG-DESC MOVE 53 TO WS-LENGTH END-IF. EXEC CICS SEND FROM (WS-OUTPUT) LENGTH(WS-LENGTH) END-EXEC. EXEC CICS RETURN END-EXEC .
  • 15. CICS - DB2 Program Preparation Compile Object Module Link-Edit Load Module Compiler Listing Translated Source Source Program Translator Listing Translate Precompile Listing Pre-Compile Application Plan DBRM Bind
  • 16. CICS Program Preparation (Contd.) COBOL-CICS programs should be compiled with RENT option to make it Re-entrant. A CICS-DB2-COBOL program would require a few more additional steps like a Pre-compile and a Bind. The pre-compiler would generate a DBRM (Database Request Module) and the bind will generate a plan or package using the DBRM.
  • 17. CICS Security - Sign-on, Sign- off Security for accessing CICS system Until CICS 2.2 users required to be defined as resources in CICS System Table - Signon Table (SNT). But with higher releases the SNT has become obsolete and RACF is used as the External Security manager. CESN or CSSN for signon, CESF or CSSF for signoff
  • 18. CICS Program Execution Register the transaction in PCT Register the Programs and Maps in PPT Sign on to CICS Enter transaction identifier
  • 19. Starting a TASK TXN1 Trans. Program TXC1 MAPPGC1 TXC2 MAPPGC2 TXN1 TXNPGM1TXN1 TXNPGM1 TXN2 TXNPGM2 PCT Program. Location MAPPGC1 In Storage MAPPGC2 On Disk TXNPGM1 In StorageTXNPGM1 In Storage TXNPGM2 On Disk PPT Load Module Library MAPPGC1 MAPLIB MAPPGC2 MAPLIB TXNPGM1 PGMLIBTXNPGM1 PGMLIB TXNPGM2 PGMLIB CICS Address Space TXNPGM1 MAPPGC1
  • 20. CICS Statements after Translation Original Source Code : EXEC CICS READ DATASET(ACCMSTR) INTO(ACCT-MSTR-DTLS) RIDFLD(ACCT-NO) RESP(RESP-CODE) END-EXEC. Translated Source * EXEC CICS * READ DATASET(‘ACCMSTR’) INTO(ACCT-MSTR-DTLS) * RIDFLD(ACCT-NO) RESP(RESP-CODE) * END-EXEC. MOVE ‘..0……00061 ‘ TO DFHEIV0 MOVE ‘ACCMSTR’ TO DFHC0080 MOVE LENGTH OF ACCT-MSTR-DTLS TO DFHB0020 CALL ‘DFHEI1’ USING DFHEIV0 DFHC0080 ACCT-MSTR-DTLS DFHB0020 ACCT-NO MOVE EIBRESP TO RESP-CODE.
  • 21. Session 2 : Summary Language support and Embedding in COBOL Command syntax & Argument values Structure of a CICS application program Control Block and Common Area to pass data across programs Program preparation and Program execution - PCT, PPT Task flow diagram