Announcement

Collapse
No announcement yet.

Rnd2 disscussion

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

    What are your thoughts about macro names along the lines of...

    RND2MIZE -- uses timer as seed
    RND2MIZE1 -- uses John's wild wheel method as seed
    RND2TRUE -- " " "
    RND2MIZE2 -- uses David's method to get MS's crypto seeds
    RND2CSEED -- " " " ( or maybe RND2CRSD or RND2CRYPT )
    RND2MIZE3 -- uses default fixed seed
    RND2DFLT -- " " "
    RND2MIZE [ ## ] -- uses the provided number as seed
    RND2REDO -- repeats sequence from a bookmarked value
    RND2MARK -- creates a bookmark
    RND2TOGN -- toggles the +/- flag for RND2() ( or maybe RND2TNEG)

    Regarding the RND2(#) functions... can we switch #s 2 and 6? I'd just as soon have the two main seeding options be sequential in their numbering.

    Comment


      Dave, I have no idea why the IF...THEN slowed it so much, but when removed, back up to speed it went.
      On first look, your asm seems fine to me. I'll try to run it thru its paces. I'm no asm expert either, but in the quest for speed, "The power of asm compels me. The power of asm compels me." (Halloween, Shocktober, Linda Blair and all )

      So, y'all wanna dump rnd2(7)? Okay, heap gone. I originally added it because it was so easy being already set up, and it's really like a 2nd deterministic random generator statistically. I was thinking, "The more, the merrier." The tough part is dumping the documentation! :coffee2:

      Gary said: I'm not seeing mathematically how it can randomly produce the "tails" near -1, 0, and +1. I'll keep on pondering...
      I postulated earlier that the max consecutive values would produce &hfffffffffe000000 (&hffffffff followed by mwcSoph - 2) but I'm thankfully wrong about that one. I ran an overnight sim with code that checks at the posts (Gary, it's like the code I posted earlier #175) to see what happens after mwcRandom hits &hffffffff. As soon as it hits it, I save the very next mwcRandom to look for max and min limits. In ~250 hits, the max was 4277181659, way over my mwcSoph 4221732234 value. So probably the top limit is near &hfffffffe after hitting a &hffffffff. The min. was 80307357 in the test. The plot is below.

      If either of you want to try zero (that is, after mwcRandom = 0, what is the next mwcRandom), your machines are 7x faster so you'd get way more data than I, here is the code.
      Code:
      #COMPILE EXE
      #DIM ALL
      #REGISTER NONE
      
      FUNCTION PBMAIN () AS LONG
      
          LOCAL mwcSoph, mwcRandom, mwcCarry, x AS DWORD
      '    PROCESS SET PRIORITY &H00000040
          mwcSoph   = 4221732234
          mwcRandom = 2946299219      'any but &hffffffff or 0
          mwcCarry  = 1547973028      '     "        "
          DO
             redo:
               !mov eax, mwcSoph
               !mov ecx, mwcRandom
               !mul ecx
               !Add eax, mwcCarry
               !adc edx, 0
               !mov mwcRandom, eax
               !mov mwcCarry,  edx
      '      !cmp eax, &hffffffff
             !cmp eax, 0
             !jne short redo
             GOSUB gsNextRnd2Long
             !mov x, eax
                retry2:
                TRY
                   OPEN "c:\mwcRandomLimits0.txt" FOR APPEND AS #1
      '            PRINT #1, "mwcRandom = &hffffffff  nextMwcRandom ="; x
                   PRINT #1, "mwcRandom = 0           nextMwcRandom ="; x
                CATCH
                   SLEEP 100
                   GOTO retry2
                END TRY
                CLOSE #1
             LOOP
      
      gsNextRnd2Long:
               !mov eax, mwcSoph
               !mov ecx, mwcRandom
               !mul ecx
               !Add eax, mwcCarry
               !adc edx, 0
               !mov mwcRandom, eax
               !mov mwcCarry,  edx
      RETURN
      END FUNCTION
      Attached Files

      Comment


        What are your thoughts about macro names along the lines of...
        I do like shorter! I'll ponder.

        Comment


          Code:
          RND2MIZE -- uses timer as seed                                     OK
          RND2MIZE1 -- uses John's wild wheel method as seed                 2 if default is 1
          RND2TRUE -- " " "                                                  No. It aint true
          RND2MIZE2 -- uses David's method to get MS's crypto seeds          3 if default is 1
          RND2CSEED -- " " " ( or maybe RND2CRSD or RND2CRYPT )              No. Casual users would forget it
          RND2MIZE3 -- uses default fixed seed                               1 should be default
          RND2DFLT -- " " "                                                  No. Casual users would forget it
          RND2MIZE [ ## ] -- uses the provided number as seed                OK
          RND2REDO -- repeats sequence from a bookmarked value               OK
          RND2MARK -- creates a bookmark                                     OK
          RND2TOGN -- toggles the +/- flag for RND2() ( or maybe RND2TNEG)   Why not RNDTOGSIGN
          Actually I don't like uppercase.

          Rnd2Mize2, Rnd2Redo, Rnd2Mark is easier to read, for me anyway.

          Regarding the RND2(#) functions... can we switch #s 2 and 6? I'd just as soon have the two main seeding options be sequential in their numbering.
          Yes.
          Last edited by David Roberts; 24 Oct 2008, 09:15 AM.

          Comment


            Not sure if we are talking about the same thing but ...

            Going back to John's post #164 he reckoned the odds of getting greater than or equal to 0.999999999989856264 were 98 billion to 1 against.

            Suppose we divide a rectangular distribution 0 to 1 into 4

            Code:
                1      2      3      4
            |......|......|......|......|
            and ask what are the odds of being in 4. Clearly they are 3 to 1 against.

            With 0.999999999989856264 we have 0.999999999989856264/(1-0.999999999989856264) = 9.858E10 which is approximately 98 billion to 1 against as opposed to 86.3 billion to see 0.99999999999856264.

            How about 7 to 9 leading 9's after the decimal point as mentioned in your post #190, Gary.

            7: 0.9999999/(1-0.9999999) = 9999999 ~ 10 million to 1 against
            8: 0.99999999/(1-0.99999999) = ~ 100 million to 1 against
            9: ~ 1 billion to 1 against

            I did a 100 run on seeing how many Rnd2()'s to clear 7: The average was 9.38 million. With 8: the average was 107.42 million.

            So, nothing out of the ordinary to justify a statistical analysis.

            Comment


              I like mixed case too on the naming.

              I ran 35 hits for the next mwcRandom after mwcRandom = 0 using post #202. Nothing to see here.
              Attached Files

              Comment


                I'm not so much stuck on the statistics of how often we'll see 6-10 leading 0s or 1s... I'm troubled by the seeming likelihood that back-to-back outputs from one mwc generator won't go too much further. Like I said, I'm still pondering... And filling up some pages with algebraic expressions. I'd prefer to have a few things straight before wasting your time.

                I do need to mention one thing on the evaluation of what mwcRandom will follow a 00000000, or 7FFFFFF, or FFFFFFFF, or 80000000. At the moment, we're loading that first gsRandomLong value into the LO DWORD of 'eq'. Your test code is more meaningful for evaluations if we move that first value into the _HI_ DWORD. Swap the loading order, but please don't do any other drastic changes for now. (FYI, I have run the simulator a bit for some of the other necessary first DWORD scenarios.)

                Please help me research two items. (1) How many tix does it take to do SHR reg32, 1 ? (2) What is the speed difference between FLD and FLID ?

                Comment


                  Main changes are: 1) Macro instead of gosub for the generator. 2) Rename Macros. 3) Removed Rnd2Crypto. 4) Redid much of the docs. Dave, didn't test your new asm yet, so that code didn't change.
                  Rnd2TC3.inc
                  Code:
                  'Rnd2TC3.inc used for Rnd2() function and macros. "Rnd2TrueCrypto"
                  
                  %USECRYPTO = 1  'If you have a PB version earlier than ver9/5, or if you don't need to use the
                                  'Crypto features, set to zero. If using Crypto features, place the statement
                                  'Rnd2goCrypto at the top of PBMAIN, and the statement Rnd2stopCrypto at the bottom.
                  
                  MACRO Rnd2goCrypto       'Rnd2goCrypto to be placed at the top of PBMAIN
                    #IF %USECRYPTO
                      LOCAL os AS OSVERSIONINFO, strOS AS STRING
                      os.dwOSVersionInfoSize=SIZEOF(os)
                      GetVersionEx os
                      IF os.dwPlatformId = %VER_PLATFORM_WIN32_NT THEN
                        strOS = TRIM$(STR$(os.dwMajorVersion)) & "." & TRIM$(STR$(os.dwMinorVersion))
                        IF strOS > "5.0" THEN ' we have XP/Vista/Server 2003 or 2008
                          LET GetCrypto = CLASS "CSpeedyCryptoRand"
                        ELSE
                          LET GetCrypto = CLASS "CCryptoRand"
                        END IF
                      ELSE
                        LET GetCrypto = CLASS "CCryptoRand"
                      END IF
                    #ENDIF
                  END MACRO
                  
                  MACRO Rnd2stopCrypto     'Rnd2stopCrypto to be placed at the bottom of PBMAIN
                    #IF %USECRYPTO
                      GetCrypto = NOTHING
                    #ENDIF
                  END MACRO
                  '----------------------------------------------------------------------------
                  
                  DECLARE FUNCTION QueryPerformanceFrequency LIB "KERNEL32.DLL" ALIAS "QueryPerformanceFrequency" _
                        (lpFrequency AS QUAD) AS LONG
                  DECLARE FUNCTION CryptAcquireContext LIB "advapi32.dll" ALIAS "CryptAcquireContextA" _
                        ( hProv AS LONG, zContainer AS ASCIIZ, zProvider AS ASCIIZ, _
                           BYVAL dwProvType AS DWORD, BYVAL dwFlags AS DWORD ) AS LONG
                  DECLARE FUNCTION CryptReleaseContext LIB "advapi32.dll" ALIAS "CryptReleaseContext" _
                        ( BYVAL hProv AS LONG, BYVAL dwFlags AS DWORD ) AS LONG
                  DECLARE FUNCTION CryptGenRandom LIB "advapi32.dll" ALIAS "CryptGenRandom" _
                        ( BYVAL hProv AS LONG, BYVAL dwLen AS DWORD, pbBuffer AS BYTE) AS LONG
                  DECLARE FUNCTION RtlGenRandom( RandomBuffer AS BYTE, BYVAL RandomBufferLength AS DWORD ) AS LONG
                  
                  #IF %USECRYPTO
                    GLOBAL GetCrypto AS ICryptoRand
                  
                    CLASS CCryptoRand
                  
                      INSTANCE hProv AS DWORD
                  
                      CLASS METHOD CREATE
                        LOCAL Prov_Rsa_Full, Flags AS DWORD
                        DIM MS_Def_Prov AS ASCIIZ * 50
                  
                        Prov_Rsa_Full = 1
                        Flags = &hF0000000
                        MS_Def_Prov = "Microsoft Base Cryptographic Provider v1.0"
                  
                        CryptAcquireContext( hProv, BYVAL %Null, BYVAL %Null, Prov_Rsa_Full, Flags )
                        CryptAcquireContext( hProv, BYVAL %Null, MS_Def_Prov, Prov_Rsa_Full, Flags )
                      END METHOD
                  
                      CLASS METHOD Destroy
                        CryptReleaseContext hProv, 0
                      END METHOD
                  
                      INTERFACE ICryptoRand: INHERIT IUNKNOWN
                  
                        METHOD Bytes( x AS EXT) AS LONG
                          DIM BinaryByte(9) AS STATIC BYTE ' John Gleason tip
                  
                          CryptGenRandom( BYVAL hProv, 10,  BinaryByte(0))
                          x = PEEK( EXT, VARPTR( BinaryByte(0)))
                  
                        END METHOD
                  
                      END INTERFACE
                  
                    END CLASS
                  
                    CLASS CSpeedyCryptoRand
                  
                      INSTANCE hLib, hProc AS DWORD
                  
                      CLASS METHOD CREATE
                        hLib = LoadLibrary( "advapi32.dll")
                        hProc = GetProcAddress(hLib, "SystemFunction036")
                      END METHOD
                  
                      CLASS METHOD Destroy
                        FreeLibrary hLib
                      END METHOD
                  
                      INTERFACE ICryptoRand: INHERIT IUNKNOWN
                  
                        METHOD Bytes(x AS EXT) AS LONG
                          DIM BinaryByte(9) AS STATIC BYTE ' John Gleason tip
                  
                          CALL DWORD hProc USING RtlGenRandom( BinaryByte(0), 10 )
                          x = PEEK( EXT, VARPTR( BinaryByte(0)))
                  
                        END METHOD
                  
                      END INTERFACE
                  
                    END CLASS
                  #ENDIF
                  
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  ' Rnd2 Macros
                  MACRO Rnd2mize           = Rnd2(1)                       'WildWheel© seed the random number generator.
                  MACRO Rnd2mizeCrypto     = Rnd2(2)                       'cryptographically seed the random number generator
                  MACRO Rnd2Long           = Rnd2(-2147483648, 2147483647) 'commonly used full LONG range
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  ' Rnd2 Additional Macros
                  MACRO Rnd2LastNum        = Rnd2(0)                       'get last random generated.
                  MACRO Rnd2Default        = Rnd2(3)                       'set or reset to default sequence
                  MACRO Rnd2Redo           = Rnd2(4)                       'repeat from beginning of seq, or last bookmarked position
                  MACRO Rnd2Mark           = Rnd2(5)                       'save position in a sequence
                  MACRO Rnd2TogSign        = Rnd2(6)                       'turn on/off EXT random range -1 to 1 exclusive.
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  MACRO mRandomLong
                     !mov eax, mwcSoph
                     !mov ecx, mwcRandom
                     !mul ecx
                     !Add eax, mwcCarry
                     !adc edx, 0
                     !mov mwcRandom, eax
                     !mov mwcCarry,  edx
                  END MACRO
                  
                  MACRO mTSCplusQPC
                     !cpuid        ;serialize
                     !dw &h310f    ;read time stamp counter
                     !ror eax, 1   ;smooth because some processors are always even low bit
                     !mov rndL,eax ;save because QPC overwrites registers
                     QueryPerformanceCounter eq
                     !mov eax, eq  ;LO dword
                     !ror eax, 1   ;smooth, low bit might always be even on some cpu's
                     !add eax, rndL;smoothed QPC + saved smoothed TSC
                  END MACRO
                  
                  FUNCTION Rnd2( OPT One AS LONG, Two AS LONG ) AS EXT
                  '-----------------------------------------------------------------------------------------
                    'I modified this function in an attempt to enhance Dave Robert's comprehensive Rnd2 posted earlier here by making it
                    '1) as exactly like RND as possible, 2) as fast as possible, while maintaining 3) random no matter how initiated & used.
                    'This function can replace PowerBasic RND function entirely I believe, and has almost the same syntax.
                    'A major difference between Rnd2 and RND is that Rnd2 has WildWheel© ;) initialization. Say what? Well read on.
                    'What are WildWheel numbers?:
                    'Some say true randomness doesn't exist, but eg. radioactive decay makes a strong case for true randomness. So Rnd2
                    'uses the natural radioactive decay of gallium arsenide isotopes in your CPU to create WildWheel numbers.
                    'Hey, just kidding. There are rapid, cycling timers in your computer, and it helps to think of them as crazy spinning
                    'wild wheels. WildWheel numbers actually get their randomness from slight timing variations that occur during
                    'eg. memory fetches, context switching, interrupt calls, hard drive head seeks--really anything that takes slightly
                    'varying amounts of time on your computer, which is actually...everything! WildWheel then multiplies these "jitter"
                    'differences HUGELY, and also accumulates them so they compound one another. This "time static" let's call it, works
                    'its magic and voila!, statistically random real-time numbers. The technique to code for WildWheel numbers is shown
                    'in the dice example below (see "1 argument").
                    'Floating point mode:
                    'Rnd2 returns a random value that is less than 1, but greater than or equal to 0. Numbers generated by Rnd2 CAN
                    'be "really" random, or can apply a pseudo-random transformation algorithm to a starting ("seed") value. Given the
                    'same seed, Rnd2 always produces the same sequence of "random" numbers. The random value is calculated
                    'internally as an extended precision representation so it can be readily used in any situation. Rnd2 has a period of
                    'at least 2^61, and if you re-seed it every few hundred years, up to ~2^70. That's 200 billion times larger than
                    'RND's period of ~2^32. All 18 digits of Rnd2 are significant.
                    'Integer Range mode:
                    'Rnd2(a, b) returns an extended value equal to a Long-integer in the range of a to b inclusive.
                    'a and b can each be a numeric literal or a numeric expression that evaluates within the range of a Long-integer
                    '(-2,147,483,648 to 2,147,483,647). The fastest mode of Rnd2 is Rnd2(-2147483648, 2147483647) which is equal to
                    'the MACRO Rnd2Long for convenience. All digits/bytes/bits in integer mode are significant.
                    'Special effects mode:
                    'When used with a single LONG numeric expression argument, the value returned by Rnd2 depends on the optional LONG
                    'numeric value you supply as the argument, as follows:
                    'No argument: Rnd2 generates the next number in sequence based on the initial seed value.
                    '0 argument : Rnd2 repeats the last number generated.
                    '- argument : negative argument causes the random number generator to be re-seeded and returns the first value in the
                    '             new sequence. Subsequent uses of Rnd2 with no argument continues the new sequence.
                    '             Different neg LONG arguments guarantee non-duplicate sequences for each integer -1 thru -2147483648
                    '             so you can select your own repeatable sequences from the 2Gig available. This gives a similar
                    '             functionality to the PB statement "RANDOMIZE number" but without dupe sequences.
                    'o-o--o-o--o The following arguments 1 thru 5 are special Rnd2 effects o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o
                    '1 argument : re-seeds the generator in a WildWheel way so its next number will be eg. like really throwing dice.
                    '             More calls with no argument use the internal pseudo-random algorithm to continue the series, HOWEVER,
                    '             unlike RND, you can call Rnd2(1) aka. Rnd2mize over and over at will to keep generating WildWheel
                    '             random numbers. For example:
                    '               DO: Rnd2mize: ? STR$(Rnd2(1, 6)): Rnd2mize: ? STR$(Rnd2(1, 6)): LOOP
                    '               or its equivalent:
                    '               DO: Rnd2(1): ? STR$(Rnd2(1, 6)): Rnd2(1): ? STR$(Rnd2(1, 6)): LOOP
                    '             is effectively just like rolling real dice in real time with no dependency on any pseudo-random algorithm!
                    '             Actually, real rolled dice would likely have to be manufactured with ultra precision to statistically
                    '             match the distribution of the above code. :o) Rnd2(1) uses ~6000 tix per call. Note that after calling
                    '             Rnd2mize, ONLY the very next Rnd2() call with either no parameters, or with a 2-parameter integer range
                    '             will be WildWheel©. Further calls without re-seeding become RAPIDLY DETERMINISTIC.
                    '2 argument : Toggles Rnd2 to return a random value that is greater than -1 and less then 1, represented (-1,1).
                    '             Next use toggles back to less than 1, but greater than or equal to 0, ie. [0,1).
                    '3 argument : Rnd2 returns its default sequence.
                    '4 argument : repeat last sequence or bookmarked sequence.
                    '5 argument : bookmark the position in current sequence.
                    'o-o--o-o--o Crypto Function o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o
                    '6 argument : Generates a cryptographically secure random seed value for the random number generator. After seeding, ONLY
                    '             the 1st call to Rnd2() with either no parameters, or with a 2-parameter integer range will be secure. Further
                    '             calls without re-seeding become RAPIDLY INSECURE. You may ask, "But how secure is that 1st Rnd2() call? Here
                    '             is what we know: There is a vulnerability in Win2000 CryptGenRandom which found its way into WinXP. It
                    '             did not find its way into Vista and it was fixed in WinXP SP3. Win2000 is still at risk. However, MS whilst
                    '             acknowledging the flaw reckoned that an exploitation required exceptional if not nigh on impossible
                    '             circumstances; but then they would, wouldn't they? CryptGenRandom is used in IE for SSL purposes and such
                    '             like. If it is not to be used in a secure environment then the risk is obviously academic.
                    '>6 argument: Rnd2 generates the next number in sequence based on the initial seed value.
                    'o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o-o--o
                    'Do not use 0, 2 thru 5, or negative value arguments in special effects mode unless you are looking for the special
                    'effects those argument values produce. And remember Rnd2(1) uses ~6000 tix doing its tuff task.
                    'The random number generator can be reset back to the default seed using the following statement: Rnd2(3)
                    'Speed:
                    'Try as we might to make it faster, in PB9, Rnd2 with no arguments is about the same speed as RND.
                    'Reasons to use Rnd2:
                    '1)Will likely never repeat a sequence even if run for years--hundreds of years. Has a big period.
                    '2)Integer mode is much faster.
                    '3)Works almost just like RND so quick learning curve.
                    '4)Can use Rnd2mize/Rnd(1) or Rnd2mizeCrypto/Rnd(2) whenever the heck fire you please, eg. to make WildWheel numbers.
                    '  Rnd2 is very forgiving, so no matter what you do (almost), you are going to get the fine random sequences you imagined.
                    '5)Can return +/- EXT randoms using Rnd2TogSign/Rnd2(6) to switch it on/off.
                    '6)All digits are statistically random; they pass all known tests for randomness. Rnd2() has a few limitations in
                    '  theory, but the odds of ever encountering one are tiny.
                  '-----------------------------------------------------------------------------------------
                  #REGISTER NONE
                  STATIC oneTime, rndL AS LONG, eq AS QUAD
                  STATIC storeState AS STRING * 12
                  STATIC mwcSoph AS DWORD, rndE AS EXT
                  STATIC mwcRandom, mwcCarry, TogScope AS LONG  'mwc prefix means "multiply with carry" random generator based on theory
                                                                'by George Marsaglia and is the fastest generator known to man. A man. Me. ;)
                    !lea eax, Two
                    !mov ecx, [eax]
                    !cmp ecx, 0
                    !jne twoParams      ;if optional parameter Two passed, belt down to integer Rnd2 code section
                    !lea eax, One
                    !mov ecx, [eax]
                    !cmp ecx, 0
                    !je noParams        ;if no params, boogie down to noParams code
                  
                    'we got here so there must be 1 parameter
                          SELECT CASE AS LONG One
                  
                            CASE 1          ' Rnd2mize. tot possible unique sequences = &hffffffff * &hedffffff * 384
                                            ' which = 6.6 * 10^21. This excess of initial sequences allows you to
                                            ' freely use Rnd2mize/Rnd(1) at will to give WildWheel numbers.
                               oneTime = 1
                               mTSCplusQPC             'add time stamp counter and queryPerfCounter, both !ror 1
                               !mov ecx, 384           ;384 possible sophie-germain multipliers
                               !mov edx, 0             ;clear edx for division
                               !div ecx                ;random remainder (MOD 384) in edx now
                               !lea ecx, multiplier    ;codeptr to 384 multipliers
                               !mov ecx, [ecx+edx*4]   ;got rnd soph germain multiplier now
                               !mov mwcSoph, ecx       ;save it
                               SLEEP 0                 'considered QPC too because rarely, this can slow 20x. Can be like idle priority.
                               mTSCplusQPC             'add time stamp counter and queryPerfCounter, after both !ror 1
                               !mov mwcRandom, eax     ;save. Now make sure mwcCarry <> mwcSoph(from above) - 1 or 0.
                              '---------------------
                               !cmp mwcCarry, 0        ;if value is already present, use it as a "memory" of previous loops
                               !ja short mwcCarNot0
                               SLEEP 0
                               mTSCplusQPC             'add time stamp counter and queryPerfCounter, both !ror 1
                               !mov mwcCarry, eax      ;4 billion+ carrys now possible
                               !jnc short mwcCarNot0   ;ok if <> 0 after add, but if there's a carry, add a constant to be sure it's <> 0
                               !mov mwcCarry,&h1234abcd;it was zero! so make it your choice of a constant
                              mwcCarNot0:
                               !mov ecx, mwcSoph
                               !sub ecx, 1             ;mwcSoph - 1
                               !cmp mwcCarry, ecx      ;is carry >= mwcSoph - 1 ?
                               !jb  short mwcAllOk     ;if not, we're done
                               !and mwcCarry,&h7fffffff;make it less than mwcSoph - 1
                              mwcAllOk:
                               mRandomLong    ' Shuffle mwcRandom a bit more and shuffle mwcCarry
                               GOSUB gsStoreSeq
                  
                            CASE 0            ' Repeat the last number generated
                              FUNCTION = rndE ' will, of course, be zero if no rndE calculated yet
                              EXIT FUNCTION
                  
                            CASE 6           'make it 50/50 + and -
                              TogScope = NOT TogScope
                  
                            CASE <= -1       ' Guarrantees a non-duplicate sequence for each integer -1 thru -2147483648
                                             ' so you can select your own repeatable sequences from the 2Gig available. This gives a
                                             ' similar functionality to the PB statement "RANDOMIZE number" but without dupe sequences.
                              mwcSoph = PEEK(DWORD, CODEPTR(multiplier) - (One MOD 384) * 4)
                              mwcRandom = &h55b218da - One 'assures maximum possible 2147483648 unique sequences
                              mwcCarry  = &h3fe8700c
                              GOSUB gsStoreSeq
                              oneTime = 1
                              GOTO noParams
                  
                            CASE 3                ' Rnd2Default seq
                               GOSUB gsDefaultSeq
                  
                            CASE 4                ' Rnd2Redo  repeat from beginning of seq, or last bookmarked position
                              IF mwcSoph = 0 THEN ' there wasn't a last sequence so use default
                                GOSUB gsDefaultSeq
                              ELSE                ' read saved values from storeState string.
                                mwcSoph    = PEEK(DWORD, VARPTR(storeState    ))
                                mwcRandom  = PEEK( LONG, VARPTR(storeState) + 4)
                                mwcCarry   = PEEK( LONG, VARPTR(storeState) + 8)
                              END IF
                  
                            CASE 5                ' Rnd2Mark is like a bookmark
                              GOSUB gsStoreSeq
                  
                  #IF %USECRYPTO
                            CASE 2                ' Rnd2mizeCrypto
                              oneTime = 1
                              !fld tbyte rndE        ;save rndE for a moment
                            reSeedCrypt:
                              GetCrypto.Bytes(rndE)  'Use rndE as a temporary buffer and populate with 10 cryptographic bytes.
                              mwcRandom = PEEK(DWORD, VARPTR(rndE))
                              mwcCarry  = PEEK(DWORD, VARPTR(rndE) + 4)
                              mwcSoph   = PEEK( WORD, VARPTR(rndE) + 8)
                              mwcSoph = PEEK(DWORD, CODEPTR(multiplier) + (mwcSoph MOD 384) * 4) 'get soph prime
                              IF (mwcCarry = 0 AND mwcRandom = 0) OR ((mwcCarry = mwcSoph -1) AND mwcRandom = &hffffffff) GOTO reSeedCrypt
                              !fstp rndE             ;restore rndE
                              GOSUB gsStoreSeq
                  #ENDIF
                            CASE ELSE
                              GOTO noParams          ' + number > 6, so just generate another EXT rnd
                  
                          END SELECT
                  
                        FUNCTION = 0 ' OK
                        EXIT FUNCTION
                  
                        gsDefaultSeq:                'gs prefix means this is a GOSUB sub
                          oneTime = 1
                          mwcSoph = 4221732234
                          mwcRandom = &ha5b218da     ' can be any LONG except &hffffffff and 0
                          mwcCarry  = &h3fe8700c     ' can be any number except (mwcSoph-1) and 0
                          GOSUB gsStoreSeq
                        RETURN
                  
                        gsStoreSeq:                  'save original starting point of sequence in 12-byte storeState string. This is more
                                                     'efficient than creating three separate variables with higher function-call overhead.
                          !lea eax, storeState       ;str address
                          !mov ecx, mwcSoph
                          !mov edx, mwcRandom
                          !mov [eax+0], ecx          ;save mwcSoph in storeState str.
                          !mov ecx, mwcCarry
                          !mov [eax+4], edx          ;save mwcRandom
                          !mov [eax+8], ecx          ;save mwcCarry
                        RETURN
                  
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                    twoParams:   ' both optional parameters passed so it's an integer range which can be quickly calculated...
                        IF oneTime = 0 THEN GOSUB gsDefaultSeq
                        !push ebx
                        !mov eax, One
                        !mov ebx, Two
                        !mov eax, [eax]      ;dereference One
                        !mov ebx, [ebx]      ;   "        Two
                        !cmp eax, ebx        ;is One > Two?
                        !jg short oneGtTwo   ;jump if One > Two
                        !sub ebx, eax        ;now ebx is range
                        !cmp ebx, &hffffffff ;is it max?
                        !jne short rangeNotMax
                        !jmp short doTheRnd
                       oneGtTwo:             'swap and do like above
                                             'Thanks Gary Ramey for pointing out we don't want to change the value of parameter One...
                        !mov edx, ebx        ;copy range to ebx
                        !sub eax, ebx        ;now eax holds range
                        !cmp eax, &hffffffff ;max?
                        !mov ebx, eax        ;save eax because gsRandomLong overwrites it. Now ebx holds range
                        !mov eax, edx        ;eax contains Two now
                        !jne short rangeNotMax
                        'above asm does this:
                  '     IF One > Two THEN use Two as low bound instead of One,
                  '     so range = Two - One or range = One - Two depending.
                  '     IF range <> &hffffffff GOTO rangeNotMax
                       doTheRnd:
                        !pop ebx
                        mRandomLong          'get a rndL
                        !mov rndL, eax       ;range is max, ie. any LONG integer is wanted, so since that is just what gsRandomLong does...
                        !fild rndL           ;give the function the direct feed. This is now by far the fastest return from Rnd2.
                        !fld st(0)
                        !fstp rndE           ;save for repeat last random--Rnd2(0)
                        !fstp FUNCTION       ;save to FUNCTION
                        EXIT FUNCTION
                  
                       rangeNotMax:
                        !mov rndL, eax       ;save low bound from above
                        rndE = .5            'ok as a single, stored as exactly .5000000000000000000
                        !add ebx, 1          ;we want range to be inclusive, eg. Rnd2(1,6) gives 1,2,3,4,5,6 evenly randomized
                        mRandomLong          'get a random into eax
                  
                        !fld rndE
                        !lea ecx, rndE
                        !lea edx, eq
                        !mov dword ptr[ecx],    &hffffffff ;save 2.328306436538696289e-10 in rndE--EXT image of 1 / 4294967296. <<max DWORD+1
                        !mov dword ptr[ecx+4],  &hffffffff ;             "
                        !mov  word ptr[ecx+8],  &h3fde     ;             "
                        !mov [edx], eax        ;save the random DWORD in LO(eq)
                        !mov dword ptr[edx+4],0;zero HI(DWORD, eq)
                                               'Locked and loaded. We have ebx=range, eq=rand dword, rndE=divisor, so
                                               'the following asm will do: FUNCTION = rand * (1 / 4294967296) * range
                        !fld rndE              ;load 1 / 4294967296 into float reg
                        !fild qword eq         ;load rand DWORD into float register
                        !fmulp st(1),st(0)     ;effectively rand dword / 4294967296 without division
                        !mov eq, ebx           ;save the range in ebx to LO(eq). HI(eq) is zero already
                        !fild qword eq         ;load range DWORD into float register
                        !fmulp st(1),st(0)     ;now makes range a rand % of original range
                        !fsub st(0),st(1)      ;sub .5 so when it rounds, high and low bounds are correct
                        !fistp eq              ;save in eq. only LO(eq) will be used
                        !mov ecx, rndL         ;get low range bound
                        !fstp st(0)            ;pop .5 off
                        !mov edx, eq           ;ok because LO only used
                        !add ecx, edx          ;add random value to it within range specified. This is: rndL = One + range
                        !mov rndL,ecx          ;finish rndL = One + range
                        !pop ebx
                  
                        !fild rndL
                        !fld st(0)
                        !fstp rndE           ;save for repeat last random--Rnd2(0)
                        !fstp FUNCTION       ;save to FUNCTION
                        EXIT FUNCTION
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                   noParams:     ' no optional parameters passed, so calculate EXT rnd...
                    IF OneTime = 0 THEN GOSUB gsDefaultSeq ' otherwise start crunching
                    mRandomLong               'sub to generate LONG rnd value
                    !lea ecx,   eq
                    !mov [ecx], eax           ; = POKE LONG, eqPtr,     rndL
                    mRandomLong               'sub to generate LONG rnd value
                    !lea ecx,     eq
                    !mov [ecx+4], eax         ; = POKE LONG, eqPtr + 4, rndL
                  
                    okQuadRnd:                'now we have a complete rand quad in eq
                      !fild qword eq          ;float load eq which is now a complete quad random
                      !cmp togScope, 0        ;do we need to make it 50/50 + and - ?
                      !jne short rndNeg       ;jump if we do.
                      !fabs                   ;make it +
                    rndNeg:
                      '---------------------  'now take the quad and divide by 9223372036854775816, and it perfectly ranges from [0,1) or (-1,1)
                      !lea ecx, rndE          ;space to hold the constant 1084202172485504433 * 10E-36 (yes I even made it 19 digits)
                      !mov dword ptr[ecx],   &hffffffef ;...-36 save in rndE. This is a binary image of the extended precision ...-36
                      !mov dword ptr[ecx+4], &hffffffff ;             "
                      !mov  word ptr[ecx+8], &h3fbf     ;             "
                      !fld tbyte [ecx]        ;float load ...-36
                      !fmulp st(1),st(0)      ;eq * ...-36 to range rnd to [0,1). This = eq / 9223372036854775816 but is much faster
                      !fld st(0)              ;copy final answer
                      !fstp rndE              ;save copy
                      !fstp FUNCTION          ;save FUNCTION
                  
                  EXIT FUNCTION
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  
                  multiplier: 'a bunch of Sophie Germain primes. Each makes its own unique sequence of ~2^63 LONG random values
                  !DD 4055108289, 4183291290, 4066422669, 4010830218, 4144557798, 4047225099, 4169878863, 4156378278
                  !DD 4068734223, 4013003148, 4128794349, 4044603045, 4147482834, 4050081738, 4169007204, 4084483623
                  !DD 4182936234, 4061167764, 4116557445, 4184835774, 4098609075, 4000058700, 4005596580, 4131991143
                  !DD 4026365904, 4082490609, 4170263943, 4064971044, 4192040679, 4069686423, 4112450355, 4116008373
                  !DD 4051352658, 4131639393, 4026209880, 4143019908, 4057560153, 4153038378, 4178347353, 4101943515
                  !DD 4163817693, 4126770675, 4122227184, 4150506573, 4124871525, 4097114355, 4171215009, 4094254353
                  !DD 4185190458, 4184112513, 4187782989, 4037092584, 4114448259, 4096721880, 4003880118, 4035500259
                  !DD 4080989598, 4090215738, 4104202098, 4144153608, 4027213065, 4112123319, 4029634383, 4188620745
                  !DD 4003957254, 4158202674, 4165028370, 4101889029, 4064867064, 4056294705, 4117302630, 4094813610
                  !DD 4089078504, 4072584339, 4075250574, 4144182519, 4020827805, 4077052605, 4012941570, 4114015830
                  !DD 4015303260, 4012049835, 4031934513, 4123667379, 4025171265, 4149021864, 4020494469, 4152989853
                  !DD 4141465314, 4050172164, 4130534940, 4124347128, 4155032220, 4123523313, 4038610005, 4066391700
                  !DD 4052359893, 4138494750, 4046848368, 4015233183, 4065337650, 4181156010, 4149686553, 4115669703
                  !DD 4080411408, 4029985884, 4072279314, 4136476293, 4102312674, 4148638644, 4020161274, 4056852945
                  !DD 4084467288, 4090139205, 4152479904, 4129623354, 4189154793, 4042650633, 4113056934, 4070634510
                  !DD 4172190345, 4012616748, 4092782529, 4042027470, 4034320863, 4017110193, 4128178095, 4005317820
                  !DD 4121565819, 4160465475, 4093432608, 4094047308, 4092039654, 4132108680, 4160799915, 4109110719
                  !DD 4190254803, 4063105479, 4123739478, 4086096945, 4113466908, 4169157873, 4036670034, 4035486873
                  !DD 4154194098, 4074334704, 4006945965, 4119880785, 4050935955, 4131729105, 4170646809, 4191996963
                  !DD 4055775498, 4029162399, 4118132214, 4116397584, 4121266560, 4102454433, 4146555864, 4103353149
                  !DD 4119974010, 4080379233, 4192378968, 4061071950, 4104928533, 4042978743, 4188739878, 4066717740
                  !DD 4017709695, 4027617453, 4110604308, 4107339654, 4076278878, 4077074274, 4097495403, 4179562659
                  !DD 4187765853, 4187454249, 4015793904, 4083863454, 4078492929, 4166495943, 4101303048, 4149525330
                  !DD 4095286830, 4078227909, 4189944624, 4010811645, 4032304584, 4151394078, 4044317298, 4136517915
                  !DD 4198354635, 4192501860, 4073134869, 4060180830, 4076815050, 4190613315, 4142749785, 4122567564
                  !DD 4071542523, 4024430004, 4122798648, 4041267495, 4006243575, 4092566124, 4141397349, 4175565558
                  !DD 4159829190, 4173505479, 4084339563, 4085131608, 4081507743, 4069428324, 4011038568, 4092438129
                  !DD 4005482298, 4020895359, 4127615184, 4162803795, 4038272028, 4123171464, 4199942199, 4067713245
                  !DD 4129181838, 4021766328, 4141102845, 4002607668, 4051580310, 4082443044, 4078962945, 4072199883
                  !DD 4180693749, 4040763375, 4025696004, 4066226853, 4013137770, 4084688994, 4081465923, 4185884010
                  !DD 4184193840, 4095653625, 4071642489, 4003011123, 4021708860, 4038391383, 4003548888, 4016275635
                  !DD 4051483344, 4052001093, 4131504594, 4129105653, 4187278653, 4058921709, 4167113355, 4106971188
                  !DD 4074045393, 4069825200, 4009724565, 4120937589, 4119577560, 4151390115, 4000637598, 4088788530
                  !DD 4014859458, 4003633353, 4192075623, 4009856424, 4048255155, 4100175633, 4129717695, 4012882215
                  !DD 4119226824, 4122492603, 4074693864, 4062187338, 4022104890, 4186039455, 4191285474, 4165800789
                  !DD 4047934929, 4045886208, 4028478450, 4098395724, 4095869853, 4004229753, 4110500373, 4188458055
                  !DD 4093944063, 4122368673, 4136075109, 4024434645, 4145270010, 4121262090, 4051650480, 4076720613
                  !DD 4057135713, 4053301650, 4074379569, 4103950185, 4146078999, 4029125490, 4036104003, 4122595203
                  !DD 4173008610, 4155931704, 4048316175, 4178853645, 4049069715, 4187855514, 4193714559, 4132340133
                  !DD 4001184978, 4087342068, 4038996009, 4032782589, 4103313705, 4057212699, 4094324010, 4117022988
                  !DD 4016133978, 4057176333, 4081210119, 4183410330, 4054406019, 4008415374, 4131217578, 4049176725
                  !DD 4033804230, 4154677353, 4194818769, 4057689999, 4065887250, 4083913149, 4160269749, 4148719650
                  !DD 4086572148, 4079152770, 4198797849, 4025836533, 4121774838, 4114818903, 4193265369, 4005720123
                  !DD 4172736744, 4113446385, 4153872675, 4022863908, 4169665353, 4080875223, 4148976378, 4158173325
                  !DD 4012107315, 4146530883, 4042645638, 4189878099, 4075365840, 4053276279, 4112504730, 4144260888
                  !DD 4102144035, 4181673825, 4171915968, 4123257354, 4032551355, 4054454535, 4132616253, 4057321905
                  !DD 4174490559, 4165419468, 4169862234, 4116771594, 4009920498, 4164231630, 4163597154, 4181713095
                  !DD 4000268439, 4077171264, 4045424718, 4116626304, 4052701140, 4140380880, 4027965249, 4102323183
                  
                  END FUNCTION
                  '
                  Rnd2TCDemo3.bas
                  Code:
                  'Rnd2TCDemo3.bas PBwin tested.
                  'Example code for Rnd2(), a function substitute for RND and RANDOMIZE.
                  #COMPILE EXE
                  #DIM ALL
                  #INCLUDE "win32api.inc"
                  #INCLUDE "Rnd2TC3.inc"
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  ' System Timer Macros
                  GLOBAL qFreq, qOverhead, qStart, qStop AS QUAD
                  GLOBAL f AS STRING
                  
                  MACRO InitializeTimer
                    f = "#####.##"
                    QueryPerformanceFrequency qFreq
                    QueryPerformanceCounter qStart ' Intel suggestion. First use may be suspect
                    QueryPerformanceCounter qStart ' So, wack it twice <smile>
                    QueryPerformanceCounter qStop
                    qOverhead = qStop - qStart     ' Relatively small
                  END MACRO
                  
                  MACRO StartTimer = QueryPerformanceCounter qStart
                  MACRO StopTimer = QueryPerformanceCounter qStop
                  
                  MACRO sTimeTaken = USING$(f,(qStop - qStart - qOverhead)*1000/qFreq) + "ms"
                  MACRO nTimeTaken = (qStop - qStart - qOverhead)*1000/qFreq
                  
                  '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
                  
                  FUNCTION PBMAIN( ) AS LONG
                  LOCAL i, j AS LONG, x AS EXT
                  
                    Rnd2goCrypto
                    InitializeTimer
                  
                   '--------------------------------------------------------------------
                   '--------------------------------------------------------------------
                                  'pb win32
                    LOCAL pStr AS STRING
                     pStr = pStr & "No chosen sequence" & $CRLF
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                    pStr = pStr & $CRLF & "Rnd2DefaultSeq" & $CRLF
                    Rnd2Default
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,,"Default"
                   pStr = ""
                  
                    pStr = pStr & "Rnd2(-1234567890)" & $CRLF
                    pStr = pStr & STR$(Rnd2(-1234567890)) & $CRLF
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2(-1234567891)" & $CRLF
                    pStr = pStr & STR$(Rnd2(-1234567891)) & $CRLF
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 6
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,,"Single Neg LONG Integer"
                   pStr = ""
                  
                    pStr = pStr & "Rnd2mize" & $CRLF
                    Rnd2mize
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,, "Rnd2mize/Rnd2(1)"
                   pStr = ""
                  
                    pStr = pStr & "Rnd2mize, Rnd2TogSign" & $CRLF
                    Rnd2mize
                    Rnd2TogSign
                    FOR i = 1 TO 10
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 10
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                         :pStr = pStr & $CRLF & "**********" & $CRLF  & $CRLF
                   ? pStr,, "Rnd2TogSign: Turn on/off +/- range"
                    Rnd2TogSign
                  
                  
                    pStr = pStr & "Repeat last number generated " & $CRLF & STR$(Rnd2LastNum)
                      '  :pStr = pStr & "**********"
                   ? pStr,, "Last # Generated"
                   pStr = ""
                  
                    pStr = pStr & "Choose from range 0 to 255:" & $CRLF
                    FOR j = 1 TO 21
                      FOR i = 1 TO 19
                        pStr = pStr & USING$("### ",Rnd2(0, 255))
                      NEXT
                      pStr = pStr & $CRLF
                    NEXT
                    pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,, "Range 0 thru 255"
                   pStr = ""
                  
                    pStr = pStr & "Rnd2Mark/Rnd2Redo example" & $CRLF
                    Rnd2mize
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Mark: Bookmark" & $CRLF
                    Rnd2Mark
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 5
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,, "Rnd2Mark"
                   pStr = ""
                  '--------------------------------------------------------------------------------
                    pStr = pStr & "WildWheel Rnd2Mark/Rnd2Redo example" & $CRLF
                    Rnd2mize
                    FOR i = 1 TO 5
                      Rnd2mize
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Mark" & $CRLF
                    Rnd2Mark
                    FOR i = 1 TO 5
                      Rnd2mize
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 5
                      Rnd2mize
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                    pStr = pStr & "As expected, no match at all. WildWheel is truly one·off" & $CRLF
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,,"WildWheel One·Off Only"
                   pStr = ""
                  '--------------------------------------------------------------------------------
                    pStr = pStr & "Rnd2() example" & $CRLF
                  
                    FOR i = 1 TO 15
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                    pStr = pStr & $CRLF & "Rnd2TogSign" & $CRLF
                    Rnd2TogSign
                    FOR i = 1 TO 15
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                    Rnd2TogSign
                  
                    pStr = pStr & $CRLF & "Rnd2() produces cryptographically secure random numbers." & $CRLF
                    pStr = pStr & "It maintains its own separate sequence internally." & $CRLF
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                  
                    Rnd2mizeCrypto 'note: does NOT affect last number
                    pStr = pStr & $CRLF & "Repeat last number generated " & $CRLF & STR$(Rnd2LastNum)
                      'pStr = pStr & "**********"
                  '? pStr,,"Rnd2() Secure Randoms"
                   pStr = ""
                  '--------------------------------------------------------------------------------
                    pStr = pStr & "Rnd2() Rnd2Mark/Rnd2Redo example" & $CRLF
                    Rnd2mize
                    FOR i = 1 TO 5
                      Rnd2(2)
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Mark" & $CRLF
                    Rnd2Mark
                    FOR i = 1 TO 5
                      Rnd2(2)
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                  
                  
                    pStr = pStr & $CRLF & "Rnd2Redo" & $CRLF
                    Rnd2Redo
                    FOR i = 1 TO 5
                      Rnd2(2)
                      pStr = pStr & STR$(Rnd2()) & $CRLF
                    NEXT
                    pStr = pStr & "Rnd2mizeCrypto Provide a Cryptographic seed to the sequence." & $CRLF
                  '  pStr = pStr & "any way. Rnd2() maintains its own separate sequence internally." & $CRLF
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                  ? pStr,,"Rnd2mizeCrypto"
                   pStr = ""
                  '--------------------------------------------------------------------------------
                  '                      WildWheel
                    pStr = pStr & "WildWheel card shuffle" & $CRLF
                    pStr = pStr & "start order: "
                    DIM card(1 TO 52) AS LONG
                    FOR i = 1 TO 52
                       card(i) = i
                       pStr = pStr & STR$(i)
                    NEXT
                  
                  ' ? pStr,,"Card Shuffle"
                    pStr = pStr & $CRLF & $CRLF
                         :pStr = pStr & "shuff order: "
                    FOR i = 1 TO 52
                       Rnd2mize
                       SWAP card(i), card(Rnd2(i, 52))
                       pStr = pStr & STR$(card(i))
                    NEXT
                  '-----------------------------------------------------------------------
                  ' for j = 1 to 10
                  '  ? pStr,,"WildWheel Card Shuffle"
                  '  pStr = "shuff order: "
                  '  FOR i = 1 TO 52                  'you CAN shuffle more than one time thru the FOR-NEXT loop, but one time
                  '     Rnd2mize                    'is statistically just as random as 2, or 10, or 100, or 1000... :)
                  '     SWAP card(i), card(Rnd2(i, 52))
                  '     pStr = pStr & STR$(card(i))
                  '  NEXT
                  ' next
                  '-----------------------------------------------------------------------
                    pStr = pStr & $CRLF
                         :pStr = pStr & $CRLF & "**********" & $CRLF
                   ? pStr,,"WildWheel Card Shuffle"
                   pStr = ""
                  
                    ? "Timing test is next for 10,000,000 iterations...",, "Timing"
                    pStr = pStr & "10,000,000 iterations" & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 10000000
                        x = RND
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "RND:          " & sTimeTaken & $CRLF
                  
                    Rnd2mize
                    StartTimer
                      FOR i = 1 TO 10000000
                        x = Rnd2
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "Rnd2 [0,1): " & sTimeTaken & $CRLF
                  
                    Rnd2Redo
                    Rnd2TogSign
                    StartTimer
                      FOR i = 1 TO 10000000
                        x = Rnd2
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "Rnd2 (-1,1):" & sTimeTaken & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 200000
                         Rnd2(2)
                        x = Rnd2()
                      NEXT i
                    StopTimer
                  
                   pStr = pStr & "Crypto(-1,1):" & sTimeTaken & " x50" & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 200000
                        Rnd2mize
                        x = Rnd2()
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "Wheel(-1,1):" & sTimeTaken & " x50" & $CRLF & $CRLF
                  
                    Rnd2TogSign
                  
                         :pStr = pStr & "*****Integer Mode*****" & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 10000000
                        j = RND(1, 52)
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "RND(1, 52): " & sTimeTaken & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 10000000
                        j = Rnd2(1, 52)
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "Rnd2(1, 52):" & sTimeTaken & $CRLF
                    StartTimer
                      FOR i = 1 TO 10000000
                        j = RND(-2147483648, 2147483647)
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "RND(-2147483648, 2147483647): " & sTimeTaken & $CRLF
                  
                    StartTimer
                      FOR i = 1 TO 10000000
                        j = Rnd2Long
                      NEXT i
                    StopTimer
                  
                    pStr = pStr & "Rnd2(-2147483648, 2147483647):" & sTimeTaken & $CRLF
                    ? pStr,,"Timing"
                  
                    Rnd2stopCrypto
                  
                  END FUNCTION

                  Comment


                    I should have mentioned

                    Code:
                    MACRO mStoreSeq ' 'save original starting point of sequence in 12-byte storeState string. This is more
                    !lea eax, storeState       ;str address
                    !mov ecx, mwcSoph
                    !mov edx, mwcRandom
                    !mov [eax+0], ecx          ;Save mwcSoph In storeState str.
                    !mov ecx, mwcCarry
                    !mov [eax+4], edx          ;Save mwcRandom
                    !mov [eax+8], ecx          ;Save mwcCarry
                    END MACRO
                    
                    MACRO mDefaultSeq 'gs prefix means this is a GOSUB sub
                    oneTime = 1
                    mwcSoph = 4221732234
                    mwcRandom = &ha5b218da     ' can be any LONG except &hffffffff and 0
                    mwcCarry  = &h3fe8700c     ' can be any number except (mwcSoph-1) and 0
                    mStoreSeq
                    END MACRO

                    Comment


                      Rnd2MizeCrypto = Rnd2(2) 'cryptographically seed the random number generator

                      Code:
                      StartTimer
                        For i = 1 To 200000
                          Rnd2(2)
                          x = Rnd2()
                        Next i
                      StopTimer
                      Folks may now think that x is cryptographic.

                      Rnd2MizeCrypto is a seeder. Mwc is a blinder of a prng and why Rnd2 was written originally. It doesn't need re-seeding between generations. You can be very trying at times, Mr Gleason.

                      Comment


                        See if this helps your speed as much as it did here... In the "noParams" section, change the way we load the multiplier via rndE.

                        Code:
                         noParams:     ' no optional parameters passed, so calculate EXT rnd...
                          rndE = 1084202172485504433E-37   ' <<< INSERT THIS LINE
                          IF OneTime = 0 THEN GOSUB gsDefaultSeq ' otherwise start crunching
                        and
                        Code:
                            '---------------------  'now take the quad ... 
                        '  >REM>  !lea ecx, rndE          ;space TO hold the constant ... 
                        '  >REM>  !mov DWORD PTR[ecx],   &hffffffef ;...-36 SAVE IN rndE... 
                        '  >REM>  !mov DWORD PTR[ecx+4], &hffffffff ;        "     "
                        '  >REM>  !mov  WORD PTR[ecx+8], &h3fbf     ;        "     "
                        '  >REM>  !fld tbyte [ecx]        ;float LOAD ...-36
                            !fld rndE       ;' <<<< INSERT THIS TO DIRECTLY LOAD rndE  <<<<
                            !fmulp st(1),st(0)

                        Comment


                          Another 5%.

                          Code:
                          RND:       324.62
                          Rnd2[0,1]: 291.47ms

                          Comment


                            rndE = 1084202172485504433E-37 ' <<< INSERT THIS LINE
                            This won't work properly in pre ver. 9/5 I'm almost sure. Dave, remember the rounding post where we needed eg. 1234567890 / 10000000 to get the proper EXT values in there? Paul P. came up with the division workaround.

                            Dave said: Folks may now think that x is cryptographic. Rnd2MizeCrypto is a seeder. Mwc is a blinder of a prng and why Rnd2 was written originally. It doesn't need re-seeding between generations.
                            I'm afraid you'll have to hunch me a bit more re. the meaning of the above. It's a little too "cryptic" for me.

                            Comment


                              > Dave, remember.....

                              Yes.

                              Code:
                              rndE = 1084202172485504433E-37 ===> 3FBFFFFFFFFFFFFFFFBC
                              instead of                          3FBFFFFFFFFFFFFFFFEF
                              I tried
                              Code:
                              rndE = 1084202172485504433E-37
                              !lea ecx, rndE
                              !mov Word Ptr[ecx], &hffef
                              and Byte, Dword but all went up to about 331ms.

                              Well remembered, John.

                              Added: I'm running on PB9 so nothing has changed.
                              Last edited by David Roberts; 24 Oct 2008, 11:28 PM.

                              Comment


                                How about this.

                                Instead of building 1084202172485504433 * 10E-36 each time we enter noParams build it only once in the 'If Onetime' construct. We have then effectively an equate.

                                Assign 'Static Factor as Ext'

                                Added: Skip the next piece of code and see the next post.
                                Code:
                                noParams:     ' no optional parameters passed, so calculate EXT rnd...
                                If OneTime = 0 Then
                                  mDefaultSeq
                                  ' Build Ext Factor
                                  ' 1084202172485504433 * 10E-36 (yes I even made it 19 digits) 
                                  !lea ecx, Factor
                                  !mov Dword Ptr[ecx], &hffffffef 
                                  !mov Dword Ptr[ecx+4], &hffffffff ;     
                                  !mov  Word Ptr[ecx+8], &h3fbf     ;
                                End If
                                This is still OK except we will use Factor2 according to next post
                                This turning into a scruffy post - sorry!
                                Code:
                                    '---------------------  'now take the quad ... 
                                '  >REM>  !lea ecx, rndE          ;space TO hold the constant ... 
                                '  >REM>  !mov DWORD PTR[ecx],   &hffffffef ;...-36 SAVE IN rndE... 
                                '  >REM>  !mov DWORD PTR[ecx+4], &hffffffff ;        "     "
                                '  >REM>  !mov  WORD PTR[ecx+8], &h3fbf     ;        "     "
                                '  >REM>  !fld tbyte [ecx]        ;float LOAD ...-36
                                  !fld Factor       ;' <<<< INSERT THIS TO DIRECTLY LOAD factor  <<<<
                                  !fmulp st(1),st(0)
                                Code:
                                RND:       323.96ms
                                Rnd2[0,1]: 252.49ms
                                We gained 5%, then lost it. This one is 20%.

                                Mine is a Guinness.

                                Added: We can do the same in rangeNotMax but I'm a bit pushed for time at the minute.
                                Last edited by David Roberts; 25 Oct 2008, 10:28 AM.

                                Comment


                                  Not very smart using OneTime as that could be true before going to noParams for the first time.

                                  So, at the function head:
                                  Code:
                                  Static Factors As Long                                              
                                  Static Factor1, Factor2 As Ext
                                  
                                  If Factors = 0 Then
                                    !lea ecx, Factor1 
                                    !mov Dword Ptr[ecx],    &hffffffff ;Save 2.328306436538696289e-10 In Factor2 -- Ext Image Of 1 / 4294967296. <<Max Dword+1
                                    !mov Dword Ptr[ecx+4],  &hffffffff ;          
                                    !mov  Word Ptr[ecx+8],  &h3fde     ;
                                    !lea ecx, Factor2          ;space To hold the constant 1084202172485504433 * 10E-36 (yes I even made it 19 digits)
                                    !mov Dword Ptr[ecx],   &hffffffef ;...-36 Save In rndE. This Is a Binary Image Of the Extended precision ...-36
                                    !mov Dword Ptr[ecx+4], &hffffffff ;     
                                    !mov  Word Ptr[ecx+8], &h3fbf     ; 
                                    Factors = 1
                                  End If
                                  In rangeNotMax
                                  Code:
                                        !fld rndE
                                  '     !lea ecx, rndE
                                        !lea edx, eq
                                  '     !mov Dword Ptr[ecx],    &hffffffff ;Save 2.328306436538696289e-10 In rndE--Ext Image Of 1 / 4294967296. <<Max Dword+1
                                  '     !mov Dword Ptr[ecx+4],  &hffffffff ;          
                                  '     !mov  Word Ptr[ecx+8],  &h3fde     ;          
                                        !mov [edx], eax        ;Save the Random Dword In Lo(eq)
                                        !mov Dword Ptr[edx+4],0;zero Hi(Dword, eq)
                                                               'Locked and loaded. We have ebx=range, eq=rand dword, rndE=divisor, so
                                                               'the following asm will do: FUNCTION = rand * (1 / 4294967296) * range
                                        !fld [COLOR="Red"][B]Factor1[/B][/COLOR]              ;Load 1 / 4294967296 into float reg
                                        !fild Qword eq         ;Load rand Dword into float Register
                                  Forgot to mention in previous post above macro mDefaultSeq used
                                  Code:
                                  noParams:     ' no optional parameters passed, so calculate EXT rnd...
                                  If OneTime = 0 Then
                                    mDefaultSeq ' otherwise start crunching
                                  End If
                                  Lost some speed though.
                                  Lost 20% and got 10%
                                  Code:
                                  RND:       324.20ms
                                  Rnd2[0,1]: 279.57ms
                                  Added: I'm not getting any benefit in rangeNotMax. I have noticed with rangeNotMax that it occasionally takes longer whilst the other metrics remain about the same.
                                  Last edited by David Roberts; 25 Oct 2008, 10:38 AM.

                                  Comment


                                    I noticed about your rangeNotMax timings. I don't know why that is. I'm 30%+ faster always.

                                    I tested your CASE 2 asm and it runs fine and is faster by very roughly ~10%, but when I checked its output against the original code using the default sequence rather than crypto bytes, they didn't match. I can't check with crypto bytes because they'll never match, and all I was testing for was an output match. Did your asm match in your tests?

                                    Comment


                                      Not sure what you did, John, but just after GetCrypto.Bytes(rndE) in CASE 2, CASE 6 with the earlier version, I loaded rndE with the default sequence, let the code rip and then printed out what was found. The asm matched with the old code. I didn't do a full run but used an app which executes one command/function once only.

                                      Comment


                                        Well, I've just got a 20ms reduction for the rangeNotMax. The last tweak was an absolute tweak so any reduction wouldn't be as obvious as with noParams which is belting along at about twice the speed.

                                        All I've done is to move the the '!fld rndE', which seemed out on a limb and not required for a while, to the front of the float code. May be my system doesn't care for jumping twix the CPU and FPU and prefers a decent run with each.

                                        Comment


                                          Two good news items, 1 so so item.
                                          1) The 2 constant floats like you both demo'd can work if we figure out where they go and their exact values. It speeds it up quite a bit, ~15%. I was surprised it was so fast.
                                          2) I previously said I didn't think the mwc generator could produce 2 identical 4-byte dwords in a row. I was wrong, because I tested it and ~1 in 4.3 billion dwords are identical to the previous dword.

                                          1) The CASE 2 Rnd2mizeCrypto asm doesn't match the original PB code output. I haven't figured out why not. I think it isn't a big deal because it only speeds the code 7% and since it is intended to be called only once for initialization--not repeatedly--the original PB code should be fine.

                                          Comment

                                          Working...
                                          X
                                          😀
                                          🥰
                                          🤢
                                          😎
                                          😡
                                          👍
                                          👎