FunctionsLibrary - TypeCobolTeam/TypeCobol GitHub Wiki
This page describes how to:
-
declare public functions or procedures in a "public library" file called
LIBRARY.cbl
-
call these public functions or procedures from a program called
CALLER.cbl
This page describes many rules regarding function or procedure declaration. All these rules begin with TCRFUN_. Procedure or function codegen rules begin with TCRFUN_CODEGEN_.
Such rules are written with one of the following 2 formats:
IDENTIFICATION DIVISION.
PROGRAM-ID. LIBRARY.
DATA DIVISION.
WORKING-STORAGE SECTION.
PROCEDURE DIVISION. *> TCRFUN_PROCEDURE_NO_USING
* function declaration
* - cannot have any OUTPUT or INOUT parameter
* - can have 0..1 RETURNING parameter
DECLARE ValidateDateFormat PUBLIC
INPUT mydate TYPE Date
format PIC X(08)
RETURNING okay TYPE Bool.
DATA DIVISION.
LOCAL-STORAGE SECTION.
* function internal data declaration
* scope of these variables is one function call
WORKING-STORAGE SECTION.
* function internal data declaration
* scope of these variables extends accross all calls to this function
PROCEDURE DIVISION.
* function implementation
* - can read input parameters mydate and format
* - must write result into parameter okay
.
END-DECLARE.
* functions do not need to take any input parameters
DECLARE GetCurrentDate PUBLIC
RETURNING result TYPE Date.
PROCEDURE DIVISION.
* function implementation
.
END-DECLARE.
* procedure declaration
* - can have 0..N OUTPUT or INOUT parameters
* - cannot have any RETURNING parameter
DECLARE ValidateDateFormat PUBLIC
INPUT mydate TYPE Date
format PIC X(08)
OUTPUT okay TYPE Bool
actual-format PIC X(08).
* can have DATA DIVISION as a function
PROCEDURE DIVISION.
* procedure implementation
* - can read input parameters mydate and format
* - must write output parameters okay and actual_format
.
END-DECLARE.
END PROGRAM LIBRARY.
-
Calling any function from this library using a
COPY
in a COBOL 85 program is discouraged.
IDENTIFICATION DIVISION.
PROGRAM-ID. LIBRARY.
* SERVICE ID YLIBCOPY. *> TCRFUN_LIBRARY_COPY
DATA DIVISION.
WORKING-STORAGE SECTION.
* TCRFUN_CODEGEN_IS_LOADED
01 LibFctList-Loaded PIC X(01) VALUE SPACE.
88 LibFctList-IsLoaded VALUE '1'.
01 LibFctList-VALUES. *> TCRFUN_CODEGEN_POINTER_ARRAY
05 PIC X(08) VALUE 'F0000001'.
05 PIC X(08) VALUE LOW-VALUES.
05 PIC X(08) VALUE 'F0000002'.
05 PIC X(08) VALUE LOW-VALUES.
05 PIC X(08) VALUE 'F0000003'.
05 PIC X(08) VALUE LOW-VALUES.
01 LibFctList REDEFINES LibFctList-Values. *> TCRFUN_CODEGEN_REDEFINED_ARRAY
* OCCURS clause is equal to the number of PUBLIC
* functions and procedures defined in this file
05 LibFctItem OCCURS 3 INDEXED BY LibFctIndex.
10 LibFctCode PIC X(08).
10 LibFctPointer PROCEDURE-POINTER.
LINKAGE SECTION.
01 FctList. *> TCRFUN_CODEGEN_CALLS_ARRAY
05 NumberOfFunctions PIC 9(04).
05 FctItem OCCURS 9999 DEPENDING ON NumberOfFunctions
INDEXED BY FctIndex.
10 FctCode PIC X(08).
10 FctPointer PROCEDURE-POINTER VALUE NULL.
COPY YLIBCOPY REPLACING ==:YLIBCOPY:== BY ==FCT==. *> TCRFUN_CODEGEN_LIBRARY_COPY
01 CallData. *> TCRFUN_CODEGEN_CALL_DATA
05 DescriptionId PIC X(08).
88 CallIsCopy VALUE 'YLIBCOPY'.
PROCEDURE DIVISION USING CallData. *> TCRFUN_CODEGEN_PROCEDURE_DIVISION
IF CallIsCopy *> TCRFUN_CODEGEN_ADAPTABLE_BEHAVIOUR
* If the called function is invoked via a COPY,
* CallData begins with 'YDVZDAT'
PERFORM Copy-Process-Mode
ELSE
* Else the called function is invoked TypeCobol-style, CallData contains an array
* of functions pointers: 1 per call to a different fonction in the caller
* (the array can contain pointers to libraries other than this one)
PEFORM FctList-Process-Mode
END-IF
GOBACK
.
Copy-Process-Mode. *> TCRFUN_CODEGEN_COBOL_BEHAVIOUR
SET ADDRESS OF FCT TO ADDRESS OF CallData
SET FCT-ValidateFormat-01 TO ENTRY 'F0000001'
SET FCT-GetCurrentDate-01 TO ENTRY 'F0000002'
SET FCT-ValidateFormat-02 TO ENTRY 'F0000003'
.
FctList-Process-Mode. *> TCRFUN_CODEGEN_TYPECOBOL_BEHAVIOUR
SET ADDRESS OF FctList TO ADDRESS OF CallData
IF NOT LibFctList-IsLoaded
SET LibFctPointer(1) TO ENTRY 'F0000001'
SET LibFctPointer(2) TO ENTRY 'F0000002'
SET LibFctPointer(3) TO ENTRY 'F0000003'
SET LibFctList-IsLoaded TO TRUE
END-IF
PERFORM VARYING FctIndex FROM 1 BY 1
UNTIL FctIndex > NumberOfFunctions
SEARCH LibFctItem VARYING LibFctIndex
WHEN LibFctCode(LibFctIndex) = FctCode(FctIndex)
SET FctPointer(FctIndex) TO LibFctPointer(LibFctIndex)
END-SEARCH
END-PERFORM
* TypeCobol declaration is commented out
* COBOL implementation of these declarations
* are found at the end of the file
*DECLARE ValidateDateFormat PUBLIC
* INPUT mydate TYPE Date
* format PIC X(08)
* RETURNING okay TYPE Bool.
*DECLARE ValidateDateFormat PUBLIC
* INPUT mydate TYPE Date
* format PIC X(08)
* OUTPUT okay TYPE Bool
* actual-format PIC X(08).
.
END PROGRAM LIBRARY.
* function ValidateDateFormat is now a subprogram
IDENTIFICATION DIVISION.
PROGRAM-ID. F0000002.
DATA DIVISION.
LINKAGE SECTION.
01 mydate.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
01 format PIC X(08).
01 okay-value PIC X VALUE LOW-VALUE.
88 okay VALUE ‘T’.
88 okay-false VALUE ‘F’.
PROCEDURE DIVISION.
* function implementation
.
END PROGRAM F0000001.
* function GetCurrentDate is now a subprogram
IDENTIFICATION DIVISION.
PROGRAM-ID. F0000002.
DATA DIVISION.
LINKAGE SECTION.
01 result.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
PROCEDURE DIVISION.
* function implementation
.
END PROGRAM F0000002.
* procedure ValidateDateFormat is now a subprogram
IDENTIFICATION DIVISION.
PROGRAM-ID. F0000003.
DATA DIVISION.
LINKAGE SECTION.
01 mydate.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
01 format PIC X(08).
01 okay-value PIC X VALUE LOW-VALUE.
88 okay VALUE ‘T’.
88 okay-false VALUE ‘F’.
01 actual-format PIC X(08).
PROCEDURE DIVISION.
* procedure implementation
.
END PROGRAM F0000003.
The following rules apply only to a TypeCobol program containing at least one PUBLIC function declaration. Such a program is be called a library.
-
✓ TCRFUN_CODEGEN_POINTER_ARRAY
An array of pointers to COBOL programs corresponding to TypeCobol functions must be generated inWORKING-STORAGE SECTION
. There must be two items in this array for each declaredPUBLIC
function : a uniquePIC X(08)
hash and a function pointer. -
✓ TCRFUN_CODEGEN_REDEFINED_ARRAY
AREDEFINES
of the pointer array must be generated inWORKING-STORAGE SECTION
. -
✓ TCRFUN_CODEGEN_IS_LOADED
A condition item for whether or not the pointer array is loaded must be generated inWORKING-STORAGE SECTION
. -
✓ TCRFUN_CODEGEN_LIBRARY_COPY
A copy directive using the copy name defined by TCRFUN_LIBRARY_COPY must be generated inLINKAGE SECTION
. -
✓ TCRFUN_CODEGEN_CALL_DATA
An item allowing the library to figure out which way it is called (either from a TypeCobol function call or a standard COBOLCALL
statement) must be generated inLINKAGE SECTION
.-
If the library function is called with a
COPY
, this item must contain:-
the copy name, if and only if it was declared (see rule TCRFUN_LIBRARY_COPY) ;
-
the fixed label
'CALL FROM COBOL NOT SUPPORTED'
if no copy name was declared.
-
-
If the library function is used through a TypeCobol function call, this item must be an array containing one element for each function called by the caller program.
-
-
✓ TCRFUN_CODEGEN_CALLS_ARRAY
An array containing all functions used by the caller (either from the current library or from others) must be generated inLINKAGE SECTION
. -
✓ TCRFUN_CODEGEN_PROCEDURE_DIVISION
PROCEDURE DIVISION
is modified by the addition of theUSING CallData
directive.
CallData
lets the library know if it is called either TypeCobol-style or with a COPY from a Cobol 85 program. -
✓ TCRFUN_CODEGEN_ADAPTABLE_BEHAVIOUR
If the library is called from a TypeCobol function call, theFctList-Process-Mode
paragraph must be performed. If the library is called from a standard Cobol 85 program with aCOPY
, theCopy-Process-Mode
paragraph must be performed.
This conditional behaviour is implemented usingCallData
and must be generated at the beginning of thePROCEDURE DIVISION
. -
✓ TCRFUN_CODEGEN_TYPECOBOL_BEHAVIOUR
TheFctList-Process-Mode
paragraph must be generated in thePROCEDURE DIVISION
. -
✓ TCRFUN_CODEGEN_COPY_BEHAVIOUR
TheCopy-Process-Mode
paragraph must be generated in thePROCEDURE DIVISION
. -
❏ TCRFUN_CODEGEN_COPY
At the same time the output COBOL program is generated from the input TypeCobol library file, a second output COBOL file must be generated. The name of this second file is given by the TCRFUN_LIBRARY_COPY rule. This second file is a COBOL copy. It allows calling all TypeCobolPUBLIC
functions of the input library from a standard COBOL program by declaring a group item containing:-
first, the copy name ;
-
second, the library version number ;
-
then, all data items referenced in the
Copy-Process-Mode
paragraph (defined by the TCRFUN_CODEGEN_COPY_BEHAVIOUR rule) ; -
last, a memory span of a size equal to
427 -8 -3 -8×<number of PUBLIC functions>
(or0
, if there are more than 42PUBLIC
functions).
-
According to the current example, the contents of the copy file are as follows:
01 :YLIBCOPY:.
02 PIC X(08) VALUE 'YLIBCOPY'.
02 PIC X(03) VALUE '000'.
02 :YLIBCOPY:-FunctionPointers.
05 :YLIBCOPY:-ValidateFormat-01 PROCEDURE-POINTER VALUE NULL.
05 :YLIBCOPY:-GetCurrentDate-01 PROCEDURE-POINTER VALUE NULL.
05 :YLIBCOPY:-ValidateFormat-02 PROCEDURE-POINTER VALUE NULL.
05 :YLIBCOPY:-Reserve PIC X(392).
IDENTIFICATION DIVISION.
PROGRAM-ID. CALLER.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 caller-date TYPE DATE.
01 caller-format PIC X(08).
01 caller-actual PIC X(08).
01 caller-result TYPE BOOL.
* TypeCobol types mimicked for COBOL-specific examples
01 SomeCOBOLDate.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
01 SomeCOBOLBOOL-value PIC X VALUE LOW-VALUE.
88 SomeCOBOLBOOL VALUE ‘T’.
88 SomeCOBOLBOOL-false VALUE ‘F’.
PROCEDURE DIVISION.
* --------------------------------------------------
* TypeCobol-style function call
MOVE FUNCTION ValidateDateFormat (caller-date caller-format) TO caller-result
* --------------------------------------------------
* TypeCobol-style procedure call
CALL ValidateDateFormat INPUT caller-date caller-format
OUTPUT caller-result caller-actual
END-CALL
* --------------------------------------------------
* COBOL-style function call
CALL ValidateDateFormat-01 USING SomeCOBOLDate caller-format
SomeCOBOLBOOL-value
END-CALL
* --------------------------------------------------
* COBOL-style procedure call
CALL ValidateDateFormat-02 USING SomeCOBOLDate caller-format
SomeCOBOLBOOL-value caller-actual
END-CALL
* --------------------------------------------------
.
END PROGRAM CALLER.
IDENTIFICATION DIVISION.
PROGRAM-ID. CALLER.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 caller-date.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
01 caller-format PIC X(08).
01 caller-actual PIC X(08).
01 caller-result-value PIC X VALUE LOW-VALUE.
88 caller-result VALUE ‘T’.
88 caller-result-false VALUE ‘F’.
* TCRFUN_CODEGEN_FUNCTION_RETURNING_PARAMETER
01 ValidateDateFormat-01-RESULT-value PIC X VALUE LOW-VALUE.
88 ValidateDateFormat-01-RESULT VALUE ‘T’.
88 ValidateDateFormat-01-RESULT-false VALUE ‘F’.
* TypeCobol types mimicked for COBOL-specific examples
01 SomeCOBOLDate.
02 YYYY PIC 9(4).
02 MM PIC 9(2).
02 DD PIC 9(2).
01 SomeCOBOLBOOL-value PIC X VALUE LOW-VALUE.
88 SomeCOBOLBOOL VALUE ‘T’.
88 SomeCOBOLBOOL-false VALUE ‘F’.
LOCAL-STORAGE SECTION.
01 ErrorCode.
05 ErrorCodePrimary PIC X(04).
88 ErrorCodeOK VALUE '0000'.
05 ErrorCodeSecondary PIC X(04).
01 ValidateDateFormat-01-RESULT-value PIC X VALUE LOW-VALUE.
88 ValidateDateFormat-01-RESULT VALUE ‘T’.
88 ValidateDateFormat-01-RESULT-false VALUE ‘F’.
PROCEDURE DIVISION.
* --------------------------------------------------
* TypeCobol-style function call
* TCRFUN_CODEGEN_PROCFUN_CALL
CALL ValidateDateFormat-01 USING caller-date caller-format
ValidateDateFormat-01-RESULT *> TCRFUN_CODEGEN_FUNCTION_RETURNING_PARAMETER
RETURNING ErrorCode *> TCRFUN_CODEGEN_PROCFUN_RETURNING_ERROR
END-CALL
* TCRFUN_CODEGEN_PROCFUN_IF
IF ErrorCodePrimary = '0000'
CONTINUE
ELSE
PERFORM ManageErrors *> TCRFUN_CODEGEN_ERROR_PARAGRAPH
END-IF
* TCRFUN_CODEGEN_PROCFUN_STATEMENT
MOVE ValidateDateFormat-01-RESULT-value TO caller-result-value
* --------------------------------------------------
* TypeCobol-style procedure call
* TCRFUN_CODEGEN_PROCFUN_CALL
CALL ValidateDateFormat-02 USING caller-date caller-format caller-result-value caller-actual
RETURNING ErrorCode *> TCRFUN_CODEGEN_PROCFUN_RETURNING_ERROR
END-CALL
* TCRFUN_CODEGEN_PROCFUN_IF
IF ErrorCodePrimary = '0000'
CONTINUE
ELSE
PERFORM ManageErrors *> TCRFUN_CODEGEN_ERROR_PARAGRAPH
END-IF
* --------------------------------------------------
* COBOL-style function call
* TODO COBOL-style functions or procedure calls are left unmodified
CALL ValidateDateFormat-01 USING SomeCOBOLDate caller-format
SomeCOBOLBOOL-value
END-CALL
* --------------------------------------------------
* COBOL-style procedure call
CALL ValidateDateFormat-02 USING SomeCOBOLDate caller-format
SomeCOBOLBOOL-value caller-actual
END-CALL
* --------------------------------------------------
.
* GENERATED CODE
* a paragraph for user-specific error management
* defaulting to built-in error management
ManageErrors. *> TCRFUN_CODEGEN_ERROR_PARAGRAPH
GOBACK
.
END PROGRAM CALLER.
-
✓ TCRFUN_CODEGEN_PROCFUN_CALL
A TypeCobol function or procedure call must be replaced by a COBOLCALL
statement. Parameters passed viaINPUT
andRETURNING
clauses must be passed viaUSING
clause. The generatedUSING
clauses must use the corresponding COBOL equivalent to the original TypeCobol parameters. -
❏ TCRFUN_CODEGEN_PROCFUN_RETURNING_ERROR
ARETURNING ErrorCode
clause is generated, whatever the function or procedure original profile. -
✓ TCRFUN_CODEGEN_FUNCTION_RETURNING_PARAMETER
The COBOL equivalent to the originalRETURNING
parameter is a parameter named<function-name>-RESULT
. This new parameter is generated inLOCAL-STORAGE SECTION
, in a way corresponding to the type of the originalRETURNING
parameter. -
❏ TCRFUN_CODEGEN_PROCFUN_IF
AIF
/THEN
/ELSE
statement must be generated after each TypeCobol procedure call.-
The
IF
clause is generated asIF ErrorCodePrimary = '0000'
and contains aCONTINUE
statement. -
The
ELSE
contains aPERFORM ManageError
statement.
-
-
❏ TCRFUN_CODEGEN_PROCFUN_STATEMENT
A statement must be generated after the statement described in TCRFUN_CODEGEN_PROCFUN_IF. This new statement is the translation in COBOL of the original TypeCobol statement, where:-
Each function call is replaced by the function result (see TCRFUN_CODEGEN_FUNCTION_RETURNING_PARAMETER)
-
Each other TypeCOBOL otem is replaced by its COBOL equivalent.
-
-
❏ TCRFUN_CODEGEN_ERROR_PARAGRAPH
AManageError
paragraph with business-specific error management must be generated in thePROCEDURE DIVISION
, excepted if a paragraph with the same name is already present (this "already present" paragraph is assumed to contain application-specific error management). If no business-specific error management is configured, aManageError
paragraph with built-in error management must be generated in thePROCEDURE DIVISION
instead. Built-in error management is a simpleGOBACK
statement.