QB64.org Forum

Active Forums => QB64 Discussion => Topic started by: SMcNeill on June 10, 2019, 04:53:58 am

Title: RND and RANDOMIZE information
Post by: SMcNeill on June 10, 2019, 04:53:58 am
For folks who want a little extra information about how RND and RANDOMIZE work in QBASIC (and has been imitated to work the same in QB64), here's a little old documentation I dug up from the old drive on them:

Quote
;***
; RANDOM - RANDOM number generator AND RANDOMIZE
;
;        Copyright <C> 1986, Microsoft Corporation
 
;
; Algorithm:
;
; We use the "linear congruential" method FOR RANDOM numnber generation. The
; formula IS:
;
;        x1 = (x0 * a + c) MOD 2^24
;
; where
;
;        x1 = IS a new RANDOM number in the range [0..1^24]
;        x0 = the previous RANDOM number (OR the seed, FOR the first one)
;        a  = 214,013
;        c  = 2,531,011
;
; The RND FUNCTION returns a floating POINT number:
;
;        x1 / (2^24)
;
; which changes the range TO [0..1].
 
;***
;GetNextRnd -- GET NEXT RANDOM number
;MakeFloat -- make the number in [b$RndVar] into a R4
;
;Purpose:
;        GET NEXT RANDOM number in sequence.
;Entry:
;        [b$RndVar] has the seed.
;EXIT:
;        [AX]        = *B$AC which contains the R4 result
;Exceptions:
;        none
;*******************************************************************************
 
cProc        GetNextRnd,<NEAR>       
 
cBegin                               
        PUSH        DI               
        MOV        AX,[WORD PTR b$RndVar]         ;low half of previous number
        MOV        CX,[RndA]        ;low half of A
        MUL        CX
        XCHG        AX,DI                ;save low half in DI
        MOV        BX,DX                ;  high half in BX
        MOV        AX,[WORD PTR b$RndVar+2] ;high half of previous
        MUL        CX
        ADD        BX,AX                ;sum partial products
        MOV        AX,[RndA]
        MUL        [WORD PTR b$RndVar]         
        ADD        BX,AX                ;last partial product (since we're mod 2^24)
        ADD        DI,[RndC]        ;add in constant C
        ADC        BL,BYTE PTR [RndC]
        XOR        BH,BH                ;extended 24-bit number TO 32 bits FOR NORM
        MOV        DX,DI                ;number in BX:DX
        MOV        [WORD PTR b$RndVar],DX         ;save FOR NEXT time
        MOV        [WORD PTR b$RndVar+2],BX
        POP        DI               
MakeFloat:                       
 
        FILD        b$RndVar        ; PUT 24-bit INTEGER ON numeric stack
        FDIV        FP_2T24         ; ST0 = seed/2^24
        MOV        BX,OFFSET DGROUP:B$AC
        FSTP        DWORD PTR [BX]        ; PUT s.p. equivalent into FAC
        XCHG        AX,BX                ; result IS *R4 in AX
        FWAIT                        ; ensure result in RAM prior TO RETURN
 
cEnd                                ; EXIT TO caller
 
;***[6]
;B$RNZP - RANDOMIZE statement
;void B$RNZP (R8 SeedNum)
;
;Purpose:
;        The number IS set into the middle word of the current RANDOM
;        number AS the seed FOR the NEXT one.
;Entry:
;        R8 SeedNum
;EXIT:
;        A new seed IS created in RndVar, based ON the seed value at entry
;        AND the least significant 2-words of the INPUT parameter.
;Exceptions:
;        none
;*******************************************************************************
 
cProc        B$RNZP,<PUBLIC,FAR>       
        ParmQ        SeedNum         ; R8 seed number
cBegin                               
        LEA        BX,SeedNum+4        ; GET MOST significant digits
        MOV        AX,[BX]         ; GET word of D.P. number
        XOR        AX,[BX+2]        ; XOR with the NEXT word
        MOV        [WORD PTR b$RndVar+1],AX ; replace middle word of current s.p. seed
                                ;        with this value - - now we're reseeded.
cEnd                                ; EXIT

As you can see, we don't have any true randomness with RND in QB64.  In fact, our results are calculated on a mathematical formula!  (Which is why we always get the same results if we don't use RANDOMIZE TIMER to jump to some off point in the list of numbers we generate and use.)

If you're interested in this stuff, then here it is.  If not, then just ignore this topic and trust that RND isn't truly random -- which is why we call it pseduo-random, at best.  ;)
Title: Re: RND and RANDOMIZE information
Post by: Qwerkey on June 10, 2019, 05:58:05 am
Yes, it's always best to put RANDOMIZE(TIMER) so that this is performed regularly in your running program.
Title: Re: RND and RANDOMIZE information
Post by: SMcNeill on June 10, 2019, 06:15:39 am
Apparently either the documentation I found is old and didn't apply to QBASIC RND (maybe it was the formula used with some other version Microsoft produced?), or else QB64 uses a different RND formula.

What we actually use is this one (as taken from libqb.cpp):

Code: [Select]
float func_rnd(float n,int32 passed){
    if (new_error) return 0;
   
    static uint32 m;
    if (!passed) n=1.0f;
    if (n!=0.0){
        if (n<0.0){
            m=*((uint32*)&n);
            rnd_seed=(m&0xFFFFFF)+((m&0xFF000000)>>24);
        }
        rnd_seed=(rnd_seed*16598013+12820163)&0xFFFFFF;
    }     
    return (double)rnd_seed/0x1000000;
}

Instead of a formula where Seed = (Seed * 214013 + 2531011) MOD 2 ^ 24, we use one where rnd_seed=(rnd_seed*16598013+12820163)&0xFFFFFF;

Basically the concept is the same, but the formula for the calculations are different in the two versions. 

I wonder how QB64's formula compares against QB45's. If anyone has a version of QB45 they can run, can you kindly tell me what the output might be for the following:

Code: [Select]
FOR i = 1 TO 20
    PRINT RND, Rand
NEXT

FUNCTION Rand
    STATIC Seed
    x1 = (Seed * 214013 + 2531011) MOD 2 ^ 24
    Seed = x1
    Rand = x1 / 2 ^ 24
END FUNCTION
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 10, 2019, 10:29:53 am
MOD 2^24 puts a limit on the numbers generated to 16+ million but does the rest of the formula even cover that amount?

Hmm... how many times 2^24 should that range be mostly covered? (for normal distribution).
 
Title: Re: RND and RANDOMIZE information
Post by: SMcNeill on June 10, 2019, 12:33:44 pm
MOD 2^24 puts a limit on the numbers generated to 16+ million but does the rest of the formula even cover that amount?

Hmm... how many times 2^24 should that range be mostly covered? (for normal distribution).

The MOD, I think, is mostly there to make certain that we generate a value from 0 to 1.

x1 = (x0 * 214,013 + 2,531,011) MOD 2^24
x0 = the previous RANDOM number (OR the seed, FOR the first one)

So, in the case of the first number, what happens if someone plants a seed which results in a return value greater than 2 ^ 24?

We'd end up with a value which, in the end, would fall outside the 0 to 1 range which the function is built to generate.  The MOD makes certain we never fall outside that boundary. (Such as a RND(2^24) would generate without it.)
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 10, 2019, 01:10:45 pm
Quote
The MOD, I think, is mostly there to make certain that we generate a value from 0 to 1.

Yes! I see that.

Do you see that there are only 16+ million actual values that can be generated by this function assuming MOD only generates Whole numbers and not Reals. No matter the seed, MOD will reduce it to < 2^24 or 16+ million values and that is only if all those values can be covered by the rest of the formula. It is possible the rest of the formula will only cycle through some fraction of 16+ million before repeating over and over again.
Title: Re: RND and RANDOMIZE information
Post by: xra7en on June 10, 2019, 06:41:45 pm
Yes, it's always best to put RANDOMIZE(TIMER) so that this is performed regularly in your running program.

I don't remember where I saw this, but for years, I always used

Code: QB64: [Select]

SEEMS to work well.
Title: Re: RND and RANDOMIZE information
Post by: MWheatley on June 11, 2019, 11:01:13 am

I wonder how QB64's formula compares against QB45's. If anyone has a version of QB45 they can run, can you kindly tell me what the output might be for the following:

Code: [Select]
FOR i = 1 TO 20
    PRINT RND, Rand
NEXT

FUNCTION Rand
    STATIC Seed
    x1 = (Seed * 214013 + 2531011) MOD 2 ^ 24
    Seed = x1
    Rand = x1 / 2 ^ 24
END FUNCTION

The result is an overflow error, as per the attached image.

Malcolm
Title: Re: RND and RANDOMIZE information
Post by: Jack002 on June 11, 2019, 11:47:48 am
I love how subjective computer random generators are. The idea of randomness is so hard to define. Shuffle some cards, now they're random, no, not yet, do it more.

A good psudorandom works well as far as I know. If you can never get a number _ from it, I'd think that is bad. Any time one number is coming out more/less than others, that is bad. A function to replicate the idea seems doable to me.

There was a test for randomness (there are many) the one I like is one that uses a poker format.
Find a way to assign your random number to one of 52 cards, record them in groups of five, then record when you see a pair, two pair, three of a kind, etc, etc, then gather some number of hands (I think a chi square thing would come into play on that number) and then look at the ratios of what hands came out and what you expect from established card probability. I think a pair is just under 50%, like 0.46 or so?

I did this test for school years back using my commodore 64, it turns out to have a very good random number generator, it passed the test
Title: Re: RND and RANDOMIZE information
Post by: Bert22306 on June 11, 2019, 03:56:59 pm
I've written two tests for PRNGs, which are attached.

One draws dots in a 2D space, using every adjacent pair of random numbers from the PRNG as x and y coordinates. Very simple code.

The second one fills 10 bins with the random numbers, as they are created by the PRNG, to see whether the distribution is even over time. It also calculates the max so far, min so far, and the running average.

A random number generator has to generate any given value with the same probability as any other value. So over time, you should notice the screen filling up evenly with dots, even if clusters do form here and there. In other words, an empty area in the screen should eventually fill in, even though, in theory, "eventually" could be a very long time. Similarly, one crowded cluster will eventually be no more crowded than the rest of the screen. And using TIMER as the seed, every iteration should look different, in terms of how the screen fills up with dots.

The test with the bins is more precise, but it's also one that would appear to do well with a non-random sequence. For example, a simple repeating sequence of 0 to 1, step 1, will be nice and evenly distributed. Still, if you run that second program, you can see how each try is giving different results, and how over time, things tend to even out.

The two tests show that QB64's PRNG is pretty good. No obvious biases. And, it's nice to have QB64's RANDOMIZE USING feature, to allow you to re-start the pseudo-random sequence, for a given seed value, from the beginning. Couldn't do that with QBasic. Essential if you're writing some sort of monte carlo simulation, where you need to be sure you're using the same random sequence every time, in testing the results.
Title: Re: RND and RANDOMIZE information
Post by: Jack002 on June 11, 2019, 05:45:55 pm
Very cool, Bert. Those are great!
Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 10:29:45 am
I was always fascinated by BASIC's RND and RANDOMIZE.  After I figured out how the seed part worked, I came up with clever uses.

For example, I had a game with a top-down map, and wanted the levels to appear semi-random, for example a dirt path was mostly dirt with a bit of mud, so I would set those tiles to 90% likelihood of dirt, 10% chance of mud.  This produced nice looking paths.  The trick was to store the seed used on each level, then when the character returned to that screen, the semi-randomness was the same.  Mud patches in the same place you remember, but different places after starting a new game.  This really added to the feel of the game.  I used this nearly everywhere, such as the edge of water (land bits randomly jutting out into the water), hedges (bits taken out so it wasn't perfectly rectangular), etc.  It was great because storing a single random seed number was just one variable, but allowed me to produce variations for every screen of the game.  I think I used a variable counter + DATE + TIMER for getting actual random numbers after drawing the screen with the fixed seed.

I never saw anyone else using RANDOMIZE this way, having it produce fixed sets of random numbers that could be reused later via the same seed number.  I'm sure lots of people found clever uses for RANDOMIZE seeds, I just never encountered anyone else utilising this oddity of non-random randomness!
Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 10:35:12 am
And, it's nice to have QB64's RANDOMIZE USING feature, to allow you to re-start the pseudo-random sequence, for a given seed value, from the beginning. Couldn't do that with QBasic. Essential if you're writing some sort of monte carlo simulation, where you need to be sure you're using the same random sequence every time, in testing the results.

Didn't read your post until after I wrote mine.  That's exactly how I used QuickBASIC seeds, resetting them by saving and reusing the seed number I passed to RANDOMIZE.  How does this not work?
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 12, 2019, 11:04:23 am
Quote
I never saw anyone else using RANDOMIZE this way, having it produce fixed sets of random numbers that could be reused later via the same seed number.  I'm sure lots of people found clever uses for RANDOMIZE seeds, I just never encountered anyone else utilising this oddity of non-random randomness!

Never say never no more! :)

see line 194:
Code: QB64: [Select]
  1. _TITLE "Happy Trails 2018"
  2. ' 2017-12-29 another redesign of fireworks
  3. ' 2017-12-28 redesign fireworks
  4. ' now with lake refelction 2017-12-27 forget the bouncing sparks
  5. ' combine Welcome Plasma Font with landscape
  6. '_title "Fireworks 3 translation to QB64 2017-12-26 bplus"
  7. 'fireworks 3.bas SmallBASIC 0.12.2 [B+=MGA] 2015-05-09
  8. 'fireworks 2.bas 2016-05-05 now with Gravity, Newtonian bounce, smoke debris
  9. 'fireworks 3.bas try with map variables make bursts around a central point
  10.  
  11.  
  12. CONST xmax = 1200
  13. CONST ymax = 720
  14. CONST waterline = 600 ' 600 = ratio 5 to 1 sky to water
  15. '                       raise and lower waterline as desired  highest about 400?
  16. CONST lTail = 15
  17. CONST bluey = 5 * 256 ^ 2 + 256 * 5 + 5
  18. CONST debrisMax = 28000
  19.  
  20. SCREEN _NEWIMAGE(xmax, ymax, 32)
  21. _SCREENMOVE 120, 20
  22.  
  23. TYPE fireWorkType
  24.     x AS INTEGER
  25.     y AS INTEGER
  26.     seed AS INTEGER
  27.     age AS INTEGER
  28.     life AS INTEGER
  29.  
  30.  
  31. TYPE debrisType
  32.     x AS SINGLE
  33.     y AS SINGLE
  34.     c AS LONG
  35.  
  36. COMMON SHARED fw() AS fireWorkType
  37. COMMON SHARED debris() AS debrisType
  38. COMMON SHARED cN, pR!, pG!, pB!
  39.  
  40. SCREEN _NEWIMAGE(xmax, ymax, 32)
  41.  
  42. 'prepare message font
  43. mess$ = " Happy New Year 2018"
  44. PRINT mess$
  45. w = 8 * LEN(mess$): h = 16
  46. DIM p(w, h)
  47. black&& = POINT(0, 10)
  48. FOR y = 0 TO h
  49.     FOR x = 0 TO w
  50.         IF POINT(x, y) <> black&& THEN
  51.             p(x, y) = 1
  52.         END IF
  53.     NEXT
  54. xo = 0: yo = 15: m = 7.2
  55. resetPlasma
  56.  
  57. 'prepare landscape
  58. land& = _NEWIMAGE(xmax, ymax, 32)
  59. _DEST land&
  60. drawLandscape
  61.  
  62. 'prepare fire works
  63. nFW = 3
  64. DIM fw(1 TO 10) AS fireWorkType
  65. FOR i = 1 TO nFW
  66.     initFireWork (i)
  67.  
  68. 'debris feild
  69. DIM debris(debrisMax) AS debrisType
  70.  
  71. 'OK start the show
  72.     'cls screen with land image
  73.     _PUTIMAGE , land&, 0
  74.  
  75.     'draw fireworks
  76.     FOR f = 1 TO nFW
  77.         IF fw(f).age <= fw(f).life THEN drawfw (f) ELSE initFireWork f
  78.     NEXT
  79.  
  80.     'debris
  81.     FOR i = 0 TO debrisStack
  82.         PSET (debris(i).x, debris(i).y), debris(i).c
  83.         debris(i).x = debris(i).x + RND * 3 - 1.5
  84.         debris(i).y = debris(i).y + RND * 3.5 - 1.5
  85.         IF debris(i).x < 0 OR debris(i).y < 0 OR debris(i).x > xmax OR debris(i).y > waterline + RND * 20 THEN NewDebris (i)
  86.     NEXT
  87.  
  88.     'text message in plasma
  89.     FOR y = 0 TO h - 1
  90.         FOR x = 0 TO w - 1
  91.             IF p(x, y) THEN
  92.                 changePlasma
  93.             ELSE
  94.                 COLOR 0
  95.             END IF
  96.             LINE (xo + x * m, yo + y * m)-(xo + x * m + m, yo + y * m + m), , BF
  97.         NEXT
  98.     NEXT
  99.     lc = lc + 1
  100.     IF lc MOD 200 = 0 THEN resetPlasma
  101.  
  102.     'reflect sky
  103.     skyWaterRatio = waterline / (ymax - waterline) - .05
  104.     FOR y = waterline TO ymax
  105.         FOR x = 0 TO xmax
  106.             c&& = POINT(x, waterline - ((y - waterline - 1) * skyWaterRatio) + RND * 5)
  107.             PSET (x, y + 1), c&& + bluey
  108.         NEXT
  109.     NEXT
  110.  
  111.     _DISPLAY
  112.     _LIMIT 200 'no limit needed on my system!
  113.  
  114.     'accumulate debris
  115.     IF lc MOD 2000 THEN
  116.         IF debrisStack < debrisMax THEN
  117.             FOR i = 1 TO 2
  118.                 NewDebris i + debrisStack
  119.             NEXT
  120.             debrisStack = debrisStack + 2
  121.         END IF
  122.     END IF
  123.  
  124. SUB NewDebris (i)
  125.     debris(i).x = RND * xmax
  126.     debris(i).y = RND * ymax
  127.     c = RND * 155
  128.     debris(i).c = _RGB32(c, c, c)
  129.  
  130. SUB changePlasma ()
  131.     cN = cN + .01
  132.     COLOR _RGB(127 + 127 * SIN(pR! * .3 * cN), 127 + 127 * SIN(pG! * .3 * cN), 127 + 127 * SIN(pB! * .3 * cN))
  133.  
  134. SUB resetPlasma ()
  135.     pR! = RND ^ 2: pG! = RND ^ 2: pB! = RND ^ 2
  136.  
  137. SUB drawLandscape
  138.     'the sky
  139.     FOR i = 0 TO ymax
  140.         midInk 0, 0, 0, 78, 28, 68, i / ymax
  141.         LINE (0, i)-(xmax, i)
  142.     NEXT
  143.     'the land
  144.     startH = waterline - 80
  145.     rr = 10: gg = 20: bb = 15
  146.     FOR mountain = 1 TO 6
  147.         Xright = 0
  148.         y = startH
  149.         WHILE Xright < xmax
  150.             ' upDown = local up / down over range, change along Y
  151.             ' range = how far up / down, along X
  152.             upDown = (RND * .8 - .35) * (1 / (1 * mountain))
  153.             range = Xright + rand&&(5, 35) * 2.5 / mountain
  154.             lastx = Xright - 1
  155.             FOR X = Xright TO range
  156.                 y = y + upDown
  157.                 COLOR _RGB32(rr, gg, bb)
  158.                 LINE (lastx, y)-(X, ymax), , BF 'just lines weren't filling right
  159.                 lastx = X
  160.             NEXT
  161.             Xright = range
  162.         WEND
  163.         rr = rand&&(rr + 5, rr): gg = rand&&(gg + 5, gg): bb = rand&&(bb + 4, bb)
  164.         IF rr < 0 THEN rr = 0
  165.         IF gg < 0 THEN gg = 0
  166.         IF bb < 0 THEN bb = 0
  167.         startH = startH + rand&&(1, 10)
  168.     NEXT
  169.     'LINE (0, waterline)-(xmax, ymax), _RGB32(0, 0, 0), BF
  170.  
  171. SUB midInk (r1, g1, b1, r2, g2, b2, fr)
  172.     COLOR _RGB(r1 + (r2 - r1) * fr, g1 + (g2 - g1) * fr, b1 + (b2 - b1) * fr)
  173.  
  174. FUNCTION rand&& (lo&&, hi&&)
  175.     rand&& = INT(RND * (hi&& - lo&& + 1)) + lo&&
  176.  
  177. SUB drawfw (i)
  178.     'here's how to "save" a bunch of random numbers without data and arrays but tons of redundant calculations
  179.     RANDOMIZE USING fw(i).seed 'this repeats all random numbers generated by seed in same sequence
  180.     'recreate our firework from scratch!
  181.     red = rand&&(200, 255)
  182.     green = rand&&(200, 255)
  183.     blue = rand&&(200, 255)
  184.     x = rand&&(1, 4)
  185.     IF x = 1 THEN
  186.         red = 0
  187.     ELSEIF x = 2 THEN
  188.         green = 0
  189.     ELSEIF x = 3 THEN
  190.         blue = 0
  191.     ELSE
  192.         x = rand&&(1, 4)
  193.         IF x = 1 THEN
  194.             red = 0: green = 0
  195.         ELSEIF x = 2 THEN
  196.             green = 0: blue = 0
  197.         ELSEIF x = 3 THEN
  198.             blue = 0: red = 0
  199.         END IF
  200.     END IF
  201.     ne = rand&&(80, 300)
  202.     DIM embers(ne, 1)
  203.     FOR e = 0 TO ne
  204.         r = RND * 3
  205.         embers(e, 0) = r * COS(e * _PI(2) / 101)
  206.         embers(e, 1) = r * SIN(e * _PI(2) / 101)
  207.     NEXT
  208.     start = fw(i).age - lTail ' don't let tails get longer than lTail const
  209.     IF start < 1 THEN start = 1
  210.     FOR e = 0 TO ne
  211.         cx = fw(i).x: cy = fw(i).y: dx = embers(e, 0): dy = embers(e, 1)
  212.         FOR t = 1 TO fw(i).age
  213.             cx = cx + dx
  214.             cy = cy + dy
  215.             IF t >= start THEN
  216.                 'too much like a flower?
  217.                 midInk 60, 60, 60, red, green, blue, (t - start) / lTail
  218.                 'midInk 60, 60, 60, 128, 160, 150, (t - start) / lTail
  219.                 fcirc cx, cy, (t - start) / lTail
  220.             END IF
  221.  
  222.             dx = dx * .99 'air resitance
  223.             dy = dy + .01 'gravity
  224.         NEXT
  225.         COLOR _RGB32(255, 255, 255)
  226.         'COLOR _RGB32(red, green, blue)
  227.         cx = cx + dx: cy = cy + dy
  228.         fcirc cx, cy, (t - start) / lTail
  229.     NEXT
  230.     fw(i).age = fw(i).age + 1
  231.  
  232. SUB initFireWork (i)
  233.     fw(i).x = rand&&(.1 * xmax, .9 * xmax)
  234.     fw(i).y = rand&&(.1 * ymax, .5 * ymax)
  235.     fw(i).seed = rand&&(0, 32000)
  236.     fw(i).age = 0
  237.     fw(i).life = rand&&(20, 120)
  238.  
  239. 'Steve McNeil's  copied from his forum   note: Radius is too common a name
  240. SUB fcirc (CX AS LONG, CY AS LONG, R AS LONG)
  241.     DIM subRadius AS LONG, RadiusError AS LONG
  242.     DIM X AS LONG, Y AS LONG
  243.  
  244.     subRadius = ABS(R)
  245.     RadiusError = -subRadius
  246.     X = subRadius
  247.     Y = 0
  248.  
  249.     IF subRadius = 0 THEN PSET (CX, CY): EXIT SUB
  250.  
  251.     ' Draw the middle span here so we don't draw it twice in the main loop,
  252.     ' which would be a problem with blending turned on.
  253.     LINE (CX - X, CY)-(CX + X, CY), , BF
  254.  
  255.     WHILE X > Y
  256.         RadiusError = RadiusError + Y * 2 + 1
  257.         IF RadiusError >= 0 THEN
  258.             IF X <> Y + 1 THEN
  259.                 LINE (CX - Y, CY - X)-(CX + Y, CY - X), , BF
  260.                 LINE (CX - Y, CY + X)-(CX + Y, CY + X), , BF
  261.             END IF
  262.             X = X - 1
  263.             RadiusError = RadiusError - X * 2
  264.         END IF
  265.         Y = Y + 1
  266.         LINE (CX - X, CY - Y)-(CX + X, CY - Y), , BF
  267.         LINE (CX - X, CY + Y)-(CX + X, CY + Y), , BF
  268.     WEND
  269.  

Another great use of Randomize Using Seed is for encoding messages for cryptography.

Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 11:17:44 am
Fireworks, landscapes, water reflections, and reusing random number sequences?

Sign me up!  I'll check it out once I'm back on Desktop, sounds very cool.

Are you reusing the random sequence to recreate the same firework as a reflection in the water?

Could you not just draw the firework twice at the time of generating the random numbers?
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 12, 2019, 11:21:44 am
Fireworks, landscapes, water reflections, and reusing random number sequences?

Sign me up!  I'll check it out once I'm back on Desktop, sounds very cool.

Are you reusing the random sequence to recreate the same firework as a reflection in the water?

Could you not just draw the firework twice at the time of generating the random numbers?

Not for reflections, that was POINT work.

I used Randomize seed to avoid having to array all the data of for tracking "tails" of a firework burst. Type Structures don't do arrays (yet) so I used a seed for Randomize.
Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 11:31:09 am
I used Randomize seed to avoid having to array all the data of for tracking "tails" of a firework burst. Type Structures don't do arrays (yet) so I used a seed for Randomize.

Ah, nice.

I had to work around not being able to store an array of variable-length strings in a custom data type recently.  In my case, I created an array of strings separately, then in the data type I had an integer referencing the element in the string array.  Not as clean code, but gets the job done!
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 12, 2019, 11:36:30 am
Ah, nice.

I had to work around not being able to store an array of variable-length strings in a custom data type recently.  In my case, I created an array of strings separately, then in the data type I had an integer referencing the element in the string array.  Not as clean code, but gets the job done!

Ha! I am using variable length strings in custom type now to save small integer arrays (hands by card index) in Blackjack thread. We can do variable length strings in Type definitions now v1.3 :)

Yeah but arrays of string... ? could be done too with a split / join routine, yeah that's ugly too ;-)

Oh hey, that might be how to handle a Split in Blackjack...
Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 11:50:38 am
Ha! I am using variable length strings in custom type now to save small integer arrays (hands by card index) in Blackjack thread.

That's like the inverse of what I'm doing, lol.


We can do variable length strings in Type definitions now v1.3 :)

Oh, really?

I started on v1.2 and only recently upgraded to v1.3.

I guess I can clean my code up a bit!  Thanks for the tip.
Title: Re: RND and RANDOMIZE information
Post by: Bert22306 on June 12, 2019, 04:39:02 pm
Didn't read your post until after I wrote mine.  That's exactly how I used QuickBASIC seeds, resetting them by saving and reusing the seed number I passed to RANDOMIZE.  How does this not work?

Not sure what you mean by "saving and reusing the seed," Raven, unless perhaps the seed was TIMER? (I have to try that, because not sure why it would work.) Or maybe you meant, save the entire pseudo-random sequence? That should be fine, but depending on your needs, it could be one huge array!

Anyway, this simple code should demonstrate the difference between the QBasic limitation of RANDOMIZE alone, as opposed to QB64's RANDOMIZE USING. Pick any seed value you want, and RANDOMIZE USING will always start from the top of the sequence.

Code: [Select]
_TITLE "Test of RANDOMIZE USING"
SCREEN _NEWIMAGE(120, 43, 0)
PRINT "First test is RANDOMIZE 2. Should see different results first and second set of numbers."
RANDOMIZE 2
PRINT RND
PRINT RND
RANDOMIZE 2
PRINT
PRINT RND
PRINT RND
PRINT
PRINT "Second test is RANDOMIZE USING 2. Should see identical results, first and second set of numbers."
RANDOMIZE USING 2
PRINT RND
PRINT RND
RANDOMIZE USING 2
PRINT
PRINT RND
PRINT RND
END
Title: Re: RND and RANDOMIZE information
Post by: bplus on June 12, 2019, 05:23:59 pm
Not sure what you mean by "saving and reusing the seed," Raven, unless perhaps the seed was TIMER? (I have to try that, because not sure why it would work.) Or maybe you meant, save the entire pseudo-random sequence? That should be fine, but depending on your needs, it could be one huge array!
...

The number you use for RANDOMIZE USING is called a "seed", because it grows the same random number sequence.

As in your example, your seed was 2.
Title: Re: RND and RANDOMIZE information
Post by: Bert22306 on June 12, 2019, 07:33:44 pm
The number you use for RANDOMIZE USING is called a "seed", because it grows the same random number sequence.

As in your example, your seed was 2.

Of course. Are you responding to me or to Raven?

With RANDOMIZE USING, for any given seed, every time you repeat that RANDOMIZE USING in your program, the sequence starts from the beginning.

Try that with RANDOMIZE, with any given seed. It doesn't start at the beginning. It continues on where it had left off before, in your program.

Raven said that with QBasic, he saved and reused the "seed," to achieve what I just described with RANDOMIZE USING. That's what I didn't understand. Unless he meant that he saved the actual random sequence, as opposed to saving the seed.
Title: Re: RND and RANDOMIZE information
Post by: SMcNeill on June 12, 2019, 07:37:41 pm
Can’t you just RND(seed) to start the sequence at the start?

PRINT RND(2)
PRINT RND
PRINT RND(2)
PRINT RND

Doesn’t that repeat the cycle?  From what I remember with QB45, it’s how you set the seed — unless I’m getting old and brain damaged.  :P
Title: Re: RND and RANDOMIZE information
Post by: Raven_Singularity on June 12, 2019, 07:57:28 pm
It has been decades since I was doing this in QB45, but I know it works, because I was reusing a fixed seed to draw my level screens.  Every time I came back to the screen, it had the same random number sequence.

Pretty sure I was just using this each time to reset it:

Code: QB64: [Select]
  1. RANDOMIZE MySeed

I'm unable to test on QB45 at the moment.  Can someone else test it?

I've never used RANDOMIZE USING before.
Title: Re: RND and RANDOMIZE information
Post by: Bert22306 on June 12, 2019, 08:58:57 pm
Can’t you just RND(seed) to start the sequence at the start?

PRINT RND(2)
PRINT RND
PRINT RND(2)
PRINT RND

Doesn’t that repeat the cycle?  From what I remember with QB45, it’s how you set the seed — unless I’m getting old and brain damaged.  :P

Don't work for me none. (As they say around your parts :) )

I thought you had stumbled on some amazing new discovery, and then I would have wondered whether it also applies to QBasic. But no. It don't work. That is, yes, it shows random numbers, but no, it doesn't repeat from the top.
Title: Re: RND and RANDOMIZE information
Post by: SMcNeill on June 12, 2019, 10:33:47 pm
Don't work for me none. (As they say around your parts :) )

I thought you had stumbled on some amazing new discovery, and then I would have wondered whether it also applies to QBasic. But no. It don't work. That is, yes, it shows random numbers, but no, it doesn't repeat from the top.

It’s because I left the minus out....

PRINT RND(-2)
PRINT RND
PRINT RND(-2)
PRINT RND

*******************

The number after RND is the seed, where with RND(n):
IF n < 0, use n as the set seed value
If n > 0, get the next value from the current seed set
And if 0...  I don’t remember what it’s for.  /blush


EDIT: As per the wiki (http://qb64.org/wiki/RND), a value of 0 returns the last value again.  It repeats the last result, basically.

Title: Re: RND and RANDOMIZE information
Post by: Bert22306 on June 12, 2019, 10:58:02 pm
It’s because I left the minus out....

PRINT RND(-2)
PRINT RND
PRINT RND(-2)
PRINT RND

Wow. Cool. Did that also work in QBasic?
Title: Re: RND and RANDOMIZE information
Post by: SMcNeill on June 12, 2019, 11:01:13 pm
It does.  Or should, at least.  ;)
Title: Re: RND and RANDOMIZE information
Post by: MWheatley on June 13, 2019, 07:19:16 am
It does.  Or should, at least.  ;)

See my earlier message re: the test that you asked to be carried out in QB45.  Do you want me to re-run this code?

Malcolm