blob: fa468a295219a15ee5b91a79c583767b2cb8207b [file] [log] [blame]
"Robert P. J. Day"63fc1a92006-07-02 19:47:05 +00001/* vi: set sw=4 ts=4: */
Rob Landley5cf7c2d2006-02-21 06:44:43 +00002/*
Denis Vlasenko56dceb92008-11-10 13:32:50 +00003 * Based on shasum from http://www.netsw.org/crypto/hash/
4 * Majorly hacked up to use Dr Brian Gladman's sha1 code
Rob Landley5cf7c2d2006-02-21 06:44:43 +00005 *
Denis Vlasenko56dceb92008-11-10 13:32:50 +00006 * Copyright (C) 2002 Dr Brian Gladman <brg@gladman.me.uk>, Worcester, UK.
7 * Copyright (C) 2003 Glenn L. McGrath
8 * Copyright (C) 2003 Erik Andersen
Denis Vlasenko9213a9e2006-09-17 16:28:10 +00009 *
"Robert P. J. Day"5d8843e2006-07-10 11:41:19 +000010 * Licensed under GPLv2 or later, see file LICENSE in this tarball for details.
Rob Landley5cf7c2d2006-02-21 06:44:43 +000011 *
Denis Vlasenko56dceb92008-11-10 13:32:50 +000012 * ---------------------------------------------------------------------------
13 * Issue Date: 10/11/2002
Rob Landley5cf7c2d2006-02-21 06:44:43 +000014 *
Denis Vlasenko56dceb92008-11-10 13:32:50 +000015 * This is a byte oriented version of SHA1 that operates on arrays of bytes
16 * stored in memory. It runs at 22 cycles per byte on a Pentium P4 processor
17 *
18 * ---------------------------------------------------------------------------
19 *
20 * SHA256 and SHA512 parts are:
21 * Released into the Public Domain by Ulrich Drepper <drepper@redhat.com>.
22 * TODO: shrink them.
Rob Landley5cf7c2d2006-02-21 06:44:43 +000023 */
24
Bernhard Reutner-Fischer421d9e52006-04-03 16:39:31 +000025#include "libbb.h"
Rob Landley5cf7c2d2006-02-21 06:44:43 +000026
Denis Vlasenko56dceb92008-11-10 13:32:50 +000027#define rotl32(x,n) (((x) << (n)) | ((x) >> (32 - (n))))
28#define rotr32(x,n) (((x) >> (n)) | ((x) << (32 - (n))))
29/* for sha512: */
30#define rotr64(x,n) (((x) >> (n)) | ((x) << (64 - (n))))
31#if BB_LITTLE_ENDIAN
32static inline uint64_t hton64(uint64_t v)
33{
34 return (((uint64_t)htonl(v)) << 32) | htonl(v >> 32);
35}
36#else
37#define hton64(v) (v)
38#endif
39#define ntoh64(v) hton64(v)
40
41/* To check alignment gcc has an appropriate operator. Other
42 compilers don't. */
43#if defined(__GNUC__) && __GNUC__ >= 2
44# define UNALIGNED_P(p,type) (((uintptr_t) p) % __alignof__(type) != 0)
45#else
46# define UNALIGNED_P(p,type) (((uintptr_t) p) % sizeof(type) != 0)
47#endif
48
49
Denis Vlasenko52417662006-09-28 00:29:00 +000050#define SHA1_BLOCK_SIZE 64
51#define SHA1_DIGEST_SIZE 20
52#define SHA1_HASH_SIZE SHA1_DIGEST_SIZE
Denis Vlasenko0a009c32008-11-10 09:51:15 +000053#define SHA1_MASK (SHA1_BLOCK_SIZE - 1)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000054
Rob Landley5cf7c2d2006-02-21 06:44:43 +000055static void sha1_compile(sha1_ctx_t *ctx)
56{
57 uint32_t w[80], i, a, b, c, d, e, t;
58
59 /* note that words are compiled from the buffer into 32-bit */
60 /* words in big-endian order so an order reversal is needed */
61 /* here on little endian machines */
62 for (i = 0; i < SHA1_BLOCK_SIZE / 4; ++i)
Denis Vlasenko56dceb92008-11-10 13:32:50 +000063 w[i] = ntohl(ctx->wbuf[i]);
Rob Landley5cf7c2d2006-02-21 06:44:43 +000064
Denis Vlasenko56dceb92008-11-10 13:32:50 +000065 for (/*i = SHA1_BLOCK_SIZE / 4*/; i < 80; ++i) {
66 t = w[i - 3] ^ w[i - 8] ^ w[i - 14] ^ w[i - 16];
67 w[i] = rotl32(t, 1);
68 }
Rob Landley5cf7c2d2006-02-21 06:44:43 +000069
70 a = ctx->hash[0];
71 b = ctx->hash[1];
72 c = ctx->hash[2];
73 d = ctx->hash[3];
74 e = ctx->hash[4];
75
Denis Vlasenko56dceb92008-11-10 13:32:50 +000076/* Reverse byte order in 32-bit words */
77#define ch(x,y,z) ((z) ^ ((x) & ((y) ^ (z))))
78#define parity(x,y,z) ((x) ^ (y) ^ (z))
79#define maj(x,y,z) (((x) & (y)) | ((z) & ((x) | (y))))
80/* A normal version as set out in the FIPS. This version uses */
81/* partial loop unrolling and is optimised for the Pentium 4 */
82#define rnd(f,k) \
83 do { \
84 t = a; a = rotl32(a,5) + f(b,c,d) + e + k + w[i]; \
85 e = d; d = c; c = rotl32(b, 30); b = t; \
86 } while (0)
87
Denis Vlasenko0a009c32008-11-10 09:51:15 +000088 for (i = 0; i < 20; ++i)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000089 rnd(ch, 0x5a827999);
Rob Landley5cf7c2d2006-02-21 06:44:43 +000090
Denis Vlasenko0a009c32008-11-10 09:51:15 +000091 for (i = 20; i < 40; ++i)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000092 rnd(parity, 0x6ed9eba1);
Rob Landley5cf7c2d2006-02-21 06:44:43 +000093
Denis Vlasenko0a009c32008-11-10 09:51:15 +000094 for (i = 40; i < 60; ++i)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000095 rnd(maj, 0x8f1bbcdc);
Rob Landley5cf7c2d2006-02-21 06:44:43 +000096
Denis Vlasenko0a009c32008-11-10 09:51:15 +000097 for (i = 60; i < 80; ++i)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000098 rnd(parity, 0xca62c1d6);
Denis Vlasenko56dceb92008-11-10 13:32:50 +000099#undef ch
100#undef parity
101#undef maj
102#undef rnd
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000103
104 ctx->hash[0] += a;
105 ctx->hash[1] += b;
106 ctx->hash[2] += c;
107 ctx->hash[3] += d;
108 ctx->hash[4] += e;
109}
110
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000111/* Process LEN bytes of BUFFER, accumulating context into CTX.
112 It is assumed that LEN % 64 == 0. */
113static void sha256_process_block(const void *buffer, size_t len, sha256_ctx_t *ctx)
114{
115 /* Constants for SHA256 from FIPS 180-2:4.2.2. */
116 static const uint32_t K[64] = {
117 0x428a2f98, 0x71374491, 0xb5c0fbcf, 0xe9b5dba5,
118 0x3956c25b, 0x59f111f1, 0x923f82a4, 0xab1c5ed5,
119 0xd807aa98, 0x12835b01, 0x243185be, 0x550c7dc3,
120 0x72be5d74, 0x80deb1fe, 0x9bdc06a7, 0xc19bf174,
121 0xe49b69c1, 0xefbe4786, 0x0fc19dc6, 0x240ca1cc,
122 0x2de92c6f, 0x4a7484aa, 0x5cb0a9dc, 0x76f988da,
123 0x983e5152, 0xa831c66d, 0xb00327c8, 0xbf597fc7,
124 0xc6e00bf3, 0xd5a79147, 0x06ca6351, 0x14292967,
125 0x27b70a85, 0x2e1b2138, 0x4d2c6dfc, 0x53380d13,
126 0x650a7354, 0x766a0abb, 0x81c2c92e, 0x92722c85,
127 0xa2bfe8a1, 0xa81a664b, 0xc24b8b70, 0xc76c51a3,
128 0xd192e819, 0xd6990624, 0xf40e3585, 0x106aa070,
129 0x19a4c116, 0x1e376c08, 0x2748774c, 0x34b0bcb5,
130 0x391c0cb3, 0x4ed8aa4a, 0x5b9cca4f, 0x682e6ff3,
131 0x748f82ee, 0x78a5636f, 0x84c87814, 0x8cc70208,
132 0x90befffa, 0xa4506ceb, 0xbef9a3f7, 0xc67178f2
133 };
134 const uint32_t *words = buffer;
135 size_t nwords = len / sizeof(uint32_t);
136 uint32_t a = ctx->H[0];
137 uint32_t b = ctx->H[1];
138 uint32_t c = ctx->H[2];
139 uint32_t d = ctx->H[3];
140 uint32_t e = ctx->H[4];
141 uint32_t f = ctx->H[5];
142 uint32_t g = ctx->H[6];
143 uint32_t h = ctx->H[7];
144
145 /* First increment the byte count. FIPS 180-2 specifies the possible
146 length of the file up to 2^64 bits. Here we only compute the
147 number of bytes. Do a double word increment. */
148 ctx->total[0] += len;
149 if (ctx->total[0] < len)
150 ctx->total[1]++;
151
152 /* Process all bytes in the buffer with 64 bytes in each round of
153 the loop. */
154 while (nwords > 0) {
155 uint32_t W[64];
156 uint32_t a_save = a;
157 uint32_t b_save = b;
158 uint32_t c_save = c;
159 uint32_t d_save = d;
160 uint32_t e_save = e;
161 uint32_t f_save = f;
162 uint32_t g_save = g;
163 uint32_t h_save = h;
164
165 /* Operators defined in FIPS 180-2:4.1.2. */
166#define Ch(x, y, z) ((x & y) ^ (~x & z))
167#define Maj(x, y, z) ((x & y) ^ (x & z) ^ (y & z))
168#define S0(x) (rotr32(x, 2) ^ rotr32(x, 13) ^ rotr32(x, 22))
169#define S1(x) (rotr32(x, 6) ^ rotr32(x, 11) ^ rotr32(x, 25))
170#define R0(x) (rotr32(x, 7) ^ rotr32(x, 18) ^ (x >> 3))
171#define R1(x) (rotr32(x, 17) ^ rotr32(x, 19) ^ (x >> 10))
172
173 /* Compute the message schedule according to FIPS 180-2:6.2.2 step 2. */
174 for (unsigned t = 0; t < 16; ++t) {
175 W[t] = ntohl(*words);
176 ++words;
177 }
178 for (unsigned t = 16; t < 64; ++t)
179 W[t] = R1(W[t - 2]) + W[t - 7] + R0(W[t - 15]) + W[t - 16];
180
181 /* The actual computation according to FIPS 180-2:6.2.2 step 3. */
182 for (unsigned t = 0; t < 64; ++t) {
183 uint32_t T1 = h + S1(e) + Ch(e, f, g) + K[t] + W[t];
184 uint32_t T2 = S0(a) + Maj(a, b, c);
185 h = g;
186 g = f;
187 f = e;
188 e = d + T1;
189 d = c;
190 c = b;
191 b = a;
192 a = T1 + T2;
193 }
194#undef Ch
195#undef Maj
196#undef S0
197#undef S1
198#undef R0
199#undef R1
200 /* Add the starting values of the context according to FIPS 180-2:6.2.2
201 step 4. */
202 a += a_save;
203 b += b_save;
204 c += c_save;
205 d += d_save;
206 e += e_save;
207 f += f_save;
208 g += g_save;
209 h += h_save;
210
211 /* Prepare for the next round. */
212 nwords -= 16;
213 }
214
215 /* Put checksum in context given as argument. */
216 ctx->H[0] = a;
217 ctx->H[1] = b;
218 ctx->H[2] = c;
219 ctx->H[3] = d;
220 ctx->H[4] = e;
221 ctx->H[5] = f;
222 ctx->H[6] = g;
223 ctx->H[7] = h;
224}
225
226/* Process LEN bytes of BUFFER, accumulating context into CTX.
227 It is assumed that LEN % 128 == 0. */
228static void sha512_process_block(const void *buffer, size_t len, sha512_ctx_t *ctx)
229{
230 /* Constants for SHA512 from FIPS 180-2:4.2.3. */
231 static const uint64_t K[80] = {
232 0x428a2f98d728ae22ULL, 0x7137449123ef65cdULL,
233 0xb5c0fbcfec4d3b2fULL, 0xe9b5dba58189dbbcULL,
234 0x3956c25bf348b538ULL, 0x59f111f1b605d019ULL,
235 0x923f82a4af194f9bULL, 0xab1c5ed5da6d8118ULL,
236 0xd807aa98a3030242ULL, 0x12835b0145706fbeULL,
237 0x243185be4ee4b28cULL, 0x550c7dc3d5ffb4e2ULL,
238 0x72be5d74f27b896fULL, 0x80deb1fe3b1696b1ULL,
239 0x9bdc06a725c71235ULL, 0xc19bf174cf692694ULL,
240 0xe49b69c19ef14ad2ULL, 0xefbe4786384f25e3ULL,
241 0x0fc19dc68b8cd5b5ULL, 0x240ca1cc77ac9c65ULL,
242 0x2de92c6f592b0275ULL, 0x4a7484aa6ea6e483ULL,
243 0x5cb0a9dcbd41fbd4ULL, 0x76f988da831153b5ULL,
244 0x983e5152ee66dfabULL, 0xa831c66d2db43210ULL,
245 0xb00327c898fb213fULL, 0xbf597fc7beef0ee4ULL,
246 0xc6e00bf33da88fc2ULL, 0xd5a79147930aa725ULL,
247 0x06ca6351e003826fULL, 0x142929670a0e6e70ULL,
248 0x27b70a8546d22ffcULL, 0x2e1b21385c26c926ULL,
249 0x4d2c6dfc5ac42aedULL, 0x53380d139d95b3dfULL,
250 0x650a73548baf63deULL, 0x766a0abb3c77b2a8ULL,
251 0x81c2c92e47edaee6ULL, 0x92722c851482353bULL,
252 0xa2bfe8a14cf10364ULL, 0xa81a664bbc423001ULL,
253 0xc24b8b70d0f89791ULL, 0xc76c51a30654be30ULL,
254 0xd192e819d6ef5218ULL, 0xd69906245565a910ULL,
255 0xf40e35855771202aULL, 0x106aa07032bbd1b8ULL,
256 0x19a4c116b8d2d0c8ULL, 0x1e376c085141ab53ULL,
257 0x2748774cdf8eeb99ULL, 0x34b0bcb5e19b48a8ULL,
258 0x391c0cb3c5c95a63ULL, 0x4ed8aa4ae3418acbULL,
259 0x5b9cca4f7763e373ULL, 0x682e6ff3d6b2b8a3ULL,
260 0x748f82ee5defb2fcULL, 0x78a5636f43172f60ULL,
261 0x84c87814a1f0ab72ULL, 0x8cc702081a6439ecULL,
262 0x90befffa23631e28ULL, 0xa4506cebde82bde9ULL,
263 0xbef9a3f7b2c67915ULL, 0xc67178f2e372532bULL,
264 0xca273eceea26619cULL, 0xd186b8c721c0c207ULL,
265 0xeada7dd6cde0eb1eULL, 0xf57d4f7fee6ed178ULL,
266 0x06f067aa72176fbaULL, 0x0a637dc5a2c898a6ULL,
267 0x113f9804bef90daeULL, 0x1b710b35131c471bULL,
268 0x28db77f523047d84ULL, 0x32caab7b40c72493ULL,
269 0x3c9ebe0a15c9bebcULL, 0x431d67c49c100d4cULL,
270 0x4cc5d4becb3e42b6ULL, 0x597f299cfc657e2aULL,
271 0x5fcb6fab3ad6faecULL, 0x6c44198c4a475817ULL,
272 };
273 const uint64_t *words = buffer;
274 size_t nwords = len / sizeof(uint64_t);
275 uint64_t a = ctx->H[0];
276 uint64_t b = ctx->H[1];
277 uint64_t c = ctx->H[2];
278 uint64_t d = ctx->H[3];
279 uint64_t e = ctx->H[4];
280 uint64_t f = ctx->H[5];
281 uint64_t g = ctx->H[6];
282 uint64_t h = ctx->H[7];
283
284 /* First increment the byte count. FIPS 180-2 specifies the possible
285 length of the file up to 2^128 bits. Here we only compute the
286 number of bytes. Do a double word increment. */
287 ctx->total[0] += len;
288 if (ctx->total[0] < len)
289 ctx->total[1]++;
290
291 /* Process all bytes in the buffer with 128 bytes in each round of
292 the loop. */
293 while (nwords > 0) {
294 uint64_t W[80];
295 uint64_t a_save = a;
296 uint64_t b_save = b;
297 uint64_t c_save = c;
298 uint64_t d_save = d;
299 uint64_t e_save = e;
300 uint64_t f_save = f;
301 uint64_t g_save = g;
302 uint64_t h_save = h;
303
304 /* Operators defined in FIPS 180-2:4.1.2. */
305#define Ch(x, y, z) ((x & y) ^ (~x & z))
306#define Maj(x, y, z) ((x & y) ^ (x & z) ^ (y & z))
307#define S0(x) (rotr64(x, 28) ^ rotr64(x, 34) ^ rotr64(x, 39))
308#define S1(x) (rotr64(x, 14) ^ rotr64(x, 18) ^ rotr64(x, 41))
309#define R0(x) (rotr64(x, 1) ^ rotr64(x, 8) ^ (x >> 7))
310#define R1(x) (rotr64(x, 19) ^ rotr64(x, 61) ^ (x >> 6))
311
312 /* Compute the message schedule according to FIPS 180-2:6.3.2 step 2. */
313 for (unsigned t = 0; t < 16; ++t) {
314 W[t] = ntoh64(*words);
315 ++words;
316 }
317 for (unsigned t = 16; t < 80; ++t)
318 W[t] = R1(W[t - 2]) + W[t - 7] + R0(W[t - 15]) + W[t - 16];
319
320 /* The actual computation according to FIPS 180-2:6.3.2 step 3. */
321 for (unsigned t = 0; t < 80; ++t) {
322 uint64_t T1 = h + S1(e) + Ch(e, f, g) + K[t] + W[t];
323 uint64_t T2 = S0(a) + Maj(a, b, c);
324 h = g;
325 g = f;
326 f = e;
327 e = d + T1;
328 d = c;
329 c = b;
330 b = a;
331 a = T1 + T2;
332 }
333#undef Ch
334#undef Maj
335#undef S0
336#undef S1
337#undef R0
338#undef R1
339 /* Add the starting values of the context according to FIPS 180-2:6.3.2
340 step 4. */
341 a += a_save;
342 b += b_save;
343 c += c_save;
344 d += d_save;
345 e += e_save;
346 f += f_save;
347 g += g_save;
348 h += h_save;
349
350 /* Prepare for the next round. */
351 nwords -= 16;
352 }
353
354 /* Put checksum in context given as argument. */
355 ctx->H[0] = a;
356 ctx->H[1] = b;
357 ctx->H[2] = c;
358 ctx->H[3] = d;
359 ctx->H[4] = e;
360 ctx->H[5] = f;
361 ctx->H[6] = g;
362 ctx->H[7] = h;
363}
364
365
Denis Vlasenkodefc1ea2008-06-27 02:52:20 +0000366void FAST_FUNC sha1_begin(sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000367{
368 ctx->count[0] = ctx->count[1] = 0;
369 ctx->hash[0] = 0x67452301;
370 ctx->hash[1] = 0xefcdab89;
371 ctx->hash[2] = 0x98badcfe;
372 ctx->hash[3] = 0x10325476;
373 ctx->hash[4] = 0xc3d2e1f0;
374}
375
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000376/* Initialize structure containing state of computation.
377 (FIPS 180-2:5.3.2) */
378void FAST_FUNC sha256_begin(sha256_ctx_t *ctx)
379{
380 ctx->H[0] = 0x6a09e667;
381 ctx->H[1] = 0xbb67ae85;
382 ctx->H[2] = 0x3c6ef372;
383 ctx->H[3] = 0xa54ff53a;
384 ctx->H[4] = 0x510e527f;
385 ctx->H[5] = 0x9b05688c;
386 ctx->H[6] = 0x1f83d9ab;
387 ctx->H[7] = 0x5be0cd19;
388 ctx->total[0] = ctx->total[1] = 0;
389 ctx->buflen = 0;
390}
391
392/* Initialize structure containing state of computation.
393 (FIPS 180-2:5.3.3) */
394void FAST_FUNC sha512_begin(sha512_ctx_t *ctx)
395{
396 ctx->H[0] = 0x6a09e667f3bcc908ULL;
397 ctx->H[1] = 0xbb67ae8584caa73bULL;
398 ctx->H[2] = 0x3c6ef372fe94f82bULL;
399 ctx->H[3] = 0xa54ff53a5f1d36f1ULL;
400 ctx->H[4] = 0x510e527fade682d1ULL;
401 ctx->H[5] = 0x9b05688c2b3e6c1fULL;
402 ctx->H[6] = 0x1f83d9abfb41bd6bULL;
403 ctx->H[7] = 0x5be0cd19137e2179ULL;
404 ctx->total[0] = ctx->total[1] = 0;
405 ctx->buflen = 0;
406}
407
408
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000409/* SHA1 hash data in an array of bytes into hash buffer and call the */
410/* hash_compile function as required. */
Denis Vlasenkodefc1ea2008-06-27 02:52:20 +0000411void FAST_FUNC sha1_hash(const void *data, size_t length, sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000412{
413 uint32_t pos = (uint32_t) (ctx->count[0] & SHA1_MASK);
414 uint32_t freeb = SHA1_BLOCK_SIZE - pos;
415 const unsigned char *sp = data;
416
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000417 ctx->count[0] += length;
418 if (ctx->count[0] < length)
Denis Vlasenko0a009c32008-11-10 09:51:15 +0000419 ctx->count[1]++;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000420
Denis Vlasenkoc028ec22008-11-10 10:47:47 +0000421 while (length >= freeb) { /* transfer whole blocks while possible */
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000422 memcpy(((unsigned char *) ctx->wbuf) + pos, sp, freeb);
423 sp += freeb;
424 length -= freeb;
425 freeb = SHA1_BLOCK_SIZE;
426 pos = 0;
427 sha1_compile(ctx);
428 }
429
430 memcpy(((unsigned char *) ctx->wbuf) + pos, sp, length);
431}
432
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000433void FAST_FUNC sha256_hash(const void *buffer, size_t len, sha256_ctx_t *ctx)
434{
435 /* When we already have some bits in our internal buffer concatenate
436 both inputs first. */
437 if (ctx->buflen != 0) {
438 size_t left_over = ctx->buflen;
439 size_t add = 128 - left_over > len ? len : 128 - left_over;
440
441 memcpy(&ctx->buffer[left_over], buffer, add);
442 ctx->buflen += add;
443
444 if (ctx->buflen > 64) {
445 sha256_process_block(ctx->buffer, ctx->buflen & ~63, ctx);
446
447 ctx->buflen &= 63;
448 /* The regions in the following copy operation cannot overlap. */
449 memcpy(ctx->buffer,
450 &ctx->buffer[(left_over + add) & ~63],
451 ctx->buflen);
452 }
453
454 buffer = (const char *)buffer + add;
455 len -= add;
456 }
457
458 /* Process available complete blocks. */
459 if (len >= 64) {
460 if (UNALIGNED_P(buffer, uint32_t)) {
461 while (len > 64) {
462 sha256_process_block(memcpy(ctx->buffer, buffer, 64),
463 64, ctx);
464 buffer = (const char *)buffer + 64;
465 len -= 64;
466 }
467 } else {
468 sha256_process_block(buffer, len & ~63, ctx);
469 buffer = (const char *)buffer + (len & ~63);
470 len &= 63;
471 }
472 }
473
474 /* Move remaining bytes into internal buffer. */
475 if (len > 0) {
476 size_t left_over = ctx->buflen;
477
478 memcpy(&ctx->buffer[left_over], buffer, len);
479 left_over += len;
480 if (left_over >= 64) {
481 sha256_process_block(ctx->buffer, 64, ctx);
482 left_over -= 64;
483 memcpy(ctx->buffer, &ctx->buffer[64], left_over);
484 }
485 ctx->buflen = left_over;
486 }
487}
488
489void FAST_FUNC sha512_hash(const void *buffer, size_t len, sha512_ctx_t *ctx)
490{
491 /* When we already have some bits in our internal buffer concatenate
492 both inputs first. */
493 if (ctx->buflen != 0) {
494 size_t left_over = ctx->buflen;
495 size_t add = 256 - left_over > len ? len : 256 - left_over;
496
497 memcpy(&ctx->buffer[left_over], buffer, add);
498 ctx->buflen += add;
499
500 if (ctx->buflen > 128) {
501 sha512_process_block(ctx->buffer, ctx->buflen & ~127, ctx);
502
503 ctx->buflen &= 127;
504 /* The regions in the following copy operation cannot overlap. */
505 memcpy(ctx->buffer,
506 &ctx->buffer[(left_over + add) & ~127],
507 ctx->buflen);
508 }
509
510 buffer = (const char *)buffer + add;
511 len -= add;
512 }
513
514 /* Process available complete blocks. */
515 if (len >= 128) {
516// #if BB_ARCH_REQUIRES_ALIGNMENT
517 if (UNALIGNED_P(buffer, uint64_t)) {
518 while (len > 128) {
519 sha512_process_block(memcpy(ctx->buffer, buffer, 128),
520 128, ctx);
521 buffer = (const char *)buffer + 128;
522 len -= 128;
523 }
524 } else
525// #endif
526 {
527 sha512_process_block(buffer, len & ~127, ctx);
528 buffer = (const char *)buffer + (len & ~127);
529 len &= 127;
530 }
531 }
532
533 /* Move remaining bytes into internal buffer. */
534 if (len > 0) {
535 size_t left_over = ctx->buflen;
536
537 memcpy(&ctx->buffer[left_over], buffer, len);
538 left_over += len;
539 if (left_over >= 128) {
540 sha512_process_block(ctx->buffer, 128, ctx);
541 left_over -= 128;
542 memcpy(ctx->buffer, &ctx->buffer[128], left_over);
543 }
544 ctx->buflen = left_over;
545 }
546}
547
548
Denis Vlasenkodefc1ea2008-06-27 02:52:20 +0000549void* FAST_FUNC sha1_end(void *resbuf, sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000550{
551 /* SHA1 Final padding and digest calculation */
Mike Frysingerf8855132006-03-28 02:35:56 +0000552#if BB_BIG_ENDIAN
Denis Vlasenko0a009c32008-11-10 09:51:15 +0000553 static const uint32_t mask[4] = { 0x00000000, 0xff000000, 0xffff0000, 0xffffff00 };
554 static const uint32_t bits[4] = { 0x80000000, 0x00800000, 0x00008000, 0x00000080 };
Mike Frysingerf8855132006-03-28 02:35:56 +0000555#else
Denis Vlasenko0a009c32008-11-10 09:51:15 +0000556 static const uint32_t mask[4] = { 0x00000000, 0x000000ff, 0x0000ffff, 0x00ffffff };
557 static const uint32_t bits[4] = { 0x00000080, 0x00008000, 0x00800000, 0x80000000 };
Rob Landley2c39eee2006-05-05 16:54:40 +0000558#endif
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000559
560 uint8_t *hval = resbuf;
561 uint32_t i, cnt = (uint32_t) (ctx->count[0] & SHA1_MASK);
562
563 /* mask out the rest of any partial 32-bit word and then set */
564 /* the next byte to 0x80. On big-endian machines any bytes in */
565 /* the buffer will be at the top end of 32 bit words, on little */
566 /* endian machines they will be at the bottom. Hence the AND */
567 /* and OR masks above are reversed for little endian systems */
568 ctx->wbuf[cnt >> 2] =
569 (ctx->wbuf[cnt >> 2] & mask[cnt & 3]) | bits[cnt & 3];
570
571 /* we need 9 or more empty positions, one for the padding byte */
572 /* (above) and eight for the length count. If there is not */
573 /* enough space pad and empty the buffer */
574 if (cnt > SHA1_BLOCK_SIZE - 9) {
575 if (cnt < 60)
576 ctx->wbuf[15] = 0;
577 sha1_compile(ctx);
578 cnt = 0;
Denis Vlasenko0a009c32008-11-10 09:51:15 +0000579 } else /* compute a word index for the empty buffer positions */
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000580 cnt = (cnt >> 2) + 1;
581
Denis Vlasenko0a009c32008-11-10 09:51:15 +0000582 while (cnt < 14) /* and zero pad all but last two positions */
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000583 ctx->wbuf[cnt++] = 0;
584
585 /* assemble the eight byte counter in the buffer in big-endian */
Denis Vlasenko52417662006-09-28 00:29:00 +0000586 /* format */
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000587 ctx->wbuf[14] = htonl((ctx->count[1] << 3) | (ctx->count[0] >> 29));
588 ctx->wbuf[15] = htonl(ctx->count[0] << 3);
589
590 sha1_compile(ctx);
591
592 /* extract the hash value as bytes in case the hash buffer is */
593 /* misaligned for 32-bit words */
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000594 for (i = 0; i < SHA1_DIGEST_SIZE; ++i)
595 hval[i] = (unsigned char) (ctx->hash[i >> 2] >> 8 * (~i & 3));
Denis Vlasenko9213a9e2006-09-17 16:28:10 +0000596
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000597 return resbuf;
598}
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000599
600
601/* Process the remaining bytes in the internal buffer and the usual
602 prolog according to the standard and write the result to RESBUF.
603
604 IMPORTANT: On some systems it is required that RESBUF is correctly
605 aligned for a 32 bits value. */
606void* FAST_FUNC sha256_end(void *resbuf, sha256_ctx_t *ctx)
607{
608 /* Take yet unprocessed bytes into account. */
609 uint32_t bytes = ctx->buflen;
610 size_t pad;
611
612 /* Now count remaining bytes. */
613 ctx->total[0] += bytes;
614 if (ctx->total[0] < bytes)
615 ctx->total[1]++;
616
617 /* Pad the buffer to the next 64-byte boundary with 0x80,0,0,0...
618 (FIPS 180-2:5.1.1) */
619 pad = (bytes >= 56 ? 64 + 56 - bytes : 56 - bytes);
620 memset(&ctx->buffer[bytes], 0, pad);
621 ctx->buffer[bytes] = 0x80;
622
623 /* Put the 64-bit file length in *bits* at the end of the buffer. */
624 *(uint32_t *) &ctx->buffer[bytes + pad + 4] = ntohl(ctx->total[0] << 3);
625 *(uint32_t *) &ctx->buffer[bytes + pad] = ntohl((ctx->total[1] << 3) | (ctx->total[0] >> 29));
626
627 /* Process last bytes. */
628 sha256_process_block(ctx->buffer, bytes + pad + 8, ctx);
629
630 /* Put result from CTX in first 32 bytes following RESBUF. */
631 for (unsigned i = 0; i < 8; ++i)
632 ((uint32_t *) resbuf)[i] = ntohl(ctx->H[i]);
633
634 return resbuf;
635}
636
637/* Process the remaining bytes in the internal buffer and the usual
638 prolog according to the standard and write the result to RESBUF.
639
640 IMPORTANT: On some systems it is required that RESBUF is correctly
641 aligned for a 64 bits value. */
642void* FAST_FUNC sha512_end(void *resbuf, sha512_ctx_t *ctx)
643{
644 /* Take yet unprocessed bytes into account. */
645 uint64_t bytes = ctx->buflen;
646 size_t pad;
647
648 /* Now count remaining bytes. */
649 ctx->total[0] += bytes;
650 if (ctx->total[0] < bytes)
651 ctx->total[1]++;
652
653 /* Pad the buffer to the next 128-byte boundary with 0x80,0,0,0...
654 (FIPS 180-2:5.1.2) */
655 pad = bytes >= 112 ? 128 + 112 - bytes : 112 - bytes;
656 memset(&ctx->buffer[bytes], 0, pad);
657 ctx->buffer[bytes] = 0x80;
658
659 /* Put the 128-bit file length in *bits* at the end of the buffer. */
660 *(uint64_t *) &ctx->buffer[bytes + pad + 8] = hton64(ctx->total[0] << 3);
661 *(uint64_t *) &ctx->buffer[bytes + pad] = hton64((ctx->total[1] << 3) | (ctx->total[0] >> 61));
662
663 /* Process last bytes. */
664 sha512_process_block(ctx->buffer, bytes + pad + 16, ctx);
665
666 /* Put result from CTX in first 64 bytes following RESBUF. */
667 for (unsigned i = 0; i < 8; ++i)
668 ((uint64_t *) resbuf)[i] = hton64(ctx->H[i]);
669
670 return resbuf;
671}