blob: ea645b735060e0d498550506543a1d2693d8e25e [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>.
Denis Vlasenkoddb1b852009-03-12 16:05:02 +000022 * Shrank by Denys Vlasenko.
23 *
24 * ---------------------------------------------------------------------------
25 *
26 * The best way to test random blocksizes is to go to coreutils/md5_sha1_sum.c
27 * and replace "4096" with something like "2000 + time(NULL) % 2097",
28 * then rebuild and compare "shaNNNsum bigfile" results.
Rob Landley5cf7c2d2006-02-21 06:44:43 +000029 */
30
Bernhard Reutner-Fischer421d9e52006-04-03 16:39:31 +000031#include "libbb.h"
Rob Landley5cf7c2d2006-02-21 06:44:43 +000032
Denis Vlasenko56dceb92008-11-10 13:32:50 +000033#define rotl32(x,n) (((x) << (n)) | ((x) >> (32 - (n))))
34#define rotr32(x,n) (((x) >> (n)) | ((x) << (32 - (n))))
35/* for sha512: */
36#define rotr64(x,n) (((x) >> (n)) | ((x) << (64 - (n))))
37#if BB_LITTLE_ENDIAN
38static inline uint64_t hton64(uint64_t v)
39{
40 return (((uint64_t)htonl(v)) << 32) | htonl(v >> 32);
41}
42#else
43#define hton64(v) (v)
44#endif
45#define ntoh64(v) hton64(v)
46
47/* To check alignment gcc has an appropriate operator. Other
48 compilers don't. */
49#if defined(__GNUC__) && __GNUC__ >= 2
50# define UNALIGNED_P(p,type) (((uintptr_t) p) % __alignof__(type) != 0)
51#else
52# define UNALIGNED_P(p,type) (((uintptr_t) p) % sizeof(type) != 0)
53#endif
54
55
Denys Vlasenkofe4ef362009-07-05 20:34:38 +020056/* Some arch headers have conflicting defines */
57#undef ch
58#undef parity
59#undef maj
60#undef rnd
61
Denis Vlasenko8ec8d5e2009-03-15 02:56:00 +000062static void FAST_FUNC sha1_process_block64(sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +000063{
Denis Vlasenko823f10b2009-03-15 04:56:51 +000064 unsigned t;
65 uint32_t W[80], a, b, c, d, e;
66 const uint32_t *words = (uint32_t*) ctx->wbuffer;
Rob Landley5cf7c2d2006-02-21 06:44:43 +000067
Denis Vlasenko823f10b2009-03-15 04:56:51 +000068 for (t = 0; t < 16; ++t) {
69 W[t] = ntohl(*words);
Denis Vlasenkoc8329c92009-03-12 19:06:18 +000070 words++;
71 }
Rob Landley5cf7c2d2006-02-21 06:44:43 +000072
Denis Vlasenko823f10b2009-03-15 04:56:51 +000073 for (/*t = 16*/; t < 80; ++t) {
74 uint32_t T = W[t - 3] ^ W[t - 8] ^ W[t - 14] ^ W[t - 16];
75 W[t] = rotl32(T, 1);
Denis Vlasenko56dceb92008-11-10 13:32:50 +000076 }
Rob Landley5cf7c2d2006-02-21 06:44:43 +000077
78 a = ctx->hash[0];
79 b = ctx->hash[1];
80 c = ctx->hash[2];
81 d = ctx->hash[3];
82 e = ctx->hash[4];
83
Denis Vlasenko56dceb92008-11-10 13:32:50 +000084/* Reverse byte order in 32-bit words */
85#define ch(x,y,z) ((z) ^ ((x) & ((y) ^ (z))))
86#define parity(x,y,z) ((x) ^ (y) ^ (z))
87#define maj(x,y,z) (((x) & (y)) | ((z) & ((x) | (y))))
88/* A normal version as set out in the FIPS. This version uses */
89/* partial loop unrolling and is optimised for the Pentium 4 */
90#define rnd(f,k) \
91 do { \
Denis Vlasenko823f10b2009-03-15 04:56:51 +000092 uint32_t T = a; \
93 a = rotl32(a, 5) + f(b, c, d) + e + k + W[t]; \
94 e = d; \
95 d = c; \
96 c = rotl32(b, 30); \
97 b = T; \
Denis Vlasenko56dceb92008-11-10 13:32:50 +000098 } while (0)
99
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000100 for (t = 0; t < 20; ++t)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000101 rnd(ch, 0x5a827999);
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000102
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000103 for (/*t = 20*/; t < 40; ++t)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000104 rnd(parity, 0x6ed9eba1);
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000105
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000106 for (/*t = 40*/; t < 60; ++t)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000107 rnd(maj, 0x8f1bbcdc);
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000108
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000109 for (/*t = 60*/; t < 80; ++t)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000110 rnd(parity, 0xca62c1d6);
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000111#undef ch
112#undef parity
113#undef maj
114#undef rnd
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000115
116 ctx->hash[0] += a;
117 ctx->hash[1] += b;
118 ctx->hash[2] += c;
119 ctx->hash[3] += d;
120 ctx->hash[4] += e;
121}
122
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000123/* Constants for SHA512 from FIPS 180-2:4.2.3.
124 * SHA256 constants from FIPS 180-2:4.2.2
125 * are the most significant half of first 64 elements
126 * of the same array.
127 */
128static const uint64_t sha_K[80] = {
129 0x428a2f98d728ae22ULL, 0x7137449123ef65cdULL,
130 0xb5c0fbcfec4d3b2fULL, 0xe9b5dba58189dbbcULL,
131 0x3956c25bf348b538ULL, 0x59f111f1b605d019ULL,
132 0x923f82a4af194f9bULL, 0xab1c5ed5da6d8118ULL,
133 0xd807aa98a3030242ULL, 0x12835b0145706fbeULL,
134 0x243185be4ee4b28cULL, 0x550c7dc3d5ffb4e2ULL,
135 0x72be5d74f27b896fULL, 0x80deb1fe3b1696b1ULL,
136 0x9bdc06a725c71235ULL, 0xc19bf174cf692694ULL,
137 0xe49b69c19ef14ad2ULL, 0xefbe4786384f25e3ULL,
138 0x0fc19dc68b8cd5b5ULL, 0x240ca1cc77ac9c65ULL,
139 0x2de92c6f592b0275ULL, 0x4a7484aa6ea6e483ULL,
140 0x5cb0a9dcbd41fbd4ULL, 0x76f988da831153b5ULL,
141 0x983e5152ee66dfabULL, 0xa831c66d2db43210ULL,
142 0xb00327c898fb213fULL, 0xbf597fc7beef0ee4ULL,
143 0xc6e00bf33da88fc2ULL, 0xd5a79147930aa725ULL,
144 0x06ca6351e003826fULL, 0x142929670a0e6e70ULL,
145 0x27b70a8546d22ffcULL, 0x2e1b21385c26c926ULL,
146 0x4d2c6dfc5ac42aedULL, 0x53380d139d95b3dfULL,
147 0x650a73548baf63deULL, 0x766a0abb3c77b2a8ULL,
148 0x81c2c92e47edaee6ULL, 0x92722c851482353bULL,
149 0xa2bfe8a14cf10364ULL, 0xa81a664bbc423001ULL,
150 0xc24b8b70d0f89791ULL, 0xc76c51a30654be30ULL,
151 0xd192e819d6ef5218ULL, 0xd69906245565a910ULL,
152 0xf40e35855771202aULL, 0x106aa07032bbd1b8ULL,
153 0x19a4c116b8d2d0c8ULL, 0x1e376c085141ab53ULL,
154 0x2748774cdf8eeb99ULL, 0x34b0bcb5e19b48a8ULL,
155 0x391c0cb3c5c95a63ULL, 0x4ed8aa4ae3418acbULL,
156 0x5b9cca4f7763e373ULL, 0x682e6ff3d6b2b8a3ULL,
157 0x748f82ee5defb2fcULL, 0x78a5636f43172f60ULL,
158 0x84c87814a1f0ab72ULL, 0x8cc702081a6439ecULL,
159 0x90befffa23631e28ULL, 0xa4506cebde82bde9ULL,
160 0xbef9a3f7b2c67915ULL, 0xc67178f2e372532bULL,
161 0xca273eceea26619cULL, 0xd186b8c721c0c207ULL, /* [64]+ are used for sha512 only */
162 0xeada7dd6cde0eb1eULL, 0xf57d4f7fee6ed178ULL,
163 0x06f067aa72176fbaULL, 0x0a637dc5a2c898a6ULL,
164 0x113f9804bef90daeULL, 0x1b710b35131c471bULL,
165 0x28db77f523047d84ULL, 0x32caab7b40c72493ULL,
166 0x3c9ebe0a15c9bebcULL, 0x431d67c49c100d4cULL,
167 0x4cc5d4becb3e42b6ULL, 0x597f299cfc657e2aULL,
168 0x5fcb6fab3ad6faecULL, 0x6c44198c4a475817ULL
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000169};
170
Denys Vlasenkofe4ef362009-07-05 20:34:38 +0200171#undef Ch
172#undef Maj
173#undef S0
174#undef S1
175#undef R0
176#undef R1
177
Denis Vlasenko8ec8d5e2009-03-15 02:56:00 +0000178static void FAST_FUNC sha256_process_block64(sha256_ctx_t *ctx)
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000179{
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000180 unsigned t;
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000181 uint32_t W[64], a, b, c, d, e, f, g, h;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000182 const uint32_t *words = (uint32_t*) ctx->wbuffer;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000183
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000184 /* Operators defined in FIPS 180-2:4.1.2. */
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000185#define Ch(x, y, z) ((x & y) ^ (~x & z))
186#define Maj(x, y, z) ((x & y) ^ (x & z) ^ (y & z))
187#define S0(x) (rotr32(x, 2) ^ rotr32(x, 13) ^ rotr32(x, 22))
188#define S1(x) (rotr32(x, 6) ^ rotr32(x, 11) ^ rotr32(x, 25))
189#define R0(x) (rotr32(x, 7) ^ rotr32(x, 18) ^ (x >> 3))
190#define R1(x) (rotr32(x, 17) ^ rotr32(x, 19) ^ (x >> 10))
191
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000192 /* Compute the message schedule according to FIPS 180-2:6.2.2 step 2. */
193 for (t = 0; t < 16; ++t) {
194 W[t] = ntohl(*words);
195 words++;
196 }
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000197
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000198 for (/*t = 16*/; t < 64; ++t)
199 W[t] = R1(W[t - 2]) + W[t - 7] + R0(W[t - 15]) + W[t - 16];
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000200
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000201 a = ctx->hash[0];
202 b = ctx->hash[1];
203 c = ctx->hash[2];
204 d = ctx->hash[3];
205 e = ctx->hash[4];
206 f = ctx->hash[5];
207 g = ctx->hash[6];
208 h = ctx->hash[7];
209
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000210 /* The actual computation according to FIPS 180-2:6.2.2 step 3. */
211 for (t = 0; t < 64; ++t) {
Denis Vlasenkoa2333c82009-03-28 19:08:23 +0000212 /* Need to fetch upper half of sha_K[t]
213 * (I hope compiler is clever enough to just fetch
214 * upper half)
215 */
216 uint32_t K_t = sha_K[t] >> 32;
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000217 uint32_t T1 = h + S1(e) + Ch(e, f, g) + K_t + W[t];
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000218 uint32_t T2 = S0(a) + Maj(a, b, c);
219 h = g;
220 g = f;
221 f = e;
222 e = d + T1;
223 d = c;
224 c = b;
225 b = a;
226 a = T1 + T2;
227 }
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000228#undef Ch
229#undef Maj
230#undef S0
231#undef S1
232#undef R0
233#undef R1
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000234 /* Add the starting values of the context according to FIPS 180-2:6.2.2
235 step 4. */
236 ctx->hash[0] += a;
237 ctx->hash[1] += b;
238 ctx->hash[2] += c;
239 ctx->hash[3] += d;
240 ctx->hash[4] += e;
241 ctx->hash[5] += f;
242 ctx->hash[6] += g;
243 ctx->hash[7] += h;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000244}
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000245
Denis Vlasenko8ec8d5e2009-03-15 02:56:00 +0000246static void FAST_FUNC sha512_process_block128(sha512_ctx_t *ctx)
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000247{
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000248 unsigned t;
249 uint64_t W[80];
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000250 /* On i386, having assignments here (not later as sha256 does)
251 * produces 99 bytes smaller code with gcc 4.3.1
252 */
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000253 uint64_t a = ctx->hash[0];
254 uint64_t b = ctx->hash[1];
255 uint64_t c = ctx->hash[2];
256 uint64_t d = ctx->hash[3];
257 uint64_t e = ctx->hash[4];
258 uint64_t f = ctx->hash[5];
259 uint64_t g = ctx->hash[6];
260 uint64_t h = ctx->hash[7];
Denis Vlasenko8ec8d5e2009-03-15 02:56:00 +0000261 const uint64_t *words = (uint64_t*) ctx->wbuffer;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000262
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000263 /* Operators defined in FIPS 180-2:4.1.2. */
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000264#define Ch(x, y, z) ((x & y) ^ (~x & z))
265#define Maj(x, y, z) ((x & y) ^ (x & z) ^ (y & z))
266#define S0(x) (rotr64(x, 28) ^ rotr64(x, 34) ^ rotr64(x, 39))
267#define S1(x) (rotr64(x, 14) ^ rotr64(x, 18) ^ rotr64(x, 41))
268#define R0(x) (rotr64(x, 1) ^ rotr64(x, 8) ^ (x >> 7))
269#define R1(x) (rotr64(x, 19) ^ rotr64(x, 61) ^ (x >> 6))
270
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000271 /* Compute the message schedule according to FIPS 180-2:6.3.2 step 2. */
272 for (t = 0; t < 16; ++t) {
273 W[t] = ntoh64(*words);
274 words++;
275 }
276 for (/*t = 16*/; t < 80; ++t)
277 W[t] = R1(W[t - 2]) + W[t - 7] + R0(W[t - 15]) + W[t - 16];
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000278
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000279 /* The actual computation according to FIPS 180-2:6.3.2 step 3. */
280 for (t = 0; t < 80; ++t) {
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000281 uint64_t T1 = h + S1(e) + Ch(e, f, g) + sha_K[t] + W[t];
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000282 uint64_t T2 = S0(a) + Maj(a, b, c);
283 h = g;
284 g = f;
285 f = e;
286 e = d + T1;
287 d = c;
288 c = b;
289 b = a;
290 a = T1 + T2;
291 }
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000292#undef Ch
293#undef Maj
294#undef S0
295#undef S1
296#undef R0
297#undef R1
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000298 /* Add the starting values of the context according to FIPS 180-2:6.3.2
299 step 4. */
300 ctx->hash[0] += a;
301 ctx->hash[1] += b;
302 ctx->hash[2] += c;
303 ctx->hash[3] += d;
304 ctx->hash[4] += e;
305 ctx->hash[5] += f;
306 ctx->hash[6] += g;
307 ctx->hash[7] += h;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000308}
309
310
Denis Vlasenkodefc1ea2008-06-27 02:52:20 +0000311void FAST_FUNC sha1_begin(sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000312{
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000313 ctx->hash[0] = 0x67452301;
314 ctx->hash[1] = 0xefcdab89;
315 ctx->hash[2] = 0x98badcfe;
316 ctx->hash[3] = 0x10325476;
317 ctx->hash[4] = 0xc3d2e1f0;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000318 ctx->total64 = 0;
319 ctx->process_block = sha1_process_block64;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000320}
321
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000322static const uint32_t init256[] = {
323 0x6a09e667,
324 0xbb67ae85,
325 0x3c6ef372,
326 0xa54ff53a,
327 0x510e527f,
328 0x9b05688c,
329 0x1f83d9ab,
330 0x5be0cd19
331};
332static const uint32_t init512_lo[] = {
333 0xf3bcc908,
334 0x84caa73b,
335 0xfe94f82b,
336 0x5f1d36f1,
337 0xade682d1,
338 0x2b3e6c1f,
339 0xfb41bd6b,
340 0x137e2179
341};
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000342
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000343/* Initialize structure containing state of computation.
344 (FIPS 180-2:5.3.2) */
345void FAST_FUNC sha256_begin(sha256_ctx_t *ctx)
346{
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000347 memcpy(ctx->hash, init256, sizeof(init256));
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000348 ctx->total64 = 0;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000349 ctx->process_block = sha256_process_block64;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000350}
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000351
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000352/* Initialize structure containing state of computation.
353 (FIPS 180-2:5.3.3) */
354void FAST_FUNC sha512_begin(sha512_ctx_t *ctx)
355{
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000356 int i;
357 for (i = 0; i < 8; i++)
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000358 ctx->hash[i] = ((uint64_t)(init256[i]) << 32) + init512_lo[i];
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000359 ctx->total64[0] = ctx->total64[1] = 0;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000360}
361
362
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000363/* Used also for sha256 */
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000364void FAST_FUNC sha1_hash(const void *buffer, size_t len, sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000365{
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000366 unsigned in_buf = ctx->total64 & 63;
367 unsigned add = 64 - in_buf;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000368
Denis Vlasenko98c87f72009-03-11 21:15:51 +0000369 ctx->total64 += len;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000370
Denis Vlasenko6a5d9fa2009-03-12 15:39:11 +0000371 while (len >= add) { /* transfer whole blocks while possible */
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000372 memcpy(ctx->wbuffer + in_buf, buffer, add);
Denis Vlasenko6a5d9fa2009-03-12 15:39:11 +0000373 buffer = (const char *)buffer + add;
374 len -= add;
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000375 add = 64;
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000376 in_buf = 0;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000377 ctx->process_block(ctx);
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000378 }
379
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000380 memcpy(ctx->wbuffer + in_buf, buffer, len);
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000381}
382
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000383void FAST_FUNC sha512_hash(const void *buffer, size_t len, sha512_ctx_t *ctx)
384{
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000385 unsigned in_buf = ctx->total64[0] & 127;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000386 unsigned add = 128 - in_buf;
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000387
388 /* First increment the byte count. FIPS 180-2 specifies the possible
389 length of the file up to 2^128 _bits_.
390 We compute the number of _bytes_ and convert to bits later. */
391 ctx->total64[0] += len;
392 if (ctx->total64[0] < len)
393 ctx->total64[1]++;
394
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000395 while (len >= add) { /* transfer whole blocks while possible */
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000396 memcpy(ctx->wbuffer + in_buf, buffer, add);
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000397 buffer = (const char *)buffer + add;
398 len -= add;
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000399 add = 128;
400 in_buf = 0;
401 sha512_process_block128(ctx);
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000402 }
403
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000404 memcpy(ctx->wbuffer + in_buf, buffer, len);
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000405}
406
407
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000408/* Used also for sha256 */
Denis Vlasenkoe9b9a192008-11-11 01:38:04 +0000409void FAST_FUNC sha1_end(void *resbuf, sha1_ctx_t *ctx)
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000410{
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000411 unsigned i, pad, in_buf;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000412
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000413 in_buf = ctx->total64 & 63;
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000414 /* Pad the buffer to the next 64-byte boundary with 0x80,0,0,0... */
415 ctx->wbuffer[in_buf++] = 0x80;
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000416
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000417 /* This loop iterates either once or twice, no more, no less */
418 while (1) {
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000419 pad = 64 - in_buf;
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000420 memset(ctx->wbuffer + in_buf, 0, pad);
421 in_buf = 0;
422 /* Do we have enough space for the length count? */
423 if (pad >= 8) {
424 /* Store the 64-bit counter of bits in the buffer in BE format */
425 uint64_t t = ctx->total64 << 3;
426 t = hton64(t);
427 /* wbuffer is suitably aligned for this */
Denis Vlasenko823f10b2009-03-15 04:56:51 +0000428 *(uint64_t *) (&ctx->wbuffer[64 - 8]) = t;
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000429 }
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000430 ctx->process_block(ctx);
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000431 if (pad >= 8)
432 break;
Denis Vlasenko6a5d9fa2009-03-12 15:39:11 +0000433 }
Rob Landley5cf7c2d2006-02-21 06:44:43 +0000434
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000435 in_buf = (ctx->process_block == sha1_process_block64) ? 5 : 8;
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000436 /* This way we do not impose alignment constraints on resbuf: */
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000437#if BB_LITTLE_ENDIAN
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000438 for (i = 0; i < in_buf; ++i)
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000439 ctx->hash[i] = htonl(ctx->hash[i]);
440#endif
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000441 memcpy(resbuf, ctx->hash, sizeof(ctx->hash[0]) * in_buf);
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000442}
443
Denis Vlasenkoe9b9a192008-11-11 01:38:04 +0000444void FAST_FUNC sha512_end(void *resbuf, sha512_ctx_t *ctx)
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000445{
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000446 unsigned i, pad, in_buf;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000447
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000448 in_buf = ctx->total64[0] & 127;
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000449 /* Pad the buffer to the next 128-byte boundary with 0x80,0,0,0...
450 * (FIPS 180-2:5.1.2)
451 */
452 ctx->wbuffer[in_buf++] = 0x80;
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000453
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000454 while (1) {
455 pad = 128 - in_buf;
456 memset(ctx->wbuffer + in_buf, 0, pad);
457 in_buf = 0;
458 if (pad >= 16) {
459 /* Store the 128-bit counter of bits in the buffer in BE format */
460 uint64_t t;
461 t = ctx->total64[0] << 3;
462 t = hton64(t);
463 *(uint64_t *) (&ctx->wbuffer[128 - 8]) = t;
464 t = (ctx->total64[1] << 3) | (ctx->total64[0] >> 61);
465 t = hton64(t);
466 *(uint64_t *) (&ctx->wbuffer[128 - 16]) = t;
467 }
Denis Vlasenkoe9afc462009-03-15 02:28:05 +0000468 sha512_process_block128(ctx);
Denis Vlasenkoc8329c92009-03-12 19:06:18 +0000469 if (pad >= 16)
470 break;
471 }
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000472
Denis Vlasenkocd2cd312009-03-12 15:40:27 +0000473#if BB_LITTLE_ENDIAN
474 for (i = 0; i < ARRAY_SIZE(ctx->hash); ++i)
475 ctx->hash[i] = hton64(ctx->hash[i]);
476#endif
477 memcpy(resbuf, ctx->hash, sizeof(ctx->hash));
Denis Vlasenko56dceb92008-11-10 13:32:50 +0000478}