8 Functions

8.1 Intrinsic Functions

GnuCOBOL supports a wide variety of “intrinsic functions” that may be used anywhere in the PROCEDURE DIVISION where a literal is allowed. For example:

MOVE FUNCTION LENGTH(Employee-Last-Name) TO Employee-LN-Len

Note how the word FUNCTION is part of the syntax when you use an intrinsic function. You can use intrinsic functions without having to include the reserved word FUNCTION via settings in the REPOSITORY ( 5.1.4 REPOSITORY) paragraph. You may accomplish the same thing by specifying the -fintrinsics switch to the GnuCOBOL compiler when you compile your programs.

User-written functions ( 11.1 Subprogram Types) never require the FUNCTION keyword when they are executed, because each user-written function a program uses must be included in that program’s REPOSITORY paragraph, which therefore makes the FUNCTION keyword optional.

The following intrinsic functions, known to other “dialects” of COBOL, are defined to GnuCOBOL as reserved words but are not otherwise implemented currently. Any attempts to use these functions will result in a compile-time error message. However they are described at the end of this chapter.

BOOLEAN-OF-INTEGER
CHAR-NATIONAL
DISPLAY-OF
EXCEPTION-FILE-N
EXCEPTION-LOCATION-N
INTEGER-OF-BOOLEAN
NATIONAL-OF
STANDARD-COMPARE
Date and Time Formats
~~~~~~~~~~~~~~~~~~~~~

For functions FORMATTED-CURRENT-DATE, FORMATTED-DATE, FORMATTED-TIME, and FORMATTED-DATETIME, the format literal argument indicates the format of the date or time value that is the result of the function. The result of the function will have the same type as its format literal, which can be alphanumeric, national or UTF-8.

For functions INTEGER-OF-FORMATTED-DATE, SECONDS-FROM-FORMATTED-TIME, and TEST-FORMATTED-DATETIME, the format literal indicates the format of the date or time value specified as the second argument of the function.

The permissible format strings are listed as follows. For a full description of each subfield in the format literals, including a range of permissible values in data associated with the formats, see the Value meanings and limits section.

Integer date form:
~~~~~~~~~~~~~~~~~

A value in integer date form is a positive integer that represents the number of days since 31 December, 1600 in the Gregorian calendar.

It must be greater than zero and less than or equal to the value of FUNCTION INTEGER-OF-DATE (99991231), which is 3,067,671.

Standard date form:
~~~~~~~~~~~~~~~~~~

A value in standard date form is an integer of the form YYYYMMDD, calculated using (YYYY * 10,000) + (MM * 100) + DD, where:

YYYY represents the year in the Gregorian calendar. It must be an integer in the range [1601, 9999].

MM represents a month and must be an integer in the range [01, 12].

DD represents a day and must be an integer in the range [01, 31], valid for the specified month and year combination.

Julian date form:
~~~~~~~~~~~~~~~~

A value in Julian date form is an integer of the form YYYYDDD, calculated using (YYYY * 1000) + DDD, where:

YYYY represents the year in the Gregorian calendar. It must be an integer in the range [1601, 9999].

DDD represents the day of the year. It must be a positive integer in the range [1, 366], valid for the year specified.

UTC offset value:
~~~~~~~~~~~~~~~~

A UTC offset value is an integer representation of offset from UTC (Coordinated Universal Time) expressed in minutes. The value must be greater than or equal to -1439 and less than or equal to 1439.

Note: The offset value 1439 represents 23 hours 59 minutes, which is one minute less than a day. Standard numeric time form

A value in standard numeric time form is a numeric value representing seconds past midnight. The value must be greater than or equal to zero and less than 86,400

Date and time formats:
~~~~~~~~~~~~~~~~~~~~~

For functions FORMATTED-CURRENT-DATE, FORMATTED-DATE, FORMATTED-TIME, and FORMATTED-DATETIME, the format literal argument indicates the format of the date or time value that is the result of the function. The result of the function will have the same type as its format literal, which can be alphanumeric, national or UTF-8.

For functions INTEGER-OF-FORMATTED-DATE, SECONDS-FROM-FORMATTED-TIME, and TEST-FORMATTED-DATETIME, the format literal indicates the format of the date or time value specified as the second argument of the function.

The permissible format strings are listed as follows. For a full description of each subfield in the format literals, including a range of permissible values in data associated with the formats, see Value meanings and limits.

Date formats            Format literals
~~~~~~~~~~~~            ~~~~~~~~~~~~~~~

Basic calendar date     YYYYMMDD
Extended calendar date  YYYY-MM-DD
Basic ordinal date      YYYYDDD
Extended ordinal date   YYYY-DDD
Basic week date         YYYYWwwD
Extended week date      YYYY-Www-D

Integer-seconds time formats:
~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Integer-seconds time formats            Format literals

Basic local time                        hhmmss
Extended local time                     hh:mm:ss
Basic Coordinated Universal Time (UTC)        hhmmssZ
Extended UTC time                       hh:mm:ssZ
Basic offset time                       hhmmss+hhmm
Extended offset time                          hh:mm:ss+hh:mm

Fractional-seconds time formats:
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Fractional-seconds time formats         Format literals
Basic local time                        hhmmss.ssss
Extended local time                     hh:mm:ss.ssss
Basic Coordinated Universal Time (UTC)        hhmmss.ssssZ
Extended UTC time                       hh:mm:ss.ssssZ
Basic offset time                       hhmmss.ssss+hhmm
Extended offset time                    hh:mm:ss.ssss+hh:mm

Note: The period is used as the decimal separator, and four “s” characters after the period are used for illustrative purposes. The number of “s” characters that might be specified after the decimal separator in these formats might range from 1 to 9.

Value meanings and limits:
~~~~~~~~~~~~~~~~~~~~~~~~~

The permissible date and time formats have the following meanings and limits:

Format    Meaning and limits
YYYY      Year, 1601-9999
MM        Month, 01-12
DD        Day of month, 01-{28|29|30|31} dependent on month sub-field
DDD       Day of year for ordinal date formats, 001-365|366
ww        Week of year, 01-53
D         Day of week, 1-7
W
-
hh        Hours, 00-23
mm        Minutes, 00-59
ss        Seconds, 00-59
.s        Fractional seconds, always prefixed with '.' then 1-9 's'
+|-hh:mm  UTC offset hours (extended times only), the offset can be adjusted
          upward (by a '+' prefix) or downward (by a - prefix). A prefix of 0
          (zero) indicates that an offset of UTC is not available on the system.
Z         UTC time indicator
Value meanings and limits:
~~~~~~~~~~~~~~~~~~~~~~~~~

The permissible date and time formats have the following meanings and limits:

Format        Meaning and limits:
~~~~~~~~~~~~~~~~~~~~~~~~~~

YYYY      Year, 1601-9999
MM        Month, 01-12
DD        Day of month, 01-{28|29|30|31} dependent on month sub-field
DDD       Day of year for ordinal date formats, 001-365|366
ww        Week of year, 01-53
D         Day of week, 1-7
W
-
hh        Hours, 00-23
mm        Minutes, 00-59
ss        Seconds, 00-59
.s        Fractional seconds, always prefixed with '.' then 1-9 's'
+|-hh:mm  UTC offset hours (extended times only), the offset can be adjusted
          upward (by a '+' prefix) or downward (by a - prefix).

          A prefix of 0 (zero) indicates that an offset of UTC is not available
          on the system.
Z            UTC time indicator

The supported intrinsic functions are listed in the following sections, along with their syntax and usage notes.

8.1.1 ABS

ABS Function Syntax

ABS(number)
~~~

This function determines and returns the absolute value of <number> (a numeric literal or data item) supplied as an argument.

Note that ABSOLUTE-VALUE has an alias for this function.

8.1.2 ACOS

ACOS Function Syntax

ACOS(cosine)
~~~~

The ACOS function determines and returns the trigonometric arc-cosine, or inverse cosine, of <cosine> value (a numeric literal or data item) supplied as an argument.

The result will be an angle, expressed in radians. You may convert this to an angle measured in degrees, as follows:

COMPUTE <degrees> = ( <radians> * 180 ) / FUNCTION PI

8.1.3 ANNUITY

ANNUITY Function Syntax

ANNUITY(interest-rate, number-of-periods)
~~~~~~~

This function returns a numeric value approximating the ratio of an annuity paid at <interest-rate> (numeric data item or literal) for each of <number-of-periods> (numeric data items or literals).

<interest-rate> is the rate of interest paid at each payment. If you only have an annual interest rate and you wish to compute monthly annuity payments, divide the annual interest rate by 12 and use that value for <interest-rate>.

Multiply the result of this function times the desired principal amount to determine the amount of each period’s payment.

A note for the financially challenged: an annuity is basically a reverse loan; an accountant would take the result of this function multiplied by -1 times the principal amount to compute a loan payment you are making.

  1. Here is an example of a program using this function. Given a total amount of 100,000 USD and an annual interest of 5% the program calculates the monthly payment for the duration of one year, two years … up to 10 years.

             >>SOURCE FREE
    IDENTIFICATION DIVISION.
    PROGRAM-ID. PANNUITY.
    *> Given a total amount of 100,000 and an annual interest of 5%
    *> the program calculates monthly payment for a duration of 1 year, 2 years
    *> ...up to 10 years.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 Total-Loan       Pic 9(9)V99 value 100000.
    01 Interest-Rate    Pic 999V99  value 0.05.
    01 Interest-RateP   Pic 999V99  value zero.
    01 Months           Pic 999     value zero.
    01 Years            Pic 999     value zero.
    01 Monthly-Payment  Pic 9(9)V99.
    01 Total-Payments   Pic 9(9)V99.
    
    PROCEDURE DIVISION.
    DISPLAY SPACE
    COMPUTE Interest-RateP = Interest-Rate * 100
    DISPLAY 'Total Loan: ' Total-Loan ' USD - Interest Rate: ' Interest-RateP '%'
    DISPLAY SPACE
    DISPLAY ' Y   M  Monthly Amount    Total Payments'
    DISPLAY '--- ---  -------------    --------------'
    PERFORM 10 TIMES
      ADD 12 to Months
      COMPUTE Monthly-Payment = Total-Loan * FUNCTION ANNUITY ((Interest-Rate / 12),
                     Months)
      COMPUTE Total-Payments = Monthly-payment * Months
      COMPUTE Years = Months / 12
      DISPLAY Years ' ' Months '   ' Monthly-Payment ' USD  ' Total-Payments
    END-PERFORM
    ACCEPT omitted
    GOBACK.
    
  2. Other additional documentation:

  3. When the value of Interest-Rate is zero, the value returned by the function is the approximation of: (1 / Number-Periods) When the value of Interest-Rate is not zero, the value of the function is the approximation of: (Interest-Rate / (1 - (1 + Interest-Rate) ** (- (Number-Periods))))

8.1.4 ASIN

ASIN Function Syntax

ASIN(sine)
~~~~

The ASIN function determines and returns the trigonometric arc-sine, or inverse sine, of <sine> value (a numeric literal or data item) supplied as an argument.

The result will be an angle, expressed in radians. You may convert this to an angle measured in degrees, as follows:

COMPUTE <degrees> = ( <radians> * 180 ) / FUNCTION PI

8.1.5 ATAN

ATAN Function Syntax

ATAN(tangent)
~~~~

Use this function to determine and return the trigonometric arc-tangent, or inverse tangent, of <tangent> value (a numeric literal or data item) supplied as an argument.

The result will be an angle, expressed in radians. You may convert this to an angle measured in degrees, as follows:

COMPUTE <degrees> = ( <radians> * 180 ) / FUNCTION PI

8.1.6 BIT-OF

BIT-OF Function Syntax

BIT-OF (argument-1)
~~~~~~

BIT-OF function returns an alphanumeric character string of ‘1’ and ‘0’ characters, which represents the binary value of each byte in the argument used on input.

  1. The function type is alphanumeric.

  2. <argument-1> must be a data item, literal, or an intrinsic function result of any data class.

Returned values:

  1. An alphanumeric character string consisting of the binary representation of each byte in <argument-1>.

  2. The length of the character string returned, in bytes, is eight times the length of <argument-1>, in bytes.

        >>SOURCE FREE
*> Example of use of function BIT-OF
identification division.
program-id. pgmbitof.
environment division.
configuration section.
   repository. function all intrinsic.
data division.
working-storage section.
01 AAA PIC XXX VALUE "1 2".
01 BBB PIC XXX VALUE "A B".

procedure division.
  display BIT-OF(1)     at 0110
  display BIT-OF(2)     at 0210
  display BIT-OF(3)     at 0310
  display BIT-OF(0123)  at 0410
  display BIT-OF(AAA)   at 0510
  display BIT-OF(BBB)   at 0610
  accept omitted
  stop run.

Produces :

00110001
00110010
00110011
00110000001100010011001000110011
001100010010000000110010
010000010010000001000010

8.1.7 BIT-TO-CHAR

BIT-TO-CHAR Function Syntax

BIT-TO-CHAR {argument-1)
~~~~~~~~~~~

BIT-TO-CHAR function returns a character string that represents a bit pattern supplied on input.

  1. The function type is alphanumeric.

  2. <argument-1> must be an alphanumeric literal, alphanumeric data item, or alphanumeric group item.

  3. <argument-1> must consist only of the characters “0” and “1”.

  4. The length of <argument-1> must be a multiple of 8 bytes.

Returned values:

  1. A character string consisting of bytes representing the sequence of “0” and “1” characters in <argument-1>.

  2. The length of the result string is equal to the length of the input string divided by 8.

        >>SOURCE FREE
*> Example of use of function BIT-TO-CHAR
identification division.
program-id. pgmbittochar.
environment division.
configuration section.
  repository. function all intrinsic.
data division.
working-storage section.
01 AAA PIC X(8) VALUE "0110000".

procedure division.
  display BIT-TO-CHAR("00110000") at 0610
  display BIT-TO-CHAR("00110001") at 0710
  display BIT-TO-CHAR("00110010") at 0810
  display BIT-TO-CHAR("00110011") at 0910
  display BIT-TO-CHAR(AAA)        at 1010
  accept omitted
  stop run.

Produces:

    0
    1
    2
    3
    a

8.1.8 BYTE-LENGTH

BYTE-LENGTH Function Syntax

BYTE-LENGTH(string)
~~~~~~~~~~~

BYTE-LENGTH returns the length — in bytes — of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal). This intrinsic function is identical to the LENGTH-AN ( 8.1.44 LENGTH-AN) function. Note that the value returned by this function is not necessarily the number of characters comprising <string>, but rather the number of actual bytes required to store it.

For example, if <string> is encoded using a double-byte character set such as Unicode UTF-16 (where each character is represented by 16 bits of storage, not the 8-bits inherent to character sets like ASCII or EBCDIC), then calling this function with a <string> argument whose PICTURE ( 6.9.37 PICTURE) is N(4) would return a value of 8 rather than the value 4.

Contrast this with the LENGTH ( 8.1.43 LENGTH) function.

8.1.9 CHAR

CHAR Function Syntax

CHAR(integer)
~~~~

This function returns the character in the ordinal position specified by <integer> (a numeric integer literal or data item with a value of 1 or greater) from the COLLATING SEQUENCE ( 5.1.2 OBJECT-COMPUTER) being used by the program.

For example, if the program is using the (default) ASCII character set, CHAR(34) returns the 34th character in the ASCII character set — an exclamation-point (’!‘). If you are using this function to convert a numeric value to its corresponding ASCII character, you must use an argument value one greater than the numeric value.

If an argument whose value is less than 1 or greater than 256 is specified, the character in the program collating sequence corresponding to a value of all zero bits is returned.

The following code is an alternative approach when you just wish to convert a number to its ASCII equivalent:

01  Char-Value.
    05 Numeric-Value        USAGE BINARY-CHAR.
...
    MOVE numeric-character-value TO Numeric-Value

The Char-Value item now has the corresponding ASCII character value.

8.1.10 COMBINED-DATETIME

COMBINED-DATETIME Function Syntax

COMBINED-DATETIME(days, seconds)
~~~~~~~~~~~~~~~~~

This function returns a 12-digit numeric result, the first seven digits of which are the integer value of <days> argument (a numeric data item or literal) and the last five of which are the integer value of <seconds> argument (also a numeric data item or literal).

If <days> is less than 1 or greater than 3,067,671, or if <seconds> is less than 1 or greater than 86,400, a value of 0 is returned and a runtime error will result.

<days> Must be in integer date form. For details, see Integer date form. A value in integer date form is a positive integer that represents a number of days succeeding 31 December 1600, in the Gregorian calendar. It is based on a starting date of Monday, 1 January 1601 and integer date 1 represents Monday, 1 January 1601.

<seconds> Must be in standard numeric time form. For details, see Standard numeric time form. A value in standard numeric time form is a numeric value representing seconds past midnight.

The returned value is determined by arithmetic expression Days-1 + (Seconds-2/100000). The date occupies the integer part of the returned value and the time is represented in the fractional part of the returned value.

Example Given the integer date form value “143951”, which represents the date 15 February 1995, and the standard numeric time form value “18867.812479168304”, which represents the time “05:14:27.812479168304”, the returned value would be exactly “143951.1886781247”.

8.1.11 CONCAT

CONCAT Function Syntax

CONCAT | CONCATENATE (argument-1 [, argument-2 ]...)
~~~~~~   ~~~~~~~~~~~

This function concatenates the <argument-1>, <argument-2>, … (group items, USAGE DISPLAY elementary items and/or alphanumeric literals) together into a single string result.

If a numeric literal or PIC 9 identifier is specified as an argument, decimal points, if any, will be removed and negative signs in PIC S9 fields or numeric literals will be inserted as defined by the SIGN IS ( 6.9.49 SIGN IS) clause (or absence thereof) of the field. Numeric literals are processed as if SIGN IS TRAILING SEPARATE were in effect.

8.1.12 CONCATENATE

CONCATENATE Function Syntax

CONCAT | CONCATENATE (argument-1 [, argument-2 ]...)
~~~~~~   ~~~~~~~~~~~

This function concatenates the <string-1>, <string-2>, … (group items, USAGE DISPLAY elementary items and/or alphanumeric literals) together into a single string result.

If a numeric literal or PIC 9 identifier is specified as an argument, decimal points, if any, will be removed and negative signs in PIC S9 fields or numeric literals will be inserted as defined by the SIGN IS ( 6.9.49 SIGN IS) clause (or absence thereof) of the field. Numeric literals are processed as if SIGN IS TRAILING SEPARATE were in effect.

CONCATENATE is a GnuCOBOL extention BUT also see the ISO standard CONCAT function.

8.1.13 CONTENT-LENGTH

CONTENT-LENGTH Function Syntax

CONTENT-LENGTH argument-1
~~~~~~~~~~~~~~

Scans for a NUL byte delimiter of the data starting at address in given pointer, and returns the length. The NUL byte is not included in the count. An EC-DATA-PTR-NUL exception is set to exist if the pointer is NUL, and a zero length is returned.

Function CONTENT-LENGTH is a GnuCOBOL extention.

Example:

 01  ptr USAGE POINTER.
 01  str  PIC X(4)  VALUE z"abc".

     SET      ptr TO ADDESS OF str.
     DISPLAY  FUNCTION CONTENT-LENGTH (str).

 Will display 3.

8.1.14 CONTENT-OF

CONTENT-OF Function Syntax

CONTENT-OF pointer-1 { length }
~~~~~~~~~~

Takes a pointer and optional length. Returns a character field of the data addressed by the pointer, either up to a NUL byte or to the given length.

The NUL byte is not included in the data when no optional length is given. With an optional count, the character field can hold any content including NUL bytes,

An EC-DATA-PTR-NUL exception is set to exist if the pointer is NUL, and a zero length space is returned.

An EC-SIZE-TRANCATION is set if the resulting field would exceed character field limits and the data is truncated.

Reference modification is allowed on resulting field.

Function CONTENT-OF is a GnuCOBOL extention.

8.1.15 COS

COS Function Syntax

COS(angle)
~~~

The COS function determines and returns the trigonometric cosine of <angle> (a numeric literal or data item) supplied as an argument.

<angle> is assumed to be a value expressed in radians. If you need to determine the cosine of an angle measured in degrees, you first need to convert that angle to radians as follows:

COMPUTE <radians> = ( <degrees> * FUNCTION PI) / 180

8.1.16 CURRENCY-SYMBOL

CURRENCY-SYMBOL Function Syntax

CURRENCY-SYMBOL
~~~~~~~~~~~~~~~

The CURRENCY-SYMBOL function returns the currency symbol character currently in effect for the locale under which your program is running. On UNIX systems, your locale is established via the run-time environment variable ( 10.2.3 Run Time Environment Variables) environment variable. On Windows, the Control Panel’s “Regional and Language Options” define the locale.

Changing the currency symbol via the SPECIAL-NAMES ( 5.1.3 SPECIAL-NAMES) paragraph’s CURRENCY SYMBOL setting will not affect the value returned by this function.

8.1.17 CURRENT-DATE

CURRENT-DATE Function Syntax

CURRENT-DATE
~~~~~~~~~~~~

Returns the current date and time as the following 21-character structure:

01  CURRENT-DATE-AND-TIME.
    05 CDT-Year                PIC 9(4).
    05 CDT-Month               PIC 9(2). *> 01-12
    05 CDT-Day                 PIC 9(2). *> 01-31
    05 CDT-Hour                PIC 9(2). *> 00-23
    05 CDT-Minutes             PIC 9(2). *> 00-59
    05 CDT-Seconds             PIC 9(2). *> 00-59
    05 CDT-Hundredths-Of-Secs  PIC 9(2). *> 00-99
    05 CDT-GMT-Diff-Hours      PIC S9(2)
                               SIGN LEADING SEPARATE.
    05 CDT-GMT-Diff-Minutes    PIC 9(2). *> 00 or 30

Since this function has no arguments, no parenthesis should be specified.

8.1.18 DATE-OF-INTEGER

DATE-OF-INTEGER Function Syntax

DATE-OF-INTEGER(integer)
~~~~~~~~~~~~~~~

This function returns a numeric calendar date in yyyymmdd (i.e. Gregorian) format. The date is determined by adding the number of days specified as <integer> (a numeric integer data item or literal) to the date December 31, 1600. For example, DATE-OF-INTEGER(1) returns 16010101 while DATE-OF-INTEGER(150000) returns 20110908.

A value less than 1 or greater than 3067671 (9999/12/31) will return a result of 0.

8.1.19 DATE-TO-YYYYMMDD

DATE-TO-YYYYMMDD Function Syntax

DATE-TO-YYYYMMDD(yymmdd [, yy-cutoff [, yy-execution-time ]])
~~~~~~~~~~~~~~~~

You can use this function to convert the six-digit Gregorian date specified as <yymmdd> (a numeric integer data item or literal) to an eight-digit format (yyyymmdd).

The optional <yy-cutoff> (a numeric integer data item or literal) argument is the year cutoff used to delineate centuries; if the year component of the date meets or exceeds this cutoff value, the result will be 19yymmdd; if the year component of the date is less than the cutoff value, the result will be 20yymmdd. The default cutoff value if no second argument is given will be 50.

The optional <yy-execution-time> argument (a numeric integer data item or literal) The default execution time value if no third argument is given will be now equivalent to specifying (FUNCTION NUMVAL (FUNCTION CURRENT-DATE (1:4))).

8.1.20 DAY-OF-INTEGER

DAY-OF-INTEGER Function Syntax

DAY-OF-INTEGER(integer)
~~~~~~~~~~~~~~

This function returns a calendar date in yyyyddd (i.e. Julian) format. The date is determined by adding the number of days specified as integer (a numeric integer data item or literal) to December 31, 1600. For example, DAY-OF-INTEGER(1) returns 1601001 while DAY-OF-INTEGER(250000) returns 2011251.

A value less than 1 or greater than 3067671 (9999/12/31) will return a result of 0.

8.1.21 DAY-TO-YYYYDDD

DAY-TO-YYYYDDD Function Syntax

DAY-TO-YYYYDDD(yyddd [, yy-cutoff [, yy-execution-time ]])
~~~~~~~~~~~~~~

You can use this function to convert the five-digit Julian date specified as <yyddd> (a numeric integer data item or literal) to a seven-digit numeric Julian format (yyyyddd).

The optional <yy-cutoff> argument (a numeric integer data item or literal) is the year cutoff used to delineate centuries; if the year component of the date meets or exceeds this cutoff value, the result will be 19yyddd; if the year component of the date is less than the cutoff, the result will be 20yyddd. The default cutoff value if no second argument is given will be 50.

The optional <yy-execution-time> argument (a numeric integer data item or literal) The default execution time value if no third argument is given will be now equivalent to specifying (FUNCTION NUMVAL (FUNCTION CURRENT-DATE (1:4))).

8.1.22 E

E Function Syntax

E
~

This function returns the mathematical constant E (the base of natural logarithms). The maximum precision with which this value may be returned is 2.7182818284590452353602874713526625.

Since this function has no arguments, no parenthesis should be specified.

8.1.23 EXCEPTION-FILE

EXCEPTION-FILE Function Syntax

EXCEPTION-FILE
~~~~~~~~~~~~~~

This function returns I/O exception information from the most-recently executed input or output statement. The information is returned as a 34-character string, where the first two characters are the two-digit file status value ( File Status Codes) and the remaining 32 are the <file-name-1> specification from the file’s SELECT ( 5.2.1 SELECT) statement.

The name returned after the file status information will be returned only if the returned file status value is not 00.

Since this function has no arguments, no parenthesis should be specified.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

8.1.24 EXCEPTION-LOCATION

EXCEPTION-LOCATION Function Syntax

EXCEPTION-LOCATION
~~~~~~~~~~~~~~~~~~

This function returns exception information from the most-recently failing statement. The information is returned to a 1023 character string in one of the following formats, depending on the nature of the failure:

  • primary-entry-point-name; paragraph OF section; statement-number

  • primary-entry-point-name; section; statement-number

  • primary-entry-point-name; paragraph; statement-number

  • primary-entry-point-name; statement-number

Since this function has no arguments, no parenthesis should be specified.

The program must be compiled with the -debug switch, -ftraceall switch or -g switch for this function to return any meaningful information.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

8.1.25 EXCEPTION-STATEMENT

EXCEPTION-STATEMENT Function Syntax

EXCEPTION-STATEMENT
~~~~~~~~~~~~~~~~~~~

This function returns the most-recent COBOL statement that generated an exception condition.

Since this function has no arguments, no parenthesis should be specified.

The program must be compiled with the -debug switch, -ftraceall switch or -g switch for this function to return any meaningful information.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

8.1.26 EXCEPTION-STATUS

EXCEPTION-STATUS Function Syntax

EXCEPTION-STATUS
~~~~~~~~~~~~~~~~

This function returns the error type (a text string — see column 2 of the upcoming table for the possible values) from the most-recent COBOL statement that generated an exception condition.

Since this function has no arguments, no parenthesis should be specified.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

The following are the error type strings, and their corresponding exception codes and descriptions.

  • Code Error Type Description

  • 0101

    EC-ARGUMENT-FUNCTION Function argument error

  • 0202

    EC-BOUND-ODO OCCURS ... DEPENDING ON data item out of bounds

  • 0204

    EC-BOUND-PTR Data-pointer contains an address that is out of bounds

  • 0205

    EC-BOUND-REF-MOD Reference modifier out of bounds

  • 0207

    EC-BOUND-SUBSCRIPT Subscript out of bounds

  • 0303

    EC-DATA-INCOMPATIBLE Incompatible data exception

  • 0500

    EC-I-O input-output exception

  • 0501

    EC-I-O-AT-END I-O status 1x

  • 0502

    EC-I-O-EOP An end of page condition occurred

  • 0504

    EC-I-O-FILE-SHARING I-O status 6x

  • 0505

    EC-I-O-IMP I-O status 9x

  • 0506

    EC-I-O-INVALID-KEY I-O status 2x

  • 0508

    EC-I-O-LOGIC-ERROR I-O status 4x

  • 0509

    EC-I-O-PERMANENT-ERROR I-O status 3x

  • 050A

    EC-I-O-RECORD-OPERATION I-O status 5x

  • 0601

    EC-IMP-ACCEPT Implementation-defined accept condition

  • 0602

    EC-IMP-DISPLAY Implementation-defined display condition

  • 0A00

    EC-OVERFLOW Overflow condition

  • 0A02

    EC-OVERFLOW-STRING STRING overflow condition

  • 0A03

    EC-OVERFLOW-UNSTRING UNSTRING overflow condition

  • 0B05

    EC-PROGRAM-NOT-FOUND Called program not found

  • 0D03

    EC-RANGE-INSPECT-SIZE Size of replace item in inspect differs

  • 1000

    EC-SIZE Size error exception

  • 1004

    EC-SIZE-OVERFLOW Arithmetic overflow in calculation

  • 1005

    EC-SIZE-TRUNCATION Significant digits truncated in store

  • 1007

    EC-SIZE-ZERO-DIVIDE Division by zero

  • 1202

    EC-STORAGE-NOT-ALLOC The data-pointer specified in a FREE statement does not identify currently allocated storage

  • 1203

    EC-STORAGE-NOT-AVAIL The amount of storage requested by an
    ALLOCATE statement is not available

8.1.27 EXP

EXP Function Syntax

EXP(number)
~~~

Computes and returns the value of the mathematical constant e raised to the power specified by <number> (a numeric literal or data item).

8.1.28 EXP10

EXP10 Function Syntax

EXP10(number)
~~~~~

Computes and returns the value of 10 raised to the power specified by <number> (a numeric literal or data item).

8.1.29 FACTORIAL

FACTORIAL Function Syntax

FACTORIAL(number)
~~~~~~~~~

This function computes and returns the factorial value of <number> (a numeric literal or data item).

8.1.30 FORMATTED-CURRENT-DATE

FORMATTED-CURRENT-DATE Function Syntax

FORMATTED-CURRENT-DATE ( argument-1 )
~~~~~~~~~~~~~~~~~~~~~~

FORMATTED-CURRENT-DATE returns the current date and time provided by the system at run-time, formatted according to date-and-time-format according to the argument type.

FUNCTION FORMATTED-CURRENT-DATE gives you exactly what you asked it to, including up to nanoseconds (8 decimal positions in the seconds) [but the system may only provide miliseconds, especially on older win32].

The function argument must be a national or alphanumeric literal and the content, a combined date and time format.

The returned value is formatted to the same form as <argument-1>.

8.1.31 FORMATTED-DATE

FORMATTED-DATE Function Syntax

FORMATTED-DATE ( argument-1, argument-2 )
~~~~~~~~~~~~~~

FORMATTED-DATE uses a format to convert a date in integer date form to a date in the requested format. The returned value will be in date format.

<argument-1> shall be a national or alphanumeric literal.

<argument-2> shall be a value in integer date form.

Example Given the date format “YYYYMMDD” and the value “143951”, which represents the date 15 February 1995, the returned value would be “19950215”.

8.1.32 FORMATTED-DATETIME

FORMATTED-DATETIME Function Syntax

FORMATTED-DATETIME ( argument-1, argument-2, argument-3, argument-4 )
~~~~~~~~~~~~~~~~~~

FORMATTED-DATETIME uses a combined time and date form to convert and combine a date in integer form and a numeric time expressed as seconds past midnight in UTC. See Date and Time Formats for details.

<argument-1> shall be a national or alphanumeric literal.

<argument-2> shall be a value in integer date form.

<argument-3> shall be a value in standard numeric time form.

<argument-4> is an integer specifying the offset from UTC expressed in minutes. If specified but have a value equal or less than 1439.

Note: The offset value 1439 represents 23 hours 59 minutes which is one minutes less than a day.

<argument-4> must not be specified if the time portion in <argument-1> is neither a UTC nor an offset format.

The returned value is a representation of the date contained in <argument-2> combined with the time contained in <argument-3> according to the format in <argument-1>.

If the format in <argument-1> indicates that the returned value is to be expressed in UTC, the time portion of the returned value reflects the adjustment of the value in <argument-3> by the offset in <argument-4>.

If the format in <argument-1> indicates that the time is to be returned as an offset from UTC, the value in <argument-3> is reflected directly in the time portion of the returned value and the offset in <argument-4> is reflected directly in the offset portion of the returned value.

Example If the first argument has the format “YYMMDDThhmmss.ss+hhmm”, the second argument the value “143951”, the third argument the value “18867.812479168304”, and the fourth argument the value “+300”, the returned value would be “19950215T05142781+0500”.

8.1.33 FORMATTED-TIME

FORMATTED-TIME Function Syntax

FORMATTED-TIME ( argument-1, argument-2, argument-3 )
~~~~~~~~~~~~~~

FORMATTED-TIME converts a value representing seconds past midnight formatted time of day with optional offset.

<argument-1> shall be a national or alphanumeric literal.

<argument-2> shall be a value in integer time form.

<argument-3> is an integer specifying the offset from UTC expressed in minutes. If specified but have a value equal or less than 1439.

Note: The offset value 1439 represents 23 hours 59 minutes which is one minutes less than a day.

<argument-3> must not be specified if the time portion in <argument-1> is neither a UTC nor an offset format.

Returned value :

Is a representation of the standard numeric time contained in <argument-2> according to the format in <argument-1>.

If the format in <argument-1> indicates that the returned value is to be expressed in UTC, the time portion of the returned value reflects the adjustment of the value in <argument-2> by the offset in <argument-3>.

If the format in <argument-1> indicates that the time is to be returned as an offset from UTC, the value in <argument-2> is reflected directly in the time portion of the returned value and the offset in <argument-3> is reflected directly in the offset portion of the returned value.

Example If the first argument has the format “hhmmss.ss+hhmm”, the second argument the value “18867.812479168304” which represents the local time, and the third argument the value “-300”, which represents the five hours that Eastern Standard Time (EST) differs from UTC, the returned value would be “05142781-0500”.

8.1.34 FRACTION-PART

FRACTION-PART Function Syntax

FRACTION-PART(number)
~~~~~~~~~~~~~

This function returns that portion of <number> (a numeric data item or a numeric literal) that occurs to the right of the decimal point. FRACTION-PART(3.1415), for example, returns a value of 0.1415. This function is equivalent to the expression:

<number> -- FUNCTION INTEGER-PART(<number>)

Example:
display "base - " FUNCTION FRACTION-PART(FLOATER).
Gives
base - 000.456789
  1. When moved to a variable, it MUST have a preceding ‘V’ in the PICTURE, i.e., PIC v(4).

8.1.35 HEX-OF

HEX-OF Function Syntax

HEX-OF {argument-1)
~~~~~~

HEX-OF function returns an alphanumeric character string consisting of a hexadecimal representation of the argument used on input.

  1. The type of the function is alphanumeric.

  2. <argument-1> must be a data item, literal, or an intrinsic function result of any data class.

Returned values:

  1. An alphanumeric character string consisting of a hexadecimal representation of <argument-1>.

  2. The length of the character string returned, in bytes, is twice the length of <argument-1>, in bytes.

8.1.36 HEX-TO-CHAR

HEX-TO-CHAR Function Syntax

HEX-TO-CHAR {argument-1)
~~~~~~~~~~~

HEX-TO-CHAR function returns a character string that represents the hexadecimal digit characters supplied on input.

  1. The type of the function is alphanumeric.

  2. <argument-1> must be an alphanumeric literal, alphanumeric data item, or alphanumeric group item.

  3. <argument-1> must consist only of the characters ‘0’ through ‘9’, ‘A’ through ‘F’, and ‘a’ through ‘f’.

  4. The length of <argument-1> must be a multiple of 2 bytes.

Returned values:

  1. A character string of bytes representing the hexadecimal digit characters of <argument-1>.

  2. The length of the result string is equal to the length of the input string divided by 2.

8.1.37 HIGHEST-ALGEBRAIC

HIGHEST-ALGEBRAIC Function Syntax

HIGHEST-ALGEBRAIC(numeric-identifier)
~~~~~~~~~~~~~~~~~

This function returns the highest (i.e. largest or farthest away from 0 in a positive direction if <numeric-identifier> is signed) value that could possibly be stored in <numeric-identifier>.

8.1.38 INTEGER

INTEGER Function Syntax

INTEGER(number)
~~~~~~~

The INTEGER function returns the greatest integer value that is less than or equal to <number> (a numeric literal or data item).

8.1.39 INTEGER-OF-DATE

INTEGER-OF-DATE Function Syntax

INTEGER-OF-DATE(date)
~~~~~~~~~~~~~~~

This function converts <date> (a numeric integer data item or literal) — presumed to be a Gregorian calendar form standard date (YYYYMMDD) — to internal date form (the number of days that have transpired since 1600/12/31).

Once in that form, mathematical operations may be performed against the internal date before it is transformed back into a date using the DATE-OF-INTEGER ( 8.1.18 DATE-OF-INTEGER) or DAY-OF-INTEGER ( 8.1.20 DAY-OF-INTEGER) function.

8.1.40 INTEGER-OF-DAY

INTEGER-OF-DAY Function Syntax

INTEGER-OF-DAY(date)
~~~~~~~~~~~~~~

This function converts <date> (a numeric integer data item or literal) — presumed to be a Julian calendar form standard date (YYYYDDD) — to internal date form (the number of days that have transpired since 1600/12/31).

Once in that form, mathematical operations may be performed against the internal date before it is transformed back into a date using the DATE-OF-INTEGER ( 8.1.18 DATE-OF-INTEGER) or DAY-OF-INTEGER ( 8.1.20 DAY-OF-INTEGER) function.

8.1.41 INTEGER-OF-FORMATTED-DATE

INTEGER-OF-FORMATTED-DATE Function Syntax

INTEGER-OF-FORMATTED-DATE ( argument-1, argument-2 )
~~~~~~~~~~~~~~~~~~~~~~~~~

INTEGER-OF-FORMATTED-DATE converts a date that is in specified format to integer date form.

<argument-1> shall be a national or alphanumeric literal. The content must be either a date format or a combined date and time format.

<argument-2> shall be a data item of the same type as <argument-1>.

If <argument-1> is a date format the content of <argument-2> shall be a valid date in that format.

If <argument-1> is a combined date and time format, the content of <argument-2> shall be a valid combined date and time in same format.

8.1.42 INTEGER-PART

INTEGER-PART Function Syntax

INTEGER-PART(number)
~~~~~~~~~~~~

Returns the integer portion of <number> (a numeric literal or data item).

8.1.43 LENGTH

LENGTH Function Syntax

LENGTH(string)
~~~~~~

Returns the length — in characters — of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal).

The value returned by this function is not the number of bytes of storage occupied by string, but rather the number of actual characters making up the string. For example, if <string> is encoded using a double-byte character set such as Unicode UTF-16 (where each character is represented by 16 bits of storage, not the 8-bits inherent to character sets like ASCII or EBCDIC), then calling this function with a <string> argument whose PICTURE is X(4) would return a value of 4 rather than the value 8 (the actual number of bytes of storage occupied by that item).

Contrast this function with the BYTE-LENGTH ( 8.1.8 BYTE-LENGTH) and LENGTH-AN ( 8.1.44 LENGTH-AN) functions.

8.1.44 LENGTH-AN

LENGTH-AN Function Syntax

LENGTH-AN(string)
~~~~~~~~~

This function returns the length — in bytes of storage — of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal).

This intrinsic function is identical to the BYTE-LENGTH ( 8.1.8 BYTE-LENGTH) function.

Note that the value returned by this function is not the number of characters making up the <string>, but rather the number of actual bytes of storage required to store <string>. For example, if <string> is encoded using a double-byte character set such as Unicode UTF-16 (where each character is represented by 16 bits of storage, not the 8-bits inherent to character sets like ASCII or EBCDIC), then calling this function with a <string> argument whose PICTURE is N(4) would return a value of 8 rather than the value 4.

Contrast this with the LENGTH ( 8.1.43 LENGTH) function.

8.1.45 LOCALE-COMPARE

LOCALE-COMPARE Function Syntax

LOCALE-COMPARE(argument-1, argument-2 [ , locale ])
~~~~~~~~~~~~~~

The LOCALE-COMPARE function returns a character indicating the result of comparing <argument-1> and <argument-2> using a culturally-preferred ordering defined by a <locale>.

Either or both of the 1st two arguments may be an alphanumeric literal, a group item or an elementary item appropriate to storing alphabetic or alphanumeric data. If the lengths of the two arguments are unequal, the shorter will be assumed to be padded to the right with spaces.

The two arguments will be compared, character by character, against each other until their relationship to each other can be determined. The comparison is made according to the cultural rules in effect for <locale> name or for the current locale if no <locale> argument is specified. Once that relationship is determined, a one-character alphanumeric value will be returned as follows:

  • <‘ — If <argument-1> is determined to be less than <argument-2>

  • =‘ — If the two arguments are equal to each other

  • >‘ — If <argument-1> is determined to be greater than <argument-2>

LOCALE Names, for a list of typically-available locale names.

8.1.46 LOCALE-DATE

LOCALE-DATE Function Syntax

LOCALE-DATE(date [, locale ])
~~~~~~~~~~~

Converts the eight-digit Gregorian <date> (a numeric integer data item or literal) from yyyymmdd format to the format appropriate to the current locale. On a Windows system, this will be the “short date” format as set using Control Panel.

You may include an optional second argument to specify the <locale> name (group item or PIC X identifier) you’d like to use for date formatting. If used, this second argument must be an identifier. Locale names are specified using UNIX-standard names.

8.1.47 LOCALE-TIME

LOCALE-TIME Function Syntax

LOCALE-TIME(time [, locale ])
~~~~~~~~~~~

Converts the four- (hhmm) or six-digit (hhmmss) <time> (a numeric integer data item or literal) to a format appropriate to the current locale. On a Windows system, this will be the “time” format as set using Control Panel.

You may include an optional <locale> name (a group item or PIC X identifier) you’d like to use for time formatting. If used, this second argument must be an identifier. Locale names are specified using UNIX-standard names.

8.1.48 LOCALE-TIME-FROM-SECONDS

LOCALE-TIME-FROM-SECONDS Function Syntax

LOCALE-TIME-FROM-SECONDS(seconds [, locale ])
~~~~~~~~~~~~~~~~~~~~~~~~

Converts the number of <seconds> since midnight (a numeric integer data item or literal) to a format appropriate to the current locale. On a Windows system, this will be the “time” format as set using Control Panel.

You may include an optional <locale> name (a group item or PIC X identifier) you’d like to use for time formatting. If used, this second argument must be an identifier. Locale names are specified using UNIX-standard names.

LOCALE Names, for a list of typically-available locale names.

8.1.49 LOG

LOG Function Syntax

LOG(number)
~~~

Computes and returns the natural logarithm (base e) of <number> (a numeric literal or data item).

8.1.50 LOG10

LOG10 Function Syntax

LOG10(number)
~~~~~

Computes and returns the base 10 logarithm of <number> (a numeric literal or data item).

8.1.51 LOWER-CASE

LOWER-CASE Function Syntax

LOWER-CASE(string)
~~~~~~~~~~

This function returns the value of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal), converted entirely to lower case.

What constitutes a “letter” (or upper/lower case too, for that manner) may be influenced through the use of a CHARACTER CLASSIFICATION ( 5.1.2 OBJECT-COMPUTER).

8.1.52 LOWEST-ALGEBRAIC

LOWEST-ALGEBRAIC Function Syntax

LOWEST-ALGEBRAIC(numeric-identifier)
~~~~~~~~~~~~~~~~

This function returns the lowest (i.e. smallest or farthest away from 0 in a negative direction if <numeric-identifier> is signed) value that could possibly be stored in <numeric-identifier>.

8.1.53 MAX

MAX Function Syntax

MAX(number-1 [, number-2 ]...)
~~~

This function returns the maximum value from the specified list of numbers (each <number-n> may be a numeric data item or a numeric literal).

8.1.54 MEAN

MEAN Function Syntax

MEAN(number-1 [, number-2 ]...)
~~~~

This function returns the statistical mean value of the specified list of numbers (each <number-n> may be a numeric data item or a numeric literal).

8.1.55 MEDIAN

MEDIAN Function Syntax

MEDIAN(number-1 [, number-2 ]...)
~~~~~~

This function returns the statistical median value of the specified list of numbers (each <number-n> may be a numeric data item or a numeric literal).

8.1.56 MIDRANGE

MIDRANGE Function Syntax

MIDRANGE(number-1 [, number-2 ]...)
~~~~~~~~

The MIDRANGE (middle range) function returns a numeric value that is the arithmetic mean (average) of the values of the minimum and maximum numbers from the supplied list. Each <number-n> may be a numeric data items or a numeric literal.

8.1.57 MIN

MIN Function Syntax

MIN(number-1 [, number-2 ]...)
~~~

This function returns the minimum value from the specified list of numbers (each <number-n> may be a numeric data item or a numeric literal).

8.1.58 MOD

MOD Function Syntax

MOD(value, modulus)
~~~

This function returns the value of <value> modulo <modulus> (essentially the remainder from the division of <value> by <modulus>). Both arguments may be numeric data items or numeric literals. Either (or both) may have a non-integer value.

8.1.59 MODULE-CALLER-ID

MODULE-CALLER-ID Function Syntax

MODULE-CALLER-ID
~~~~~~~~~~~~~~~~

This function returns the null string if it is executed within a main program. When executed with a subprogram, it returns the entry-point name of the program that called the subprogram.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.60 MODULE-DATE

MODULE-DATE Function Syntax

MODULE-DATE
~~~~~~~~~~~

This function Returns the date the GnuCOBOL program that is executing the function was compiled, in the form yyyymmdd.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.61 MODULE-FORMATTED-DATE

MODULE-FORMATTED-DATE Function Syntax

MODULE-FORMATTED-DATE
~~~~~~~~~~~~~~~~~~~~~

This function returns the fully-formatted date and time when the program executing the function was compiled. The exact format of this returned string value may vary depending on the operating system and GnuCOBOL build type.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.62 MODULE-ID

MODULE-ID Function Syntax

MODULE-ID
~~~~~~~~~

This function returns the primary entry-point name (i.e. the PROGRAM-ID or FUNCTION-ID of the program. 4 IDENTIFICATION DIVISION, for information on those clauses.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.63 MODULE-PATH

MODULE-PATH Function Syntax

MODULE-PATH
~~~~~~~~~~~

This function returns the full path to the executable version of this GnuCOBOL program. The filename component of this value will be exactly as typed on the command line, down to the use of upper- and lower-case letters and presence (or absence) of any extension.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.64 MODULE-SOURCE

MODULE-SOURCE Function Syntax

MODULE-SOURCE
~~~~~~~~~~~~~

The filename of the source code of the program (as specified on the cobc command when the program was compiled) is returned by this function.

The discussion of the MODULE-TIME ( 8.1.65 MODULE-TIME) function includes a sample program that uses this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.65 MODULE-TIME

MODULE-TIME Function Syntax

MODULE-TIME
~~~~~~~~~~~

This function returns the time the GnuCOBOL program was compiled, in the form hhmmss.

Since this function has no arguments, no parenthesis should be specified.

The following sample program uses all the MODULE- Functions:

IDENTIFICATION DIVISION.
PROGRAM-ID. DEMOMODULE.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
REPOSITORY.
    FUNCTION ALL INTRINSIC.
PROCEDURE DIVISION.
000-Main.
    DISPLAY "MODULE-CALLER-ID      = [" MODULE-CALLER-ID ']'
    DISPLAY "MODULE-DATE           = [" MODULE-DATE ']'
    DISPLAY "MODULE-FORMATTED-DATE = [" MODULE-FORMATTED-DATE ']'
    DISPLAY "MODULE-ID             = [" MODULE-ID ']'
    DISPLAY "MODULE-PATH           = [" MODULE-PATH ']'
    DISPLAY "MODULE-SOURCE         = [" MODULE-SOURCE ']'
    DISPLAY "MODULE-TIME           = [" MODULE-TIME ']'
    STOP RUN
    .

The program produces this output when executed:

MODULE-CALLER-ID = []
MODULE-DATE = [20180522]
MODULE-FORMATTED-DATE = [May 22 2018 12:43:14]
MODULE-ID = [DEMOMODULE]
MODULE-PATH = [/home/vince/cobolsrc/ACAS/demomodule]
MODULE-SOURCE = [demomodule.cbl]
MODULE-TIME = [124314]

8.1.66 MONETARY-DECIMAL-POINT

MONETARY-DECIMAL-POINT Function Syntax

MONETARY-DECIMAL-POINT
~~~~~~~~~~~~~~~~~~~~~~

MONETARY-DECIMAL-POINT returns the character used to separate the integer portion from the fractional part of a monetary currency value according to the rules currently in effect for the locale under which your program is running.

On UNIX (including OSX, Windows/Cygwin and Windows/MinGW) systems, your locale is established via the run-time environment variable ( 10.2.3 Run Time Environment Variables) environment variable. On Windows, the Control Panel’s Regional and Language Options define the locale.

Using the DECIMAL-POINT IS COMMA ( 5.1.3 SPECIAL-NAMES) clause in your program will not affect the value returned by this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.67 MONETARY-THOUSANDS-SEPARATOR

MONETARY-THOUSANDS-SEPARATOR Function Syntax

MONETARY-THOUSANDS-SEPARATOR
~~~~~~~~~~~~~~~~~~~~~~~~~~~~

This function returns the character used to separate the thousands digit groupings of monetary currency values according to the rules currently in effect for the locale under which your program is running.

On UNIX (including OSX, Windows/Cygwin and Windows/MinGW) systems, your locale is established via the run-time environment variable ( 10.2.3 Run Time Environment Variables) environment variable. On Windows, the Control Panel’s Regional and Language Options define the locale.

Using the DECIMAL-POINT IS COMMA ( 5.1.3 SPECIAL-NAMES) clause in your program will not affect the value returned by this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.68 NUMERIC-DECIMAL-POINT

NUMERIC-DECIMAL-POINT Function Syntax

NUMERIC-DECIMAL-POINT
~~~~~~~~~~~~~~~~~~~~~

This function returns the character used to separate the integer portion of a non-integer numeric item from the fractional part according to the rules currently in effect for the locale under which your program is running.

On UNIX (including OSX, Windows/Cygwin and Windows/MinGW) systems, your locale is established via the run-time environment variable ( 10.2.3 Run Time Environment Variables) environment variable. On Windows, the Control Panel’s Regional and Language Options define the locale.

Using the DECIMAL-POINT IS COMMA ( 5.1.3 SPECIAL-NAMES) clause in your program will not affect the value returned by this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.69 NUMERIC-THOUSANDS-SEPARATOR

NUMERIC-THOUSANDS-SEPARATOR Function Syntax

NUMERIC-THOUSANDS-SEPARATOR
~~~~~~~~~~~~~~~~~~~~~~~~~~~

This function returns the character used to separate the thousands digit groupings of numeric values according to the rules currently in effect for the locale under which your program is running.

On UNIX (including OSX, Windows/Cygwin and Windows/MinGW) systems, your locale is established via the run-time environment variable ( 10.2.3 Run Time Environment Variables) environment variable. On Windows, the Control Panel’s Regional and Language Options define the locale.

Using the DECIMAL-POINT IS COMMA ( 5.1.3 SPECIAL-NAMES) clause in your program will not affect the value returned by this function.

Since this function has no arguments, no parenthesis should be specified.

8.1.70 NUMVAL

NUMVAL Function Syntax

NUMVAL(string)
~~~~~~

The NUMVAL function converts a <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) to its corresponding numeric value.

The <string> must have any of the following formats, where ‘#’ represents a sequence of one or more decimal digits:

#  -#  +#  #-  #+  #CR  #DB

#.#  -#.#  +#.#  #.#-  #.#+  #.#CR  #.#DB

There must be at least one digit character in the string.

Leading and/or trailing spaces are allowed, as are spaces before the first digit.

The character period in <argument-1> <string>, represents the decimal separator. The character comma in <argument-1> represents the grouping separator. When the DECIMAL-POINT IS COMMA clause is specified, the character comma shall be used in <argument-1> to represent the decimal separator and the character period shall be used to represent the grouping separator.

Note: Locale-based functionality equivalent to NUMVAL can be obtained by using the NUMVAL-C function with the LOCALE keyword. A currency sign is optional in NUMVAL-C. The locale category LC_MONETARY will be used because there is no sign convention specified in locale category LC_NUMERIC.

Returned values:

The returned value is the numeric value represented by <string>.

If it contains a CR, DB, or the minus sign (’-‘), the returned value is negative.

8.1.71 NUMVAL-C

NUMVAL-C Function Syntax

NUMVAL-C (string [, symbol               ]
~~~~~~~~
                 [, LOCALE locale-name-1 ] [, ANYCASE ])

This function converts a <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) representing a currency value to its corresponding numeric value.

The currency string if any, and any grouping separators preceding the decimal separator are ignored. Optionally, the currency string, sign convention, grouping separator and the decimal separator permitted in the character string may be specified by locale category LC-MONETARY, or the currency string may be specified by <symbol>.

The optional <symbol> character represents the currency symbol (a non-space single-character group item, USAGE DISPLAY elementary item or alphanumeric literal) that may be used as the currency character in <string>. Any spaces including leading or trailing are ignored. If no <symbol> is specified, the value that would be returned by the CURRENCY-SYMBOL intrinsic function ( 8.1.16 CURRENCY-SYMBOL) will be used.

If this references the LOCALE :

Changing the currency symbol via the SPECIAL-NAMES paragraph’s CURRENCY SYMBOL setting will not affect the value returned by this function.

While NUMVAL-C will always use the currency symbol that is specified via the SPECIAL-NAMES paragraph’s CURRENCY SYMBOL (or the system default which is currently always ‘$‘).

<string> may have any of the following formats, where ‘#’ represents a sequence of one or more decimal digits and ‘$’ represents the <symbol> character:

#  -#  +#  #-  #+  #CR  #DB

#.#  -#.#  +#.#  #.#-  #.#+  #.#CR  #.#DB

$#  -$#  +$#  $#-  $#+  $#CR  $#DB

$#.#  -$#.#  +$#.#  $#.#-  $#.#+  $#.#CR  $#.#DB

There must be at least one digit character in the string.

Leading and/or trailing spaces are allowed, as are spaces before and/or after the currency symbol, sign, CR and DB characters.

If the ANYCASE keyword is used the matching rules for detecting a currency string in <argument-1> are case-insensitive. If the ANYCASE keyword is not specified, the matching rules are case-sensitive.

If neither symbol nor the LOCALE keyword is specified, there shall be only one currency string used, either the default currency sign or a currency string specified in the SPECIAL-NAMES paragraph.

The returned value is the numeric value represented by string.

When the LOCALE keyword is specified, the returned value is negative if string contains a negative sign.

When the LOCALE keyword is not specified, the returning value is negative if string contains CR, DB, or a minus sign.

8.1.72 NUMVAL-C-2

NUMVAL-C Function Syntax

NUMVAL-C (argument-1 [, argument-2           ]
~~~~~~~~
                     [, LOCALE locale-name-1 ] [, ANYCASE ])

This function returns the numeric value represented by the character string specified by <argument-1> and defined as alphanumeric.

<argument-2>, the currency string if any, and any grouping separators preceding the decimal separator are ignored. Optionally, the currency string, sign convention, grouping separator and the decimal separator permitted in the character string may be specified by locale category LC-MONETARY, or the currency string may be specified by <argument-2>.

The optional alphanumeric <argument-2> character represents the currency symbol (a non-space and at least one single-character item, that may be used as the currency character in <argument-1>. Any spaces including leading or trailing are ignored. If no <argument-2> is specified, the value that would be returned by the CURRENCY-SYMBOL intrinsic function ( 8.1.16 CURRENCY-SYMBOL) will be used. <argument-2> must not contain any of the digits - through 9, characters ‘*‘, ‘+‘, ‘-‘, ‘,‘ or ‘.‘; or the two consecutive letters CR or DB, whether upper or lower case or a combination of both.

<argument-2> specifies a currency string that may appear in <argument-1>.

If the ANYCASE keyword is specified, the matching rules for detecting a currency string in <argument-1> are case-insensitive. If not specified, the matching rules are case-sensitive.

If neither <argument-2> nor the LOCALE keyword is specified, there shall be only one currency string used, either the default currency sign or a currency string specified in the SPECIAL-NAMES paragraph.

While NUMVAL-C will always use the currency symbol that is specified via the SPECIAL-NAMES paragraph’s CURRENCY SYMBOL (or the system default which is currently always ‘$’) <argument-1> shall have any of the following formats, where ‘#’ represents a sequence of one or more decimal digits and ‘$’ represents the <symbol> character:

#  -#  +#  #-  #+  #CR  #DB

#.#  -#.#  +#.#  #.#-  #.#+  #.#CR  #.#DB

$#  -$#  +$#  $#-  $#+  $#CR  $#DB

$#.#  -$#.#  +$#.#  $#.#-  $#.#+  $#.#CR  $#.#DB

There must be at least one digit character in the string.

Leading and/or trailing spaces are allowed, as are spaces before and/or after the currency symbol, sign, CR and DB characters.

The returned value is the numeric value represented by <argument-1>.

When the LOCALE keyword is specified, the returned value is negative if string contains a negative sign and when not specified, the returning value is negative if string contains CR, DB, or a minus sign.

8.1.73 NUMVAL-F

NUMVAL-F Function Syntax

NUMVAL-F(char)
~~~~~~~~

This function converts a <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) representing a floating-point value to its corresponding numeric value.

#  -#  +#  #E#  -#E#  +#E#

#E+#  -#E+#  +#E+#  #E-#  -#E-#  +#E-#

#.#  -#.#  +#.#  #.#E#  -#.#E#  +#.#E#

#.#E+#  -#.#E+#  +#.#E+#  #.#E-#  -#.#E-#  +#.#E-#

There must be at least one digit character both before and after the E in the string.

Leading and/or trailing spaces are allowed, as are spaces before and/or after any sign characters.

8.1.74 ORD

ORD Function Syntax

ORD(char)
~~~

This function returns the ordinal position in the program character set (usually ASCII) corresponding to the 1st character of <char> argument (a group item, USAGE DISPLAY elementary item or alphanumeric literal).

For example, assuming the program is using the standard ASCII collating sequence, ORD('!') returns 34 because ‘!‘ is the 34th ASCII character. If you are using this function to convert an ASCII character to its numeric value, you must subtract one from the result.

The following code is an alternative approach when you just wish to convert an ASCII character to its numeric equivalent:

01  Char-Value.
    05 Numeric-Value        USAGE BINARY-CHAR.
...
    MOVE "character" TO Char-Value

Numeric-Value now has the numeric value of character.

8.1.75 ORD-MAX

ORD-MAX Function Syntax

ORD-MAX(char-1 [, char-2 ]...)
~~~~~~~

This function returns the ordinal position in the argument list corresponding to the <char-n> whose 1st character has the highest position in the program collating sequence (usually ASCII).

For example, assuming the program is using the standard ASCII collating sequence, ORD-MAX('Z', 'z', '!') returns 2 because the 2nd character in the argument list (the ASCII character ‘z‘) occurs after ‘Z‘ and ‘!‘ in the program collating sequence. Each <char-n> argument may be a group item, USAGE DISPLAY elementary item or alphanumeric literal.

8.1.76 ORD-MIN

ORD-MIN Function Syntax

ORD-MIN(char-1 [, char-2 ]...)
~~~~~~~

This function returns the ordinal position in the argument list corresponding to the <char-n> whose 1st character has the lowest position in the program collating sequence (usually ASCII).

For example, assuming the program is using the standard ASCII collating sequence, ORD-MIN('Z', 'z', '!') returns 3 because the 3rd character in the argument list (the ASCII character ‘!‘) occurs before ‘Z‘ and ‘z‘ in the program collating sequence. Each <char-n> argument may be a group item, USAGE DISPLAY elementary item or alphanumeric literal.

8.1.77 PI

PI Function Syntax

PI
~~

This function returns the mathematical constant PI. The maximum precision with which this value may be returned is 3.1415926535897932384626433832795029.

Since this function has no arguments, no parenthesis should be specified.

8.1.78 PRESENT-VALUE

PRESENT-VALUE Function Syntax

PRESENT-VALUE(rate, value-1 [, value-2 ])
~~~~~~~~~~~~~

The PRESENT-VALUE function returns a value that approximates the present value of a series of future period-end amounts specified by the various <value-n> arguments at a discount rate specified by the <rate> argument.

All arguments are numeric data items and/or numeric literals.

  1. Example of function in use :

             >>SOURCE FREE
    IDENTIFICATION DIVISION.
    PROGRAM-ID. PPresValue.
    *> The sample: you pay for a machine 1500 USD
    *> You rent the machine at 350 USD per year per 5 years (= 1750).
    *> The program calculates (NET)PRESENT VALUE of 1750
    *> when the discount rate is 1%, 2% up to 10%.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01  PaymentsNum      constant as   5.
    01  PaymentsAmount   constant as 350.
    01  Expenditure      PIC 999999V99 value 1500.
    01  TOTAL-CASH-FLOW  PIC 999999V99 value zero.
    01  DiscountRate     PIC S99V99 VALUE 0.00.
    77  DiscountRateP    PIC S99V99 VALUE 0.00.
    01  filler.
        05 PaymentAmount PIC S9999V99 OCCURS PaymentsNum TIMES VALUE PaymentsAmount.
    01  PresValue        PIC  9(6)V99  value zero.
    01  NET-PresValue    PIC S9(6)V99  value zero.
    
    PROCEDURE DIVISION.
    COMPUTE TOTAL-CASH-FLOW =
        FUNCTION SUM (PaymentAmount(1) PaymentAmount(2) PaymentAmount(3)
                      PaymentAmount(4) PaymentAmount(5))
    DISPLAY SPACE
    DISPLAY   'Expenditure: ' Expenditure ' Total Cashflow: ' TOTAL-CASH-FLOW
    DISPLAY SPACE
    
    PERFORM 10 TIMES
      COMPUTE DiscountRate  = DiscountRate + 0.01
      COMPUTE DiscountRateP = DiscountRate * 100
      COMPUTE PresValue ROUNDED =
          FUNCTION PRESENT-VALUE (DiscountRate PaymentAmount(1) PaymentAmount(2)
                              PaymentAmount(3) PaymentAmount(4) PaymentAmount(5))
      COMPUTE NET-PresValue = - Expenditure + PresValue
      DISPLAY 'DiscountRate: ' DiscountRateP '%   PresValue: ' PresValue
              ' NET-PresValue: ' NET-PresValue
    END-PERFORM
    ACCEPT omitted
    GOBACK.
    
  2. This is a case where passing parameters to the intrinsic function PRESENT-VALUE would need the ability to indicate “ALL” and then write the statement as:

  3. FUNCTION PRESENT-VALUE (DiscountRate PaymentAmount(ALL) )

  4. GnuCOBOL does not have this feature (ALL parameter) i.,e has NOT YET been implemented.

8.1.79 RANDOM

RANDOM Function Syntax

RANDOM[(seed)]
~~~~~~

This function returns a pseudo-random non-integer value in the range 0 to 1 (for example, 0.123456789).

The purpose of the optional <seed> argument, is to initialize the chain of pseudo-random numbers that will be returned by the function. Not only will calls to this function using the same <seed> value return the same pseudo-random number, but so will all subsequent executions of the function without a <seed>. This is actually a good thing when you are testing your program because you can rely on always receiving the same sequence of “random” numbers if you always start using the same <seed>.

The <seed> may be any form of literal or data item. If <seed> is numeric, its numeric value will serve as the seed value. If <seed> is alphanumeric, a value for it will be determined as if it were used as an argument to NUMVAL ( 8.1.70 NUMVAL).

Take, for example, the following sample program:

IDENTIFICATION DIVISION.
PROGRAM-ID. DEMORANDOM.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  Pseudo-Random-Number        USAGE COMP-1.
PROCEDURE DIVISION.
000-Main.
    MOVE FUNCTION RANDOM(1) TO Pseudo-Random-Number
    DISPLAY Pseudo-Random-Number
    PERFORM 4 TIMES
        MOVE FUNCTION RANDOM    TO Pseudo-Random-Number
        DISPLAY Pseudo-Random-Number
    END-PERFORM
    STOP RUN
    .

Every time this program is executed, it will produce the same output, because the same sequence of pseudo-random numbers will be generated:

0.41
0.18467
0.63340002
0.26499999
0.19169

It is worth mentioning that if the first execution of RANDOM in your program lacks a <seed> argument, the result will be exactly as if that execution were coded with a <seed> argument value of 1.

Once your program has been thoroughly tested, you’ll want different sequences to be generated each time the program runs. One possible way to accomplish this is to use a <seed> that is likely to be different every time the program is executed, as is likely to be the case if the first MOVE statement in the previous example were replaced by this:

MOVE RANDOM(FUNCTION CURRENT-DATE(1:16))
  TO Pseudo-Random-Number

The first 16 characters returned by the CURRENT-DATE ( 8.1.17 CURRENT-DATE) function will be a number in the format <YYYYMMDDhhmmssnn>, where <YYYYMMDD> is the current calendar date and <hhmmssnn> is the current time of day to the one one-hundredth of a second. Since two different executions of the program will never get identical CURRENT-DATE values (unless they are executed in extremely close time frames to one another), using those first sixteen characters as the RANDOM seed will guarantee that receiving a duplicate sequence of pseudo-random numbers in two different executions of the program will be highly unlikely.

8.1.80 RANGE

RANGE Function Syntax

RANGE(number-1 [, number-2 ]...)
~~~~~

The RANGE function returns a value that is equal to the value of the maximum <number-n> in the argument list minus the value of the minimum <number-n> argument.

All <number-n> arguments are numeric data items and/or numeric literals.

8.1.81 REM

REM Function Syntax

REM(number,divisor)
~~~

This function returns a numeric value that is the remainder of <number> divided by <divisor>. Both arguments must be numeric data items or numeric literals.

8.1.82 REVERSE

REVERSE Function Syntax

REVERSE(string)
~~~~~~~

This function returns the byte-by-byte reversed value of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal).

8.1.83 SECONDS-FROM-FORMATTED-TIME

SECONDS-FROM-FORMATTED-TIME Function Syntax

SECONDS-FROM-FORMATTED-TIME(format,time)
~~~~~~~~~~~~~~~~~~~~~~~~~~~

This function decodes the string <time> — whose value represents a formatted time — and returns the total number of seconds that string represents.

The <time> string must contain hours, minutes and seconds. The time argument may be specified as a group item, USAGE DISPLAY elementary item or an alphanumeric literal.

The <format> argument is a string (a group item, USAGE DISPLAY elementary item or an alphanumeric literal) documenting the format of <time> using <hh>, <mm> and <ss> to denote where the respective time information can be found. Any other characters found in <format> represent character positions that will be ignored. For example, a format of hhmmss indicates that <time> will be treated as a six-digit string value where the first two characters are the number of hours, the next two represent minutes and the last two represent seconds. A <format> of hh:mm:ss, however, describes <time> as an eight-character string where characters 3 and 6 will be ignored.

8.1.84 SECONDS-PAST-MIDNIGHT

SECONDS-PAST-MIDNIGHT Function Syntax

SECONDS-PAST-MIDNIGHT
~~~~~~~~~~~~~~~~~~~~~

This function returns the current time of day expressed as the total number of elapsed seconds since midnight.

Since this function has no arguments, no parenthesis should be specified.

8.1.85 SIGN

SIGN Function Syntax

SIGN(number)
~~~~

The SIGN function returns a -1 if the value of <number> (a numeric literal or numeric data item) is negative, a zero if the value of <number> is exactly zero and a 1 if the value of <number> if greater than 0.

8.1.86 SIN

SIN Function Syntax

SIN(angle)
~~~

This function determines and returns the trigonometric sine of <angle> (a numeric literal or numeric data item).

The <angle> is assumed to be a value expressed in radians. If you need to determine the sine of an angle measured in degrees, you first need to convert that angle to radians as follows:

COMPUTE <radians> = ( <degrees> * FUNCTION PI) / 180

8.1.87 SQRT

SQRT Function Syntax

SQRT(number)
~~~~

The SQRT function returns a numeric value that approximates the square root of <number> (a numeric data item or numeric literal with a non-negative value).

The following two statements produce identical results:

01  Result           PIC 9(4).9(10).
...
    MOVE FUNCTION SQRT(15) TO Result
    COMPUTE Result = 15 ^ 0.5

8.1.88 STANDARD-DEVIATION

STANDARD-DEVIATION Function Syntax

STANDARD-DEVIATION(number-1 [, number-2 ]...)
~~~~~~~~~~~~~~~~~~

This function returns the statistical standard deviation of the list of <number-n> arguments (numeric data items or numeric literals).

8.1.89 STORED-CHAR-LENGTH

STORED-CHAR-LENGTH Function Syntax

STORED-CHAR-LENGTH(string)
~~~~~~~~~~~~~~~~~~

Returns the length — in bytes — of the specified string (a group item, USAGE DISPLAY elementary item or alphanumeric literal), minus the total number of trailing spaces, if any.

8.1.90 SUBSTITUTE

SUBSTITUTE Function Syntax

SUBSTITUTE(string, from-1, to-1 [, from-n, to-n ]...)
~~~~~~~~~~

This function parses <string>, replacing all occurrences of <from-n> strings with the corresponding <to-n> strings.

The <from-n> strings must match sequences in <string> exactly with regard to value and case.

A <from-n> string does not have to be the same length as its corresponding <to-n> string.

All arguments are group items, USAGE DISPLAY elementary items or alphanumeric literals.

A null <to-n> string will be treated as a single space.

When using Variables in place of <string> attention to NOT wanting Leading or trailing spaces usage of function TRIM needs to be utilised as failure to do so will result in variables treated with any unwanted spaces leading and/or trailing, i.e.,

move     function SUBSTITUTE-CASE (WS-Dest-File-Path,
                    function TRIM (WS-Inbound-Path),
                    function TRIM (WS-Desc-Path))
                               to WS-Dest-File-Path

8.1.91 SUBSTITUTE-CASE

SUBSTITUTE-CASE Function Syntax

SUBSTITUTE-CASE(string, from-1, to-1 [, from-n, to-n ]...)
~~~~~~~~~~~~~~~

The SUBSTITUTE-CASE function operates the same as the SUBSTITUTE ( 8.1.90 SUBSTITUTE) function, except that <from-n> string matching is performed without regard to case.

All arguments are group items, USAGE DISPLAY elementary items or alphanumeric literals.

When using Variables in place of <string> attention to NOT wanting Leading or trailing spaces usage of function TRIM needs to be utilised as failure to do so will result in variables treated with any unwanted spaces leading and/or trailing, i.e.,

move     function SUBSTITUTE-CASE (WS-Dest-File-Path,
                    function TRIM (WS-Inbound-Path),
                    function TRIM (WS-Desc-Path))
                               to WS-Dest-File-Path

8.1.92 SUM

SUM Function Syntax

SUM(number-1 [, number-2 ]...)
~~~

The SUM function returns a value that is the sum of <number-n> arguments (these may be numeric data items or numeric literals).

8.1.93 TAN

TAN Function Syntax

TAN(angle)
~~~

This function determines and returns the trigonometric tangent of <angle> (a numeric literal or numeric data item).

The <angle> is assumed to be a value expressed in radians. If you need to determine the tangent of an angle measured in degrees, you first need to convert that angle to radians as follows:

COMPUTE <radians> = ( <degrees> * FUNCTION PI) / 180

8.1.94 TEST-DATE-YYYYMMDD

TEST-DATE-YYYYMMDD Function Syntax

TEST-DATE-YYYYMMDD(date)
~~~~~~~~~~~~~~~~~~

This function determines if the supplied <date> argument (a numeric integer data item or literal) is a valid date.

A valid date is one of the form yyyymmdd in the range 1601/01/01 to 9999/12/31, with no more than the expected maximum number of days in the month, accounting for leap year.

If the <date> is valid, a 0 value is returned. If it isn’t, a value of 1, 2 or 3 is returned signalling the problem lies with the year, month or day, respectively.

8.1.95 TEST-DAY-YYYYDDD

TEST-DAY-YYYYDDD Function Syntax

TEST-DATE-YYYYDDD(date)
~~~~~~~~~~~~~~~~~

This function determines if the supplied <date> (a numeric integer data item or literal) is a valid date.

A valid date is one of the form yyyyddd in the range 1601001 to 9999365. Leap year is accounted for in determining the maximum number of days in a year.

If the date is valid, a 0 value is returned. If it isn’t, a value of 1 or 2 is returned signalling the problem lies with the year or day, respectively.

8.1.96 TEST-FORMATTED-DATETIME

TEST-FORMATTED-DATETIME Function Syntax

TEST-FORMATTED-DATETIME ( argument-1, argument-2 )
~~~~~~~~~~~~~~~~~~~~~~~

TEST-FORMATTED-DATETIME tests whether a date literal representing a date, a time or a combined date and time is valid according to the specified format.

<argument-1> must a literal of type alphanumeric, UTF-8 or national, that contains a date, time or combined data time format. See Date and Time formats for details.

<argument-2> must be a data item of the same type as <argument-1>.

Returned value:

If no format or range problems occur during evaluation of <argument-2> according to the format in <argument-1>, the returned value is zero. Otherwise the returned value is the ordinal character position at which the first error in <argument-2> was detected.

Example

Using the following arguments, it will generates a return value of 5, as the fifth character of argument-2 (“4”) contains an incorrect value for the first digit of the month representation.

FUNCTION TEST-FORMATTED-DATETIME(“YYYYMMDD”, “20124523”)

8.1.97 TEST-NUMVAL

TEST-NUMVAL Function Syntax

TEST-NUMVAL(string)
~~~~~~~~~~~

The TEST-NUMVAL function evaluates <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) for being appropriate for use as the <string> argument to a NUMVAL ( 8.1.70 NUMVAL) function, returning to a integer a zero value if it is appropriate otherwise if one or more characters are in error, the position of the first character in error or the length of the field plus one for other cases such as all spaces.

Note that these errors include but are not limited to: argument (<string>) is zero length, contains only spaces or contains valid characters but is incomplete, such as the string ‘+.‘.

8.1.98 TEST-NUMVAL-C

TEST-NUMVAL-C Function Syntax

TEST-NUMVAL-C(string[,symbol])
~~~~~~~~~~~~~

This function evaluates <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) for being appropriate for use as the <string> argument to a NUMVAL-C ( 8.1.71 NUMVAL-C) function, returning to a integer a zero value if it is appropriate otherwise if one or more characters are in error, the position of the first character in error or the length of the field plus one for other cases such as all spaces.

Note that these errors include but are not limited to: argument (<string>) is zero length, contains only spaces or contains valid characters but is incomplete, such as the string ‘+.‘.

The optional <symbol> argument serves the same function — and has the same default and possible values — as the corresponding argument of the NUMVAL-C function.

8.1.99 TEST-NUMVAL-F

TEST-NUMVAL-F Function Syntax

TEST-NUMVAL-F(string)
~~~~~~~~~~~~~

This function evaluates <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal) for being appropriate for use as the <string> argument to a NUMVAL-F ( 8.1.73 NUMVAL-F) function, returning to a integer a zero value if it is appropriate otherwise if one or more characters are in error, the position of the first character in error or the length of the field plus one for other cases such as all spaces.

Note that these errors include but are not limited to: argument (string) is zero length, contains only spaces or contains valid characters but is incomplete, such as the string ‘+.‘.

8.1.100 TRIM

TRIM Function Syntax

TRIM(string [, LEADING|TRAILING ])
~~~~           ~~~~~~~ ~~~~~~~~

This function removes LEADING or TRAILING spaces from <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal).

The second argument is specified as a keyword, not a quoted string or identifier. If no second argument is specified, both leading and trailing spaces will be removed. The case (upper, lower or mixed) of this argument is irrelevant.

8.1.101 UPPER-CASE

UPPER-CASE Function Syntax

UPPER-CASE(string)
~~~~~~~~~~

This function returns the value of <string> (a group item, USAGE DISPLAY elementary item or alphanumeric literal), converted entirely to upper case.

What constitutes a “letter” (or upper/lower case too, for that manner) may be influenced through the use of a CHARACTER CLASSIFICATION ( 5.1.2 OBJECT-COMPUTER).

8.1.102 VARIANCE

VARIANCE Function Syntax

VARIANCE(number-1 [, number-2 ]...)
~~~~~~~~

This function returns the statistical variance of the specified list of <number-n> arguments (these may be numeric data items or numeric literals).

8.1.103 WHEN-COMPILED

WHEN-COMPILED Function Syntax

WHEN-COMPILED
~~~~~~~~~~~~~

The WHEN-COMPILED intrinsic function, not to be confused with the WHEN-COMPILED ( 7.7 Special Registers) special register, returns the date and time the program was compiled, in ASCII.

Since this function has no arguments, no parenthesis should be specified.

Unlike the WHEN-COMPILED special register, which has an ASCII value of the compilation date/time in the format mm/dd/yyhh.mm.ss, the WHEN-COMPILED intrinsic function returns the compilation date/time as an ASCII string in the format yyyymmddhhmmssnnooooo, where yyyymmdd is the date, hhmmss is the time, nn is the hundredths of a second component of the compilation time, if available (or 00 if it isn’t) and ooooo is the time zone offset from GMT.

If the -fintrinsics=WHEN-COMPILED switch or -fintrinsics=ALL switch is specified to the compiler or the REPOSITORY ( 5.1.4 REPOSITORY) paragraph specifies either FUNCTION WHEN-COMPILED INTRINSIC or FUNCTION ALL INTRINSIC, then references to WHEN-COMPILED (without a leading FUNCTION keyword will always reference this intrinsic function and there will be no way to access the WHEN-COMPILED special register.

8.1.104 YEAR-TO-YYYY

YEAR-TO-YYYY Function Syntax

YEAR-TO-YYYY(yy [, yy-cutoff [, yy-execution-time ]])
~~~~~~~~~~~~

YEAR-TO-YYYY converts <yy> — a two-digit year — to a four-digit format (yyyy).

The optional <yy-cutoff> argument is the year cutoff used to delineate centuries; if <yy> meets or exceeds this cutoff value, the result will be 19yy; if <yy> is less than the cutoff, the result will be 20yy. The default cutoff value if no second argument is given will be 50.

The optional <yy-execution-time> argument (a numeric integer data item or literal) The default execution time value if no third argument is given will be now equivalent to specifying (FUNCTION NUMVAL (FUNCTION CURRENT-DATE (1:4))).

All arguments must be numeric data items or numeric literals.

8.1.105 BOOLEAN-OF-INTEGER

BOOLEAN-OF-INTEGER Function Syntax

BOOLEAN-OF-INTEGER(argument-1 argument-2)
~~~~~~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. BOOLEAN-OF-INTEGER returns a boolean item of usage bit representing the binary value of <argument-1>. <argument-2> specifies the length of the boolean data item that is returned.

<argument-1> must be a positive integer.

<argument-2> must be a positive non-zero integer

Returned value is a boolean item of usage bit that has the same bit configuration as the binary representation of the value of <argument-1>, where the rightmost boolean position is the low-order binary digit. The boolean value is zero-filled or truncated on the left, if necessary, in order to return a boolean item whose length is specified by <argument-2> in therms of boolean positions.

8.1.106 CHAR-NATIONAL

CHAR-NATIONAL Function Syntax

CHAR-NATIONAL(argument-1)
~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. CHAR-NATIONAL returns a one character value that is a character in the national program collating sequence having the ordinal position equal to the value of the argument.

<argument-1> must be a integer and greater than zero and less than or equal to the number of positions in the national program collating sequence.

8.1.107 DISPLAY-OF

DISPLAY-OF Function Syntax

DISPLAY-OF(argument-1 [ argument-2] )
~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. DISPLAY-OF returns a character string containing the alphabetic coded character set representation of the national characters in the argument.

<argument-1> must be of class national.

<argument-2> must be a of class alphabetic or alphanumeric and is one character position in length. It specifies an alphanumeric substitution character for use in conversion of national characters for which there is no corresponding alphanumeric character.

A character string is returned with each national character of <argument-1> converted to its corresponding alphanumeric character representation, if any.

If <argument-2> is specified, the alphanumeric substitution character is returned for each national character in <argument-1> that has no corresponding alphanumeric character representation.

If <argument-2> is un-specified, and <argument-1> contains a national character for which there is no corresponding alphanumeric character representation, an substitution character is used as the corresponding alphanumeric character and the EC-DATA-CONVERSION exception condition is set.

The length of the returned value is the number of character positions of usage display required to hold the converted argument and depends on the number of characters contained in <argument-1>.

8.1.108 EXCEPTION-FILE-N

EXCEPTION-FILE-N Function Syntax

EXCEPTION-FILE-N
~~~~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. EXCEPTION-FILE-N returns a national character string that is the I/O status value and file-name of the file connector, if any, associated with the last exception status.

The value returned has a length that is based on its contents and the concents are as follows:

If the last exception status is not an EC-I-O exception condition, the returned value is two national zeros.

The returned value is two national spaces when the last exception status indicates an EC-I-O exception condition that originates from one of the following statements:

  • a RAISE statement.

  • an EXIT or a GOBACK statement with a RAISING phrase that specifies an EC-I-O exception-name.

Otherwise the returned value is a character string that is as long as is needed to contain the I-O status value and the filename. The first two characters are the I-O status value in national characters. The succeeding characters contain the file-name exactly as specified in the SELECT clause converted at runtime to the runtime national character set.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

8.1.109 EXCEPTION-LOCATION-N

EXCEPTION-LOCATION-N Function Syntax

EXCEPTION-LOCATION-N
~~~~~~~~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. EXCEPTION-LOCATION-N returns an national character string containing exception information from the most-recently failing statement. The information is returned to a 1023 character string in one of the following formats, depending on the nature of the failure:

  • primary-entry-point-name; paragraph OF section; statement-number

  • primary-entry-point-name; section; statement-number

  • primary-entry-point-name; paragraph; statement-number

  • primary-entry-point-name; statement-number

Since this function has no arguments, no parenthesis should be specified.

The program must be compiled with the -debug switch, -ftraceall switch or -g switch for this function to return any meaningful information.

The documentation of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine illustrates the use of this function.

8.1.110 INTEGER-OF-BOOLEAN

INTEGER-OF-BOOLEAN Function Syntax

INTEGER-OF-BOOLEAN(argument-1)
~~~~~~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. INTEGER-OF-BOOLEAN returns the numeric value of the boolean string in <argument-1> which is class boolean.

Returned value as <argument-1> is assigned to a temporary boolean data item of usage bit described with the same number of boolean positions.

The unsigned binary value represented by the same bit configuration as the bit configuration of that temporary boolean data item is determined.

Note: Binary representation is a mathematical concept. It is not required that this representation be the same as a COBOL representation.

8.1.111 NATIONAL-OF

NATIONAL-OF Function Syntax

NATIONAL-OF(argument-1 [argument-2] )
~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. NATIONAL-OF returns a character string containing the national character representation of the characters in the argument which must be of class boolean.

A character string is returned with each alphanumeric character in <argument-1> converted to its corresponding national coded character set representation.

If <argument-2> is specified, each character in <argument-1> that has no corresponding national representation is converted to the substitution character specified by <argument-2>.

If <argument-2> is unspecified and <argument-1> contains an alphanumeric character for which there is no corresponding national character representation, a substitution character is used as the corresponding national character and the EC-DATA-CONVERSION exception condition is set to exist.

The length of the returned value is the number of character positions of usage national required to hold the converted argument and depends on the number of characters contained in <argument-1>.

8.1.112 STANDARD-COMPARE

STANDARD-COMPARE Function Syntax

STANDARD-COMPARE(argument-1 argument-2 [ordering-name-1] [argument-4] )
~~~~~~~~~~~~~~~~

This option is not yet implemented.

The included file NEWS will indicate when it is. STANDARD-COMPARE returns a character indicating the result of comparing <argument-1> as a alphanumeric and <argument-2> using a cultural ordering table.

  1. <argument-1> shall be of class alphabetic, alphanumeric, or national.

  2. <argument-2> shall be of class alphabetic, alphanumeric, or national.

  3. <argument-1> and <argument-2> may be of different classes.

  4. Neither <argument-1> nor <argument-2> shall be a zero-length literal.

  5. <ordering-name-1>, if specified, shall be associated with a cultural ordering table in the ORDER TABLE clause of the SPECIAL-NAMES paragraph. <ordering-name-1> identifies the ordering table to be used for the comparison. If <ordering-name-1> is not specified, the default ordering table `ISO14651_2010_TABLE1’ described in Appendix A of ISO/IEC 14651:2011 shall be used.

  6. <argument-4>, if specified, shall be a positive nonzero integer.

Returned values:

  1. If <argument-4> is unspecified, the highest level defined in the ordering table is used for the comparison.

  2. If the cultural ordering table is not available on the processor, or the specified ordering level is not available, or the level number specified by <argument-4> is not defined in the ordering table, the EC-ORDER-NOT-SUPPORTED exception condition is set.

  3. If the arguments are of different classes, and one is national, the other argument is converted to class national for purposes of comparison.

  4. For purposes of comparison, trailing spaces are truncated from the operands except that an operand consisting of all spaces is truncated to a single space.

  5. <argument-1> and <argument-2> are compared in accordance with the ordering table and ordering level being used.

    Note: This comparison is culturally sensitive and the default ordering table is acceptable for most cultures. It is not necessarily a character-by-character comparison and not necessarily a case-sensitive comparison. In order to use this function, users should understand the types of comparisons specified by ISO/IEC 14651:2D11 and the ordering tables in use for their installation.

  6. The returned value is:

    • =

      the arguments compare equal,

    • -=.:

      <argument-1> is less than <argument-2>,

    • :>

      <argument-1> is greater than <argument-2>.

  7. The length of the returned value is 1.

8.2 Built-In System Subroutines

There are a number of built-in system subroutines included with GnuCOBOL.

Generally, these routines are intended to match those available in Micro Focus COBOL, ACUCOBOL and directly for GnuCOBOL.

It is recommended to change the CBL_OC routines to CBL_GC for forward compatibility as at some point they will be removed as they are a hangover from Open Cobol.

Prefix explanation:

  • C$

    –> ACU

  • CBL_

    –> MF

  • CBL_GC_

    (For backwards compatibility some routines are also available as CBL_OC_as well): but these wonderful extensions are only available with GnuCOBOL.

These routines, all executed via their upper-case names via the CALL statement ( 7.8.5 CALL), are capable of performing the following functions:

  • Changing the current directory

  • Copying files

  • Creating a directory

  • Creating, Opening, Closing, Reading and Writing byte-stream files

  • Deleting directories (folders)

  • Deleting files

  • Determining how many arguments were passed to a subroutine

  • Getting file information (size and last-modification date/time)

  • Getting the length (in bytes) of an argument passed to a subroutine

  • Justifying a field left-, right- or center-aligned

  • Moving files (a destructive “copy”)

  • Putting the program “to sleep”, specifying the sleep time in seconds

  • Putting the program “to sleep”, specifying the sleep time in nanoseconds; Caveat: although you’ll express the time in nanoseconds, Windows systems will only be able to sleep at a millisecond granularity

  • Retrieving information about the currently-executing program

  • Submitting a command to the shell environment appropriate for the version of GnuCOBOL you are using for execution

Early versions of Micro Focus COBOL allowed programmers to access various runtime library routines by using a single two-digit hexadecimal number as the entry-point name. These were known as call-by-number routines. Over time, Micro Focus COBOL evolved, replacing most of the call-by-number routines with ones accessible using a more conventional call-by-name technique.

Most of the call-by-number routines have evolved into even more powerful call-by-name routines, many of which are supported by GnuCOBOL.

Some of the original call-by-number routines never evolved call-by-name equivalents; GnuCOBOL supports some of these routines.

The following sections describe the various built-in subroutines. All subroutine arguments are mandatory except where explicitly noted to the contrary. Any subroutine returning a value to the RETURN-CODE special register ( 7.7 Special Registers) could utilize the RETURNING clause on the CALL statement to return the result back to the full-word binary data item of your choice.

8.2.1 C$CALLEDBY

C$CALLEDBY Built-In Subroutine Syntax

CALL "C$CALLEDBY" USING prog-name-area
~~~~              ~~~~~

This routine returns the name of the program that called the currently-executing program. The program name will be returned, left-justified and space filled, in <prog-name-area> argument, which should be a PIC X elementary item or a group item. If <prog-name-area> is too small to receive the entire program name, the program name value will be truncated (on the right) to fit.

The RETURN-CODE special register ( 7.7 Special Registers) will be set to one of the following values:

  • -1

    An error occurred. The <prog-name-area> contents will be unchanged.

  • 0

    The program calling C$CALLEDBY was not called by any other program (in other words, it is a main program). The <prog-name-area> contents will be set entirely to spaces.

  • 1

    The program calling C$CALLEDBY was indeed called by another program, and that program’s name has been saved in <prog-name-area>.

8.2.2 C$CHDIR

C$CHDIR Built-In Subroutine Syntax

CALL "C$CHDIR" USING directory-path, result
~~~~           ~~~~~

This routine makes <directory-path> (an alphanumeric literal or identifier) the current directory.

The return code of the operation is returned both in the <result> argument (any non-edited numeric identifier) as well as in the RETURN-CODE special register ( 7.7 Special Registers). The return code of the operation will be either 0=Success or 128=failure.

The directory change remains in effect until the program terminates (in which the original current directory at the time the program was started will be automatically restored) or until another C$CHDIR or a CBL_CHANGE_DIR built-in system subroutine ( 8.2.16 CBL_CHANGE_DIR) is executed.

8.2.3 C$COPY

C$COPY Built-In Subroutine Syntax

CALL "C$COPY" USING src-file-path, dest-file-path, 0
~~~~          ~~~~~

Use this subroutine to copy file <src-file-path> to <dest-file-path> as if it were done via the cp (Unix/OSX) or COPY (Windows) command.

Both file path arguments may be alphanumeric literals or identifiers.

The third argument is required, but is unused.

If the attempt to copy the file fails (for example, it or the destination directory doesn’t exist), the RETURN-CODE special register ( 7.7 Special Registers) will be set to 128; on successful completion it will be set to 0.

8.2.4 C$DELETE

C$DELETE Built-In Subroutine Syntax

CALL "C$DELETE" USING file-path, 0
~~~~            ~~~~~

This routine deletes the file specified by the <file-path> argument (an alphanumeric literal or identifier) just as if that were done using the rm (Unix/OSX) or ERASE (Windows) command.

The second argument is required, but is unused.

If the attempt to delete the file fails (for example, it doesn’t exist), the RETURN-CODE special register ( 7.7 Special Registers) will be set to 128; on successful completion it will be set to 0.

8.2.5 C$FILEINFO

C$FILEINFO Built-In Subroutine Syntax

CALL "C$FILEINFO" USING file-path, file-info
~~~~              ~~~~~

With this routine you may retrieve the size of the file specified as the <file-path> argument (an alphanumeric literal or identifier) and the date/time that file was last modified. File size information may not be available in the particular GnuCOBOL build / Operating System combination you are using and may therefore always be returned as zero. The information is returned to the <file-info> argument, which is defined as the following 16-byte area:

01  File-Info.
    05 File-Size-In-Bytes  PIC 9(18) COMP.
    05 Mod-YYYYMMDD        PIC 9(8)  COMP. *> Modification Date
    05 Mod-HHMMSS00        PIC 9(8)  COMP. *> Modification Time

The last two decimal digits in the modification time will always be 00.

If the subroutine is successful, a value of 0 will be returned in the RETURN-CODE special register ( 7.7 Special Registers). Failure to retrieve the needed statistics on the file will cause a RETURN-CODE special register value of 35 to be passed back. Supplying less than two arguments will generate a 128 RETURN-CODE special register value.

8.2.6 C$GETPID

C$GETPID Built-In Subroutine Syntax

CALL "C$GETPID"
~~~~

Use this subroutine to return the PID (process ID) of the executing GnuCOBOL program. The PID value is returned into the RETURN-CODE special register ( 7.7 Special Registers).

There are no arguments to this routine.

8.2.7 C$JUSTIFY

C$JUSTIFY Built-In Subroutine Syntax

CALL "C$JUSTIFY" USING data-item, "justification-type"
~~~~             ~~~~~

Use C$JUSTIFY to left, right or center-justify an alphabetic, alphanumeric or numeric edited data-item. The optional <justification-type> argument indicates the type of the justification to be performed. Its value is interpreted as follows:

  • C

    the value will be centered

  • R

    the value will be right-justified, space-filled to the left

  • L

    the value will be left-justified, space-filled to the right

If it begins with anything else, or is absent, it will be treated as if it is present and begins with a capital ‘R

8.2.8 C$MAKEDIR

C$MAKEDIR Built-In Subroutine Syntax

CALL "C$MAKEDIR" USING dir-path
~~~~             ~~~~~

With this routine you may create a new directory — the name of which is supplied as the <dir-path> argument (an alphanumeric literal or identifier).

Only the lowest-level directory (last) in the specified path can be created — all others must already exist. This subroutine will not behave as a mkdir -p (Unix) or mkdir /p (Windows).

The RETURN-CODE special register ( 7.7 Special Registers) will be set to the return code of the operation; the value will be either 0=Success or 128=failure.

8.2.9 C$NARG

C$NARG Built-In Subroutine Syntax

CALL "C$NARG" USING arg-count-result
~~~~          ~~~~~

This subroutine returns the number of arguments passed to the program that calls it back to in the numeric field <arg-count-result>. When called from within a user-defined function, a value of one (1) is returned if any arguments were passed to the function or a zero (0) otherwise.

When called from a main program, the returned value will always be 0.

8.2.10 C$PARAMSIZE

C$PARAMSIZE Built-In Subroutine Syntax

CALL "C$PARAMSIZE" USING argument-number
~~~~               ~~~~~

This subroutine returns the size (in bytes) of the subroutine argument supplied using the <argument-number> parameter (a numeric literal or data item).

The size is returned in the RETURN-CODE special register ( 7.7 Special Registers).

If the specified argument does not exist, or an invalid argument number is specified, a value of 0 is returned.

8.2.11 C$PRINTABLE

C$PRINTABLE Built-In Subroutine Syntax

CALL "C$PRINTABLE" USING data-item [ , char ]
~~~~               ~~~~~

The C$PRINTABLE subroutine converts the contents of the data-item specified as the first argument to printable characters. Those characters that are deemed printable (as defined by the character set used by <data-item>) will remain unchanged, while those that are NOT printable will be converted to the character specified as the second argument.

If no <char> argument is provided, a period (’.‘) will be used.

Note: CBL_GC_PRINTABLE replaces this although it is currently still supported for legacy reasons.

8.2.12 C$SLEEP

C$SLEEP Built-In Subroutine Syntax

CALL "C$SLEEP" USING seconds-to-sleep
~~~~           ~~~~~

C$SLEEP puts the program to sleep for the specified number of seconds and/or fractions of a second. The <seconds-to-sleep> argument may be a numeric literal or data item.

Sleep times less than 1 will be interpreted as 0, subject to the speed of the CPU and the O/S (Operating System) used, as well as the timing of the generated C code, which can immediately returns control to the calling program without any sleep delay.

When using a variable argument defined as 9(n)v9(m) where n is maximum seconds in 7 days, i.e., (60 x 60 x 24 x 7) = 604,800 (seconds) and m is at a point too fast for the CPU and O/S. In practice m should be 2 for a hundredth of a second but actual testing against the target CPU would be need.

The maximum time can be adjusted by the define MAX_SLEEP_TIME during compilation of the compiler [and no I do not know where it is in the codebase] e.g.:

/* maximum sleep time in seconds, currently 7 days */
#define MAX_SLEEP_TIME 3600*24*7

8.2.13 C$TOLOWER

C$TOLOWER Built-In Subroutine Syntax

CALL "C$TOLOWER" USING data-item, BY VALUE convert-length
~~~~             ~~~~~               ~~~~~

This routine will converts the <convert-length> (a numeric literal or data item) leading characters of <data-item> (an alphanumeric identifier) to lower-case.

The <convert-length> argument must be specified BY VALUE ( 7.8.5 CALL). Any characters in <data-item> after the <convert-length> point will remain unchanged.

If <convert-length> is negative or zero, no conversion will be performed.

8.2.14 C$TOUPPER

C$TOUPPER Built-In Subroutine Syntax

CALL "C$TOUPPER" USING data-item, BY VALUE convert-length
~~~~             ~~~~~               ~~~~~

This routine will converts the <convert-length> (a numeric literal or data item) leading characters of <data-item> (an alphanumeric identifier) to upper-case.

The <convert-length> argument must be specified BY VALUE ( 7.8.5 CALL). Any characters in <data-item> after the <convert-length> point will remain unchanged.

If <convert-length> is negative or zero, no conversion will be performed.

8.2.15 CBL_AND

CBL_AND Built-In Subroutine Syntax

CALL "CBL_AND" USING item-1, item-2, BY VALUE byte-length
~~~~           ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      0
      0      1      0
      1      0      0
      1      1      1
    

    This subroutine performs a bit-by-bit logical AND operation between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the AND process. | | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.16 CBL_CHANGE_DIR

CBL_CHANGE_DIR Built-In Subroutine Syntax

CALL "CBL_CHANGE_DIR" USING directory-path
~~~~                  ~~~~~

This routine makes <directory-path> (an alphanumeric literal or identifier) the current directory.

The return code of the operation, which will be either 0=Success or 128=failure, is returned in the RETURN-CODE special register ( 7.7 Special Registers).

The directory change remains in effect until the program terminates (in which the original current directory at the time the program was started will be automatically restored) or until another CBL_CHANGE_DIR or a C$CHDIR built-in system subroutine ( 8.2.2 C$CHDIR) is executed.

8.2.17 CBL_CHECK_FILE_EXIST

CBL_CHECK_FILE_EXIST Built-In Subroutine Syntax

CALL "CBL_CHECK_FILE_EXIST" USING file-path, file-info
~~~~                        ~~~~~

With this routine you may retrieve the size of the file specified as the <file-path> argument (an alphanumeric literal or identifier) and the date/time that file was last modified. File size information may not be available in the particular GnuCOBOL build / Operating System combination you are using and may therefore always be returned as zero.

The information is returned to the <file-info> argument, which is defined as the following 16-byte area:

01  file-info.
    05 File-Size-In-Bytes  PIC 9(18)  COMP.
    05 Mod-DD              PIC 9(2)   COMP.  *> Modification Date
    05 Mod-MO              PIC 9(2)   COMP.
    05 Mod-YYYY            PIC 9(4)   COMP.
    05 Mod-HH              PIC 9(2)   COMP.  *> Modification Time
    05 Mod-MM              PIC 9(2)   COMP.
    05 Mod-SS              PIC 9(2)   COMP.
    05 FILLER              PIC 9(2)   COMP.  *> Always 00

If the subroutine is successful, a value of 0 will be returned in the RETURN-CODE special register ( 7.7 Special Registers). Failure to retrieve the needed statistics on the file will cause a RETURN-CODE special register value of 35 to be passed back. Supplying less than two arguments will generate a 128 RETURN-CODE special register value.

8.2.18 CBL_CLOSE_FILE

CBL_CLOSE_FILE Built-In Subroutine Syntax

CALL "CBL_CLOSE_FILE" USING file-handle
~~~~                  ~~~~~

The CBL_CLOSE_FILE subroutine closes a byte stream file previously opened by either the CBL_OPEN_FILE built-in system subroutine ( 8.2.41 CBL_OPEN_FILE) or CBL_CREATE_FILE built-in system subroutine ( 8.2.21 CBL_CREATE_FILE) subroutines.

If the file defined by the <file-handle> argument (a PIC X(4) USAGE COMP-X data item) was opened for output, an implicit CBL_FLUSH_FILE built-in system subroutine ( 8.2.27 CBL_FLUSH_FILE) will be performed before the file is closed.

If the subroutine is successful, a value of 0 will be returned in the RETURN-CODE special register ( 7.7 Special Registers). Failure will cause a RETURN-CODE special register value of -1 to be passed back.

8.2.19 CBL_COPY_FILE

CBL_COPY_FILE Built-In Subroutine Syntax

CALL "CBL_COPY_FILE" USING src-file-path, dest-file-path
~~~~                 ~~~~~

Use this subroutine to copy file <src-file-path> to <dest-file-path> as if it were done via the cp (Unix/OSX) or COPY (Windows) command.

Both arguments may be alphanumeric literals or identifiers.

If the attempt to copy the file fails (for example, it or the destination directory doesn’t exist), the RETURN-CODE special register ( 7.7 Special Registers) will be set to 128; on successful completion it will be set to 0.

8.2.20 CBL_CREATE_DIR

CBL_CREATE_DIR Built-In Subroutine Syntax

CALL "CBL_CREATE_DIR" USING dir-path
~~~~                  ~~~~~

With this routine you may create a new directory — the name of which is supplied as the <dir-path> argument (an alphanumeric literal or identifier).

Only the lowest-level directory (last) in the specified path can be created — all others must already exist. This subroutine will not behave as a mkdir -p (Unix) or mkdir /p (Windows).

The RETURN-CODE special register ( 7.7 Special Registers) will be set to the return code of the operation; the value will be either 0=Success or 128=failure.

8.2.21 CBL_CREATE_FILE

CBL_CREATE_FILE Built-In Subroutine Syntax

CALL "CBL_CREATE_FILE" USING file-path, 2, 0, 0, file-handle
~~~~                   ~~~~~

The CBL_CREATE_FILE subroutine creates the new file specified using the file-path argument and opens it for output as a byte-stream file usable by CBL_WRITE_FILE built-in system subroutine ( 8.2.50 CBL_WRITE_FILE).

Arguments 2, 3 and 4 should be coded as the constant values shown. CBL_CREATE_FILE is actually a special-case of the CBL_OPEN_FILE built-in system subroutine ( 8.2.41 CBL_OPEN_FILE) routine — see that routine for a description of the meanings of arguments 2, 3 and 4.

A <file-handle> (PIC X(4) USAGE COMP-X) will be returned, for use on any subsequent CBL_WRITE_FILE built-in system subroutine ( 8.2.50 CBL_WRITE_FILE) or CBL_CLOSE_FILE built-in system subroutine ( 8.2.18 CBL_CLOSE_FILE) calls.

The success or failure of the subroutine will be reported back in the RETURN-CODE special register ( 7.7 Special Registers), with a value of -1 indicating an invalid argument and a value of 0 indicating success.

8.2.22 CBL_DELETE_DIR

CBL_DELETE_DIR Built-In Subroutine Syntax

CALL "CBL_DELETE_DIR" USING dir-path
~~~~                  ~~~~~

This subroutine deletes an empty directory.

The only argument — <dir-path> (an alphanumeric literal or identifier) — is the name of the directory to be deleted.

Only the lowest-level directory (last) in the specified path will be deleted, and that directory must be empty to be deleted.

The RETURN-CODE special register ( 7.7 Special Registers) will be set to the return code of the operation; the value will be either 0=Success or 128=failure.

8.2.23 CBL_DELETE_FILE

CBL_DELETE_FILE Built-In Subroutine Syntax

CALL "CBL_DELETE_FILE" USING file-path
~~~~                   ~~~~~

This routine deletes the file specified by the <file-path> argument (an alphanumeric literal or identifier) just as if that were done using the rm (Unix/OSX) or ERASE (Windows) command.

If the attempt to delete the file fails (for example, it doesn’t exist), the RETURN-CODE special register ( 7.7 Special Registers) will be set to 128; on successful completion it will be set to 0.

8.2.24 CBL_EQ

CBL_EQ Built-In Subroutine Syntax

CALL "CBL_EQ" USING item-1, item-2, BY VALUE byte-length
~~~~          ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      1
      0      1      0
      1      0      0
      1      1      1
    

    This subroutine performs a bit-by-bit comparison between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the EQ process. | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.25 CBL_ERROR_PROC

CBL_ERROR_PROC Built-In Subroutine Syntax

CALL "CBL_ERROR_PROC" USING function, program-pointer
~~~~                  ~~~~~

This routine registers a general error-handling routine.

The <function> argument must be a numeric literal or a 32-bit binary data item (USAGE BINARY-LONG, for example) with a value of 0 or 1. A value of 0 means that you will be registering (“installing”) an error procedure while a value of 1 indicates you’re de-registering (“uninstalling”) a previously-installed error procedure.

The <program-pointer> must be a data item with a USAGE ( 6.9.61 USAGE) of PROGRAM-POINTER containing the address of your error procedure. This item should be given a value using the SET Program-Pointer statement ( 7.8.41.2 SET Program-Pointer). If the error procedure is written in GnuCOBOL, it must be a subroutine, not a user-defined function.

A success (0) or failure (non-0) result will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

A custom error procedure will trigger when a runtime error condition is encountered. An error procedure may be registered by a main program or a subprogram, but regardless of from where it was registered, it applies to the overall program compilation group and will trigger when a runtime error occurs anywhere in the executable program. If the error procedure was defined by a subprogram, that program must be loaded at the time the error procedure is executed.

An error procedure may be used to take whatever actions might be warranted to display additional information or to gracefully close down work in progress, but it cannot prevent the termination of program execution; should the error procedure not issue its own STOP RUN, control will return back to the standard error routine when the error procedure exits.

The code within the handler will be executed and — once the handler issues a return, if it was written in C, or an EXIT PROGRAM statement ( 7.8.18 EXIT) or GOBACK statement, if it was written in GnuCOBOL, the system-standard error handling routine will be executed.

Only one user-defined error procedure may be in effect at any time.

The following is a sample GnuCOBOL program that registers an error procedure. The output of that program is shown as well. As as you can see, the error handler’s messages appear followed by the standard GnuCOBOL message.

1.     IDENTIFICATION DIVISION.
2.     PROGRAM-ID. DemoERRPROC.
3.     ENVIRONMENT DIVISION.
4.     DATA DIVISION.
5.     WORKING-STORAGE SECTION.
6.     01  Err-Proc-Address            USAGE PROGRAM-POINTER.
7.     PROCEDURE DIVISION.
8.     S1.
9.         DISPLAY 'Program is starting'
10.        SET Err-Proc-Address TO ENTRY 'ErrProc'
11.        CALL 'CBL_ERROR_PROC' USING 0, Err-Proc-Address
12.        CALL 'Tilt' *> THIS DOESN'T EXIST!!!!
13.        DISPLAY 'Program is stopping'
14.        STOP RUN
15.        .
16.    END PROGRAM DemoERRPROC.
17.
18.    IDENTIFICATION DIVISION.
19.    PROGRAM-ID. ErrProc.
20.    PROCEDURE DIVISION.
21.    000-Main.
22.        DISPLAY 'Error: ' FUNCTION EXCEPTION-LOCATION
23.        DISPLAY '       ' FUNCTION EXCEPTION-STATEMENT
24.        DISPLAY '       ' FUNCTION EXCEPTION-FILE
25.        DISPLAY '       ' FUNCTION EXCEPTION-STATUS
26.        DISPLAY '*** Returning to Standard Error Routine ***'
27.        EXIT PROGRAM
28.        .
29.    END PROGRAM ErrProc.

When executed, this sample program generates the following console output.

E:\Programs\Demos>demoerrproc
Program is starting
Error: DemoERRPROC; S1; 12
       CALL
       00
       EC-PROGRAM-NOT-FOUND
*** Returning to Standard Error Routine ***
DEMOERRPROC.cbl: 27: libcob: Cannot find module 'Tilt'

E:\Programs\Demos>

8.2.26 CBL_EXIT_PROC

CBL_EXIT_PROC Built-In Subroutine Syntax

CALL "CBL_EXIT_PROC" USING function, program-pointer
~~~~                 ~~~~~

This routine registers a general exit-handling routine.

The <function> argument must be a numeric literal or a 32-bit binary data item (USAGE BINARY-LONG, for example) with a value of 0 or 1. A value of 0 means that you will be registering (“installing”) an exit procedure while a value of 1 indicates you’re deregistering (“uninstalling”) a previously-installed exit procedure.

The <program-pointer> must be a data item with a USAGE ( 6.9.61 USAGE) of PROGRAM-POINTER containing the address of your exit procedure.

A success (0) or failure (non-0) result will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

An exit procedure, once registered, will trigger whenever a STOP RUN statement ( 7.8.44 STOP) or a GOBACK statement ( 7.8.21 GOBACK) is executed anywhere in the program. The exit procedure may execute whatever code is desired to undertake an orderly shut down of the program. Once the exit procedure terminates by executing an EXIT PROGRAM statement ( 7.8.18 EXIT) or a GOBACK statement, the system-standard program termination routine will be executed.

Only one user-defined exit procedure may be in effect at any time.

The following is a sample GnuCOBOL program that registers an exit procedure. The output of that program is shown as well.

IDENTIFICATION DIVISION.
PROGRAM-ID. demoexitproc.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  Exit-Proc-Address           USAGE PROGRAM-POINTER.
PROCEDURE DIVISION.
000-Register-Exit-Proc.
    SET Exit-Proc-Address TO ENTRY "ExitProc"
    CALL "CBL_EXIT_PROC" USING 0, Exit-Proc-Address
    IF RETURN-CODE NOT = 0
        DISPLAY 'Error: Could not register Exit Procedure'
    END-IF
    .
099-Now-Test-Exit-Proc.
    DISPLAY
        'Executing a STOP RUN...'
    END-DISPLAY
    GOBACK.
END PROGRAM demoexitproc.

IDENTIFICATION DIVISION.
PROGRAM-ID. ExitProc.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  Display-Date                PIC XXXX/XX/XX.
01  Display-Time                PIC XX/XX/XX.
01  Now                         PIC X(8).
01  Today                       PIC X(8).
PROCEDURE DIVISION.
000-Main.
    DISPLAY '*** STOP RUN has been executed ***'
    ACCEPT Today FROM DATE YYYYMMDD
    ACCEPT Now   FROM TIME
    MOVE Today TO Display-Date
    MOVE Now   TO Display-Time
    INSPECT Display-Time REPLACING ALL '/' BY ':'
    DISPLAY '***    ' Display-Date '  ' Display-Time '    ***'
    GOBACK.
END PROGRAM ExitProc.

8.2.27 CBL_FLUSH_FILE

CBL_FLUSH_FILE Built-In Subroutine Syntax

CALL "CBL_FLUSH_FILE" USING file-handle
~~~~                  ~~~~~

In Micro Focus COBOL, calling this subroutine flushes any as-yet unwritten buffers for the (output) file whose file-handle is specified as the argument to disk.

This routine is non-functional in GnuCOBOL. It exists only to provide compatibility for applications that may have been developed for Micro Focus COBOL.

8.2.28 CBL_GC_FORK

CBL_GC_FORK Built-In Subroute Syntax

CALL "CBL_GC_FORK" USING Child-PID
~~~~               ~~~~~

CBL_GC_FORK allows you to fork the current COBOL process to a new one.

The current content of the process’s storage (including LOCAL-STORAGE) will be identical, any file handles get invalid in the new process, positions and file and record locks are only available to the original process.

This system routine is not available on Windows (exception: GCC on Cygwin).

Parameters: none

Returns: pid (the child process gets ‘0’ returned, the calling process gets the pid of the created child).

Negative values are returned for system dependant error codes and -1 if the function is not available on the current system.

CBL_GC_FORK allows you to fork the current COBOL process to a new one. The current content of the process’ storage (including LOCAL-STORAGE) will be identical, any file handles get invalid in the new process, positions and file / record locks are only available to the original process. This system routine is not available on Windows (exception: gcc on Cygwin). Parameters: none Returns: pid (the child process gets 0 returned, the calling process gets the pid of the created children). Negative values are returned for system dependant error codes and -1 if the function is not available on the current system.

IDENTIFICATION DIVISION.
PROGRAM-ID. prog.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  CHILD-PID      PIC S9(9) BINARY.
01  WAIT-STS       PIC S9(9) BINARY.
PROCEDURE DIVISION.
    CALL     "CBL_GC_FORK" RETURNING CHILD-PID END-CALL
    EVALUATE TRUE
             WHEN CHILD-PID = ZERO
                  PERFORM CHILD-CODE
             WHEN CHILD-PID > ZERO
                  PERFORM PARENT-CODE
             WHEN CHILD-PID = -1
                  DISPLAY 'CBL_GC_FORK is not available on the current'
                  ' system!'
                  PERFORM CHILD-CODE
                  MOVE 0 TO CHILD-PID
                  PERFORM PARENT-CODE
             WHEN OTHER
                  MULTIPLY -1 BY CHILD-PID END-MULTIPLY
                  DISPLAY 'CBL_GC_FORK returned system error: ' CHILD-PID
    END-EVALUATE
    STOP     RUN.
CHILD-CODE.
    CALL     "C$SLEEP" USING 1 END-CALL
    DISPLAY  "Hello, I am the child"
    MOVE     2 TO RETURN-CODE.
PARENT-CODE.
    DISPLAY  "Hello, I am the parent"
    CALL     "CBL_GC_WAITPID" USING CHILD-PID RETURNING WAIT-STS
    MOVE     0 TO RETURN-CODE
    EVALUATE TRUE
             WHEN WAIT-STS >= 0
                  DISPLAY 'Child ended with status: ' WAIT-STS
             WHEN WAIT-STS = -1
                  DISPLAY 'CBL_GC_WAITPID is not available on the '
                  'current system!'
             WHEN WAIT-STS < -1
                  MULTIPLY -1 BY WAIT-STS END-MULTIPLY
                  DISPLAY 'CBL_GC_WAITPID returned system error: ' WAIT-STS
    END-EVALUATE.

8.2.29 CBL_GC_GETOPT

CBL_GC_GETOPT Built-In Subroutine Syntax

CALL "CBL_GC_GETOPT" USING BY REFERENCE SHORTOPTIONS LONGOPTIONS LONGIND
~~~~                 ~~~~~
                           BY VALUE LONG-ONLY
                           BY REFERENCE RETURN-CHAR OPT-VAL

CBL_GC_GETOPT adapts the well-known option parser, getopt, to GnuCOBOL.

The usage of this system routine is described by the following example.

IDENTIFICATION DIVISION.
PROGRAM-ID. PROG.
DATA DIVISION.
WORKING-STORAGE SECTION.
78  SHORTOPTIONS VALUE "jkl".
01  LONGOPTIONS.
    05 OPTIONRECORD OCCURS 2 TIMES.
       10  OPTIONNAME   PIC X(25).
       10  HAS-VALUE    PIC 9.
       10  VALPOINT     POINTER VALUE NULL.
       10  RETURN-VALUE PIC X(4).
01  LONGIND             PIC 99.
01  LONG-ONLY           PIC 9 VALUE 1.
01  RETURN-CHAR         PIC X(4).
01  OPT-VAL             PIC X(10).
01  COUNTER             PIC 9 VALUE 0.

We first need to define the necessary fields for getopt‘s shortoptions, longoptions, longoption index (longind), long-only-option (long-only) and also the fields for return values return-char and opt-val (arbitrary size with trimming, see return codes).

The shortoptions are written down as an alphanumeric field (i.e., a string with arbitrary size) as follows:

"ab:c::d"

This means we want getopt to look for short options named ‘a‘, ‘b‘, ‘c‘ or ‘d‘, require an option value for ‘b‘, and accept an optional one for ‘c‘.

The longoptions are defined as a table of records with oname, has-value, valpoint and val. [1]

oname defines the name of a longoption. has-value defines if an option value is demanded (has-val = 1), optional (has-val = 2) or not required (has-val = 0).

valpoint is a pointer used to specify an address to save getopt's return value to. The pointer is optional. If it is NULL, getopt returns a value as usual. If you use the pointer it has to point to a PIC X(4) field. The field val is a PIC X(4) character which is returned if the longoption was recognized.

The longoption structure is immutable! You can only vary the number of records.

Now we have the tools to run CBL_GC_GETOPT within the procedure division.

PROCEDURE DIVISION.
     MOVE     "version" to OPTIONNAME (1).
     MOVE     0 TO HAS-VALUE (1).
     MOVE     'V' TO RETURN-VALUE (1).
     MOVE     "verbose" TO OPTIONNAME (2).
     MOVE     0 TO HAS-VALUE (2).
     MOVE     'V' TO RETURN-VALUE (2).
     PERFORM  WITH TEST AFTER UNTIL RETURN-CODE = -1
              CALL 'CBL_GC_GETOPT' USING
                  BY REFERENCE SHORTOPTIONS LONGOPTIONS LONGIND
                  BY VALUE LONG-ONLY
                  BY REFERENCE RETURN-CHAR OPT-VAL
              END-CALL
              DISPLAY RETURN-CHAR END-DISPLAY
              DISPLAY OPT-VAL END-DISPLAY
     END-PERFORM
     STOP RUN.

The example shows how we initialize all parameters and call the routine until CBL_GC_GETOPT runs out of options and returns -1.

return-char might contain the following regular character if an option was recognized:

  • ?

    undefined or ambiguous option

  • 1

    non-option (only if first byte of so is ‘-‘)

  • 0

    valpoint != NULL and we are writing the return value to the specified address

  • -1

    no more options (or reach the first non-option if first byte of shortoptions is ‘+‘)

The return-codes of CBL_GC_GETOPT are:

  • 1

    a non-option (only if first byte of so is ‘-‘)

  • 0

    valpoint != NULL and we are writing the return value to the specified address

  • -1

    no more options (or reach the first non-option if first byte of shortoptions is ‘+‘)

  • 2

    truncated option value in opt-val (because opt-val was too small)

  • 3

    a regular answer from getopt

8.2.30 CBL_GC_HOSTED

CBL_GC_HOSTED Built-In Subroutine Syntax

CALL "CBL_GC_HOSTED" USING ARG-1  ARG-2
~~~~                 ~~~~~

Note replaces CBL_OC_HOSTED which is kept as a legacy item.

CBL_GC_HOSTED provides access to the following C hosted variables:

  • argc

    binary-long by value

  • argv

    pointer to char **

  • stdin, stdout, stderr

    pointer

  • errno

    giving address of errno in pointer to binary-long, use based for more

Direct access and conditional access to the following variables:

  • tzname

    pointer to pointer to array of two char pointers

  • timezone

    C long, will be seconds west of UTC

  • daylight

    C int, will be 1 during daylight savings

The system will need HAVE TIMEZONE defined for these to return anything meaningful. Attempts made when they are not available will return 1 from CBL GC HOSTED.

It returns 0 when match, 1 on failure, case matters as does length, “arg” won’t match.

The usage of this system routine is described by the following example.

IDENTIFICATION DIVISION.
 PROGRAM-ID. HOSTED.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  Argc        BINARY-LONG.
 01  Argv        POINTER.
 01  Stdin       POINTER.
 01  Stdout      POINTER.
 01  Stderr      POINTER.
 01  Errno       POINTER.
 01  Err         BINARY-LONG BASED.
 01  Domain      FLOAT-LONG VALUE 3.0.
 01  Tzname      POINTER.
 01  Tznames     POINTER BASED.
     05  Tzs     POINTER OCCURS 2.
 01  Timezone    BINARY-LONG.
 01  Daylight    BINARY-SHORT.
*>
 PROCEDURE DIVISION.
     call     "CBL_GC_HOSTED" using stdin "stdin"
     display  "stdin : " stdin
     call     "feof" using by value stdin
     display  "feof stdin : " return-code
     call     "CBL_GC_HOSTED" using stdout "stdout"
     display  "stdout : " stdout
     call     "fprintf" using by value stdout by content "Hello" & x"0a"
     call     "CBL_GC_HOSTED" using stderr "stderr"
     display  "stderr : " stderr
     call     "fprintf" using by value stderr by content "on err" & x"0a"
     call     "CBL_GC_HOSTED" using argc "argc"
     display  "argc : " argc
     call     "CBL_GC_HOSTED" using argv "argv"
     display  "argv : " argv
     call     "args" using by value argc argv
     call     "CBL_GC_HOSTED" using errno "errno"
     display  "&errno : " errno
     set      address of err to errno
     display  "errno : " err
     call     "acos" using by value domain
     display  "errno after acos(3.0): " err ", EDOM is 33"
     call     "CBL_GC_HOSTED" using argc "arg"
     display  "'arg' lookup : " return-code
     call     "CBL_GC_HOSTED" using null "argc"
     display  "null with argc : " return-code
     display  "argc is still : " argc
*> the following only returns zero if the system has HAVE_TIMEZONE set
     call     "CBL_GC_HOSTED" using daylight "daylight "
     display  "'timezone' lookup : " return-code
     if       return-code not = 0
              display "system doesn't has timezone"
     else
              display "timezone is : " timezone
              call "CBL_GC_HOSTED" using daylight "daylight "
              display "'daylight' lookup : " return-code
              display "daylight is : " daylight
              set environment "TZ" to "PST8PDT"
              call static "tzset" returning omitted on exception
                        continue end-call
              call "CBL_GC_HOSTED" using tzname "tzname"
              display "'tzname' lookup : " return-code
*> tzs(1) will point to z"PST" and tzs(2) to z"PDT"
              if   return-code equal 0 and tzname not equal null then
                   set address of tznames to tzname
                   if   tzs(1) not equal null then
                        display "tzs #1 : " tzs(1)
                   end-if
                   if   tzs(2) not equal null then
                        display "tzs #2 : " tzs(2)
                   end-if
              end-if
     end-if
     goback.
 end program hosted.

Note that the legacy name of this routine that starts with CBL_OC is deprecated, as is NANOSLEEP but will still work. It is recommended that all library routines names starting with CBL_OC are replaced with CBL_GC to minimise issues.

8.2.31 CBL_GC_NANOSLEEP

CBL_GC_NANOSLEEP Built-In Subroutine Syntax

CALL "CBL_GC_NANOSLEEP" USING nanoseconds-to-sleep
~~~~                    ~~~~~

Note replaces CBL_OC_NANOSLEEP which is kept as a legacy item.

This subroutine puts the program to sleep for the specified number of nanoseconds.

The effective granularity of <nanoseconds-to-sleep> values will depend upon the granularity of the system clock your computer is using and the timing granularity of the operating system that computer is running.

For example, you will not expect to see any difference between values of 1, 100, 500 or 1000, but you should see a difference between values such as 250000000 and 500000000.

The <nanoseconds-to-sleep> argument is a numeric literal or data item.

There are one billion nanoseconds in a second, so if you wanted to put the program to sleep for 1/4 second you’d use a <nanoseconds-to-sleep> value of 250000000.

Note that the legacy name of this routine starts with “CBL_OC” is deprecated, as is HOSTED, but will still work. It is recommended that all library routines names starting with “CBL_OC” are replaced with “CBL_GC” to minimise issues.

8.2.32 CBL_GC_PRINTABLE

CBL_GC_PRINTABLE Built-In Subroutine Syntax

 CALL "CBL_GC_PRINTABLE" USING data-item [ , char ]
 ~~~~                    ~~~~~

Note replaces C$PRINTABLE which is kept as a legacy item.

The CBL_GC_PRINTABLE subroutine converts the contents of the data-item specified as the first argument to printable characters.

Those characters that are deemed printable (as defined by the character set used by <data-item>) will remain unchanged, while those that are not printable will be converted to the character specified as the second argument.

If no <char> argument is provided, a period (’.‘) will be used.

8.2.33 CBL_GC_WAITPID

CBL_GC_WAITPID Built-In Subroutine Syntax

CALL "CBL_GC_WAITPID" USING ARG-1
~~~~                  ~~~~~
                      RETURNING RET-STATUS
                      ~~~~~~~~~

CBL_GC_WAITPID allows you to wait until another system process ended.

Additionally you can check the process’s return code.

Parameters: none

Returns: function-status / child-status

Negative values are returned for system dependant error codes and -1 if the function is not available on the current system.

CALL     "CBL_GC_WAITPID" USING CHILD-PID RETURNING WAIT-STS
MOVE     0 TO RETURN-CODE
DISPLAY  'CBL_GC_WAITPID ended with status: ' WAIT-STS

8.2.34 CBL_GET_CSR_POS

CBL_GET_CSR_POS Built-In Subroutine Syntax

CALL "CBL_GET_CSR_POS" USING cursor-locn-buffer
~~~~                   ~~~~~

This subroutine will retrieve the current cursor location on the screen, returning a 2-byte value into the supplied <cursor-locn-buffer>. The first byte of <cursor-locn-buffer> will receive the current line (row) location while the second receives the current column location.

The returned location data will be in binary form, and will be based upon starting values of 0, meaning that if the cursor is located at line 15, column 12 at the time this routine is called, a value of (14,11) will be returned.

The following is a typical <cursor-locn-buffer> definition:

01  CURSOR-LOCN-BUFFER.
    05 CURSOR-LINE          USAGE BINARY-CHAR.
    05 CURSOR-COLUMN        USAGE BINARY-CHAR.

Values of 1 (Line) and 1 (column) will be returned if GnuCOBOL was not generated to include screen I/O.

8.2.35 CBL_GET_CURRENT_DIR

CBL_GET_CURRENT_DIR Built-In Subroutine Syntax

CALL "CBL_GET_CURRENT_DIR" USING BY VALUE 0,
~~~~                       ~~~~~    ~~~~~
                                 BY VALUE length,
                                    ~~~~~
                                 BY REFERENCE buffer
                                    ~~~~~~~~~

This retrieves the fully-qualified pathname of the current directory, saving up to <length> characters of that name into <buffer>.

The first argument is unused, but must be specified. It must be specified BY VALUE ( 7.8.5 CALL).

The <length> argument must be specified BY VALUE. The <buffer> argument must be specified BY REFERENCE.

The value specified for the <length> argument (a numeric literal or data item) should not exceed the actual length of <buffer> argument.

If the value specified for the <length> argument is LESS THAN the actual length of <buffer> argument, the current directory path will be left-justified and space filled within the first <length> bytes of <buffer> — any bytes in <buffer> after that point will be unchanged.

If the routine is successful, a value of 0 will be returned to the RETURN-CODE special register ( 7.7 Special Registers). If the routine failed because of a problem with an argument (such as a negative or 0 length), a value of 128 will result. Finally, if the 1st argument value is anything but zero, the routine will fail with a 129 value.

8.2.36 CBL_GET_SCR_SIZE

CBL_GET_SCR_SIZE Built-In Subroutine Syntax

CALL "CBL_GET_SCR_SIZE" USING no-of-lines, no-of-cols
~~~~                    ~~~~~

Use this subroutine to retrieve the current console screen size.

When the system is running in a windowed environment, this will be the sizing of the console window in which the program is executing. When the system is not running a windowing environment, the physical console screen attributes will be returned. In environments such as a Windows console window, where the logical size of the window may far exceed that of the physical console window, the size returned will be that of the physical console window. Two one-byte values will be returned — the first will be the current number of lines (rows) while the second will be the number of columns.

The returned size data will be in binary form.

The following are typical <no-of-lines> and <no-of-columns> definitions:

01  NO-OF-LINES             USAGE BINARY-CHAR.
01  NO-OF-COLUMNS           USAGE BINARY-CHAR.

GnuCOBOL run-time screen management must have been initialized prior to CALLing this routine in order to receive meaningful values. This means that a DISPLAY data-item statement ( 7.8.12.4 DISPLAY data-item) or a ACCEPT data-item statement ( 7.8.1.4 ACCEPT data-item) must have been executed prior to executing the CALL statement.

Zero values will be returned if the screen has not been initialized and values of 24 (lines) and 80 (columns) will be returned if GnuCOBOL was not generated to include screen I/O.

8.2.37 CBL_IMP

CBL_IMP Built-In Subroutine Syntax

CALL "CBL_IMP" USING item-1, item-2, BY VALUE byte-length
~~~~           ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      1
      0      1      1
      1      0      0
      1      1      1
    

    This subroutine performs a bit-by-bit logical implies process between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the IMP process. | | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.38 CBL_NIMP

CBL_NIMP Built-In Subroutine Syntax

CALL "CBL_NIMP" USING item-1, item-2, BY VALUE byte-length
~~~~            ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      0
      0      1      0
      1      0      1
      1      1      0
    

    This subroutine performs the negation of a bit-by-bit logical implies process between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the NIMP process. | | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.39 CBL_NOR

CBL_NOR Built-In Subroutine Syntax

CALL "CBL_NOR" USING item-1, item-2, BY VALUE byte-length
~~~~           ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      1
      0      1      0
      1      0      0
      1      1      0
    

    This subroutine performs the negation of a bit-by-bit logical or’ process between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the NOR process. | | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.40 CBL_NOT

CBL_NOT Built-In Subroutine Syntax

CALL "CBL_NOT" USING item-1, BY VALUE byte-length
~~~~           ~~~~~            ~~~~~

This subroutine “flips” the left-most 8*<byte-length> bits of <item-1>, changing 0 bits to 1, and 1 bits to 0. The changes are made directly im <item-1>.

The <item-1> argument must be a data item. The length of <item-1> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be passed using BY VALUE ( 7.8.5 CALL).

Any bits in <item-1> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.41 CBL_OPEN_FILE

CBL_OPEN_FILE Built-In Subroutine Syntax

CALL "CBL_OPEN_FILE" USING file-path, access-mode, 0, 0, handle
~~~~                 ~~~~~

This routine opens an existing file for use as a byte-stream file usable by CBL_WRITE_FILE or CBL_READ_FILE.

The <file-path> argument is an alphanumeric literal or data-item.

The <access-mode> argument is a numeric literal or data item with a PIC X USAGE COMP-X (or USAGE BINARY-CHAR) definition; it specifies how you wish to use the file, as follows:

  • 1

    input (read-only)

  • 2

    output (write-only)

  • 3

    input and/or output

The third and fourth arguments would specify a locking mode and device specification, respectively, but they’re not implemented in GnuCOBOL (currently, at least) — just specify each as 0.

The final argument (<handle>) is a PIC X(4) USAGE COMP-X item that will receive the handle to the file. That handle is used on all other byte-stream functions to reference this specific file.

A RETURN-CODE special register ( 7.7 Special Registers) value of -1 indicates an invalid argument, while a value of 0 indicates success. A value of 35 means the file does not exist.

8.2.42 CBL_OR

CBL_OR Built-In Subroutine Syntax

CALL "CBL_OR" USING item-1, item-2, BY VALUE byte-length
~~~~          ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      0
      0      1      1
      1      0      1
      1      1      1
    

    This subroutine performs a bit-by-bit logical or process between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the OR process. | | | The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.43 CBL_READ_FILE

CBL_READ_FILE Built-In Subroutine Syntax

CALL "CBL_READ_FILE" USING handle, offset, nbytes, flag, buffer
~~~~                 ~~~~~

This routine reads <nbytes> of data starting at byte number <offset> from the byte-stream file defined by <handle> into <buffer>.

The <handle> argument (PIC X(4) USAGE COMP-X) must have been populated by a prior call to CBL_OPEN_FILE built-in system subroutine ( 8.2.41 CBL_OPEN_FILE).

The <offset> argument (PIC X(8) USAGE COMP-X) defines the location in the file of the first byte to be read. The first byte of a file is byte offset 0 and MUST be preset to zero for first use.

The <nbytes> argument (PIC X(4) USAGE COMP-X) specifies how many bytes (maximum) will be read. If the <flag> argument is specified as 128, the size of the file (in bytes) will be returned into the file offset argument (argument 2) upon completion. Not all operating system/GnuCOBOL environments may be able to retrieve file sizes in such cases, a value of zero will be returned. The only other valid value for flags is 0. This argument may be specified either as a numeric literal or as a PIC X USAGE COMP-X data item.

Upon completion, the RETURN-CODE special register ( 7.7 Special Registers) will be set to 0 if the read was successful or to 10 if an “end-of-file” condition occurred. If a value of -1 is returned, a problem was identified with the subroutine arguments.

8.2.44 CBL_READ_KBD_CHAR

CBL_READ_KBD_CHAR Build-In Subroutine Syntax

CALL "CBL_READ_KBD_CHAR" USING char RETURNING status-code.
~~~~                     ~~~~~      ~~~~~~~~~

Waits until a character is typed from the terminal and then read it with no echo.

Parameters: char PIC X. Receives the character that was typed, in ASCII.

status-code PIC XX COMP-5.

If RETURNING is not used the RETURN-CODE special register receives the status-code where zero is success and non-zero it is not.

[Above information taken from MF WB manual].

8.2.45 CBL_RENAME_FILE

CBL_RENAME_FILE Built-In Subroutine Syntax

CALL "CBL_RENAME_FILE" USING old-file-path, new-file-path
~~~~                   ~~~~~

You may use this subroutine to rename a file.

The file specified by <old-file-path> will be “renamed” to the name specified as <new-file-path>. Each argument may be an alphanumeric literal or data item.

Despite what the name of this routine might make you believe, this routine is more than just a simple “rename” — it will actually move the file supplied as the 1st argument to the file specified as the 2nd argument. Think of it as a two-step sequence, first copying the <old-file-path> file to the <new-file-path> file and then a second step where the <old-file-path> is deleted.

If the attempt to move the file fails (for example, it doesn’t exist), the RETURN-CODE special register ( 7.7 Special Registers) will be set to 128; on successful completion it will be set to 0.

8.2.46 CBL_SET_CSR_POS

CBL_SET_CSR_POS Build-In Subroutine Syntax

CALL "CBL_SET_CSR_POS" USING cursor-locn-buffer
~~~~                   ~~~~~

Set current cursor position on terminal.

This subroutine will set the cursor location on the screen, using a 2-byte value into the supplied <cursor-locn-buffer>. The first byte of <cursor-locn-buffer> is for the line (row) location while the second sets the column location.

The two byte data block must be in binary form, and will be based upon starting values of 0, meaning that if the routine is called with a value of (14,11) cursor will be located at line 15, column 12.

The following is a typical <cursor-locn-buffer> definition:

01  CURSOR-LOCN-BUFFER.
    05 CURSOR-LINE          USAGE BINARY-CHAR.
    05 CURSOR-COLUMN        USAGE BINARY-CHAR.

8.2.47 CBL_SET_SCR_SIZE

CBL_SET_SRC_SIZE Built-In Subroutine Syntax

CALL "CBL_SET_SCR_SIZE" USING no-of-lines, no-of-cols
~~~~                    ~~~~~

Use this subroutine to set the current console screen size.

WARNING: This function may well not be created so this text is really a place holder as no information about its use is currently available - at least as of v3.2 final although it is in one of the compiler source files.

This also means that the definition of this function has NOT been passed to the manual maintainer, i.e., Vincent Coen. If you know exactly where this is correctly defined, may be in another compiler manual please pass link of it, or better still the exact definition, thanks.

The following are typical <no-of-lines> and <no-of-columns> definitions:

01  NO-OF-LINES             USAGE BINARY-CHAR.
01  NO-OF-COLUMNS           USAGE BINARY-CHAR.

GnuCOBOL run-time screen management must have been initialized prior to CALLing this routine in order to set meaningful values. This means that a DISPLAY data-item statement ( 7.8.12.4 DISPLAY data-item) or a ACCEPT data-item statement ( 7.8.1.4 ACCEPT data-item) must have been executed prior to executing the CALL statement.

Zero values will be returned if the screen has not been initialized and values of 24 (lines) and 80 (columns) will be returned if GnuCOBOL was not generated to include screen I/O.

8.2.48 CBL_TOLOWER

CBL_TOLOWER Built-In Subroutine Syntax

CALL "CBL_TOLOWER" USING data-item, BY VALUE convert-length
~~~~               ~~~~~               ~~~~~

This routine will convert the first <convert-length> (a numeric literal or data item) characters of <data-item> (an alpha-numeric identifier) to lower-case.

The <convert-length> argument must be specified BY VALUE ( 7.8.5 CALL). It specifies how many (leading) characters in data-item will be converted — any characters after that will remain unchanged.

If <convert-length> is negative or zero, no conversion will be performed.

8.2.49 CBL_TOUPPER

CBL_TOUPPER Built-In Subroutine Syntax

CALL "CBL_TOUPPER" USING data-item, BY VALUE convert-length
~~~~               ~~~~~               ~~~~~

This routine will convert the first <convert-length> (a numeric literal or data item) characters of <data-item> (an alpha-numeric identifier) to upper-case.

The <convert-length> argument must be specified BY VALUE ( 7.8.5 CALL). It specifies how many (leading) characters in data-item will be converted — any characters after that will remain unchanged.

If <convert-length> is negative or zero, no conversion will be performed.

8.2.50 CBL_WRITE_FILE

CBL_WRITE_FILE Built-In Subroutine Syntax

CALL "CBL_WRITE_FILE" USING handle, offset, nbytes, 0, buffer
~~~~                  ~~~~~

This routine writes <nbytes> of data from <buffer> to the byte-stream file defined by <handle> starting at byte number <offset> within the file.

The <handle> argument (PIC X(4) USAGE COMP-X) must have been populated by a prior call to CBL_OPEN_FILE. The offset argument (PIC X(4) USAGE COMP-X) defines the location in the file of the first byte to be written to. The first byte of a file is byte offset 0.

The <nbytes> argument (PIC X(4) USAGE COMP-X) specifies how many bytes (maximum) will be written.

Currently, the only allowable value for the flags argument is 0. This argument may be specified either as a numeric literal or as a PIC X(1) USAGE COMP-X data item.

Upon completion, the RETURN-CODE special register ( 7.7 Special Registers) will be set to 0 if the write was successful or to 30 if an I/O error condition occurred. If a value of -1 is returned, a problem was identified with the subroutine arguments.

8.2.51 CBL_XOR

CBL_XOR Built-In Subroutine Syntax

CALL "CBL_XOR" USING item-1, item-2, BY VALUE byte-length
~~~~           ~~~~~                    ~~~~~
  •  Old    Old    New
    Arg 1  Arg 2  Arg 2
     Bit    Bit    Bit
    =====  =====  =====
      0      0      0
      0      1      1
      1      0      1
      1      1      0
    
    This subroutine performs a bit-by-bit logical exclusive or process between the left-most 8*<byte-length> corresponding bits of <item-1> and <item-2>, storing the resulting bit string into <item-2>. The truth table shown to the left documents the XOR process.

    The <item-1> argument may be an alphanumeric literal or a data item and <item-2> must be a data item. The length of both <item-1> and <item-2> must be at least 8*<byte-length>.

The <byte-length> argument may be a numeric literal or data item, and must be specified using BY VALUE ( 7.8.5 CALL).

Any bits in <item-2> after the 8*<byte-length> point will be unaffected.

A result of zero will be passed back in the RETURN-CODE special register ( 7.7 Special Registers).

8.2.52 SYSTEM

SYSTEM Built-In Subroutine Syntax

CALL "SYSTEM" USING command
~~~~          ~~~~~

This subroutine submits <command> (an alphanumeric literal or data item) to a command shell for execution as if it were typed into a console/terminal window.

A shell will be opened subordinate to the GnuCOBOL program issuing the call to SYSTEM.

Output from the command (if any) will appear in the command window in which the GnuCOBOL program was executed.

On a Unix system, the shell environment will be established using the default shell program. This is also true when using a GnuCOBOL build created with and for OSX or the Cygwin Unix emulator.

With native Windows Windows/MinGW builds, the shell environment will be the Windows console window command processor (usually cmd.exe) appropriate for the version of Windows you’re using.

To trap output from the executed command and process it within the GnuCOBOL program, use a redirection (’>‘) to send the command output to a temporary file which you read from within the program once control returns.

The exit status of the executed command will be available in the RETURN-CODE special-register.

8.2.53 X”91”

X”91” Built-In Subroutine Syntax

CALL X"91" USING return-code, function-code, binary-variable-arg
~~~~       ~~~~~

The original Micro Focus version of this routine is capable of providing a wide variety of functions. GnuCOBOL supports just three of them:

  • Turning runtime switches (SWITCH-1, … , SWITCH-8) on.

  • Turning runtime switches (SWITCH-1, … , SWITCH-8) off.

  • Retrieving the number of arguments passed to a subroutine.

The <return-code> argument must be a one-byte binary numeric data item (USAGE BINARY-CHAR is recommended). It will receive a value of 0 if the operation was successful, 1 otherwise.

The <function-code> argument must be either a numeric literal or a one-byte binary numeric data item (USAGE BINARY-CHAR is recommended).

The third argument — <variable-arg> — is defined differently depending upon the <function-code> value, as follows:

  • 11

    Sets and/or clears all eight of the COBOL switches (SWITCH-1 through SWITCH-8). 5.1.3 SPECIAL-NAMES, for an explanation of those switches.

    The <variable-arg> argument should be an OCCURS 8 TIMES table of USAGE BINARY-CHAR.

    Each occurrence that is set to a value of zero prior to the CALL X"91" will cause the corresponding switch to be cleared. Each occurrence set to 1 prior to the CALL X"91" will cause the corresponding switch to be set.

    Values other than 0 or 1 will be ignored.

  • 12

    Reads all eight of the COBOL switches (SWITCH-1 through SWITCH-8)

    The <variable-arg> argument should be an OCCURS 8 TIMES table of USAGE BINARY-CHAR.

    Each of the 1st eight occurrences of the array will be set to either 0 or 1 — 1 if the corresponding switch is set, 0 otherwise.

  • 16

    Retrieves the number of arguments passed to the program executing the CALL X"91", saving that number into the <variable-arg> argument. That should be a binary numeric data item (USAGE BINARY-CHAR is recommended).

8.2.54 X”E4”

X”E4” Built-In Subroutine Syntax

CALL X"E4"
~~~~

Use X"E4" to clear the screen. There are no arguments and no returned value.

8.2.55 X”E5”

X”E5” Built-In Subroutine Syntax

CALL X"E5"
~~~~

The X"E5" routine will sound the PC “bell”. There are no arguments and no returned value.

8.2.56 X”F4”

X”F4” Built-In Subroutine Syntax

CALL X"F4" USING byte, table
~~~~       ~~~~~

This routine packs the low-order (rightmost) bit from each of the eight 1-byte items in <table> into the corresponding bit positions of the single-byte data item <byte>.

The <byte> data item need be only a single byte in size. If it is longer, the excess will be unaffected by this subroutine.

The <table> data item must be at least 8 bytes long. If it is longer, the excess will be ignored by this subroutine.

Typically, table is defined similarly to the following:

01  Table-Arg.
    05 Each-Byte OCCURS 8 TIMES USAGE BINARY-CHAR.

8.2.57 X”F5”

X”F5” Built-In Subroutine Syntax

CALL X"F5" USING byte, table
~~~~       ~~~~~

This routine unpacks each bit of the single-byte data item <byte> into the low-order (rightmost) bit of each of the corresponding eight 1-byte items in <table>. The other seven bit positions of each of the first eight entries in <table> will be set to zero.

The <byte> data item need be only a single byte in size. If it is longer, the excess will be unaffected by this subroutine.

The <table> data item must be at least 8 bytes long. If it is longer, the excess will be ignored by this subroutine.

Typically, table is defined similarly to the following:

01  Table-Arg.
    05 Each-Byte OCCURS 8 TIMES USAGE BINARY-CHAR.