1 /*******************************************************************************
2 
3         copyright:      Copyright (c) 2006 Tango. All rights reserved
4 
5         license:        BSD style: see doc/license.txt for details
6 
7         version:        Initial release: Feb 2006
8 
9         author:         Regan Heath, Oskar Linde
10 
11         This module implements the SHA-512 Algorithm described by Secure
12         Hash Standard, FIPS PUB 180-2
13 
14 *******************************************************************************/
15 
16 module tango.util.digest.Sha512;
17 
18 private import tango.core.ByteSwap;
19 
20 private import tango.util.digest.MerkleDamgard;
21 
22 public  import tango.util.digest.Digest;
23 
24 /*******************************************************************************
25 
26 *******************************************************************************/
27 
28 final class Sha512 : MerkleDamgard
29 {
30         private ulong[8]        context;
31         private enum uint      padChar = 0x80;
32 
33         /***********************************************************************
34 
35                 Construct a Sha512 hash algorithm context
36 
37         ***********************************************************************/
38 
39         this() { }
40 
41         /***********************************************************************
42 
43         ***********************************************************************/
44 
45         protected override void createDigest(ubyte[] buf)
46         {
47                 version (LittleEndian)
48                          ByteSwap.swap64(context.ptr, context.length * ulong.sizeof);
49 
50                 buf[] = (cast(ubyte[]) context)[];
51         }
52 
53         /***********************************************************************
54 
55                 The digest size of Sha-512 is 64 bytes
56 
57         ***********************************************************************/
58 
59         override uint digestSize() {return 64;}
60 
61         /***********************************************************************
62 
63                 Initialize the cipher
64 
65                 Remarks:
66                 Returns the cipher state to it's initial value
67 
68         ***********************************************************************/
69 
70         protected override void reset()
71         {
72                 super.reset();
73                 context[] = initial[];
74         }
75 
76         /***********************************************************************
77 
78                 Cipher block size
79 
80                 Returns:
81                 the block size
82 
83                 Remarks:
84                 Specifies the size (in bytes) of the block of data to pass to
85                 each call to transform(). For SHA512 the blockSize is 128.
86 
87         ***********************************************************************/
88 
89         protected override uint blockSize() { return 128; }
90 
91         /***********************************************************************
92 
93                 Length padding size
94 
95                 Returns:
96                 the length padding size
97 
98                 Remarks:
99                 Specifies the size (in bytes) of the padding which uses the
100                 length of the data which has been ciphered, this padding is
101                 carried out by the padLength method. For SHA512 the addSize is 16.
102 
103         ***********************************************************************/
104 
105         protected override uint addSize()   { return 16;  }
106 
107         /***********************************************************************
108 
109                 Pads the cipher data
110 
111                 Params:
112                 data = a slice of the cipher buffer to fill with padding
113 
114                 Remarks:
115                 Fills the passed buffer slice with the appropriate padding for
116                 the final call to transform(). This padding will fill the cipher
117                 buffer up to blockSize()-addSize().
118 
119         ***********************************************************************/
120 
121         protected override void padMessage(ubyte[] data)
122         {
123                 data[0] = padChar;
124                 data[1..$] = 0;
125         }
126 
127         /***********************************************************************
128 
129                 Performs the length padding
130 
131                 Params:
132                 data   = the slice of the cipher buffer to fill with padding
133                 length = the length of the data which has been ciphered
134 
135                 Remarks:
136                 Fills the passed buffer slice with addSize() bytes of padding
137                 based on the length in bytes of the input data which has been
138                 ciphered.
139 
140         ***********************************************************************/
141 
142         protected override void padLength(ubyte[] data, ulong length)
143         {
144                 length <<= 3;
145                 for(auto j = data.length; j > 0;) {
146                         j--;
147                         data[data.length-j-1] = cast(ubyte) (length >> j*8);
148                 }
149                 data[0..8] = 0;
150         }
151 
152         /***********************************************************************
153 
154                 Performs the cipher on a block of data
155 
156                 Params:
157                 data = the block of data to cipher
158 
159                 Remarks:
160                 The actual cipher algorithm is carried out by this method on
161                 the passed block of data. This method is called for every
162                 blockSize() bytes of input data and once more with the remaining
163                 data padded to blockSize().
164 
165         ***********************************************************************/
166 
167         protected override void transform(const(ubyte[]) input)
168         {
169                 ulong[80] W;
170                 ulong a,b,c,d,e,f,g,h;
171                 ulong t1,t2;
172                 uint j;
173 
174                 a = context[0];
175                 b = context[1];
176                 c = context[2];
177                 d = context[3];
178                 e = context[4];
179                 f = context[5];
180                 g = context[6];
181                 h = context[7];
182 
183                 bigEndian64(input,W[0..16]);
184                 for(j = 16; j < 80; j++) {
185                         W[j] = mix1(W[j-2]) + W[j-7] + mix0(W[j-15]) + W[j-16];
186                 }
187 
188                 for(j = 0; j < 80; j++) {
189                         t1 = h + sum1(e) + Ch(e,f,g) + K[j] + W[j];
190                         t2 = sum0(a) + Maj(a,b,c);
191                         h = g;
192                         g = f;
193                         f = e;
194                         e = d + t1;
195                         d = c;
196                         c = b;
197                         b = a;
198                         a = t1 + t2;
199                 }
200 
201                 context[0] += a;
202                 context[1] += b;
203                 context[2] += c;
204                 context[3] += d;
205                 context[4] += e;
206                 context[5] += f;
207                 context[6] += g;
208                 context[7] += h;
209         }
210 
211         /***********************************************************************
212 
213         ***********************************************************************/
214 
215         private static ulong Ch(ulong x, ulong y, ulong z)
216         {
217                 return (x&y)^(~x&z);
218         }
219 
220         /***********************************************************************
221 
222         ***********************************************************************/
223 
224         private static ulong Maj(ulong x, ulong y, ulong z)
225         {
226                 return (x&y)^(x&z)^(y&z);
227         }
228 
229         /***********************************************************************
230 
231         ***********************************************************************/
232 
233         private static ulong sum0(ulong x)
234         {
235                 return rotateRight(x,28)^rotateRight(x,34)^rotateRight(x,39);
236         }
237 
238         /***********************************************************************
239 
240         ***********************************************************************/
241 
242         private static ulong sum1(ulong x)
243         {
244                 return rotateRight(x,14)^rotateRight(x,18)^rotateRight(x,41);
245         }
246 
247         /***********************************************************************
248 
249         ***********************************************************************/
250 
251         private static ulong mix0(ulong x)
252         {
253                 return rotateRight(x,1)^rotateRight(x,8)^shiftRight(x,7);
254         }
255 
256         /***********************************************************************
257 
258         ***********************************************************************/
259 
260         private static ulong mix1(ulong x)
261         {
262                 return rotateRight(x,19)^rotateRight(x,61)^shiftRight(x,6);
263         }
264 
265         /***********************************************************************
266 
267         ***********************************************************************/
268 
269         private static ulong rotateRight(ulong x, uint n)
270         {
271                 return (x >> n) | (x << (64-n));
272         }
273 
274         /***********************************************************************
275 
276         ***********************************************************************/
277 
278         private static ulong shiftRight(ulong x, uint n)
279         {
280                 return x >> n;
281         }
282 
283 }
284 
285 /*******************************************************************************
286 
287 *******************************************************************************/
288 
289 private __gshared immutable ulong[] K =
290 [
291         0x428a2f98d728ae22, 0x7137449123ef65cd, 0xb5c0fbcfec4d3b2f, 0xe9b5dba58189dbbc,
292         0x3956c25bf348b538, 0x59f111f1b605d019, 0x923f82a4af194f9b, 0xab1c5ed5da6d8118,
293         0xd807aa98a3030242, 0x12835b0145706fbe, 0x243185be4ee4b28c, 0x550c7dc3d5ffb4e2,
294         0x72be5d74f27b896f, 0x80deb1fe3b1696b1, 0x9bdc06a725c71235, 0xc19bf174cf692694,
295         0xe49b69c19ef14ad2, 0xefbe4786384f25e3, 0x0fc19dc68b8cd5b5, 0x240ca1cc77ac9c65,
296         0x2de92c6f592b0275, 0x4a7484aa6ea6e483, 0x5cb0a9dcbd41fbd4, 0x76f988da831153b5,
297         0x983e5152ee66dfab, 0xa831c66d2db43210, 0xb00327c898fb213f, 0xbf597fc7beef0ee4,
298         0xc6e00bf33da88fc2, 0xd5a79147930aa725, 0x06ca6351e003826f, 0x142929670a0e6e70,
299         0x27b70a8546d22ffc, 0x2e1b21385c26c926, 0x4d2c6dfc5ac42aed, 0x53380d139d95b3df,
300         0x650a73548baf63de, 0x766a0abb3c77b2a8, 0x81c2c92e47edaee6, 0x92722c851482353b,
301         0xa2bfe8a14cf10364, 0xa81a664bbc423001, 0xc24b8b70d0f89791, 0xc76c51a30654be30,
302         0xd192e819d6ef5218, 0xd69906245565a910, 0xf40e35855771202a, 0x106aa07032bbd1b8,
303         0x19a4c116b8d2d0c8, 0x1e376c085141ab53, 0x2748774cdf8eeb99, 0x34b0bcb5e19b48a8,
304         0x391c0cb3c5c95a63, 0x4ed8aa4ae3418acb, 0x5b9cca4f7763e373, 0x682e6ff3d6b2b8a3,
305         0x748f82ee5defb2fc, 0x78a5636f43172f60, 0x84c87814a1f0ab72, 0x8cc702081a6439ec,
306         0x90befffa23631e28, 0xa4506cebde82bde9, 0xbef9a3f7b2c67915, 0xc67178f2e372532b,
307         0xca273eceea26619c, 0xd186b8c721c0c207, 0xeada7dd6cde0eb1e, 0xf57d4f7fee6ed178,
308         0x06f067aa72176fba, 0x0a637dc5a2c898a6, 0x113f9804bef90dae, 0x1b710b35131c471b,
309         0x28db77f523047d84, 0x32caab7b40c72493, 0x3c9ebe0a15c9bebc, 0x431d67c49c100d4c,
310         0x4cc5d4becb3e42b6, 0x597f299cfc657e2a, 0x5fcb6fab3ad6faec, 0x6c44198c4a475817
311 ];
312 
313 /*******************************************************************************
314 
315 *******************************************************************************/
316 
317 private __gshared immutable ulong[8] initial =
318 [
319         0x6a09e667f3bcc908,
320         0xbb67ae8584caa73b,
321         0x3c6ef372fe94f82b,
322         0xa54ff53a5f1d36f1,
323         0x510e527fade682d1,
324         0x9b05688c2b3e6c1f,
325         0x1f83d9abfb41bd6b,
326         0x5be0cd19137e2179
327 ];
328 
329 
330 /*******************************************************************************
331 
332 *******************************************************************************/
333 
334 debug(UnitTest)
335 {
336         unittest
337         {
338         __gshared immutable immutable(char)[][] strings =
339         [
340                 "",
341                 "abc",
342                 "abcdefghbcdefghicdefghijdefghijkefghijklfghijklmghijklmnhijklmnoijklmnopjklmnopqklmnopqrlmnopqrsmnopqrstnopqrstu"
343         ];
344 
345         __gshared immutable immutable(char)[][] results =
346         [
347                 "cf83e1357eefb8bdf1542850d66d8007d620e4050b5715dc83f4a921d36ce9ce47d0d13c5d85f2b0ff8318d2877eec2f63b931bd47417a81a538327af927da3e",
348                 "ddaf35a193617abacc417349ae20413112e6fa4e89a97ea20a9eeee64b55d39a2192992a274fc1a836ba3c23a3feebbd454d4423643ce80e2a9ac94fa54ca49f",
349                 "8e959b75dae313da8cf4f72814fc143f8f7779c6eb9f7fa17299aeadb6889018501d289e4900f7e4331b99dec4b5433ac7d329eeb6dd26545e96e55b874be909"
350         ];
351 
352         Sha512 h = new Sha512;
353 
354         foreach (int i, immutable(char)[] s; strings)
355                 {
356                 h.update(cast(ubyte[])s);
357                 char[] d = h.hexDigest();
358                 assert(d == results[i],"DigestTransform:("~s~")("~d~")!=("~results[i]~")");
359                 }
360         }
361 }