Monday, July 20, 2020

Find MAX and MIN value in an array

Hi Friends,

This post is to display the maximum and minimum value from an array.


For example array, ar[19,15,66,41,12]

Here, 66 is the maximum value and 12 is minimum.
 

It is pretty simple. 

Please check the code below :


IDENTIFICATION DIVISION.
PROGRAM-ID. HELLO-WORLD.

DATA DIVISION. 
WORKING-STORAGE SECTION.
01 WS-HIGH   PIC 9(2)  VALUE 0.
01 WS-LOW    PIC 9(2)  VALUE 99.
01 WS-I      PIC 9(2)  VALUE 0. 
01 WS-TAB    VALUE "1915664112".
  05 WS-ELE PIC 9(2) OCCURS 5 TIMES.

PROCEDURE DIVISION.

PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > 5
  IF WS-ELE(WS-I) > WS-HIGH
     MOVE WS-ELE(WS-I) TO WS-HIGH
  END-IF
  IF WS-ELE(WS-I) < WS-LOW
     MOVE WS-ELE(WS-I) TO WS-LOW
  END-IF  
END-PERFORM. 

DISPLAY 'THE HIGHEST NUMBER IS : ' WS-HIGH.
DISPLAY 'THE LOWEST NUMBER IS  : ' WS-LOW.
STOP RUN.

Below will be the output:-


THE HIGHEST NUMBER IS : 66
THE LOWEST NUMBER IS  : 12
That's it :)
Happy Learning.

Sunday, July 19, 2020

Write a program that prints a staircase of size 'N' .

Hi Friends,

In this post, I will show you how to print a staircase of n height, which is right aligned like below :
      #
    ##
  ###
####

Note: In my code, I didn't include steps to take inputs at run time. Instead, I've used the VALUE clause to assign input.

Pseudocode will be like below :

1- Perform a loop from 1 till the height of the staircase(in my code, it is WS-N ).
2- Take a variable to indicate the print position, which will be equal to the hight. (WS-POS)
3- Within LOOP, move # to the output field.
  a.) In the first iteration, The # will be placed at 4th position and single occurrence.
  b.) Shift the position by one space back. 
  b.) in the next iteration, The # will be placed at 3rd position and two occurrences and so on till the end of the LOOP.

Now, have a look at the code :


IDENTIFICATION DIVISION.
PROGRAM-ID. HELLO-WORLD.

DATA DIVISION. 
WORKING-STORAGE SECTION.
01 WS-OUT    PIC X(80) VALUE SPACES.
01 WS-I      PIC 9(2)  VALUE 0. 
01 WS-N      PIC 9(2)  VALUE 4. 
01 WS-POS    PIC 9(2)  VALUE 4.  

PROCEDURE DIVISION.

PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > WS-N
MOVE ALL '#' TO WS-OUT(WS-POS:WS-I)
DISPLAY WS-OUT
COMPUTE WS-POS = WS-POS - 1
END-PERFORM. 

STOP RUN.

Here the point to be noted that, I have used 'MOVE ALL' instead of 'MOVE'.

So the question is, what is the difference between 'MOVE ALL' and 'MOVE'?
The answer is:- If you use 'MOVE', it will move single # in the output field. But if you want to fill the complete string then use 'MOVE ALL'. 
For example :
01 WS-VAR    PIC X(5).
MOVE '#' TO WS-VAR.
OUTPUT : #
MOVE ALL '#' TO WS-VAR.
OUTPUT : #####
Happy Learning :)

Monday, July 6, 2020

Display table from 1 to 10 in COBOL.

Hi Friends,

This post is to display the table from 1 to 10 in metrics format.
For example :
  1   2   3   4   5   6   7   8   9  10                                                             
  2   4   6   8  10  12  14  16  18  20                                                             
  3   6   9  12  15  18  21  24  27  30                                                             
  4   8  12  16  20  24  28  32  36  40                                                             
  5  10  15  20  25  30  35  40  45  50                                                             
  6  12  18  24  30  36  42  48  54  60                                                             
  7  14  21  28  35  42  49  56  63  70                                                             
  8  16  24  32  40  48  56  64  72  80                                                             
  9  18  27  36  45  54  63  72  81  90                                                             
 10  20  30  40  50  60  70  80  90 100  

It is pretty simple. Please check the code below :

IDENTIFICATION DIVISION.
PROGRAM-ID. TABLE1.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-I      PIC 9(2) VALUE 0.
01 WS-J      PIC 9(2) VALUE 0.
01 WS-PROD   PIC zz9  VALUE 0.
01 WS-PTR    PIC 9(3) VALUE 0.
01 WS-TAB    PIC X(100) VALUE SPACE.
PROCEDURE DIVISION.
PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > 10
 MOVE 1 TO WS-PTR
 PERFORM VARYING WS-J FROM 1 BY 1 UNTIL WS-J > 10
    MULTIPLY WS-I BY WS-J GIVING WS-PROD
    PERFORM 1000-PARA
 END-PERFORM
 DISPLAY WS-TAB
END-PERFORM.
STOP RUN.

1000-PARA.
STRING WS-PROD DELIMITED BY SIZE INTO WS-TAB
                  WITH POINTER WS-PTR
ADD 1 TO WS-PTR.

That's it :)

Happy Learning.

Convert Numeric digit into WORD in COBOL

Hi Friends,

In this post, I will show you that how you can convert number into words.
For example :

123 - One Hundred and Twenty Three
514 - Five Hundred and Fourteen

Pseudo code will be like below :

1- For any number either 3 digit or more, You will need 3 arrays :
    a.) Array1 for number 1 to 9
    b.) Array2 for number 10-19
    c.) Array3 for number 20,30,40 till 90
2- Take a variable for input number, Then divide it into ones,tens,hundreds and so on. Take one variable to store remainder value.
3- Now, Accept the number. 
4- Then check if HUNDRED > 0, divide the number by 100, Then take the quotient occurrence from Array1. For example : 234 , So after dividing it from 100, The quotient will be 2.So the 2nd occurrence will be taken form Array1.
5- Then perform STRING operation over this value.
6- Move 'Hundred' to a temp variable.
7- Repeat STRING para.
8- Now Repeat the processing from 4th step till 7th step for remainder value till the remainder become zero.
9- Special consideration needs to be taken for last two numbers. As, they can be from 10-19 or 20-90.
10- In this case we need to check if last two digits are less than 20 then take word from Array2 else from Array3.

Below is the code :

IDENTIFICATION DIVISION.
PROGRAM-ID. NUMTOWORD.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 NUM.
   05 HUNDRED    PIC 9(1)  VALUE 0.
   05 TEN        PIC 9(1)  VALUE 0.
   05 ONE        PIC 9(1)  VALUE 0.
01 WS-NUM        PIC 9(3)  VALUE 0.
01 WS-REM        PIC 9(3)  VALUE 0.
01 WS-PTR        PIC 9(3)  VALUE 0.
01 WS-DIGIT.
   05 WS-D1      PIC 9(1)  VALUE 0.
   05 WS-D2      PIC 9(1)  VALUE 0.
01 WS-TEMP       PIC X(10) VALUE SPACE.
01 NUM-IN-WORD   PIC X(60) VALUE SPACE.
01 WS-TAB1 VALUE "One   Two   Three Four  Five  Six   Seven "
-    "Eight Nine  ".
  05 WS-ONES PIC X(6) OCCURS 9 TIMES.
01 WS-TAB2 VALUE "Ten       Eleven    Twelve    Thirteen  Fourteen  "
-   "Fifteen   Sixteen   Seventeen Eighteen  Ninteen   ".
  05 WS-TENS PIC X(10) OCCURS 10 TIMES.
01 WS-TAB3 VALUE "Twenty  Thirty  Fourty  Fifty   Sixty   "
-    "Seventy Eighty  Ninty   ".
  05 WS-TIES PIC X(8) OCCURS 8 TIMES.
PROCEDURE DIVISION.
MOVE 123 TO NUM.
MOVE 1   TO WS-PTR.
DISPLAY 'NUMBER IN DIGIT : ' NUM.
IF HUNDRED > 0
   DIVIDE NUM BY 100 GIVING WS-NUM REMAINDER WS-REM
   MOVE WS-ONES(WS-NUM) TO WS-TEMP
   PERFORM 1000-PARA1
   MOVE 'Hundred' TO WS-TEMP
   PERFORM 1000-PARA1
   MOVE WS-REM TO NUM
END-IF.
IF TEN >= 2
   MOVE 'and' TO WS-TEMP
   PERFORM 1000-PARA1
   DIVIDE NUM BY 10 GIVING WS-NUM REMAINDER WS-REM
   COMPUTE WS-NUM = WS-NUM - 1
   MOVE WS-TIES(WS-NUM) TO WS-TEMP
   PERFORM 1000-PARA1
   MOVE WS-REM TO NUM
   IF ONE > 0
        MOVE WS-ONES(ONE) TO WS-TEMP
        PERFORM 1000-PARA1
   END-IF
ELSE
   MOVE 'and' TO WS-TEMP
   PERFORM 1000-PARA1
   MOVE NUM TO WS-DIGIT
   COMPUTE WS-D2 = WS-D2 + 1
   MOVE WS-TENS(WS-D2)  TO WS-TEMP
   PERFORM 1000-PARA1
END-IF.
   DISPLAY 'NUMBER IN WORDS : ' NUM-IN-WORD.
STOP RUN.

1000-PARA1.
   STRING WS-TEMP DELIMITED BY SIZE INTO NUM-IN-WORD 
                  WITH POINTER WS-PTR
   ADD 1 TO WS-PTR.


Output will be like below :
NUMBER IN DIGIT : 555
NUMBER IN WORDS : Five       Hundred    and        Fifty      Five
For the post, I have taken 3 bytes digit only.The same process can be done for number more 
than 3 digit.
Hope this help..Happy Learning :)

Friday, July 3, 2020

Write a COBOL code to find the DUPLICATE in a STRING.

Hello Friends,

There is very common interview question to identify the duplicate word in a string. So in this post, I will be showing that how you can find the duplicate in a string.
For example -

String :- 'LIKE IN THIS TEXT . THIS IS IS COMING TWICE'

So, here 'THIS' and 'IS' are duplicate in the string.

Pseudo-code will be like below :

1- Store the string into an array.
2- MATCH will be performed using two loops :-
    a.) First loop will start from the beginning of the array till end of the array.
    b.) Second loop will start from +1 occurrence of the array till the end of the array.
3- In second loop, it will match the 1st occurrence from 2nd occurrence till end, then 2nd occurrence          from 3rd occurrence till end and so on.
4- If MATCH found , it will display the duplicate word.

Now, have a look at the code :

IDENTIFICATION DIVISION.
PROGRAM-ID. DUP_FOUND.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-STR       PIC X(50) VALUE 'LIKE IN THIS TEXT . THIS IS IS COMING TWICE'.
01 WS-TAB.
   05 WS-ELE    OCCURS 10 TIMES.
      10 WS-E   PIC X(10).
01 WS-I         PIC 9(2).
01 WS-J         PIC 9(2).
01 WS-PTR       PIC 9(3).
PROCEDURE DIVISION.
MOVE 1 TO WS-PTR.
PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > 10
  UNSTRING WS-STR DELIMITED BY '' INTO WS-E(WS-I)
  POINTER WS-PTR
  END-UNSTRING
END-PERFORM.
PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > 10
  COMPUTE WS-J = WS-I + 1
  PERFORM VARYING WS-J FROM WS-J BY 1 UNTIL WS-J > 10
                                         OR WS-E(WS-J) = SPACE
      IF WS-E(WS-I) = WS-E(WS-J)
       DISPLAY 'DUPLICATE FOUND : ' WS-E(WS-I)
      END-IF
  END-PERFORM
END-PERFORM.
STOP RUN.


Simple Right :)

Hope this helps. Happy Learning.



Thursday, July 2, 2020

Write a COBOL code to find if there is a balance of parenthesis in the sentence or not

Hello Friends,

In this post, I will show how to check if the parenthesis is in balance or not in a STRING.
Example:
(empty)      OK
( )               OK   
( )( )           OK   
(( )( ))        OK 
)(                NOT OK
)( )(            NOT OK
() )(()         NOT OK

Pseudocode will be like below :

1- Have the string in which you want to check the parenthesis pair.
2- Have one COUNTER field and one SWITCH field.
3- PERFORM a loop till the length of the string.
4- Under the loop :
    a.) If '(' found, increase COUNTER by 1.
    b.) If ')' found, decrease COUNTER by 1.
5- After the PERFORM loop, Check the COUNTER
   a.) If COUNTER = 0, set SWITCH TRUE.
   b.) else set SWITCH FALSE.
6- Now, EVALUATE SWITCH
   a.) If TRUE, Balance Found.
   b.) If FALSE, Balance NOT Found.

Now, Have a look at the program.

IDENTIFICATION DIVISION.
PROGRAM-ID. BAL_PAREN.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-STR       PIC X(5)   VALUE '())'.
01 WS-CNT       PIC S9(2)  VALUE 0.
01 SW-BAL       PIC X(1).
   88 SW-YES               VALUE 'Y'.
   88 SW-NA                VALUE 'N'.
01 WS-I         PIC 9(2).
PROCEDURE DIVISION.
PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > 5
   IF WS-STR(WS-I:1) = '('
      ADD      1 TO   WS-CNT
   ELSE 
      IF WS-STR(WS-I:1) = ')'
      SUBTRACT 1 FROM WS-CNT
      END-IF 
   END-IF
END-PERFORM.

IF WS-CNT = 0
   MOVE 'Y' TO SW-BAL
ELSE
   MOVE 'N' TO SW-BAL
END-IF.

EVALUATE SW-BAL
 WHEN 'Y'
   DISPLAY 'BALANCED'
 WHEN 'N'
   DISPLAY 'NOT BALANCED'
 WHEN OTHER
   DISPLAY 'ERROR'
END-EVALUATE.
STOP RUN.

So you have seen,  How simple is that :)

Hope this helps. Happy Learning.

Sunday, June 28, 2020

Reverse a string without using REVERSE and also remove the LEADING SPACE from the output field

Hello Friends,

In this blog, I will be showing how to reverse a string in COBOL without using the REVERSE function. If you have gone thru a similar post before, You might have seen that LEADING SPACE has not been handle. So in this post, I will show how to handle the leading spaces as well.

IDENTIFICATION DIVISION.
PROGRAM-ID. REVERS.
DATA DIVISION.
WORKING-STORAGE SECTION.
    01 WS-VAR1 PIC X(50) VALUE 'ABCDEFGHIJKLMNOPQRST'.
    01 WS-VAR2.
       05 WS-REV OCCURS 0 TO 50 TIMES DEPENDING ON WS-LEN PIC X. 
    01 WS-I   PIC 9(3) VALUE 0.
    01 WS-J   PIC 9(2) VALUE 1. 
    01 WS-LEN PIC 9(3) VALUE 0. 
    01 WS-CNT PIC 9(3) VALUE 0.

PROCEDURE DIVISION.

    INSPECT WS-VAR1 TALLYING WS-CNT FOR TRAILING SPACES.
    MOVE FUNCTION LENGTH(WS-VAR1) TO WS-LEN.
    COMPUTE WS-LEN = WS-LEN - WS-CNT.
    PERFORM VARYING WS-I FROM WS-LEN BY -1 UNTIL WS-I = 0
        MOVE WS-VAR1(WS-I:1) TO WS-REV(WS-J)
        ADD 1 TO WS-J
    END-PERFORM

    DISPLAY 'INPUT STRING   : ' WS-VAR1. 
    DISPLAY 'REVERSE STRING : ' WS-VAR2. 

    STOP RUN.

OUTPUT (when handling LEADING SPACE) : 

INPUT STRING   : ABCDEFGHIJKLMNOPQRST                              
REVERSE STRING : TSRQPONMLKJIHGFEDCBA

In this example, WS-VAR1 is 50 bytes but the actual length of the data is 20. If we will not handle actual data length. Then the output will look like below because it will reverse the complete 50 bytes of field, not just 20 bytes actual data.

OUTPUT ( when NOT handling LEADING SPACE):

INPUT STRING   : ABCDEFGHIJKLMNOPQRST                              
REVERSE STRING :                               TSRQPONMLKJIHGFEDCBA



Find MAX and MIN value in an array

Hi Friends, This post is to display the maximum and minimum value from an array. For example array, ar[ 19,15,66,41,12 ] Here, 66 is th...