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

SHA256 Secure Hash for PBCC 4/5+ and PBWin 8/9+

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

  • Greg Turgeon
    replied
    Code:
    '=====================================================================
    '-- SHA256c.BAS
    '-- Test bed for SHA256c.INC
    '-- Compiles with either PBWIN 8/9+ or PBCC 4/5+
    '=====================================================================
    #COMPILE EXE
    #DIM ALL
    #REGISTER NONE
    
    '============
    #INCLUDE "WIN32API.INC"
    #INCLUDE "SHA256c.INC"
    
    '--------------------
    'Utility macros
    '--------------------
    #IF %def(%pb_win32)
       MACRO eol=$CR
       MACRO say(t)
          #IF %PB_REVISION >= &H900
             MessageBox 0&, BYCOPY (t), exe.namex$, %MB_OK OR %MB_TASKMODAL
          #ELSE
             MessageBox 0&, BYCOPY (t), "", %MB_OK OR %MB_TASKMODAL
          #ENDIF
       END MACRO
       MACRO EnterCC
       END MACRO
       MACRO ExitCC
       END MACRO
       #IF %PB_REVISION < &H900
          MACRO IsFile(fname) =(len(dir$(fname,(%READONLY OR %HIDDEN OR %SYSTEM)))<>0)
       #ENDIF
    #ELSEIF %def(%pb_cc32)
       MACRO eol=$CRLF
       MACRO say(t)=stdout t
    
       MACRO EnterCC
          LOCAL launched AS LONG
          if (cursory = 1) and (cursorx = 1) then launched = -1
       END MACRO
    
       MACRO ExitCC
          if launched then
             input flush
             stdout "Press any key to end"
             waitkey$
          end if
       END MACRO
    
       #IF %PB_REVISION < &H500
          MACRO IsFile(fname) =(len(dir$(fname,(%READONLY OR %HIDDEN OR %SYSTEM)))<>0)
       #ENDIF
    #ENDIF
    
    DECLARE SUB VerifyImplementation()
    DECLARE FUNCTION ShowHash32(shouldBe$, Hash$) AS LONG
    DECLARE FUNCTION Hex2ShowDword(Buffer$) AS STRING
    DECLARE FUNCTION Get_FileSize(File_Name$) AS QUAD
    
    
    '====================
    FUNCTION PBMain() AS LONG
    REGISTER i AS LONG
    EnterCC   
    VerifyImplementation
    '============
    ExitMain:
    ExitCC
    END FUNCTION
    
    
    '====================
    SUB VerifyImplementation()
    LOCAL buffer, sha, shouldBe AS STRING
    gosub TestVectors1
    gosub TestVectors2
    gosub TestVectors3
    gosub TestVectors4
    gosub TestVectors5
    gosub TestVectors6
    gosub TestVectors7
    gosub FileHash
    EXIT SUB
    
    '============
    TestVectors1:
    buffer = "abc" 
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldBe = "BA7816BF 8F01CFEA 414140DE 5DAE2223 B00361A3 96177A9C B410FF61 F20015AD"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors2:
    buffer = "abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq"
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldBe = "248D6A61 D20638B8 E5C02693 0C3E6039 A33CE459 64FF2167 F6ECEDD4 19DB06C1"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors3:
    buffer = "abcdefghbcdefghicdefghijdefghijkefghijklfghijklmghijklmnhij"
    buffer = buffer + "klmnoijklmnopjklmnopqklmnopqrlmnopqrsmnopqrstnopqrstu"
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldBe = "CF5B16A7 78AF8380 036CE59E 7B049237 0B249B11 E8F07A51 AFAC4503 7AFEE9D1"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors4:
    buffer = string$(1000000,"a")
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldBe = "CDC76E5C 9914FB92 81A1C7E2 84D73E67 F1809A48 A497200E 046D39CC C7112CD0"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors5:
    buffer = "message digest"
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldbe = "F7846F55 CF23E14E EBEAB5B4 E1550CAD 5B509E33 48FBC4EF A3A1413D 393CB650"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors6:
    buffer = "abcdefghijklmnopqrstuvwxyz"
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldbe = "71C480DF 93D6AE2F 1EFAD144 7C66C952 5E316218 CF51FC8D 9ED832F2 DAF18B73"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    TestVectors7:
    buffer = ""
    sha = string$(32,0)
    SHA256_Buffer byval strptr(buffer), len(buffer), byval strptr(sha)
    shouldbe = "E3B0C442 98FC1C14 9AFBF4C8 996FB924 27AE41E4 649B934C A495991B 7852B855"
    ShowHash32 shouldBe, sha
    RETURN
    
    '============
    FileHash:
    LOCAL t$, file_name$, ecode&, file_size AS QUAD
    LOCAL t1, t2, t3 AS SINGLE
    
    file_name = ""
    
    if len(file_name) = 0 then
       say("No file specified")
       return
    end if
    if isfile(file_name) = 0 then
       say("Cannot find file " + file_name)
       return
    end if
    
    t1 = GetTickCount
    ecode = SHA256_File(File_Name$, sha$)
    t2 = GetTickCount
    if ecode then 
       say("SHA256_File error" + str$(ecode) + eol + error$(ecode))
       return
    end if
    
    say(eol + file_name + eol + Hex2ShowDword(sha))
    file_size = Get_FileSize(file_name$)
    t3 = (t2-t1)/1000
    t = "File size: " + using$(",",file_size) + " bytes" + eol
    t = t + "Time elapsed: " + format$(t3,"###.###") + " seconds" + eol
    t = t + format$(file_size/t3,"#########,") + " BPS"
    say(t+eol)
    RETURN
    END SUB
    
    
    '====================
    FUNCTION ShowHash32(shouldBe$, Hash$) AS LONG
    LOCAL t$
    t = "Should be:"   + eol + shouldBe$ + eol
    t = t + "Actual: " + eol + Hex2ShowDWord(Hash$)
    say(t)
    END FUNCTION
    
    
    '====================
    FUNCTION Hex2ShowDword(Buffer$) AS STRING
    REGISTER i AS LONG, j AS LONG
    LOCAL t$, pbyte AS BYTE PTR
    pbyte = strptr(Buffer$)
    for i = 0 to (%HASHLEN\4)-1
       for j = 0 to 3
          t = t +  hex$(@pbyte,2)
          incr pbyte
       next j
       t = t + " "
    next i
    function = t
    END FUNCTION
    
    
    #IF %PB_REVISION >= &H900
    '====================
    FUNCTION Get_FileSize(File_Name$) AS QUAD
    LOCAL totalbytes AS QUAD, fdata AS DIRDATA
    if len(dir$(File_Name$, to fdata)) then
       totalbytes = fdata.FileSizeLow + fdata.FileSizeHigh
    end if
    function = totalbytes
    END FUNCTION
    #ELSE
    '====================
    FUNCTION Get_FileSize(File_Name$) AS QUAD
    LOCAL hFind, i AS LONG, totalBytes AS QUAD
    LOCAL fname AS ASCIIZ * %MAX_PATH
    LOCAL fdata AS WIN32_FIND_DATA
    
    fname = File_Name$
    hFind = FindFirstFile(fname, fdata)
    if hFind then
       totalBytes = fdata.nFileSizeLow + fdata.nFileSizeHigh
       if hFind then FindClose hFind
    end if
    function = totalbytes
    END FUNCTION
    #ENDIF
    
    '-- END SHA256c.BAS ---------------------------------------------------

    Leave a comment:


  • Greg Turgeon
    replied
    Code:
    '=====================================================================
    '-- SHA256c.INC
    '-- Compiles with either PBWIN 8/9+ or PBCC 4/5+
    '-- WIN32 API not required
    '-- Uses no global data
    '=====================================================================
    
    %TRUE                = 1
    %FALSE               = 0
    
    '-- Set to %FALSE to return big-endian hash$ (as in 2001 code)
    %RETURN_LITTLE_ENDIAN   = %TRUE
    
    %ALIGNMENT           =  16   
    
    %HASHLEN             = 32     'bytes
    %BLOCKSIZE           = 64     'bytes
    %FILE_BUFFERSIZE     = 32000  'bytes
    
    %S_ARRAY_SIZE        = (%HASHLEN)
    %W_ARRAY_SIZE        = (%BLOCKSIZE*4)
    
    TYPE SHA256_CONTEXT
       state       AS STRING * (%HASHLEN+%ALIGNMENT)
       pstate      AS DWORD PTR
       pdata       AS BYTE PTR
       datalength  AS LONG
       HasSSE2     AS LONG
       HasMMX      AS LONG
       k_array     AS LONG PTR
       s_array     AS LONG PTR
       w_array     AS LONG PTR
       Workspace   AS STRING * (%S_ARRAY_SIZE + %W_ARRAY_SIZE + (%ALIGNMENT * 2))  'w_array&() + s+_array&()
    END TYPE
    
    '--------------------
    MACRO align(p,alignment)=((p+(alignment-1)) AND (NOT(alignment-1)))
    
    DECLARE FUNCTION SHA256_Buffer(BYVAL pBuffer AS BYTE PTR, BYVAL Length AS DWORD, BYVAL Hash AS DWORD PTR) AS LONG
    DECLARE FUNCTION SHA256_File(File_Name$, Hash$) AS LONG
    DECLARE FUNCTION SHA256_Init(Ctx AS SHA256_CONTEXT) AS LONG
    DECLARE FUNCTION SHA256_MakePadding(BYVAL TotalBytes AS DWORD) AS STRING
    #IF %PB_REVISION >= &H900
    DECLARE FUNCTION HasSSE2() AS LONG
    DECLARE FUNCTION SHA256_Compress128(Ctx AS SHA256_CONTEXT) AS LONG
    #ENDIF
    DECLARE FUNCTION HasMMX() AS LONG
    DECLARE FUNCTION SHA256_Compress64(Ctx AS SHA256_CONTEXT) AS LONG
    DECLARE FUNCTION SHA256_Compress32(Ctx AS SHA256_CONTEXT) AS LONG
    
    
    '====================
    FUNCTION SHA256_Init(Ctx AS SHA256_CONTEXT) AS LONG
    LOCAL pInit, pworkspace, pstate AS LONG
    
    #IF %PB_REVISION >= &H900
    Ctx.HasSSE2= HasSSE2
    #ENDIF
    Ctx.HasMMX = HasMMX
    
    Ctx.k_array = codeptr(K_Array_Data)
    pInit = codeptr(Init_Values)
    
    pworkspace  = align(varptr(Ctx.Workspace), %ALIGNMENT)
    Ctx.s_array = pworkspace
    Ctx.w_array = pworkspace + %S_ARRAY_SIZE
    
    Ctx.pstate  = align(varptr(Ctx.state), %ALIGNMENT)
    pstate      = Ctx.pstate
    
    !  push     esi
    !  push     edi
    !  mov      esi,     pInit
    !  mov      edi,     pstate
    !  mov      ecx,     8
    !  cld
    !  rep      movsd
    !  pop      edi
    !  pop      esi
    EXIT FUNCTION
    '============
    #IF %PB_REVISION >= &H900
    #ALIGN 16
    #ENDIF
    Init_Values:
    ! DD  &h6A09E667???, &hBB67AE85???, &h3C6EF372???, &hA54FF53A???
    ! DD  &h510E527F???, &h9B05688C???, &h1F83D9AB???, &h5BE0CD19???
    K_Array_Data:
    ! DD  &h428a2f98???, &h71374491???, &hb5c0fbcf???, &he9b5dba5???, &h3956c25b???, &h59f111f1???
    ! DD  &h923f82a4???, &hab1c5ed5???, &hd807aa98???, &h12835b01???, &h243185be???, &h550c7dc3???
    ! DD  &h72be5d74???, &h80deb1fe???, &h9bdc06a7???, &hc19bf174???, &he49b69c1???, &hefbe4786???
    ! DD  &h0fc19dc6???, &h240ca1cc???, &h2de92c6f???, &h4a7484aa???, &h5cb0a9dc???, &h76f988da???
    ! DD  &h983e5152???, &ha831c66d???, &hb00327c8???, &hbf597fc7???, &hc6e00bf3???, &hd5a79147???
    ! DD  &h06ca6351???, &h14292967???, &h27b70a85???, &h2e1b2138???, &h4d2c6dfc???, &h53380d13???
    ! DD  &h650a7354???, &h766a0abb???, &h81c2c92e???, &h92722c85???, &ha2bfe8a1???, &ha81a664b???
    ! DD  &hc24b8b70???, &hc76c51a3???, &hd192e819???, &hd6990624???, &hf40e3585???, &h106aa070???
    ! DD  &h19a4c116???, &h1e376c08???, &h2748774c???, &h34b0bcb5???, &h391c0cb3???, &h4ed8aa4a???
    ! DD  &h5b9cca4f???, &h682e6ff3???, &h748f82ee???, &h78a5636f???, &h84c87814???, &h8cc70208???
    ! DD  &h90befffa???, &ha4506ceb???, &hbef9a3f7???, &hc67178f2???
    END FUNCTION
    
    
    #IF %PB_REVISION >= &H900
    '====================
    FUNCTION SHA256_Compress128(Ctx AS SHA256_CONTEXT) AS LONG
    #REGISTER NONE
    LOCAL k_array, s_array, w_array AS LONG
    LOCAL pstate, pdata, wi, ki, i AS LONG   
    
    '-- Copy for inline assembler
    w_array  = Ctx.w_array
    s_array  = Ctx.s_array
    k_array  = Ctx.k_array
    pstate   = Ctx.pstate
    pdata    = Ctx.pdata
    
    !  push     esi
    !  push     edi
    !  push     ebx
    
    '-- Copy current state into s&()
    !  mov      esi,     pstate           ;esi -> pCtx.state0
    !  mov      edi,     s_array
    !  movdqa   xmm0,    [esi]
    !  movdqa   xmm1,    [esi+16]
    !  movdqa   [edi],   xmm0
    !  movdqa   [edi+16],xmm1
    
    '-- Copy current data block to w&() w/little-to-big endian conversion
    !  mov      esi,     pdata
    !  mov      edi,     w_array
    !  movdqu   xmm0,    [esi]
    !  movdqu   xmm2,    [esi+16]
    !  movdqu   xmm4,    [esi+32]
    !  movdqu   xmm6,    [esi+48]
    
    !  pshufhw  xmm1,    xmm0, &b10110001
    !  pshufhw  xmm3,    xmm2, &b10110001
    !  pshufhw  xmm5,    xmm4, &b10110001
    !  pshufhw  xmm7,    xmm6, &b10110001
    
    !  pshuflw  xmm0,    xmm1, &b10110001
    !  pshuflw  xmm2,    xmm3, &b10110001
    !  pshuflw  xmm4,    xmm5, &b10110001
    !  pshuflw  xmm6,    xmm7, &b10110001
    
    !  movdqa   xmm1,    xmm0
    !  movdqa   xmm3,    xmm2
    !  movdqa   xmm5,    xmm4
    !  movdqa   xmm7,    xmm6
    
    !  psllw    xmm0,    8
    !  psllw    xmm2,    8
    !  psllw    xmm4,    8
    !  psllw    xmm6,    8
    
    !  psrlw    xmm1,    8
    !  psrlw    xmm3,    8
    !  psrlw    xmm5,    8
    !  psrlw    xmm7,    8
    
    !  por      xmm0,    xmm1
    !  por      xmm2,    xmm3
    !  por      xmm4,    xmm5
    !  por      xmm6,    xmm7
    
    !  movdqa   [edi],   xmm0
    !  movdqa   [edi+16],xmm2
    !  movdqa   [edi+32],xmm4
    !  movdqa   [edi+48],xmm6
    
    '-- Fill W[16to63]
    ! mov       esi,     w_array
    ! push      ebp
    ! mov       ebp,     16
    #ALIGN 4
    FillTop:
    !  mov      ebx,     ebp
    !  sub      ebx,     2
    !  mov      eax,     [esi+ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  sub      ebx,     13             ;prep for next access: (-2)+(-13) = -15
    !  ror      eax,     17
    !  ror      ecx,     19
    !  shr      edx,     10
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  mov      edi,     eax            ;edi = temp total
    !  mov      eax,     [esi+ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  ror      eax,     7
    !  ror      ecx,     18
    !  shr      edx,     3
    !  add      ebx,     8              ;= (-15)+8 = -7
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  add      edi,     eax
       
    !  mov      eax,     [esi+ebx*4]
    !  sub      ebx,     9              ;= (-7)+(-9) = -16
    !  add      edi,     eax
       
    !  mov      eax,     [esi+ebx*4]
    !  mov      ebx,     ebp
    !  add      eax,     edi
       
    !  inc      ebp
    !  mov      [esi+ebx*4], eax
    !  test     ebp,     &b111111       ;<64?
    !  jnz      FillTop
    !  pop      ebp
       
    '-- Compress: i& = 0 to 63
    !  xor      eax,     eax
    !  mov      esi,     s_array        ;here to CompressDone & END SUB: esi -> s[0]
    !  mov      i,       eax
    #ALIGN 4
    CompressTop:
    !  mov      ebx,     eax
    !  mov      edx,     w_array
    !  mov      eax,     [edx+ebx*4]
    !  mov      wi,      eax
    !  mov      edx,     k_array
    !  mov      eax,     [edx+ebx*4]
    !  mov      ki,      eax
       
    !  mov      eax,     [esi+16]
    !  mov      ecx,     [esi+20]
    !  mov      ebx,     eax
    !  mov      edx,     eax
    !  and      eax,     [esi+20]
       
    !  not      edx
    !  and      edx,     [esi+24]
    !  xor      eax,     edx
       
    !  mov      ecx,     ebx
    !  mov      ebx,     eax
    !  mov      eax,     ecx
       
    !  mov      edx,     ecx
    !  ror      eax,     6
    !  ror      ecx,     11
    !  ror      edx,     25
       
    !  add      ebx,     ki
    !  xor      eax,     ecx
    !  add      ebx,     wi
    !  xor      eax,     edx
       
    !  add      eax,     ebx
    !  add      eax,     [esi+28]
    !  movd     xmm6,    eax            ;xmm6 = t0
       
    !  mov      eax,     [esi]
    !  mov      ecx,     [esi+4]
    !  mov      ebx,     eax
       
    !  mov      edx,     eax
    !  and      eax,     ecx
       
    !  and      edx,     [esi+8]
    !  xor      eax,     edx
       
    !  and      ecx,     [esi+8]
    !  xor      eax,     ecx
    !  mov      edx,     eax
       
    !  mov      eax,     ebx
    !  mov      ecx,     ebx
    !  ror      eax,     2
    !  ror      ecx,     13
    !  ror      ebx,     22
    !  xor      eax,     ecx
    !  xor      eax,     ebx
       
    !  add      eax,     edx
    !  movd     xmm7,    eax            ;xmm7 = t1
       
    '  @s[7] = @s[6] : @s[6] = @s[5] : @s[5] = @s[4] : @s[4] = @s[3] + t0&
    '  @s[3] = @s[2] : @s[2] = @s[1] : @s[1] = @s[0] : @s[0] = t0& + t1&
    #ALIGN 16
    !  movdqa   xmm0,    [esi]
    !  movdqa   xmm1,    [esi+16]
    !  movd     xmm3,    [esi+12]       ;xmm3 = @s[3]
    
    !  pslldq   xmm1,    4
    !  pslldq   xmm0,    4
    
    !  paddd    xmm1,    xmm3           ;xmm1[0] = @s{3]
    
    !  paddd    xmm0,    xmm6           ;+t0
    !  paddd    xmm1,    xmm6           ;+t0
    !  paddd    xmm0,    xmm7           ;+t1
    
    !  movdqa   [esi+16],xmm1
    !  movdqa   [esi],   xmm0
    
    !  mov      eax,     i
    !  inc      eax
    !  test     eax,     &b111111       ;<64?
    !  mov      i,       eax
    !  jnz      CompressTop
    
    '-- Add current state s() to context
    '  for i& = 0 to 7 : [email protected][i&] = [email protected][i&] + @s[i&] : next i&
    !  mov      edi,     pstate
    !  movdqa   xmm0,    [edi]
    !  movdqa   xmm1,    [edi+16]
    !  paddd    xmm0,    [esi]
    !  paddd    xmm1,    [esi+16]
    !  movdqa   [edi],   xmm0
    !  movdqa   [edi+16],xmm1
    
    !  pop   ebx
    !  pop   edi
    !  pop   esi
    END FUNCTION
    #ENDIF   '%PB_REVISION >= &H900
    
    
    '====================
    FUNCTION SHA256_Compress64(Ctx AS SHA256_CONTEXT) AS LONG
    #REGISTER NONE
    LOCAL k_array, s_array, w_array AS LONG
    LOCAL pstate, pdata, wi, ki, i AS LONG   
    
    '-- Copy for inline assembler
    w_array  = Ctx.w_array
    s_array  = Ctx.s_array
    k_array  = Ctx.k_array
    pstate   = Ctx.pstate
    pdata    = Ctx.pdata
    
    !  push     esi
    !  push     edi
    !  push     ebx
    
    '-- Copy current state into s&()
    !  mov      esi,     pstate           ;esi -> pCtx.state0
    !  mov      edi,     s_array
    !  movq     mm0,     [esi]
    !  movq     mm1,     [esi+8]
    !  movq     mm2,     [esi+16]
    !  movq     mm3,     [esi+24]
    !  movq     [edi],   mm0
    !  movq     [edi+8], mm1
    !  movq     [edi+16],mm2
    !  movq     [edi+24],mm3
    
    '-- Copy current data block to w&() w/little-to-big endian conversion
    !  mov      esi,     pdata
    !  mov      edi,     w_array
    !  mov      ecx,     %BLOCKSIZE
    
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    BSwapCopyTop:
    !  sub      ecx,     4
    !  mov      eax,     [esi+ecx]
    !  sub      ecx,     4
    !  bswap    eax
    !  mov      edx,     [esi+ecx]
    !  mov      [edi+ecx+4], eax
    !  bswap    edx
    !  test     ecx,     ecx
    !  mov      [edi+ecx], edx
    !  jnz      BSwapCopyTop
       
    '-- Fill W[16to63]
    ! mov       esi,     w_array
    ! push      ebp
    ! mov       ebp,     16
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    FillTop:
    !  mov      ebx,     ebp
    !  sub      ebx,     2
    !  mov      eax,     [esi+ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  sub      ebx,     13             ;prep for next access: (-2)+(-13) = -15
    !  ror      eax,     17
    !  ror      ecx,     19
    !  shr      edx,     10
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  mov      edi,     eax            ;edi = temp total
    !  mov      eax,     [esi+ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  ror      eax,     7
    !  ror      ecx,     18
    !  shr      edx,     3
    !  add      ebx,     8              ;= (-15)+8 = -7
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  add      edi,     eax
       
    !  mov      eax,     [esi+ebx*4]
    !  sub      ebx,     9              ;= (-7)+(-9) = -16
    !  add      edi,     eax
       
    !  mov      eax,     [esi+ebx*4]
    !  mov      ebx,     ebp
    !  add      eax,     edi
       
    !  inc      ebp
    !  mov      [esi+ebx*4], eax
    !  test     ebp,     &b111111       ;<64?
    !  jnz      FillTop
    !  pop      ebp
    
    '-- Compress: i& = 0 to 63
    !  xor      eax,     eax
    !  mov      esi,     s_array        ;here to CompressDone & END SUB: esi -> s[0]
    !  mov      i,       eax
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    CompressTop:
    !  mov      ebx,     eax
    !  mov      edx,     w_array
    !  mov      eax,     [edx+ebx*4]
    !  mov      wi,      eax
    !  mov      edx,     k_array
    !  mov      eax,     [edx+ebx*4]
    !  mov      ki,      eax
    
    !  mov      eax,     [esi+16]
    !  mov      ecx,     [esi+20]
    !  mov      ebx,     eax
    !  mov      edx,     eax
    !  and      eax,     [esi+20]
    
    !  not      edx
    !  and      edx,     [esi+24]
    !  xor      eax,     edx
    
    !  mov      ecx,     ebx
    !  mov      ebx,     eax
    !  mov      eax,     ecx
    
    !  mov      edx,     ecx
    !  ror      eax,     6
    !  ror      ecx,     11
    !  ror      edx,     25
    
    !  add      ebx,     ki
    !  xor      eax,     ecx
    !  add      ebx,     wi
    !  xor      eax,     edx
    
    !  add      eax,     ebx
    !  add      eax,     [esi+28]
    !  movd     mm6,     eax            ;mm6 = t0
    
    !  mov      eax,     [esi]
    !  mov      ecx,     [esi+4]
    !  mov      ebx,     eax
    
    !  mov      edx,     eax
    !  and      eax,     ecx
    
    !  and      edx,     [esi+8]
    !  xor      eax,     edx
    
    !  and      ecx,     [esi+8]
    !  xor      eax,     ecx
    !  mov      edx,     eax
    
    !  mov      eax,     ebx
    !  mov      ecx,     ebx
    !  ror      eax,     2
    !  ror      ecx,     13
    !  ror      ebx,     22
    !  xor      eax,     ecx
    !  xor      eax,     ebx
    
    !  add      eax,     edx
    !  movd     mm7,     eax            ;mm7 = t1
    
    '  @s[7] = @s[6] : @s[6] = @s[5] : @s[5] = @s[4] : @s[4] = @s[3] + t0&
    '  @s[3] = @s[2] : @s[2] = @s[1] : @s[1] = @s[0] : @s[0] = t0& + t1&
    #IF %PB_REVISION >= &H900
    #ALIGN 8
    #ENDIF
    !  movq     mm3,     [esi+20]       ;mm3 = @s[6-5]
    !  movq     mm2,     [esi+12]       ;mm2 = @s[4-3]
    !  movq     mm1,     [esi+4]        ;mm1 = @s[2-1]
    !  movq     mm0,     [esi]          ;mm0 = @s[1-0]
    
    !  psllq    mm0,     32             ;mm0 = @s[0- ]
    
    !  paddd    mm2,     mm6            ;+t0
    !  paddd    mm0,     mm6            ;+t0
    !  paddd    mm0,     mm7            ;+t1
    
    !  movq     [esi+24],mm3
    !  movq     [esi+16],mm2
    !  movq     [esi+8], mm1
    !  movq     [esi],   mm0
    
    !  mov      eax,     i
    !  inc      eax
    !  test     eax,     &b111111       ;<64?
    !  mov      i,       eax
    !  jnz      CompressTop  
    
    '-- Add current state s() to context
    '  for i& = 0 to 7 : [email protected][i&] = [email protected][i&] + @s[i&] : next i&
    !  mov      edi,     pstate
    !  movq     mm0,     [edi]
    !  movq     mm1,     [edi+8]
    !  movq     mm2,     [edi+16]
    !  movq     mm3,     [edi+24]
    
    !  paddd    mm0,     [esi]
    !  paddd    mm1,     [esi+8]
    !  paddd    mm2,     [esi+16]
    !  paddd    mm3,     [esi+24]
    
    !  movq     [edi],   mm0
    !  movq     [edi+8], mm1
    !  movq     [edi+16],mm2
    !  movq     [edi+24],mm3
    
    !  emms
    !  pop   ebx
    !  pop   edi
    !  pop   esi
    END FUNCTION
    
    
    '====================
    FUNCTION SHA256_Compress32(Ctx AS SHA256_CONTEXT) AS LONG
    #REGISTER NONE
    LOCAL k_array, s_array, w_array AS LONG
    LOCAL pstate, pdata AS LONG   
    LOCAL t0, t1, wi, ki, i AS LONG
    
    '-- Copy for inline assembler
    w_array  = Ctx.w_array
    s_array  = Ctx.s_array
    k_array  = Ctx.k_array
    pstate   = Ctx.pstate
    pdata    = Ctx.pdata
    
    !  push     esi
    !  push     edi
    !  push     ebx
    
    '-- Copy current state into s&()
    !  mov      esi,     pstate           ;esi -> pCtx.state0
    !  mov      edi,     s_array
    !  mov      ecx,     8
    !  cld
    !  rep      movsd
    
    '-- Copy current data block to w&() w/little-to-big endian conversion
    !  mov      esi,     pdata
    !  mov      edi,     w_array
    !  mov      ecx,     %BLOCKSIZE
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    BSwapCopyTop:
    !  sub      ecx,     4
    !  mov      eax,     [esi+ecx]
    !  sub      ecx,     4
    !  bswap    eax
    !  mov      edx,     [esi+ecx]
    !  mov      [edi+ecx+4],eax
    !  bswap    edx
    !  test     ecx,     ecx
    !  mov      [edi+ecx],  edx
    !  jnz      BSwapCopyTop
    
    '-- Fill W[16to63]
    ! mov       esi,     w_array
    ! push      ebp
    ! mov       ebp,     16
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    FillTop:
    !  mov      ebx,     ebp
    !  sub      ebx,     2
    !  mov      eax,     [esi]+[ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  sub      ebx,     13           ;prep for next access: (-2)+(-13) = -15
    !  ror      eax,     17
    !  ror      ecx,     19
    !  shr      edx,     10
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  mov      edi,     eax          ;edi = temp total
    !  mov      eax,     [esi]+[ebx*4]
    !  mov      ecx,     eax
    !  mov      edx,     ecx
    !  ror      eax,     7
    !  ror      ecx,     18
    !  shr      edx,     3
    !  add      ebx,     8            ;= (-15)+8 = -7
    !  xor      eax,     ecx
    !  xor      eax,     edx
    !  add      edi,     eax
    
    !  mov      eax,     [esi]+[ebx*4]
    !  sub      ebx,     9            ;= (-7)+(-9) = -16
    !  add      edi,     eax
    
    !  mov      eax,     [esi]+[ebx*4]
    !  mov      ebx,     ebp
    !  add      eax,     edi
    
    !  inc      ebp
    !  mov      [esi]+[ebx*4], eax
    !  cmp      ebp,     63
    !  jg       FillDone
    !  jmp      FillTop
    FillDone:
    !  pop   ebp
    
    '-- Compress: i& = 0 to 63
    !  xor      eax,     eax
    !  mov      esi,     s_array            ;here to CompressDone & END SUB: esi -> s[0]
    !  mov      i,       eax
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    CompressTop:
    !  mov      ebx,     eax
    !  mov      edx,     w_array
    !  mov      eax,     [edx]+[ebx*4]
    !  mov      wi,      eax
    !  mov      edx,     k_array&
    !  mov      eax,     [edx]+[ebx*4]
    !  mov      ki,      eax
    
    !  mov      eax,     [esi+16]
    !  mov      ecx,     [esi+20]
    !  mov      ebx,     eax
    !  mov      edx,     eax
    !  and      eax,     [esi+20]
    
    !  not      edx
    !  and      edx,     [esi+24]
    !  xor      eax,     edx
    
    !  mov      ecx,     ebx
    !  mov      ebx,     eax
    !  mov      eax,     ecx
    
    !  mov      edx,     ecx
    !  ror      eax,     6
    !  ror      ecx,     11
    !  ror      edx,     25
    
    !  add      ebx,     ki
    !  xor      eax,     ecx
    !  add      ebx,     wi
    !  xor      eax,     edx
    
    !  add      eax,     ebx
    !  add      eax,     [esi+28]
    
    !  mov      t0&,     eax
    
    !  mov      eax,     [esi]
    !  mov      ecx,     [esi+4]
    !  mov      ebx,     eax
    
    !  mov      edx,     eax
    !  and      eax,     ecx
    
    !  and      edx,     [esi+8]
    !  xor      eax,     edx
    
    !  and      ecx,     [esi+8]
    !  xor      eax,     ecx
    !  mov      edx,     eax
    
    !  mov      eax,     ebx
    !  mov      ecx,     ebx
    !  ror      eax,     2
    !  ror      ecx,     13
    !  ror      ebx,     22
    !  xor      eax,     ecx
    !  xor      eax,     ebx
    
    !  add      eax,     edx
    !  mov      t1,      eax
    
    '  @s[7] = @s[6] : @s[6] = @s[5] : @s[5] = @s[4] : @s[4] = @s[3] + t0&
    '  @s[3] = @s[2] : @s[2] = @s[1] : @s[1] = @s[0] : @s[0] = t0& + t1&
    !  mov      edi,     esi
    !  mov      ecx,     t0
    
    !  mov      eax,     [esi+24]     ;@s[7] = @s[6]
    !  mov      ebx,     [esi+20]     ;@s[6] = @s[5]
    !  mov      edx,     [esi+16]     ;@s[5] = @s[4]
    !  mov      [edi+28], eax
    !  mov      [edi+24], ebx
    !  mov      [edi+20], edx
    
    !  mov      eax,     [esi+12]     ;@s[4] = @s[3] + T0&
    !  mov      ebx,     [esi+8]      ;@s[3] = @s[2]
    !  add      eax,     ecx
    !  mov      edx,     [esi]        ;@s[1] = @s[0]
    !  mov      [edi+12],ebx
    !  mov      [edi+16],eax
    !  mov      ebx, ecx          ;@s[0] = T0& + T1&
    !  mov      eax, [esi+4]      ;@s[2] = @s[1]
    !  mov      [edi+4], edx
    !  add      ebx, t1
    !  mov      [edi+8], eax
    !  mov      [edi],   ebx
    
    !  mov      eax,     i
    !  inc      eax
    !  test     eax,     &b111111       ;<64?
    !  mov      i,       eax
    !  jnz      CompressTop  
    
    '-- Add current state s() to context
    '  for i& = 0 to 7 : [email protected][i&] = [email protected][i&] + @s[i&] : next i&
    !  mov      edi, pstate
    !  mov      ecx, %HASHLEN
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    AddCopyTop:
    !  sub      ecx,     4
    !  mov      eax,     [edi+ecx]
    !  add      eax,     [esi+ecx]
    !  mov      [edi+ecx], eax
    !  test     ecx,     ecx
    !  jnz      AddCopyTop
    
    !  pop      ebx
    !  pop      edi
    !  pop      esi
    END FUNCTION
    
    
    '====================
    FUNCTION SHA256_Buffer(BYVAL DataBuffer AS BYTE PTR, BYVAL Length AS DWORD, BYVAL Hash AS DWORD PTR) EXPORT AS LONG
    '-- Expects parameter Hash to point to buffer of correct size of 32 bytes (256bits \ 8)
    REGISTER i AS LONG
    LOCAL lastbuff$, ctx AS SHA256_CONTEXT
    LOCAL pState, pFunction AS LONG
    
    i = Length AND (%BLOCKSIZE-1)
    lastbuff$ = peek$((DataBuffer + Length) - i, i)
    lastbuff$ = lastbuff$ + SHA256_MakePadding$(Length)
    
    SHA256_Init byval varptr(ctx)
    
    #IF %PB_REVISION >= &H900
    if Ctx.HasSSE2 then
       pfunction = codeptr(SHA256_Compress128)
    elseif Ctx.HasMMX then
       pfunction = codeptr(SHA256_Compress64)
    else
       pfunction = codeptr(SHA256_Compress32)
    end if
    #ELSE
    if Ctx.HasMMX then
       pfunction = codeptr(SHA256_Compress64)
    else
       pfunction = codeptr(SHA256_Compress32)
    end if
    #ENDIF
    
    ctx.datalength = Length
    ctx.pdata = DataBuffer
    
    i = Length AND (NOT %BLOCKSIZE-1)
    do while i
       call dword pfunction STDCALL (BYREF ctx)
       ctx.pdata = ctx.pdata + %BLOCKSIZE
       i = i - %BLOCKSIZE
    loop
    
    ctx.datalength = len(lastbuff$)
    ctx.pdata = strptr(lastbuff$)
    
    do while ctx.datalength
       call dword pfunction STDCALL (BYREF ctx)
       ctx.pdata = ctx.pdata + %BLOCKSIZE
       ctx.datalength = ctx.datalength - %BLOCKSIZE
    loop
    
    '-- Copy current state (as dwords) from s&() to Hash
    '   for i& = 0 to 7 : @Hash[i&] = [email protected][i&] : next i&
    pstate = ctx.pstate
    
    #IF %RETURN_LITTLE_ENDIAN
    !  push  edi
    !  mov   edx,  pstate           ;esi -> ctx.state0
    !  mov   edi,  Hash
    !  mov   ecx,  (%HASHLEN\4)
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    LoopTop:
    !  mov   eax,  [edx+ecx*4]
    !  bswap eax
    !  mov   [edi+ecx*4],eax
    !  dec   ecx
    !  jns   LoopTop
    !  pop   edi
    #ELSE
    !  push  esi
    !  push  edi
    !  mov   esi,  pstate           ;esi -> ctx.state0
    !  mov   edi,  Hash
    !  mov   ecx,  8
    !  cld
    !  rep   movsd
    !  pop   edi
    !  pop   esi
    #ENDIF
    END FUNCTION
    
    
    '====================
    FUNCTION SHA256_File(File_Name$, Hash$) EXPORT AS LONG
    '-- Returns 0 on success, or PB (not OS) error code
    REGISTER i AS LONG, bytesleft AS DWORD
    LOCAL buffer$, padding$
    LOCAL ctx AS SHA256_CONTEXT
    LOCAL infile, ecode, pfunction, phash, pstate, lastpass, maxstring AS LONG
    
    '-- If file not found, return PB error code
    if len(dir$(File_Name$)) = 0 then
       function = 53 : exit function
    end if
    
    #IF %PB_REVISION >= &H900
    if Ctx.HasSSE2 then
       pfunction = codeptr(SHA256_Compress128)
    elseif Ctx.HasMMX then
       pfunction = codeptr(SHA256_Compress64)
    else
       pfunction = codeptr(SHA256_Compress32)
    end if
    #ELSE
    if Ctx.HasMMX then
       pfunction = codeptr(SHA256_Compress64)
    else
       pfunction = codeptr(SHA256_Compress32)
    end if
    #ENDIF
    
    buffer$ = nul$(%FILE_BUFFERSIZE)
    maxstring = %FILE_BUFFERSIZE
    
    ctx.datalength = %BLOCKSIZE
    SHA256_Init ctx
    
    infile = freefile
    open File_Name$ for binary lock shared as infile base=0
    if err then goto SHA256_File_Error
    bytesleft = lof(infile)
    padding$ = SHA256_MakePadding$(bytesleft)
    
    do
       'Resize if necessary & flag final buffer
       if bytesleft =< maxstring then
          maxstring = bytesleft
          buffer$ = nul$(maxstring)
          incr lastpass
       end if
       get infile,, buffer$ : if err then goto SHA256_File_Error
       if lastpass then buffer$ = buffer$ + padding$
       ctx.pdata = strptr(buffer$)
       for i = 1 to (len(buffer$) \ %BLOCKSIZE)
          call dword pfunction STDCALL (BYREF ctx)
          ctx.pdata = ctx.pdata + %BLOCKSIZE
       next i
       bytesleft = bytesleft - maxstring
    loop until lastpass
    close infile : if err then goto SHA256_File_Error
    
    '-- Copy current state (as dwords) from s&() to Hash$
    'for i& = 0 to 7 : @Hash[i&] = [email protected][i&] : next i&
    Hash$ = nul$(%HASHLEN)
    phash = strptr(Hash$)
    pstate = ctx.pstate
    #IF %RETURN_LITTLE_ENDIAN
    !  push  edi
    !  mov   edx,  pstate           ;esi -> ctx.state0
    !  mov   edi,  phash
    !  mov   ecx,  (%HASHLEN\4)
    #IF %PB_REVISION >= &H900
    #ALIGN 4
    #ENDIF
    LoopTop:
    !  mov   eax,  [edx+ecx*4]
    !  bswap eax
    !  mov   [edi+ecx*4],eax
    !  dec   ecx
    !  jns   LoopTop
    !  pop   edi
    #ELSE
    !  push  esi
    !  push  edi
    !  mov   esi,  pstate           ;esi -> ctx.state0
    !  mov   edi,  Hash
    !  mov   ecx,  8
    !  cld
    !  rep   movsd
    !  pop   edi
    !  pop   esi
    #ENDIF
    
    Exit_SHA256_File:
    function = ecode
    EXIT FUNCTION
    
    '============
    SHA256_File_Error:
    if err then 
       ecode = err
    else
       ecode = -1
    end if
    resume Exit_SHA256_File
    END FUNCTION
    
    
    '=========================
    FUNCTION SHA256_MakePadding(BYVAL TotalBytes AS DWORD) AS STRING
    '-- Creates the necessary string to append to buffer being hashed
    REGISTER i AS LONG, padBytes AS LONG
    LOCAL buffbits AS QUAD, padding$
    LOCAL pbyte1, pbyte2 AS BYTE PTR
    
    buffbits = TotalBytes * 8
    padding$ = nul$(8)
    pbyte1 = strptr(padding$) : pbyte2 = varptr(buffbits)
    
    '-- Copy bytes in reverse
    for i = 0 to 7
       @pbyte1[i&] = @pbyte2[7 - i&]
    next i&
    
    padBytes = %BLOCKSIZE - ((TotalBytes+9) AND (%BLOCKSIZE-1))
    function = chr$(&h80) + nul$(padBytes) + padding
    END FUNCTION
    
    
    #IF %PB_REVISION >= &H900
    '===================
    FUNCTION HasSSE2() AS LONG
    !  mov   eax, 1            ;function 1
    !  cpuid
    !  xor   eax, eax
    !  test  edx, &h04000000   ;bit 26
    !  setnz al                ;rem to force downgrade to MMX
    !  mov   function, eax
    END FUNCTION
    #ENDIF
    
    
    '===================
    FUNCTION HasMMX() AS LONG
    !  mov      eax,  1
    !  cpuid
    !  xor      eax,  eax
    !  test     edx,  &h800000 ;bit 23
    !  setnz    al             ;rem here and in HasSE2() to force downgrade to 32-bit
    !  mov      function, eax
    END FUNCTION
    
    '-- END SHA256c.INC ---------------------------------------------------

    Leave a comment:


  • Greg Turgeon
    started a topic SHA256 Secure Hash for PBCC 4/5+ and PBWin 8/9+

    SHA256 Secure Hash for PBCC 4/5+ and PBWin 8/9+

    Secure 256-bit hashing (ver. 4) for PowerBASIC

    Code for the following two files appears below:
    • SHA256c.INC
      Hash routines for returning 32-byte SHA256 hashes of buffers and files
    • SHA256c.BAS
      Test bed EXE illustrating buffer and file hashing.


    All code compiles with either PBDLL 8.0/9.0+ or PBCC 4.0/5.0+. Conditional compiling makes use of features of the newer compilers if available. This code should be treated as a replacement of my 2001 posting of SHA256 code.


    MAJOR CHANGES

    Many of the following revisions are contained in code updates which I distributed privately.

    SHA256c.INC
    • Added conditional compile %RETURN_LITTLE_ENDIAN setting for return of hash in little-endian format, with %RETURN_LITTLE_ENDIAN = %TRUE as default.
    • Added MMX and SSE2 code support (with the original 32-bit code remaining intact). Run-time checking of CPU capabilities causes branching to the most advanced instruction set available.
    • Aligned arrays and loops.
    • Renamed hash context UDT. (SHA256_CONTEXT replaces original tSHA_STATE).
    • Simplified parameter passing of two routines, with parameter Length& of FUNCTION SHA256_Buffer() changed to dword.
    • Added %HASHLEN equate for consistency with other hash code.

    SHA256c.BAS
    • Replaced ShowHash&() function with revision which treats returned hash as series of bytes rather than dwords.
    • Get_FileSize() utility function returns quad instead of dword.


    from the original 2001 code:
    ----------------------------------------------------------------------
    A hash is considered secure when it possesses the following qualities.
    • Determining the input string from the hash (i.e., working backward from the hash alone to determine the string which generated it) is not considered feasible.
    • Given an input string, it is not considered feasible to find another string which hashes to the same value.
    • It is not considered feasible to find two random strings which hash to the same value.


    An input string can be of any length and thus far longer than its resulting hash. This is accomplished through use of a compression function which treats the input as a combination of any previously hashed input and the current input. Designing this feature is one of the most important challenges when creating a secure hash algorithm.

    Secure hashes have many uses, among them validation of passphrases. In this arrangement, a user enters a passphrase when setting up an account. The input string is hashed, and the hash is stored (not the passphrase). When the user seeks readmission, the passphrase entered is hashed, and the hash is compared with the one on record. If the hashes match, the strings which generated them also must match. If the collection of stored hashes is compromised, the passphrases remain unknown.

    Secure hashes are not designed for speed. The implementation below relies on assembly language to improve speed in its most heavily traveled section of code, but unless security is required, a secure hash is a poor choice when compared with the many simpler, far more efficient hash algorithms in widespread use.
    ----------------------------------------------------------------------

    Available at the following URL is NIST information about the 256-bit, 384-bit, and 512-bit extensions to the SHA standard: http://csrc.nist.gov/groups/ST/toolk...e_hashing.html


    This PB implementation of SHA256 is hereby placed in the public domain. Use it as you wish.

    Greg Turgeon
    gturgeon at ssge dot net
    2/2009
    Attached Files
    Last edited by Greg Turgeon; 11 Feb 2009, 09:36 PM.
Working...
X