Part of the reason for this chapter is to prepare you for the manpower shortage that is already resulting from the year 2000 problem. (This subject is covered in greater detail in Bonus Day 6, "Dates and the Year 2000.") Recent versions of COBOL include several tools designed to help you handle year 2000 problems and date issues. These tools are called intrinsic functions. Intrinsic functions aren't limited to handling date problems, but many intrinsic functions are targeted at dates.
New Term: intrinsic--Belonging to the essential nature or constitution of something.
New Term: function--A computer subroutine--specifically, one that performs an action using zero, one, or more variables from a program and supplies the program with a single result.
Today you will learn about the following topics:
Intrinsic functions were added to the COBOL 85 standard. You've already seen something that looks and acts somewhat like an intrinsic function:
ACCEPT SYSTEM-DATE FROM DATE
The ACCEPT...FROM DATE syntax was covered in Bonus Day 2, "Miscellaneous COBOL Syntax." In the preceding example, DATE isn't a data item--it is a request for the system date from the operating system. DATE doesn't really exist as something on the system. It is actually a routine that looks up, builds, and returns a six-digit date. It does this dynamically while the program is running. If you run the program on two separate days, DATE will return two separate dates from the operating system, even though you haven't changed the program.
Intrinsic functions are similar to DATE, but their syntax is different. They are easier to understand with an example. The first intrinsic function we will look at is CURRENT-DATE. The CURRENT-DATE function returns the current date as a PIC X(21) that is broken down into a date and time and a number of hours difference from Greenwich Mean Time (GMT). The date fills the first eight positions with digits in the form of CCYYMMDD (where CC represents the hundredths of years of the four-digit year). The next eight positions are the time down to hundredths of a second in the form HHMMSSDD (where DD represents hundredths). The next five positions give you the difference in hours and minutes of local time from GMT.
The five-character GMT is broken down into a sign and four digits. The sign is - if local time is earlier than GMT. The sign is + if local time is the same as or later than GMT. The sign is set to 0 if the difference from GMT is not available on this system. Using Micro Focus Personal COBOL on an MS-DOS-based machine, this character will always be 0, because MS-DOS doesn't store information about your local time zone. The remaining four character positions are the hour and minute difference from GMT if the sign is not 0. Many operating systems store the difference from GMT, and you will see these five-character positions filled in when you use CURRENT-DATE on larger computers.
Listing B5.1, CURDAT.CBL, uses the CURRENT-DATE intrinsic function to extract the current date information.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. CURDAT. 000300 AUTHOR. MO BUDLONG. 000400 INSTALLATION. 000500 DATE-WRITTEN. 09/07/96. 000600 DATE-COMPILED. 000700 SECURITY. NONE 000800 ENVIRONMENT DIVISION. 000900 INPUT-OUTPUT SECTION. 001000 FILE-CONTROL. 001100 DATA DIVISION. 001200 FILE SECTION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 CD-DATE PIC X(21). 001600 01 FILLER REDEFINES CD-DATE. 001700 05 CD-CYMD PIC 9(8). 001800 05 CD-HMSD PIC 9(8). 001900 05 CD-GMT-OFF PIC S9(4) SIGN LEADING SEPARATE. 002000 05 FILLER REDEFINES CD-GMT-OFF. 002100 10 CD-GMT-OFF-SIGN PIC X. 002200 10 CD-GMT-OFF-HM PIC 9(4). 002300 002400 01 CD-MDCY PIC 9(8). 002500 01 CD-FORMATTED-MDCY PIC Z9/99/9999. 002600 01 CD-FORMATTED-HMSD PIC Z9/99/99/99. 002700 01 CD-FORMATTED-GMT-OFF PIC 99/99. 002800 002900 01 DUMMY PIC X. 003000 003100 PROCEDURE DIVISION. 003200 MAIN-LOGIC SECTION. 003300 PROGRAM-BEGIN. 003400 003500 PERFORM OPENING-PROCEDURE. 003600 PERFORM MAIN-PROCESS. 003700 PERFORM CLOSING-PROCEDURE. 003800 003900 EXIT-PROGRAM. 004000 EXIT PROGRAM. 004100 STOP-RUN. 004200 STOP RUN. 004300 004400 004500 THE-OTHER SECTION. 004600 004700 OPENING-PROCEDURE. 004800 CLOSING-PROCEDURE. 004900 MAIN-PROCESS. 005000 005100 MOVE FUNCTION CURRENT-DATE TO CD-DATE. 005200 005300 DISPLAY CD-DATE. 005400 COMPUTE CD-MDCY = CD-CYMD * 10000.0001. 005500 MOVE CD-MDCY TO CD-FORMATTED-MDCY. 005600 MOVE CD-HMSD TO CD-FORMATTED-HMSD. 005700 INSPECT CD-FORMATTED-HMSD REPLACING ALL `/' BY `:'. 005800 MOVE CD-GMT-OFF-HM TO CD-FORMATTED-GMT-OFF. 005900 INSPECT CD-FORMATTED-GMT-OFF REPLACING ALL `/' BY `:'. 006000 DISPLAY "DATE = " CD-FORMATTED-MDCY. 006100 DISPLAY "TIME = " CD-FORMATTED-HMSD. 006200 DISPLAY "GMT OFFSET = " CD-GMT-OFF-SIGN CD-FORMATTED-GMT-OFF. 006300 ACCEPT DUMMY. 006400
The following output was created by running CURDAT.CBL three times in a row. You will see the time portion of the displayed data change each time you run the program, because the system time has moved forward each time.
OUTPUT:
Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright(C) 1983-1993 Micro Focus Ltd. 199701052258001100000 DATE = 1/05/1997 TIME = 22:58:00:11 GMT OFFSET = 000:00 C:\pcobol\DATE8\intrnsic>pcobrun curdat Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. 199701052258210400000 DATE = 1/05/1997 TIME = 22:58:21:04 GMT OFFSET = 000:00 C:\pcobol\DATE8\intrnsic>pcobrun curdat Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. 199701052258572300000 DATE = 1/05/1997 TIME = 22:58:57:23 GMT OFFSET = 000:00
ANALYSIS: The key syntax for using CURRENT-DATE is on line 005100:
005100 MOVE FUNCTION CURRENT-DATE TO CD-DATE.
As I mentioned earlier, an intrinsic function behaves as if it were a data item. It doesn't have to be defined in WORKING-STORAGE--it is there already. In order for the compiler to recognize that it is dealing with a function as a pseudo-data item rather than a real data item, the keyword FUNCTION appears before the function name.
The destination of the MOVE, CD-DATE, is a real data item and is defined in WORKING-STORAGE on lines 001500 through 002200. The execution of the statement on line 005100 causes the program to create a temporary variable of a PIC X(21) size. This variable is filled with eight digits of current date, eight digits of current time, and a sign plus four digits of GMT offset information. The resulting 21 bytes are moved to CD-DATE, just as if CURRENT-DATE had already existed in WORKING-STORAGE and had been filled in somewhere else in the program.
The remainder of the program displays CD-DATE as it was received from CURRENT-DATE and then formats and displays the parts of CD-DATE.
Some intrinsic functions act on data that is passed to the function. Data passed to a function is similar to arguments passed in linkage to called programs (as covered in Bonus Day 2).
Listing B5.2, UPPER.CBL, illustrates the use of the UPPER-CASE intrinsic function. This function requires an alphabetic or alphanumeric argument, and it will convert the argument to uppercase. You coded an uppercase conversion program, UPPER01.CBL, on Day 15, "Data Integrity," but you will see that the intrinsic function makes the case conversion problem easier to solve.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. UPPER. 000300 AUTHOR. MO BUDLONG. 000400 INSTALLATION. 000500 DATE-WRITTEN. 09/07/96. 000600 DATE-COMPILED. 000700 SECURITY. NONE 000800 ENVIRONMENT DIVISION. 000900 INPUT-OUTPUT SECTION. 001000 FILE-CONTROL. 001100 DATA DIVISION. 001200 FILE SECTION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 ALPHA-FIELD PIC X(20). 001600 001700 01 DUMMY PIC X. 001800 001900 PROCEDURE DIVISION. 002000 MAIN-LOGIC SECTION. 002100 PROGRAM-BEGIN. 002200 002300 PERFORM OPENING-PROCEDURE. 002400 PERFORM MAIN-PROCESS. 002500 PERFORM CLOSING-PROCEDURE. 002600 002700 EXIT-PROGRAM. 002800 EXIT PROGRAM. 002900 STOP-RUN. 003000 STOP RUN. 003100 003200 003300 THE-OTHER SECTION. 003400 003500 OPENING-PROCEDURE. 003600 CLOSING-PROCEDURE. 003700 MAIN-PROCESS. 003800 003900 MOVE FUNCTION UPPER-CASE("goodbye") TO ALPHA-FIELD. 004000 004100 DISPLAY ALPHA-FIELD. 004200 004300 MOVE "hello" TO ALPHA-FIELD. 004400 004500 DISPLAY FUNCTION UPPER-CASE(ALPHA-FIELD). 004600 004700 ACCEPT DUMMY. 004800
OUTPUT:
C:\pcobol\DATE8\intrnsic>pcobrun upper Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. GOODBYE HELLO
ANALYSIS: UPPER.CBL provides two separate examples of using the UPPER-CASE function. In the first, UPPER-CASE("goodbye") is used as the source of a MOVE statement, and the result is moved to ALPHA-FIELD and then displayed on lines 003900 through 004100.
In this example, the running program creates a temporary variable, calls the subroutine UPPER-CASE, and passes it "goodbye". The result of converting it to uppercase is moved to the temporary variable. The temporary variable is then moved to ALPHA-FIELD.
UPPER-CASE(constant or data-item) acts like a data item, so it should be possible to directly display the result of an UPPER-CASE function call. Lines 004300 through 004500 illustrate this by moving a value to ALPHA-FIELD and then using DISPLAY UPPER-CASE(ALPHA-FIELD) to place the information onscreen.
In this use of UPPER-CASE, a temporary variable is created, and then the uppercase subroutine is called and passed the contents of ALPHA-FIELD. The result is moved to the temporary variable. The temporary variable is then displayed as if it had always existed in WORKING-STORAGE.
FUNCTION UPPER-CASE("goodbye") acts as if it were a single PIC X item containing the uppercase version of "goodbye", just as FUNCTION UPPER-CASE(ALPHA-FIELD) acts as if it were a single PIC X item containing the uppercase version of whatever is in ALPHA-FIELD. In either case, you can move from it or display it.
Because an intrinsic function is actually a call to a subroutine that acts like a data item, you can't use an intrinsic function as the destination of a MOVE or in any command that attempts to use it as a destination type data item. An intrinsic function acts like a constant or a read-only value.
The following statements are illegal because the intrinsic function is being used as the destination of a MOVE or STRING:
MOVE "199701011236174800000" TO FUNCTION CURRENT-DATE. STRING "199701011236174800000" DELIMITED BY SIZE INTO FUNCTION CURRENT-DATE.
An intrinsic function doesn't actually modify the data item arguments that it operates on. Instead, it creates a temporary variable and acts on that. In the following example, after the two statements are executed, ALPHA-FIELD still contains the lowercase "hello", while OTHER-FIELD now contains "HELLO". The call to FUNCTION UPPER-CASE(ALPHA-FIELD) doesn't modify the contents of ALPHA-FIELD:
MOVE "hello" TO ALPHA-FIELD. MOVE FUNCTION UPPER-CASE(ALPHA-FIELD) TO OTHER-FIELD.
The complementary intrinsic function FUNCTION LOWER-CASE (argument) creates a lowercase version of its argument. There is also an intrinsic function, REVERSE, that reverses its argument:
MOVE FUNCTION REVERSE("hello") TO BACK-WARDS.
In this example, REVERSE will produce the value olleh in BACK-WARDS.
Listing B5.3, STRNG.CBL, illustrates the three string-handling functions: FUNCTION UPPER-CASE(argument), FUNCTION LOWER-CASE (argument), and FUNCTION REVERSE(argument). It also highlights some additional actions you can take with an intrinsic, such as using an intrinsic as the source of a STRING command.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. STRNG. 000300 AUTHOR. MO BUDLONG. 000400 INSTALLATION. 000500 DATE-WRITTEN. 09/07/96. 000600 DATE-COMPILED. 000700 SECURITY. NONE 000800 ENVIRONMENT DIVISION. 000900 INPUT-OUTPUT SECTION. 001000 FILE-CONTROL. 001100 DATA DIVISION. 001200 FILE SECTION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 ALPHA-FIELD PIC X(26). 001600 01 SECOND-FIELD PIC X(26). 001700 001800 01 DUMMY PIC X. 001900 002000 PROCEDURE DIVISION. 002100 MAIN-LOGIC SECTION. 002200 PROGRAM-BEGIN. 002300 002400 PERFORM OPENING-PROCEDURE. 002500 PERFORM MAIN-PROCESS. 002600 PERFORM CLOSING-PROCEDURE. 002700 002800 EXIT-PROGRAM. 002900 EXIT PROGRAM. 003000 STOP-RUN. 003100 STOP RUN. 003200 003300 003400 THE-OTHER SECTION. 003500 003600 OPENING-PROCEDURE. 003700 CLOSING-PROCEDURE. 003800 MAIN-PROCESS. 003900 004000 MOVE FUNCTION UPPER-CASE("goodbye") TO ALPHA-FIELD. 004100 004200 DISPLAY ALPHA-FIELD. 004300 004400 MOVE FUNCTION LOWER-CASE(ALPHA-FIELD) TO SECOND-FIELD. 004500 004600 DISPLAY "ALPHA = " ALPHA-FIELD. 004700 DISPLAY "SECOND = " SECOND-FIELD. 004800 004900 MOVE "abcdefghijklmnopqrstuvwxyz" TO ALPHA-FIELD. 005000 005100 STRING 005200 FUNCTION UPPER-CASE( "hello") DELIMITED BY SIZE 005300 INTO ALPHA-FIELD. 005400 005500 DISPLAY FUNCTION REVERSE(ALPHA-FIELD). 005600 005700 ACCEPT DUMMY. 005800
OUTPUT:
C:\pcobol\DATE8\intrnsic>pcobrun strng Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. GOODBYE ALPHA = GOODBYE SECOND = goodbye zyxwvutsrqponmlkjihgfOLLEH
ANALYSIS: On lines 004000 and 004200, goodbye is converted to uppercase, stored in ALPHA-FIELD, and then displayed. On line 004400, ALPHA-FIELD is converted to lowercase and stored in SECOND-FIELD, and then, on lines 004600 and 004700, ALPHA-FIELD and SECOND-FIELD are displayed.
On line 004900, a new value is moved to ALPHA-FIELD that contains the letters of the alphabet. On lines 005100 through 005300, the STRING verb moves an uppercase version of hello into the same field.
Remember that the STRING verb won't clear out the rest of ALPHA-FIELD, which would have happened if a MOVE verb had been used. Instead, the uppercase letters HELLO are moved over the first five positions of the contents of ALPHA-FIELD.
Finally, on line 005500, a reversed version of ALPHA-FIELD is displayed.
An intrinsic function acts like a data item. Data items can be numeric or alphanumeric, so there must be some intrinsic functions that can act like numbers. There are several, including intrinsic functions that act on dates. For the moment, we will look at a simple intrinsic function that doesn't involve dates so that you can get a feel for them.
Listing B5.4, REMEX.CBL, illustrates the REM function. REM returns the remainder of a division between two numbers. The REM function behaves as a numeric data item, but in the Micro Focus personal COBOL compiler, a numeric function can't be used as the source of a MOVE. Other compilers also have this limitation. The best way to use a numeric function is in a COMPUTE statement, as shown in Listing B5.4.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. REMEX. 000300 AUTHOR. MO BUDLONG. 000400 INSTALLATION. 000500 DATE-WRITTEN. 09/07/96. 000600 DATE-COMPILED. 000700 SECURITY. NONE 000800 ENVIRONMENT DIVISION. 000900 INPUT-OUTPUT SECTION. 001000 FILE-CONTROL. 001100 DATA DIVISION. 001200 FILE SECTION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 NUMERIC-1 PIC 9(9). 001600 01 NUMERIC-2 PIC 9(9). 001700 01 NUMERIC-3 PIC 9(9). 001800 001900 01 DUMMY PIC X. 002000 002100 PROCEDURE DIVISION. 002200 MAIN-LOGIC SECTION. 002300 PROGRAM-BEGIN. 002400 002500 PERFORM OPENING-PROCEDURE. 002600 PERFORM MAIN-PROCESS. 002700 PERFORM CLOSING-PROCEDURE. 002800 002900 EXIT-PROGRAM. 003000 EXIT PROGRAM. 003100 STOP-RUN. 003200 STOP RUN. 003300 003400 003500 THE-OTHER SECTION. 003600 003700 OPENING-PROCEDURE. 003800 CLOSING-PROCEDURE. 003900 MAIN-PROCESS. 004000 MOVE 1 TO NUMERIC-1, NUMERIC-2. 004100 PERFORM ENTER-PARAMETERS. 004200 PERFORM TEST-REM UNTIL 004300 NUMERIC-1 = 0 004400 OR NUMERIC-2 = 0. 004500 004600 ENTER-PARAMETERS. 004700 DISPLAY "ENTER LARGER NUMBER (0 TO QUIT)". 004800 ACCEPT NUMERIC-1. 004900 005000 IF NUMERIC-1 NOT = 0 005100 DISPLAY "ENTER SMALLER NUMBER (0 TO QUIT)" 005200 ACCEPT NUMERIC-2. 005300 005400 TEST-REM. 005500 COMPUTE NUMERIC-3 = 005600 FUNCTION REM (NUMERIC-1, NUMERIC-2). 005700 005800 DISPLAY "REMAINDER OF " NUMERIC-1 "/" NUMERIC-2 " IS ". 005900 DISPLAY NUMERIC-3. 006000 DISPLAY "PRESS ENTER TO CONTINUE . . . " 006100 ACCEPT DUMMY. 006200 006300 PERFORM ENTER-PARAMETERS. 006400
The output illustrates several remainder calculations.
OUTPUT:
C:\pcobol\DATE8\intrnsic>pcobrun remex Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. ENTER LARGER NUMBER (0 TO QUIT) 23 ENTER SMALLER NUMBER (0 TO QUIT) 7 REMAINDER OF 000000023/000000007 IS 000000002 PRESS ENTER TO CONTINUE . . . ENTER LARGER NUMBER (0 TO QUIT) 4266 ENTER SMALLER NUMER (0 TO QUIT) 11 REMAINDER OF 000004266/000000011 IS 000000009 PRESS ENTER TO CONTINUE . . . ENTER LARGER NUMBER (0 TO QUIT) 0 C:\pcobol\DATE8\intrnsic>
On lines 004600 through 005300, a larger number and a smaller number are accepted as input. TEST-REM, on lines 005400 through 006400, displays the remainder of dividing the larger number by the smaller. MAIN-PROCESS, on lines 003900 through 004500, creates a loop that repeats until the user enters 0.
Today you learned about intrinsic functions, why they were introduced in the COBOL 85 standard, and how to use several of them in your programs. You explored the following:
What does the following call to REM return as a value that is stored in RESULT?
COMPUTE RESULT = REM(15, 4).
Review the date routines in Day 19, "Complex Data Entry Problems," and work out a way to use the REM function to check for leap years.
© Copyright, Macmillan Computer Publishing. All rights reserved.