0% found this document useful (0 votes)
30 views45 pages

Int Function

int fuction

Uploaded by

Mayank Singh
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PPTX, PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
30 views45 pages

Int Function

int fuction

Uploaded by

Mayank Singh
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PPTX, PDF, TXT or read online on Scribd
You are on page 1/ 45

Intrinsic Functions

• Intrinsic functions allow you to access certain values that are


derived at run time.

• Coded as part of statements in the Procedure Division

• FUNCTION is now a reserved word

• Instrinsic Functions may not be used as a receiving operand

• Usage-Example
– Move FUNCTION CURRENT-DATE to CURR-DT
– If FUNCTION DATE-OF-INTEGER(base-date)
– When FUNCTIO DAY-OF-INTEGER(base-date)

• Examples
– Current-date, Length, Lower-case, Date-of-integer
Intrinsic Functions
• DATE
– 77 X1 PIC 9(6) VALUE 0.
– ACCEPT X1 FROM DATE
– DISPLAY X1
– DATE will be YYMMDD ie PIC 9(6) format

• TIME
– ACCEPT X1 FROM TIME
– TIME will be HHMMSSCC ie PIC 9(8) format

• DAY
– ACCEPT X1 FROM DAY
– X1 PIC 9(3) ie 1-365 format

• DAY-OF-WEEK
– ACCEPT X1 FROM DAY-OF-WEEK
– Value ranges from 1 to 7
Intrinsic Functions
• Date Format : Range: January 1, 1601 to December 31, 9999

• Gregorian Date -YYYYMMDD

• Julian Date –YYYYDDD

• Notes:
– Before we examine date type intrinsic functions, we need to define three basic
date formats that COBOL can work with

– A. Gregorian date, or Standard date


• An eight digit date of the form YYYYMMDD,

• In the range of January 1, 1601 through December31,9999

• With MM being from 01 through 12 and DD being from 01 through 31 ,


dependent upon the month
Intrinsic Functions
• CURRENT-DATE
– Returns 21 characters
– MOVE FUNCTION CURRENT-DATE (1:8) TO Y
– YYYYMMDDHHmmsshhShhmm
• HHmmsshhShhmm Currenttimeinhours(24hourclock), minutes, seconds, and
hundredths of a second (HHmmsshh)

• INTEGER-OF-DATE
– COMPUTE integer-date = FUNCTION INTEGER-OF-DATE (20210218)
– Gregorian-Date must be in the form of YYYYMMDD.
– The function result is a 7 digit integer
– Year must be 1600 < YYYY < 9999 & 0 < MM < 13 & 0 < DD < 32

• DATE-OF-INTEGER
– COMPUTE Gregorian-Date = FUNCTION DATE-OF-INTEGER (Integer-Value)
– The function results Gregorian-date of 8 digit integer in the form of
YYYYMMDD
Intrinsic Functions
• INTEGER-OF-DAY
– COMPUTE Integer-Date = FUNCTION INTEGER-OF-DAY
(2021049)
– Julian Date must be in form of YYYYDDD
– The function result 7 digit Integer
– Year must be 1600 < YYYY < 9999 and 0 < DDD < 367

• DAY-OF-INTEGER
– COMPUTE Julian-Date = FUNCTION DAY-OF-
INTEGER(Integer-Date)
– Julian Date is in form of YYYYDDD and 7 digit Integer
– Integer-Date represents a number of days after December 31,
1600 in Gregorian calendar.
Intrinsic Functions
• LENGTH
– MOVE IN-EMPREC (1: FUNCTION LENGTH (ABC)) TO PQR.
– COMPUTE PQR = FUNCTION LENGTH(ABC)
• Returns the length of 77 ABC PIC X(10) , the declaration size.
• MOVE FUNCTION LENGTH(ABC) not allowed.

• LOWER-CASE
– MOVE FUNCTION LOWER-CASE (ANSWER) TO Y.

• UPPER-CASE
– MOVE FUNCTION UPPER-CASE (ANSWER) TO Y.

• NESTING FUNCTION
– COMPUTE NEW-DUE-DATE = FUNCTION DATE-OF-
INTEGER(FUNCTION INTEGER-OF-DATE(DATE-OF-ORDER
+ 30))
Intrinsic Functions
• REM – Returns remainder for the input non-integer value.
– COMPUTE X = FUNCTION REM (D, E)

• MOD
– Returns the remainder for the input integer value
• COMPUTE X = FUNCTION MOD (D, E)

• SQRT – SQRT of a numeric item


– COMPUTE X = FUNCTION SQRT (D)

• SUM – SUM of list items, all items are of numeric or integer


– COMPUTE X = FUNCTION SUM (D, E, F)
Intrinsic Functions
• MAX
– Largest value in the list of values
– COMPUTE X = FUNCTION MAX (D, E, F)

• MIN
– Lowest value in the list of values
– COMPUTE X = FUNCTION MIN (D, E, F)

• FACTORIAL
– COMPUTE X = FUNCTION FACTORIAL (D)

• REVERSE
– MOVE FUNCTION REVERSE(Y) TO Q
STRING HANDLING
Introduction to String handling
• Programs often require that data be moved from one area to
another and / or that operations be performed on the individual
characters of a data set.
• 77 ABC PIC X(20) VALUE ‘COFORGE’.
• 77 PQR PIC X(10) VALUE ‘TECHNOLOGIES’.

• String handling operation includes


– Scanning and replacement – INSPECT verb
– Concatenation – STRING verb
– Segmentation - UNSTRING verb

• Introduction to String handling


– INSPECT verb
– STRING verb
– UNSTRING verb
INSPECT VERB
Points on INSPECT verb
• Allows group of characters to be counted in a user-
defined data name and replaced

• Permits several tallies and replacements with one


statement

• Used only with alphanumeric data item


Format 1 – Syntax

INSPECT identifier-1 TALLYING identifier-2

ALL identifier-3
FOR LEADING literal-1
CHARACTERS

BEFORE identifier-4
INITIAL
AFTER literal-2
• LEADING
– COUNTS/REPLACE all compare $1 character from the first
valid one encountered to the first invalid one.

• FIRST
– REPLACES only the first valid characters.

• BEFORE
– Designates characters to the left of delimiter as valid

• AFTER
– Designates character to the right of delimiters as valid
Example

77 ID-1 PIC X(15) VALUE ‘FFFBCGHIFFFJKL’.


77 ID-2 PIC 99 VALUE 0.
77 ID-3 PIC 99 VALUE 0.
77 ID-4 PIC 99 VALUE 0
• INSPECT ID-1 TALLYING ID-2 FOR ALL “F”.
– ID-2 value is 6.

• INSPECT ID-1 TALLYING ID-3 FOR LEADING “F”.


– ID-3 value is 3.

• INSPECT ID-1 TALLYING ID-4 FOR ALL “F” BEFORE INITIAL “G’.
– ID-4 value is 3
Example contd

77 ID-1 PIC X(15) VALUE ‘FFFBCGHIFFFJKLF’.


77 ID-5 PIC 99 VALUE 0.
77 ID-6 PIC 99 VALUE 0.

• INSPECT ID-1 TALLYING ID-5 FOR CHARACTERS


• ID-5 value is 15.

• INSPECT ID-1 TALLYING ID-5 FOR CHARACTERS BEFORE


INITIAL “I”.
– ID-5 value is 7.

• INSPECT ID-1 TALLYING ID-6 FOR CHARACTERS AFTER


INITIAL “I”.
– ID-5 value is 7 .
Format 2 - Syntax
INSPECT identifier-1 REPLACING

CHARACTERS BY {id-2/lit-1}

BEFORE INITIAL {id-6/lit-5}


AFTER

ALL
LEADING {id-4/lit-3} BY {id-5/lit-4}
FIRST
BEFORE INITIAL {id-6/lit-5}
AFTER
Example

77 ID-1 PIC X(15) VALUE ‘FFFBCGHIFFFJKL’.

• INSPECT ID-1 REPLACING CHARACTERS BY “*” AFTER INITIAL


“I”.
– ID-1 value is FFFBCGHI*******

• INSPECT ID-1 REPLACING CHARACTERS BY “$” BEFORE INITIAL


“B”.
– ID-1 value is $$$BCGHIFFFJKL

• INSPECT ID-1 REPLACING ALL “F” BY “&”.


– ID-1 value is &&&BCGHI&&&JKL
Example contd

77 ID-1 PIC X(15) VALUE ‘AFFFBCGHIFFFJKL’.

• INSPECT ID-1 REPLACING FIRST “FFF” BY “$$$”.


– ID-1 value is A$$$BCGHIFFFJKL

• INSPECT ID-1 REPLACING LEADING “A” BY “&”.


– ID-1 value is &FFFBCGHIFFFJKL
Format 3 – Syntax & Example

• Syntax
INSPECT identifier-1 TALLYING
<tallying part as in format 1>
REPLACING
<replacing part as in format 2>.
• Example
– 77 ID-1 PIC X(15) VALUE 'FFFBCGHIFFFJKL'.
– 77 ID-2 PIC 99 VALUE 0.
– INSPECT ID-1
TALLYING ID-2 FOR CHARACTERS BEFORE INITIAL “I”
REPLACING CHARACTERS BY “*” AFTER INITIAL “I”.
• ID-1 value is FFFBCGHI*******
• ID-2 value is 07
Format 4 – Syntax & Example
• INSPECT <identifier1> CONVERTING <identifier2/literal1> TO
<identifier3/literal2>
BEFORE/AFTER INTIAL < identifier4/literal-3>

Example

• 77 ID-1 PIC X(15) VALUE 'ABCDEFAB'.

• INSPECT ID-1 CONVERTING 'ABC' TO 'SER'.


– ID-1 value is SERDEFSE( value changes character wise)
STRING VERB
Purpose of STRING verb
• Two or more strings of characters can be combined

• To transfer characters from a string to another string


starting at some particular character position either in the
receiving field or in the sending field
Syntax - STRING verb
STRING {id-1 / lit-1} , {id-2 / lit-2},….
DELIMITED BY {id-3 / lit-3/SIZE}

{id-4 / lit-4} , {id-5 / lit-5},….


DELIMITED BY {id-6 / lit-6/SIZE}

INTO {id-7} [ WITH POINTER id-8 ]

[ ON OVERFLOW imperative-statement ]
STRING
Ident1 DELIMITED BY SIZE
Ident2 DELIMITED BY SPACES
Ident3 DELIMITED BY "Frogs"
INTO Ident4
WITH POINTER StrPtr
END-STRING.
STRING verb
• DELIMITED BY SIZE
The DELIMITED BY SIZE clause means that the whole of the
sending field will be added to the destination string.

• ON OVERFLOW
If the ON OVERFLOW clause is used then the statement
following it will be executed if there are still characters left to
pass across in the source field(s) but the destination field has
been filled.

• WITH POINTER
The WITH POINTER phrase allows an identifier/dataname to be
kept which holds the position in the Destination String where the
next character will go.
• When the WITH POINTER phrase is used, the program must set
the pointer to an initial value greater than 0 and less than the
length of the destination string before the STRING statement
executes.
• If the WITH POINTER phrase is not used, operation on the
destination field starts from the leftmost position.
Example 1

01 name-in.
05 first-name pic x(10) value 'Mahender '
05 Last name pic x(10) value 'Reddy '
05 initial pic x(2) value 'G ‘
01 NAME-OUT PIC X(25) VALUES SPACES.

STRING
FIRST-NAME DELIMITED BY SPACE
LAST-NAME DELIMITED BY SPACE
INITIAL INTO NAME-OUT.

Now NAME-OUT would be ‘mahenderreddyg ‘.


Example 2
01 StringFields.
02 Field1 PIC X(18) VALUE "Where does this go".
02 Field2 PIC X(30)
VALUE "This is the destination string".
02 Field3 PIC X(15) VALUE "Here is another".

STRING Field1 DELIMITED BY SPACES INTO Field2.


DISPLAY Field2.

Displays WHEREIS THE DESTINATION STRING


Example 3
01 StringFields.
02 Field1 PIC X(18) VALUE "Where does this go".
02 Field2 PIC X(30)
VALUE "This is the destination string".
02 Field3 PIC X(15) VALUE "Here is another".

STRING Field1 DELIMITED BY SIZE INTO Field2.


DISPLAY Field2.

 Displays WHERE DOES THIS GOATION STRING


Example 4
01 StringFields.
02 Field1 PIC X(18) VALUE "Where does this go".
02 Field2 PIC X(30)
VALUE "This is the destination string".
02 Field3 PIC X(15) VALUE "Here is another".
01 StrPtr PIC 99.

MOVE 6 TO StrPtr.

STRING Field1, Field3 DELIMITED BY SPACE


INTO Field2 WITH POINTER StrPtr
ON OVERFLOW DISPLAY "String Error“.

 Displays THIS WHEREHERESTINATION STRING


Example 5

01 StringFields.
02 Field1 PIC X(18) VALUE "Where does this go".
02 Field2 PIC X(30)
VALUE "This is the destination string".
02 Field3 PIC X(15) VALUE "Here is another".
02 Field4 PIC X(20) VALUE SPACES.

STRING Field1, Field2, Field3 DELIMITED BY SPACES


INTO Field4.

DISPLAY Field4
 Displays WHERETHISHERE
Example 6

01 DayStr PIC XX. 5


01 MonthStr PIC X(9). J U N E
01 YearStr PIC X(4). 1 9 9 4
01 DateStr PIC X(15) VALUE ALL "-".
- - - - - - - - - - - - - - -

STRING DayStr DELIMITED BY SPACES


", " DELIMITED BY SIZE
MonthStr DELIMITED BY SPACES
", " DELIMITED BY SIZE
YearStr DELIMITED BY SIZE
INTO DateStr
DISPLAY DateStr.  Displays 5, JUNE, 1994--
UNSTRING VERB
Purpose of UNSTRING verb
• Used to split one string to many substrings.

• As like STRING verb, based on the delimiter specified, the


splitting occurs
Syntax - UNSTRING verb

UNSTRING id-1

DELIMITED BY [ALL] {id-2/lit-1}, OR [ALL] {id-3/lit-2}

INTO id-4 [ , DELIMITER IN id-5 ]


[ , COUNT IN id-6 ]
[ id-7 [ , DELIMITER IN id-8 ]
[ , COUNT IN id-9 ]
[ WITH POINTER id-10 ]
[ TALLYING IN id-11 ] [; ON OVERFLOW imperative-stmt]
Example 1
01 WHOLE-NAME PIC X(25).
01 FIRST-NAME PIC X(25).
01 MIDDLE-NAME PIC X(25).
01 LAST-NAME PIC X(25).

PROCEDURE DIVISION.
MAIN-STREET.
MOVE 'ROGERS WILLIAM THOMAS' TO WHOLE-NAME.
UNSTRING WHOLE-NAME
DELIMITED BY SPACE
INTO LAST-NAME FIRST-NAME MIDDLE-NAME.
DISPLAY 'FIRST NAME: ' FIRST-NAME.
DISPLAY 'MIDDLE NAME: ' MIDDLE-NAME.
DISPLAY 'LAST NAME: ' LAST-NAME.
 Displays FIRST NAME: WILLIAM
MIDDLE NAME: THOMAS
LAST NAME: ROGERS
Example 1 A

• Multiple Delimiters

UNSTRING INREC
DELIMITED BY ',' OR SPACE
INTO A1, B1, C1.

DISPLAY A1 SPACE B1 SPACE C1.


Example 2
WORKING-STORAGE SECTION.
01 WW-U4-INPUT PIC X(12) VALUE 'AAA B CCCC '.
01 WW-UNSTRING.
05 WW-U1 PIC XXXX VALUE SPACES.
05 WW-U2 PIC XXXX VALUE SPACES.
05 WW-U3 PIC XXXXXX VALUE SPACES.
05 WW-CH-1 PIC 99.
05 WW-CH-2 PIC 99.
05 WW-CH-3 PIC 99.
PROCEDURE DIVISION.
UNSTRING WW-U4-INPUT DELIMITED BY SPACE
INTO WW-U1 COUNT IN WW-CH-1, WW-U2 COUNT IN WW-CH-2,
WW-U3 COUNT IN WW-CH-3
END-UNSTRING.
DISPLAY 'WW-U1 --' WW-U1 OUTPUT WILL BE
DISPLAY 'WW-U2 --' WW-U2 WW-U1 -- AAA
DISPLAY 'WW-U3 --' WW-U3 WW-U2 -- B
DISPLAY 'WW-CH-1--' WW-CH-1 WW-U3 -- CCCC
DISPLAY 'WW-CH-2--' WW-CH-2
WW-CH-1-- 03
WW-CH-2-- 01
DISPLAY 'WW-CH-3--' WW-CH-3. WW-CH-3— 04
Example 3
• Delimiter is spaces and given only Two receiving fields

77 WW-U4-INPUT PIC X(12) VALUE 'AA BBB C'.


77 WW-U1 PIC X(2) VALUE SPACES.
77 WW-U2 PIC X(6) VALUE SPACES.
PROCEDURE DIVISION.
UNSTRING WW-U4-INPUT DELIMITED BY SPACE
INTO WW-U1, WW-U2
DISPLAY WW-U1, SPACE, WW-U2 .

Result will be - AA BBB


Example 4
• If More than one delimiter is present in between two strings, then ALL
should be used.

01 WW-U4-INPUT PIC X(12) VALUE ‘AA BB CC ‘.


* there are 2 spaces in between BB and CC

UNSTRING WW-U4-INPUT DELIMITED BY ALL SPACE


INTO WW-U1 COUNT IN WW-CH-1,
WW-U2 COUNT IN WW-CH-2, For the same ABOVE INPUT
VALUE, if we change the Unstring
WW-U3 COUNT IN WW-CH-3. value with ‘DELIMITED BY ALL
Result: without ALL SPACES Instead of ‘delimited by
SPACE.
WW-U1 --AA
Result: with ALL
WW-U2 --BB
WW-U3 -- WW-U1 --AA
WW-U2 --BB
WW-CH-1--02 WW-U3 --CC
WW-CH-1--02
WW-CH-2--02 WW-CH-2--02
WW-CH-3--00 WW-CH-3—02
Example 5
01 WW-U4-INPUT PIC X(12) VALUE ' ,BBB, CC, '.

UNSTRING WW-U4-INPUT DELIMITED BY ','


INTO WW-U1 COUNT IN WW-CH-1,
WW-U2 COUNT IN WW-CH-2,
WW-U3 COUNT IN WW-CH-3
END-UNSTRING

Result:
WW-U1 --
WW-U2 --BBB
WW-U3 -- CC
WW-CH-1--02
WW-CH-2--03
WW-CH-3--03
Note – Count takes Spaces also into consideration.
Example 6

01 DayStr PIC XX.


01 MonthStr PIC XX.
01 YearStr PIC XX.
01 DateStr PIC X(8).

1 9 -0 5 - 8 0
ACCEPT DateStr.
UNSTRING DateStr
INTO DayStr, MonthStr, YearStr
ON OVERFLOW DISPLAY “OVERFLOWING“.

 Displays OVERFLOWING
Example 7
• Multiple delimiters by Using OR in UNSTRING

01 WW-U4-INPUT PIC X(12) VALUE 'AA,BBB CC, '.

UNSTRING WW-U4-INPUT DELIMITED BY ',' OR SPACE


INTO WW-U1 COUNT IN WW-CH-1,
WW-U2 COUNT IN WW-CH-2,
WW-U3 COUNT IN WW-CH-3
END-UNSTRING.

Result:
WW-U1 --AA
WW-U2 --BBB
WW-U3 --CC
WW-CH-1--02
WW-CH-2--03
WW-CH-3--02
Example 8
01 DayStr PIC XX.
01 MonthStr PIC XX.
01 YearStr PIC XX.
01 DateStr PIC X(8). 1 9 - 0 5 / 8 0
01 HOLD1 PIC XX.
01 HOLD2 PIC XX.

ACCEPT DateStr.
UNSTRING DateStr
DELIMITED BY "/" OR "-"
INTO DayStr DELIMITER IN Hold1
MonthStr DELIMITER IN Hold2
YearStr.
DISPLAY DayStr SPACE MonthStr SPACE YearStr.
DISPLAY Hold1 SPACE Hold2
 Displays 19 05 80 and HOLD1 is - , HOLD2 is /
Example 9
• UNSTRING with Tallying Option
– It gives the count of number of receiving fields. If there are 4 fields in INTO
clause then the count would be 4.

UNSTRING WW-U4-INPUT DELIMITED BY SPACE


INTO WW-U1 COUNT IN WW-CH-1,
WW-U2 COUNT IN WW-CH-2,
WW-U3 COUNT IN WW-CH-3
WW-U4 COUNT IN WW-CH-4 TALLYING IN WW-TL-1

RESULT
• In this case WW-TL-1 contains a value of 4.

Note: TALLYING SHOULD BE CODED for the last receiving field.

You might also like