Skip to content

A Brief Example

Dave Nicolette edited this page Feb 19, 2021 · 10 revisions

Home -> User Guide ->

This document was last updated on February 11, 2021.

Description

The unit test precompiler copies the program under test and inserts test code into the WORKING-STORAGE SECTION and PROCEDURE DIVISION. The test code consists of

  • a user-written test suite along the lines of the sample below;
  • copybook CCHECKWS.CPY containing WORKING-STORAGE entries used by cobol-check; and
  • copybook CCHECKPD.CPY containing PROCEDURE DIVISION code used by cobol-check.

You write the test cases using syntax like that in the sample and save the test suite as a Cobol copybook. We have found Cobol programmers are often able to guess what to write, as the tool's syntax approximates typical Cobol source code.

You can then run the copy of the program, which executes the isolated unit test cases without running the program from start to finish.

A brief sample

           TESTSUITE 'CONVERT COMMA-DELIMITED FILE TO FIXED FORMAT' 

      *****************************************************************
      * COBOL COMMENTS ARE IGNORED SO YOU CAN DO THIS SORT OF THING IF
      * YOU PLEASE.
      *****************************************************************  

           BEFORE-EACH
               MOVE FOO TO BAR
               MOVE ZERO TO WS-COUNT
           END-BEFORE

           AFTER-EACH
               INITIALIZE WS-RESULTS-TABLE
           END-AFTER

           TESTCASE 'IT CONVERTS TEXT FIELD 1 TO UPPER CASE' 
               MOVE 'something' TO TEXT-VALUE-1
               PERFORM 2100-CONVERT-TEXT-FIELD-1
               EXPECT TEXT-OUT-1 TO BE 'SOMETHING'

           TESTCASE 'IT HANDLES FILE NOT FOUND GRACEFULLY'
               MOCK
                   FILE INPUT-FILE 
                   ON OPEN STATUS FILE-NOT-FOUND
               END-MOCK    
               PERFORM 0100-OPEN-INPUT
               EXPECT WS-INPUT-FILE-STATUS TO BE '35'
               EXPECT WS-FRIENDLY-MESSAGE TO BE 'SORRY, COULDN''T FIND INPUT-FILE'

Arrange-Act-Assert

The standard sequence of steps in an automated check consist of

  • Arrange - set up the preconditions for the case
  • Act - run the code under test
  • Assert - assert the expected result of the test

The sample contains two test cases. In the first, the Arrange step consists of this code:

               MOVE 'something' TO TEXT-VALUE-1

This is a plain Cobol MOVE statement that populates a field in the WORKING-STORAGE SECTION of the program under test. It sets the precondition for the test case: TEXT-VALUE-1 contains a lower-case value.

The Act step consists of:

               PERFORM 2100-CONVERT-TEXT-FIELD-1

This is a plain Cobol PERFORM statement that runs the paragraph we are interested in checking.

The Assert step consists of:

               EXPECT TEXT-OUT-1 TO BE 'SOMETHING'

Here we have some special cobol-check code. The keyword EXPECT and the tokens TO BE are defined in cobol-check. They are not standard Cobol, but they are Cobol-like or Cobol-ish. Programmers can understand the intent of the code quite easily. In this case, we expect the contents of field TEXT-OUT-1 to be the same value as TEXT-VALUE-1 contained before running paragraph 2100-CONVERT-TEXT-FIELD-1, only in uppercase.

The second sample test case also follows the Arrange-Act-Assert pattern. In this example, the Arrange code is:

               MOCK
                   FILE INPUT-FILE 
                   ON OPEN STATUS FILE-NOT-FOUND
               END-MOCK    

To set up this test case, cobol-check comments the code that opens file INPUT-FILE and moves '35' to the file status item.

The Act step consists of this code:

               PERFORM 0100-OPEN-INPUT

This is a standard Cobol PERFORM statement that runs just the one paragraph we want to check. When the code under test opens file INPUT-FILE, status code 35 (NOT FOUND) is set by the MOCK code cobol-check inserted into the test copy of the program under test.

Finally, the code for the assert step contains two assertions:

               EXPECT WS-INPUT-FILE-STATUS TO BE '35'
               EXPECT WS-FRIENDLY-MESSAGE TO BE 'SORRY, COULDN''T FIND INPUT-FILE'

These contain EXPECT clauses as you saw in the first example. In this case, our expectation is that code in paragraph 0100-OPEN-INPUT will set the indicated values in the two WORKING-STORAGE items, WS-INPUT-FILE-STATUS and WS-FRIENDLY-MESSAGE.

Test cases can contain an arbitrary amount of code consisting of standard Cobol statements and cobol-check keywords.

Notes

The precompiler recognizes certain keywords and substitutes test code, so that you need not write a lot of boilerplate code manually. Clearly, you could write equivalent code in plain Cobol. We believe there is value in the DSL as it makes the test cases shorter and more revealing of their intent than the equivalent code in plain Cobol. Please see the wiki for syntax details.

TESTSUITE - Provides a description for a series of test cases. The description is echoed in the output from the test run.

MOCK - declares a mock. Current version has support for mocking EXEC CICS commands, Cobol CALL statements, and rudimentary support for mocking batch file I/O.

BEFORE-EACH, AFTER-EACH - the precompiler copies these statements into paragraphs that are performed at the start and end of each test case.

TESTCASE - identifies a test case. The description is echoed in the output of the test run.

EXPECT - asserts an expected result. Current version supports PIC X, numeric, and 88-level compares.

VERIFY - verifies that a mock was accessed the expected number of times.

The precompiler ignores Cobol-style comment lines.

Clone this wiki locally