# 30ish (non-contiguous) days of Cobol

Am I mad? 😄 Just curious.

Heard on a podcast that in 2004 there were ~2,000,000 Cobol programmers and that number was declining 5% annually (I believe this came from gartner). That would put us at ~835,000 today (2021). I have no idea how you'd actually confirm that.

https://www.youtube.com/watch?v=RdMAEdGvtLA 20 mins in

# Day 1: Installing Cobol and running Hello world!

  • Install cobol, On a mac: brew install gnu-cobol | on Debian sudo apt install open-cobol
  • Check the install worked cobc -v
  • Copy the example hello world program (./1-helloworld)
  • (Install something for syntax highlighting, eg Z Open Editor for VSCode)
  • Compile the program: cobc -x helloworld.cob
  • Run the program ./helloworld Tada!

# Day 2: Cobol columns

| 1 2 3 4 5 6 | 7 | 8 9 10 11 | 12 - 72 | 73 - 80 | | | | | Identification Area | | | | | The compiler ignores this, put whatever you want | | | | | | | | | B Area | | | | The code | | | | Entries, sentences, statements, clauses | | | | level-numbers: 02 thru 49, 66 or 88 | | | | | | | A Area | | | Division headers | | | Section headers | | | Paragraph headers / names | | | Levels: FD SD 01 66 77 88 | | | Declaratives | | | END markers: PROGRAM, CLASS, METHOD, OBJECT, FACTORY | | | | | Indicator area | | * comment | | - continue previous line | | d debugging line | | / source code listing formatting
| | | Sequence area | Used to label the line | Any characters are valid

# Day 3: Vertical Structure

Divisions must appear in this order.

IDENTIFICATION DIVISION. - metadata ENVIRONMENT DIVISION. - system requirements / expectations CONFIGURATION SECTION. - define the type of computer / env needed to run this program. INPUT-OUTPUT SECTION. - maps files in the code to files in the JCL. Kind of like defining your types if types were files. DATA DIVISION. FILE SECTION. - defines the structure of data files that the program will be working with. WORKING-STORAGE SECTION. - global variables, initialized at the start of the programs run. LOCAL-STORAGE SECTION. - variables scoped to a function or method (any runtime call) THREAD-LOCAL-STORAGE SECTION. - unique per thread, cannot be used in class programs compiled for managed code (but can be used in procedural COBOL programs compiled to managed code) OBJECT-STORAGE SECTION. - Class and instance object data... maybe this'll become clearer later. LINKAGE SECTION. - used to map data between programs or the jcl (eg global variables that span programs) REPORT SECTION. - used to "write reports" (print data to a file) http://www.pgrocer.net/Cis52/rptwritr.html SCREEN SECTION. - used to create interactive screens for data entry/editing PROCEDURE DIVISION. - the code!

"PARAGRAPH" seems pretty comparable to what I think of as a function (coming from Javascript). "SENTENCE" I think this is pushing the whole "human speak" metaphor a bit far. Some lines end with ., comparable to ; in JS.

# Day 4: Variables, PIC / PICTURE

Cobol has defined types & lengths, this allows it to be super efficient. The key (the variable name) can be no longer than 30 chars.

  • Numeric
    • PIC 9 - single digit number
    • PIC 9(4) - 4 digit number
    • PIC 99V99 || PIC 9(2)V9(2) || PIC 9(2)V99 || PIC 99V9(2) - 25.31
  • Alphabetic
  • Alphanumeric
    • PIC X - single character alphanumeric
    • PIC X(4) - 4 char alphanumeric
  • Currency symbol cs

Cobol also has Literals, or in JS terms a const.

Built in literals:

  • ZERO ZEROS
  • SPACE SPACES
  • LOW-VALUE
  • HIGH-VALUE
  • NULL NULLS

# Day 5: level numbers

01 A area 02 - 49 B area

Level numbers indicate (no hard rules here) the relationship of subdivided data. eg 01 CUSTOMER. 05 ADDRESS. 10 STREET PIC X(10). 10 POSTCODE PIC X(10). 05 NAME. 11 FIRST PIC X(10). 11 LAST PIC X(10). Indentation not required

FD file description SD sort-merge file description

66 A or B area contains that must contain a RENAMES clause 77 A area WORKING-STORAGE, LOCAL-STORAGE, or LINKAGE SECTION items 88 A or B area condition entries

# Day 6: The JCL

The JCL is mentioned all over the place...?

"Job Control Language" The system used to tell z/OS what to do through "JCL statements" (or "JCL cards" as they used to be passed in via punch cards).

  • JOB a unit of work, one or a set of programs.
  • EXEC the name? of the JCL procedure to run
  • DD "Data Defenition" input and output for the program run by EXEC.

Side note, z/OS is an IBM OS for IBM mainframes. You can run linux on a mainframe for more versatility but performance apparently takes a hit as it'd be run in a vm. Also found notes saying it's better to use z/OS if you're planning to run cobol programs.

So mainframes (up until now all I knew was the name): Enjoyed this video summarising what a mainframe is (opens new window)

  • massive number of in/out throughput
  • automatic redundncy (so you can take out a rack of processors from a running mainframe and pop a new one in without stopping it - they apparently can go decades between restarts)
  • crazy expensive
  • can you simulate one locally for testing? Hercules (opens new window) looks to be the main one. I'll maybe get to that later

# Day 7: Some reserve words / Cobol verbs

  • MOVE "thing" TO MYVAR or in JS, MYVAR = "thing"
  • COMPUTE DOUBLETHING = MYVAR * 2 or in JS, DOUBLETHING = MYVAR * 2
  • PERFORM, similar to when you call a function (paragraph), though this can do loops as well
  • GO TO, like perform but won't return
  • FILLER, used to define values for variables that will be used in reports (usually)
  • SEARCH iterate throughsomething until you meet a condition

# Day 8: working with files!

Example code in ./2-files.

Cobol has acces to traditional z/OS data sets (records) & unix files.

Within files

  • Each line is a record
  • The line is divided up between the different fields
  • each field has an explicit length so the layout of every record is the same (in terms of character length)

Blocks are defenitions of the physical size of a physical record.

When writing data cobol gives us a few different recording modes (eg FD YOUR-FILE RECORDING MODE F.) Apparently this is irrelivent for Windows, DOS, and Unix. Only of use in ... These impact how data is stored in "blocks".

  • F fixed
  • V variable
  • U is F or V
  • S spanned

We can open files in different modes:

  • OUTPUT: when you want to write to a file without worrying about anything that might alrady be there.
  • EXTEND: to append data to a file
  • I-O: to modify data in a file
  • INPUT: read ony

File organization

  • ORGANIZATION IS SEQUENTIAL append
  • ORGANIZATION IS INDEXED requires a data file & an index file, allows random access
  • ORGANIZATION IS RELATIVE relative from the start of the file. Fastest access but likely te least efficent use of space.

File access modes

  • ACCESS MODE IS SEQUENTIAL reads records in the order defined by the file organization (seq / index / relativ)
  • ACCESS MODE IS RANDOM allows you to jump to the part of the file you're interested in, by index or relative, not sequence it seems.
  • ACCESS MODE IS DYNAMIC Allows you to swap between sequential and dynamic access modes

# Day 9: Program Flow

Paragraphs seem to be like JS functions in that they are named sections of code that you can call with PERFORM. However, it also looks like and the program executes, it will move through paragraphs it comes accross. They also don't have scope in the way we'd think of it in JS.

Linkage. Calling one program from another.

CALL 'MY-PROGRAM-ID' USING VARIABLE-NAME-1, VARIABLE-NAME-2

Then in your program:

LINKAGE SECTION
01 VARIABLE-1-LS PIC 9
01 VARIABLE-2-LS PIC 99

(Note the variable name is postfixed with LS, that's not required just handy apparently!)

# Day 10: Reports

# Day 11: conditionals

variable level needs to be 88 88 MY-CONDITION-VAR-NAME VALUE 'Only true if equal to this value'

IF MY-CONDITION-VAR-NAME DISPLAY 'It is true'

Or there's the switch statement like EVALUATE

EVALUATE MY-CONDITION-VAR-NAME
  WHEN 'One'
    DISPLAY '1'
  WHEN 'Two'
    DISPLAY '2'
END-EVALUATE