| 
				
					|  | Das deutsche QBasic- und FreeBASIC-Forum Für euch erreichbar unter qb-forum.de, fb-forum.de und freebasic-forum.de!
 
 |  
 
	
		| Vorheriges Thema anzeigen :: Nächstes Thema anzeigen |  
		| Autor | Nachricht |  
		| 28398 
 
 
 Anmeldungsdatum: 25.04.2008
 Beiträge: 1917
 
 
 | 
			
				|  Verfasst am: 26.10.2008, 15:28    Titel: SHA512 |   |  
				| 
 |  
				|  	  | Code: |  	  | '       sha512.bas '
 '       Copyright 2008 28398 Laboratories <admin@28398.org>
 '
 '       This program is free software; you can redistribute it and/or modify
 '       it under the terms of the GNU General Public License as published by
 '       the Free Software Foundation; either version 2 of the License, or
 '       (at your option) any later version.
 '
 '       This program is distributed in the hope that it will be useful,
 '       but WITHOUT ANY WARRANTY; without even the implied warranty of
 '       MERChFunANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 '       GNU General Public License for more details.
 '
 '       You should have received a copy of the GNU General Public License
 '       along with this program; if not, write to the Free Software
 '       Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
 '       MA 02110-1301, USA.
 
 
 
 #include once "crt.bi"
 
 
 #ifndef u8
 type u8 as ubyte
 type u32 as uinteger
 type u64 as ulongint
 #endif
 
 #ifndef sha512_ctx
 type sha512_ctx
 as u64 state(0 to 8)
 as u32 count(0 to 4)
 as u8 buf(0 to 128)
 as u64 W(0 to 80)
 end type
 #endif
 
 #ifndef sha512_init
 declare function sha512_init() as sha512_ctx ptr
 declare sub sha512_update(ctx as sha512_ctx ptr, dat as u8 ptr, length as uinteger)
 declare sub sha512_transform (state as u64 ptr, W as u64 ptr, inpt as u8 ptr)
 declare sub sha512_final(ctx as sha512_ctx ptr, byref hash as u8 ptr)
 #endif
 
 #define SHA512_H0   &h6a09e667f3bcc908ULL
 #define SHA512_H1   &hbb67ae8584caa73bULL
 #define SHA512_H2   &h3c6ef372fe94f82bULL
 #define SHA512_H3   &ha54ff53a5f1d36f1ULL
 #define SHA512_H4   &h510e527fade682d1ULL
 #define SHA512_H5   &h9b05688c2b3e6c1fULL
 #define SHA512_H6   &h1f83d9abfb41bd6bULL
 #define SHA512_H7   &h5be0cd19137e2179ULL
 
 ' changed from functions to macros by csde_rats
 ' notice (csde_rats): I have no idea why the heck they have functions like
 ' "LOAD_OP", which exactly do a memcpy. I have although no idea, why they using
 ' "BLEND_OP" as an procedure, and not as an macro, which is more optimized by the
 ' majority of the compilers.
 #ifdef _SHA512_OLD
 function ChFun(x as u64, y as u64, z as u64) as u64
 return z xor (x and (y xor z))
 end function
 function Maj(x as u64, y as u64, z as u64) as u64
 return (x and y) or (z and (x or y))
 end function
 function RORu64 (x as u64, y as u64) as u64
 return (x shl y) or (x shr (64-y))
 end function
 sub LOAD_OP(i as integer, W as u64 ptr, inpt as u8 ptr)
 W[i] = inpt[i]
 end sub
 sub BLEND_OP (i as integer, W as u64 ptr)
 W[i] = s1(W[i - 2]) + W[i - 7] + s0(W[i - 15]) + W[i - 16]
 end sub
 #else
 #define ChFun(x, y, z) ((z) xor ((x) and ((y) xor (z))))
 #define Maj(x, y, z) (((x) and (y)) or ((z) and ((x) or (y))))
 #define RORu64(x, y) (((x) shl (y)) or ((x) shr (64 - (y))))
 
 #define LOAD_OP(i, W, inpt) W[i] = inpt[i]
 #define BLEND_OP(i, W) W[i] = s1(W[i - 2]) + W[i - 7] + s0(W[i - 15]) + W[i - 16]
 #endif
 
 #define e0(x)   (RORu64(x, 28) xor RORu64(x, 34) xor RORu64(x, 39))
 #define e1(x)   (RORu64(x, 14) xor RORu64(x, 18) xor RORu64(x, 41))
 #define s0(x)   (RORu64(x,  1) xor RORu64(x,  8) xor (x shr 7))
 #define s1(x)   (RORu64(x, 19) xor RORu64(x, 61) xor (x shr 6))
 
 dim shared as u64 sha512_K(0 to 80) => _
 { _
 &h428a2f98d728ae22ULL, &h7137449123ef65cdULL, &hb5c0fbcfec4d3b2fULL, _
 &he9b5dba58189dbbcULL, &h3956c25bf348b538ULL, &h59f111f1b605d019ULL, _
 &h923f82a4af194f9bULL, &hab1c5ed5da6d8118ULL, &hd807aa98a3030242ULL, _
 &h12835b0145706fbeULL, &h243185be4ee4b28cULL, &h550c7dc3d5ffb4e2ULL, _
 &h72be5d74f27b896fULL, &h80deb1fe3b1696b1ULL, &h9bdc06a725c71235ULL, _
 &hc19bf174cf692694ULL, &he49b69c19ef14ad2ULL, &hefbe4786384f25e3ULL, _
 &h0fc19dc68b8cd5b5ULL, &h240ca1cc77ac9c65ULL, &h2de92c6f592b0275ULL, _
 &h4a7484aa6ea6e483ULL, &h5cb0a9dcbd41fbd4ULL, &h76f988da831153b5ULL, _
 &h983e5152ee66dfabULL, &ha831c66d2db43210ULL, &hb00327c898fb213fULL, _
 &hbf597fc7beef0ee4ULL, &hc6e00bf33da88fc2ULL, &hd5a79147930aa725ULL, _
 &h06ca6351e003826fULL, &h142929670a0e6e70ULL, &h27b70a8546d22ffcULL, _
 &h2e1b21385c26c926ULL, &h4d2c6dfc5ac42aedULL, &h53380d139d95b3dfULL, _
 &h650a73548baf63deULL, &h766a0abb3c77b2a8ULL, &h81c2c92e47edaee6ULL, _
 &h92722c851482353bULL, &ha2bfe8a14cf10364ULL, &ha81a664bbc423001ULL, _
 &hc24b8b70d0f89791ULL, &hc76c51a30654be30ULL, &hd192e819d6ef5218ULL, _
 &hd69906245565a910ULL, &hf40e35855771202aULL, &h106aa07032bbd1b8ULL, _
 &h19a4c116b8d2d0c8ULL, &h1e376c085141ab53ULL, &h2748774cdf8eeb99ULL, _
 &h34b0bcb5e19b48a8ULL, &h391c0cb3c5c95a63ULL, &h4ed8aa4ae3418acbULL, _
 &h5b9cca4f7763e373ULL, &h682e6ff3d6b2b8a3ULL, &h748f82ee5defb2fcULL, _
 &h78a5636f43172f60ULL, &h84c87814a1f0ab72ULL, &h8cc702081a6439ecULL, _
 &h90befffa23631e28ULL, &ha4506cebde82bde9ULL, &hbef9a3f7b2c67915ULL, _
 &hc67178f2e372532bULL, &hca273eceea26619cULL, &hd186b8c721c0c207ULL, _
 &heada7dd6cde0eb1eULL, &hf57d4f7fee6ed178ULL, &h06f067aa72176fbaULL, _
 &h0a637dc5a2c898a6ULL, &h113f9804bef90daeULL, &h1b710b35131c471bULL, _
 &h28db77f523047d84ULL, &h32caab7b40c72493ULL, &h3c9ebe0a15c9bebcULL, _
 &h431d67c49c100d4cULL, &h4cc5d4becb3e42b6ULL, &h597f299cfc657e2aULL, _
 &h5fcb6fab3ad6faecULL, &h6c44198c4a475817ULL _
 }
 
 sub sha512_transform (state as u64 ptr, W as u64 ptr, inpt as u8 ptr)
 dim as u64 a, b, c, d, e, f, g, h, t1, t2
 dim as integer i
 
 #ifdef _SHA512_OLD
 for i = 0 to 16
 LOAD_OP(i, W, inpt)
 next i
 #else
 memcpy(W, inpt, 16)
 #endif
 
 for i = 16 to 80
 BLEND_OP(i, W)
 next i
 
 a = state[0]
 b = state[1]
 c = state[2]
 d = state[3]
 e = state[4]
 f = state[5]
 g = state[6]
 h = state[7]
 
 for i = 0 to 72 step 8
 t1 = h + e1(e) + ChFun(e,f,g) + sha512_K(i  ) + W[i  ]
 t2 = e0(a) + Maj(a,b,c):    d+=t1:    h=t1+t2
 t1 = g + e1(d) + ChFun(d,e,f) + sha512_K(i+1) + W[i+1]
 t2 = e0(h) + Maj(h,a,b):    c+=t1:    g=t1+t2
 t1 = f + e1(c) + ChFun(c,d,e) + sha512_K(i+2) + W[i+2]
 t2 = e0(g) + Maj(g,h,a):    b+=t1:    f=t1+t2
 t1 = e + e1(b) + ChFun(b,c,d) + sha512_K(i+3) + W[i+3]
 t2 = e0(f) + Maj(f,g,h):    a+=t1:    e=t1+t2
 t1 = d + e1(a) + ChFun(a,b,c) + sha512_K(i+4) + W[i+4]
 t2 = e0(e) + Maj(e,f,g):    h+=t1:    d=t1+t2
 t1 = c + e1(h) + ChFun(h,a,b) + sha512_K(i+5) + W[i+5]
 t2 = e0(d) + Maj(d,e,f):    g+=t1:    c=t1+t2
 t1 = b + e1(g) + ChFun(g,h,a) + sha512_K(i+6) + W[i+6]
 t2 = e0(c) + Maj(c,d,e):    f+=t1:    b=t1+t2
 t1 = a + e1(f) + ChFun(f,g,h) + sha512_K(i+7) + W[i+7]
 t2 = e0(b) + Maj(b,c,d):    e+=t1:    a=t1+t2
 next i
 
 state[0] += a
 state[1] += b
 state[2] += c
 state[3] += d
 state[4] += e
 state[5] += f
 state[6] += g
 state[7] += h
 
 a  = 0
 b  = 0
 c  = 0
 d  = 0
 e  = 0
 f  = 0
 g  = 0
 h  = 0
 t1 = 0
 t2 = 0
 end sub
 
 function sha512_init() as sha512_ctx ptr
 dim as sha512_ctx ptr ctx
 ctx = new sha512_ctx
 
 ctx->state(0) = SHA512_H0
 ctx->state(1) = SHA512_H1
 ctx->state(2) = SHA512_H2
 ctx->state(3) = SHA512_H3
 ctx->state(4) = SHA512_H4
 ctx->state(5) = SHA512_H5
 ctx->state(6) = SHA512_H6
 ctx->state(7) = SHA512_H7
 
 return ctx
 end function
 
 sub sha512_update(ctx as sha512_ctx ptr, dat as u8 ptr, length as uinteger)
 dim as uinteger i, index, part_len
 
 index = cast(uinteger, ((ctx->count(0) shr 3) and &h7F))
 
 ctx->count(0) += length shl 3
 if ctx->count(0) < (length shl 3) then
 ctx->count(1) += 1
 if ctx->count(1) < 1 then
 ctx->count(2) += 1
 if ctx->count(2) < 1 then
 ctx->count(3) += 1
 endif
 endif
 ctx->count(1) += (length shr 29)
 endif
 
 part_len = 128 - index
 
 if length >= part_len then
 memcpy(@ctx->buf(index), dat, part_len)
 sha512_transform(@ctx->state(0), @ctx->W(0), @ctx->buf(0))
 
 i = part_len
 while (i + 127) < length
 sha512_transform(@ctx->state(0), @ctx->W(0), @dat[i])
 i += 128
 wend
 
 index = 0
 else
 i = 0
 endif
 
 memcpy(@ctx->buf(index), @dat[i], length - i)
 
 ' this is not in the reference implementation, but I added it, because
 ' otherwise blocks with a size smaller than 128 bytes aren't processed, so
 ' sha512_final generates always the same hash for blocks smaller 128 bytes
 sha512_transform(@ctx->state(0), @ctx->W(0), @ctx->buf(0))
 
 memset(@ctx->W(0), 0, sizeof(ctx->W))
 end sub
 
 sub sha512_final(ctx as sha512_ctx ptr, byref hash as u8 ptr)
 dim as u8 padding(0 to 128) => {&h80}
 dim as uinteger index, pad_len
 dim as integer i
 dim as u32 bits(0 to 3)
 
 bits(3) = ctx->count(0)
 bits(2) = ctx->count(1)
 bits(1) = ctx->count(2)
 bits(0) = ctx->count(3)
 
 index = (ctx->count(0) shl 3) and &h7F
 pad_len = iif(index < 112, 112 - index, (128 + 112) - index)
 sha512_update(ctx, @padding(0), pad_len)
 
 sha512_update(ctx, cast(u8 ptr, @bits(0)), sizeof(bits))
 
 hash = callocate(64)
 memcpy(hash, @ctx->state(0), 64)
 end sub
 
 | 
 
 
  	  | Code: |  	  | '       sha512test.bas '
 '       Copyright 2008 28398 Laboratories <admin@28398.org>
 '
 '       This program is free software; you can redistribute it and/or modify
 '       it under the terms of the GNU General Public License as published by
 '       the Free Software Foundation; either version 2 of the License, or
 '       (at your option) any later version.
 '
 '       This program is distributed in the hope that it will be useful,
 '       but WITHOUT ANY WARRANTY; without even the implied warranty of
 '       MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 '       GNU General Public License for more details.
 '
 '       You should have received a copy of the GNU General Public License
 '       along with this program; if not, write to the Free Software
 '       Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
 '       MA 02110-1301, USA.
 
 Type u8 As UByte
 Type u32 As UInteger
 Type u64 As ULongInt
 
 Type sha512_ctx
 As u64 state(0 To 8)
 As u32 count(0 To 4)
 As u8 buf(0 To 128)
 As u64 W(0 To 80)
 End Type
 
 #Include "SHA512.bas"
 
 ' works up to ~16384 bytes
 Function sha512(dat As String) As String
 Dim As sha512_ctx Ptr ctx
 Dim As UByte Ptr dgst
 Dim As String hash
 
 ctx = sha512_init
 sha512_update(ctx, StrPtr(dat), Len(dat))
 sha512_final(ctx, dgst)
 
 For i As Integer = 0 To 64
 hash += Hex(dgst[i], 2)
 Next
 
 Return hash
 End Function
 
 dim as string ls
 while not(inkey = chr(27))
 line input, ls
 print sha512(ls)
 ls = ""
 wend
 
 
 | 
 
 Portiert aus den Kernelsourcen 2.6.27.1
 |  |  
		| Nach oben |  |  
		|  |  
		| frebas 
 
 
 Anmeldungsdatum: 20.06.2008
 Beiträge: 245
 
 
 | 
			
				|  Verfasst am: 26.10.2008, 19:40    Titel: |   |  
				| 
 |  
				| Was macht das Programm denn? Stell es mal vor. |  |  
		| Nach oben |  |  
		|  |  
		| 28398 
 
 
 Anmeldungsdatum: 25.04.2008
 Beiträge: 1917
 
 
 |  |  
		| Nach oben |  |  
		|  |  
		| volta 
 
 
 Anmeldungsdatum: 04.05.2005
 Beiträge: 1876
 Wohnort: D59192
 
 | 
			
				|  Verfasst am: 28.10.2008, 16:46    Titel: |   |  
				| 
 |  
				| Hi, ich befürchte du warst bei der Portierung sehr nachlässig
   
 In dem von dir angegebenen Wiki-Link kannst du erkennen was es mit "LOAD_OP" auf sich hat.
 
  	  | Zitat: |  	  | // Verarbeite die Nachricht in aufeinander folgenden 512-Bit Blöcken: für alle 512-Bit Block von message
 unterteile Block in 16 32-bit big-endian Worte w(i), 0 ≤ i ≤ 15
 
 // erweitere die 16 32-bit Worte auf 80 32-bit Worte:
 für alle i von 16 bis 79
 w(i) := (w(i-3) xor w(i-8 ) xor w(i-14) xor w(i-16)) leftrotate 1
 | 
 Auch "dim shared as u64 sha512_K(0 to 80)" , also 81 Elemente, doch dann folgen nur 80 Werte?
 
 In dem Artikel steht der Hash für :
 
  	  | Zitat: |  	  | SHA512("Franz jagt im komplett verwahrlosten Taxi quer durch Bayern") = af9ed2de700433b803240a552b41b5a472a6ef3fe1431a722b2063c75e9f0745
 1f67a28e37d09cde769424c96aea6f8971389db9e1993d6c565c3c71b855723c
 | 
 Eine einfache Probe zeigt dir ob dein Prog funktioniert.
  _________________
 Warnung an Choleriker:
 Dieser Beitrag kann Spuren von Ironie & Sarkasmus enthalten.
 Zu Risiken & Nebenwirkungen fragen Sie Ihren Therapeuten oder Psychiater.
 |  |  
		| Nach oben |  |  
		|  |  
		| 28398 
 
 
 Anmeldungsdatum: 25.04.2008
 Beiträge: 1917
 
 
 | 
			
				|  Verfasst am: 28.10.2008, 17:20    Titel: |   |  
				| 
 |  
				| Ach ich hab doch irgendwie geahnt, dass es mit "__be32_to_cpu__" was auf sich hatte^^ 
 Naja sry, ich habe das ohne Internet aus den Kernelsourcen portiert.
 
 Weiterhin habe ich eine Zeile bei sha512_update hinzugefügt, damit dass ganze auch mit Datenblöcken kleiner als 128 Byte funktioniert...
 
 Ganz btw. steht in der C-Implementation "... sha512_K[80]...", sprich von 0 bis 80... das sind auch 81 Werte...
 |  |  
		| Nach oben |  |  
		|  |  
		| Jojo alter Rang
 
  
 Anmeldungsdatum: 12.02.2005
 Beiträge: 9736
 Wohnort: Neben der Festplatte
 
 | 
			
				|  Verfasst am: 28.10.2008, 18:27    Titel: |   |  
				| 
 |  
				|  	  | Zitat: |  	  | Naja sry, ich habe das ohne Internet aus den Kernelsourcen portiert. | 
 das veröffentlichen eines solchen codes sollte aber niemals ungetestet (sprich: beispiele vergleichen!) geschehen!
 _________________
 » Die Mathematik wurde geschaffen, um Probleme zu lösen, die es nicht gäbe, wenn die Mathematik nicht erschaffen worden wäre.
 
  |  |  
		| Nach oben |  |  
		|  |  
		| Sebastian Administrator
 
  
 Anmeldungsdatum: 10.09.2004
 Beiträge: 5969
 Wohnort: Deutschland
 
 |  |  
		| Nach oben |  |  
		|  |  
		| volta 
 
 
 Anmeldungsdatum: 04.05.2005
 Beiträge: 1876
 Wohnort: D59192
 
 | 
			
				|  Verfasst am: 28.10.2008, 20:52    Titel: |   |  
				| 
 |  
				| schau mal hier: http://www.freebasic.net/forum/viewtopic.php?p=41268#41268
 das ist zwar SHA256 aber die Routinen können dir weiterhelfen.
 
 Da gibt es auch noch
 
 BSWAP nimmt eine Konvertierung zwischen Little Endian und Big Endian vor, indem Byte 0 und Byte 3 sowie Byte 1 und Byte 2 gegeneinander ausgetauscht werden.
 
 EDIT/
 hier ein lauffähiges Prog zum Link oben: SHA256.bas
 http://www.freebasic-portal.de/index.php?s=fbporticula&mode=show&id=749
 _________________
 Warnung an Choleriker:
 Dieser Beitrag kann Spuren von Ironie & Sarkasmus enthalten.
 Zu Risiken & Nebenwirkungen fragen Sie Ihren Therapeuten oder Psychiater.
 |  |  
		| Nach oben |  |  
		|  |  
		|  |  
  
	| 
 
 | Du kannst keine Beiträge in dieses Forum schreiben. Du kannst auf Beiträge in diesem Forum nicht antworten.
 Du kannst deine Beiträge in diesem Forum nicht bearbeiten.
 Du kannst deine Beiträge in diesem Forum nicht löschen.
 Du kannst an Umfragen in diesem Forum nicht mitmachen.
 
 |  |