Search code examples
cobolgnucobol

CALL unpredicatably changes unrelated variables in program


To preface, I am incredibly new to COBOL, and have only been writing it for about a week.

I wrote a program that plays a Rock-Paper-Scissors (RPS) game and the computer randomly picks an option each turn.

Originally, I had the section that generates a random value in the same program, but I wanted to make a module out of it, since I didn't want to have to write that random number generation for each program I write.

The way I found on the internet to do this was to use CALL on the module I compiled, and feed it the necessary variables. However, while randomly generating a number, it also changed two variables that weren't related to the CALL: USER-WIN, COMP-WIN.

Here is the code for the RPS program:

IDENTIFICATION DIVISION.
PROGRAM-ID. ADVENT-RPS.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 CHOICE.
    03 USER-CHOICE PIC A(1).
    03 COMP-CHOICE PIC A(1).
01 WIN.
    03 COMP-WIN PIC 9 VALUE 0.
    03 USER-WIN PIC 9 VALUE 0.
01 RAND.
    03 UPPER-BOUND PIC 9 VALUE 3.
    03 RAND-VAL PIC 9.
PROCEDURE DIVISION.
    DISPLAY "Choose R, P, or S"
    PERFORM UNTIL 1 = 0
*>      ACCEPT USER INPUT FROM TERMINAL AND CHECK FOR CORRECTNESS
        PERFORM USER-PIC
*>      GENERATES RANDOM COMPUTER CHOICE  
        PERFORM COMP-PICK
*>      CHECKS WHO WON THE ROUND AND IF SOMEONE WON THE GAME 
        PERFORM CHECK-WIN
    END-PERFORM.
    STOP RUN.
USER-PIC.
    ACCEPT USER-CHOICE FROM CONSOLE.
    IF (USER-CHOICE NOT = "R") AND
       (USER-CHOICE NOT = "P") AND
       (USER-CHOICE NOT = "S")
       DISPLAY "Please choose a valid input (R, P, S)."
       PERFORM USER-PIC
    END-IF.
COMP-PICK.
*>  CAUSING USER-WIN AND COMP-WIN TO CHANGE UNCONTROLLABLY 
    CALL "RAND" USING UPPER-BOUND, RAND-VAL.
    IF RAND-VAL = 0
       MOVE "R" TO COMP-CHOICE
    ELSE
       IF RAND-VAL = 1
          MOVE "P" TO COMP-CHOICE
       ELSE
          MOVE "S" TO COMP-CHOICE
       END-IF
    END-IF.
    DISPLAY "Computer chose: " COMP-CHOICE.
CHECK-WIN.
    IF USER-CHOICE = COMP-CHOICE
        DISPLAY "It's a tie!"
        EXIT PARAGRAPH
    ELSE
        IF (USER-CHOICE = "R" AND COMP-CHOICE = "P") OR
           (USER-CHOICE = "P" AND COMP-CHOICE = "S") OR
           (USER-CHOICE = "S" AND COMP-CHOICE = "R")
            DISPLAY "Computer beat you this round!"
            COMPUTE COMP-WIN = COMP-WIN + 1
        ELSE
            DISPLAY "You beat the computer this round!"
            COMPUTE USER-WIN = USER-WIN + 1
        END-IF
    END-IF.

    IF USER-WIN = 2
        DISPLAY "You won!"
        STOP RUN.
    IF COMP-WIN = 2
        DISPLAY "Computer won!"
        STOP RUN.
END PROGRAM ADVENT-RPS.

This is the random number generation program:

IDENTIFICATION DIVISION.
PROGRAM-ID. RAND.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-SEED-STRING PIC X(16).
01 WS-SEED-INT PIC 9(16).
LINKAGE SECTION.
01 UPPER-BOUND PIC 9(38).
01 RAND-VAL PIC 9(38).
PROCEDURE DIVISION USING UPPER-BOUND, RAND-VAL.
    MOVE FUNCTION CURRENT-DATE TO WS-SEED-STRING.
    MOVE FUNCTION NUMVAL(WS-SEED-STRING) TO WS-SEED-INT.
    COMPUTE RAND-VAL = FUNCTION RANDOM(WS-SEED-INT) * UPPER-BOUND.
EXIT PROGRAM.

I am using the GnuCOBOL compiler and used cobc -m -free RAND.COBOL to compile the random number generator and cobc -x -free RPS.COBOL to compile the RPS program. I am on Linux Mint Xfce if that is also important.

I tried putting variables on different levels, thinking that would change something, and it didn't. I also added the random number generator code back in to the RPS code, and it work perfectly fine then.

I also tried changing the size of UPPER-BOUND and RAND-VAL in the RAND program, and I found that if they are declared as size 9(15) and lower they work perfectly fine.

I think this has something to do with the RAND program overwriting memory that is used for COMP-WIN and USER-WIN, however I don't know if that is the case, and would like to know why this occurs and how to prevent similar thing in the future.

Additionally, I don't understand why changing the sizes of UPPER-BOUND and RAND-VAL in RAND fixes the issue. Does it have something to do with the size of WS-SEED-INT and what the RANDOM function returns?


Solution

  • calling and called programs must use the same communication area length and offsets for fields. You don't need to declare the parameters in the linkage section as group level, as shown bellow, but is a good practice to avoid mistakes and better understanding. As mentioned at comments, it's a good practice using copybooks too, for the same reason (but in that case, do not initialize the value in the copybook; just move the desired values to input fields at calling program).

    If you want reuse the random module, I suggest you using a pic definition big enough for your future uses. In my test, I've used 5 bytes for both upper-bound and rand-val (keeping the max digits equal 18 for numeric fields it's a good practice too). Both fields (UPPER-BOUND and RAND-VAL) must be the same length because the RANDOM intrinsic function returns a value between 0 and 1, when multiplied by upper-bound will produce a value between 0 and upper-bound.

    For example:


    RPS.CBL
    ...
    01 RAND-COMM-AREA.
       03 RAND-INPUT.
          05 UPPER-BOUND   PIC 9(5).
       03 RAND-OUTPUT.
          05 RAND-VAL      PIC 9(5).
    ...
      MOVE 3   TO UPPER-BOUND.
      CALL "RAND" USING RAND-COMM-AREA.
    


    RAND.CBL
    ...
    LINKAGE SECTION 
    01 RAND-COMM-AREA.
       03 RAND-INPUT.
          05 UPPER-BOUND   PIC 9(5).
       03 RAND-OUTPUT.
          05 RAND-VAL      PIC 9(5).
    PROCEDURE DIVISION USING RAND-COMM-AREA.
    

    The question about WS-SEED-INT is related with the seed you are using to feed the random generator. You are getting the timestamp with the function CURRENT DATE and converting that string to a numeric value, with the same length. It works fine, but use a huge number.

    The code bellow will have the same effect, if you move just the last 4 digits that represent the seconds and hundredths to the feed.


     01 WS-SEED-STRING PIC X(16).
     01 WS-SEED-INT PIC 9(4).
     ...
    *> RETURNS YYYYMMDDhhmmsscc
         MOVE FUNCTION CURRENT-DATE TO WS-SEED-STRING.
    *> MOVE just seconds and hundredths TO seed
         MOVE FUNCTION NUMVAL(WS-SEED-STRING(13:4)) TO WS-SEED-INT.
     ...
    

    I hope this help you. Have a lot of fun.