COBOL - MAINFRAMES - PART 4

SSRANGE AND NOSSRANGE
If you specify the SSRANGE compiler option, the VS COBOL II compiler generates additional code that makes certain a table subscript or index does not address an area outside the boundaries of the associated table. This compiler option also generates code to ensure that OCCURS DEPENDING ON values, which are set dynamically by VS COBOL II source code statements, do not go beyond the maximum boundaries initially defined for the associated variable-length table.
To invoke this option you need to code the parameter
COPT=SSRANGE
On the compile step of your job.
If you have compiled your program with the SSRANGE compiler option, subscript range checking will occur during program execution for all tables as they are referenced. If an "out of bounds" condition occurs, a diagnostic message is generated and the program is abnormally terminated. Subscript range checking occurs when a program is being executed because most table elements are referenced using computed subscripts or indexes rather than numeric literals.
The default VS COBOL II compiler option is NOSSRANGE.
If your program is compiled with the SSRANGE option you have the option to cancel the checking performed at execution time. This is accomplished by specifying the NOSSRANGE execution time option as follows:
//RUN EXEC PGM=MYPROG,PARM='/NOSSRANGE'
You can tell NOSSRANGE is a run-time option rather than a compiler option because of the slash.
It is recommended that you use the SSRANGE compiler option when you are testing programs. However because script range checking involves the execution of additional code, your program executes a little slower than it might. Therefore when programs are ready to be handed over for production running they should have the default compiler option of NOSSRANGE.
RELEASE STATEMENT
The release statement transfers records from the INPUT PROCEDURE to the input Phase of the sort operation
RETURN STATEMENT
The RETURN statement transfers records from the final phase of a sorting or merging operation to an OUTPUT PROCEDURE.
The RETURN statement can be used only within the range of an OUTPUT PROCEDURE associated with a SORT or MERGE statement
RETURN FILENAME-1RECORD INTO IDENTIFIER-1
AT END DISPLAY ‘IMPERATIVE STATEMENT-1’
NOT AT END DISPLAY ‘IMPERATIVE STATEMENT-2’
END-RETURN.
SORT AND MERGE
External sort is used to sort files by using the SORT utility in JCL. We have discussed this in the JCL chapter. As of now, we will focus on internal sort.
Internal sort is used to sort files with in a COBOL program. SORT verb is used to sort a file.


Three files are used in the Sort process in COBOL
Input file is the file which we have to sort either in ascending or descending order.
Work file is used to hold records while the sort process is in progress. Input file records are transferred to the work file for the sorting process. This file should be defined in the File-Section under SD entry.
Output file is the file which we get after sorting process. It is the final output of the Sort verb
SYNTAX
              SORT workfile ON ASCENDING KEY reckey1[ON DESCENDING KEY     reckey2]
USING inputfile GIVING outputfile.
SORT performs the following operations:
Opens work-file in the I-O mode, input-file in the INPUT mode and output-file in the OUTPUT mode.
Transfers the records present in the input-file to the work-file.
Sorts the SORT-FILE in ascending/descending sequence by rec-key.
Transfers the sorted records from the work-file to the output-file.
Closes the input-file and the output-file and deletes the work-file.
EX
IDENTIFICATION DIVISION.
PROGRAMID. HELLO.
ENVIRONMENT DIVISION.
INPUTOUTPUT SECTION.
FILECONTROL.
SELECT INPUT ASSIGN TO IN.
SELECT OUTPUT ASSIGN TO OUT.
SELECT WORK ASSIGN TO WRK.
DATA DIVISION.
FILE SECTION.
FD INPUT.
01INPUTSTUDENT.
05 STUDENTIDI PIC 9(5).
05 STUDENTNAMEI PIC A(25).
FD OUTPUT.
01 OUTPUTSTUDENT.
05 STUDENTIDO PIC 9(5).
05STUDENTNAMEO PIC A(25).
SD WORK.
01WORKSTUDENT.
05STUDENTIDW PIC 9(5).
05 STUDENTNAMEW PIC A(25).
PROCEDURE DIVISION.
SORT WORK ON ASCENDING KEY STUDENTIDO
USING INPUT GIVING OUTPUT.
DISPLAY 'Sort Successful'.
STOP RUN.
MergeVerb
Two or more identically sequenced files are combined using Merge statement. Files used in the merge process:
Input Files : Input-1, Input-2
Work File
Output File
SYNTAX
                MERGE workfile ON ASCENDING KEY reckey1[ON DESCENDING KEY reckey2]
    USING input1, input2 GIVING outputfile.
Merge performs the following operations:
Opens the work-file in the I-O mode, input-files in the INPUT mode and output-file in the OUTPUT mode.
Transfers the records present in the input-files to the work-file.
Sorts the SORT-FILE in ascending/descending sequence by rec-key.
Transfers the sorted records from the work-file to the output-file.
Closes the input-file and the output-file and deletes the work-file.
EX
IDENTIFICATION DIVISION.
PROGRAMID. HELLO.
ENVIRONMENT DIVISION.
INPUTOUTPUT SECTION.
FILECONTROL.
SELECT INPUT1 ASSIGN TO IN1.
SELECT INPUT2 ASSIGN TO IN2.
SELECT OUTPUT ASSIGN TO OUT.
SELECT WORK ASSIGN TO WRK.
DATA DIVISION.
FILE SECTION.
FD INPUT1.
01INPUT1STUDENT.
05 STUDENTIDI1 PIC 9(5).
05 STUDENTNAMEI1 PIC A(25).
FD INPUT2.
01INPUT2STUDENT.
05 STUDENTIDI2 PIC 9(5).
05 STUDENTNAMEI2 PIC A(25).
FD OUTPUT.
01 OUTPUTSTUDENT.
05 STUDENTIDO PIC 9(5).
05STUDENTNAMEO PIC A(25).
SD WORK.
01WORKSTUDENT.
05STUDENTIDW PIC 9(5).
05 STUDENTNAMEW PIC A(25).
PROCEDURE DIVISION.
MERGE WORK ON ASCENDING KEY STUDENTIDO
USING INPUT1, INPUT2 GIVING OUTPUT.
DISPLAY 'Merge Successful'.
STOP RUN.
EX.1 PROGRAM TO FIND WHETHER THE GIVEN NUMBER IS PALINDROME OR NOT.
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM56.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       77 N PIC 9(3) VALUE ZERO.
       77 REM PIC 9(3) VALUE ZERO.
       77 Q PIC 9 VALUE ZERO.
       77 REV PIC 9(3) VALUE ZERO.
       77 P PIC 9(3) VALUE ZERO.
       PROCEDURE DIVISION.
       MAIN-PARA.
               PERFORM ACCEPT-PARA.
               PERFORM PROCESS-PARA.
               PERFORM DISPLAY-PARA.
               STOP RUN.
       ACCEPT-PARA.
               DISPLAY 'ENTER N VALUE'.
               ACCEPT N.
               MOVE N TO P.
       PROCESS-PARA.
               PERFORM UNTIL N  <= 0
                   DIVIDE N BY 10 GIVING Q REMAINDER REM
                   COMPUTE REV = REV * 10 + REM
                   DIVIDE N BY 10 GIVING N
               END-PERFORM.
       DISPLAY-PARA.
               IF REV = P THEN
                   DISPLAY 'GIVEN NUMBER IS  PALINDROME  '
               ELSE
                   DISPLAY 'GIVEN NUMBER IS NOT PALINDROME'
               END-IF.


EX2. MATCHING LOGIC.
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM80.
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
                   SELECT OLD-MASTER ASSIGN TO DATA13O.
                   SELECT TRANS-FILE ASSIGN TO DATA13T.
                   SELECT NEW-MASTER ASSIGN TO DATA13N.
       DATA DIVISION.
       FILE SECTION.
       FD OLD-MASTER
                   LABEL RECORDS ARE STANDARD.
       01 OLD-MASTER-REC.
           05 M-ACCT-NO PIC X(5).
           05 AMOUNT-DUE  PIC 9(4)V99.
           05 FILLER PIC X(89).
       FD TRANS-FILE
                   LABEL RECORDS ARE STANDARD.
       01 TRANS-REC.
           05 T-ACCT-NO PIC X(5).
           05 AMT-TRANS-IN-CURRENT-PER PIC 9(4)V99.
           05 FILLER PIC X(89).
       FD NEW-MASTER
                   LABEL RECORDS ARE STANDARD.
       01 NEW-MASTER-REC.
           05 ACCT-NO-OUT PIC X(5).
           05 AMOUNT-DUE-OUT PIC 9(4)V99.
           05 FILLER PIC X(89).
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
       MAIN-MODULE.
               PERFORM INITIALIZATION-RTN.
               PERFORM READ-MASTER.
               PERFORM READ-TRANS.
               PERFORM COMP-RTN
                       UNTIL M-ACCT-NO = HIGH-VALUES
                               AND
                       T-ACCT-NO = HIGH-VALUES
               PERFORM END-OF-JOB-RTN.
               STOP RUN.
      COMP-RTN.
               EVALUATE TRUE
                   WHEN T-ACCT-NO = M-ACCT-NO
                       PERFORM REGULAR-UPDATE
                    WHEN T-ACCT-NO < M-ACCT-NO
                       PERFORM NEW-ACCOUNT
                    WHEN OTHER
                       PERFORM NO-UPDATE
               END-EVALUATE.
      REGULAR-UPDATE.
               MOVE OLD-MASTER-REC TO NEW-MASTER-REC
               COMPUTE AMOUNT-DUE-OUT = AMT-TRANS-IN-CURRENT-PER
                                        + AMOUNT-DUE
               WRITE NEW-MASTER-REC
               PERFORM READ-MASTER
               PERFORM READ-TRANS.
      NEW-ACCOUNT.
               MOVE SPACES TO NEW-MASTER-REC.
               MOVE T-ACCT-NO TO ACCT-NO-OUT.
               MOVE AMT-TRANS-IN-CURRENT-PER TO AMOUNT-DUE-OUT.
               WRITE NEW-MASTER-REC.
               PERFORM READ-TRANS.
      NO-UPDATE.
               WRITE NEW-MASTER-REC FROM OLD-MASTER-REC.
               PERFORM READ-MASTER.
      READ-MASTER.
               READ OLD-MASTER
                   AT END
                       MOVE HIGH-VALUES TO M-ACCT-NO
               END-READ.
      READ-TRANS.
               READ TRANS-FILE
                   AT END
                       MOVE HIGH-VALUES TO T-ACCT-NO
               END-READ.
      INITIALIZATION-RTN.
               OPEN INPUT OLD-MASTER
                      TRANS-FILE.
                OPEN OUTPUT NEW-MASTER.
      END-OF-JOB-RTN.
                  CLOSE OLD-MASTER
                        TRANS-FILE
                        NEW-MASTER.
EX3.Program to CALL SUBROUTINES 
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM104.
       *PROGRAM TO CALL SUBROUTINES
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
           CALL 'SUBPGM'.
           STOP RUN.
SUBPGM 
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPGM.
       *SUB PROGRAM
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
           DISPLAY 'HAI'.
           EXIT PROGRAM. 
EX4. Program to CALL SUBROUTINES AND PASSING VALUE BY REFERENCE 
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM105.
       *PROGRAM TO CALL SUBROUTINES AND PASSING VALUE BY     REFERENCE       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       77 A PIC 9 VALUE IS 3.
       77 B PIC 9 VALUE IS 6.
       PROCEDURE DIVISION.
           CALL 'SUBPGM1' USING A B.
           DISPLAY B.
           STOP RUN.
SUBPGM1
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPGM1.
       AUTHOR. Indus Computer Services.
       *SUB PROGRAM
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       LINKAGE SECTION.
       77 A PIC 9.
       77 B PIC 9.
       PROCEDURE DIVISION USING A B.
           ADD A TO B.
           EXIT PROGRAM.
 EX.5 Program to CALL SUBROUTINES AND PASSING VALUE BY VALUE
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM106.
       *PROGRAM TO CALL SUBROUTINES AND PASSING VALUE BY VALUE       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       77 A PIC 9 VALUE IS 3.
       77 B PIC 9 VALUE IS 6.
       PROCEDURE DIVISION.
           CALL 'SUBPGM1' USING BY CONTENT A B.
           DISPLAY B.
           STOP RUN.
SUBPGM1
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPGM1.
       *SUB PROGRAM       ENVIRONMENT DIVISION.
       DATA DIVISION.
       LINKAGE SECTION.
       77 A PIC 9.
       77 B PIC 9.
       PROCEDURE DIVISION USING A B.
           ADD A TO B.
           EXIT PROGRAM.
 EX6. Program to CALL SUBROUTINES DYNAMICALLY
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM107.
       *PROGRAM TO CALL SUBROUTINES DYNAMICALLY
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       77 SUBNAME PIC X(6) VALUE IS SPACES.
       PROCEDURE DIVISION.
           MOVE 'SUBPGM' TO SUBNAME.
           CALL SUBNAME
           STOP RUN.
SUBPGM
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPGM.
       *SUB PROGRAM
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
           DISPLAY 'HAI'.
           EXIT PROGRAM.
EX7. Program for DYNAMIC CALL 
       IDENTIFICATION DIVISION.
       PROGRAM-ID. Pgm108.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-REC.
           05 A PIC 99.
           05 B PIC 99.
           05 C PIC 9999.
       77 WS-REC-1 PIC X(6) VALUE 'PGM83A'.
       77 WS-REC-2 PIC X(6) VALUE 'PGM83B'.
       LINKAGE SECTION.
       PROCEDURE DIVISION.
       MAIN-PARA.
              ACCEPT A.
              ACCEPT B.
              CALL WS-REC-1 USING  BY REFERENCE A, B, C.
              DISPLAY  'C= ' C.
              CALL WS-REC-2 USING BY REFERENCE A, B,C.
              DISPLAY 'C= ' C.
              STOP RUN. 
Sub Program PGM83A
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM83A.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       LINKAGE SECTION.
       01 X PIC 99.
       01 Y PIC 99.
       01 Z PIC 9999.
       PROCEDURE DIVISION USING X, Y, Z.
               COMPUTE Z = X + Y.
               EXIT PROGRAM.
PGM83B 
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PGM83B.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       LINKAGE SECTION.
       01 X PIC 99.
       01 Y PIC 99.
       01 Z PIC 9999.
       PROCEDURE DIVISION USING X, Y, Z.
               COMPUTE Z = X * Y.
               EXIT PROGRAM.
DATE FUNCTIONS
1. CURRENTDATE is COBOL intrinsic function to get current date, time and difference. COBOL DATE Functions between current location time and Greenwich Mean Time.
                      MOVE FUNCTION CURRENTDATE TO WSCURRENTDATEDATA
                      This function returns a 20character alphanumeric field in the below format
                      01 WSCURRENTDATEDATA.
                      05 WSCURRENTDATE.
                             10 WSCURRENT-YEAR PIC 9(4).
                             10 WSCURRENT-MONTH PIC 9(2).
                             10 WSCURRENT-DAY PIC 9(2).
                      05 WSCURRENT-TIME.
                             10 WSCURRENT-HOURS PIC 9(2).
                             10 WSCURRENT-MINUTES PIC 9(2).
                             10 WSCURRENT-SECONDS PIC 9(2).
                             10 WSCURRENT-MILLISECONDS PIC 9(2).
                      05 WS-DIFF-FROM-GMT PIC S9(4).
WSCURRENTDATEDATA contains : 2010111917542857+0800
2. Other COBOL date intrinsic function.
a) Converting from Gregorian dates to integer date.
COMPUTE integerdate = FUNCTION INTEGEROFDATE (Gregorian date).
Gregoriandate must be in form YYYYMMDD. The function result is a 7digit integer
Note: 1600 < YYYY < 9999; 0 < MM < 13; 0 < DD < 32
(provided that day is valid for the specified month and year combination).
b)Convert from Integer to Gregorian formats.
COMPUTE Gregoriandate = FUNCTION DATEOFINTEGER (integerdate)
The function result Gregoriandate is an eightdigit integer in the form YYYYMMDD.
c)Convert from Julian to Integer formats
COMPUTE integerdate = FUNCTION INTEGEROFDAY (Juliandate)
Juliandate must be in the form YYYYDDD, The function result is a 7digit integer.
Note: 1600 < YYYY < 9999 and 0 < DDD < 367 (provided the day is valid for the specified year)
d) Convert from Integer to Julian formats
COMPUTE Juliandate = FUNCTION DAYOFINTEGER (integerdate)
The Juliandate is a sevendigit integer in the form YYYYDDD. Integerdate represents a number of days after December 31, 1600, in the Gregorian calendar.
All these functions deal with converting between Gregorian dates or Julian dates and integer format date. This integer format date is number of days from fixed date
Example : Converting Gregorian format date 20101202 to Julian format date.
COMPUTE integerdate = FUNCTION INTEGEROFDATE (Gregorian date).
This converts 20101202(Gregorian date) to 0149720(integer format date).
COMPUTE Juliandate = FUNCTION DAYOFINTEGER (integerdate).
This converts 0149720(integer format date) to 2010336(Julian format date YYYDD) using above date functions, one can get add or subtract days from current date. It is easy with these functions.
Example2: Calculate date after 10 days from Today.
MOVE FUNCTION CURRENTDATE TO WSCURRENTDATEDATA.
This move statement moves current timestamp (20bytes) to WSCURRENTDATEDATA. Since we need only current date, we will take 8 bytes from WSCURRENTDATEDATA.
COMPUTE wsinteger = FUNCTION INEGEROFDATE (WSCURRENTDATEDATA(1:8))
This converts 20101202 to integer form 0149720 ( i.e. no of days from fixed date)
ADD 10 TO wsinteger
This calculates the integer form date of future date. it will add 10 days to wsinteger.
COMPUTE wsfuturedate = FUNCTION DATEOFINTEGER (wsinteger).

Convert integer form date (i.e. 149730) to date format i.e. 20101222

No comments:

Post a Comment