Prim numbers and random values

The enclosed members calculate prim numbers and provide functions for random values.

Program PRIM
Calculate prim numbers until a given max value (I4).

Function RAND
Returns random (F8) number 0 <= RAND < 1
It uses the time stamp and the biggest (I4) prim number for the calculation.

Function DICE
Returns random number from 1 to #P_MAX (input parm).

Program DICE06
Call the function DICE(<6>) to throw a standard dice (1 to 6) and count the occurences.

Subprogram DEAL
Mix numbers randomly like dealing cards

Program DEAL1
Mixes the numbers from 1 to 20 by calling the subprogram DEAL.
RANDOM.zip (4.15 KB)

1 Like

Iā€™ve also writen some time ago a Subprogramm to generate Random Numbers. Here is the Code.

Greeting Sascha Wiegandt


0010 ************************************************************************
0020 * PROGRAMM/TEXT: SXRANDOM               USER/DATE: WIEGANDT / 20030513 *
0030 *                Generates Random Numbers with the                     *
0040 *                Algorithm from Brian Wichmann and David Hill          *
0050 *                                                                      *
0060 ************************************************************************
0070 DEFINE DATA
0080 PARAMETER
0090 01 #RANDOM (F8)
0100 *
0110 01 #STARTVALUES
0120  02 #X (I4)
0130  02 #Y (I4)
0140  02 #Z (I4)
0150 *
0160 LOCAL
0170 01 #X-DIV (I4)
0180 01 #Y-DIV (I4)
0190 01 #Z-DIV (I4)
0200 *
0210 01 #T (F8)
0220 01 #T-ADD (I4)
0230 *
0240 01 #GEN1 (I4)
0250 01 #GEN2 (I4)
0260 01 #GEN3 (I4)
0270 01 #TEMP (I4)
0280 END-DEFINE
0290 *
0300 PERFORM RANDOM
0310 *
0320 ************************************************************************
0330 DEFINE SUBROUTINE RANDOM
0340 PERFORM GEN1
0350 PERFORM GEN2
0360 PERFORM GEN3
0370 COMPUTE #T = #GEN1 / 30269.0 + #GEN2  / 30307.0 + #GEN3 / 30323.0
0380 COMPUTE ROUNDED #T-ADD = #T *1
0390 COMPUTE #RANDOM = #T - #T-ADD
0400 END-SUBROUTINE /* RANDOM
0410 ************************************************************************
0420 DEFINE SUBROUTINE GEN1
0430 IF #X = 0 OR #X > 30000
0440   #X := *TIMN / 7
0450   REPEAT
0460     IF #X > 30000
0470       #X := #X / 7
0480       ESCAPE TOP
0490     ELSE
0500       ESCAPE BOTTOM
0510     END-IF
0520   END-REPEAT
0530 END-IF
0540 DIVIDE 177 INTO #X GIVING #TEMP REMAINDER #X-DIV
0550 COMPUTE #X = 171 * (#X-DIV) - 2 * (#X / 177)
0560 IF #X < 0
0570   ADD 30269 TO #X
0580 END-IF
0590 #GEN1 := #X
0600 IF #X > 30000
0610   RESET #X
0620 END-IF
0630 END-SUBROUTINE /* GEN1
0640 ************************************************************************
0650 DEFINE SUBROUTINE GEN2
0660 IF #Y = 0 OR #Y > 30000
0670   #Y := *TIMN / 77
0680   REPEAT
0690     IF #Y > 30000
0700       #Y := #Y / 77
0710       ESCAPE TOP
0720     ELSE
0730       ESCAPE BOTTOM
0740     END-IF
0750   END-REPEAT
0760 END-IF
0770 DIVIDE 176 INTO #Y GIVING #TEMP REMAINDER #Y-DIV
0780 COMPUTE #Y = 172 * (#Y-DIV) - 35 * (#Y / 176)
0790 IF #Y < 0
0800   ADD 30307 TO #Y
0810 END-IF
0820 #GEN2 := #Y
0830 IF #Y > 30000
0840   RESET #Y
0850 END-IF
0860 END-SUBROUTINE /* GEN2
0870 ************************************************************************
0880 DEFINE SUBROUTINE GEN3
0890 IF #Z = 0 OR #Z > 30000
0900   #Z := *TIMN / 777
0910   REPEAT
0920     IF #Z > 30000
0930       #Z := #Z / 777
0940       ESCAPE TOP
0950     ELSE
0960       ESCAPE BOTTOM
0970     END-IF
0980   END-REPEAT
0990 END-IF
1000 DIVIDE 178 INTO #Z GIVING #TEMP REMAINDER #Z-DIV
1010 COMPUTE #Z = 170 * (#Z-DIV) - 63 * (#Z / 178)
1020 IF #X < 0
1030   ADD 30323 TO #Z
1040 END-IF
1050 #GEN3 := #Z
1060 IF #Z > 30000
1070   RESET #Z
1080 END-IF
1090 END-SUBROUTINE /* GEN3
1100 ************************************************************************
1110 END

Great, although I donā€™t understand the algorithm.

My algorithm uses the fact that e=2 is a prim element (not sure if this is the correct translation, in German it is named ā€˜primitives Elementā€™) of the big prim number (p=2147483629). This was quite probabil because p is 5 mod 2 and I proved it with another program. Such a prim element has the property that it runs through all numbers in the modules (but not 0) if you take
e^^0, e^^1, e^^2, ā€¦, e^^(p-2)
e^^(p-1) = e^^0 = 1 (mod p) again which closes the circle.
It can of cause never be 0 because p is prim.

As input I take an independent variable +RAND which is in the range from 1 to p-1. If it is 0, the routine is called for the first time and I derive a value from the timestamp.
Then I multiply the value n-times with 2 where n (1-255) is also derived from the timestamp. The multiplication with 2, maps the values to any other value from 1 to p-1 and by repeating it randomly, I receive any random value x in the range from 1 to p-1.
The random value returned is then (x-1) / (p-1)

Hi Lukas, here ist the Source where i also found my Generator:

http://www.informatik.uni-hamburg.de/TKRN/world/abro/NMI/kapitel07.pdf
(Only in German)

I only searched in 2003 an easy to use algorythm to implement in Natural and found this one. I want it to use to get random records from an Database to print some records for the controlling department.

great, thanks :wink:
I made the algorithm by myself and if I look to that article it is the special case 3.

Hi Lucas,

this is probably an absolute newbie question, sorry for that, but maybe you can give me a hint nevertheless:

I experimented with your random-function and reworked it into a subprogram to be able to use it on the mainframe too. I keep getting very puzzling results, though - in short: it seems to work on PC but not on the mainframe!? :? I copied both the subprogram and the calling program from my PC-environment to my library on the mainframe so I am using the exact same coding. On PC I get a desired series of pseudo-random numbers, on the mainframe (IBM Host, z/OS), however, I get the same number over and over again. I assume this has to do with the F8 format (or the conversion F8 to I4 ) - does that work differently on the mainframe???

Hereā€™s your function as subprogram (I added some ā€œwritesā€ for testing):

* (Pseudo-) Zufallszahl
*
* Function .... RAND
* Author ...... Lukas Hundemer
* Last edit ... 2006-07-20
* Copyright ... Software AG 2006. All rights reserved.
*
* Description
* Returns random number 0 <= RAND < 1
*
* Note
* It uses the independent variable +RAND when called iple times
*
* Anmerkung: Da Funktionen und Funktionsaufrufe auf dem HOST (NAT 4)
*            nicht implementiert sind, habe ich die Funktion in ein
*            Subprogram umgewandelt.
*
* ************************************************************************************
DEFINE DATA
PARAMETER
1 #RAND-F8 ( F8 )
LOCAL
1 #PRIM (I4) INIT <2147483629>  /* big I4 prim number, 2 as prim element
1 #P1 (I4)  /* p-1
1 #PH (I4)  /* (p-1)/2
1 #VAL (I4)
1 #VAL1 (I4)
1 #STCL ( B8 )
1 REDEFINE #STCL
  2 #S1 (B2)
  2 #T4 (I4)  /* random start if required
  2 REDEFINE #T4
    3 #T4A (B3)
    3 #T1 (B1)  /* 0 - 255 random repeat
  2 #S2 (B2)
1 #R2 (I2)
1 REDEFINE #R2
  2 #R21 (B1)
  2 #R22 (B1)
1 #I (I4)
1 #J (N4)
1 #F ( F8 )
INDEPENDENT
1 +RAND (I4)
END-DEFINE
*
#P1 := #PRIM - 1
#PH := #P1 / 2
MOVE *TIMESTMP TO #STCL
*
IF +RAND = 0  /* first call
  MOVE #T4 TO #VAL  /* random time
  IF #VAL >= #P1  /* mod p-1
    #VAL := #VAL - #P1
  ELSE
    REPEAT
      IF #VAL >= 0
        ESCAPE BOTTOM
      ELSE
        #VAL := #VAL + #P1
      END-IF
    END-REPEAT
  END-IF
  +RAND := #VAL + 1   /* range 1 to p-1
END-IF
*
#VAL := +RAND
WRITE *PROGRAM '=' #VAL '=' +RAND
RESET #R22
MOVE #T1 TO #R21  /* get unsigned (i1)
*
FOR #I = 1 TO #R2 /* ** rand(i1)
  IF #VAL > #PH  /*   2 * #val > p
    #VAL1 := #PRIM - #VAL /* avoid overflow
    #VAL := #VAL - #VAL1 /* = v-(p-v) = 2v-p = 2v (mod p)
  ELSE
    ADD #VAL TO #VAL
  END-IF
END-FOR
*
MOVE #VAL TO +RAND
#F := #VAL - 1
WRITE *PROGRAM '=' #F
#RAND-F8 := #F / #P1
*
END

Hereā€™s the calling PGM:

DEFINE DATA LOCAL
1 #RUECK ( F8 )
1 #CNTR (I2)
1 #RUECK-I4 (I4)
END-DEFINE
*
FOR #CNTR = 1 TO 8
  CALLNAT '#DHRANDN' #RUECK
  #RUECK-I4 := 10 * #RUECK + 1
  PRINT '=' #RUECK '=' #RUECK-I4
END-FOR
*
END

The function was designed for PC. To bring it on the mainframe is no big deal.
The problem which you found comes from the byte-swapping on the PC and the fact that my program uses redefined binary fields (not well designed when you go to other platforms :oops: ).
The main part which redefines the time still works because it redefines the middle 4 bytes of the 8 byte binary time. And the middle remains the middle :wink:
The part which does not work, is the conversion from the 1 byte unsigned binary to an integer. Just replace the lines

RESET #R22
MOVE #T1 TO #R21  /* get unsigned (i1)

by


MOVE #T1 TO #R2  /* get unsigned (i1)

This worked on my side (PC & mainframe).

1 Like

Hi all,

playing around with ā€œnewā€ functions like REQUEST DOCUMENT I wrote a small program that fetches true random numbers from the website www.random.org - they claim that their numbers are generated from atmospheric noise and thus truly random - as opposed to algorithm-generated pseudo-random numbers.

**  request n random numbers from www.random.org
**
************************************************************************
**
DEFINE DATA
LOCAL
1 #IN-URL              (A) DYNAMIC INIT <'http://www.random.org/integers/'>
1 #HEADER_STATUS       (A253)
1 #HEADER_CONTENT_TYPE (A253)
1 #HEADER_LOCATION     (A253)
1 #HEADER_AUTHENTICATE (A) DYNAMIC
1 #RETURN_HEADER       (A) DYNAMIC
1 #RETURN_PAGE         (A) DYNAMIC
1 #RESPONSE            (I4)
1 #ERROR-NUM           (I4)
1 #NUM                 (I4) INIT <10>    /* how many randoms?
1 #MIN                 (I4) INIT <1>     /* smallest random
1 #MAX                 (I4) INIT <9999>  /* largest random
1 #RANDOM-ARRAY        (A4/1:*)
1 #I                   (I4)
1 #LF                  (A1) CONST <H> 
/* that should read H'0A' of course - the forum editor is taking away the hex-string??
END-DEFINE
*

** for more options see www.random.org
COMPRESS #IN-URL '?num=' #NUM '&min=' #MIN '&max=' #MAX
  '&col=1&base=10&format=plain&rnd=new' INTO #IN-URL LEAVING NO
**
RESET #RETURN_HEADER #RETURN_PAGE
RESET #RESPONSE #ERROR-NUM
**
REQUEST DOCUMENT FROM #IN-URL
  RETURN HEADER ALL  #RETURN_HEADER
      NAME ' '                VALUE #HEADER_STATUS
      NAME 'Content-Type'     VALUE #HEADER_CONTENT_TYPE
      NAME 'Location'         VALUE #HEADER_LOCATION
      NAME 'WWW-authenticate' VALUE #HEADER_AUTHENTICATE
    PAGE #RETURN_PAGE       ENCODED CODEPAGE ' '
RESPONSE #RESPONSE
  GIVING #ERROR-NUM
**
IF #ERROR-NUM GT 0             /* Natural error occurred
  IF #ERROR-NUM = 8301        /* Wrong Url was entered
    WRITE 'NAT8301 Wrong URL syntax.'
  ELSE
    COMPRESS 'Natural error NAT' #ERROR-NUM ' occurred.'
      INTO #RETURN_HEADER LEAVING NO
    WRITE #RETURN_HEADER (AL=79)
  END-IF
  ESCAPE ROUTINE
END-IF
**
** separate output into array
**
ADD 1 TO #NUM /* one element more than numbers returned
EXPAND OCCURRENCES OF ARRAY #RANDOM-ARRAY TO (1:#NUM)
SEPARATE #RETURN_PAGE INTO #RANDOM-ARRAY(*) WITH DELIMITER #LF
**
SUBTRACT 1 FROM #NUM
RESIZE OCCURRENCES OF ARRAY #RANDOM-ARRAY TO (1:#NUM)
*
FOR #I 1 #num             /* or: 1 to *OCC(#RANDOM-ARRAY) 
  PRINT #RANDOM-ARRAY(#I)
END-FOR
**
END
**

Notes:

  1. there is only a LF (Hā€™0Aā€™) in the return-string, not a CRLF (took some time to figure that out) :?
  2. if an x-array is used as recieving field it must be instantiated with a number at least one greater than the number of randoms received, otherwise it wouldnā€™t work (NAT1313)

Iā€™m not a math boffin but based the following subroutine on some web-site info I found. It looks shorter, but perhaps it does not work properly?


* Generates next pseudo-random number X based on last one
* If zero is passed in then it is based on some bytes from *timestamp.
DEFINE DATA
PARAMETER
1 #RANDOM-NUMBER    (P11.7) BY VALUE RESULT
LOCAL
1 #A                (P11.7) CONST <16807>
1 #Y                (P11.7)
1 #M                (P11)   CONST <2147483647>
1 #TIMESTMP         (B8)
1 REDEFINE #TIMESTMP
  2 FILLER          (A4)
  2 #TIMESTMP-I     (I4)
1 #TIMESTMP-N       (N10.7)
1 REDEFINE #TIMESTMP-N
  2 FILLER          (A7)
  2 #SEED           (N3.7)
END-DEFINE
DEFINE RANDOM
REPEAT WHILE #RANDOM-NUMBER = 0
  #TIMESTMP := *TIMESTMP
  #TIMESTMP-N := ABS(#TIMESTMP-I)
  #RANDOM-NUMBER := #SEED
END-REPEAT
COMPUTE ROUNDED #Y := #A * #RANDOM-NUMBER
DIVIDE #M INTO #Y GIVING #Y REMAINDER #RANDOM-NUMBER
END-SUBROUTINE
END

This code is more simple and effective.


/*
/* RUTINA GENERADOR DE NUMERO ALEATORIO
/* POR  : ANGEL MENDOZA O - SOFTWARE AG VENEZUELA
/* FECHA: OCTUBRE 2008
/*
DEFINE DATA
PARAMETER
1 #RANDOM-NUMBER (P9)
1 #START-RANGE (P9)
1 #END-RANGE (P9)
1 #SEED (P20.7)
*
LOCAL
1 #ZERO (P10.7) CONST <0>
1 #HOLD-TIME (P7)
1 #HOLD-NUMBER (P9)
1 #TEMP (P10.7)
1 #RAN-FRAC (N20.7)1 REDEFINE #RAN-FRAC
  2 #INTEGER (N20)
  2 #DECIMAL (N0.7)
1 #CONS1 (P10.7) CONST <982146>
1 #CONS2 (P10.7)
1 #HUNDRED (P10.7) CONST <100>
1 #ONE (I4) CONST <1>
1 #I (I4)
END-DEFINE
*
#CONS2 := 0.2113272
*
IF #SEED = #ZERO THEN
  MOVE *TIMN TO #HOLD-TIME
  #SEED := #HOLD-TIME / #HUNDRED
END-IF
*
#SEED := (#CONS1 * #SEED) + #CONS2
#RAN-FRAC := #SEED
#SEED := #DECIMAL #SEED := #DECIMAL
#TEMP := ((#END-RANGE - #START-RANGE + #ONE) * #DECIMAL)
  + #START-RANGE
#RANDOM-NUMBER := INT (#TEMP)
END