.. |_| unicode:: 0xA0 :trim: .. role:: small-caps :class: small-caps .. include:: .. index:: single:Functions .. _Functions: 8 Functions =========== .. index:: single:Intrinsic Functions .. _IntrinsicAFunctions: 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 .. index:: single:-fintrinsics Compiler Switch .. index:: single:Compiler Switches, -fintrinsics Note how the word \ :code:`FUNCTION`\ is part of the syntax when you use an intrinsic function. You can use intrinsic functions without having to include the reserved word \ :code:`FUNCTION`\ via settings in the \ :code:`REPOSITORY`\ ( :ref:`REPOSITORY`) paragraph. You may accomplish the same thing by specifying the \ \ \ :code:`-fintrinsics`\ switch to the GnuCOBOL compiler when you compile your programs. User-written functions ( :ref:`SubprogramATypes`) never require the \ :code:`FUNCTION`\ keyword when they are executed, because each user-written function a program uses \ *must*\ be included in that program's \ :code:`REPOSITORY`\ paragraph, which therefore makes the \ :code:`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 \ :code:`FORMATTED-CURRENT-DATE`\ , \ :code:`FORMATTED-DATE`\ , \ :code:`FORMATTED-TIME`\ , and \ :code:`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 \ :code:`INTEGER-OF-FORMATTED-DATE`\ , \ :code:`SECONDS-FROM-FORMATTED-TIME`\ , and \ :code:`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 \ :code:`FORMATTED-CURRENT-DATE`\ , \ :code:`FORMATTED-DATE`\ , \ :code:`FORMATTED-TIME`\ , and \ :code:`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 \ :code:`INTEGER-OF-FORMATTED-DATE`\ , \ :code:`SECONDS-FROM-FORMATTED-TIME`\ , and \ :code:`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. .. index:: single:ABS .. _ABS: 8.1.1 ABS ~~~~~~~~~ ABS Function Syntax :: ABS(number) ~~~ This function determines and returns the absolute value of (a numeric literal or data item) supplied as an argument. Note that \ :code:`ABSOLUTE-VALUE`\ has an alias for this function. .. index:: single:ACOS .. _ACOS: 8.1.2 ACOS ~~~~~~~~~~ ACOS Function Syntax :: ACOS(cosine) ~~~~ The \ :code:`ACOS`\ function determines and returns the trigonometric arc-cosine, or inverse cosine, of 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 = ( * 180 ) / FUNCTION PI .. index:: single:ANNUITY .. _ANNUITY: 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 (numeric data item or literal) for each of (numeric data items or literals). 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 . 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. #. 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. #. Other additional documentation: #. 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)))) .. index:: single:ASIN .. _ASIN: 8.1.4 ASIN ~~~~~~~~~~ ASIN Function Syntax :: ASIN(sine) ~~~~ The \ :code:`ASIN`\ function determines and returns the trigonometric arc-sine, or inverse sine, of 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 = ( * 180 ) / FUNCTION PI .. index:: single:ATAN .. _ATAN: 8.1.5 ATAN ~~~~~~~~~~ ATAN Function Syntax :: ATAN(tangent) ~~~~ Use this function to determine and return the trigonometric arc-tangent, or inverse tangent, of 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 = ( * 180 ) / FUNCTION PI .. index:: single:BIT-OF .. _BIT-OF: 8.1.6 BIT-OF ~~~~~~~~~~~~ BIT-OF Function Syntax :: BIT-OF (argument-1) ~~~~~~ \ :code:`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. #. The function type is alphanumeric. #. must be a data item, literal, or an intrinsic function result of any data class. Returned values: #. An alphanumeric character string consisting of the binary representation of each byte in . #. The length of the character string returned, in bytes, is eight times the length of , 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 .. index:: single:BIT-TO-CHAR .. _BIT-TO-CHAR: 8.1.7 BIT-TO-CHAR ~~~~~~~~~~~~~~~~~ BIT-TO-CHAR Function Syntax :: BIT-TO-CHAR {argument-1) ~~~~~~~~~~~ \ :code:`BIT-TO-CHAR`\ function returns a character string that represents a bit pattern supplied on input. #. The function type is alphanumeric. #. must be an alphanumeric literal, alphanumeric data item, or alphanumeric group item. #. must consist only of the characters "0" and "1". #. The length of must be a multiple of 8 bytes. Returned values: #. A character string consisting of bytes representing the sequence of "0" and "1" characters in . #. 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 .. index:: single:BYTE-LENGTH .. _BYTE-LENGTH: 8.1.8 BYTE-LENGTH ~~~~~~~~~~~~~~~~~ BYTE-LENGTH Function Syntax :: BYTE-LENGTH(string) ~~~~~~~~~~~ \ :code:`BYTE-LENGTH`\ returns the length --- in bytes --- of (a group item, \ :code:`USAGE DISPLAY`\ elementary item or alphanumeric literal). This intrinsic function is identical to the \ :code:`LENGTH-AN`\ ( :ref:`LENGTH-AN`) function. Note that the value returned by this function is not necessarily the number of \ *characters*\ comprising , but rather the number of actual \ *bytes*\ required to store it. For example, if 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 :small-caps:`ASCII` or :small-caps:`EBCDIC`), then calling this function with a argument whose \ :code:`PICTURE`\ ( :ref:`PICTURE`) is \ :code:`N(4)`\ would return a value of 8 rather than the value 4. Contrast this with the \ :code:`LENGTH`\ ( :ref:`LENGTH`) function. .. index:: single:CHAR .. _CHAR: 8.1.9 CHAR ~~~~~~~~~~ CHAR Function Syntax :: CHAR(integer) ~~~~ This function returns the character in the ordinal position specified by (a numeric integer literal or data item with a value of 1 or greater) from the \ :code:`COLLATING SEQUENCE`\ ( :ref:`OBJECT-COMPUTER`) being used by the program. For example, if the program is using the (default) :small-caps:`ASCII` character set, CHAR(34) returns the 34th character in the :small-caps:`ASCII` character set --- an exclamation-point ('\ :code:`!`\ '). If you are using this function to convert a numeric value to its corresponding :small-caps:`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 :small-caps:`ASCII` equivalent: :: 01 Char-Value. 05 Numeric-Value USAGE BINARY-CHAR. ... MOVE numeric-character-value TO Numeric-Value The \ :code:`Char-Value`\ item now has the corresponding :small-caps:`ASCII` character value. .. index:: single:COMBINED-DATETIME .. _COMBINED-DATETIME: 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 argument (a numeric data item or literal) and the last five of which are the integer value of argument (also a numeric data item or literal). If is less than 1 or greater than 3,067,671, or if is less than 1 or greater than 86,400, a value of 0 is returned and a runtime error will result. 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. 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". .. index:: single:CONCAT .. _CONCAT: 8.1.11 CONCAT ~~~~~~~~~~~~~ CONCAT Function Syntax :: CONCAT | CONCATENATE (argument-1 [, argument-2 ]...) ~~~~~~ ~~~~~~~~~~~ This function concatenates the , , ... (group items, \ :code:`USAGE DISPLAY`\ elementary items and/or alphanumeric literals) together into a single string result. If a numeric literal or \ :code:`PIC 9`\ identifier is specified as an argument, decimal points, if any, will be removed and negative signs in \ :code:`PIC S9`\ fields or numeric literals will be inserted as defined by the \ :code:`SIGN IS`\ ( :ref:`SIGNAIS`) clause (or absence thereof) of the field. Numeric literals are processed as if \ :code:`SIGN IS TRAILING SEPARATE`\ were in effect. .. index:: single:CONCATENATE .. _CONCATENATE: 8.1.12 CONCATENATE ~~~~~~~~~~~~~~~~~~ CONCATENATE Function Syntax :: CONCAT | CONCATENATE (argument-1 [, argument-2 ]...) ~~~~~~ ~~~~~~~~~~~ This function concatenates the , , ... (group items, \ :code:`USAGE DISPLAY`\ elementary items and/or alphanumeric literals) together into a single string result. If a numeric literal or \ :code:`PIC 9`\ identifier is specified as an argument, decimal points, if any, will be removed and negative signs in \ :code:`PIC S9`\ fields or numeric literals will be inserted as defined by the \ :code:`SIGN IS`\ ( :ref:`SIGNAIS`) clause (or absence thereof) of the field. Numeric literals are processed as if \ :code:`SIGN IS TRAILING SEPARATE`\ were in effect. CONCATENATE is a GnuCOBOL extention BUT also see the ISO standard CONCAT function. .. index:: single:CONTENT-LENGTH .. _CONTENT-LENGTH: 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. .. index:: single:CONTENT-OF .. _CONTENT-OF: 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. .. index:: single:COS .. _COS: 8.1.15 COS ~~~~~~~~~~ COS Function Syntax :: COS(angle) ~~~ The \ :code:`COS`\ function determines and returns the trigonometric cosine of (a numeric literal or data item) supplied as an argument. 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 = ( * FUNCTION PI) / 180 .. index:: single:CURRENCY-SYMBOL .. _CURRENCY-SYMBOL: 8.1.16 CURRENCY-SYMBOL ~~~~~~~~~~~~~~~~~~~~~~ .. index:: single:Environment Variables, LANG .. index:: single:LANG Environment Variable CURRENCY-SYMBOL Function Syntax :: CURRENCY-SYMBOL ~~~~~~~~~~~~~~~ The \ :code:`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 ( :ref:`RunATimeAEnvironmentAVariables`) environment variable. On Windows, the Control Panel's "Regional and Language Options" define the locale. Changing the currency symbol via the \ :code:`SPECIAL-NAMES`\ ( :ref:`SPECIAL-NAMES`) paragraph's \ :code:`CURRENCY SYMBOL`\ setting will \ *not*\ affect the value returned by this function. .. index:: single:CURRENT-DATE .. _CURRENT-DATE: 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. .. index:: single:DATE-OF-INTEGER .. _DATE-OF-INTEGER: 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 (a numeric integer data item or literal) to the date December 31, 1600. For example, \ :code:`DATE-OF-INTEGER(1)`\ returns 16010101 while \ :code:`DATE-OF-INTEGER(150000)`\ returns 20110908. A value less than 1 or greater than 3067671 (9999/12/31) will return a result of 0. .. index:: single:DATE-TO-YYYYMMDD .. _DATE-TO-YYYYMMDD: 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 (a numeric integer data item or literal) to an eight-digit format (\ *yyyymmdd*\ ). The optional (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 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 \ :code:`(FUNCTION NUMVAL (FUNCTION CURRENT-DATE (1:4)))`\ . .. index:: single:DAY-OF-INTEGER .. _DAY-OF-INTEGER: 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, \ :code:`DAY-OF-INTEGER(1)`\ returns 1601001 while \ :code:`DAY-OF-INTEGER(250000)`\ returns 2011251. A value less than 1 or greater than 3067671 (9999/12/31) will return a result of 0. .. index:: single:DAY-TO-YYYYDDD .. _DAY-TO-YYYYDDD: 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 (a numeric integer data item or literal) to a seven-digit numeric Julian format (yyyyddd). The optional 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 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))). .. index:: single:E .. _E: 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. .. index:: single:EXCEPTION-FILE .. _EXCEPTION-FILE: 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 ( :ref:`File Status Codes `) and the remaining 32 are the specification from the file's \ :code:`SELECT`\ ( :ref:`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 \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) built-in subroutine illustrates the use of this function. .. index:: single:EXCEPTION-LOCATION .. _EXCEPTION-LOCATION: 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. .. index:: single:-g Compiler Switch .. index:: single:Compiler Switches, -g .. index:: single:-ftraceall Compiler Switch .. index:: single:Compiler Switches, -ftraceall .. index:: single:-debug Compiler Switch .. index:: single:Compiler Switches, -debug The program must be compiled with the \ \ \ :code:`-debug`\ switch, \ \ \ :code:`-ftraceall`\ switch or \ \ \ :code:`-g`\ switch for this function to return any meaningful information. The documentation of the \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) built-in subroutine illustrates the use of this function. .. index:: single:EXCEPTION-STATEMENT .. _EXCEPTION-STATEMENT: 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. .. index:: single:-g Compiler Switch .. index:: single:Compiler Switches, -g .. index:: single:-ftraceall Compiler Switch .. index:: single:Compiler Switches, -ftraceall .. index:: single:-debug Compiler Switch .. index:: single:Compiler Switches, -debug The program must be compiled with the \ \ \ :code:`-debug`\ switch, \ \ \ :code:`-ftraceall`\ switch or \ \ \ :code:`-g`\ switch for this function to return any meaningful information. The documentation of the \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) built-in subroutine illustrates the use of this function. .. index:: single:EXCEPTION-STATUS .. _EXCEPTION-STATUS: 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 \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) built-in subroutine illustrates the use of this function. .. index:: single:Error Type Strings .. index:: single:Error Exception Codes .. _ErrorATypeAStrings: .. _ErrorAExceptionACodes: The following are the error type strings, and their corresponding exception codes and descriptions. \ \ * Code Error Type Description * \ :code:`0101`\ \ :code:`EC-ARGUMENT-FUNCTION`\ Function argument error * \ :code:`0202`\ \ :code:`EC-BOUND-ODO`\ \ :code:`OCCURS ... DEPENDING`\ ON data item out of bounds * \ :code:`0204`\ \ :code:`EC-BOUND-PTR`\ Data-pointer contains an address that is out of bounds * \ :code:`0205`\ \ :code:`EC-BOUND-REF-MOD`\ Reference modifier out of bounds * \ :code:`0207`\ \ :code:`EC-BOUND-SUBSCRIPT`\ Subscript out of bounds * \ :code:`0303`\ \ :code:`EC-DATA-INCOMPATIBLE`\ Incompatible data exception * \ :code:`0500`\ \ :code:`EC-I-O`\ input-output exception * \ :code:`0501`\ \ :code:`EC-I-O-AT-END`\ I-O status \ :code:`1x`\ * \ :code:`0502`\ \ :code:`EC-I-O-EOP`\ An end of page condition occurred * \ :code:`0504`\ \ :code:`EC-I-O-FILE-SHARING`\ I-O status \ :code:`6x`\ * \ :code:`0505`\ \ :code:`EC-I-O-IMP`\ I-O status \ :code:`9x`\ * \ :code:`0506`\ \ :code:`EC-I-O-INVALID-KEY`\ I-O status \ :code:`2x`\ * \ :code:`0508`\ \ :code:`EC-I-O-LOGIC-ERROR`\ I-O status \ :code:`4x`\ * \ :code:`0509`\ \ :code:`EC-I-O-PERMANENT-ERROR`\ I-O status \ :code:`3x`\ * \ :code:`050A`\ \ :code:`EC-I-O-RECORD-OPERATION`\ I-O status \ :code:`5x`\ * \ :code:`0601`\ \ :code:`EC-IMP-ACCEPT`\ Implementation-defined accept condition * \ :code:`0602`\ \ :code:`EC-IMP-DISPLAY`\ Implementation-defined display condition * \ :code:`0A00`\ \ :code:`EC-OVERFLOW`\ Overflow condition * \ :code:`0A02`\ \ :code:`EC-OVERFLOW-STRING`\ \ :code:`STRING`\ overflow condition * \ :code:`0A03`\ \ :code:`EC-OVERFLOW-UNSTRING`\ \ :code:`UNSTRING`\ overflow condition * \ :code:`0B05`\ \ :code:`EC-PROGRAM-NOT-FOUND`\ Called program not found * \ :code:`0D03`\ \ :code:`EC-RANGE-INSPECT-SIZE`\ Size of replace item in inspect differs * \ :code:`1000`\ \ :code:`EC-SIZE`\ Size error exception * \ :code:`1004`\ \ :code:`EC-SIZE-OVERFLOW`\ Arithmetic overflow in calculation * \ :code:`1005`\ \ :code:`EC-SIZE-TRUNCATION`\ Significant digits truncated in store * \ :code:`1007`\ \ :code:`EC-SIZE-ZERO-DIVIDE`\ Division by zero * \ :code:`1202`\ \ :code:`EC-STORAGE-NOT-ALLOC`\ The data-pointer specified in a \ :code:`FREE`\ statement does not identify currently allocated storage * \ :code:`1203`\ | \ :code:`EC-STORAGE-NOT-AVAIL`\ The amount of storage requested by an | \ :code:`ALLOCATE`\ statement is not available .. index:: single:EXP .. _EXP: 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 (a numeric literal or data item). .. index:: single:EXP10 .. _EXP10: 8.1.28 EXP10 ~~~~~~~~~~~~ EXP10 Function Syntax :: EXP10(number) ~~~~~ Computes and returns the value of 10 raised to the power specified by (a numeric literal or data item). .. index:: single:FACTORIAL .. _FACTORIAL: 8.1.29 FACTORIAL ~~~~~~~~~~~~~~~~ FACTORIAL Function Syntax :: FACTORIAL(number) ~~~~~~~~~ This function computes and returns the factorial value of (a numeric literal or data item). .. index:: single:FORMATTED-CURRENT-DATE .. _FORMATTED-CURRENT-DATE: 8.1.30 FORMATTED-CURRENT-DATE ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ FORMATTED-CURRENT-DATE Function Syntax :: FORMATTED-CURRENT-DATE ( argument-1 ) ~~~~~~~~~~~~~~~~~~~~~~ \ :code:`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 . .. index:: single:FORMATTED-DATE .. _FORMATTED-DATE: 8.1.31 FORMATTED-DATE ~~~~~~~~~~~~~~~~~~~~~ FORMATTED-DATE Function Syntax :: FORMATTED-DATE ( argument-1, argument-2 ) ~~~~~~~~~~~~~~ \ :code:`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. shall be a national or alphanumeric literal. 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". .. index:: single:FORMATTED-DATETIME .. _FORMATTED-DATETIME: 8.1.32 FORMATTED-DATETIME ~~~~~~~~~~~~~~~~~~~~~~~~~ FORMATTED-DATETIME Function Syntax :: FORMATTED-DATETIME ( argument-1, argument-2, argument-3, argument-4 ) ~~~~~~~~~~~~~~~~~~ \ :code:`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. shall be a national or alphanumeric literal. shall be a value in integer date form. shall be a value in standard numeric time form. 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. must not be specified if the time portion in is neither a UTC nor an offset format. The returned value is a representation of the date contained in combined with the time contained in according to the format in . If the format in 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 by the offset in . If the format in indicates that the time is to be returned as an offset from UTC, the value in is reflected directly in the time portion of the returned value and the offset in 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". .. index:: single:FORMATTED-TIME .. _FORMATTED-TIME: 8.1.33 FORMATTED-TIME ~~~~~~~~~~~~~~~~~~~~~ FORMATTED-TIME Function Syntax :: FORMATTED-TIME ( argument-1, argument-2, argument-3 ) ~~~~~~~~~~~~~~ \ :code:`FORMATTED-TIME`\ converts a value representing seconds past midnight formatted time of day with optional offset. shall be a national or alphanumeric literal. shall be a value in integer time form. 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. must not be specified if the time portion in is neither a UTC nor an offset format. Returned value : Is a representation of the standard numeric time contained in according to the format in . If the format in 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 by the offset in . If the format in indicates that the time is to be returned as an offset from UTC, the value in is reflected directly in the time portion of the returned value and the offset in 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". .. index:: single:FRACTION-PART .. _FRACTION-PART: 8.1.34 FRACTION-PART ~~~~~~~~~~~~~~~~~~~~ FRACTION-PART Function Syntax :: FRACTION-PART(number) ~~~~~~~~~~~~~ This function returns that portion of (a numeric data item or a numeric literal) that occurs to the right of the decimal point. \ :code:`FRACTION-PART(3.1415)`\ , for example, returns a value of 0.1415. This function is equivalent to the expression: :: -- FUNCTION INTEGER-PART() Example: display "base - " FUNCTION FRACTION-PART(FLOATER). Gives base - 000.456789 #. When moved to a variable, it MUST have a preceding 'V' in the PICTURE, i.e., PIC v(4). .. index:: single:HEX-OF .. _HEX-OF: 8.1.35 HEX-OF ~~~~~~~~~~~~~ HEX-OF Function Syntax :: HEX-OF {argument-1) ~~~~~~ \ :code:`HEX-OF`\ function returns an alphanumeric character string consisting of a hexadecimal representation of the argument used on input. #. The type of the function is alphanumeric. #. must be a data item, literal, or an intrinsic function result of any data class. Returned values: #. An alphanumeric character string consisting of a hexadecimal representation of . #. The length of the character string returned, in bytes, is twice the length of , in bytes. .. index:: single:HEX-TO-CHAR .. _HEX-TO-CHAR: 8.1.36 HEX-TO-CHAR ~~~~~~~~~~~~~~~~~~ HEX-TO-CHAR Function Syntax :: HEX-TO-CHAR {argument-1) ~~~~~~~~~~~ \ :code:`HEX-TO-CHAR`\ function returns a character string that represents the hexadecimal digit characters supplied on input. #. The type of the function is alphanumeric. #. must be an alphanumeric literal, alphanumeric data item, or alphanumeric group item. #. must consist only of the characters '0' through '9', 'A' through 'F', and 'a' through 'f'. #. The length of must be a multiple of 2 bytes. Returned values: #. A character string of bytes representing the hexadecimal digit characters of . #. The length of the result string is equal to the length of the input string divided by 2. .. index:: single:HIGHEST-ALGEBRAIC .. _HIGHEST-ALGEBRAIC: 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 is signed) value that could possibly be stored in . .. index:: single:INTEGER .. _INTEGER: 8.1.38 INTEGER ~~~~~~~~~~~~~~ INTEGER Function Syntax :: INTEGER(number) ~~~~~~~ The \ :code:`INTEGER`\ function returns the greatest integer value that is less than or equal to (a numeric literal or data item). .. index:: single:INTEGER-OF-DATE .. _INTEGER-OF-DATE: 8.1.39 INTEGER-OF-DATE ~~~~~~~~~~~~~~~~~~~~~~ INTEGER-OF-DATE Function Syntax :: INTEGER-OF-DATE(date) ~~~~~~~~~~~~~~~ This function converts (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 \ :code:`DATE-OF-INTEGER`\ ( :ref:`DATE-OF-INTEGER`) or \ :code:`DAY-OF-INTEGER`\ ( :ref:`DAY-OF-INTEGER`) function. .. index:: single:INTEGER-OF-DAY .. _INTEGER-OF-DAY: 8.1.40 INTEGER-OF-DAY ~~~~~~~~~~~~~~~~~~~~~ INTEGER-OF-DAY Function Syntax :: INTEGER-OF-DAY(date) ~~~~~~~~~~~~~~ This function converts (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 \ :code:`DATE-OF-INTEGER`\ ( :ref:`DATE-OF-INTEGER`) or \ :code:`DAY-OF-INTEGER`\ ( :ref:`DAY-OF-INTEGER`) function. .. index:: single:INTEGER-OF-FORMATTED-DATE .. _INTEGER-OF-FORMATTED-DATE: 8.1.41 INTEGER-OF-FORMATTED-DATE ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ INTEGER-OF-FORMATTED-DATE Function Syntax :: INTEGER-OF-FORMATTED-DATE ( argument-1, argument-2 ) ~~~~~~~~~~~~~~~~~~~~~~~~~ \ :code:`INTEGER-OF-FORMATTED-DATE`\ converts a date that is in specified format to integer date form. shall be a national or alphanumeric literal. The content must be either a date format or a combined date and time format. shall be a data item of the same type as . If is a date format the content of shall be a valid date in that format. If is a combined date and time format, the content of shall be a valid combined date and time in same format. .. index:: single:INTEGER-PART .. _INTEGER-PART: 8.1.42 INTEGER-PART ~~~~~~~~~~~~~~~~~~~ INTEGER-PART Function Syntax :: INTEGER-PART(number) ~~~~~~~~~~~~ Returns the integer portion of (a numeric literal or data item). .. index:: single:LENGTH .. _LENGTH: 8.1.43 LENGTH ~~~~~~~~~~~~~ LENGTH Function Syntax :: LENGTH(string) ~~~~~~ Returns the length --- in characters --- of (a group item, \ :code:`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 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 :small-caps:`ASCII` or :small-caps:`EBCDIC`), then calling this function with a argument whose \ :code:`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 \ :code:`BYTE-LENGTH`\ ( :ref:`BYTE-LENGTH`) and \ :code:`LENGTH-AN`\ ( :ref:`LENGTH-AN`) functions. .. index:: single:LENGTH-AN .. _LENGTH-AN: 8.1.44 LENGTH-AN ~~~~~~~~~~~~~~~~ LENGTH-AN Function Syntax :: LENGTH-AN(string) ~~~~~~~~~ This function returns the length --- in bytes of storage --- of (a group item, \ :code:`USAGE DISPLAY`\ elementary item or alphanumeric literal). This intrinsic function is identical to the \ :code:`BYTE-LENGTH`\ ( :ref:`BYTE-LENGTH`) function. Note that the value returned by this function is not the number of \ *characters*\ making up the , but rather the number of actual \ *bytes*\ of storage required to store . For example, if 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 :small-caps:`ASCII` or :small-caps:`EBCDIC`), then calling this function with a argument whose \ :code:`PICTURE is N(4)`\ would return a value of 8 rather than the value 4. Contrast this with the \ :code:`LENGTH`\ ( :ref:`LENGTH`) function. .. index:: single:LOCALE-COMPARE .. _LOCALE-COMPARE: 8.1.45 LOCALE-COMPARE ~~~~~~~~~~~~~~~~~~~~~ LOCALE-COMPARE Function Syntax :: LOCALE-COMPARE(argument-1, argument-2 [ , locale ]) ~~~~~~~~~~~~~~ The \ :code:`LOCALE-COMPARE`\ function returns a character indicating the result of comparing and using a culturally-preferred ordering defined by a . Either or both of the 1\ :sup:`st`\ 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 name or for the current locale if no argument is specified. Once that relationship is determined, a one-character alphanumeric value will be returned as follows: * '\ :code:`<`\ ' --- If is determined to be less than * '\ :code:`=`\ ' --- If the two arguments are equal to each other * '\ :code:`>`\ ' --- If is determined to be greater than :ref:`LOCALE Names `, for a list of typically-available locale names. .. index:: single:LOCALE-DATE .. _LOCALE-DATE: 8.1.46 LOCALE-DATE ~~~~~~~~~~~~~~~~~~ LOCALE-DATE Function Syntax :: LOCALE-DATE(date [, locale ]) ~~~~~~~~~~~ Converts the eight-digit Gregorian (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 name (group item or \ :code:`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. .. index:: single:LOCALE-TIME .. _LOCALE-TIME: 8.1.47 LOCALE-TIME ~~~~~~~~~~~~~~~~~~ LOCALE-TIME Function Syntax :: LOCALE-TIME(time [, locale ]) ~~~~~~~~~~~ Converts the four- (hhmm) or six-digit (hhmmss)