Skip to content

TypeCobolFunctionsCodegen

Olivier Smedile edited this page Nov 29, 2016 · 6 revisions

#Code generation Each TypeCobol function or procedure translate in COBOL 85 into a program. This program is nested in the same PROCEDURE DIVISION as the original function or procedure.

Example

DECLARE FUNCTION MyProcedure PRIVATE
  INPUT  param1    PIC 9(04)
  OUTPUT outParam1 PIC 9(04).
  PROCEDURE DIVISION.
   ...
   .
END-DECLARE.
DECLARE FUNCTION MyPublic PUBLIC
  INPUT param1 PIC 9(04)
  RETURNING result TYPE bool.
  PROCEDURE DIVISION.
   ...
   .
end-declare.

is translated into this COBOL 85 code:

PROGRAM-ID. MyProcedure.
  DATA DIVISION.
  LINKAGE SECTION.
    01 param1    PIC 9(04).
    01 outParam1 PIC 9(04).
  PROCEDURE DIVISION
    USING BY REFERENCE param1 outParam1
  .
   ...
END PROGRAM.
PROGRAM-ID. function-name.
  DATA DIVISION.
  LINKAGE SECTION.
    01 param1 PIC 9(04).
    01 result-value PIC X VALUE LOW-VALUE.
      88 result       VALUE 'T'.
      88 result-false VALUE 'F'.
  PROCEDURE DIVISION
    USING param1
    RETURNING BY REFERENCE result-value
  .
    ...
END PROGRAM.
  • TCRFUN_CODEGEN_AS_NESTED_PROGRAM The procedure or function declaration header becomes a program identification header with neither INITIAL, RECURSIVE or COMMON phrase, nor authoring properties. The information regarding the procedure or function access modifier is not translatable and is therefore lost.
  • TCRFUN_CODEGEN_NO_ADDITIONAL_DATA_SECTION Each section of the DATA DIVISION will only be present in the generated code if it was present in the original code.
  • TCRFUN_CODEGEN_PARAMETERS_IN_LINKAGE_SECTION Each INPUT, OUTPUT, INOUT or RETURNING parameter is generated as an entry of the LINKAGE SECTION of the generated nested program, if a data description entry with the same name is not already present.
  • TCRFUN_CODEGEN_DATA_SECTION_AS_IS Each entry in a section of the DATA DIVISION already present in the TypeCobol source code is translated with no additional consideration than what is described in TypeCobol Types codegen.
  • TCRFUN_CODEGEN_PARAMETERS_ORDER All input, inoutand output parameters are translated using the USING phrase, in the following order: USING input-parameter* inout-parameters* output-parameter* return-code
  • TCRFUN_CODEGEN_RETURNING_PARAMETER The returning parameter is translated using the RETURNING phrase.

Clone this wiki locally