You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
Copy file name to clipboardExpand all lines: COBOL Programming Course #1 - Getting Started/COBOL Programming Course #1 - Getting Started.md
+326Lines changed: 326 additions & 0 deletions
Display the source diff
Display the rich diff
Original file line number
Diff line number
Diff line change
@@ -1903,6 +1903,332 @@ Notice that this line tells you to focus on the GROSS-PAY picture clause in orde
1903
1903
1904
1904
\newpage
1905
1905
1906
+
# Table handling
1907
+
1908
+
This section introduces the concept of tables, which are a collection of data items that have the same description. The subordinate items are called table elements. A table is the COBOL equivalent of arrays.
1909
+
1910
+
The objective of this chapter is to provide information for the reader to be able to handle tables inside COBOL programs.
1911
+
1912
+
## Defining a table
1913
+
1914
+
To code a table, we need to give the table a group name and define a subordinate item which we are repeating n times.
1915
+
1916
+
```
1917
+
01 TABLE-NAME.
1918
+
05 SUBORDINATE-NAME OCCURS n TIMES.
1919
+
10 ELEMENT1 PIC X(2).
1920
+
10 ELEMENT2 PIC 9(2).
1921
+
```
1922
+
1923
+
In the example above, TABLE-NAME is the name of the group item. The table also contains a subordinate item called SUBORDINATE-NAME which we are repeating n times. Each SUBORDINATE-ITEM has 2 elementary items, ELEMENT1 and ELEMENT2. In this case, we called SUBORDINATE-NAME as the table element definition (since it includes the OCCURS clause). Note that the OCCURS clause cannot be used in a level-01 description.
1924
+
1925
+
Alternatively, we can also make simpler tables:
1926
+
1927
+
```
1928
+
01 TABLE-NAME.
1929
+
05 SUBORDINATE OCCURS n TIMES PIC X(10).
1930
+
```
1931
+
1932
+
In this case, TABLE-NAME contains n SUBORDINATE items, each can contain up to 10 alphanumeric characters.
1933
+
1934
+
We can also nest multiple OCCURS elements to create a table of additional dimensions, up to a limit of seven dimensions. Note the example below:
1935
+
1936
+
```
1937
+
01 PROGRAM-DETAILS.
1938
+
05 PROGRAM-DEGREE PIC X(32).
1939
+
05 COURSE-DETAILS OCCURS 10 TIMES.
1940
+
10 COURSE-NAME PIC X(32).
1941
+
10 INSTRUCTOR-ID PIC 9(10).
1942
+
10 ASSIGNMENT-DETAILS OCCURS 8 TIMES.
1943
+
15 ASSIGNMENT-NAME PIC X(32).
1944
+
15 ASSIGMMENT-WEIGHTAGE PIC 9(03).
1945
+
```
1946
+
1947
+
Here, we are defining a degree program which has 10 courses and each course will have 8 assignments. What if we don't know how many times a table element will occur? To solve that, we can use variable-length table, using the OCCURS DEPENDING ON (ODO) clause which we will be going into more details on a later section.
1948
+
1949
+
## Referring to an item in a table
1950
+
1951
+
While a table element has a collective name, the individual items within do not have a unique name. To refer to an item, we can either use subscript, index, or a combination of both.
1952
+
1953
+
### Subscripting
1954
+
1955
+
Subscripting is using the data name of the table element, along with its occurence number (which is called a subscript). The lowest possible subscript number is 1, which defines the first occurence of a table element. We can also use literal or data name as a subscript. Note that if you are using data name, it must be an elementary numeric integer.
1956
+
1957
+
```
1958
+
01 TABLE-NAME.
1959
+
05 TABLE-ELEMENT OCCURS 3 TIMES PIC X(03) VALUE "ABC".
1960
+
...
1961
+
MOVE "DEF" TO TABLE-ELEMENT (2)
1962
+
```
1963
+
1964
+
In the above example, the second table-element will contain "DEF" instead of "ABC".
1965
+
1966
+
### Indexing
1967
+
1968
+
Alternatively, we can create an index using the INDEXED BY phrase of the OCCURS clause. This index is added to the address of the table to locate an item (as a displacement from the start of the table). For example,
1969
+
1970
+
```
1971
+
05 TABLE-ELEMENT OCCURS 10 TIMES INDEXED BY INX-A PIC X(03).
1972
+
```
1973
+
1974
+
Here, INX-A is an index name. The compiler will calculate the value in the index as the occurence number minus 1 multiplied by the length of the table element. So, for example, for the second occurence of TABLE-ELEMENT, the binary value contained in INX-A is (2-1) * 3, or 3.
1975
+
1976
+
If you happen to have another table with the same number of table elements of the same length, you can use an index name as a reference for both tables.
1977
+
1978
+
We can also define an index data item using the USAGE IS INDEX clause. These index data items can be used with any table. For example,
1979
+
1980
+
```
1981
+
77 INX-B USAGE IS INDEX.
1982
+
...
1983
+
SET INX-A TO 10.
1984
+
SET INX-B TO INX-A.
1985
+
PERFORM VARYING INX-A FROM 1 BY 1 UNTIL INX-A > INX-B
1986
+
DISPLAY TABLE-ELEMENT (INX-A)
1987
+
...
1988
+
END-PERFORM.
1989
+
```
1990
+
1991
+
The index name INX-A is used to traverse the TABLE-ELEMENT table, while INX-B is used to hold the index of the last element of the table. By doing this, we minimize the calculation of offsets and no conversion will be necessary for the UNTIL condition.
1992
+
1993
+
We can also increment or decrement an index name by an elementary integer data item. For example,
1994
+
1995
+
```
1996
+
SET INX-A DOWN BY 3
1997
+
```
1998
+
1999
+
The integer there represents the number of occurences. So it will be converted to an index value first before it adds or subtract the index.
2000
+
2001
+
Since we are comparing physical displacements, we cannot use index data items as subscripts or indexes. We can only directly use it in SEARCH and SET statements or in comparisons with indexes.
2002
+
2003
+
The following example shows how to calculate displacements to elements that are referenced with indexes.
2004
+
2005
+
Consider the following two dimensional table, TABLE-2D:
2006
+
2007
+
```
2008
+
01 TABLE-2D.
2009
+
05 TABLE-ROW OCCURS 2 TIMES INDEXED BY INX-A.
2010
+
10 TABLE-COL OCCURS 5 TIMES INDEXED BY INX-B PIC X(4).
2011
+
```
2012
+
2013
+
Suppose we code the following index:
2014
+
2015
+
```
2016
+
TABLE-COL (INX-A + 2, INXB - 1)
2017
+
```
2018
+
2019
+
This will cause the computation of the displacement to the TABLE-COL element:
2020
+
2021
+
```
2022
+
(contents of INX-A) + (20 * 2) + (contents of INX-B) - (4 * 1)
2023
+
```
2024
+
2025
+
The calculation is based on the length of the elements. Each occurence of TABLE-ROW is 20 bytes in length (5 * 4) and each occurence of TABLE-COL is 4 bytes in length.
2026
+
2027
+
## Loading a table with data
2028
+
2029
+
There are many ways we can load a table. The first one involves loading the table dynamically, from a screen, file or database. We can also use the REDEFINES clause on hard-coded field values along with an OCCURS clause. The third way is using the INITIALIZE statement, and lastly, we can also use the VALUE clause when defining the table.
2030
+
2031
+
### Loading a table dynamically
2032
+
2033
+
To load a table dynamically, we need to use the PERFORM statement with either subscripting or indexing. When doing this, we need to make sure that the data does not exceed the space allocated for the table. We will discuss file handling and the use of PERFORM clause at a later chapter. For example,
2034
+
2035
+
```
2036
+
PROCEDURE DIVISION
2037
+
...
2038
+
PERFORM READ-FILE.
2039
+
PERFORM VARYING SUB FROM 1 BY 1 UNTIL END-OF-FILE
2040
+
MOVE DATA TO WS-DATA(SUB)
2041
+
PERFORM READ-FILE
2042
+
END-PERFORM.
2043
+
```
2044
+
2045
+
In this example above, we execute a paragraph which read files, and then we will iterate through every line of the file until the end, putting each value into the table.
2046
+
2047
+
### REDEFINES a hard-coded values
2048
+
2049
+
Consider the following example,
2050
+
2051
+
```
2052
+
WORKING-STORAGE SECTION.
2053
+
01 NUMBER-VALUES.
2054
+
05 FILLER PIC X(05) VALUE "One "
2055
+
05 FILLER PIC X(05) VALUE "Two "
2056
+
05 FILLER PIC X(05) VALUE "Three"
2057
+
05 FILLER PIC X(05) VALUE "Four "
2058
+
05 FILLER PIC X(05) VALUE "Five "
2059
+
2060
+
01 NUMBER-TABLES REDEFINES NUMBER-VALUES.
2061
+
05 WS-NUMBER PIC X(05) OCCURS 5 TIMES.
2062
+
```
2063
+
2064
+
Here, we are taking hard-coded values of spelled out numbers from 1 to 5 and loading them to a table through the use of a REDEFINES clause.
2065
+
2066
+
### INITIALIZE a table
2067
+
2068
+
We can also use the INITIALIZE statement to load data into a table. The table will be processed as a group item and each elementary data item within it will be recognized and processed. For example, assume that we have the following table:
2069
+
2070
+
```
2071
+
01 TABLE-ONE.
2072
+
05 TABLE-ELEMENT OCCURS 10 TIMES.
2073
+
10 NUMBER-CODE PIC 9(02) VALUE 10.
2074
+
10 ITEM-ID PIC X(02) VALUE "R3".
2075
+
```
2076
+
2077
+
Here we have a table that contains 10 elements, each with their own NUMBER-CODE (with a value of 10) and ITEM-ID (with a value of "R3").
2078
+
2079
+
We can move the value 3 to each of the elementary numeric data items and the value "X" into each of the elementary alphanumeric data items in the table:
2080
+
2081
+
```
2082
+
INITIALIZE TABLE-ONE REPLACING NUMERIC DATA BY 3.
2083
+
INITIALIZE TABLE-ONE REPLACING ALPHANUMERIC DATA BY "X".
2084
+
```
2085
+
2086
+
After running the two INITIALIZE statements, NUMBER-CODE will contain the value of 3, while ITEM-ID will contain the value of "X ".
2087
+
2088
+
### Assigning values using VALUE clause
2089
+
2090
+
If a table is expected to contain stable values, we can set them when defining the table. Take for example, the WEEK-DAY-TABLES and TABLE-ONE on the previous sections. Both of them have assigned values when defined. Here are some more examples:
2091
+
2092
+
```
2093
+
01 TABLE-TWO VALUE "1234".
2094
+
05 TABLE-TWO-DATA OCCURS 4 TIMES PIC X.
2095
+
```
2096
+
2097
+
In the above example, the alphanumeric group data item TABLE-TWO uses a VALUE clause which initialize each of the four element of TABLE-TWO-DATA. So after initialization, TABLE-TWO-DATA(1) will contain the alphanumeric '1', TABLE-TWO-DATA(2) will contain the alphanumeric '2' and so on.
2098
+
2099
+
## Variable-length tables
2100
+
2101
+
If we do not know before runtime how many times a table element will occur, we can define a variable-length table using the OCCURS DEPENDING ON (ODO) clause.
2102
+
2103
+
```
2104
+
X OCCURS 1 TO 10 TIMES DEPENDING ON Y
2105
+
```
2106
+
2107
+
In the above example, X is the ODO subject and Y is the ODO object.
2108
+
2109
+
There are a couple of factors affecting the successful manipulation of variable-length records:
2110
+
2111
+
- Correct calculation of record lengths
2112
+
2113
+
Here, the length of the variable portion is the product of the object of the DEPENDING ON phrase and the length of the subject of the OCCURS clause.
2114
+
2115
+
- Conformance of the data in the object of the OCCURS DEPENDING ON clause to its PICTURE clause
2116
+
2117
+
We must ensure that the ODO object correctly specifies the number of occurences of table elements, or the program could terminate abnormally.
2118
+
2119
+
The following example shows how we can use an OCCURS DEPENDING ON clause:
2120
+
2121
+
```
2122
+
WORKING-STORAGE SECTION
2123
+
01 MAIN-AREA.
2124
+
03 REC-1.
2125
+
05 FIELD-1 PIC 9.
2126
+
05 FIELD-2 OCCURS 1 TO 5 TIMES
2127
+
DEPENDING ON FIELD-1 PIC X(05).
2128
+
01 REC-2.
2129
+
03 REC-2-DATA PIC X(50).
2130
+
```
2131
+
2132
+
If we are moving REC-1 to REC-2, the length of REC-1 will be determined immediately before-hand using the current value of FIELD-1. If FIELD-1 doesn't conform to its PICTURE clause, the result is unpredictable. So, we need to ensure that the ODO object (FIELD-1) has the correct value before moving REC-1 to REC-2.
2133
+
2134
+
On the otherhand, if we are moving to REC-1, the length is determined using the maximum number of occurences. However, if REC-1 is followed by a variably located group, the ODO object will be used in calculation of the actual length of REC-1. An example of such case is provided below:
2135
+
2136
+
```
2137
+
01 MAIN-AREA.
2138
+
03 REC-1.
2139
+
05 FIELD-1 PIC 9.
2140
+
05 FIELD-3 PIC 9.
2141
+
05 FIELD-2 OCCURS 1 TO 5 TIMES
2142
+
DEPENDING ON FIELD-1 PIC X(05).
2143
+
03 REC-2.
2144
+
05 FIELD-4 OCCURS 1 TO 5 TIMES
2145
+
DEPENDING ON FIELD-3 PIC X(05).
2146
+
```
2147
+
2148
+
So in the case above, the value of the ODO object must be set before using the group item as a receiving field.
2149
+
2150
+
## Searching a table
2151
+
2152
+
There are two techniques for searching a table: serial and binary.
2153
+
2154
+
A binary search can be more efficient than a serial search, however it requires that the table items already be sorted.
2155
+
2156
+
### Serial search
2157
+
2158
+
We can do a serial search by using the SEARCH statement. The search will begin at the current index setting and will continue until the condition in the WHEN phrase is fulfilled. To modify the index setting, we can use the SET statement. If there are multiple conditions in the WHEN phrase, the search will end when the one of the conditions is satisfied and the index will remain pointing to the element that satisfied the condition.
2159
+
2160
+
For example, assume that we have a list of names:
2161
+
2162
+
```
2163
+
77 PEOPLE-SEARCH-DATA PIC X(20).
2164
+
01 PEOPLE-SERIAL.
2165
+
05 PEOPLE-NAME OCCURS 50 TIMES
2166
+
INDEXED BY PL-IDX PIC X(20).
2167
+
...
2168
+
PROCEDURE-DIVISION.
2169
+
...
2170
+
SET PL-IDX TO 1.
2171
+
SEARCH PEOPLE-NAME VARYING PL-IDX
2172
+
AT END DISPLAY "Not found"
2173
+
WHEN PEOPLE-SEARCH-DATA = PEOPLE-NAME(PL-IDX)
2174
+
DISPLAY "Found".
2175
+
```
2176
+
2177
+
The code above will search the list of names from an index of 1. If it found the content of PEOPLE-SEARCH-DATA, it will DISPLAY "Found", otherwise, it will DISPLAY "Not found".
2178
+
2179
+
For a more complex use case, we can also use nested SEARCH statements. We will need to delimit each nested SEARCH statements with END-SEARCH.
2180
+
2181
+
### Binary search
2182
+
2183
+
To do a binary search, we can use a SEARCH ALL statement. We do not need to set the index, but it will use the one associated in the OCCURS clause. To use the SEARCH ALL statement, the table must specify the ASCENDING or DESCENDING KEY phrases of the OCCURS clause, or both, and it must be ordered on the specified key.
2184
+
2185
+
Using the WHEN phrase, you can test any key that is named in the ASCENDING or DESCENDING KEY phrases. The test must be an equal-to condition, and the WHEN phrase must specify either a key or a condition-name associated with the key.
2186
+
2187
+
For example, assume that we have a list of names sorted in an ascending order:
2188
+
2189
+
```
2190
+
77 PEOPLE-SEARCH-DATA PIC X(20).
2191
+
01 PEOPLE-TABLE-BINARY.
2192
+
05 PEOPLE-NAME OCCURS 50 TIMES
2193
+
ASCENDING KEY IS PEOPLE-NAME
2194
+
INDEXED BY PL-IDX PIC X(20).
2195
+
...
2196
+
PROCEDURE-DIVISION.
2197
+
...
2198
+
SEARCH ALL PEOPLE-NAME
2199
+
AT END DISPLAY "Not found"
2200
+
WHEN PEOPLE-SEARCH-DATA = PEOPLE-NAME(PL-IDX)
2201
+
DISPLAY "Found".
2202
+
```
2203
+
2204
+
The code above will search the alphabetically-sorted list of names. If it found the content of PEOPLE-SEARCH-DATA, it will DISPLAY "Found", otherwise, it will DISPLAY "Not found".
2205
+
2206
+
## Lab
2207
+
2208
+
**Note** : It may take a few seconds to load in all segments of this lab. If files are not loading, hit the refresh button on the list that appears when hovering over the section bar.
2209
+
2210
+
1. View the SRCHSER COBOL source code member in the 'id'.CBL data set.
2211
+
2212
+
2. Submit the JCL member, SRCHSERJ, from the id.JCL, where id is your id,dropdown. This is where id.JCL(SRCHSERJ) compiles and successfully executes the SRCHSER program.
2213
+
2214
+
3. View both compile and execution of SRCHSERJ job output.
2215
+
2216
+
4. Next, view SRCHBIN COBOL source code member in id.CBL data set.
2217
+
2218
+
5. View and submit the JCL member, SRCHBINJ, from the id.JCL dropdown. This is where id.JCL(SRCHBINJ) compiles and executes the SRCHBIN program.
2219
+
2220
+
6. View the compile and execution of SRCHBINJ job output.
2221
+
2222
+
7. Compare SRCHSER with SRCHBIN. Do you notice the differences?
2223
+
2224
+
a. Observe how the tables are defined.
2225
+
2226
+
b. Observe how the tables are loaded from the id.DATA data set.
2227
+
2228
+
c. Observe the SEARCH and SEARCH ALL statement.
2229
+
2230
+
\newpage
2231
+
1906
2232
# File handling
1907
2233
1908
2234
The previous chapter and lab focused on variables and moving literals into variables, then writing variable content using the COBOL DISPLAY statement. This section introduces reading records from files into variables, moving the variables to output variables, and writing the output variables to a different file. A simple COBOL program to read each record from a file and write each record to a different file is used to illustrate COBOL code necessary to read records from an input external data source and write records to an output external data source.
0 commit comments