Announcement

Collapse

Forum Guidelines

This forum is for finished source code that is working properly. If you have questions about this or any other source code, please post it in one of the Discussion Forums, not here.
See more
See less

On cryptographic random bytes

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

  • David Roberts
    replied
    PART 6

    This post does not belong here because we are not talking about cryptographic random bytes. On the contrary, we are talking about the same bytes being generated in a similar way to that of 'Randomize number'. If you have no use for 'Randomize number' then you will have no use for the following. The reason why we are here is because the function employed is a derivative of PBCryptRandom called PBCryptFixedSeed. Clearly, Random has been replaced with FixedSeed giving the game away; even though Crypt and FixedSeed is a contradiction in terms.

    There is no need for an Inner IV so that has been dropped - the default MS empty array is fine.

    The outer IV and password saw a variety of values ranging from hash values of files grabbed at random to all sorts of weird and wonderful values. I finally settled on both being &B10 repeated. Why? Well, I have no particular reason and can only say, why not?

    The monotonic counter has been based upon the block index counter with a variety of starting values. The starting value I ended up with was nothing, ie 128 zero bits with the last 32 bits being the counter. As we leave the function the next block, NextBlock, is kept static so that we follow on with a subsequent re-entry - we gotta keep monotonic. You may think that 128 zero bits is asking for trouble and that would be true if we used the ECB block cipher mode. With CBC any patterns in the plaintext are scrambled by virtue of the feedback; which is initially the Outer IV.

    We cannot test the data as previously - 5 x 100MB files will give five identical files - so 10MB was generated with a further nine 10MB following on.

    These are the respective chi-squared values:

    44.32 71.07 26.95 17.86 68.87 55.53 76.01 39.01 89.62 65.09.

    The thing about chi-squared as with any null-hypothesis test is that the null-hypothesis is rejected if results are within the tails of the normal distribution otherwise the test is inconclusive. We cannot say that 55%, for example, is better than 65%; they are both inconclusive and the null-hypothesis holds. So, although that 89.62% is scratching at the "almost suspect" region it is still less than 90%. However, having said that Die-Hard was dusted down and a full test applied to that 9th block. The worst case close to zero and one was 0.0010 and 0.9985 respectively. The p values of the Die-Hard tests should not to be treated in the same way as the chi-squared above. That 9th block is OK. Of course, we don't have to use it. Interestingly, if we jumped straight to the 9th block by using a starting value for NextBlock from nth block as 10*1024*1024 * n \32 then get a chi-squared of 33.32%. We have, of course, bypassed 8 blocks of feedback.

    Part Va may use the above principle but I have not examined that.

    Using unbiased data is probably more important in a 'Randomize number' scenario so it may be worthwhile to download ent.exe from the Fourmilab link in PART V above if you have specific data sizes differing to those examined above just to make sure that you don't use a bad set. Bad sets are a fact of life but we are not obliged to use them.

    Have fun.

    Code:
    #Compile Exe
    #Dim All
    #Tools Off
    
    %NOMMIDS = 1
    %NOGDI = 1 
    
    #Include "win32api.inc"
    #Include "wincrypt.inc"
    
    %Bin = 1
    %Hex = 0
    
    '*************************************************************************
    ' API error macro
    Macro SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FuncName$, Number ), "AES", %MB_ICONERROR + %MB_TOPMOST
    '*************************************************************************
    
    Global hProv As Dword
    ' Always determine in PBMain and not in a function to be called often - it is time consuming - 6ms on my machine!
    
    %Display = %True
    
    Function PBMain
    Local sInterimOutPut, sFinalOutPut As String
    Local i As Long
      
      hProv = crGetDefaultRSAHandle
      If hProv = 0 Then Exit Function
      
      #If %Display
        sFinalOutPut = "PBCryptoFixedSeed" + $CrLf + $CrLf
        For i= 1 To 16
          sInterimOutPut = PBCryptoFixedSeed( 32, %Hex )
          sFinalOutPut = sFinalOutPut + sInterimOutPut + $CrLf
        Next i
        MsgBox sFinalOutPut, %MB_TOPMOST
      #Else
        For i = 1 To 10
          sFinalOutPut = PBCryptoFixedSeed(10*1024*1024, %Bin)
          Kill "c:\test" + Trim$(Str$(i)) + ".txt"
          Open "c:\test" + Trim$(Str$(i)) + ".txt" For Binary As #1
          Put$ #1, sFinalOutPut
          Close #1
          sFinalOutPut = ""
        Next
        MsgBox "Done"
      #EndIf
    
      If hProv Then CryptReleaseContext hProv, 0  
    	
    End Function
    
    '*************************************************************************
    
    Function PBCryptoFixedSeed( ByVal ToTalBytes As Long, ByVal Flag As Long ) As String
    #Register None
    Local Blocks, Clip, i, j, hKey, hHash, WinErr As Long
    Local sHex, sPlaintext As String
    Local ptrPT As Dword
    Local pbyte As Byte Ptr
    Dim sTotalPbdata As String ' Dim to avoid potential stack overuse
    Static sPassword, OuterIV, pbdata As String, NextBlock As Dword
    
      If pbdata = "" Then ' this is the 1st pass of PBCryptRandom
        OuterIV = "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA" ' &B10 repeated
        If Len( OuterIV ) Mod 2 <> 0 Then
          MsgBox "OuterIV is not an even length"
          GoTo TidyUp
        End If
        Hex2Bin( OuterIV )
        sPassword = "AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA" ' &B10 repeated
        If  Len( sPassword ) Mod 2 <> 0 Then
          MsgBox "sPassword is not an even length"
          GoTo TidyUp
        End If
        Hex2Bin( sPassword )
        pbdata = OuterIV
      End If
    	    
      If CryptCreateHash( hProv, %CALG_SHA_256, 0, 0, hHash ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptCreateHash", 10 )
        Function = ""
        GoTo TidyUp
      Else
        If CryptHashData( hHash, ByVal StrPtr(sPassword), Len( sPassword ), 0 ) = %False Then
          WinErr = GetLastError : SysErrMsg( "CryptHasData", 20 )
          Function = ""
          GoTo TidyUp
        Else
          If CryptDeriveKey( hProv, %CALG_AES_256, hHash, 0, hKey ) = %False Then
    	WinErr = GetLastError : SysErrMsg( "CryptDeriveKey", 30 )
    	Function = ""
    	GoTo TidyUp
          End If
        End If
      End If
    	
      Blocks = TotalBytes\32
      If (TotalBytes < 32) Or (TotalBytes Mod 32 <> 0) Then
        Incr Blocks
        Clip = %True
      End If
    	
      If Flag = %Bin Then
        sTotalPbdata = Space$( 32*Blocks )
      Else
        sTotalPbdata = Space$( 64*Blocks )
      End If
    	
      For i = 0 To Blocks - 1
    	
        sPlaintext = Space$(16)
        ptrPt = StrPtr( sPlaintext )
        ! mov esi, ptrPt
        ! Xor eax, eax
        ! mov [esi], eax
        ! mov [esi+4], eax
        ! mov [esi+8], eax
        ! mov eax, NextBlock
        ! mov ebx, i
        ! Add eax, ebx
        ! mov [esi+12], eax
          	  	
        ' pbdata = OuterIV when i = 0 and this is the 1st or only application session
        ' and equals the output of CryptEncrypt for all other events.
        AXorB(sPlaintext, pbdata) ' sPlainText = sPlainText XOR pbdata
        ' AES ciphertext = plaintext + 16 bytes
        pbdata = sPlaintext + Space$(16)
          	
        If CryptEncrypt( hKey, 0, %True, 0, ByVal StrPtr( pbdata ), 16, 32 ) = %False Then 
          WinErr = GetLastError : SysErrMsg( "CryptEncrypt", 40 )
          Function = "" 
          GoTo TidyUp 
        End If
        
        If Flag = %Bin Then
          Mid$( sTotalPbdata, 32*i + 1, 32 ) = pbdata
        Else
          pbyte = StrPtr(pbdata)
          For j = 0 To 31
            sHex = sHex + Hex$(@pbyte[j],2)
          Next j
          Mid$( sTotalPbdata, 64*i + 1, 64 ) = sHex
        End If
     
      Next
       
      If Clip Then sTotalPbdata = Left$(sTotalPbdata, (2-Flag)*TotalBytes)
      
      NextBlock = NextBlock + Blocks
       
      Function = sTotalPbdata
      
    TidyUp:	
    	
      If hHash Then CryptDestroyHash hHash
      If hKey Then CryptDestroyKey hKey
    	
    End Function
    
    '*************************************************************************
    
    Function Hex2Bin( A As String) As Long
    
    ' Input: A is upper or lower case hexadecimal
    ' Output: A is half length of input A
    
    #Register None
    Local ptrA, StringEnd As Dword
      
      A = UCase$(A)
      	
      ptrA = StrPtr( A ) - 1
      StringEnd = StrPtr( A ) + Len( A )
      ! mov esi, ptrA
      ! mov edi, ptrA
      ! mov ecx, StringEnd
    StartLoop:
      ! inc esi ' 1st pass is
      ! inc edi ' start of string
      ' esi will move in steps of two and edi will move in steps of one
      ! cmp esi, ecx ' Are we at the end of the string
      ! je Endloop
      ! mov al, [esi] ' Get byte in A
      ! cmp al, 57    ' Is it numeric?
      ! jg NotNum1    ' No
      ! Sub al, 48    ' Yes
      ! jmp IsNo1
    NotNum1:
      ! Sub al, 55    ' Is aphabetic so get numeric value
    IsNo1:
      ! shl al, 4     ' Multiply by 16
      ! inc esi       ' Move on to next character of hex pair
      ! mov bl, [esi] ' Get byte
      ! cmp bl, 57    ' Is it numeric?
      ! jg NotNum2    ' No
      ! Sub bl, 48    ' Yes
      ! jmp IsNo2
    NotNum2:
      ! Sub bl, 55    ' Is alphabetic so get numeric value
    IsNo2:
      ! Add al, bl    ' Add 2nd of pair to 1st of pair
      ! mov [edi], al ' and put into next edi slot
      ! jmp StartLoop
    Endloop:
    
      A = Left$(A, Len(A)\2)
    
      Function = %True
      
    End Function
    
    '*****************************************************************************
    
    Function AXorB( A As String, B As String ) As Long
    
    ' A becomes A Xor B, B remains unchanged
    ' Computation is limited to the length of the shorter string
    ' if the strings are not the same length
    
    #Register None
    Local ptrA, ptrB, StringEnd As Dword
    	
      ptrA = StrPtr( A ) - 1
      ptrB = StrPtr( B ) - 1
      StringEnd = StrPtr( A ) + Len( A )
      If Len( A ) > Len( B ) Then StringEnd = StrPtr( A ) + Len( B )
      ! mov esi, ptrA
      ! mov edi, ptrB
      ! mov ecx, StringEnd
    StartLoop:
      ! inc esi ' 1st pass is
      ! inc edi ' start of strings
      ! cmp esi, ecx ' Are we at end of strings?
      ! je EndLoop ' Yes
      ! mov al, [esi ] ' Get byte in A
      ! Xor al, [edi ] ' al becomes byte in A Xor byte in B
      ! mov [esi ], al ' Put byte in A
      ' [edi] is unchanged ie B
      ! jmp StartLoop
    EndLoop:
    
      Function = %True
    
    End Function
    
    '*************************************************************************
    
    Function crGetDefaultRSAHandle As Long
    Local WinErr As Long
    
    If CryptAcquireContext( hProv, ByVal %Null, ByVal %Null, %PROV_RSA_AES, 0 ) = %False Then
      If CryptAcquireContext( hProv, ByVal %Null, $MS_ENH_RSA_AES_PROV, %PROV_RSA_AES, %CRYPT_NEWKEYSET ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptAcquireContext", 10 )
        Function = %False
      Else
        Function = hProv
      End If
    Else
      Function = hProv
    End If
    End Function
    
    '*************************************************************************
    
    Function SystemErrorMessage( ByVal WinErr As Long, API As String, sFunction As String, ByVal Number As Long ) As String
      Local pBuffer As Asciiz Ptr, ncbBuffer As Dword
      Local sText As String
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER Or %FORMAT_MESSAGE_FROM_SYSTEM Or %FORMAT_MESSAGE_IGNORE_INSERTS, _
        ByVal %Null, WinErr, %Null, ByVal VarPtr( pBuffer ), 0, ByVal %Null )
      If ncbBuffer Then
        sText = Peek$( pBuffer, ncbBuffer )
        sText = Remove$( sText, Any Chr$( 13 ) + Chr$( 10 ) )
        Function = $CrLf + "Error" + Format$( WinErr, " #####" ) + " during " + API + $CrLf + $CrLf + _
          Chr$(34) + sText + Chr$(34) + $CrLf + $CrLf + "Location : " + sFunction + IIf$( Number, Format$( Number, " ###" ), "" )
        LocalFree pBuffer
      Else
        Function = "Unknown error - Code:" + Format$( WinErr, " #####" )
      End If
    
    End Function
    
    '*************************************************************************

    Leave a comment:


  • David Roberts
    replied
    PART Va

    For those of you with less than XP SP3 here is a 1.6 litre engine. Its top speed is less than the 'SHA256/AES256' combo because it uses 'SHA1/Triple DES' but is a nice little runner nonetheless.

    Effectively, everything is halved and the Seed is randomly split in two then RND(0,4) is used as above using blocks of 8 bytes instead of 16.

    Chi-squared is well away from the "almost suspect" region. This is good quality data but not up to the 'SHA256/AES256' standard and still better than MSCryptRandom.

    Code:
    PB Triple DES
     
      74.95      33.79      69.71      67.85      32.51      
     127.5032   127.5002   127.4991   127.4975   127.4992   127.4998
       1.000127   1.000226   1.000052   1.000147   1.000171   1.000145
      -0.000172  -0.000092  -0.000042   0.000054  -0.000255   0.000123
    There is a drawback - it is only half the speed of MSCryptRandom.

    If you want to give it a test run then replace the above PBCryptRandom with the following one. You will also need to replace the crGetDefaultRSAHandle to access the older Cryptographic Service Provider.

    Code:
    Function PBCryptRandom( ByVal ToTalbytes As Long, ByVal Flag As Long ) As String
    Local Blocks, Clip, i, j, hKey, hHash, WinErr, Split As Long
    Local Seed, sHex, sPlaintext As String
    Local ptrPT As Dword
    Local pbyte As Byte Ptr
    Dim sTotalPbdata As String ' Dim to avoid potential stack overuse
    Dim Dummy As String * 16
    Static sPassword, OuterIV, pbdata As String
    Static InnerIV() As Byte
    
      If pbdata = "" Then ' this is the 1st pass of PBCryptRandom
        Seed = GetCryptoSeed(%Bin)
        Randomize
        Split = Rnd(0,1)
        If Split = 0 Then
          Seed = Left$(Seed, 40)
        Else
          Seed = Right$(Seed, 40)
        End If
        Seed = StrDelete$( Seed, 8*Rnd(0,4)+1, 8 )
        OuterIV = Left$( Seed, 8 )
        sPassword = Mid$( Seed, 9, 16 )
        Dim InnerIV(0 To 7) As Static Byte At VarPtr( Dummy )
        Dummy = Right$( Seed, 8 )
        pbdata = OuterIV
      End If
    	    
      If CryptCreateHash( hProv, %CALG_SHA, 0, 0, hHash ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptCreateHash", 10 )
        Function = ""
        GoTo TidyUp
      Else
        If CryptHashData( hHash, ByVal StrPtr(sPassword), Len( sPassword ), 0 ) = %False Then
          WinErr = GetLastError : SysErrMsg( "CryptHasData", 20 )
          Function = ""
          GoTo TidyUp
        Else
          If CryptDeriveKey( hProv, %CALG_3DES, hHash, 0, hKey ) = %False Then
            WinErr = GetLastError : SysErrMsg( "CryptDeriveKey", 30 )
    	Function = ""
    	GoTo TidyUp
          End If
        End If
      End If
    	
      ' Override default inner IV array
      If CryptSetKeyParam( hKey, %KP_IV, InnerIV( 0 ), 0 ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptSetKeyParam", 40 )
        Function = ""
        GoTo TidyUp
      End If
    	
      Blocks = TotalBytes\16
      If (TotalBytes < 16) Or (TotalBytes Mod 16 <> 0) Then
        Incr Blocks
        Clip = %True
      End If
    	
      If Flag = %Bin then
        sTotalPbdata = Space$( 16*Blocks )
      Else
        sTotalPbdata = Space$( 32*Blocks )
      End If
    	
      For i = 0 To Blocks - 1
    	
        ' Get a couple of Time Stamps and put into sPlainText
        sPlaintext = Space$(8)
        ptrPt = StrPtr( sPlaintext )
        ! cpuid
        ! RDTSC
        ! mov esi, ptrPt
        ! mov [esi], edx
        ! mov [esi+4], eax
        	  	
        ' pbdata = OuterIV when i = 0 and this is the 1st or only application session
        ' and equals the output of CryptEncrypt for all other events.
        AXorB(sPlaintext, pbdata) ' sPlainText = sPlainText XOR pbdata
        ' AES ciphertext = plaintext + 16 bytes
        pbdata = sPlaintext + Space$(8)
          	
        If CryptEncrypt( hKey, 0, %True, 0, ByVal StrPtr( pbdata ), 8, 16 ) = %False Then 
          WinErr = GetLastError : SysErrMsg( "CryptEncrypt", 40 )
          Function = "" 
          GoTo TidyUp 
        End If
        
        If Flag = %Bin Then
          Mid$( sTotalPbdata, 16*i + 1, 16 ) = pbdata
        Else
          pbyte = StrPtr(pbdata)
          For j = 0 To 31
            sHex = sHex + Hex$(@pbyte[j],2)
          Next j
          Mid$( sTotalPbdata, 32*i + 1, 32 ) = sHex
        End If
     
      Next
      
      If Clip Then sTotalPbdata = Left$(sTotalPbdata, (2-Flag)*TotalBytes)
      
      Function = sTotalPbdata
      
    TidyUp:	
    	
      If hHash Then CryptDestroyHash hHash
      If hKey Then CryptDestroyKey hKey
      
    End Function
    
    '*******************************************************
    
    Function crGetDefaultRSAHandle As Long
    Local WinErr As Long
    
      If CryptAcquireContext( hProv, ByVal %Null, ByVal %Null, %PROV_RSA_FULL, 0 ) = %False Then
        If CryptAcquireContext( hProv, ByVal %Null, $MS_DEF_PROV, %PROV_RSA_FULL, %CRYPT_NEWKEYSET ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptAcquireContext", 10 )
        Function = %False
      Else
        Function = hProv
      End If
    Else
      Function = hProv
    End If
    End Function
    Last edited by David Roberts; 23 Mar 2010, 09:41 AM.

    Leave a comment:


  • David Roberts
    replied
    Part V

    Here is another way to generate cryptographic random numbers.

    HEALTH WARNING: Not for less than XP SP3 - MS SHA256 and AES 256 are implemented. I don't check for OS in 'ideas' type code.

    The method is from Steve Gibson here.

    Schematically we have

    Code:
       IV    Monotonic Counter  Password
        |            |              |
        |----->---- XOR ---->--- Encrypt --
        |                                 |
        |-----<-------------<-------------|
    with the scheme obeying the Cipher Block Chaining principle.

    We supply a 128 bit initial value (IV) and a 256 bit password key. In our case the system supplies the Monotonic Counter (MC) via the Time Stamp and this is the plaintext element in cryptography parlance. I am not sure what Steve Gibson uses for the MC.

    Initially, IV is XOR'd with the MC and this is, in turn, encrypted with the password by AES 256. AES ciphertext is 16 bytes larger than the plaintext so we get a 256 bit output. If more data is required the output is XOR'd with the updated MC and encrypted and so on. Although the output is 256 byte and the MC is 128 bit the function which does the XORing, AXorB, limits computation to the length of the shorter string. The low 128 bits of the output are then effectively ignored.

    Since the MC will never be repeated the contention is that the AES output will never be repeated either.

    Actually, it will when the Time Stamp rolls over but few of us will ever see that if a PC is switched on at our birth and left on for the rest of our life. <Gulp>

    Greg Turgen's RandBytes written in 2003 uses a similar approach. Two aspects caught my eye. Firstly, the Time Stamp is queried twice in succession. This would be ideal here as the Time Stamp is 64 bit and MC is 128 bits wide. Secondly, entropy is harvested from the system.

    A departure is made from the Gibson approach by not supplying a IV or password but to build them from entropy as with Greg's code. Rather than re-invent the wheel, PART I above showed us that we have a 80 byte Seed value in the registry. There is very little information about this key but further reading states that this entry is not the entropy per se but is the entropy encrypted by RC4. Since the entropy is a snapshot off our machines' psyche, so to speak, then encrypting it seems an expedient measure. Encrypting the entropy will neither degrade nor enhance it. 80 bytes is 640 bits so we can take 128 bits for IV and 256 bits for the password. The scheme above is a mirror of what CBC encryption does and that also uses a IV. By default Microsoft uses an empty IV. With my MSCrypto a random IV is calculated and put into the header of the encrypted file to be read on decryption. We are not using decryption here so we do not have to publish a IV and we can take another 128 bits from the 640 bits and keep quiet about it. In the following code I refer to these IVs as OuterIV and InnerIV. That leaves us with 128 bits unused. I have not found a use for that. However, from 80 bytes we effectively use 4 blocks of 16 and discard one block of 16 so we can randomly choose a block to discard and use the remainder. To do that our old friend RND is used via RND(0,4). I doubt if using a non-cryptographic function here is grounds for concern and, being proprietary, may a good idea.

    If the random data produced is sensitive for any reason I reckon that an attacker would find it very difficult to get their hands on the Seed value we get from the registry. An attack application must be in place before our application because the Seed value would change on launching the attack application. I mentioned in PART I that I could not find an exact pattern of behaviour for the Seed generation. If this is by design then Microsoft have been very smart.

    Gibson's idea is to generate unique keys but, of course, it may be extended to supplying almost unlimited amounts of random data and that is what the following code does.

    Included is a routine, called MSCryptRandom, implementing CrypGenRandom to compare with the above speed wise. The routine implementing the above is called PBCryptRandom. Let us hope that my code is more imaginative than the naming conventions. OutPut from both is either hex or binary. Only the binary output has been timed as a binary output is probably what folk want. The compilation is conditional upon %Display. If true then a small number are calculated for display purposes. If false then a large number are calculated and only the time taken is shown. Surprisingly there is not a great difference in speed between the two approaches with PBCryptRandom being the faster; about 8% to 10% for 1000000 bytes.

    Ideally, a request should be made for a multiple of 32 bytes. If not the next multiple of 32 bytes are computed and the result clipped according to the request.

    There is a small overhead with PBCryptRandom on the first or only application session setting up the initial values. To maintain a level playing field, I think, a dummy run is executed before the benchmarking.

    Statistics:

    I dumped 5x100MB files for PBCryptRandom and 5x100Mb files for MSCryptRandom and run the ent.exe application from A Pseudorandom Number Sequence Test Program.

    In the following we have:
    1st row: Chi-squared test
    2nd row: Arithmetic mean, ideally 127.5
    3rd row: Monte Carlo value for Pi divided by Pi and reciprocated if less than 1
    4th row: Serial correlation coefficient - average is on absolute values

    and the end column is the average; except for the first column.

    Rows three to four show no difference between PBCryptRandom and MSCryptRandom.

    From Fourmilab at the above link:

    Chi-square Test

    The chi-square test is the most commonly used test for the randomness of data, and is extremely sensitive to errors in pseudorandom sequence generators. The chi-square distribution is calculated for the stream of bytes in the file and expressed as an absolute number and a percentage which indicates how frequently a truly random sequence would exceed the value calculated. We interpret the percentage as the degree to which the sequence tested is suspected of being non-random. If the percentage is greater than 99% or less than 1%, the sequence is almost certainly not random. If the percentage is between 99% and 95% or between 1% and 5%, the sequence is suspect. Percentages between 90% and 95% and 5% and 10% indicate the sequence is “almost suspect”.
    The first row clearly shows that PBCryptRandom provides a better quality of data and is more reliable. Actually, that is the best grouping of Chi-squared that I have ever seen for random numbers.

    That, plus PBCryptRandom is faster then MSCryptRandom, although not much faster, gives us a clear winner.

    Code:
    PB
     
      57.74      35.58      46.53      46.75      34.51      
     127.4957   127.4959   127.4888   127.5026   127.5127   127.4991
       1.000244   1.000000   1.000187   1.000045   1.000122   1.000119
      -0.000147   0.000092  -0.000050  -0.000108  -0.000109  0.000101
     
    MS
     
      75.32      89.58      99.73      91.19      46.88     
     127.4981   127.4903  127.5046    127.5023   127.5006  127.4992
       1.000017   1.000165  1.000165    1.000142   1.000060  1.000110
       -.000098  -0.000112  0.000010   -0.000070   0.000079  0.000074
    The following requires 'wincrypt.inc' which is attached - it is pushing 500 lines now.

    The following is not as tidy as it was in the JellyFish Pro editor but I'm pushed for time and will dispense with tidying up.

    Added: I tidied it up.

    Code:
    #Compile Exe
    #Dim All
    #Tools Off
    
    %NOMMIDS = 1
    %NOGDI = 1 
    
    #Include "win32api.inc"
    #Include "wincrypt.inc"
    
    %Bin = 1
    %Hex = 0
    
    '*************************************************************************
    ' Timer macros - 16 timers available
    Global qFreq, qStart(), qStop(), qOverhead As Quad
    
    Macro InitializeTimer
      Dim qStart( 0 To 15) As Global Quad
      Dim qStop( 0 To 15 ) As Global Quad
      QueryPerformanceFrequency qFreq 
      QueryPerformanceCounter qStart(0) ' Intel suggestion. First use may be suspect 
      QueryPerformanceCounter qStart(0) ' So, wack it twice <smile>
      QueryPerformanceCounter qStop(0)
      qOverhead = qStop(0) - qStart(0)  ' Relatively small 
    End Macro
    
    Macro StartTimer(i) = QueryPerformanceCounter qStart(i)
    Macro StopTimer(i) = QueryPerformanceCounter qStop(i)
    
    ' In the following i is the ith timer and 0 <= j <= 3 For 0 To 3 decimal places - any other j and we get an empty string!
    Macro sTimeTaken( i, j ) = Using$(Choose$(j+1,"####","####.#", "####.##","####.###"), (qStop(i) - qStart(i) - qOverhead)*1000/qFreq) + "ms"
    
    Macro nTimeTaken(i) = (qStop(i) - qStart(i) - qOverhead)*1000/qFreq
    ' End Timer Macros
    '*************************************************************************
    
    '*************************************************************************
    ' API error macro
    Macro SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FuncName$, Number ), "AES", %MB_ICONERROR + %MB_TOPMOST
    '*************************************************************************
    
    Global hProv As Dword
    ' Always determine in PBMain and not in a function to be called often - it is time consuming - 6ms on my machine!
    
    %Display = %True
    
    Function PBMain
    Local sInterimOutPut, sFinalOutPut As String
    Local i As Long
    
      InitializeTimer
      
      hProv = crGetDefaultRSAHandle
      If hProv = 0 Then Exit Function
      
      PBCryptRandom( 32, %Bin ) ' Dummy run to set up initial values
       
      #If %Display 
        sFinalOutPut = "PBCryptRandom" + $CrLf + $CrLf
        For i= 1 To 32
          sInterimOutPut = PBCryptRandom( 32, %Hex )
          sFinalOutPut = sFinalOutPut + sInterimOutPut + $CrLf
        Next i
      #Else
        StartTimer(0)
          PBCryptRandom( 1000000, %Bin )
        StopTimer(0)
      #EndIf
    	
      #If %Display
        MsgBox sFinalOutput
      #Else
        MsgBox "PBCryptRandom: " + sTimeTaken( 0, 2 )
      #EndIf
    	
      Reset sFinalOutput 
    	
      #If %Display
        sFinalOutPut = "MSCryptRandom" + $CrLf + $CrLf
        For i = 1 To 32
          sInterimOutPut = MSCryptRandom( 32, %Hex )
          sFinalOutPut = sFinalOutPut + sInterimOutPut + $CrLf
        Next i
      #Else
        StartTimer(0)
          MSCryptRandom( 1000000, %Bin )
        StopTimer(0)
      #EndIf
    	
      #If %Display
        MsgBox sFinalOutPut
      #Else
        MsgBox "MSCryptRandom:" + sTimeTaken( 0, 2 )
      #EndIf
    
      If hProv Then CryptReleaseContext hProv, 0  
    	
    End Function
    
    '*************************************************************************
    
    Function PBCryptRandom( ByVal ToTalbytes As Long, ByVal Flag As Long ) As String
    Local Blocks, Clip, i, j, hKey, hHash, WinErr As Long
    Local Seed, sHex, sPlaintext As String
    Local ptrPT As Dword
    Local pbyte As Byte Ptr
    Dim sTotalPbdata As String ' Dim to avoid potential stack overuse
    Dim Dummy As String * 16
    Static sPassword, OuterIV, pbdata As String
    Static InnerIV() As Byte
    
      If pbdata = "" Then ' this is the 1st pass of PBCryptRandom
        Seed = GetCryptoSeed(%Bin)
        Randomize
        Seed = StrDelete$( Seed, 16*Rnd(0,4)+1, 16 )
        OuterIV = Left$( Seed, 16 )
        sPassword = Mid$( Seed, 17, 32 )
        Dim InnerIV(0 To 15) As Static Byte At VarPtr( Dummy )
        Dummy = Right$( Seed, 16 )
        pbdata = OuterIV
      End If
    	    
      If CryptCreateHash( hProv, %CALG_SHA_256, 0, 0, hHash ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptCreateHash", 10 )
        Function = ""
        GoTo TidyUp
      Else
        If CryptHashData( hHash, ByVal StrPtr(sPassword), Len( sPassword ), 0 ) = %False Then
          WinErr = GetLastError : SysErrMsg( "CryptHasData", 20 )
          Function = ""
          GoTo TidyUp
        Else
          If CryptDeriveKey( hProv, %CALG_AES_256, hHash, 0, hKey ) = %False Then
            WinErr = GetLastError : SysErrMsg( "CryptDeriveKey", 30 )
    	Function = ""
    	GoTo TidyUp
          End If
        End If
      End If
    	
      ' Override default inner IV array
      If CryptSetKeyParam( hKey, %KP_IV, InnerIV( 0 ), 0 ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptSetKeyParam", 40 )
        Function = ""
        GoTo TidyUp
      End If
    	
      Blocks = TotalBytes\32
      If (TotalBytes < 32) Or (TotalBytes Mod 32 <> 0) Then
        Incr Blocks
        Clip = %True
      End If
    	
      If Flag = %Bin then
        sTotalPbdata = Space$( 32*Blocks )
      Else
        sTotalPbdata = Space$( 64*Blocks )
      End If
    	
      For i = 0 To Blocks - 1
    	
        ' Get a couple of Time Stamps and put into sPlainText
        sPlaintext = Space$(16)
        ptrPt = StrPtr( sPlaintext )
        ! cpuid
        ! RDTSC
        ! mov esi, ptrPt
        ! mov [esi+8], edx
        ! mov [esi+12], eax
        ! RDTSC
        ! mov [esi], edx
        ! mov [esi+4], eax
      	  	  	
        ' pbdata = OuterIV when i = 0 and this is the 1st or only application session
        ' and equals the output of CryptEncrypt for all other events.
        AXorB(sPlaintext, pbdata) ' sPlainText = sPlainText XOR pbdata
        ' AES ciphertext = plaintext + 16 bytes
        pbdata = sPlaintext + Space$(16)
          	
        If CryptEncrypt( hKey, 0, %True, 0, ByVal StrPtr( pbdata ), 16, 32 ) = %False Then 
          WinErr = GetLastError : SysErrMsg( "CryptEncrypt", 40 )
          Function = "" 
          GoTo TidyUp 
        End If
        
        If Flag = %Bin Then
          Mid$( sTotalPbdata, 32*i + 1, 32 ) = pbdata
        Else
          pbyte = StrPtr(pbdata)
          For j = 0 To 31
            sHex = sHex + Hex$(@pbyte[j],2)
          Next j
          Mid$( sTotalPbdata, 64*i + 1, 64 ) = sHex
        End If
     
      Next
      
      If Clip Then sTotalPbdata = Left$(sTotalPbdata, (2-Flag)*TotalBytes)
      
      Function = sTotalPbdata
      
    TidyUp:	
    	
    	If hHash Then CryptDestroyHash hHash
    	If hKey Then CryptDestroyKey hKey
      
    End Function
    
    '*************************************************************************
    
    Function MSCryptRandom(ByVal ToTalbytes As Dword, ByVal Flag As Long) As String
    Local WinErr, i As Long
    Dim RandomBytes() As Byte
    Dim strHex As String
    
      ReDim RandomBytes( TotalBytes - 1 ) As Byte
      
      If CryptGenRandom( ByVal hProv, ByVal ToTalBytes, RandomBytes( 0 ) )= 0 Then
        WinErr = GetLastError : SysErrMsg( "CryptGenRandom", 10 )
        Function = ""
        Exit Function
      End If
    
      If Flag = %Bin Then
        Function = Peek$( VarPtr( RandomBytes( 0 ) ), TotalBytes )
      Else
        For i = 0 To TotalBytes -1 
          strHex = strHex + Hex$(Randombytes(i),2)  
        Next
        Function = strHex
      End If
    
    End Function
    
    '*************************************************************************
    
    Function AXorB( A As String, B As String ) As Long
    
    ' A becomes A Xor B, B remains unchanged
    ' Computation is limited to the length of the shorter string
    ' if the strings are not the same length
    
    #Register None
    Local ptrA, ptrB, StringEnd As Dword
    	
      ptrA = StrPtr( A ) - 1
      ptrB = StrPtr( B ) - 1
      StringEnd = StrPtr( A ) + Len( A )
      If Len( A ) > Len( B ) Then StringEnd = StrPtr( A ) + Len( B )
      ! mov esi, ptrA
      ! mov edi, ptrB
      ! mov ecx, StringEnd
    StartLoop:
      ! inc esi ' 1st pass is
      ! inc edi ' start of strings
      ! cmp esi, ecx ' Are we at end of strings?
      ! je EndLoop ' Yes
      ! mov al, [esi ] ' Get byte in A
      ! Xor al, [edi ] ' al becomes byte in A Xor byte in B
      ! mov [esi ], al ' Put byte in A
      ' [edi] is unchanged ie B
      ! jmp StartLoop
    EndLoop:
    
      Function = %True
    
    End Function
    
    '*************************************************************************
    
    Function GetCryptoSeed( ByVal Flag As Long) As String
    Local hKey, BinarySize As Dword
    Local WinErr, i As Long
    Local RegKey, RegValueName As Asciiz * 256
    Dim BinaryByte( ) As Byte
    Dim HexByte( ) As String * 2
    Local hexString As String
    
      BinarySize = 80
      ReDim BinaryByte( BinarySize - 1 ) As Byte
    
      RegKey = "SOFTWARE\Microsoft\Cryptography\RNG"
      RegValueName = "Seed"
      
      WinErr = RegOpenKeyEx( %HKEY_LOCAL_MACHINE, RegKey, ByVal %Null, %KEY_READ, hKey )
      If WinErr <> %ERROR_SUCCESS Then
        SysErrMsg( "RegOpenKeyEx", 10 )
        Exit Function
      End If
    
      WinErr = RegQueryValueEx( ByVal hKey, RegValueName, ByVal %Null, %REG_BINARY, BinaryByte( 0 ), BinarySize )
      If WinErr <> %ERROR_SUCCESS Then
        SysErrMsg( "RegQueryValueEx", 20 )
        Exit Function
      End If
    
      WinErr = RegCloseKey( ByVal hKey )
      If WinErr <> %ERROR_SUCCESS Then
        SysErrMsg( "RegCloseKey", 30 )
        Exit Function
      End If
      
      If Flag = %Bin Then
        Function = Peek$( VarPtr( BinaryByte( 0 ) ), BinarySize )
      Else
        hexString = Space$( 2 * BinarySize )
        ReDim HexByte( BinarySize - 1 ) As String * 2 At StrPtr( hexString )
        ' Overlay hexString with HexByte()
        For i = 0 To BinarySize - 1
          HexByte( i ) = Hex$( BinaryByte( i ), 2 )
        Next
        Function = hexString
      End If
      
    End Function
    
    '*************************************************************************
    
    Function crGetDefaultRSAHandle As Long
    Local WinErr As Long
    
    If CryptAcquireContext( hProv, ByVal %Null, ByVal %Null, %PROV_RSA_AES, 0 ) = %False Then
      If CryptAcquireContext( hProv, ByVal %Null, $MS_ENH_RSA_AES_PROV, %PROV_RSA_AES, %CRYPT_NEWKEYSET ) = %False Then
        WinErr = GetLastError : SysErrMsg( "CryptAcquireContext", 10 )
        Function = %False
      Else
        Function = hProv
      End If
    Else
      Function = hProv
    End If
    
    End Function
    
    '*************************************************************************
    
    Function SystemErrorMessage( ByVal WinErr As Long, API As String, sFunction As String, ByVal Number As Long ) As String
      Local pBuffer As Asciiz Ptr, ncbBuffer As Dword
      Local sText As String
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER Or %FORMAT_MESSAGE_FROM_SYSTEM Or %FORMAT_MESSAGE_IGNORE_INSERTS, _
        ByVal %Null, WinErr, %Null, ByVal VarPtr( pBuffer ), 0, ByVal %Null )
      If ncbBuffer Then
        sText = Peek$( pBuffer, ncbBuffer )
        sText = Remove$( sText, Any Chr$( 13 ) + Chr$( 10 ) )
        Function = $CrLf + "Error" + Format$( WinErr, " #####" ) + " during " + API + $CrLf + $CrLf + _
          Chr$(34) + sText + Chr$(34) + $CrLf + $CrLf + "Location : " + sFunction + IIf$( Number, Format$( Number, " ###" ), "" )
        LocalFree pBuffer
      Else
        Function = "Unknown error - Code:" + Format$( WinErr, " #####" )
      End If
    
    End Function
    
    '*************************************************************************
    Attached Files
    Last edited by David Roberts; 23 Mar 2010, 09:40 AM.

    Leave a comment:


  • David Roberts
    replied
    Part IV

    Drifting a little off topic here as we look at generating random numeric values such as Word, Double, Long and so on via a single function.

    A random string, sRandom, is generated and converted to numeric form with one of the CVx functions and assigned as a VARIANT.

    We cannot assign a VARIANT to a FUNCTION, so it seems, so the returned value comes back to the caller via a parameter.

    We would have something like this.

    Local x As Variant
    Local Test As Double

    GetRandomNumeric( x, hProc, "double" )
    Test = Variant#(x)

    In the following code the method in Part III is used, and hence hProc, but the method in Part II could be used and even the method in Part I if only a few random numerics were required.

    However, if cryptographic security was not a requirement then this would be an ideal candidate for RND and GetRandomNumeric can easily be rewritten to accommodate RND.

    The code below generates a random byte, integer, word, dword, long, single, currency, double and quad with successive calls to GetRandomNumeric.

    Code:
    #COMPILE  EXE
    #REGISTER NONE
    #DIM      ALL
    #TOOLS    OFF
    
    #INCLUDE "WIN32API.INC"
    
    %NOMMIDS = 1
    %NOGDI = 1
    
    $App = "GetRandomNumeric"
    
    MACRO SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FUNCNAME$, Number ), $App, %MB_ICONERROR + %MB_TOPMOST
    
    DECLARE FUNCTION GetRandomNumeric( VARIANT, BYVAL DWORD, BYVAL STRING ) AS LONG
    DECLARE FUNCTION RtlGenRandom( RandomBuffer AS BYTE, BYVAL RandomBufferLength AS DWORD ) AS LONG
    DECLARE FUNCTION SystemErrorMessage( BYVAL LONG, STRING, STRING, BYVAL LONG ) AS STRING
    
    FUNCTION PBMAIN( ) AS LONG
      
      LOCAL hLib, hProc AS DWORD, WinErr AS LONG
      LOCAL x AS VARIANT, msgboxText AS STRING
       
      hLib = LoadLibrary( "advapi32.dll")
      IF hLib = 0 THEN
        WinErr = GetLastError : SysErrMsg( "LoadLibrary", 10 )
        EXIT FUNCTION
      END IF
      
      hProc = GetProcAddress(hLib, "SystemFunction036")
      IF hProc = 0 THEN
        WinErr = GetLastError : SysErrMsg( "GetProcAddress", 20 )
        EXIT FUNCTION
      END IF
       
      GetRandomNumeric( x, hProc, "byte" )
      msgboxText = msgboxText + "Byte: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "integer" )
      msgboxText = msgboxText + "Integer: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "word" )
      msgboxText = msgboxText + "Word: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "dword" )
      msgboxText = msgboxText + "Dword: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "long" )
      msgboxText = msgboxText + "Long: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "single" )
      msgboxText = msgboxText + "Single: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "currency" )
      msgboxText = msgboxText + "Currency: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "double" )
      msgboxText = msgboxText + "Double: " + STR$( VARIANT#(x) ) + $CRLF
      
      GetRandomNumeric( x, hProc, "quad" )
      msgboxText = msgboxText + "Quad: " + STR$( VARIANT#(x) ) + $CRLF
      
      MSGBOX msgboxText,, "GetRandomNumeric"
      
      FreeLibrary hLib
      
    END FUNCTION
    
    FUNCTION GetRandomNumeric( x AS VARIANT, BYVAL hProc AS DWORD, BYVAL ContentType AS STRING ) AS LONG
      LOCAL ReturnValue, BinarySize AS LONG
      DIM BinaryByte( )   AS BYTE
      LOCAL sRandom   AS STRING
         
      ContentType = UCASE$( ContentType )
      
      SELECT CASE ContentType
        CASE "BYTE"
          BinarySize = 1
        CASE "INTEGER", "WORD"
          BinarySize = 2
        CASE "DWORD", "LONG", "SINGLE"
          BinarySize = 4
        CASE "CURRENCY", "DOUBLE", "QUAD"
          BinarySize = 8
        CASE ELSE
          MSGBOX "Content Type " + ContentType + " is not known",, "GetRandomNumeric"
          EXIT FUNCTION
      END SELECT
      
      REDIM BinaryByte( BinarySize - 1 ) AS BYTE
        
      CALL DWORD hProc USING RtlGenRandom( BinaryByte(0), BYVAL BinarySize ) TO ReturnValue
      
      IF ReturnValue = %False THEN EXIT FUNCTION
      
      sRandom = PEEK$( VARPTR( BinaryByte( 0 ) ), BinarySize )
      
      SELECT CASE ContentType
        CASE "BYTE"
          x = CVBYT( sRandom ) AS BYTE
        CASE "INTEGER"
          x = CVI( sRandom ) AS INTEGER
        CASE "WORD"
          x = CVWRD( sRandom ) AS WORD
        CASE "DWORD"
          x = CVDWD( sRandom ) AS DWORD
        CASE "LONG"
          x = CVL( sRandom ) AS LONG
        CASE "SINGLE"
          x = CVS( sRandom ) AS SINGLE
        CASE "CURRENCY"
          x = CVCUR( sRandom ) AS CURRENCY
        CASE "DOUBLE"
          x = CVD( sRandom ) AS DOUBLE
        CASE "QUAD"
          x = CVQ( sRandom ) AS QUAD
      END SELECT
      
      FUNCTION = %True
              
    END FUNCTION
    
    FUNCTION SystemErrorMessage( BYVAL WinErr AS LONG, API AS STRING, sFunction AS STRING, BYVAL Number AS LONG ) AS STRING
      LOCAL pBuffer AS ASCIIZ PTR, ncbBuffer AS DWORD
      DIM sText           AS STRING
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER OR %FORMAT_MESSAGE_FROM_SYSTEM OR %FORMAT_MESSAGE_IGNORE_INSERTS, _
        BYVAL %Null, WinErr, %Null, BYVAL VARPTR( pBuffer ), 0, BYVAL %Null )
      IF ncbBuffer THEN
        sText = PEEK$( pBuffer, ncbBuffer )
        sText = REMOVE$( sText, ANY CHR$( 13 ) + CHR$( 10 ) )
        FUNCTION = $CRLF + "Error" + FORMAT$( WinErr, " #####" ) + " during " + API + $CRLF + $CRLF + _
          $DQ + sText + $DQ + $CRLF + $CRLF + "Location : " + sFunction + IIF$( Number, FORMAT$( Number, " ###" ), "" )
        LocalFree pBuffer
      ELSE
        FUNCTION = "Unknown error - Code:" + FORMAT$( WinErr, " #####" )
      END IF
    
    END FUNCTION

    Leave a comment:


  • David Roberts
    replied
    Part III

    As mentioned in Part I the Windows CryptoAPI function CryptGenRandom is currently based on an internal function RtlGenRandom. CryptGenRandom has been around since at least Windows 95. RtlGenRandom, on the other hand, was introduced in Windows XP and is used in Windows Vista as well. In particular, note then that it is not used in Windows 2000.

    The following code does not test for OS version so, please, bear in mind - XP and Vista ONLY.

    There is no interface for RtlGenRandom and there is no dll entry point for it either. Don't worry, it is documented and is exported via SystemFunction036 in advapi32.dll. To get at it we have to use the LoadLibrary/GetProcAddress combination.

    The point of the exercise? We don't need to implement the CrytoAPI.

    The example simply determines a 32 byte hex string.

    As with all the code in this thread the output may be binary as well.

    Code:
    #COMPILE  EXE
    #REGISTER NONE
    #DIM      ALL
    #TOOLS    OFF
    
    #INCLUDE "WIN32API.INC"
    
    %NOMMIDS = 1
    %NOGDI = 1
    
    $App = "GenKey036"
    %Bin = 1
    %Hex = 0
    
    MACRO SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FUNCNAME$, Number ), $App, %MB_ICONERROR + %MB_TOPMOST
    
    DECLARE FUNCTION RtlGenRandom( RandomBuffer AS BYTE, BYVAL RandomBufferLength AS DWORD ) AS LONG
    DECLARE FUNCTION GetCryptoKey036( BYVAL DWORD, BYVAL LONG ) AS STRING
    DECLARE FUNCTION SystemErrorMessage( BYVAL LONG, STRING, STRING, BYVAL LONG ) AS STRING
    
    FUNCTION PBMAIN( ) AS LONG
      DIM sKey AS STRING
      
      sKey = GetCryptoKey036( 32, %Hex )
      MSGBOX sKey,, "GenKey036"
    
    END FUNCTION
    
    FUNCTION GetCryptoKey036( BYVAL BinarySize AS DWORD, BYVAL Flag AS LONG ) AS STRING
      LOCAL hLib, hProc AS DWORD, i, WinErr, ReturnValue AS LONG
      DIM BinaryByte( )   AS BYTE
      DIM HexByte( ) AS STRING * 2
      LOCAL hexString       AS STRING
      
      REDIM BinaryByte( BinarySize - 1 ) AS BYTE
      
      hLib = LoadLibrary( "advapi32.dll")
      IF hLib = 0 THEN
        WinErr = GetLastError : SysErrMsg( "LoadLibrary", 10 )
        EXIT FUNCTION
      END IF
      
      hProc = GetProcAddress(hLib, "SystemFunction036")
      IF hProc = 0 THEN
        WinErr = GetLastError : SysErrMsg( "GetProcAddress", 20 )
        EXIT FUNCTION
      END IF
      
      CALL DWORD hProc USING RtlGenRandom( BinaryByte(0), BYVAL BinarySize ) TO ReturnValue
      FreeLibrary hLib
      IF ReturnValue = %False THEN EXIT FUNCTION
      
      IF Flag = %Bin THEN
        FUNCTION = PEEK$( VARPTR( BinaryByte( 0 ) ), BinarySize )
      ELSE
        hexString = SPACE$( 2 * BinarySize )
        REDIM HexByte( BinarySize - 1 ) AS STRING * 2 AT STRPTR( hexString )
        ' Overlay hexString with HexByte()
        FOR i = 0 TO BinarySize - 1
          HexByte( i ) = HEX$( BinaryByte( i ), 2 )
        NEXT
        FUNCTION = hexString
      END IF
      
    END FUNCTION
    
    FUNCTION SystemErrorMessage( BYVAL WinErr AS LONG, API AS STRING, sFunction AS STRING, BYVAL Number AS LONG ) AS STRING
      LOCAL pBuffer AS ASCIIZ PTR, ncbBuffer AS DWORD
      DIM sText           AS STRING
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER OR %FORMAT_MESSAGE_FROM_SYSTEM OR %FORMAT_MESSAGE_IGNORE_INSERTS, _
        BYVAL %Null, WinErr, %Null, BYVAL VARPTR( pBuffer ), 0, BYVAL %Null )
      IF ncbBuffer THEN
        sText = PEEK$( pBuffer, ncbBuffer )
        sText = REMOVE$( sText, ANY CHR$( 13 ) + CHR$( 10 ) )
        FUNCTION = $CRLF + "Error" + FORMAT$( WinErr, " #####" ) + " during " + API + $CRLF + $CRLF + _
          $DQ + sText + $DQ + $CRLF + $CRLF + "Location : " + sFunction + IIF$( Number, FORMAT$( Number, " ###" ), "" )
        LocalFree pBuffer
      ELSE
        FUNCTION = "Unknown error - Code:" + FORMAT$( WinErr, " #####" )
      END IF
    
    END FUNCTION
    Last edited by David Roberts; 24 Apr 2008, 09:20 AM. Reason: MsgBox title

    Leave a comment:


  • David Roberts
    replied
    Part II

    CryptGenRandom's output buffer may be pre-filled with, preferably, random data to further 'muddy the waters'. As mentioned above the Seed employed uses a large entropy and we'd be hard pressed to find another source of random input.

    However, there is a source of random data that we can use - the output of CryptGenRandom itself.

    The following code employs a two-pass implementation of CryptGenRandom. The first pass generates 64 bytes [512 bits] or less if the requested output is less.

    GetCrytoKey will output either a binary or hex string and may be used for a variety of jobs including shared keys for HMAC, 'passwords' in text form or key files for PassKey and TrueCrypt, for example. The commented code was used for testing but left in for completeness.

    It is worth noting that the code is not written for speed and is a 'run every now and then' application. Nor should the code be regarded as an alternative for RND. RND is blindingly fast and superb for 'on the fly' random number generation. However, for cryptographic purposes RND should not be used - it was not designed for that.

    Added: BTW, hProv is got in 'GetCryptoKey'. If CrytoAPi is used extensively in an app then I get hProv in PBMain and set hProv as a Global. CRYPT_VERIFYCONTEXT is used in 'crGetDefaultRSAHandle' as no public/private key pairs are used. This would be the case for hashing algorithms as well. CRYPT_NEWKEYSET would be used when public/private key pairs are used as well.



    Code:
    #COMPILE EXE
    #REGISTER NONE
    #DIM ALL
    #TOOLS OFF
    
    #INCLUDE "WIN32API.INC"
    
    %NOMMIDS = 1
    %NOGDI = 1
    
    $MS_DEF_PROV = "Microsoft Base Cryptographic Provider v1.0"
    %CRYPT_VERIFYCONTEXT = &hF0000000
    %PROV_RSA_FULL = 1
    
    $App = "GenKey"
    %Bin = 1
    %Hex = 0
    
    MACRO SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FUNCNAME$, Number ), $App, %MB_ICONERROR + %MB_TOPMOST
    
    DECLARE FUNCTION CryptAcquireContext LIB "advapi32.dll" ALIAS "CryptAcquireContextA" _
      ( hCryptProv 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 hCryptProv 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 GetCryptoKey( BYVAL DWORD, BYVAL LONG ) AS STRING
    DECLARE FUNCTION crGetDefaultRSAHandle AS LONG
    DECLARE FUNCTION SystemErrorMessage( BYVAL LONG, STRING, STRING, BYVAL LONG ) AS STRING
    
    FUNCTION PBMAIN( ) AS LONG
    DIM sKey AS STRING
    LOCAL sngSeed AS SINGLE, i AS LONG
    
    ' *************************************************************
    
      ' Create a 20 Byte hex String For illustration purposes
    
      sKey = GetCryptoKey( 20, %Hex )
      MSGBOX sKey,, "GenKey"
      
    ' *************************************************************
    
    ' The following will create a file, Test.txt, on the root of C:
    ' In practice we would disguise the file and save to a folder
    ' where such files, bas for example, reside. Better still, save to
    ' a USB stick.
    
    ' Create a hex string key file for an app requiring one as
    ' input and converted internally to a binary string
    
    'sKey = GetCryptoKey( 32, %Hex ) ' Perhaps a shared key for HMAC-SHA256
    'Open "c:\Test.txt" For Binary As #1
    '  Put$ #1, sKey
    'Close #1
    'MsgBox "Done",, "GenKey"
    
    ' Create a 64 byte [512 bit] binary key file for PassKey
    
    'sKey = GetCryptoKey( 64, %Bin )
    'Open "c:\Test.txt" For Binary As #1
    '  Put$ #1, sKey
    'Close #1
    'MsgBox "Done",, "GenKey"
    
    ' Create a large binary key file for TrueCrypt
    
    'sKey = GetCryptoKey( 100*1024, %Bin )
    'Open "c:\Test.txt" For Binary As #1
    '  Put$ #1, sKey
    'Close #1
    'MsgBox "Done",, "GenKey"
    
    ' *************************************************************
    
    ' Create a Single seed for Randomize
    ' Lets knock out 20 to see what they look like
    
    LOCAL msgboxText AS STRING, RndSeed AS SINGLE
    msgboxText = "20 Single precision" + $CRLF + $CRLF
    FOR i = 1 TO 20
      DO
        sKey = GetCryptoKey( 4, %Bin )
        
        ' Reject 'Infinity', '-Infinity', '0', '-0' and remember little endian
        ' Requiring this loop will be a very rare event but, nonetheless, possible
      LOOP UNTIL ( sKey <> CHR$(0, 0, &H80, &H7F) ) AND ( sKey <> CHR$(0, 0, &H80, &HFF) ) _
      AND ( sKey <> CHR$(0,0,0,0) ) AND ( sKey <> CHR$(0,0,0, &H80) )
      RndSeed = CVS(sKey)
      msgboxText = msgboxText + STR$( RndSeed ) + $CRLF
    NEXT
    
    MSGBOX msgboxText,, "GenKey"
    
    ' *************************************************************
    
    END FUNCTION
    
    FUNCTION GetCryptoKey( BYVAL BinarySize AS DWORD, BYVAL Flag AS LONG ) AS STRING
    REGISTER i AS LONG
    LOCAL hProv, WinErr, CopyBinarySize, doRedim AS LONG
    DIM BinaryByte( )     AS BYTE
    DIM HexByte( )  AS STRING * 2
    LOCAL hexString   AS STRING
    
      IF BinarySize > 64 THEN ' if <= 64 then use same size buffer for both passes
        CopyBinarySize = BinarySize
        ' set up a small buffer to accept CryptGenRandom 1st pass output
        BinarySize = 64 ' 512 bit
        doRedim = %True
      END IF
      
      REDIM BinaryByte( BinarySize - 1 ) AS BYTE
      
      hProv = crGetDefaultRSAHandle
      IF hProv = 0 THEN EXIT FUNCTION
    
      ' 1st pass of CryptGenRandom has BinaryByte() empty
      IF CryptGenRandom( BYVAL hProv, BYVAL BinarySize, BinaryByte( 0 ) ) = 0 THEN
        WinErr = GetLastError : SysErrMsg( "CryptGenRandom", 10 )
        EXIT FUNCTION
      END IF
    
      IF doRedim THEN
        ' resize buffer to requested size
        BinarySize = CopyBinarySize
        ' and preserve 1st pass output
        REDIM PRESERVE BinaryByte( BinarySize - 1 ) AS BYTE
      END IF
      
      ' 2nd pass has BinaryByte() with 1st pass
      ' output as an auxiliary random seed
      IF CryptGenRandom( BYVAL hProv, BYVAL BinarySize, BinaryByte( 0 ) ) = 0 THEN
        WinErr = GetLastError : SysErrMsg( "CryptGenRandom", 10 )
        EXIT FUNCTION
      END IF
      
      IF Flag = %Bin THEN
        FUNCTION = PEEK$( VARPTR( BinaryByte( 0 ) ), BinarySize )
      ELSE
        hexString = SPACE$( 2 * BinarySize )
        REDIM HexByte( BinarySize - 1 ) AS STRING * 2 AT STRPTR( hexString )
        ' Overlay hexString with HexByte()
        FOR i = 0 TO BinarySize - 1
          HexByte( i ) = HEX$( BinaryByte( i ), 2 )
        NEXT
        FUNCTION = hexString
      END IF
    
      CryptReleaseContext hProv, 0
    
    END FUNCTION
    
    FUNCTION crGetDefaultRSAHandle AS LONG
    LOCAL hProv, WinErr AS LONG
    
      IF CryptAcquireContext( hProv, BYVAL %Null, BYVAL %Null, %PROV_RSA_FULL, 0 ) = %FALSE THEN
        IF CryptAcquireContext( hProv, BYVAL %Null, $MS_DEF_PROV, %PROV_RSA_FULL, _
          %CRYPT_VERIFYCONTEXT ) = %FALSE THEN
          WinErr = GetLastError : SysErrMsg( "CryptAcquireContext", 10 )
          FUNCTION = %FALSE
        ELSE
          FUNCTION = hProv
        END IF
      ELSE
        FUNCTION = hProv
      END IF
    
    END FUNCTION
    
    FUNCTION SystemErrorMessage( BYVAL WinErr AS LONG, API AS STRING, sFunction AS STRING, BYVAL Number AS LONG ) AS STRING
    LOCAL pBuffer AS ASCIIZ PTR, ncbBuffer AS DWORD
    DIM sText   AS STRING
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER OR %FORMAT_MESSAGE_FROM_SYSTEM OR %FORMAT_MESSAGE_IGNORE_INSERTS, _
        BYVAL %Null, WinErr, %Null, BYVAL VARPTR( pBuffer ), 0, BYVAL %Null )
      IF ncbBuffer THEN
        sText = PEEK$( pBuffer, ncbBuffer )
        sText = REMOVE$( sText, ANY CHR$( 13 ) + CHR$( 10 ) )
        FUNCTION = $CRLF + "Error" + FORMAT$( WinErr, " #####" ) + " during " + API + $CRLF + $CRLF + _
          $DQ + sText + $DQ + $CRLF + $CRLF + "Location : " + sFunction + IIF$( Number, FORMAT$( Number, " ###" ), "" )
        LocalFree pBuffer
      ELSE
        FUNCTION = "Unknown error - Code:" + FORMAT$( WinErr, " #####" )
      END IF
    
    END FUNCTION
    Last edited by David Roberts; 24 Apr 2008, 08:16 AM.

    Leave a comment:


  • David Roberts
    started a topic On cryptographic random bytes

    On cryptographic random bytes

    Part I

    The Windows CryptoAPI function CryptGenRandom is currently based on an internal function RtlGenRandom.

    The seed for this function is generated internally - we are not required to supply one. The entropy of this seed is got from a particularly comprehensive list of sources sufficient to produce a cryptographic value. The list includes the current process ID, the current thread ID, the ticks since boot, the current time, various high-precision counters (QueryPerformanceCounter), an MD4 hash of the user's environment block, high-precision internal CPU counters such as RDTSC, RDMSR and RDPMC. In addition, there is a long list of low-level system information.

    The generated seed is placed in the registry at

    %HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Cryptography\RNG with Seed as a 80 byte REG_BINARY.

    There is precious little mentioned of this key anywhere and has not been found at microsoft.com.

    Running Process Monitor from Windows Sysinternals with a filter of RNG\Seed it was found that Seed is refreshed each time a process opens. This is analogous to our including RANDOMIZE in each of our applications. With PowerBASIC each thread has its own, independent random number seed. With Windows Seed isn't even application specific - it is machine wide.

    The following code simply reads the above registry key into a string in either binary or hex format. A small and otherwise useless exe, "DoNowt.exe", is then opened and allowed to close without further ado and the registry key read again. In practice, we would, of course, not use "DoNowt.exe" - it is used here simply to illustrate the 'new process - new Seed' behaviour.

    Before running, "DoNowt.exe" will have to be compiled to the same directory as the main code and is no more than

    #Compile Exe "DoNowt.exe"

    Function PBMain() As Long

    END FUNCTION

    Here is a snapshot of Process Monitor executed before an early version of ReadSeed, the main code.



    Seed is refreshed eight times before we get a chance to read it. There is a short delay between the first and second refresh. Further refreshing is very rapid. This behaviour is the most common. Sometimes Seed is refreshed once and will not be refreshed again until some work is done by an application.

    No information has been found to explain this behaviour but what can be said is that Seed is refreshed at least once each time a process is opened. Second and subsequent instances of a process will also see Seed refreshed at least once.

    So, if an application requires random bytes and no more than 80 are needed then we need do no more than read Seed. A bonus is that these random bytes are cryptographic and can therefore be used for such things as HMAC shared keys, for example.

    Sometime ago a discussion in the forums considered using the system Time Stamp for seeding RND instead of using TIMER. The main code here finishes with using Seed to format a single precision value for seeding RND. A SINGLE is the preferred input according to Bob Zale.

    Part II will look at a two pass implementation of CryptGenRandom and Part III will look at an implementation of RtlGenRandom, thus avoiding any CryptoAPI overhead.

    Part IV looks at a method to provide random Bytes, Singles, Dwords, Longs and so on via a single function.

    Code:
    #COMPILE EXE
    #REGISTER NONE
    #DIM ALL
    #TOOLS OFF
    
    %NOMMIDS  = 1
    %NOGDI    = 1
    $App      = "ReadSeed"
    %Bin = 1
    %Hex = 0
    
    #INCLUDE "WIN32API.INC"
    
    MACRO SysErrMsg( API, Number ) = MessageBox 0, SystemErrorMessage( WinErr, API, FUNCNAME$, Number ), $App, %MB_ICONERROR + %MB_TOPMOST
    
    DECLARE FUNCTION GetCryptoSeed( BYVAL LONG ) AS STRING
    DECLARE FUNCTION SystemErrorMessage( BYVAL LONG, STRING, STRING, BYVAL LONG ) AS STRING
    
    FUNCTION PBMAIN( ) AS LONG
    
    LOCAL i AS LONG
    LOCAL sSeed, BinSeed, msgboxText AS STRING
    LOCAL RndSeed AS SINGLE
    
      msgboxText = "Before 'DoNowt.exe' executed" + $CRLF + $CRLF
      
      DO
        
        sSeed = GetCryptoSeed( %Hex )
    
        msgboxText = msgboxText + MID$( sSeed, 1, 80 ) + $CRLF
        msgboxText = msgboxText + MID$( sSeed, 81, 160 ) + $CRLF + $CRLF
            
        INCR i : IF i = 2 THEN EXIT LOOP
        msgboxText = msgboxText + "After 'DoNowt.exe' executed" + $CRLF + $CRLF
        
        SHELL "DoNowt.exe", 0
    
      LOOP
      
      sSeed = GetCryptoSeed( %Bin )
      FOR i = 1 TO 77
        BinSeed = MID$(sSeed, i, 4 )
        ' Reject 'Infinity', '-Infinity', '0', '-0' and remember little endian
        ' Requiring this loop will be a very rare event but, nonetheless, possible
        IF ( BinSeed <> CHR$(0, 0, &H80, &H7F) ) AND ( BinSeed <> CHR$(0, 0, &H80, &HFF) ) _
          AND ( BinSeed <> CHR$(0,0,0,0) ) AND ( BinSeed <> CHR$(0,0,0, &H80) ) THEN EXIT FOR
      NEXT
      
      RndSeed = CVS( BinSeed )
      
      msgboxText = msgboxText + "Single precision seed for RND: " + STR$( RndSeed )
         
      MSGBOX msgboxText
      
    END FUNCTION 
    
    FUNCTION GetCryptoSeed( BYVAL Flag AS LONG) AS STRING
    LOCAL hKey, BinarySize AS DWORD
    LOCAL WinErr, i AS LONG
    LOCAL RegKey, RegValueName AS ASCIIZ * 256
    DIM BinaryByte( )    AS BYTE
    DIM HexByte( )     AS STRING * 2
    LOCAL hexString AS STRING
    
      BinarySize = 80
      REDIM BinaryByte( BinarySize - 1 ) AS BYTE
    
      RegKey = "SOFTWARE\Microsoft\Cryptography\RNG"
      RegValueName = "Seed"
      
      WinErr = RegOpenKeyEx( %HKEY_LOCAL_MACHINE, RegKey, BYVAL %Null, %KEY_READ, hKey )
      IF WinErr <> %ERROR_SUCCESS THEN
        SysErrMsg( "RegOpenKeyEx", 10 )
        EXIT FUNCTION
      END IF
    
      WinErr = RegQueryValueEx( BYVAL hKey, RegValueName, BYVAL %Null, %REG_BINARY, BinaryByte( 0 ), BinarySize )
      IF WinErr <> %ERROR_SUCCESS THEN
        SysErrMsg( "RegQueryValueEx", 20 )
        EXIT FUNCTION
      END IF
    
      WinErr = RegCloseKey( BYVAL hKey )
      IF WinErr <> %ERROR_SUCCESS THEN
        SysErrMsg( "RegCloseKey", 30 )
        EXIT FUNCTION
      END IF
      
      IF Flag = %Bin THEN
        FUNCTION = PEEK$( VARPTR( BinaryByte( 0 ) ), BinarySize )
      ELSE
        hexString = SPACE$( 2 * BinarySize )
        REDIM HexByte( BinarySize - 1 ) AS STRING * 2 AT STRPTR( hexString )
        ' Overlay hexString with HexByte()
        FOR i = 0 TO BinarySize - 1
          HexByte( i ) = HEX$( BinaryByte( i ), 2 )
        NEXT
        FUNCTION = hexString
      END IF
      
    END FUNCTION
    
    FUNCTION SystemErrorMessage( BYVAL WinErr AS LONG, API AS STRING, sFunction AS STRING, BYVAL Number AS LONG ) AS STRING
    
    LOCAL pBuffer AS ASCIIZ PTR, ncbBuffer AS DWORD
    DIM sText AS STRING
    
      ncbBuffer = FormatMessage( %FORMAT_MESSAGE_ALLOCATE_BUFFER OR %FORMAT_MESSAGE_FROM_SYSTEM OR %FORMAT_MESSAGE_IGNORE_INSERTS, _
        BYVAL %Null, WinErr, %Null, BYVAL VARPTR( pBuffer ), 0, BYVAL %Null )
      IF ncbBuffer THEN
        sText = PEEK$( pBuffer, ncbBuffer )
        sText = REMOVE$( sText, ANY CHR$( 13 ) + CHR$( 10 ) )
        FUNCTION = $CRLF + "Error" + FORMAT$( WinErr, " #####" ) + " during " + API + $CRLF + $CRLF + _
          $DQ + sText + $DQ + $CRLF + $CRLF + "Location : " + sFunction + IIF$( Number, FORMAT$( Number, " ###" ), "" )
        LocalFree pBuffer
      ELSE
          FUNCTION = "Unknown error - Code:" + FORMAT$( WinErr, " #####" )
      END IF
    
    END FUNCTION
    Last edited by David Roberts; 26 Apr 2008, 02:43 PM. Reason: Mentioned Part IV
Working...
X
😀
🥰
🤢
😎
😡
👍
👎