SlideShare a Scribd company logo
CICS - DATA ACCESS
DAY 2 - SESSION 4
Updated in Nov 2004
Session 4 : ObjectivesTo Understand
CICS File handling Concepts
VSAM file types supported
VSAM File control Commands
VSAM File Browse Commands
Exceptions in File Handling
CICS-Database access : DB2 & IMS/DB
CICS Data Management
CICS and Database
Overview
RCT
CICS – VSAM File Handling
Supports VSAM
◦ BDAM supported in earlier versions of CICS
Files to be defined to CICS as resources in the FCT
File Opening, Closing done by CICS
Provides interface for
◦ Random access
◦ Sequential access
◦ Read, Write, Update, Delete
File Access Methods - VSAM
VSAM is the primary data access method for CICS
VSAM file types supported
◦ Key Sequenced Data Set (KSDS)
◦ Entry Sequenced Data Set (ESDS)
◦ Relative Record Data Set (RRDS)
Entry Sequenced Data Set
(ESDS)
Records to be
entered into
the data set
VSAM ESDS
ESDS - Relative Byte
Address
100
BYTES
REC1
200
BYTES
REC2
300
BYTES
REC3
0 100 200
RBA of REC3
is 200
Key Sequenced Data Set
(KSDS)
60
40
Key Field
20 25 58 63
Records For
Insert
Relative Record Data Set (RRDS)
REC3
REC1 REC2
REC5
REC3
SLOT 1 SLOT 2 SLOT 3 SLOT 4 SLOT 5
Record identification (RIDFLD)
RECORD KEY
PARTIAL KEY
RELATIVE BYTE ADDRESS (RBA)
RELATIVE RECORD NUMBER (RRN)
VSAM File – Random Access
Random Access
READ
WRITE a new record
REWRITE a record previously ‘read for update’
DELETE
UNLOCK a record previously ‘read for update’
VSAM File – Sequential
AccessSequential Read (Browsing)
Start Browsing
Read Next
Read Previous
End Browsing
Reset Browsing conditions
VSAM - READ from File :
Syntax
EXEC CICS READ DATASET(file-name)
INTO (rec-area)
LENGTH(record_length)]
RIDFLD(key-value)
RBA | RRN]
GENERIC]
KEYLENGTH(key-length)]
[UPDATE]
[GTEQ | EQUAL]
END-EXEC.
VSAM - READ from FILE : Example
WORKING- STORAGE SECTION.
77 WS-REC-LEN PIC S9(4) COMP.
77 WS-FILE-NAME PIC X(8) VALUE ‘ACCTMSTR’
01 WS-FILE-REC
05 WS-REC-KEY PIC X(6).
05 WS-REC-DATA PIC X(34).
PROCEDURE DIVISION.
MOVE 40 TO WS-REC-LEN.
MOVE ‘ABC451’ TO WS-REC-KEY.
EXEC CICS READ DATASET(WS-FILE-NAME)
INTO (WS-FILE-REC)
RIDFLD(WS-REC-KEY)
LENGTH(WS-REC-LEN)
END-EXEC.
VSAM – Steps to Add New
Records
WRITE NEW
RECORD
SET UP DATA VALUES
FOR NEW RECORD
MOVE KEY VALUE
TO RID FIELD
VSAM – Write to File : Syntax
EXEC CICS WRITE
DATASET(file-name)
FROM(file-rec)
LENGTH(rec-length)
RIDFLD(rec-key)
[RBA | RRN]
END-EXEC.
VSAM - File Update : Syntax
EXEC CICS REWRITE
DATASET (file-name)
FROM (data-area)
[LENGTH (rec-len)
END EXEC.
VSAM – File UnlockTo release a record previously read for update
EXEC CICS UNLOCK
FILE / DATASET (name)
END-EXEC.
VSAM - Delete From File :
Syntax
EXEC CICS DELETE
DATASET (file-name)
RIDFLD(rec-key)
[KEY-LENGTH(key-length)]
[GENERIC[NUMREC(rec-number)]]
[RBA | RRN]
END-EXEC.
VSAM - BROWSE Operation
ESTABLISH START
POSITION
RETRIEVE
NEXT RECORD
PROCESS
RECORD?
TERMINATE
BROWSE
END OF
BROWSE?
PROCESS
CHANGE
POSITION
YES
YES
YES
NO
NO
NO
VSAM - BROWSE CommandsSTARTBR - Establish starting position within file
READNEXT - Retrieve records in ascending order
sequentially as set by STARTBR
READPREV - Retrieve Records in descending
(reverse) order as set by STARTBR
RESETBR - Restart Browse by re-positioning the
pointer
ENDBR - Terminate Browse
VSAM - BROWSE : Example
MOVE ‘VALUE’ TO KEY-REC
EXEC CICS STARTBR FILE(‘FILEA’)
RIDFLD(RECKEY) RESP(ERR-CODE)
END-EXEC.
IF ERR-CODE = DFHRESP(NORMAL)
PERFORM UNTIL ERR-CODE = DFHRESP(ENDFILE).
PERFORM 2000-REC-FROM-FILE
UNTIL 2000-REC-FROM-FIL-EXIT
EXEC CICS READNEXT FILE(‘FILEA’)
INTO(FILEREC) RIDFLD(RECKEY)
RESP(ERR-CODE)
END-EXEC
END-PERFORM
EXEC CICS ENDBR FILE(‘FILEA’) …. END-EXEC
ELSE
PERFORM 9000-HANDLE-ERROR …..
END-IF.
File Handling - Exceptional
Conditions
Processing Information
◦ NOTFND
◦ ENDFILE
◦ LENGERR
Application Program Error
◦ INVREQ
◦ FILENOTFOUND
◦ ILLOGIC
◦ DUPREC
External Conditions
◦ IOERR
◦ DISABLED
◦ NOTOPEN
◦ NOSPACE
File Handling - Program
Organization
WORKING STORAGE
RECORD LAYOUT DEFINITION
RECORD ID FIELD
LINKAGE SECTION
EIB
PROCEDURE DIVISION
IDENTIFY KEY OF THE RECORD TO BE READ
EXEC CICS READ FILE....
CICS - Database Access
Provides Interface to
◦Hierarchical Database - IMS/DB
◦Relational Database - DB2
DB2 Database Access from
CICS
Terminal Users
CICS subsystem
CICS subsystem
Terminal Control & BMS modules
CICS - DB2 Attachment Facility Modules
DB2 Sub system
Appl.
pgm1
Appl.
pgm2
Appl.
pgm3
Threads
Tables, Files
Stored on disk
Other CICS
Modules
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
Files - Data Tables
New feature of storing VSAM files in virtual
storage
Improved performance
◦ User Maintained Table(UMT)
◦ CICS Maintained Table (CMT)
◦ Shared Data Tables
Transparent to application program
Session 4 : Summary
CICS File handling - use of FCT
VSAM file types Supported - Random Access & Sequential
Read
File control commands - READ, WRITE, REWRITE, DELETE
Browse commands – STARTBR, READNEXT, READPREV,
RESETBR, ENDBR
Exceptional Conditions in File Handling
CICS-DB2 program preparation; RCT entries

More Related Content

PPTX
Mass storage structure
PDF
HDFS_Command_Reference
PPTX
Mass storage systemsos
PPT
Linux lecture5
DOC
White Paper, System Z Dataset Naming Standards
PPT
Ch10
PPT
11.file system implementation
PPTX
Massstorage
Mass storage structure
HDFS_Command_Reference
Mass storage systemsos
Linux lecture5
White Paper, System Z Dataset Naming Standards
Ch10
11.file system implementation
Massstorage

What's hot (20)

PPT
I/O System and Csae Study
PPT
Compression Commands in Linux
PPTX
Sheik Mohamed Shadik - BSc - Project Details
DOCX
Mass storage structurefinal
PPTX
PPT
PPT
Chapter 12 - Mass Storage Systems
PPSX
Linux04 dns 2
PPT
PPT
PPT
operating system
PPT
Pandi
PPTX
Mass Storage Structure
PPTX
Hadoop Interacting with HDFS
PPTX
2 introduction of storage
PPTX
Magnetism data addressing
I/O System and Csae Study
Compression Commands in Linux
Sheik Mohamed Shadik - BSc - Project Details
Mass storage structurefinal
Chapter 12 - Mass Storage Systems
Linux04 dns 2
operating system
Pandi
Mass Storage Structure
Hadoop Interacting with HDFS
2 introduction of storage
Magnetism data addressing
Ad

Similar to Cics data access-session 4 (20)

PPT
Oracle apps dba training dba technologies
PPT
Seismic Analysis Code (SAC)
PPT
Dns introduction
PDF
Colvin RMAN New Features
PPT
WAVV 2009 - Migration to CICS TS for VSE/ESA
PPT
Intro to IDMS
PPTX
Oracle ASM Training
PPT
Introduction to dns domain name syst.ppt
PPT
Les 01 Arch
PPTX
DNS-overview.pptx
PPT
040419 san forum
PDF
Apache: Big Data - Starting with Apache Spark, Best Practices
PPT
Champion Fas Deduplication
PDF
RMAN in 12c: The Next Generation (PPT)
PPT
Dpm Disaster Recovery Sonvu
PDF
CICS Configuration Manager - flexibility and control
PPT
Introduction.ppt
PPT
Introduction.ppt
PPT
Ssm Appliance Ssm Demo
ODP
Oracle apps dba training dba technologies
Seismic Analysis Code (SAC)
Dns introduction
Colvin RMAN New Features
WAVV 2009 - Migration to CICS TS for VSE/ESA
Intro to IDMS
Oracle ASM Training
Introduction to dns domain name syst.ppt
Les 01 Arch
DNS-overview.pptx
040419 san forum
Apache: Big Data - Starting with Apache Spark, Best Practices
Champion Fas Deduplication
RMAN in 12c: The Next Generation (PPT)
Dpm Disaster Recovery Sonvu
CICS Configuration Manager - flexibility and control
Introduction.ppt
Introduction.ppt
Ssm Appliance Ssm Demo
Ad

More from Srinimf-Slides (20)

PPTX
software-life-cycle.pptx
PDF
Python Tutorial Questions part-1
PPT
Cics testing and debugging-session 7
PPT
CICS error and exception handling-recovery and restart-session 6
PPT
Cics program, interval and task control commands-session 5
PPT
CICS basic mapping support - session 3
PPT
Cics application programming - session 2
PPT
CICS basics overview session-1
PPTX
100 sql queries
PDF
The best Teradata RDBMS introduction a quick refresher
PDF
The best ETL questions in a nut shell
PDF
IMS DC Self Study Complete Tutorial
PPT
How To Master PACBASE For Mainframe In Only Seven Days
PPT
Assembler Language Tutorial for Mainframe Programmers
PPT
The Easytrieve Presention by Srinimf
PPTX
Writing command macro in stratus cobol
PPT
PLI Presentation for Mainframe Programmers
PPTX
PL/SQL Interview Questions
PPTX
Macro teradata
PPTX
DB2-SQL Part-2
software-life-cycle.pptx
Python Tutorial Questions part-1
Cics testing and debugging-session 7
CICS error and exception handling-recovery and restart-session 6
Cics program, interval and task control commands-session 5
CICS basic mapping support - session 3
Cics application programming - session 2
CICS basics overview session-1
100 sql queries
The best Teradata RDBMS introduction a quick refresher
The best ETL questions in a nut shell
IMS DC Self Study Complete Tutorial
How To Master PACBASE For Mainframe In Only Seven Days
Assembler Language Tutorial for Mainframe Programmers
The Easytrieve Presention by Srinimf
Writing command macro in stratus cobol
PLI Presentation for Mainframe Programmers
PL/SQL Interview Questions
Macro teradata
DB2-SQL Part-2

Recently uploaded (20)

PDF
Unlocking AI with Model Context Protocol (MCP)
PDF
NewMind AI Weekly Chronicles - August'25 Week I
PPTX
VMware vSphere Foundation How to Sell Presentation-Ver1.4-2-14-2024.pptx
PPT
“AI and Expert System Decision Support & Business Intelligence Systems”
PDF
Chapter 3 Spatial Domain Image Processing.pdf
PDF
cuic standard and advanced reporting.pdf
PDF
Encapsulation theory and applications.pdf
PPTX
PA Analog/Digital System: The Backbone of Modern Surveillance and Communication
PPTX
Detection-First SIEM: Rule Types, Dashboards, and Threat-Informed Strategy
PPTX
Understanding_Digital_Forensics_Presentation.pptx
PDF
CIFDAQ's Market Insight: SEC Turns Pro Crypto
PDF
TokAI - TikTok AI Agent : The First AI Application That Analyzes 10,000+ Vira...
PDF
Network Security Unit 5.pdf for BCA BBA.
PDF
Advanced methodologies resolving dimensionality complications for autism neur...
PDF
Electronic commerce courselecture one. Pdf
PPT
Teaching material agriculture food technology
PPTX
Cloud computing and distributed systems.
PDF
Peak of Data & AI Encore- AI for Metadata and Smarter Workflows
PPTX
Digital-Transformation-Roadmap-for-Companies.pptx
PDF
How UI/UX Design Impacts User Retention in Mobile Apps.pdf
Unlocking AI with Model Context Protocol (MCP)
NewMind AI Weekly Chronicles - August'25 Week I
VMware vSphere Foundation How to Sell Presentation-Ver1.4-2-14-2024.pptx
“AI and Expert System Decision Support & Business Intelligence Systems”
Chapter 3 Spatial Domain Image Processing.pdf
cuic standard and advanced reporting.pdf
Encapsulation theory and applications.pdf
PA Analog/Digital System: The Backbone of Modern Surveillance and Communication
Detection-First SIEM: Rule Types, Dashboards, and Threat-Informed Strategy
Understanding_Digital_Forensics_Presentation.pptx
CIFDAQ's Market Insight: SEC Turns Pro Crypto
TokAI - TikTok AI Agent : The First AI Application That Analyzes 10,000+ Vira...
Network Security Unit 5.pdf for BCA BBA.
Advanced methodologies resolving dimensionality complications for autism neur...
Electronic commerce courselecture one. Pdf
Teaching material agriculture food technology
Cloud computing and distributed systems.
Peak of Data & AI Encore- AI for Metadata and Smarter Workflows
Digital-Transformation-Roadmap-for-Companies.pptx
How UI/UX Design Impacts User Retention in Mobile Apps.pdf

Cics data access-session 4

  • 1. CICS - DATA ACCESS DAY 2 - SESSION 4 Updated in Nov 2004
  • 2. Session 4 : ObjectivesTo Understand CICS File handling Concepts VSAM file types supported VSAM File control Commands VSAM File Browse Commands Exceptions in File Handling CICS-Database access : DB2 & IMS/DB
  • 5. CICS – VSAM File Handling Supports VSAM ◦ BDAM supported in earlier versions of CICS Files to be defined to CICS as resources in the FCT File Opening, Closing done by CICS Provides interface for ◦ Random access ◦ Sequential access ◦ Read, Write, Update, Delete
  • 6. File Access Methods - VSAM VSAM is the primary data access method for CICS VSAM file types supported ◦ Key Sequenced Data Set (KSDS) ◦ Entry Sequenced Data Set (ESDS) ◦ Relative Record Data Set (RRDS)
  • 7. Entry Sequenced Data Set (ESDS) Records to be entered into the data set VSAM ESDS
  • 8. ESDS - Relative Byte Address 100 BYTES REC1 200 BYTES REC2 300 BYTES REC3 0 100 200 RBA of REC3 is 200
  • 9. Key Sequenced Data Set (KSDS) 60 40 Key Field 20 25 58 63 Records For Insert
  • 10. Relative Record Data Set (RRDS) REC3 REC1 REC2 REC5 REC3 SLOT 1 SLOT 2 SLOT 3 SLOT 4 SLOT 5
  • 11. Record identification (RIDFLD) RECORD KEY PARTIAL KEY RELATIVE BYTE ADDRESS (RBA) RELATIVE RECORD NUMBER (RRN)
  • 12. VSAM File – Random Access Random Access READ WRITE a new record REWRITE a record previously ‘read for update’ DELETE UNLOCK a record previously ‘read for update’
  • 13. VSAM File – Sequential AccessSequential Read (Browsing) Start Browsing Read Next Read Previous End Browsing Reset Browsing conditions
  • 14. VSAM - READ from File : Syntax EXEC CICS READ DATASET(file-name) INTO (rec-area) LENGTH(record_length)] RIDFLD(key-value) RBA | RRN] GENERIC] KEYLENGTH(key-length)] [UPDATE] [GTEQ | EQUAL] END-EXEC.
  • 15. VSAM - READ from FILE : Example WORKING- STORAGE SECTION. 77 WS-REC-LEN PIC S9(4) COMP. 77 WS-FILE-NAME PIC X(8) VALUE ‘ACCTMSTR’ 01 WS-FILE-REC 05 WS-REC-KEY PIC X(6). 05 WS-REC-DATA PIC X(34). PROCEDURE DIVISION. MOVE 40 TO WS-REC-LEN. MOVE ‘ABC451’ TO WS-REC-KEY. EXEC CICS READ DATASET(WS-FILE-NAME) INTO (WS-FILE-REC) RIDFLD(WS-REC-KEY) LENGTH(WS-REC-LEN) END-EXEC.
  • 16. VSAM – Steps to Add New Records WRITE NEW RECORD SET UP DATA VALUES FOR NEW RECORD MOVE KEY VALUE TO RID FIELD
  • 17. VSAM – Write to File : Syntax EXEC CICS WRITE DATASET(file-name) FROM(file-rec) LENGTH(rec-length) RIDFLD(rec-key) [RBA | RRN] END-EXEC.
  • 18. VSAM - File Update : Syntax EXEC CICS REWRITE DATASET (file-name) FROM (data-area) [LENGTH (rec-len) END EXEC.
  • 19. VSAM – File UnlockTo release a record previously read for update EXEC CICS UNLOCK FILE / DATASET (name) END-EXEC.
  • 20. VSAM - Delete From File : Syntax EXEC CICS DELETE DATASET (file-name) RIDFLD(rec-key) [KEY-LENGTH(key-length)] [GENERIC[NUMREC(rec-number)]] [RBA | RRN] END-EXEC.
  • 21. VSAM - BROWSE Operation ESTABLISH START POSITION RETRIEVE NEXT RECORD PROCESS RECORD? TERMINATE BROWSE END OF BROWSE? PROCESS CHANGE POSITION YES YES YES NO NO NO
  • 22. VSAM - BROWSE CommandsSTARTBR - Establish starting position within file READNEXT - Retrieve records in ascending order sequentially as set by STARTBR READPREV - Retrieve Records in descending (reverse) order as set by STARTBR RESETBR - Restart Browse by re-positioning the pointer ENDBR - Terminate Browse
  • 23. VSAM - BROWSE : Example MOVE ‘VALUE’ TO KEY-REC EXEC CICS STARTBR FILE(‘FILEA’) RIDFLD(RECKEY) RESP(ERR-CODE) END-EXEC. IF ERR-CODE = DFHRESP(NORMAL) PERFORM UNTIL ERR-CODE = DFHRESP(ENDFILE). PERFORM 2000-REC-FROM-FILE UNTIL 2000-REC-FROM-FIL-EXIT EXEC CICS READNEXT FILE(‘FILEA’) INTO(FILEREC) RIDFLD(RECKEY) RESP(ERR-CODE) END-EXEC END-PERFORM EXEC CICS ENDBR FILE(‘FILEA’) …. END-EXEC ELSE PERFORM 9000-HANDLE-ERROR ….. END-IF.
  • 24. File Handling - Exceptional Conditions Processing Information ◦ NOTFND ◦ ENDFILE ◦ LENGERR Application Program Error ◦ INVREQ ◦ FILENOTFOUND ◦ ILLOGIC ◦ DUPREC External Conditions ◦ IOERR ◦ DISABLED ◦ NOTOPEN ◦ NOSPACE
  • 25. File Handling - Program Organization WORKING STORAGE RECORD LAYOUT DEFINITION RECORD ID FIELD LINKAGE SECTION EIB PROCEDURE DIVISION IDENTIFY KEY OF THE RECORD TO BE READ EXEC CICS READ FILE....
  • 26. CICS - Database Access Provides Interface to ◦Hierarchical Database - IMS/DB ◦Relational Database - DB2
  • 27. DB2 Database Access from CICS Terminal Users CICS subsystem CICS subsystem Terminal Control & BMS modules CICS - DB2 Attachment Facility Modules DB2 Sub system Appl. pgm1 Appl. pgm2 Appl. pgm3 Threads Tables, Files Stored on disk Other CICS Modules
  • 28. 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
  • 29. Files - Data Tables New feature of storing VSAM files in virtual storage Improved performance ◦ User Maintained Table(UMT) ◦ CICS Maintained Table (CMT) ◦ Shared Data Tables Transparent to application program
  • 30. Session 4 : Summary CICS File handling - use of FCT VSAM file types Supported - Random Access & Sequential Read File control commands - READ, WRITE, REWRITE, DELETE Browse commands – STARTBR, READNEXT, READPREV, RESETBR, ENDBR Exceptional Conditions in File Handling CICS-DB2 program preparation; RCT entries