Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

RANDOM - Random number

The RANDOM function returns a numeric value that is a pseudo-random number from a rectangular distribution.
The type of this function is numeric.

Format


FUNCTION RANDOM [(argument-1)]


Arguments

  1. If argument-1 is specified, it must be zero or a positive integer. It is used as the seed value to generate a sequence of pseudo-random numbers.

  2. If a subsequent reference specifies argument-1, a new sequence of pseudo-random numbers is started.

  3. If the first reference to this function in the run unit does not specify argument-1, the seed value is 0.

  4. In each case, subsequent references without specifying argument-1 return the next number in the current sequence.

Returned values

  1. The returned value is greater than or equal to zero and less than one.

  2. For a given seed value, the sequence of pseudo-random numbers will always be the same.

  3. The range of argument-1 values that will yield distinct sequences of pseudo-random numbers is
    0 through 231-1.

  4. The error default value is -1.

Example 9-37

  IDENTIFICATION DIVISION.
 PROGRAM-ID. LOTTO.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SPECIAL-NAMES.
     TERMINAL IS VIDEO.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01 LIST.
  05 ELEM        OCCURS 6 INDEXED BY SI, LI.
   10 Z          PIC Z9 VALUE FROM (1) IS ZERO REPEATED TO END.
   10 T          PIC XX VALUE FROM (1) IS ", " REPEATED TO END.
 01 Z-0         PIC Z9.
 01 RAN-VAL       PIC V9(18) BINARY.
 01 INIT-ARG       PIC 9(5) BINARY.
 01 ID-1.
  02             PIC X(5).
  02 D1          PIC 9.
  02             PIC X.
  02 D2          PIC 9.
  02             PIC X.
  02 D3          PIC 9.
  02             PIC X.
  02 D4          PIC 9.
  02             PIC X.
  02 D5          PIC 9.
  02             PIC X(7).
 01 D6           PIC 9.
 PROCEDURE DIVISION.
 M SECTION.
 M1.
*
* Select a seed for the random function based on the
* time, date, and weekday
*
      MOVE FUNCTION CURRENT-DATE TO ID-1
      ACCEPT D6 FROM DAY-OF-WEEK
      COMPUTE INIT-ARG =
           (10 * D1 + 1000 * D2 + 100 * D3 + D4 + 10000 * D5) * D6
*
* Compute the first random number
*
      COMPUTE RAN-VAL = FUNCTION RANDOM (INIT-ARG)
*
* Traverse the loop until 6 elements have been entered
* into the list
*
      PERFORM VARYING LI FROM 1 BY 1 UNTIL LI > 6
*
* Traverse the loop until a unique number is found
* and entered into the current list element
*
        PERFORM UNTIL Z (LI) NOT ZERO
*
* Map the return value of the RANDOM function
* to an integer between 1 and 49
* 
          COMPUTE Z-0 = FUNCTION INTEGER (49 * RAN-VAL) + 1
          SET SI TO 1
*
* Check the result for uniqueness
*
          SEARCH ELEM
*
* If number not found in list -> enter the number
*
          AT END MOVE Z-0 TO Z (LI)
*
* If number is already in the list -> new random number
*
            WHEN Z (SI) = Z-0 CONTINUE
          END-SEARCH
*
* Compute next random number
*
          COMPUTE RAN-VAL = FUNCTION RANDOM
        END-PERFORM
      END-PERFORM
      SORT ELEM ASCENDING Z
      MOVE "." TO T (6)
      DISPLAY LISTE UPON VIDEO
      STOP RUN.

Result:              6 numbers from 1 to 49