Title: TSYS: Advanced COBOL
1TSYS Advanced COBOL
- Dr. David E. Woolbright
- 2008
2Documentation
- IBM Enterprise COBOL for z/OS
- http//www-306.ibm.com/software/awdtools/cobol/zos
/library/ - Especially helpful for programmers
- Language Reference Manual
- Programming Guide
3Course Outline
- QSAM File Processing
- Defining files
- Dynamic File processing in COBOL
- Subprograms
- CALL
- Parameter passing techniques
- CANCEL
- Nested programs
- Recursion
- Tables
- Single Dimension
- Multi-Dimension
- Subscripts and Indexes
- Searching
4Course Outline
- Debugging
- Basics
- Dumps
- XML and COBOL
- Introduction to XML
- Parsers
- Cobol Features
- Parsing
- Events
5Course Outline
- Files with Variable Length Records
- Strings
- STRING
- UNSTRING
- INSPECT
- Reference modification
- Pointers
- VSAM File Processing
6Course Outline
- Files with Variable Length Records
- Strings
- STRING
- UNSTRING
- INSPECT
- Reference modification
- Pointers
- VSAM File Processing
7QSAM File Processing
- Queued Sequential Access Method
8QSAM Files
- Unkeyed, Sequentially created and processed
- Records cannot change length or position
- QSAM files on direct access storage can be
modified with REWRITE - ENVIRONMENT DIVISION.
- FILE-CONTROL paragraph
- SELECT
- I-O-CONTOL paragraph
- APPLY WRITE-ONLY
- DATA DIVISION
- FILE SECTION
- FD
9(No Transcript)
10Environment Division - File Control
- SELECT file-name1
- OPTIONAL
-
- ASSIGN assignment-name
- TO
11Environment Division File-CONTROL
- Optional used for files opened in I-O, INPUT,
or EXTEND. File doesnt have to be present when
the program is executed. - File-name1 identifies an FD entry (internal
file name) - Assignment-name identifies the external file.
If name component of the SELECT clause is found
in the JCL it is treated as a DD name. If not
found in the JCL, then name is treated an an
environment variable
12QSAM File Name
- Label documents for the programmer the device
and device class to which the file is assigned.
No effect on execution. Must end with a dash - S Optional. Indicates sequential
organization
13Environment Variables
14Exercise A (Dynamic Files)
- Statically allocate and read BCST.SICCC01.TESTPDS(
DYNAMDAT) - This file contains member names of other members
in BCST.SICCC01.TESTPDS - Dynamically Read each member that is listed and
display the records in each member - After you can display all the records, try
writing out the records to a dynamically
allocated file - Use BCST.SICCC01.PDSLIB(DYNAM2) to help you read
a file dynamically - Use BCSC.SICCC01.PDSLIB(DYNAM1) to help you write
a file dynamically
15Environment Variables
- Defined as WORKING-STORAGE fields using value
clauses - 01 FILE-ENV-VAR PIC X(39)
- VALUE DYNFILEDSN(INPUT.FILE) SHR.
16Reserve Clause (optional)
- RESERVE integer
-
AREA -
AREAS
17RESERVE Clause
- Specifies the number of I/O buffers allocated the
file at run-time - If omitted, the number of buffers is taken from
the DD statement. If none are specified, the
system default is taken
18QSAM Buffering
- QSAM buffers can be allocated above the 16 MB
line if all of the following are true - - Enterprise COBOL
- - z/OS Language Environment
- - the programs are compiled with RENT and
DATA(31) - or
- compiled with NORENT and RMODE(ANY)
- - the program is executing in AMODE 31
- - the program is executing on MVS
- - the ALL31(ON) run-time option is used (for
EXTERNAL files)
19ORGANIZATION Clause (optional)
- ORGANIZATION IS SEQUENTIAL
- Other non-QSAM options INDEXED, RELATIVE, LINE
SEQUENTIAL - Records are read and written in a serial manner
20PADDING Clause
- PADDING data
name - CHARACTER IS literal
-
Specifies a character for block padding on
sequential files Data name a one character
field Literal a one character alphanumeric
literal or national symbol
21ACCESS MODE Clause
- ACCESS SEQUENTIAL
- MODE IS
Default mode is SEQUENTIAL Options for other
types of files include RANDOM and DYNAMIC
22FILE STATUS Clause
- STATUS dname1
- FILE IS
dname2
- - The operating system moves a value to dname1
and possibly dname2 after each I/O operation. - dname1 - a two character alphanumeric or
national field - dname2 used for VSAM
23Environment DivisionI-O-CONTROL
- ENVIRONMENT DIVISION.
- INPUT-OUTPUT SECTION.
- FILE-CONTROL.
- SELECT
- I-O-CONTROL.
- APPLY WRITE-ONLY ON MYFILE.
- (Used for sequential variable blocked files.)
24Defining QSAM Files and Records
- FILE-CONTROL.
- SELECT CUSTOMER-MASTER
- ASSIGN TO CUSTMAST
- ORGANIZATION IS SEQUENTIAL
- ACCESS MODE IS SEQUENTIAL
- FILE STATUS IS RC.
25DATA DIVISIONFILE SECTION - Sequential
26(No Transcript)
27DATA DIVISIONFILE SECTION - FD
28EXTERNAL
- The EXTERNAL clause specifies that a file
connector is external, permitting file sharing
between two programs in the same run unit
29GLOBAL
- GLOBAL clause specifies the file-connector name
is available to the declaring program and all
programs contained directly or indirectly - Used for nested programs
30BLOCK CONTAINS
- BLOCK CONTAINS 0 RECORDS
- If this clause is omitted, records are unblocked
by default! - Allows the blocksize to be specified in the JCL
or by the operating system - Code this Statement! (TSYS Standard)
31RECORD Clause
- Specifies the number of bytes in a record (fixed
or variable) - When omitted, the compiler determines lengths
based on record descriptions. - RECORD CONTAINS 80 CHARACTERS
- RECORD CONTAINS 50 TO 80 CHARACTERS
- RECORD IS VARYING IN SIZE
- FROM 40 TO 60 CHARACTERS
- DEPENDING ON REC-COUNT.
32RECORDING MODE
- Specifies the format of physical records in a
QSAM file (ignored for VSAM) - F fixed size, V variable size, U unblocked,
fixed or variable, S spanned, large records
that span a block - RECORDING MODE IS F
- RECORDING MODE IS V
- RECORDING MODE IS U
- RECORDING MODE IS S
33DATA RECORD Clause
- DATA RECORD clause identifies the data areas
associated with the file - Syntax checked but is only documentation
- DATA RECORD IS INPUT-AREA.
- DATA RECORDS ARE INPUT-AREA1
- INPUT-AREA2
34FD Example
- FD IN-FILE IS GLOBAL
- RECORDING MODE F
- BLOCK CONTAINS 0 RECORDS
- LABEL RECORDS ARE STANDARD
- RECORD CONTAINS 80 CHARACTERS
- DATA RECORD IS IN-AREA.
- 01 IN-AREA.
- 05
-
35LABEL RECORDS
- Label records are records written at the
beginning and end of DASD and Tape files that
provide information about file - Enterprise COBOL only supports standard labels
- LABEL RECORDS ARE STANDARD
- LABEL RECORDS ARE OMITTED
36Subprograms
37Calling a Subprogram
- Syntax for CALL
- CALL subprog name
- USING BY REFERENCE BY CONTENT
- ident1
- END-CALL
- The subprog name usually refers to an 8 byte
field that contains the program name to be called - Static call is made when subprogram name is
hard-coded and compiler option NODYNAM - Subprogram can be written in any supported
language
38Calling a Subprogram
- CALL variable-name
- USING BY REFERENCE
- BY CONTENT
- BY CONTENT LENGTH OF
- BY CONTENT ADDRESS OF
- ident1
- END-CALL
- The variable-name usually refers to an 8 byte
field that contains the program name to be called - Names can be longer with Enterprise COBOL
- The variable-name can be modified as the program
is running to call different programs
39Calling a Subprogram
- Linking to the called program is dynamic
- At TSYS, all calls are dynamic ( DYNAM compiler
option) - BY REFERENCE is the default
- BY REFERENCE provides the subprogram with access
to a main program variable. The receiving
variable is an alias for the passed variable - BY CONTENT provides the subprogram with access to
a copy of a main program variable
40Calling a Subprogram
- BY CONTENT ADDRESS OF provides a copy of the
address of the passed variable (must be a linkage
area name) - BY CONTENT LENGTH provides a copy of the length
of a variable
41Example Parameters
42The Called Program
- Specifies the names of the receiving variables
with a USING statement in the PROCEDURE DIVISION
statement or in an ENTRY statement - PROCEDURE DIVISION USING A.
- Or
- ENTRY COMPUTE USING COST RESULT.
- Or
- PROCEDURE DIVISION USING A COST RESULT.
- The variables in the using statement are 01
group items defined in the LINKAGE SECTION or 77
items - LINKAGE SECTION.
- 01 A PIC X(8).
- O1 COST PIC S9(5) PACKED-DECIMAL.
- 01 RESULT PIC S9(5) BINARY.
43The Called Program
- The called program can return values to the
calling program by modifying variables that are
passed by reference - PROCEDURE DIVISION USING
- COST.
-
- MOVE ITEM-COST TO COST
44Exercise 1
- Create a main program that calls a subprogram
- Print I am in the main program in the main
program - Call the subprogram
- Print I am in the subprogram in the subprogram
- Print I am back in the main program in the main.
45Exercise 2
- Create a two variables X and Y in the main
program (you pick the type and value). - Print the values of X and Y in the main program
- Pass X BY REFERENCE and Y BY CONTENT to the
subprogram - Print the variables in the subprogram
- Change the values of each variable in the
subprogram - Print the length of x by passing the length using
BY CONTENT LENGTH (Receiving variable PIC S9(8)
BINARY) - Print the values of the variables again in the
main program
46Canceling a Subprogram
- CANCEL syntax
- CANCEL literal
- CANCEL identifier
- Canceling a program means the program will be in
its initial state if the program is called again - Canceling a program closes all files associated
with an internal file connector of the canceled
program - No action is taken when canceling a previously
canceled program or one that has not been
dynamically called
47Exercise 3
- Have the main program call a subprogram four
times. - Create a local numeric variable Z in the
subprogram with initial value 1. - Each time the program is called, print Z and then
add 1 to it. - Repeat the experiment after adding IS INITIAL
to the PROGRAM-ID - PROGRAM-ID. MYPROG IS INITIAL.
48Subprograms
- Subprograms remain in their last used state when
they terminate with EXIT PROGRAM or GOBACK - A program that is coded with INITIAL will always
be called with its initial state -
49Exercise 4
- Repeat Exercise 3, canceling each program after
each subprogram call
50Return Codes
- Use the RETURN-CODE special register to test and
transmit return codes through register 15 - After calling a subprogram, test RETURN-CODE to
see if the subprogram completed normally - At the end of a suprogram, set RETURN-CODE to
indicate the results of the call
51Exercise 5
- Write a main program that passes a numeric
parameter, say X, to a subprogram. If the
parameter is negative have the subprogram set a
return code of 4. If the parameter is
non-negative, the subprogram should set the
return code to 0. Have the main program test the
return code after the subprogram has completed.
The main program should print a message
indicating the type of number the subprogram
received. Try running the main program passing
negative and non-negative values for X.
52External Files
- Files can be shared by multiple programs in the
same run unit. - Each program declares the file to be EXTERNAL
- FD MYFILE IS EXTERNAL
- RECORD CONTAINS 80 CHARACTERS
- RECORDING MODE IS F.
- 01 MY-RECORD.
-
53External Files
- Each program has the same SELECT statement
- SELECT MY-FILE
- ASSIGN TO MYFILE
- FILE STATUS IS MYSTATUS
- ORGANIZATION IS SEQUENTIAL.
54External Files
- Make the file status field external so there is
only one shared field for all programs. Each
program declares - 01 MYSTATUS PIC 99 EXTERNAL.
- Be sure to work in locate-mode.
55Exercise 6
- Write a main program that opens a sequential file
and calls a subprogram each time it needs a
record. Write a subprogram that reads a single
record and returns to the main program. Have the
main program print all the records in the
sequential file and then close the file. - Share the same file between the two programs by
making the file external with a shared file
status field.
56PROCEDURE DIVISIONRETURNING
- An alternate form of passing information back to
a calling program is provided - PROCEDURE DIVISION RETURNING dataname
- To call a Function the invocation is
- CALL program-name RETURNING dataname
- Avoid this alternative in favor of Pass By
Reference.
57Nested Programs
- Avoided in production programs at TSYS
- Convenient for developing (one file, one
compilation) - Nested programs can be separated easily into
regular programs after debugging - Can be used instead of PERFORM
- CALL to a nested program is as efficient as a
PERFORM - Each program ends with END PROGRAM
58Nested Program Structure
- ID DIVISION.
- PROGRAM-ID. X.
- PROCEDURE DIVISION.
- CALL X1
- GOBACK
- .
- ID DIVISION.
- PROGRAM-ID. X1.
- PROCEDURE DIVISION.
- DISPLAY I AM IN X1
- GOBACK
- .
- END PROGRAM X1.
- END PROGRAM X.
PROGRAM X
PROGRAM X1
59Exercise 7
- Convert one of your main programs and subprograms
to a nested program version - Canceling only makes sense for dynamically called
programs - Cause an abend in your subprogram. Look at the
storage dump and error information. Is it any
harder to debug than a regular program?
60COBOL is Recursive Now
- A COBOL program can call itself
- To make a program recursive, add IS RECURSIVE
to the PROGRAM-ID statement - PROGRAM-ID. SUBPROG IS RECURSIVE.
- Nested programs cannot be recursive
61Passing a Parm with JCL
- A parm can be coded on the EXEC statement in
order to pass a parameter to the program that is
being executed - // EXEC PGMPROGNAME,PARMHI there!'
- The COBOL program will receive the parm through
the LINKAGE SECTION - Code a LINKAGE SECTION description similar to
this - 01 PARM-BUFF.
- 05 PARM-LEN PIC S9(4) BINARY.
- 05 PARM-DATA PIC X(256).
- Code a using statement on the PROCEDURE DIVISION
- PROCEDURE DIVISION USING PARM-BUFF.
62Passing a Parm with JCL
- The parm field is variable in length
- Use the length field and reference modification
to move variable length data - MOVE PARM-DATA(1PARM-LEN)TO PARMO
63Exercise 8
- Try coding a main program that receives a parm
and prints it out - Run the program with the following EXEC
statements - // EXEC PGMPROGNAME,PARMHI!
- // EXEC PGMPROGNAME,PARMHI THERE!
- // EXEC PGMPROGNAME,PARMABCDEFGHIJKLMNOPQRSTUV'
64Omitted Parameters
- You can leave out some arguments when coding a
CALL statement by coding OMITTED in place of the
passed variable - CALL THATPROG USING P1,OMITTED,P3
- Test for the OMITTED parameter by checking to see
if the address of the received parm is NULL. - PROCEDURE DIVISION USING X Y Z.
-
- IF ADDRESS OF Y NULL
- DISPLAY PARM Y WAS NOT PASSED
- END-IF
65Tables
66Creating A Single Dimension Table
- Build a storage area with list of data values
defined with multiple picture clauses - Redefine the storage area as a single dimension
table by defining a typical table entry as an
occuring item.
67Creating A Single Dimension Table
01 DAY-TABLE-VALUES. 05
PIC X(9) VALUE 'SUNDAY '. 05
PIC X(9) VALUE 'MONDAY '. 05
PIC X(9) VALUE 'TUESDAY '. 05
PIC X(9) VALUE 'WEDNESDAY'. 05
PIC X(9) VALUE 'THURSDAY '. 05
PIC X(9) VALUE 'FRIDAY '.
05 PIC X(9) VALUE 'SATURDAY
'. 01 DAY-TABLE REDEFINES
DAY-TABLE-VALUES. 05 WEEKDAY PIC
X(9) OCCURS 7 TIMES.
68Fat Single-Dimension Tables
- 01 EMPLOYEE-TABLE.
- 05 EMPLOYEE-REC OCCURS 100 TIMES.
- 15 EMP-NO PIC X(5).
- 15 NAME PIC X(20).
- 15 LOC-CODE.
- 25 TERR-NO PIC XX.
- 25 OFFICE-NO PIC XX.
-
69Employee Table
EMPLOYEE-REC(1)
12345 Joe Brown
10 20
12345 Joe Brown
10 20
12345 Joe Brown
10 20
54321 Betty Smith
30 40
54555 Joy Dokes
31 45
54321 Jim Doyle
32 90
LOC-CODE(3)
NAME(3)
EMP-NO(4)
70Exercise 9
- Implement a single dimension table of days.
Print the table from beginning to end - Turn the table into a fat table by adding a
column with the number of letters in each day
name. - Print each day name and the number of letters it
contains.
71Multi-Dimension Tables
- COBOL supports up to 7 dimensions in tables
- Use OCCURS within OCCURS to add multiple
dimensions - 01 EMP-TABLE
- 05 EMPLOYEE OCCURS 100 TIMES.
- 10 NAME PIC X(30).
- 10 HOURS PIC S99 OCCURS 7 TIMES.
72Multi-Dimension Table
- 01 EMP-TABLE.
- 05 EMPLOYEE OCCURS 3 TIMES.
- 10 NAME PIC X(30).
- 10 HRS PIC S99 OCCURS 3 TIMES.
NAME(1)
HRS(1,1)
HRS(1,2)
HRS(1,3)
NAME(2)
HRS(2,2)
HRS(2,3)
HRS(2,1)
NAME(3)
HRS(3,1)
HRS(3,3)
HRS(3,2)
EMPLOYEE(3)
73Exercise 10
- Create a table of integers with 4 rows and 5
columns. - Print the table row by row
- Print the table column by column
- Compute and print the sum of each row
- Compute and print the sum of each column
- Compute and print the sum of all entries in the
table
74Creating Tables with Indexes
- 01 EMPLOYEE TABLE.
- 05 EMPLOYEE OCCURS 100 TIMES
- INDEXED BY I,J.
- 01 SALES-TABLE.
- 05 MONTH-RECORD OCCURS 12 TIMES
- INDEXED BY M.
- 10 NAME PIC X(30).
- 2O AMOUNT PIC 9(5)V99 PACKED-DECIMAL
- OCCURS 31 TIMES
- INDEXED BY D.
75Subscripts vs Indexes
- Subscripts
- Represent an occurrence number
- User defined as a numeric field best to choose
USAGE IS BINARY - Printable (since they are numeric)
- Can use relative subscripts J1 or J-3
- Manipulated with PERFORM loops, assignments, and
arithmetic commands
76Subscripts vs Indexes
- Indexes
- Represent a displacement value from the start of
a table. - More efficient than subscripts
- Created automatically when a table is defined
with indexes - Cant be printed
- Manipulated with PERFORM loops, and SET
statements
77SET Statements
- Examples
- SET J TO K
- SET J TO 1
- SET K UP BY 1
- SET K DOWN BY 1
- SET K TO K 1
78Exercise 11
- Convert Exercise 10 so that you are using
indexes instead of subscripts
79Sequential Search
- COBOL provides a SEARCH command that provides a
sequential search for tables that have indexes - Table entries do not have to be sorted
- AT END clause provides code in the situation that
the search is unsuccessful - Searching starts with the current index value
80SEARCH
81Sequential Searching
- 01 EMPLOYEE-TABLE.
- 05 EMPLOYEE OCCURS 100 TIMES
- INDEXED BY I-NDX.
- 10 EMP-NO PIC 9(5).
- 10 EMP-RANK PIC X(5).
-
- SET I-NDX TO 1
- SEARCH EMPLOYEE
- AT END
- DISPLAY NOT FOUND
- WHEN EMP-NO(I-NDX) 12345
- DISPLAY EMP-RANK(I-NDX)
- END-SEARCH
82Sequential Searching
- 01 EMPLOYEE-TABLE.
- 05 EMPLOYEE OCCURS 100 TIMES
- INDEXED BY I-NDX.
- 10 EMP-NO PIC 9(5).
- 10 EMP-RANK PIC X(5).
-
- SET I-NDX TO 1
- SEARCH EMPLOYEE
- AT END
- DISPLAY NOT FOUND
- WHEN EMP-NO(I-NDX)
- DISPLAY EMP-RANK(I-NDX)
- WHEN EMP-NO(I-NDX) 2000
- DISPLAY EMP-RANK(I-NDX)
- END-SEARCH
83Exercise 12
- Create a fat single dimension table with the data
in the file DATA1. Read the file and store the
second (Item ) and third fields (Item name) in
the table. - Assume a fixed size table of 40 items.
- Sequentially search the table for item 400 and
450. Print out the results of the search.
84Binary Searching
- Entire table is searched. No need to initialize
an index - Table must have an ASCENDING or DESCENDING KEY IS
clause. Table must be sorted. - Only one When clause and WHEN clause is one or
more equal tests joined by AND operators - AT END clause is invoked if the WHEN clause is
never satisfied
85Binary Search
86Binary Searching
- 01 EMPLOYEE-TABLE.
- 05 EMPLOYEE OCCURS 100 TIMES
- ASCENDING KEY IS EMP-NO
- INDEXED BY I-NDX.
- 10 EMP-NO PIC 9(5).
- 10 EMP-RANK PIC X(5).
-
- SEARCH ALL EMPLOYEE
- AT END
- DISPLAY NOT FOUND
- WHEN EMP-NO(I-NDX) 12345
- DISPLAY EMP-RANK(I-NDX)
- END-SEARCH
87SEARCH ALL
- SEARCH ALL performs a binary search with an index
- ENTRIES MUST BE IN ORDER
- No SET necessary (whole table searched)
- 01 SALES-TAX.
- 05 TAB-ENTRIES OCCURS 100 TIMES
- ASCENDING KEY
ZIPCODE - INDEXED BY K.
- 10 ZIPCODE PIC 9(5).
- 10 RATE PIC V999.
- SEARCH ALL TAB-ENTRIES
- AT END MOVE 0 TO TAX
- WHEN ZIPCODE(K) ZIPIN
- COMPUTE TAX RATE(K) AMOUNT
- END-SEARCH
88SEARCH ALL CONSTRAINTS
- The condition following WHEN must test for
equality - Compound conditions with ANDs not Ors
- Only one WHEN clause
- VARYING not allowed
- OCCURS item and its index must appear on the left
of the equal sign - WHEN TEMP(K) 80
89SEARCH ALL Constraints
- Table must indicate ASCENDING or DESCENDING KEY
- 01 TABLE.
- 05 CUST-REC OCCURS 40 TIMES
- ASCENDING KEY CUST
- INDEXED BY K.
- 10 CUST PIC 9(4).
- 10 RATE PIC V999.
90Exercise 13
- Convert Exercise 12 to a binary search.
91Variable Length Tables
- Storage for variable length tables is statically
created - To create a variable length table, use an
alternative version of OCCURS - Example OCCURS 1 TO 100 TIMES
- To create a variable length table add a DEPENDING
ON clause to the table definition - Example DEPENDING ON REC-COUNT
92Variable Length Tables
- After loading the table with entries, set the
index to point at the last item. Move the index
to the DEPENDING ON field - 01 CUST-TABLE.
- 05 CUSTOMER OCCURS 1 TO 50 TIMES
- DEPENDING ON C-COUNT
- ASCENDING KEY IS AGE
- INDEXED BY I.
- 10 NAME PIC X(20).
- 10 AGE PIS S999.
-
93Exercise 14
- Convert Exercise 12 to a variable length table.
- Assume you dont know how many items will be in
the table, but the range is 30 to 100 items.
94Intrinsic Functions
- MEAN ( ARG1, ARG2,)
- MEDIAN (ARG1, ARG2)
- STANDARD-DEVIATION(ARG1,ARG2,)
- VARIANCE (ARG1,ARG2, )
- RANGE (ARG1, ARG2, )
- MAX (ARG1, ARG2, )
- MIN (ARG1, ARG2, )
- ORD-MIN (ARG1,ARG2,)
- ORD-MAX (ARG1,ARG2,)
- SUM (ARG1, ARG2, )
95Intrinsic Functions
- CURRENT-DATE
- UPPER-CASE (ARG)
- LOWER-CASE(ARG)
- ANNUITY(RATE,NO-OF-PAYMENTS)- returns a decimal
fraction that when multiplied by loan amount
produces the payment. Rate must be consistent
with payment period. - PRESENT-VALUE(RATE,AMT1,AMT2,) returns the
present value of future payments
96Intrinsic Functions
- SQRT(ARG)
- REM(ARG1,ARG2) returns the remainder of arg1
divided by arg2 - MOD(ARG1,ARG2)- similar to REM but with integer
arguments - INTEGER(ARG) the greatest integer less than or
equal to ARG - INTEGER-PART(ARG) the integer part of ARG
- NUMVAL(ARG) the numeric value of an argument
that contains leading spaces, sign, or decimal
point
97Intrinsic Function Syntax
- FUNCTION function-name (arg1
- Arguments can be literals, variables,
expressions, other functions - Functions can operate on tables by using the word
ALL for the subscript - COMPUTE X FUNCTION SUM(SALARY(ALL))
- COMPUTE Y FUNCTION SUM(PRICE(1 ALL))
- Usually used with COMPUTE or MOVE
98Exercise 15
- Using Exercise 10 and intrinsic functions,
compute the minimum value of each row and the
mean of the entire array.
99Reconsidering Tables
- With vast amounts of main storage today, you
should consider the types of file operations you
are using and whether or not an application could
benefit by pulling an entire file (or part of a
file) into main storage. Working directly with
records in memory is very efficient and can speed
up an application greatly - Most of the time spent in an application is in
I/O.
100Files with Variable Length Records
101Variable Length Records
- FD CUSTFILE
- RECORD IS VARYING IN SIZE
- FROM 1 TO 80 CHARACTERS
- DEPENDING ON RECSIZE.
- When a record is read from a file, defined with
the RECORD IS VARYING IN SIZE.. DEPENDING ON
ident phrase, the size of the record read into
the buffer is moved into the data-item ident - To write to a file, defined with the RECORD IS
VARYING IN SIZE.. DEPENDING ON ident phrase, the
size of the record to be written must first be
moved to ident data-item, and then the WRITE
statement must be executed.
102Exercise 16
- Use program WRITEVAR as a model. Run the
program to create a variable length record file. - Write a program READVAR that reads the file and
prints out the total sales for each person
103Strings
104Joining Strings
- Use STRING to join multiple parts of strings into
an entirely new string - STRING ident1 DELIMITED ident2
- literal BY literal
- size
- INTO ident3
- POINTER ident4
- WITH
- OVERFLOW imperative stmt
- ON
105Joining Strings
-
- NOT OVERFLOW imperative stmt
END-STRING
106Example String Operation
- STRING ID-1 DELIMITED BY
- ID-2 ID-3 DELIMITED BY SIZE
- INTO ID-4 WITH POINTER PTR
- END-STRING
-
ID-1 ABCDE
ID-3 XYZ
PTR 13
ID-2 12345
ID-4 (Assume PIC X(20) ABC12345XYZ
Assume PTR is Initially 1
107STRING
108STRING Operation
- String does not replace rightmost character with
spaces - The POINTER field is a numeric field that
afterwards contains the position of the next
byte in the receiving field that would have been
processed. (Max string length 1)
109Exercise 17
- Read the file DATA1.
- Create three fields in the input record
- 1) cols 1 11
- 2) cols 15-18
- 3) cols 40-65
- Remove the first part of field 1 up to the .
- Remove all of field 2.
- Remove all of field 3 up to the first space
- String these three fields together. For
example the first record would produce - 66660066PEANUT
- Print the results of each record.
110UNSTRING
111UNSTRING
- Extracts a field into multiple strings and stores
them into one or more fields - DELIMITED BY indicates how each subfield ends
- If ALL is specified for a delimiter, successive
occurrences of the delimiter are treated as one - UNSTRING ADDRESS DELIMITED BY ALL
- INTO STATE ZIP
- WITH POINTER PTR
- END-UNSTRING
112UNSTRING
- UNSTRING copies Characters from the source string
to the destination strings according to the rules
for alphanumeric moves. - UNSTRING uses space filling.
- The DELIMITED BY clause causes data movement from
the source string to the current destination
string to end when - 1) a delimiter is encountered in the source
string - 2) the end of the source string is reached.
113UNSTRING
- If DELIMITED BY is not used, data movement
terminates when - 1) the destination string is full
- 2) the end of the source string is reached
- The UNSTRING terminates when
- 1) All the characters in the source string
have been processed - 2) All the destination strings have been
processed - 3) An OVERFLOW condition is encountered when
the pointer is pointing outside the source
string.
114UNSTRING EXAMPLE
- UNSTRING ADDRESS DELIMITED BY ALL
- INTO STATE COUNT IN STCNT
- ZIP COUNT IN ZIPCNT
- WITH POINTER PTR
- END-UNSTRING
115UNSTRING Example
- UNSTRING ADDRESS DELIMITED BY ","
- INTO LINE(1)
- LINE(2)
- LINE(3)
- Line(4)
- TALLYING IN NOLINES
- END-UNSTRING.
- Tallying leaves the number of receiving fields
that receive data in the named variable
116Exercise 18
- Read the file DATA1.
- For each record in the file, UNSTRING field 1-11
into two parts (separate at the ). Print each
part.
117INSPECT Statement
118INSPECT Statement
119Formats
- INSPECT has four formats
- 1) TALLYING used to count characters in a
string. - 2) REPLACING used to replace a group of
characters in a string with another group of
characters. - 3) TALLYINGREPLACING combines both
operations in one statement. - 4) INSPECT CONVERTING converts each of a
set of characters to its corresponding character
in another set of characters.
120TALLYING
- INSPECT LINE TALLYING ACOUNT
- FOR ALL A
- INSPECT LINE TALLYING XCOUNT
- FOR ALL X"
- AFTER INITIAL S"
- BEFORE INITIAL E".
121REPLACING
- INSPECT MYSTRING
- REPLACING ALL X BY Y"
- AFTER INITIAL A"
- BEFORE INITIAL Z
- INSPECT MYSTRING
- REPLACING ALL XXXX" BY ABCD
- AFTER INITIAL A
- BEFORE INITIAL P"
122TALLYING REPLACING
- INSPECT LINE TALLYING ACOUNT
- FOR ALL A
- REPLACING ALL X BY Y"
- AFTER INITIAL A"
- BEFORE INITIAL Z
123CONVERTING
- INSPECT MYTEXT
- CONVERTING "abcdefghijklmnopqrstuvwxyz
- TO "ABCDEFGHIJKLMNOPQRSTUVWXYZ
-
124Pointers
125Creating a Pointer
- 05 PTR USAGE IS POINTER.
- 05 A-PTR POINTER.
- These definitions create 4 byte fullwords capable
of containing addresses of memory locations
126Setting a Pointer
- SET PTR TO ADDRESS OF X
- SET PTR1 TO PTR2
127Dropping a Linkage Area
- To position a linkage section item onto a storage
area, use SET ADDRESS - Linkage Section.
- 01 X PIC X(8).
- SET ADDRESS OF X TO PTR
128Exercise 19
- Try running programs LINKED and LINKED1 in
BCST.SICCC01.PDSLIB
129VSAM File Processing
- Virtual Storage Access Method
130VSAM File Types
- ESDS Entry Sequenced Data Set
- Allows sequential processing
- RRDS Relative Record Data Set
- Allows sequential or random access by relative
record number - KSDS Key-Sequenced Data Set
- Allows sequential, skip sequential, and random
processing by key
131VSAM
- VSAM data sets are known as Clusters
- For ESDS or RRDS the cluster consists of a data
component - For KSDS the cluster consists of a data component
and an index component - VSAM data is stored on DASD in control intervals
which are grouped into control areas
132VSAM
- The Control Interval (CI) is the unit of data
that transfers between the disk and virtual
storage - CI sizes are multiples of 2K with 4k being common
- CIs can be constructed with free space to
accommodate additions to the file - Control Areas (CA) can be constructed with free
space to accommodate additions
133VSAM
- VSAM dynamically manages the file by maintaining
information in each CI and CA - When a CI becomes too full the data it contains
is split into two CIs - When a CA becomes too full the data it contains
is split into two CAs - VSAM tries to keep records that are logically
close together, physically close as well
134VSAM Indexes
135VSAM Components
136Access Method Services (AMS)
- AMS is a VSAM utility that provides numerous
options - DEFINE CLUSTER
- PRINT
- REPRO
- LISTCAT
- DELETE
- DEFINE ALTERNATEINDEX
- DEFINE PATH
- BLDINDEX
137VSAM JCL
- Unlike QSAM files, VSAM files must be allocated
in a separate job step before data can be written
to the file - VSAM cluster can be created by deleting and then
defining the cluster - After the cluster is defined, a job can run which
writes data to the file
138VSAM JCL
- Parameters
- INDEXED KSDS
- NONINDEXED ESDS
- NUMBERED RRDS
- KEYS ( len off) primary key info
- CISZ (size) control interval size
- FREESPACE (ci ca) free space s
139MAKEKSDS
- 000100 //TSYSAD2C JOB 'YOUR NAME',USERTSYSAD2,REG
ION2048K,MSGCLASSV - 000200 //MAIN CLASSTSYSC,USERTSYSAD2
- 000300 //DEFINE EXEC PGMIDCAMS
- 000400 //SYSPRINT DD SYSOUT
- 000500 //SYSIN DD
- 000600 DELETE TSYSAD2.PAYROLL.MASTER
- 000700 DEFINE CLUSTER
- - 000800 (NAME(TSYSAD2.PAYROLL.MA
STER) - - 000900 INDEXED
- - 001000 RECORDSIZE(31 31)
- - 001100 KEYS(5 0)
- - 001200 MGMTCLAS(STANDARD)
- - 001210 FREESPACE(0 0)
- - 001220 SHAREOPTIONS (3 3))
- - 001230 DATA (NAME(TSYSAD2.PAYROLL.MA
STER.DATA) - - 001240 TRK(1 1)
- - 001250 CONTROLINTERVALSIZE(409
6)) - - 001260 INDEX (NAME(TSYSAD2.PAYROLL.MA
STER.INDEX) - - 001270 TRK(1 1))
140IDCAMS PRINT
- 000100 //TSYSAD2P JOB 'A.STUDENT',USERTSYSAD2,REG
ION2048K,MSGCLASSV - 000200 //MAIN CLASSTSYSC,USERTSYSAD2
- 000210 // THIS IS AN IDCAMS PRINT
- 000220 //PRINT EXEC PGMIDCAMS
- 000230 //SYSPRINT DD SYSOUT
- 000240 //SYSIN DD
- 000250 PRINT INFILE(IFILE) -
- 000251 DUMP
- 000252 /
- 000253 //IFILE DD DSNTSYSAD2.PAYROLL.MASTER,
DISPSHR - 000254 //
141IDCAMS REPRO
- 000100 //TSYSAD2R JOB 'A.STUDENT',USERTSYSAD2,REG
ION2048K,MSGCLASSV - 000200 //MAIN CLASSTSYSC,USERTSYSAD2
- 000210 // THIS AN IDCAMS REPRO
- 000220 //REPRO EXEC PGMIDCAMS
- 000230 //FILEIN DD DSNTSYSAD2.PGM1.RESULTS,DI
SPSHR - 000240 //FILEOUT DD DSNTSYSAD2.I10.PGM1.RESULT
S,DISP(NEW,CATLG,DELETE), - 000250 // UNITSYSDA,DCB(RECFMFB,LRECL80
), - 000251 // SPACE(TRK,(1,1),RLSE)
- 000252 //SYSIN DD
- 000253 REPRO -
- 000254 INFILE(FILEIN) -
- 000255 OUTFILE(FILEOUT)
- 000256 /
- 000257 //AMSDUMP DD SYSOUT
- 000258 //
142Creating a VSAM File
- 000100 IDENTIFICATION DIVISION.
- 000200 PROGRAM-ID. VSAM1.
- 000300 ENVIRONMENT DIVISION.
- 000400 INPUT-OUTPUT SECTION.
- 000500 FILE-CONTROL.
- 000600 SELECT PAYROLL-MASTER-OUT ASSIGN TO
PAYMASTO - 000610 ORGANIZATION IS INDEXED
- 000620 ACCESS IS SEQUENTIAL
- 000630 RECORD KEY IS ID-OUT
- 000640 FILE STATUS IS PM-STATUS.
- 000700 SELECT PAYROLL-MASTER-IN ASSIGN TO
PAYMASTI.
143Creating a VSAM File
- 004410 01 PM-STATUS.
- 004430 05 PM-STAT1 PIC X.
- 004440 05 PM-STAT2 PIC X.
- 004441 PROCEDURE DIVISION.
- 004450 OPEN INPUT PAYROLL-MASTER-IN
- 004460 OPEN OUTPUT PAYROLL-MASTER-OUT
- 004461 IF PM-STATUS NOT '00'
- 004462 PERFORM 300-PRINT-STATUS
- 004463 END-IF
- 004470 PERFORM UNTIL ARE-THERE-MORE-RECORDS
'NO ' - 004480 READ PAYROLL-MASTER-IN
- 004490 AT END
- 004500 MOVE 'NO ' TO
ARE-THERE-MORE-RECORDS - 004600 NOT AT END
- 004700 PERFORM 200-READ-MODULE
- 004800 END-READ
- 004900 END-PERFORM
- 005000 CLOSE PAYROLL-MASTER-IN
- 005100 PAYROLL-MASTER-OUT
144Creating a VSAM File
- 005130 200-READ-MODULE.
- 005410 MOVE ID-IN TO ID-OUT
- 005420 MOVE NAME-IN TO NAME-OUT
- 005430 MOVE HOURS-IN TO HOURS-OUT
- 005440 MOVE RATE-IN TO RATE-OUT
- 005450 DISPLAY MASTER-REC-OUT
- 005500 WRITE MASTER-REC-OUT
- 005510 IF PM-STATUS NOT '00'
- 005520 PERFORM 300-PRINT-STATUS
- 005530 END-IF
- 005600 .
- 005700 300-PRINT-STATUS.
- 005800 DISPLAY 'FILE STATUS CODE'
PM-STATUS - 005900 GOBACK
- 006000 .
145VSAM Error Strategy
- VSAM returns a status code after each operation
- It is imperative that you check each status code
after each operation to insure that the program
is proceeding normally - The status code is a two byte field
146OPEN
- OPEN INPUT file-name
- OPEN OUTPUT file-name
- OPEN I-O file-name
- OPEN EXTEND file-name
- For EXTEND, access mode must be sequential
147Reading for Sequential Access
- READ file-name NEXT RECORD
- INTO data-name
- AT END imperative stmt
- NOT AT END imperative stmt
- END-READ
- Specify NEXT if access is DYNAMIC and you want
sequential processing - Can be omitted when access is SEQUENTIAL
- INTO provides move mode I/O
- Omitting INTO provides locate mode I/O
148Reading for Random Access
- READ file-name RECORD
- INTO data-name
- INVALID KEY imperative stmt
- NOT INVALID KEY imperative stmt
- END-READ
- Be sure to set the key of the record you wish to
read beforehand
149Writing
- WRITE record-name FROM data-name
- INVALID KEY imperative stmt
- NOT INVALID KEY imperative stmt
- END-WRITE
150REWRITE
- REWRITE record-name FROM data-name
- INVALID KEY imperative stmt
- NOT INVALID KEY imperative stmt
- END-REWRITE
- A typical scenario is to read the record, modify
it (cant change the key field), and then rewrite
it. - For random and dynamic access, you can REWRITE a
record without first reading it.
151DELETE
- DELETE file-name RECORD
- INVALID KEY imperative stmt
- NOT INVALID KEY imperative stmt
- END-DELETE
- DELETE can only be used for a file in I-O mode
- If file is in sequential mode, the DELETE can
only be used after executing a READ statement for
that record. (Omit INVALID KEY) - If file is in random or dynamic mode, a DELETE
can be issued without previously reading the
record (specify INVALID KEY)
152START
- START file-name
- KEY IS EQUAL TO data-name
-
- GREATER THAN
-
- NOT LESS THAN
- NOT
-
- INVALID KEY imperative stmt
- NOT INVALID KEY imperative stmt
- END-START
- Used for sequential and skip-sequential
processing - Does not return a record positions you in the
file
153File Status Codes
- 00 Operation completed successfully
- 02 Duplicate Key was found
- 04 Invalid fixed length record
- 05 The file was created when opened - Successful
Completion - 07 CLOSE with REEL or NO REWIND executed for non
tape dataset. - 10 End of File encountered
- 14 Attempted to READ a relative record outside
file boundary - 21 Invalid Key - Sequence error
- 22 Invalid Key - Duplicate Key found
- 23 Invalid key - No record found
- 24 Invalid Key - key outside boundary of file.
154File Status Codes
- 30 Permanent I/O Error34 Permanent I/O Error -
Record outside file boundary - 35 OPEN, but file not found
- 37 OPEN with wrong mode
- 38 Tried to OPEN a LOCKed file
- 39 OPEN failed, conflicting file attributes
- 41 Tried to OPEN a file that is already open
- 42 Tried to CLOSE a file that is not OPEN
- 43 Tried to REWRITE without READing a record
first - 44 Tried to REWRITE a record of a different
length - 46 Tried to READ beyond End-of-file
- 47 Tried to READ from a file that was not opened
I-O or INPUT - 48 Tried to WRITE to a file that was not opened
I-O or OUTPUT - 49 Tried to DELETE or REWRITE to a file that was
not opened I-O
155File Status Codes
- 91 Password or authorization failed
- 92 Logic Error
- 93 Resource was not available (may be allocated
to CICS or another user) - 94 Sequential record unavailable or concurrent
OPEN error - 95 File Information invalid or incomplete
- 96 No DD statement for the file
- 97 OPEN successful and file integrity verified
- 98 File is Locked - OPEN failed
- 99 Record Locked - record access failed.
156Exercise 20
- Create a data file of records which is sorted on
a key field (choose a 5 byte key). Creating an
80 byte record in a PDS is easiest. Let some of
the keys be in the 10000 19999 range, some in
range 20000 29999, some in range 30000 39999,
and some in range 40000-49999. (VSAMDATA) - Read the file and output a fixed size record VSAM
file.
157Exercise 21
- Read the VSAM file you created in Exercise 20 and
print out the records (your choice of format).
158Exercise 22
- Create a small file of keys. Some of the keys
should match records in your VSAM file and some
should not. (VSAMKEYS) - Process the VSAM file randomly. Take each key,
print it, and print the record if it is on the
file, otherwise print a message indicating the
record was not found.
159Exercise 23
- Process the VSAM file dynamically with
skip-sequential processing. - Issue a Start statement and print the records
with keys in the range 20000-29999. Issue
another START and print the records in the range
40000 49999.
160Exercise 24
- Create a small file of keys. Some of the keys
should match records in your VSAM file and some
should not. - Process the VSAM file randomly. Take each key,
read the VSAM file, and delete each record that
is found. If the record is not found print a
message indicating this.
161Alternate Indexes
- An alternate index provides a way to navigate
through a VSAM cluster using an alternate key - Creating an alternate index is a 3 step process
- DEFINE ALTERNATE INDEX
- DEFINE PATH
- BLDINDEX
162Define Alternateindex
- //KC02107X JOB 'WOOLBRIGHT',REGION2M,MSGCLASSQ,M
SGLEVEL(0,0), - // NOTIFYKC02107
- //-----------------------------------------------
----------- - // VSAM
- //-----------------------------------------------
----------- - //STEPMAKE EXEC PGMIDCAMS
- //SYSPRINT DD SYSOUT
- //SYSIN DD
- DELETE KC02107.SICCC01.MYVSAM.AIX
- DEFINE ALTERNATEINDEX
- - (NAME (KC02107.SICCC01.MYVSAM.AIX)
- - RELATE (KC02107.SICCC01.MYVSAM)
- - KEYS (20 5)
- - NONUNIQUEKEY
- - UPGRADE
- - REUSE )
- - DATA (NAME (KC02107.SICCC01.MYVSAM.AIX.DATA)
- - TRACKS(1 1))
- - INDEX (NAME (KC02107.SICCC01.MYVSAM.AIX.INDEX)
)
163BLDINDEX
- //KC02107X JOB 'WOOLBRIGHT',REGION2M,MSGCLASSQ,M
SGLEVEL(0,0), - // NOTIFYKC02107
- //-----------------------------------------------
----------- - // VSAM BLDNDX CLUSTER
- //-----------------------------------------------
----------- - //STEPMAKE EXEC PGMIDCAMS
- //SYSPRINT DD SYSOUT
- //SYSIN DD
- BLDINDEX INDATASET(KC02107.SICCC01.MYVSAM) -
- OUTDATASET(KC02107.SICCC01.MYVSAM.AIX)
- /
- //
164VSAM REPRO
- //KC02107X JOB 'WOOLBRIGHT',REGION2M,MSGCLASSQ,M
SGLEVEL(0,0), - // NOTIFYKC02107
- //-----------------------------------------------
----------- - // VSAM REPRO CLUSTER
- //-----------------------------------------------
----------- - //STEPMAKE EXEC PGMIDCAMS
- //SYSPRINT DD SYSOUT
- //SYSIN DD
- REPRO INDATASET(KC02107.ASM.DAT(VSAMDATA)) -
- OUTDATASET(KC02107.SICCC01.MYVSAM)
- /
- //
165Debugging
166Learn Hex Basics
- Decimal
- 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15
- Hexadecimal
- 0 1 2 3 4 5 6 7 9 9 A B C D E F
167Learn Binary Basics
- Every digit is a power of 2
- 1 1 1 0 1 0 0 1
- 128 32 8 2 1
- 64 16 4
- 1286432080 01 233
168Binary to Hex
- Conversion rule Remove blocks of 4 binary
digits and replace them with a single hex digit - 1 1 0 1 1 1 0 0 0 0 1 1 1 0 1 1
- D C 3 B
- Hex dumps are made of hex digits and represent
binary values that are stored in memory a
short-hand notation - 2 HEX DIGITS 1 BYTE
169EBCDIC Characters
- CHAR HEX CHAR HEX CHAR HEX CHAR HEX
- 0 F0 A C1 J D1
- 1 F1 B C2 K D2 S E2
- 2 F2 C C3 L D3 T E3
- 3 F3 D C4 M D4 U E4
- 4 F4 E C5 N D5 V E5
- 5 F5 F C6 O D6 W E6
- 6 F6 G C7 P D7 X E7
- 7 F7 H C8 Q D8 Y E8
- 8 F8 I C9 R D9 Z E9
- F9
- SPACE 40 COMMA 6B PERIOD 4B 5C
- MINUS 60
-
170Zoned Decimal Format
- Byte 8 bits
- Leftmost 4 bits zone part
- Rightmost 4 bits numeric part
- PIC S9999
- PIC 99
- PIC 99V99
- One digit per byte sign in zone portion of last
byte. Preferred signs C , D - Signs A C E F B D -
ZONE NUMERIC
171Zoned Decimal Format
- PIC S999 VALUE 123 F1F2C3
- PIC 99V99 VALUE 12.34 F1F2F3C4
- PIC S99 VALUE -12 F1D2
- PIC S999 VALUE 0 F0F0C0
172Packed Decimal Format
- Two decimal digits per byte
- Sign stored in numeric portion of the rightmost
byte 12345C - Decimal points are implied (not stored)
- Always an odd number of decimal digits
- Good choice for business arithmetic
173Packed Decimal
- PIC S999 PACKED-DECIMAL VALUE 123
- 123C
- PIC S9(3)V99 PACKED-DECIMAL VALUE -123
- 00123D
- PIC S9(4) PACKED-DECIMAL VALUE -98
- 00098D
- PIC 9(7) PACKED-DECIMAL VALUE -32
- COMPILE ERROR
- PIC 9(7) PACKED-DECIMAL VALUE 32
- 0000032C
174Binary Data
- 1-4 digits 2 bytes halfword
- 5-9 digits 4 bytes fullword
- 10-18 digits 8 bytes doubleword
- PIC S9(4) BINARY 2 BYTES
- PIC S9(5) BINARY 4 BYTES
- PIC S9(9) BINARY 4 BYTES
- PIC 9(8) BINARY 4 BYTES
175Signed Binary
- Signed binary data is stored in 2s complement
format - High order bit is a sign 1 is negative, 0 is
positive - 0001101 13 in decimal
- 1110010 -14
- Conversion rule Change the 1s to 0s and 0s to
1s, then add 1. This computes the 2s complement
176Pointers
- USAGE IS POINTER A 4 BYTE FULLWORD STORED IN
BINARY -
177Signed Binary
- Example 111111
- Changing 000000
- Add 1 000000 1 000001
- 1 is the complement so 111111 is -1
- Example 110011
- Changing 001100
- Add 1 001100 1 001101 13
- 110011 -13
178Display
- The answer to all debugging problems is to gain
more information. DISPLAY can provide it.
179Finding the Problem
- Display Filter View Print Options Help
- -------------------------------------------------
------------------------------ - SDSF OUTPUT DISPLAY SICCC01A JOB22537 DSID
102 LINE 116 COLUMNS 02- 81 - COMMAND INPUT
SCROLL CSR - Data Division Map
- Data Definition Attribute codes (rightmost
column) have the following meanings - D Object of OCCURS DEPENDING G GLOBAL
S - E EXTERNAL O Has
OCCURS clause U - F Fixed-length file OG Group
has own length definition V - FB Fixed-length blocked file R
REDEFINES VB - Source Hierarchy and
Base Hex-Displac - LineID Data Name
Locator Blk Struc - 2 PROGRAM-ID BOMB1--------------------------
------------------------------ - 6 1 MYTABLE-VALUES. . . . . . . . . . . .
. . . . BLW00000 000 - 7 2 FILLER. . . . . . . . . . . . . . .
. . . . BLW00000 000 0 000 - 8 2 MYPTR1. . . . . . . . . . . . . . .
. . . . BLW00000 010 0 000 - 9 2 FILLER. . . . . . . . . . . . . . .
. . . . BLW00000 014 0 000 - 10 2 FILLER. . . . . . . . . . . . . . .
. . . . BLW00000 024 0 000 - 11 2 FILLER. . . . . . . . . . . . . . .
. . . . BLW00000 034 0 000
180Data Division Map
- 0Source Hierarchy and
Base Hex-Displa - LineID Data Name
Locator Blk Stru - 2 PROGRAM-ID BOMB1-------------------------
------------------------------ - 6 1 MYTABLE-VALUES. . . . . . . . . . .
. . . . . BLW00000 000 - 7 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000 000 0 00 - 8 2 MYPTR1. . . . . . . . . . . . . .
. . . . . BLW00000 010 0 00 - 9 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000 014 0 00 - 10 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000 024 0 00 - 11 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000 034 0 00 - 12 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000 044 0 00 - 13 2 FILLER. . . . . . . . . . . . . .
. . . . . BLW00000