This commit is contained in:
Russ Cox
2005-08-08 12:50:13 +00:00
parent 0189e66e88
commit 934846f35c
382 changed files with 62614 additions and 0 deletions

60
libsec/Makefile Normal file
View File

@ -0,0 +1,60 @@
LIB=libsec.a
CC=gcc
CFLAGS=-I../include -I. -c -ggdb -D_THREAD_SAFE -pthread
O=o
OFILES=\
aes.$O\
blowfish.$O\
decodepem.$O\
des.$O\
des3CBC.$O\
des3ECB.$O\
desCBC.$O\
desECB.$O\
desmodes.$O\
dsaalloc.$O\
dsagen.$O\
dsaprimes.$O\
dsaprivtopub.$O\
dsasign.$O\
dsaverify.$O\
egalloc.$O\
egdecrypt.$O\
egencrypt.$O\
eggen.$O\
egprivtopub.$O\
egsign.$O\
egverify.$O\
fastrand.$O\
genprime.$O\
genrandom.$O\
gensafeprime.$O\
genstrongprime.$O\
hmac.$O\
md4.$O\
md5.$O\
md5block.$O\
md5pickle.$O\
nfastrand.$O\
prng.$O\
probably_prime.$O\
rc4.$O\
rsaalloc.$O\
rsadecrypt.$O\
rsaencrypt.$O\
rsafill.$O\
rsagen.$O\
rsaprivtopub.$O\
sha1.$O\
sha1block.$O\
sha1pickle.$O\
smallprimes.$O
$(LIB): $(OFILES)
ar r $(LIB) $(OFILES)
ranlib $(LIB)
%.$O: %.c
$(CC) $(CFLAGS) $*.c

1544
libsec/aes.c Normal file

File diff suppressed because it is too large Load Diff

579
libsec/blowfish.c Normal file
View File

@ -0,0 +1,579 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// Blowfish block cipher. See:
// Lecture Notes in Computer Science 809
// Fast Software Encryption
// Cambridge Security Workshop, Cambridge, England (1993)
static u32int sbox[1024];
static u32int pbox[BFrounds+2];
static void bfencrypt(u32int *, BFstate *);
static void bfdecrypt(u32int *, BFstate *);
void
setupBFstate(BFstate *s, uchar key[], int keybytes, uchar *ivec)
{
int i, j;
u32int n, buf[2];
memset(s, 0, sizeof(*s));
memset(buf, 0, sizeof buf);
if (keybytes > sizeof(s->key))
keybytes = sizeof(s->key);
memmove(s->key, key, keybytes);
if (ivec != nil)
memmove(s->ivec, ivec, sizeof(s->ivec));
else
memset(s->ivec, 0, sizeof(s->ivec));
memmove(s->pbox, pbox, sizeof(pbox));
memmove(s->sbox, sbox, sizeof(sbox));
if (keybytes > 4*(BFrounds + 2))
keybytes = 4*(BFrounds + 2);
for(i=j=0; i < BFrounds+2; i++) {
n = key[j];
j = (j+1) % keybytes;
n <<= 8;
n |= key[j];
j = (j+1) % keybytes;
n <<= 8;
n |= key[j];
j = (j+1) % keybytes;
n <<= 8;
n |= key[j];
j = (j+1) % keybytes;
s->pbox[i] ^= n;
}
for(i=0; i < BFrounds+2; i += 2) {
bfencrypt(buf, s);
s->pbox[i] = buf[0];
s->pbox[i+1] = buf[1];
}
for(i=0; i < 1024; i += 2) {
bfencrypt(buf, s);
s->sbox[i] = buf[0];
s->sbox[i+1] = buf[1];
}
s->setup = 0xcafebabe;
}
void
bfCBCencrypt(uchar *buf, int n, BFstate *s)
{
int i;
uchar *p;
u32int bo[2], bi[2], b;
assert((n & 7) == 0);
bo[0] = s->ivec[0] | ((u32int) s->ivec[1]<<8) | ((u32int)s->ivec[2]<<16) | ((u32int)s->ivec[3]<<24);
bo[1] = s->ivec[4] | ((u32int) s->ivec[5]<<8) | ((u32int)s->ivec[6]<<16) | ((u32int)s->ivec[7]<<24);
for(i=0; i < n; i += 8, buf += 8) {
bi[0] = buf[0] | ((u32int) buf[1]<<8) | ((u32int)buf[2]<<16) | ((u32int)buf[3]<<24);
bi[1] = buf[4] | ((u32int) buf[5]<<8) | ((u32int)buf[6]<<16) | ((u32int)buf[7]<<24);
bi[0] ^= bo[0];
bi[1] ^= bo[1];
bfencrypt(bi, s);
bo[0] = bi[0];
bo[1] = bi[1];
p = buf;
b = bo[0];
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b = bo[1];
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p = b;
}
s->ivec[7] = bo[1] >> 24;
s->ivec[6] = bo[1] >> 16;
s->ivec[5] = bo[1] >> 8;
s->ivec[4] = bo[1];
s->ivec[3] = bo[0] >> 24;
s->ivec[2] = bo[0] >> 16;
s->ivec[1] = bo[0] >> 8;
s->ivec[0] = bo[0];
return;
}
void
bfCBCdecrypt(uchar *buf, int n, BFstate *s)
{
int i;
uchar *p;
u32int b, bo[2], bi[2], xr[2];
assert((n & 7) == 0);
bo[0] = s->ivec[0] | ((u32int) s->ivec[1]<<8) | ((u32int)s->ivec[2]<<16) | ((u32int)s->ivec[3]<<24);
bo[1] = s->ivec[4] | ((u32int) s->ivec[5]<<8) | ((u32int)s->ivec[6]<<16) | ((u32int)s->ivec[7]<<24);
for(i=0; i < n; i += 8, buf += 8) {
bi[0] = buf[0] | ((u32int) buf[1]<<8) | ((u32int)buf[2]<<16) | ((u32int)buf[3]<<24);
bi[1] = buf[4] | ((u32int) buf[5]<<8) | ((u32int)buf[6]<<16) | ((u32int)buf[7]<<24);
xr[0] = bi[0];
xr[1] = bi[1];
bfdecrypt(bi, s);
bo[0] ^= bi[0];
bo[1] ^= bi[1];
p = buf;
b = bo[0];
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b = bo[1];
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p++ = b;
b >>= 8;
*p = b;
bo[0] = xr[0];
bo[1] = xr[1];
}
s->ivec[7] = bo[1] >> 24;
s->ivec[6] = bo[1] >> 16;
s->ivec[5] = bo[1] >> 8;
s->ivec[4] = bo[1];
s->ivec[3] = bo[0] >> 24;
s->ivec[2] = bo[0] >> 16;
s->ivec[1] = bo[0] >> 8;
s->ivec[0] = bo[0];
return;
}
void
bfECBencrypt(uchar *buf, int n, BFstate *s)
{
int i;
u32int b[2];
for(i=0; i < n; i += 8, buf += 8) {
b[0] = buf[0] | ((u32int) buf[1]<<8) | ((u32int)buf[2]<<16) | ((u32int)buf[3]<<24);
b[1] = buf[4] | ((u32int) buf[5]<<8) | ((u32int)buf[6]<<16) | ((u32int)buf[7]<<24);
bfencrypt(b, s);
buf[7] = b[1] >> 24;
buf[6] = b[1] >> 16;
buf[5] = b[1] >> 8;
buf[4] = b[1];
buf[3] = b[0] >> 24;
buf[2] = b[0] >> 16;
buf[1] = b[0] >> 8;
buf[0] = b[0];
}
return;
}
void
bfECBdecrypt(uchar *buf, int n, BFstate *s)
{
int i;
u32int b[2];
for(i=0; i < n; i += 8, buf += 8) {
b[0] = buf[0] | ((u32int) buf[1]<<8) | ((u32int)buf[2]<<16) | ((u32int)buf[3]<<24);
b[1] = buf[4] | ((u32int) buf[5]<<8) | ((u32int)buf[6]<<16) | ((u32int)buf[7]<<24);
bfdecrypt(b, s);
buf[7] = b[1] >> 24;
buf[6] = b[1] >> 16;
buf[5] = b[1] >> 8;
buf[4] = b[1];
buf[3] = b[0] >> 24;
buf[2] = b[0] >> 16;
buf[1] = b[0] >> 8;
buf[0] = b[0];
}
return;
}
static void
bfencrypt(u32int *b, BFstate *s)
{
int i;
u32int l, r;
u32int *pb, *sb;
l = b[0];
r = b[1];
pb = s->pbox;
sb = s->sbox;
l ^= pb[0];
for(i=1; i<16; i += 2) {
r ^= pb[i];
r ^= ( (sb[ (uchar) (l>>24)] + sb[256 + ((uchar) (l>>16))]) ^
sb[512 + ((uchar) (l>>8))]) + sb[768 +((uchar) l)];
l ^= pb[i+1];
l ^= ( (sb[ (uchar) (r>>24)] + sb[256 + ((uchar) (r>>16))]) ^
sb[512 + ((uchar) (r>>8))]) + sb[768 +((uchar) r)];
}
r ^= pb[BFrounds+1];
/* sic */
b[0] = r;
b[1] = l;
return;
}
static void
bfdecrypt(u32int *b, BFstate *s)
{
int i;
u32int l, r;
u32int *pb, *sb;
l = b[0];
r = b[1];
pb = s->pbox;
sb = s->sbox;
l ^= pb[BFrounds+1];
for(i=16; i > 0; i -= 2) {
r ^= pb[i];
r ^= ( (sb[ (uchar) (l>>24)] + sb[256 + ((uchar) (l>>16))]) ^
sb[512 + ((uchar) (l>>8))]) + sb[768 +((uchar) l)];
l ^= pb[i-1];
l ^= ( (sb[ (uchar) (r>>24)] + sb[256 + ((uchar) (r>>16))]) ^
sb[512 + ((uchar) (r>>8))]) + sb[768 +((uchar) r)];
}
r ^= pb[0];
/* sic */
b[0] = r;
b[1] = l;
return;
}
static u32int pbox[BFrounds+2] = {
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
0x9216d5d9, 0x8979fb1b
};
static u32int sbox[1024] = {
0xd1310ba6L, 0x98dfb5acL, 0x2ffd72dbL, 0xd01adfb7L,
0xb8e1afedL, 0x6a267e96L, 0xba7c9045L, 0xf12c7f99L,
0x24a19947L, 0xb3916cf7L, 0x0801f2e2L, 0x858efc16L,
0x636920d8L, 0x71574e69L, 0xa458fea3L, 0xf4933d7eL,
0x0d95748fL, 0x728eb658L, 0x718bcd58L, 0x82154aeeL,
0x7b54a41dL, 0xc25a59b5L, 0x9c30d539L, 0x2af26013L,
0xc5d1b023L, 0x286085f0L, 0xca417918L, 0xb8db38efL,
0x8e79dcb0L, 0x603a180eL, 0x6c9e0e8bL, 0xb01e8a3eL,
0xd71577c1L, 0xbd314b27L, 0x78af2fdaL, 0x55605c60L,
0xe65525f3L, 0xaa55ab94L, 0x57489862L, 0x63e81440L,
0x55ca396aL, 0x2aab10b6L, 0xb4cc5c34L, 0x1141e8ceL,
0xa15486afL, 0x7c72e993L, 0xb3ee1411L, 0x636fbc2aL,
0x2ba9c55dL, 0x741831f6L, 0xce5c3e16L, 0x9b87931eL,
0xafd6ba33L, 0x6c24cf5cL, 0x7a325381L, 0x28958677L,
0x3b8f4898L, 0x6b4bb9afL, 0xc4bfe81bL, 0x66282193L,
0x61d809ccL, 0xfb21a991L, 0x487cac60L, 0x5dec8032L,
0xef845d5dL, 0xe98575b1L, 0xdc262302L, 0xeb651b88L,
0x23893e81L, 0xd396acc5L, 0x0f6d6ff3L, 0x83f44239L,
0x2e0b4482L, 0xa4842004L, 0x69c8f04aL, 0x9e1f9b5eL,
0x21c66842L, 0xf6e96c9aL, 0x670c9c61L, 0xabd388f0L,
0x6a51a0d2L, 0xd8542f68L, 0x960fa728L, 0xab5133a3L,
0x6eef0b6cL, 0x137a3be4L, 0xba3bf050L, 0x7efb2a98L,
0xa1f1651dL, 0x39af0176L, 0x66ca593eL, 0x82430e88L,
0x8cee8619L, 0x456f9fb4L, 0x7d84a5c3L, 0x3b8b5ebeL,
0xe06f75d8L, 0x85c12073L, 0x401a449fL, 0x56c16aa6L,
0x4ed3aa62L, 0x363f7706L, 0x1bfedf72L, 0x429b023dL,
0x37d0d724L, 0xd00a1248L, 0xdb0fead3L, 0x49f1c09bL,
0x075372c9L, 0x80991b7bL, 0x25d479d8L, 0xf6e8def7L,
0xe3fe501aL, 0xb6794c3bL, 0x976ce0bdL, 0x04c006baL,
0xc1a94fb6L, 0x409f60c4L, 0x5e5c9ec2L, 0x196a2463L,
0x68fb6fafL, 0x3e6c53b5L, 0x1339b2ebL, 0x3b52ec6fL,
0x6dfc511fL, 0x9b30952cL, 0xcc814544L, 0xaf5ebd09L,
0xbee3d004L, 0xde334afdL, 0x660f2807L, 0x192e4bb3L,
0xc0cba857L, 0x45c8740fL, 0xd20b5f39L, 0xb9d3fbdbL,
0x5579c0bdL, 0x1a60320aL, 0xd6a100c6L, 0x402c7279L,
0x679f25feL, 0xfb1fa3ccL, 0x8ea5e9f8L, 0xdb3222f8L,
0x3c7516dfL, 0xfd616b15L, 0x2f501ec8L, 0xad0552abL,
0x323db5faL, 0xfd238760L, 0x53317b48L, 0x3e00df82L,
0x9e5c57bbL, 0xca6f8ca0L, 0x1a87562eL, 0xdf1769dbL,
0xd542a8f6L, 0x287effc3L, 0xac6732c6L, 0x8c4f5573L,
0x695b27b0L, 0xbbca58c8L, 0xe1ffa35dL, 0xb8f011a0L,
0x10fa3d98L, 0xfd2183b8L, 0x4afcb56cL, 0x2dd1d35bL,
0x9a53e479L, 0xb6f84565L, 0xd28e49bcL, 0x4bfb9790L,
0xe1ddf2daL, 0xa4cb7e33L, 0x62fb1341L, 0xcee4c6e8L,
0xef20cadaL, 0x36774c01L, 0xd07e9efeL, 0x2bf11fb4L,
0x95dbda4dL, 0xae909198L, 0xeaad8e71L, 0x6b93d5a0L,
0xd08ed1d0L, 0xafc725e0L, 0x8e3c5b2fL, 0x8e7594b7L,
0x8ff6e2fbL, 0xf2122b64L, 0x8888b812L, 0x900df01cL,
0x4fad5ea0L, 0x688fc31cL, 0xd1cff191L, 0xb3a8c1adL,
0x2f2f2218L, 0xbe0e1777L, 0xea752dfeL, 0x8b021fa1L,
0xe5a0cc0fL, 0xb56f74e8L, 0x18acf3d6L, 0xce89e299L,
0xb4a84fe0L, 0xfd13e0b7L, 0x7cc43b81L, 0xd2ada8d9L,
0x165fa266L, 0x80957705L, 0x93cc7314L, 0x211a1477L,
0xe6ad2065L, 0x77b5fa86L, 0xc75442f5L, 0xfb9d35cfL,
0xebcdaf0cL, 0x7b3e89a0L, 0xd6411bd3L, 0xae1e7e49L,
0x00250e2dL, 0x2071b35eL, 0x226800bbL, 0x57b8e0afL,
0x2464369bL, 0xf009b91eL, 0x5563911dL, 0x59dfa6aaL,
0x78c14389L, 0xd95a537fL, 0x207d5ba2L, 0x02e5b9c5L,
0x83260376L, 0x6295cfa9L, 0x11c81968L, 0x4e734a41L,
0xb3472dcaL, 0x7b14a94aL, 0x1b510052L, 0x9a532915L,
0xd60f573fL, 0xbc9bc6e4L, 0x2b60a476L, 0x81e67400L,
0x08ba6fb5L, 0x571be91fL, 0xf296ec6bL, 0x2a0dd915L,
0xb6636521L, 0xe7b9f9b6L, 0xff34052eL, 0xc5855664L,
0x53b02d5dL, 0xa99f8fa1L, 0x08ba4799L, 0x6e85076aL,
0x4b7a70e9L, 0xb5b32944L, 0xdb75092eL, 0xc4192623L,
0xad6ea6b0L, 0x49a7df7dL, 0x9cee60b8L, 0x8fedb266L,
0xecaa8c71L, 0x699a17ffL, 0x5664526cL, 0xc2b19ee1L,
0x193602a5L, 0x75094c29L, 0xa0591340L, 0xe4183a3eL,
0x3f54989aL, 0x5b429d65L, 0x6b8fe4d6L, 0x99f73fd6L,
0xa1d29c07L, 0xefe830f5L, 0x4d2d38e6L, 0xf0255dc1L,
0x4cdd2086L, 0x8470eb26L, 0x6382e9c6L, 0x021ecc5eL,
0x09686b3fL, 0x3ebaefc9L, 0x3c971814L, 0x6b6a70a1L,
0x687f3584L, 0x52a0e286L, 0xb79c5305L, 0xaa500737L,
0x3e07841cL, 0x7fdeae5cL, 0x8e7d44ecL, 0x5716f2b8L,
0xb03ada37L, 0xf0500c0dL, 0xf01c1f04L, 0x0200b3ffL,
0xae0cf51aL, 0x3cb574b2L, 0x25837a58L, 0xdc0921bdL,
0xd19113f9L, 0x7ca92ff6L, 0x94324773L, 0x22f54701L,
0x3ae5e581L, 0x37c2dadcL, 0xc8b57634L, 0x9af3dda7L,
0xa9446146L, 0x0fd0030eL, 0xecc8c73eL, 0xa4751e41L,
0xe238cd99L, 0x3bea0e2fL, 0x3280bba1L, 0x183eb331L,
0x4e548b38L, 0x4f6db908L, 0x6f420d03L, 0xf60a04bfL,
0x2cb81290L, 0x24977c79L, 0x5679b072L, 0xbcaf89afL,
0xde9a771fL, 0xd9930810L, 0xb38bae12L, 0xdccf3f2eL,
0x5512721fL, 0x2e6b7124L, 0x501adde6L, 0x9f84cd87L,
0x7a584718L, 0x7408da17L, 0xbc9f9abcL, 0xe94b7d8cL,
0xec7aec3aL, 0xdb851dfaL, 0x63094366L, 0xc464c3d2L,
0xef1c1847L, 0x3215d908L, 0xdd433b37L, 0x24c2ba16L,
0x12a14d43L, 0x2a65c451L, 0x50940002L, 0x133ae4ddL,
0x71dff89eL, 0x10314e55L, 0x81ac77d6L, 0x5f11199bL,
0x043556f1L, 0xd7a3c76bL, 0x3c11183bL, 0x5924a509L,
0xf28fe6edL, 0x97f1fbfaL, 0x9ebabf2cL, 0x1e153c6eL,
0x86e34570L, 0xeae96fb1L, 0x860e5e0aL, 0x5a3e2ab3L,
0x771fe71cL, 0x4e3d06faL, 0x2965dcb9L, 0x99e71d0fL,
0x803e89d6L, 0x5266c825L, 0x2e4cc978L, 0x9c10b36aL,
0xc6150ebaL, 0x94e2ea78L, 0xa5fc3c53L, 0x1e0a2df4L,
0xf2f74ea7L, 0x361d2b3dL, 0x1939260fL, 0x19c27960L,
0x5223a708L, 0xf71312b6L, 0xebadfe6eL, 0xeac31f66L,
0xe3bc4595L, 0xa67bc883L, 0xb17f37d1L, 0x018cff28L,
0xc332ddefL, 0xbe6c5aa5L, 0x65582185L, 0x68ab9802L,
0xeecea50fL, 0xdb2f953bL, 0x2aef7dadL, 0x5b6e2f84L,
0x1521b628L, 0x29076170L, 0xecdd4775L, 0x619f1510L,
0x13cca830L, 0xeb61bd96L, 0x0334fe1eL, 0xaa0363cfL,
0xb5735c90L, 0x4c70a239L, 0xd59e9e0bL, 0xcbaade14L,
0xeecc86bcL, 0x60622ca7L, 0x9cab5cabL, 0xb2f3846eL,
0x648b1eafL, 0x19bdf0caL, 0xa02369b9L, 0x655abb50L,
0x40685a32L, 0x3c2ab4b3L, 0x319ee9d5L, 0xc021b8f7L,
0x9b540b19L, 0x875fa099L, 0x95f7997eL, 0x623d7da8L,
0xf837889aL, 0x97e32d77L, 0x11ed935fL, 0x16681281L,
0x0e358829L, 0xc7e61fd6L, 0x96dedfa1L, 0x7858ba99L,
0x57f584a5L, 0x1b227263L, 0x9b83c3ffL, 0x1ac24696L,
0xcdb30aebL, 0x532e3054L, 0x8fd948e4L, 0x6dbc3128L,
0x58ebf2efL, 0x34c6ffeaL, 0xfe28ed61L, 0xee7c3c73L,
0x5d4a14d9L, 0xe864b7e3L, 0x42105d14L, 0x203e13e0L,
0x45eee2b6L, 0xa3aaabeaL, 0xdb6c4f15L, 0xfacb4fd0L,
0xc742f442L, 0xef6abbb5L, 0x654f3b1dL, 0x41cd2105L,
0xd81e799eL, 0x86854dc7L, 0xe44b476aL, 0x3d816250L,
0xcf62a1f2L, 0x5b8d2646L, 0xfc8883a0L, 0xc1c7b6a3L,
0x7f1524c3L, 0x69cb7492L, 0x47848a0bL, 0x5692b285L,
0x095bbf00L, 0xad19489dL, 0x1462b174L, 0x23820e00L,
0x58428d2aL, 0x0c55f5eaL, 0x1dadf43eL, 0x233f7061L,
0x3372f092L, 0x8d937e41L, 0xd65fecf1L, 0x6c223bdbL,
0x7cde3759L, 0xcbee7460L, 0x4085f2a7L, 0xce77326eL,
0xa6078084L, 0x19f8509eL, 0xe8efd855L, 0x61d99735L,
0xa969a7aaL, 0xc50c06c2L, 0x5a04abfcL, 0x800bcadcL,
0x9e447a2eL, 0xc3453484L, 0xfdd56705L, 0x0e1e9ec9L,
0xdb73dbd3L, 0x105588cdL, 0x675fda79L, 0xe3674340L,
0xc5c43465L, 0x713e38d8L, 0x3d28f89eL, 0xf16dff20L,
0x153e21e7L, 0x8fb03d4aL, 0xe6e39f2bL, 0xdb83adf7L,
0xe93d5a68L, 0x948140f7L, 0xf64c261cL, 0x94692934L,
0x411520f7L, 0x7602d4f7L, 0xbcf46b2eL, 0xd4a20068L,
0xd4082471L, 0x3320f46aL, 0x43b7d4b7L, 0x500061afL,
0x1e39f62eL, 0x97244546L, 0x14214f74L, 0xbf8b8840L,
0x4d95fc1dL, 0x96b591afL, 0x70f4ddd3L, 0x66a02f45L,
0xbfbc09ecL, 0x03bd9785L, 0x7fac6dd0L, 0x31cb8504L,
0x96eb27b3L, 0x55fd3941L, 0xda2547e6L, 0xabca0a9aL,
0x28507825L, 0x530429f4L, 0x0a2c86daL, 0xe9b66dfbL,
0x68dc1462L, 0xd7486900L, 0x680ec0a4L, 0x27a18deeL,
0x4f3ffea2L, 0xe887ad8cL, 0xb58ce006L, 0x7af4d6b6L,
0xaace1e7cL, 0xd3375fecL, 0xce78a399L, 0x406b2a42L,
0x20fe9e35L, 0xd9f385b9L, 0xee39d7abL, 0x3b124e8bL,
0x1dc9faf7L, 0x4b6d1856L, 0x26a36631L, 0xeae397b2L,
0x3a6efa74L, 0xdd5b4332L, 0x6841e7f7L, 0xca7820fbL,
0xfb0af54eL, 0xd8feb397L, 0x454056acL, 0xba489527L,
0x55533a3aL, 0x20838d87L, 0xfe6ba9b7L, 0xd096954bL,
0x55a867bcL, 0xa1159a58L, 0xcca92963L, 0x99e1db33L,
0xa62a4a56L, 0x3f3125f9L, 0x5ef47e1cL, 0x9029317cL,
0xfdf8e802L, 0x04272f70L, 0x80bb155cL, 0x05282ce3L,
0x95c11548L, 0xe4c66d22L, 0x48c1133fL, 0xc70f86dcL,
0x07f9c9eeL, 0x41041f0fL, 0x404779a4L, 0x5d886e17L,
0x325f51ebL, 0xd59bc0d1L, 0xf2bcc18fL, 0x41113564L,
0x257b7834L, 0x602a9c60L, 0xdff8e8a3L, 0x1f636c1bL,
0x0e12b4c2L, 0x02e1329eL, 0xaf664fd1L, 0xcad18115L,
0x6b2395e0L, 0x333e92e1L, 0x3b240b62L, 0xeebeb922L,
0x85b2a20eL, 0xe6ba0d99L, 0xde720c8cL, 0x2da2f728L,
0xd0127845L, 0x95b794fdL, 0x647d0862L, 0xe7ccf5f0L,
0x5449a36fL, 0x877d48faL, 0xc39dfd27L, 0xf33e8d1eL,
0x0a476341L, 0x992eff74L, 0x3a6f6eabL, 0xf4f8fd37L,
0xa812dc60L, 0xa1ebddf8L, 0x991be14cL, 0xdb6e6b0dL,
0xc67b5510L, 0x6d672c37L, 0x2765d43bL, 0xdcd0e804L,
0xf1290dc7L, 0xcc00ffa3L, 0xb5390f92L, 0x690fed0bL,
0x667b9ffbL, 0xcedb7d9cL, 0xa091cf0bL, 0xd9155ea3L,
0xbb132f88L, 0x515bad24L, 0x7b9479bfL, 0x763bd6ebL,
0x37392eb3L, 0xcc115979L, 0x8026e297L, 0xf42e312dL,
0x6842ada7L, 0xc66a2b3bL, 0x12754cccL, 0x782ef11cL,
0x6a124237L, 0xb79251e7L, 0x06a1bbe6L, 0x4bfb6350L,
0x1a6b1018L, 0x11caedfaL, 0x3d25bdd8L, 0xe2e1c3c9L,
0x44421659L, 0x0a121386L, 0xd90cec6eL, 0xd5abea2aL,
0x64af674eL, 0xda86a85fL, 0xbebfe988L, 0x64e4c3feL,
0x9dbc8057L, 0xf0f7c086L, 0x60787bf8L, 0x6003604dL,
0xd1fd8346L, 0xf6381fb0L, 0x7745ae04L, 0xd736fcccL,
0x83426b33L, 0xf01eab71L, 0xb0804187L, 0x3c005e5fL,
0x77a057beL, 0xbde8ae24L, 0x55464299L, 0xbf582e61L,
0x4e58f48fL, 0xf2ddfda2L, 0xf474ef38L, 0x8789bdc2L,
0x5366f9c3L, 0xc8b38e74L, 0xb475f255L, 0x46fcd9b9L,
0x7aeb2661L, 0x8b1ddf84L, 0x846a0e79L, 0x915f95e2L,
0x466e598eL, 0x20b45770L, 0x8cd55591L, 0xc902de4cL,
0xb90bace1L, 0xbb8205d0L, 0x11a86248L, 0x7574a99eL,
0xb77f19b6L, 0xe0a9dc09L, 0x662d09a1L, 0xc4324633L,
0xe85a1f02L, 0x09f0be8cL, 0x4a99a025L, 0x1d6efe10L,
0x1ab93d1dL, 0x0ba5a4dfL, 0xa186f20fL, 0x2868f169L,
0xdcb7da83L, 0x573906feL, 0xa1e2ce9bL, 0x4fcd7f52L,
0x50115e01L, 0xa70683faL, 0xa002b5c4L, 0x0de6d027L,
0x9af88c27L, 0x773f8641L, 0xc3604c06L, 0x61a806b5L,
0xf0177a28L, 0xc0f586e0L, 0x006058aaL, 0x30dc7d62L,
0x11e69ed7L, 0x2338ea63L, 0x53c2dd94L, 0xc2c21634L,
0xbbcbee56L, 0x90bcb6deL, 0xebfc7da1L, 0xce591d76L,
0x6f05e409L, 0x4b7c0188L, 0x39720a3dL, 0x7c927c24L,
0x86e3725fL, 0x724d9db9L, 0x1ac15bb4L, 0xd39eb8fcL,
0xed545578L, 0x08fca5b5L, 0xd83d7cd3L, 0x4dad0fc4L,
0x1e50ef5eL, 0xb161e6f8L, 0xa28514d9L, 0x6c51133cL,
0x6fd5c7e7L, 0x56e14ec4L, 0x362abfceL, 0xddc6c837L,
0xd79a3234L, 0x92638212L, 0x670efa8eL, 0x406000e0L,
0x3a39ce37L, 0xd3faf5cfL, 0xabc27737L, 0x5ac52d1bL,
0x5cb0679eL, 0x4fa33742L, 0xd3822740L, 0x99bc9bbeL,
0xd5118e9dL, 0xbf0f7315L, 0xd62d1c7eL, 0xc700c47bL,
0xb78c1b6bL, 0x21a19045L, 0xb26eb1beL, 0x6a366eb4L,
0x5748ab2fL, 0xbc946e79L, 0xc6a376d2L, 0x6549c2c8L,
0x530ff8eeL, 0x468dde7dL, 0xd5730a1dL, 0x4cd04dc6L,
0x2939bbdbL, 0xa9ba4650L, 0xac9526e8L, 0xbe5ee304L,
0xa1fad5f0L, 0x6a2d519aL, 0x63ef8ce2L, 0x9a86ee22L,
0xc089c2b8L, 0x43242ef6L, 0xa51e03aaL, 0x9cf2d0a4L,
0x83c061baL, 0x9be96a4dL, 0x8fe51550L, 0xba645bd6L,
0x2826a2f9L, 0xa73a3ae1L, 0x4ba99586L, 0xef5562e9L,
0xc72fefd3L, 0xf752f7daL, 0x3f046f69L, 0x77fa0a59L,
0x80e4a915L, 0x87b08601L, 0x9b09e6adL, 0x3b3ee593L,
0xe990fd5aL, 0x9e34d797L, 0x2cf0b7d9L, 0x022b8b51L,
0x96d5ac3aL, 0x017da67dL, 0xd1cf3ed6L, 0x7c7d2d28L,
0x1f9f25cfL, 0xadf2b89bL, 0x5ad6b472L, 0x5a88f54cL,
0xe029ac71L, 0xe019a5e6L, 0x47b0acfdL, 0xed93fa9bL,
0xe8d3c48dL, 0x283b57ccL, 0xf8d56629L, 0x79132e28L,
0x785f0191L, 0xed756055L, 0xf7960e44L, 0xe3d35e8cL,
0x15056dd4L, 0x88f46dbaL, 0x03a16125L, 0x0564f0bdL,
0xc3eb9e15L, 0x3c9057a2L, 0x97271aecL, 0xa93a072aL,
0x1b3f6d9bL, 0x1e6321f5L, 0xf59c66fbL, 0x26dcf319L,
0x7533d928L, 0xb155fdf5L, 0x03563482L, 0x8aba3cbbL,
0x28517711L, 0xc20ad9f8L, 0xabcc5167L, 0xccad925fL,
0x4de81751L, 0x3830dc8eL, 0x379d5862L, 0x9320f991L,
0xea7a90c2L, 0xfb3e7bceL, 0x5121ce64L, 0x774fbe32L,
0xa8b6e37eL, 0xc3293d46L, 0x48de5369L, 0x6413e680L,
0xa2ae0810L, 0xdd6db224L, 0x69852dfdL, 0x09072166L,
0xb39a460aL, 0x6445c0ddL, 0x586cdecfL, 0x1c20c8aeL,
0x5bbef7ddL, 0x1b588d40L, 0xccd2017fL, 0x6bb4e3bbL,
0xdda26a7eL, 0x3a59ff45L, 0x3e350a44L, 0xbcb4cdd5L,
0x72eacea8L, 0xfa6484bbL, 0x8d6612aeL, 0xbf3c6f47L,
0xd29be463L, 0x542f5d9eL, 0xaec2771bL, 0xf64e6370L,
0x740e0d8dL, 0xe75b1357L, 0xf8721671L, 0xaf537d5dL,
0x4040cb08L, 0x4eb4e2ccL, 0x34d2466aL, 0x0115af84L,
0xe1b00428L, 0x95983a1dL, 0x06b89fb4L, 0xce6ea048L,
0x6f3f3b82L, 0x3520ab82L, 0x011a1d4bL, 0x277227f8L,
0x611560b1L, 0xe7933fdcL, 0xbb3a792bL, 0x344525bdL,
0xa08839e1L, 0x51ce794bL, 0x2f32c9b7L, 0xa01fbac9L,
0xe01cc87eL, 0xbcc7d1f6L, 0xcf0111c3L, 0xa1e8aac7L,
0x1a908749L, 0xd44fbd9aL, 0xd0dadecbL, 0xd50ada38L,
0x0339c32aL, 0xc6913667L, 0x8df9317cL, 0xe0b12b4fL,
0xf79e59b7L, 0x43f5bb3aL, 0xf2d519ffL, 0x27d9459cL,
0xbf97222cL, 0x15e6fc2aL, 0x0f91fc71L, 0x9b941525L,
0xfae59361L, 0xceb69cebL, 0xc2a86459L, 0x12baa8d1L,
0xb6c1075eL, 0xe3056a0cL, 0x10d25065L, 0xcb03a442L,
0xe0ec6e0eL, 0x1698db3bL, 0x4c98a0beL, 0x3278e964L,
0x9f1f9532L, 0xe0d392dfL, 0xd3a0342bL, 0x8971f21eL,
0x1b0a7441L, 0x4ba3348cL, 0xc5be7120L, 0xc37632d8L,
0xdf359f8dL, 0x9b992f2eL, 0xe60b6f47L, 0x0fe3f11dL,
0xe54cda54L, 0x1edad891L, 0xce6279cfL, 0xcd3e7e6fL,
0x1618b166L, 0xfd2c1d05L, 0x848fd2c5L, 0xf6fb2299L,
0xf523f357L, 0xa6327623L, 0x93a83531L, 0x56cccd02L,
0xacf08162L, 0x5a75ebb5L, 0x6e163697L, 0x88d273ccL,
0xde966292L, 0x81b949d0L, 0x4c50901bL, 0x71c65614L,
0xe6c6c7bdL, 0x327a140aL, 0x45e1d006L, 0xc3f27b9aL,
0xc9aa53fdL, 0x62a80f00L, 0xbb25bfe2L, 0x35bdd2f6L,
0x71126905L, 0xb2040222L, 0xb6cbcf7cL, 0xcd769c2bL,
0x53113ec0L, 0x1640e3d3L, 0x38abbd60L, 0x2547adf0L,
0xba38209cL, 0xf746ce76L, 0x77afa1c5L, 0x20756060L,
0x85cbfe4eL, 0x8ae88dd8L, 0x7aaaf9b0L, 0x4cf9aa7eL,
0x1948c25cL, 0x02fb8a8cL, 0x01c36ae4L, 0xd6ebe1f9L,
0x90d4f869L, 0xa65cdea0L, 0x3f09252dL, 0xc208e69fL,
0xb74e6132L, 0xce77e25bL, 0x578fdfe3L, 0x3ac372e6L,
};

59
libsec/decodepem.c Normal file
View File

@ -0,0 +1,59 @@
#include <u.h>
#include <libc.h>
#include <mp.h>
#include <libsec.h>
#define STRLEN(s) (sizeof(s)-1)
uchar*
decodepem(char *s, char *type, int *len)
{
uchar *d;
char *t, *e, *tt;
int n;
/*
* find the correct section of the file, stripping garbage at the beginning and end.
* the data is delimited by -----BEGIN <type>-----\n and -----END <type>-----\n
*/
n = strlen(type);
e = strchr(s, '\0');
for(t = s; t != nil && t < e; ){
tt = t;
t = strchr(tt, '\n');
if(t != nil)
t++;
if(strncmp(tt, "-----BEGIN ", STRLEN("-----BEGIN ")) == 0
&& strncmp(&tt[STRLEN("-----BEGIN ")], type, n) == 0
&& strncmp(&tt[STRLEN("-----BEGIN ")+n], "-----\n", STRLEN("-----\n")) == 0)
break;
}
for(tt = t; tt != nil && tt < e; tt++){
if(strncmp(tt, "-----END ", STRLEN("-----END ")) == 0
&& strncmp(&tt[STRLEN("-----END ")], type, n) == 0
&& strncmp(&tt[STRLEN("-----END ")+n], "-----\n", STRLEN("-----\n")) == 0)
break;
tt = strchr(tt, '\n');
if(tt == nil)
break;
}
if(tt == nil || tt == e){
werrstr("incorrect .pem file format: bad header or trailer");
return nil;
}
n = ((tt - t) * 6 + 7) / 8;
d = malloc(n);
if(d == nil){
werrstr("out of memory");
return nil;
}
n = dec64(d, n, t, tt - t);
if(n < 0){
free(d);
werrstr("incorrect .pem file format: bad base64 encoded data");
return nil;
}
*len = n;
return d;
}

480
libsec/des.c Normal file
View File

@ -0,0 +1,480 @@
#include "os.h"
#include <libsec.h>
/*
* integrated sbox & p perm
*/
static u32int spbox[] = {
0x00808200,0x00000000,0x00008000,0x00808202,0x00808002,0x00008202,0x00000002,0x00008000,
0x00000200,0x00808200,0x00808202,0x00000200,0x00800202,0x00808002,0x00800000,0x00000002,
0x00000202,0x00800200,0x00800200,0x00008200,0x00008200,0x00808000,0x00808000,0x00800202,
0x00008002,0x00800002,0x00800002,0x00008002,0x00000000,0x00000202,0x00008202,0x00800000,
0x00008000,0x00808202,0x00000002,0x00808000,0x00808200,0x00800000,0x00800000,0x00000200,
0x00808002,0x00008000,0x00008200,0x00800002,0x00000200,0x00000002,0x00800202,0x00008202,
0x00808202,0x00008002,0x00808000,0x00800202,0x00800002,0x00000202,0x00008202,0x00808200,
0x00000202,0x00800200,0x00800200,0x00000000,0x00008002,0x00008200,0x00000000,0x00808002,
0x40084010,0x40004000,0x00004000,0x00084010,0x00080000,0x00000010,0x40080010,0x40004010,
0x40000010,0x40084010,0x40084000,0x40000000,0x40004000,0x00080000,0x00000010,0x40080010,
0x00084000,0x00080010,0x40004010,0x00000000,0x40000000,0x00004000,0x00084010,0x40080000,
0x00080010,0x40000010,0x00000000,0x00084000,0x00004010,0x40084000,0x40080000,0x00004010,
0x00000000,0x00084010,0x40080010,0x00080000,0x40004010,0x40080000,0x40084000,0x00004000,
0x40080000,0x40004000,0x00000010,0x40084010,0x00084010,0x00000010,0x00004000,0x40000000,
0x00004010,0x40084000,0x00080000,0x40000010,0x00080010,0x40004010,0x40000010,0x00080010,
0x00084000,0x00000000,0x40004000,0x00004010,0x40000000,0x40080010,0x40084010,0x00084000,
0x00000104,0x04010100,0x00000000,0x04010004,0x04000100,0x00000000,0x00010104,0x04000100,
0x00010004,0x04000004,0x04000004,0x00010000,0x04010104,0x00010004,0x04010000,0x00000104,
0x04000000,0x00000004,0x04010100,0x00000100,0x00010100,0x04010000,0x04010004,0x00010104,
0x04000104,0x00010100,0x00010000,0x04000104,0x00000004,0x04010104,0x00000100,0x04000000,
0x04010100,0x04000000,0x00010004,0x00000104,0x00010000,0x04010100,0x04000100,0x00000000,
0x00000100,0x00010004,0x04010104,0x04000100,0x04000004,0x00000100,0x00000000,0x04010004,
0x04000104,0x00010000,0x04000000,0x04010104,0x00000004,0x00010104,0x00010100,0x04000004,
0x04010000,0x04000104,0x00000104,0x04010000,0x00010104,0x00000004,0x04010004,0x00010100,
0x80401000,0x80001040,0x80001040,0x00000040,0x00401040,0x80400040,0x80400000,0x80001000,
0x00000000,0x00401000,0x00401000,0x80401040,0x80000040,0x00000000,0x00400040,0x80400000,
0x80000000,0x00001000,0x00400000,0x80401000,0x00000040,0x00400000,0x80001000,0x00001040,
0x80400040,0x80000000,0x00001040,0x00400040,0x00001000,0x00401040,0x80401040,0x80000040,
0x00400040,0x80400000,0x00401000,0x80401040,0x80000040,0x00000000,0x00000000,0x00401000,
0x00001040,0x00400040,0x80400040,0x80000000,0x80401000,0x80001040,0x80001040,0x00000040,
0x80401040,0x80000040,0x80000000,0x00001000,0x80400000,0x80001000,0x00401040,0x80400040,
0x80001000,0x00001040,0x00400000,0x80401000,0x00000040,0x00400000,0x00001000,0x00401040,
0x00000080,0x01040080,0x01040000,0x21000080,0x00040000,0x00000080,0x20000000,0x01040000,
0x20040080,0x00040000,0x01000080,0x20040080,0x21000080,0x21040000,0x00040080,0x20000000,
0x01000000,0x20040000,0x20040000,0x00000000,0x20000080,0x21040080,0x21040080,0x01000080,
0x21040000,0x20000080,0x00000000,0x21000000,0x01040080,0x01000000,0x21000000,0x00040080,
0x00040000,0x21000080,0x00000080,0x01000000,0x20000000,0x01040000,0x21000080,0x20040080,
0x01000080,0x20000000,0x21040000,0x01040080,0x20040080,0x00000080,0x01000000,0x21040000,
0x21040080,0x00040080,0x21000000,0x21040080,0x01040000,0x00000000,0x20040000,0x21000000,
0x00040080,0x01000080,0x20000080,0x00040000,0x00000000,0x20040000,0x01040080,0x20000080,
0x10000008,0x10200000,0x00002000,0x10202008,0x10200000,0x00000008,0x10202008,0x00200000,
0x10002000,0x00202008,0x00200000,0x10000008,0x00200008,0x10002000,0x10000000,0x00002008,
0x00000000,0x00200008,0x10002008,0x00002000,0x00202000,0x10002008,0x00000008,0x10200008,
0x10200008,0x00000000,0x00202008,0x10202000,0x00002008,0x00202000,0x10202000,0x10000000,
0x10002000,0x00000008,0x10200008,0x00202000,0x10202008,0x00200000,0x00002008,0x10000008,
0x00200000,0x10002000,0x10000000,0x00002008,0x10000008,0x10202008,0x00202000,0x10200000,
0x00202008,0x10202000,0x00000000,0x10200008,0x00000008,0x00002000,0x10200000,0x00202008,
0x00002000,0x00200008,0x10002008,0x00000000,0x10202000,0x10000000,0x00200008,0x10002008,
0x00100000,0x02100001,0x02000401,0x00000000,0x00000400,0x02000401,0x00100401,0x02100400,
0x02100401,0x00100000,0x00000000,0x02000001,0x00000001,0x02000000,0x02100001,0x00000401,
0x02000400,0x00100401,0x00100001,0x02000400,0x02000001,0x02100000,0x02100400,0x00100001,
0x02100000,0x00000400,0x00000401,0x02100401,0x00100400,0x00000001,0x02000000,0x00100400,
0x02000000,0x00100400,0x00100000,0x02000401,0x02000401,0x02100001,0x02100001,0x00000001,
0x00100001,0x02000000,0x02000400,0x00100000,0x02100400,0x00000401,0x00100401,0x02100400,
0x00000401,0x02000001,0x02100401,0x02100000,0x00100400,0x00000000,0x00000001,0x02100401,
0x00000000,0x00100401,0x02100000,0x00000400,0x02000001,0x02000400,0x00000400,0x00100001,
0x08000820,0x00000800,0x00020000,0x08020820,0x08000000,0x08000820,0x00000020,0x08000000,
0x00020020,0x08020000,0x08020820,0x00020800,0x08020800,0x00020820,0x00000800,0x00000020,
0x08020000,0x08000020,0x08000800,0x00000820,0x00020800,0x00020020,0x08020020,0x08020800,
0x00000820,0x00000000,0x00000000,0x08020020,0x08000020,0x08000800,0x00020820,0x00020000,
0x00020820,0x00020000,0x08020800,0x00000800,0x00000020,0x08020020,0x00000800,0x00020820,
0x08000800,0x00000020,0x08000020,0x08020000,0x08020020,0x08000000,0x00020000,0x08000820,
0x00000000,0x08020820,0x00020020,0x08000020,0x08020000,0x08000800,0x08000820,0x00000000,
0x08020820,0x00020800,0x00020800,0x00000820,0x00000820,0x00020020,0x08000000,0x08020800,
};
/*
* for manual index calculation
* #define fetch(box, i, sh) (*((u32int*)((uchar*)spbox + (box << 8) + ((i >> (sh)) & 0xfc))))
*/
#define fetch(box, i, sh) ((spbox+(box << 6))[((i >> (sh + 2)) & 0x3f)])
/*
* DES electronic codebook encryption of one block
*/
void
block_cipher(ulong key[32], uchar text[8], int decrypting)
{
u32int right, left, v0, v1;
int i, keystep;
/*
* initial permutation
*/
v0 = text[0] | ((u32int)text[2]<<8) | ((u32int)text[4]<<16) | ((u32int)text[6]<<24);
left = text[1] | ((u32int)text[3]<<8) | ((u32int)text[5]<<16) | ((u32int)text[7]<<24);
right = (left & 0xaaaaaaaa) | ((v0 >> 1) & 0x55555555);
left = ((left << 1) & 0xaaaaaaaa) | (v0 & 0x55555555);
left = ((left << 6) & 0x33003300)
| (left & 0xcc33cc33)
| ((left >> 6) & 0x00cc00cc);
left = ((left << 12) & 0x0f0f0000)
| (left & 0xf0f00f0f)
| ((left >> 12) & 0x0000f0f0);
right = ((right << 6) & 0x33003300)
| (right & 0xcc33cc33)
| ((right >> 6) & 0x00cc00cc);
right = ((right << 12) & 0x0f0f0000)
| (right & 0xf0f00f0f)
| ((right >> 12) & 0x0000f0f0);
if (decrypting) {
keystep = -2;
key = key + 32 - 2;
} else
keystep = 2;
for (i = 0; i < 8; i++) {
v0 = key[0];
v0 ^= (right >> 1) | (right << 31);
left ^= fetch(0, v0, 24)
^ fetch(2, v0, 16)
^ fetch(4, v0, 8)
^ fetch(6, v0, 0);
v1 = key[1];
v1 ^= (right << 3) | (right >> 29);
left ^= fetch(1, v1, 24)
^ fetch(3, v1, 16)
^ fetch(5, v1, 8)
^ fetch(7, v1, 0);
key += keystep;
v0 = key[0];
v0 ^= (left >> 1) | (left << 31);
right ^= fetch(0, v0, 24)
^ fetch(2, v0, 16)
^ fetch(4, v0, 8)
^ fetch(6, v0, 0);
v1 = key[1];
v1 ^= (left << 3) | (left >> 29);
right ^= fetch(1, v1, 24)
^ fetch(3, v1, 16)
^ fetch(5, v1, 8)
^ fetch(7, v1, 0);
key += keystep;
}
/*
* final permutation, inverse initial permutation
*/
v0 = ((left << 1) & 0xaaaaaaaa) | (right & 0x55555555);
v1 = (left & 0xaaaaaaaa) | ((right >> 1) & 0x55555555);
v1 = ((v1 << 6) & 0x33003300)
| (v1 & 0xcc33cc33)
| ((v1 >> 6) & 0x00cc00cc);
v1 = ((v1 << 12) & 0x0f0f0000)
| (v1 & 0xf0f00f0f)
| ((v1 >> 12) & 0x0000f0f0);
v0 = ((v0 << 6) & 0x33003300)
| (v0 & 0xcc33cc33)
| ((v0 >> 6) & 0x00cc00cc);
v0 = ((v0 << 12) & 0x0f0f0000)
| (v0 & 0xf0f00f0f)
| ((v0 >> 12) & 0x0000f0f0);
text[0] = v0;
text[2] = v0 >> 8;
text[4] = v0 >> 16;
text[6] = v0 >> 24;
text[1] = v1;
text[3] = v1 >> 8;
text[5] = v1 >> 16;
text[7] = v1 >> 24;
}
/*
* triple DES electronic codebook encryption of one block
*/
void
triple_block_cipher(ulong expanded_key[3][32], uchar text[8], int ende)
{
ulong *key;
u32int right, left, v0, v1;
int i, j, keystep;
/*
* initial permutation
*/
v0 = text[0] | ((u32int)text[2]<<8) | ((u32int)text[4]<<16) | ((u32int)text[6]<<24);
left = text[1] | ((u32int)text[3]<<8) | ((u32int)text[5]<<16) | ((u32int)text[7]<<24);
right = (left & 0xaaaaaaaa) | ((v0 >> 1) & 0x55555555);
left = ((left << 1) & 0xaaaaaaaa) | (v0 & 0x55555555);
left = ((left << 6) & 0x33003300)
| (left & 0xcc33cc33)
| ((left >> 6) & 0x00cc00cc);
left = ((left << 12) & 0x0f0f0000)
| (left & 0xf0f00f0f)
| ((left >> 12) & 0x0000f0f0);
right = ((right << 6) & 0x33003300)
| (right & 0xcc33cc33)
| ((right >> 6) & 0x00cc00cc);
right = ((right << 12) & 0x0f0f0000)
| (right & 0xf0f00f0f)
| ((right >> 12) & 0x0000f0f0);
for(j = 0; j < 3; j++){
if((ende & 1) == DES3D) {
key = &expanded_key[2-j][32-2];
keystep = -2;
} else {
key = &expanded_key[j][0];
keystep = 2;
}
ende >>= 1;
for (i = 0; i < 8; i++) {
v0 = key[0];
v0 ^= (right >> 1) | (right << 31);
left ^= fetch(0, v0, 24)
^ fetch(2, v0, 16)
^ fetch(4, v0, 8)
^ fetch(6, v0, 0);
v1 = key[1];
v1 ^= (right << 3) | (right >> 29);
left ^= fetch(1, v1, 24)
^ fetch(3, v1, 16)
^ fetch(5, v1, 8)
^ fetch(7, v1, 0);
key += keystep;
v0 = key[0];
v0 ^= (left >> 1) | (left << 31);
right ^= fetch(0, v0, 24)
^ fetch(2, v0, 16)
^ fetch(4, v0, 8)
^ fetch(6, v0, 0);
v1 = key[1];
v1 ^= (left << 3) | (left >> 29);
right ^= fetch(1, v1, 24)
^ fetch(3, v1, 16)
^ fetch(5, v1, 8)
^ fetch(7, v1, 0);
key += keystep;
}
v0 = left;
left = right;
right = v0;
}
/*
* final permutation, inverse initial permutation
* left and right are swapped here
*/
v0 = ((right << 1) & 0xaaaaaaaa) | (left & 0x55555555);
v1 = (right & 0xaaaaaaaa) | ((left >> 1) & 0x55555555);
v1 = ((v1 << 6) & 0x33003300)
| (v1 & 0xcc33cc33)
| ((v1 >> 6) & 0x00cc00cc);
v1 = ((v1 << 12) & 0x0f0f0000)
| (v1 & 0xf0f00f0f)
| ((v1 >> 12) & 0x0000f0f0);
v0 = ((v0 << 6) & 0x33003300)
| (v0 & 0xcc33cc33)
| ((v0 >> 6) & 0x00cc00cc);
v0 = ((v0 << 12) & 0x0f0f0000)
| (v0 & 0xf0f00f0f)
| ((v0 >> 12) & 0x0000f0f0);
text[0] = v0;
text[2] = v0 >> 8;
text[4] = v0 >> 16;
text[6] = v0 >> 24;
text[1] = v1;
text[3] = v1 >> 8;
text[5] = v1 >> 16;
text[7] = v1 >> 24;
}
/*
* key compression permutation, 4 bits at a time
*/
static u32int comptab[] = {
0x000000,0x010000,0x000008,0x010008,0x000080,0x010080,0x000088,0x010088,
0x000000,0x010000,0x000008,0x010008,0x000080,0x010080,0x000088,0x010088,
0x000000,0x100000,0x000800,0x100800,0x000000,0x100000,0x000800,0x100800,
0x002000,0x102000,0x002800,0x102800,0x002000,0x102000,0x002800,0x102800,
0x000000,0x000004,0x000400,0x000404,0x000000,0x000004,0x000400,0x000404,
0x400000,0x400004,0x400400,0x400404,0x400000,0x400004,0x400400,0x400404,
0x000000,0x000020,0x008000,0x008020,0x800000,0x800020,0x808000,0x808020,
0x000002,0x000022,0x008002,0x008022,0x800002,0x800022,0x808002,0x808022,
0x000000,0x000200,0x200000,0x200200,0x001000,0x001200,0x201000,0x201200,
0x000000,0x000200,0x200000,0x200200,0x001000,0x001200,0x201000,0x201200,
0x000000,0x000040,0x000010,0x000050,0x004000,0x004040,0x004010,0x004050,
0x040000,0x040040,0x040010,0x040050,0x044000,0x044040,0x044010,0x044050,
0x000000,0x000100,0x020000,0x020100,0x000001,0x000101,0x020001,0x020101,
0x080000,0x080100,0x0a0000,0x0a0100,0x080001,0x080101,0x0a0001,0x0a0101,
0x000000,0x000100,0x040000,0x040100,0x000000,0x000100,0x040000,0x040100,
0x000040,0x000140,0x040040,0x040140,0x000040,0x000140,0x040040,0x040140,
0x000000,0x400000,0x008000,0x408000,0x000008,0x400008,0x008008,0x408008,
0x000400,0x400400,0x008400,0x408400,0x000408,0x400408,0x008408,0x408408,
0x000000,0x001000,0x080000,0x081000,0x000020,0x001020,0x080020,0x081020,
0x004000,0x005000,0x084000,0x085000,0x004020,0x005020,0x084020,0x085020,
0x000000,0x000800,0x000000,0x000800,0x000010,0x000810,0x000010,0x000810,
0x800000,0x800800,0x800000,0x800800,0x800010,0x800810,0x800010,0x800810,
0x000000,0x010000,0x000200,0x010200,0x000000,0x010000,0x000200,0x010200,
0x100000,0x110000,0x100200,0x110200,0x100000,0x110000,0x100200,0x110200,
0x000000,0x000004,0x000000,0x000004,0x000080,0x000084,0x000080,0x000084,
0x002000,0x002004,0x002000,0x002004,0x002080,0x002084,0x002080,0x002084,
0x000000,0x000001,0x200000,0x200001,0x020000,0x020001,0x220000,0x220001,
0x000002,0x000003,0x200002,0x200003,0x020002,0x020003,0x220002,0x220003,
};
static int keysh[] =
{
1, 1, 2, 2, 2, 2, 2, 2, 1, 2, 2, 2, 2, 2, 2, 1,
};
static void
keycompperm(u32int left, u32int right, ulong *ek)
{
u32int v0, v1;
int i;
for(i = 0; i < 16; i++){
left = (left << keysh[i]) | (left >> (28 - keysh[i]));
left &= 0xfffffff0;
right = (right << keysh[i]) | (right >> (28 - keysh[i]));
right &= 0xfffffff0;
v0 = comptab[6 * (1 << 4) + ((left >> (32-4)) & 0xf)]
| comptab[5 * (1 << 4) + ((left >> (32-8)) & 0xf)]
| comptab[4 * (1 << 4) + ((left >> (32-12)) & 0xf)]
| comptab[3 * (1 << 4) + ((left >> (32-16)) & 0xf)]
| comptab[2 * (1 << 4) + ((left >> (32-20)) & 0xf)]
| comptab[1 * (1 << 4) + ((left >> (32-24)) & 0xf)]
| comptab[0 * (1 << 4) + ((left >> (32-28)) & 0xf)];
v1 = comptab[13 * (1 << 4) + ((right >> (32-4)) & 0xf)]
| comptab[12 * (1 << 4) + ((right >> (32-8)) & 0xf)]
| comptab[11 * (1 << 4) + ((right >> (32-12)) & 0xf)]
| comptab[10 * (1 << 4) + ((right >> (32-16)) & 0xf)]
| comptab[9 * (1 << 4) + ((right >> (32-20)) & 0xf)]
| comptab[8 * (1 << 4) + ((right >> (32-24)) & 0xf)]
| comptab[7 * (1 << 4) + ((right >> (32-28)) & 0xf)];
ek[0] = (((v0 >> (24-6)) & 0x3f) << 26)
| (((v0 >> (24-18)) & 0x3f) << 18)
| (((v1 >> (24-6)) & 0x3f) << 10)
| (((v1 >> (24-18)) & 0x3f) << 2);
ek[1] = (((v0 >> (24-12)) & 0x3f) << 26)
| (((v0 >> (24-24)) & 0x3f) << 18)
| (((v1 >> (24-12)) & 0x3f) << 10)
| (((v1 >> (24-24)) & 0x3f) << 2);
ek += 2;
}
}
void
des_key_setup(uchar key[8], ulong *ek)
{
u32int left, right, v0, v1;
v0 = key[0] | ((u32int)key[2] << 8) | ((u32int)key[4] << 16) | ((u32int)key[6] << 24);
v1 = key[1] | ((u32int)key[3] << 8) | ((u32int)key[5] << 16) | ((u32int)key[7] << 24);
left = ((v0 >> 1) & 0x40404040)
| ((v0 >> 2) & 0x10101010)
| ((v0 >> 3) & 0x04040404)
| ((v0 >> 4) & 0x01010101)
| ((v1 >> 0) & 0x80808080)
| ((v1 >> 1) & 0x20202020)
| ((v1 >> 2) & 0x08080808)
| ((v1 >> 3) & 0x02020202);
right = ((v0 >> 1) & 0x04040404)
| ((v0 << 2) & 0x10101010)
| ((v0 << 5) & 0x40404040)
| ((v1 << 0) & 0x08080808)
| ((v1 << 3) & 0x20202020)
| ((v1 << 6) & 0x80808080);
left = ((left << 6) & 0x33003300)
| (left & 0xcc33cc33)
| ((left >> 6) & 0x00cc00cc);
v0 = ((left << 12) & 0x0f0f0000)
| (left & 0xf0f00f0f)
| ((left >> 12) & 0x0000f0f0);
right = ((right << 6) & 0x33003300)
| (right & 0xcc33cc33)
| ((right >> 6) & 0x00cc00cc);
v1 = ((right << 12) & 0x0f0f0000)
| (right & 0xf0f00f0f)
| ((right >> 12) & 0x0000f0f0);
left = v0 & 0xfffffff0;
right = (v1 & 0xffffff00) | ((v0 << 4) & 0xf0);
keycompperm(left, right, ek);
}
static uchar parity[128] =
{
0x01, 0x02, 0x04, 0x07, 0x08, 0x0b, 0x0d, 0x0e,
0x10, 0x13, 0x15, 0x16, 0x19, 0x1a, 0x1c, 0x1f,
0x20, 0x23, 0x25, 0x26, 0x29, 0x2a, 0x2c, 0x2f,
0x31, 0x32, 0x34, 0x37, 0x38, 0x3b, 0x3d, 0x3e,
0x40, 0x43, 0x45, 0x46, 0x49, 0x4a, 0x4c, 0x4f,
0x51, 0x52, 0x54, 0x57, 0x58, 0x5b, 0x5d, 0x5e,
0x61, 0x62, 0x64, 0x67, 0x68, 0x6b, 0x6d, 0x6e,
0x70, 0x73, 0x75, 0x76, 0x79, 0x7a, 0x7c, 0x7f,
0x80, 0x83, 0x85, 0x86, 0x89, 0x8a, 0x8c, 0x8f,
0x91, 0x92, 0x94, 0x97, 0x98, 0x9b, 0x9d, 0x9e,
0xa1, 0xa2, 0xa4, 0xa7, 0xa8, 0xab, 0xad, 0xae,
0xb0, 0xb3, 0xb5, 0xb6, 0xb9, 0xba, 0xbc, 0xbf,
0xc1, 0xc2, 0xc4, 0xc7, 0xc8, 0xcb, 0xcd, 0xce,
0xd0, 0xd3, 0xd5, 0xd6, 0xd9, 0xda, 0xdc, 0xdf,
0xe0, 0xe3, 0xe5, 0xe6, 0xe9, 0xea, 0xec, 0xef,
0xf1, 0xf2, 0xf4, 0xf7, 0xf8, 0xfb, 0xfd, 0xfe,
};
/*
* convert a 7 byte key to an 8 byte one
*/
void
des56to64(uchar *k56, uchar *k64)
{
u32int hi, lo;
hi = ((u32int)k56[0]<<24)|((u32int)k56[1]<<16)|((u32int)k56[2]<<8)|k56[3];
lo = ((u32int)k56[4]<<24)|((u32int)k56[5]<<16)|((u32int)k56[6]<<8);
k64[0] = parity[(hi>>25)&0x7f];
k64[1] = parity[(hi>>18)&0x7f];
k64[2] = parity[(hi>>11)&0x7f];
k64[3] = parity[(hi>>4)&0x7f];
k64[4] = parity[((hi<<3)|(lo>>29))&0x7f];
k64[5] = parity[(lo>>22)&0x7f];
k64[6] = parity[(lo>>15)&0x7f];
k64[7] = parity[(lo>>8)&0x7f];
}
/*
* convert an 8 byte key to a 7 byte one
*/
void
des64to56(uchar *k64, uchar *k56)
{
u32int hi, lo;
hi = (((u32int)k64[0]&0xfe)<<24)|(((u32int)k64[1]&0xfe)<<17)|(((u32int)k64[2]&0xfe)<<10)
|((k64[3]&0xfe)<<3)|(k64[4]>>4);
lo = (((u32int)k64[4]&0xfe)<<28)|(((u32int)k64[5]&0xfe)<<21)|(((u32int)k64[6]&0xfe)<<14)
|(((u32int)k64[7]&0xfe)<<7);
k56[0] = hi>>24;
k56[1] = hi>>16;
k56[2] = hi>>8;
k56[3] = hi>>0;
k56[4] = lo>>24;
k56[5] = lo>>16;
k56[6] = lo>>8;
}
void
key_setup(uchar key[7], ulong *ek)
{
uchar k64[8];
des56to64(key, k64);
des_key_setup(k64, ek);
}

59
libsec/des3CBC.c Normal file
View File

@ -0,0 +1,59 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// Because of the way that non multiple of 8
// buffers are handled, the decryptor must
// be fed buffers of the same size as the
// encryptor
// If the length is not a multiple of 8, I encrypt
// the overflow to be compatible with lacy's cryptlib
void
des3CBCencrypt(uchar *p, int len, DES3state *s)
{
uchar *p2, *ip, *eip;
for(; len >= 8; len -= 8){
p2 = p;
ip = s->ivec;
for(eip = ip+8; ip < eip; )
*p2++ ^= *ip++;
triple_block_cipher(s->expanded, p, DES3EDE);
memmove(s->ivec, p, 8);
p += 8;
}
if(len > 0){
ip = s->ivec;
triple_block_cipher(s->expanded, ip, DES3EDE);
for(eip = ip+len; ip < eip; )
*p++ ^= *ip++;
}
}
void
des3CBCdecrypt(uchar *p, int len, DES3state *s)
{
uchar *ip, *eip, *tp;
uchar tmp[8];
for(; len >= 8; len -= 8){
memmove(tmp, p, 8);
triple_block_cipher(s->expanded, p, DES3DED);
tp = tmp;
ip = s->ivec;
for(eip = ip+8; ip < eip; ){
*p++ ^= *ip;
*ip++ = *tp++;
}
}
if(len > 0){
ip = s->ivec;
triple_block_cipher(s->expanded, ip, DES3EDE);
for(eip = ip+len; ip < eip; )
*p++ ^= *ip++;
}
}

48
libsec/des3ECB.c Normal file
View File

@ -0,0 +1,48 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// I wasn't sure what to do when the buffer was not
// a multiple of 8. I did what lacy's cryptolib did
// to be compatible, but it looks dangerous to me
// since its encrypting plain text with the key. -- presotto
void
des3ECBencrypt(uchar *p, int len, DES3state *s)
{
int i;
uchar tmp[8];
for(; len >= 8; len -= 8){
triple_block_cipher(s->expanded, p, DES3EDE);
p += 8;
}
if(len > 0){
for (i=0; i<8; i++)
tmp[i] = i;
triple_block_cipher(s->expanded, tmp, DES3EDE);
for (i = 0; i < len; i++)
p[i] ^= tmp[i];
}
}
void
des3ECBdecrypt(uchar *p, int len, DES3state *s)
{
int i;
uchar tmp[8];
for(; len >= 8; len -= 8){
triple_block_cipher(s->expanded, p, DES3DED);
p += 8;
}
if(len > 0){
for (i=0; i<8; i++)
tmp[i] = i;
triple_block_cipher(s->expanded, tmp, DES3EDE);
for (i = 0; i < len; i++)
p[i] ^= tmp[i];
}
}

59
libsec/desCBC.c Normal file
View File

@ -0,0 +1,59 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// Because of the way that non multiple of 8
// buffers are handled, the decryptor must
// be fed buffers of the same size as the
// encryptor
// If the length is not a multiple of 8, I encrypt
// the overflow to be compatible with lacy's cryptlib
void
desCBCencrypt(uchar *p, int len, DESstate *s)
{
uchar *p2, *ip, *eip;
for(; len >= 8; len -= 8){
p2 = p;
ip = s->ivec;
for(eip = ip+8; ip < eip; )
*p2++ ^= *ip++;
block_cipher(s->expanded, p, 0);
memmove(s->ivec, p, 8);
p += 8;
}
if(len > 0){
ip = s->ivec;
block_cipher(s->expanded, ip, 0);
for(eip = ip+len; ip < eip; )
*p++ ^= *ip++;
}
}
void
desCBCdecrypt(uchar *p, int len, DESstate *s)
{
uchar *ip, *eip, *tp;
uchar tmp[8];
for(; len >= 8; len -= 8){
memmove(tmp, p, 8);
block_cipher(s->expanded, p, 1);
tp = tmp;
ip = s->ivec;
for(eip = ip+8; ip < eip; ){
*p++ ^= *ip;
*ip++ = *tp++;
}
}
if(len > 0){
ip = s->ivec;
block_cipher(s->expanded, ip, 0);
for(eip = ip+len; ip < eip; )
*p++ ^= *ip++;
}
}

48
libsec/desECB.c Normal file
View File

@ -0,0 +1,48 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// I wasn't sure what to do when the buffer was not
// a multiple of 8. I did what lacy's cryptolib did
// to be compatible, but it looks dangerous to me
// since its encrypting plain text with the key. -- presotto
void
desECBencrypt(uchar *p, int len, DESstate *s)
{
int i;
uchar tmp[8];
for(; len >= 8; len -= 8){
block_cipher(s->expanded, p, 0);
p += 8;
}
if(len > 0){
for (i=0; i<8; i++)
tmp[i] = i;
block_cipher(s->expanded, tmp, 0);
for (i = 0; i < len; i++)
p[i] ^= tmp[i];
}
}
void
desECBdecrypt(uchar *p, int len, DESstate *s)
{
int i;
uchar tmp[8];
for(; len >= 8; len -= 8){
block_cipher(s->expanded, p, 1);
p += 8;
}
if(len > 0){
for (i=0; i<8; i++)
tmp[i] = i;
block_cipher(s->expanded, tmp, 0);
for (i = 0; i < len; i++)
p[i] ^= tmp[i];
}
}

31
libsec/desmodes.c Normal file
View File

@ -0,0 +1,31 @@
#include "os.h"
#include <libsec.h>
/*
* these routines use the 64bit format for
* DES keys.
*/
void
setupDESstate(DESstate *s, uchar key[8], uchar *ivec)
{
memset(s, 0, sizeof(*s));
memmove(s->key, key, sizeof(s->key));
des_key_setup(key, s->expanded);
if(ivec)
memmove(s->ivec, ivec, 8);
s->setup = 0xdeadbeef;
}
void
setupDES3state(DES3state *s, uchar key[3][8], uchar *ivec)
{
memset(s, 0, sizeof(*s));
memmove(s->key, key, sizeof(s->key));
des_key_setup(key[0], s->expanded[0]);
des_key_setup(key[1], s->expanded[1]);
des_key_setup(key[2], s->expanded[2]);
if(ivec)
memmove(s->ivec, ivec, 8);
s->setup = 0xdeadbeef;
}

69
libsec/dsaalloc.c Normal file
View File

@ -0,0 +1,69 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
DSApub*
dsapuballoc(void)
{
DSApub *dsa;
dsa = mallocz(sizeof(*dsa), 1);
if(dsa == nil)
sysfatal("dsapuballoc");
return dsa;
}
void
dsapubfree(DSApub *dsa)
{
if(dsa == nil)
return;
mpfree(dsa->p);
mpfree(dsa->q);
mpfree(dsa->alpha);
mpfree(dsa->key);
}
DSApriv*
dsaprivalloc(void)
{
DSApriv *dsa;
dsa = mallocz(sizeof(*dsa), 1);
if(dsa == nil)
sysfatal("dsaprivalloc");
return dsa;
}
void
dsaprivfree(DSApriv *dsa)
{
if(dsa == nil)
return;
mpfree(dsa->pub.p);
mpfree(dsa->pub.q);
mpfree(dsa->pub.alpha);
mpfree(dsa->pub.key);
mpfree(dsa->secret);
}
DSAsig*
dsasigalloc(void)
{
DSAsig *dsa;
dsa = mallocz(sizeof(*dsa), 1);
if(dsa == nil)
sysfatal("dsasigalloc");
return dsa;
}
void
dsasigfree(DSAsig *dsa)
{
if(dsa == nil)
return;
mpfree(dsa->r);
mpfree(dsa->s);
}

61
libsec/dsagen.c Normal file
View File

@ -0,0 +1,61 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
DSApriv*
dsagen(DSApub *opub)
{
DSApub *pub;
DSApriv *priv;
mpint *exp;
mpint *g;
mpint *r;
int bits;
priv = dsaprivalloc();
pub = &priv->pub;
if(opub != nil){
pub->p = mpcopy(opub->p);
pub->q = mpcopy(opub->q);
} else {
pub->p = mpnew(0);
pub->q = mpnew(0);
DSAprimes(pub->q, pub->p, nil);
}
bits = Dbits*pub->p->top;
pub->alpha = mpnew(0);
pub->key = mpnew(0);
priv->secret = mpnew(0);
// find a generator alpha of the multiplicative
// group Z*p, i.e., of order n = p-1. We use the
// fact that q divides p-1 to reduce the exponent.
//
// This isn't very efficient. If anyone has a better
// idea, mail presotto@closedmind.org
exp = mpnew(0);
g = mpnew(0);
r = mpnew(0);
mpsub(pub->p, mpone, exp);
mpdiv(exp, pub->q, exp, r);
if(mpcmp(r, mpzero) != 0)
sysfatal("dsagen foul up");
while(1){
mprand(bits, genrandom, g);
mpmod(g, pub->p, g);
mpexp(g, exp, pub->p, pub->alpha);
if(mpcmp(pub->alpha, mpone) != 0)
break;
}
mpfree(g);
mpfree(exp);
// create the secret key
mprand(bits, genrandom, priv->secret);
mpmod(priv->secret, pub->p, priv->secret);
mpexp(pub->alpha, priv->secret, pub->p, pub->key);
return priv;
}

97
libsec/dsaprimes.c Normal file
View File

@ -0,0 +1,97 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// NIST algorithm for generating DSA primes
// Menezes et al (1997) Handbook of Applied Cryptography, p.151
// q is a 160-bit prime; p is a 1024-bit prime; q divides p-1
// arithmetic on unsigned ints mod 2**160, represented
// as 20-byte, little-endian uchar array
static void
Hrand(uchar *s)
{
ulong *u = (ulong*)s;
*u++ = fastrand();
*u++ = fastrand();
*u++ = fastrand();
*u++ = fastrand();
*u = fastrand();
}
static void
Hincr(uchar *s)
{
int i;
for(i=0; i<20; i++)
if(++s[i]!=0)
break;
}
// this can run for quite a while; be patient
void
DSAprimes(mpint *q, mpint *p, uchar seed[SHA1dlen])
{
int i, j, k, n = 6, b = 63;
uchar s[SHA1dlen], Hs[SHA1dlen], Hs1[SHA1dlen], sj[SHA1dlen], sjk[SHA1dlen];
mpint *two1023, *mb, *Vk, *W, *X, *q2;
two1023 = mpnew(1024);
mpleft(mpone, 1023, two1023);
mb = mpnew(0);
mpleft(mpone, b, mb);
W = mpnew(1024);
Vk = mpnew(1024);
X = mpnew(0);
q2 = mpnew(0);
forever:
do{
Hrand(s);
memcpy(sj, s, 20);
sha1(s, 20, Hs, 0);
Hincr(sj);
sha1(sj, 20, Hs1, 0);
for(i=0; i<20; i++)
Hs[i] ^= Hs1[i];
Hs[0] |= 1;
Hs[19] |= 0x80;
letomp(Hs, 20, q);
}while(!probably_prime(q, 18));
if(seed != nil) // allow skeptics to confirm computation
memmove(seed, s, SHA1dlen);
i = 0;
j = 2;
Hincr(sj);
mpleft(q, 1, q2);
while(i<4096){
memcpy(sjk, sj, 20);
for(k=0; k <= n; k++){
sha1(sjk, 20, Hs, 0);
letomp(Hs, 20, Vk);
if(k == n)
mpmod(Vk, mb, Vk);
mpleft(Vk, 160*k, Vk);
mpadd(W, Vk, W);
Hincr(sjk);
}
mpadd(W, two1023, X);
mpmod(X, q2, W);
mpsub(W, mpone, W);
mpsub(X, W, p);
if(mpcmp(p, two1023)>=0 && probably_prime(p, 5))
goto done;
i += 1;
j += n+1;
for(k=0; k<n+1; k++)
Hincr(sj);
}
goto forever;
done:
mpfree(q2);
mpfree(X);
mpfree(Vk);
mpfree(W);
mpfree(mb);
mpfree(two1023);
}

16
libsec/dsaprivtopub.c Normal file
View File

@ -0,0 +1,16 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
DSApub*
dsaprivtopub(DSApriv *priv)
{
DSApub *pub;
pub = dsapuballoc();
pub->p = mpcopy(priv->pub.p);
pub->q = mpcopy(priv->pub.q);
pub->alpha = mpcopy(priv->pub.alpha);
pub->key = mpcopy(priv->pub.key);
return pub;
}

52
libsec/dsasign.c Normal file
View File

@ -0,0 +1,52 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
DSAsig*
dsasign(DSApriv *priv, mpint *m)
{
DSApub *pub = &priv->pub;
DSAsig *sig;
mpint *qm1, *k, *kinv, *r, *s;
mpint *q = pub->q, *p = pub->p, *alpha = pub->alpha;
int qlen = mpsignif(q);
qm1 = mpnew(0);
kinv = mpnew(0);
r = mpnew(0);
s = mpnew(0);
k = mpnew(0);
mpsub(pub->q, mpone, qm1);
// find a k that has an inverse mod q
while(1){
mprand(qlen, genrandom, k);
if((mpcmp(mpone, k) > 0) || (mpcmp(k, qm1) >= 0))
continue;
mpextendedgcd(k, q, r, kinv, s);
if(mpcmp(r, mpone) != 0)
continue;
break;
}
// make kinv positive
mpmod(kinv, qm1, kinv);
// r = ((alpha**k) mod p) mod q
mpexp(alpha, k, p, r);
mpmod(r, q, r);
// s = (kinv*(m + ar)) mod q
mpmul(r, priv->secret, s);
mpadd(s, m, s);
mpmul(s, kinv, s);
mpmod(s, q, s);
sig = dsasigalloc();
sig->r = r;
sig->s = s;
mpfree(qm1);
mpfree(k);
mpfree(kinv);
return sig;
}

46
libsec/dsaverify.c Normal file
View File

@ -0,0 +1,46 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
int
dsaverify(DSApub *pub, DSAsig *sig, mpint *m)
{
int rv = -1;
mpint *u1, *u2, *v, *sinv;
if(sig->r->sign < 0 || mpcmp(sig->r, pub->q) >= 0)
return rv;
if(sig->s->sign < 0 || mpcmp(sig->s, pub->q) >= 0)
return rv;
u1 = mpnew(0);
u2 = mpnew(0);
v = mpnew(0);
sinv = mpnew(0);
// find (s**-1) mod q, make sure it exists
mpextendedgcd(sig->s, pub->q, u1, sinv, v);
if(mpcmp(u1, mpone) != 0)
goto out;
// u1 = (sinv * m) mod q, u2 = (r * sinv) mod q
mpmul(sinv, m, u1);
mpmod(u1, pub->q, u1);
mpmul(sig->r, sinv, u2);
mpmod(u2, pub->q, u2);
// v = (((alpha**u1)*(key**u2)) mod p) mod q
mpexp(pub->alpha, u1, pub->p, sinv);
mpexp(pub->key, u2, pub->p, v);
mpmul(sinv, v, v);
mpmod(v, pub->p, v);
mpmod(v, pub->q, v);
if(mpcmp(v, sig->r) == 0)
rv = 0;
out:
mpfree(v);
mpfree(u1);
mpfree(u2);
mpfree(sinv);
return rv;
}

67
libsec/egalloc.c Normal file
View File

@ -0,0 +1,67 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
EGpub*
egpuballoc(void)
{
EGpub *eg;
eg = mallocz(sizeof(*eg), 1);
if(eg == nil)
sysfatal("egpuballoc");
return eg;
}
void
egpubfree(EGpub *eg)
{
if(eg == nil)
return;
mpfree(eg->p);
mpfree(eg->alpha);
mpfree(eg->key);
}
EGpriv*
egprivalloc(void)
{
EGpriv *eg;
eg = mallocz(sizeof(*eg), 1);
if(eg == nil)
sysfatal("egprivalloc");
return eg;
}
void
egprivfree(EGpriv *eg)
{
if(eg == nil)
return;
mpfree(eg->pub.p);
mpfree(eg->pub.alpha);
mpfree(eg->pub.key);
mpfree(eg->secret);
}
EGsig*
egsigalloc(void)
{
EGsig *eg;
eg = mallocz(sizeof(*eg), 1);
if(eg == nil)
sysfatal("egsigalloc");
return eg;
}
void
egsigfree(EGsig *eg)
{
if(eg == nil)
return;
mpfree(eg->r);
mpfree(eg->s);
}

28
libsec/egdecrypt.c Normal file
View File

@ -0,0 +1,28 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
mpint*
egdecrypt(EGpriv *priv, mpint *in, mpint *out)
{
EGpub *pub = &priv->pub;
mpint *gamma, *delta;
mpint *p = pub->p;
int plen = mpsignif(p)+1;
int shift = ((plen+Dbits-1)/Dbits)*Dbits;
if(out == nil)
out = mpnew(0);
gamma = mpnew(0);
delta = mpnew(0);
mpright(in, shift, gamma);
mpleft(gamma, shift, delta);
mpsub(in, delta, delta);
mpexp(gamma, priv->secret, p, out);
mpinvert(out, p, gamma);
mpmul(gamma, delta, out);
mpmod(out, p, out);
mpfree(gamma);
mpfree(delta);
return out;
}

38
libsec/egencrypt.c Normal file
View File

@ -0,0 +1,38 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
mpint*
egencrypt(EGpub *pub, mpint *in, mpint *out)
{
mpint *m, *k, *gamma, *delta, *pm1;
mpint *p = pub->p, *alpha = pub->alpha;
int plen = mpsignif(p);
int shift = ((plen+Dbits)/Dbits)*Dbits;
// in libcrypt version, (int)(LENGTH(pub->p)*sizeof(NumType)*CHARBITS);
if(out == nil)
out = mpnew(0);
pm1 = mpnew(0);
m = mpnew(0);
gamma = mpnew(0);
delta = mpnew(0);
mpmod(in, p, m);
while(1){
k = mprand(plen, genrandom, nil);
if((mpcmp(mpone, k) <= 0) && (mpcmp(k, pm1) < 0))
break;
}
mpexp(alpha, k, p, gamma);
mpexp(pub->key, k, p, delta);
mpmul(m, delta, delta);
mpmod(delta, p, delta);
mpleft(gamma, shift, out);
mpadd(delta, out, out);
mpfree(pm1);
mpfree(m);
mpfree(k);
mpfree(gamma);
mpfree(delta);
return out;
}

21
libsec/eggen.c Normal file
View File

@ -0,0 +1,21 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
EGpriv*
eggen(int nlen, int rounds)
{
EGpub *pub;
EGpriv *priv;
priv = egprivalloc();
pub = &priv->pub;
pub->p = mpnew(0);
pub->alpha = mpnew(0);
pub->key = mpnew(0);
priv->secret = mpnew(0);
gensafeprime(pub->p, pub->alpha, nlen, rounds);
mprand(nlen-1, genrandom, priv->secret);
mpexp(pub->alpha, priv->secret, pub->p, pub->key);
return priv;
}

17
libsec/egprivtopub.c Normal file
View File

@ -0,0 +1,17 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
EGpub*
egprivtopub(EGpriv *priv)
{
EGpub *pub;
pub = egpuballoc();
if(pub == nil)
return nil;
pub->p = mpcopy(priv->pub.p);
pub->alpha = mpcopy(priv->pub.alpha);
pub->key = mpcopy(priv->pub.key);
return pub;
}

43
libsec/egsign.c Normal file
View File

@ -0,0 +1,43 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
EGsig*
egsign(EGpriv *priv, mpint *m)
{
EGpub *pub = &priv->pub;
EGsig *sig;
mpint *pm1, *k, *kinv, *r, *s;
mpint *p = pub->p, *alpha = pub->alpha;
int plen = mpsignif(p);
pm1 = mpnew(0);
kinv = mpnew(0);
r = mpnew(0);
s = mpnew(0);
k = mpnew(0);
mpsub(p, mpone, pm1);
while(1){
mprand(plen, genrandom, k);
if((mpcmp(mpone, k) > 0) || (mpcmp(k, pm1) >= 0))
continue;
mpextendedgcd(k, pm1, r, kinv, s);
if(mpcmp(r, mpone) != 0)
continue;
break;
}
mpmod(kinv, pm1, kinv); // make kinv positive
mpexp(alpha, k, p, r);
mpmul(priv->secret, r, s);
mpmod(s, pm1, s);
mpsub(m, s, s);
mpmul(kinv, s, s);
mpmod(s, pm1, s);
sig = egsigalloc();
sig->r = r;
sig->s = s;
mpfree(pm1);
mpfree(k);
mpfree(kinv);
return sig;
}

34
libsec/egtest.c Normal file
View File

@ -0,0 +1,34 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
void
main(void)
{
EGpriv *sk;
mpint *m, *gamma, *delta, *in, *out;
int plen, shift;
fmtinstall('B', mpconv);
sk = egprivalloc();
sk->pub.p = uitomp(2357, nil);
sk->pub.alpha = uitomp(2, nil);
sk->pub.key = uitomp(1185, nil);
sk->secret = uitomp(1751, nil);
m = uitomp(2035, nil);
plen = mpsignif(sk->pub.p)+1;
shift = ((plen+Dbits-1)/Dbits)*Dbits;
gamma = uitomp(1430, nil);
delta = uitomp(697, nil);
out = mpnew(0);
in = mpnew(0);
mpleft(gamma, shift, in);
mpadd(delta, in, in);
egdecrypt(sk, in, out);
if(mpcmp(m, out) != 0)
print("decrypt failed to recover message\n");
}

29
libsec/egverify.c Normal file
View File

@ -0,0 +1,29 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
int
egverify(EGpub *pub, EGsig *sig, mpint *m)
{
mpint *p = pub->p, *alpha = pub->alpha;
mpint *r = sig->r, *s = sig->s;
mpint *v1, *v2, *rs;
int rv = -1;
if(mpcmp(r, mpone) < 0 || mpcmp(r, p) >= 0)
return rv;
v1 = mpnew(0);
rs = mpnew(0);
v2 = mpnew(0);
mpexp(pub->key, r, p, v1);
mpexp(r, s, p, rs);
mpmul(v1, rs, v1);
mpmod(v1, p, v1);
mpexp(alpha, m, p, v2);
if(mpcmp(v1, v2) == 0)
rv = 0;
mpfree(v1);
mpfree(rs);
mpfree(v2);
return rv;
}

16
libsec/fastrand.c Normal file
View File

@ -0,0 +1,16 @@
#include <u.h>
#include <libc.h>
#include <libsec.h>
/*
* use the X917 random number generator to create random
* numbers (faster than truerand() but not as random).
*/
ulong
fastrand(void)
{
ulong x;
genrandom((uchar*)&x, sizeof x);
return x;
}

27
libsec/genprime.c Normal file
View File

@ -0,0 +1,27 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// generate a probable prime. accuracy is the miller-rabin interations
void
genprime(mpint *p, int n, int accuracy)
{
mpdigit x;
// generate n random bits with high and low bits set
mpbits(p, n);
genrandom((uchar*)p->p, (n+7)/8);
p->top = (n+Dbits-1)/Dbits;
x = 1;
x <<= ((n-1)%Dbits);
p->p[p->top-1] &= (x-1);
p->p[p->top-1] |= x;
p->p[0] |= 1;
// keep icrementing till it looks prime
for(;;){
if(probably_prime(p, accuracy))
break;
mpadd(p, mptwo, p);
}
}

62
libsec/genrandom.c Normal file
View File

@ -0,0 +1,62 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
typedef struct State{
QLock lock;
int seeded;
uvlong seed;
DES3state des3;
} State;
static State x917state;
static void
X917(uchar *rand, int nrand)
{
int i, m, n8;
uvlong I, x;
/* 1. Compute intermediate value I = Ek(time). */
I = nsec();
triple_block_cipher(x917state.des3.expanded, (uchar*)&I, 0); /* two-key EDE */
/* 2. x[i] = Ek(I^seed); seed = Ek(x[i]^I); */
m = (nrand+7)/8;
for(i=0; i<m; i++){
x = I ^ x917state.seed;
triple_block_cipher(x917state.des3.expanded, (uchar*)&x, 0);
n8 = (nrand>8) ? 8 : nrand;
memcpy(rand, (uchar*)&x, n8);
rand += 8;
nrand -= 8;
x ^= I;
triple_block_cipher(x917state.des3.expanded, (uchar*)&x, 0);
x917state.seed = x;
}
}
static void
X917init(void)
{
int n;
uchar mix[128];
uchar key3[3][8];
ulong *ulp;
ulp = (ulong*)key3;
for(n = 0; n < sizeof(key3)/sizeof(ulong); n++)
ulp[n] = truerand();
setupDES3state(&x917state.des3, key3, nil);
X917(mix, sizeof mix);
x917state.seeded = 1;
}
void
genrandom(uchar *p, int n)
{
qlock(&x917state.lock);
if(x917state.seeded == 0)
X917init();
X917(p, n);
qunlock(&x917state.lock);
}

36
libsec/gensafeprime.c Normal file
View File

@ -0,0 +1,36 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// find a prime p of length n and a generator alpha of Z^*_p
// Alg 4.86 Menezes et al () Handbook, p.164
void
gensafeprime(mpint *p, mpint *alpha, int n, int accuracy)
{
mpint *q, *b;
q = mpnew(n-1);
while(1){
genprime(q, n-1, accuracy);
mpleft(q, 1, p);
mpadd(p, mpone, p); // p = 2*q+1
if(probably_prime(p, accuracy))
break;
}
// now find a generator alpha of the multiplicative
// group Z*_p of order p-1=2q
b = mpnew(0);
while(1){
mprand(n, genrandom, alpha);
mpmod(alpha, p, alpha);
mpmul(alpha, alpha, b);
mpmod(b, p, b);
if(mpcmp(b, mpone) == 0)
continue;
mpexp(alpha, q, p, b);
if(mpcmp(b, mpone) != 0)
break;
}
mpfree(b);
mpfree(q);
}

57
libsec/genstrongprime.c Normal file
View File

@ -0,0 +1,57 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// Gordon's algorithm for generating a strong prime
// Menezes et al () Handbook, p.150
void
genstrongprime(mpint *p, int n, int accuracy)
{
mpint *s, *t, *r, *i;
if(n < 64)
n = 64;
s = mpnew(n/2);
genprime(s, (n/2)-16, accuracy);
t = mpnew(n/2);
genprime(t, n-mpsignif(s)-32, accuracy);
// first r = 2it + 1 that's prime
i = mpnew(16);
r = mpnew(0);
itomp(0x8000, i);
mpleft(t, 1, t); // 2t
mpmul(i, t, r); // 2it
mpadd(r, mpone, r); // 2it + 1
for(;;){
if(probably_prime(r, 18))
break;
mpadd(r, t, r); // r += 2t
}
// p0 = 2(s**(r-2) mod r)s - 1
itomp(2, p);
mpsub(r, p, p);
mpexp(s, p, r, p);
mpmul(s, p, p);
mpleft(p, 1, p);
mpsub(p, mpone, p);
// first p = p0 + 2irs that's prime
itomp(0x8000, i);
mpleft(r, 1, r); // 2r
mpmul(r, s, r); // 2rs
mpmul(r, i, i); // 2irs
mpadd(p, i, p); // p0 + 2irs
for(;;){
if(probably_prime(p, accuracy))
break;
mpadd(p, r, p); // p += 2rs
}
mpfree(i);
mpfree(s);
mpfree(r);
mpfree(t);
}

56
libsec/hmac.c Normal file
View File

@ -0,0 +1,56 @@
#include "os.h"
#include <libsec.h>
/* rfc2104 */
static DigestState*
hmac_x(uchar *p, ulong len, uchar *key, ulong klen, uchar *digest, DigestState *s,
DigestState*(*x)(uchar*, ulong, uchar*, DigestState*), int xlen)
{
int i;
uchar pad[65], innerdigest[256];
if(xlen > sizeof(innerdigest))
return nil;
if(klen>64)
return nil;
/* first time through */
if(s == nil){
for(i=0; i<64; i++)
pad[i] = 0x36;
pad[64] = 0;
for(i=0; i<klen; i++)
pad[i] ^= key[i];
s = (*x)(pad, 64, nil, nil);
if(s == nil)
return nil;
}
s = (*x)(p, len, nil, s);
if(digest == nil)
return s;
/* last time through */
for(i=0; i<64; i++)
pad[i] = 0x5c;
pad[64] = 0;
for(i=0; i<klen; i++)
pad[i] ^= key[i];
(*x)(nil, 0, innerdigest, s);
s = (*x)(pad, 64, nil, nil);
(*x)(innerdigest, xlen, digest, s);
return nil;
}
DigestState*
hmac_sha1(uchar *p, ulong len, uchar *key, ulong klen, uchar *digest, DigestState *s)
{
return hmac_x(p, len, key, klen, digest, s, sha1, SHA1dlen);
}
DigestState*
hmac_md5(uchar *p, ulong len, uchar *key, ulong klen, uchar *digest, DigestState *s)
{
return hmac_x(p, len, key, klen, digest, s, md5, MD5dlen);
}

19
libsec/hmactest.c Normal file
View File

@ -0,0 +1,19 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
uchar key[] = "Jefe";
uchar data[] = "what do ya want for nothing?";
void
main(void)
{
int i;
uchar hash[MD5dlen];
hmac_md5(data, strlen((char*)data), key, 4, hash, nil);
for(i=0; i<MD5dlen; i++)
print("%2.2x", hash[i]);
print("\n");
print("750c783e6ab0b503eaa86e310a5db738\n");
}

271
libsec/md4.c Normal file
View File

@ -0,0 +1,271 @@
#include "os.h"
#include <libsec.h>
/*
* This MD4 is implemented from the description in Stinson's Cryptography,
* theory and practice. -- presotto
*/
/*
* Rotate ammounts used in the algorithm
*/
enum
{
S11= 3,
S12= 7,
S13= 11,
S14= 19,
S21= 3,
S22= 5,
S23= 9,
S24= 13,
S31= 3,
S32= 9,
S33= 11,
S34= 15,
};
typedef struct MD4Table MD4Table;
struct MD4Table
{
uchar x; /* index into data block */
uchar rot; /* amount to rotate left by */
};
static MD4Table tab[] =
{
/* round 1 */
/*[0]*/ { 0, S11},
{ 1, S12},
{ 2, S13},
{ 3, S14},
{ 4, S11},
{ 5, S12},
{ 6, S13},
{ 7, S14},
{ 8, S11},
{ 9, S12},
{ 10, S13},
{ 11, S14},
{ 12, S11},
{ 13, S12},
{ 14, S13},
{ 15, S14},
/* round 2 */
/*[16]*/{ 0, S21},
{ 4, S22},
{ 8, S23},
{ 12, S24},
{ 1, S21},
{ 5, S22},
{ 9, S23},
{ 13, S24},
{ 2, S21},
{ 6, S22},
{ 10, S23},
{ 14, S24},
{ 3, S21},
{ 7, S22},
{ 11, S23},
{ 15, S24},
/* round 3 */
/*[32]*/{ 0, S31},
{ 8, S32},
{ 4, S33},
{ 12, S34},
{ 2, S31},
{ 10, S32},
{ 6, S33},
{ 14, S34},
{ 1, S31},
{ 9, S32},
{ 5, S33},
{ 13, S34},
{ 3, S31},
{ 11, S32},
{ 7, S33},
{ 15, S34},
};
static void encode(uchar*, u32int*, ulong);
static void decode(u32int*, uchar*, ulong);
static void
md4block(uchar *p, ulong len, MD4state *s)
{
int i;
u32int a, b, c, d, tmp;
MD4Table *t;
uchar *end;
u32int x[16];
for(end = p+len; p < end; p += 64){
a = s->state[0];
b = s->state[1];
c = s->state[2];
d = s->state[3];
decode(x, p, 64);
for(i = 0; i < 48; i++){
t = tab + i;
switch(i>>4){
case 0:
a += (b & c) | (~b & d);
break;
case 1:
a += ((b & c) | (b & d) | (c & d)) + 0x5A827999;
break;
case 2:
a += (b ^ c ^ d) + 0x6ED9EBA1;
break;
}
a += x[t->x];
a = (a << t->rot) | (a >> (32 - t->rot));
/* rotate variables */
tmp = d;
d = c;
c = b;
b = a;
a = tmp;
}
s->state[0] += a;
s->state[1] += b;
s->state[2] += c;
s->state[3] += d;
s->len += 64;
}
}
MD4state*
md4(uchar *p, ulong len, uchar *digest, MD4state *s)
{
u32int x[16];
uchar buf[128];
int i;
uchar *e;
if(s == nil){
s = malloc(sizeof(*s));
if(s == nil)
return nil;
memset(s, 0, sizeof(*s));
s->malloced = 1;
}
if(s->seeded == 0){
/* seed the state, these constants would look nicer big-endian */
s->state[0] = 0x67452301;
s->state[1] = 0xefcdab89;
s->state[2] = 0x98badcfe;
s->state[3] = 0x10325476;
s->seeded = 1;
}
/* fill out the partial 64 byte block from previous calls */
if(s->blen){
i = 64 - s->blen;
if(len < i)
i = len;
memmove(s->buf + s->blen, p, i);
len -= i;
s->blen += i;
p += i;
if(s->blen == 64){
md4block(s->buf, s->blen, s);
s->blen = 0;
}
}
/* do 64 byte blocks */
i = len & ~0x3f;
if(i){
md4block(p, i, s);
len -= i;
p += i;
}
/* save the left overs if not last call */
if(digest == 0){
if(len){
memmove(s->buf, p, len);
s->blen += len;
}
return s;
}
/*
* this is the last time through, pad what's left with 0x80,
* 0's, and the input count to create a multiple of 64 bytes
*/
if(s->blen){
p = s->buf;
len = s->blen;
} else {
memmove(buf, p, len);
p = buf;
}
s->len += len;
e = p + len;
if(len < 56)
i = 56 - len;
else
i = 120 - len;
memset(e, 0, i);
*e = 0x80;
len += i;
/* append the count */
x[0] = s->len<<3;
x[1] = s->len>>29;
encode(p+len, x, 8);
/* digest the last part */
md4block(p, len+8, s);
/* return result and free state */
encode(digest, s->state, MD4dlen);
if(s->malloced == 1)
free(s);
return nil;
}
/*
* encodes input (u32int) into output (uchar). Assumes len is
* a multiple of 4.
*/
static void
encode(uchar *output, u32int *input, ulong len)
{
u32int x;
uchar *e;
for(e = output + len; output < e;) {
x = *input++;
*output++ = x;
*output++ = x >> 8;
*output++ = x >> 16;
*output++ = x >> 24;
}
}
/*
* decodes input (uchar) into output (u32int). Assumes len is
* a multiple of 4.
*/
static void
decode(u32int *output, uchar *input, ulong len)
{
uchar *e;
for(e = input+len; input < e; input += 4)
*output++ = input[0] | (input[1] << 8) |
(input[2] << 16) | (input[3] << 24);
}

31
libsec/md4test.c Normal file
View File

@ -0,0 +1,31 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
char *tests[] = {
"",
"a",
"abc",
"message digest",
"abcdefghijklmnopqrstuvwxyz",
"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789",
"12345678901234567890123456789012345678901234567890123456789012345678901234567890",
0
};
void
main(void)
{
char **pp;
uchar *p;
int i;
uchar digest[MD5dlen];
for(pp = tests; *pp; pp++){
p = (uchar*)*pp;
md4(p, strlen(*pp), digest, 0);
for(i = 0; i < MD5dlen; i++)
print("%2.2ux", digest[i]);
print("\n");
}
}

148
libsec/md5.c Normal file
View File

@ -0,0 +1,148 @@
#include "os.h"
#include <libsec.h>
/*
* rfc1321 requires that I include this. The code is new. The constants
* all come from the rfc (hence the copyright). We trade a table for the
* macros in rfc. The total size is a lot less. -- presotto
*
* Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All
* rights reserved.
*
* License to copy and use this software is granted provided that it
* is identified as the "RSA Data Security, Inc. MD5 Message-Digest
* Algorithm" in all material mentioning or referencing this software
* or this function.
*
* License is also granted to make and use derivative works provided
* that such works are identified as "derived from the RSA Data
* Security, Inc. MD5 Message-Digest Algorithm" in all material
* mentioning or referencing the derived work.
*
* RSA Data Security, Inc. makes no representations concerning either
* the merchantability of this software or the suitability of this
* software forany particular purpose. It is provided "as is"
* without express or implied warranty of any kind.
* These notices must be retained in any copies of any part of this
* documentation and/or software.
*/
static void encode(uchar*, u32int*, ulong);
static void decode(u32int*, uchar*, ulong);
extern void _md5block(uchar*, ulong, u32int*);
MD5state*
md5(uchar *p, ulong len, uchar *digest, MD5state *s)
{
u32int x[16];
uchar buf[128];
int i;
uchar *e;
if(s == nil){
s = malloc(sizeof(*s));
if(s == nil)
return nil;
memset(s, 0, sizeof(*s));
s->malloced = 1;
}
if(s->seeded == 0){
/* seed the state, these constants would look nicer big-endian */
s->state[0] = 0x67452301;
s->state[1] = 0xefcdab89;
s->state[2] = 0x98badcfe;
s->state[3] = 0x10325476;
s->seeded = 1;
}
/* fill out the partial 64 byte block from previous calls */
if(s->blen){
i = 64 - s->blen;
if(len < i)
i = len;
memmove(s->buf + s->blen, p, i);
len -= i;
s->blen += i;
p += i;
if(s->blen == 64){
_md5block(s->buf, s->blen, s->state);
s->len += s->blen;
s->blen = 0;
}
}
/* do 64 byte blocks */
i = len & ~0x3f;
if(i){
_md5block(p, i, s->state);
s->len += i;
len -= i;
p += i;
}
/* save the left overs if not last call */
if(digest == 0){
if(len){
memmove(s->buf, p, len);
s->blen += len;
}
return s;
}
/*
* this is the last time through, pad what's left with 0x80,
* 0's, and the input count to create a multiple of 64 bytes
*/
if(s->blen){
p = s->buf;
len = s->blen;
} else {
memmove(buf, p, len);
p = buf;
}
s->len += len;
e = p + len;
if(len < 56)
i = 56 - len;
else
i = 120 - len;
memset(e, 0, i);
*e = 0x80;
len += i;
/* append the count */
x[0] = s->len<<3;
x[1] = s->len>>29;
encode(p+len, x, 8);
/* digest the last part */
_md5block(p, len+8, s->state);
s->len += len;
/* return result and free state */
encode(digest, s->state, MD5dlen);
if(s->malloced == 1)
free(s);
return nil;
}
/*
* encodes input (u32int) into output (uchar). Assumes len is
* a multiple of 4.
*/
static void
encode(uchar *output, u32int *input, ulong len)
{
u32int x;
uchar *e;
for(e = output + len; output < e;) {
x = *input++;
*output++ = x;
*output++ = x >> 8;
*output++ = x >> 16;
*output++ = x >> 24;
}
}

267
libsec/md5block.c Normal file
View File

@ -0,0 +1,267 @@
#include "os.h"
#include <libsec.h>
/*
* rfc1321 requires that I include this. The code is new. The constants
* all come from the rfc (hence the copyright). We trade a table for the
* macros in rfc. The total size is a lot less. -- presotto
*
* Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All
* rights reserved.
*
* License to copy and use this software is granted provided that it
* is identified as the "RSA Data Security, Inc. MD5 Message-Digest
* Algorithm" in all material mentioning or referencing this software
* or this function.
*
* License is also granted to make and use derivative works provided
* that such works are identified as "derived from the RSA Data
* Security, Inc. MD5 Message-Digest Algorithm" in all material
* mentioning or referencing the derived work.
*
* RSA Data Security, Inc. makes no representations concerning either
* the merchantability of this software or the suitability of this
* software forany particular purpose. It is provided "as is"
* without express or implied warranty of any kind.
* These notices must be retained in any copies of any part of this
* documentation and/or software.
*/
/*
* Rotate ammounts used in the algorithm
*/
enum
{
S11= 7,
S12= 12,
S13= 17,
S14= 22,
S21= 5,
S22= 9,
S23= 14,
S24= 20,
S31= 4,
S32= 11,
S33= 16,
S34= 23,
S41= 6,
S42= 10,
S43= 15,
S44= 21,
};
static u32int md5tab[] =
{
/* round 1 */
/*[0]*/ 0xd76aa478,
0xe8c7b756,
0x242070db,
0xc1bdceee,
0xf57c0faf,
0x4787c62a,
0xa8304613,
0xfd469501,
0x698098d8,
0x8b44f7af,
0xffff5bb1,
0x895cd7be,
0x6b901122,
0xfd987193,
0xa679438e,
0x49b40821,
/* round 2 */
/*[16]*/0xf61e2562,
0xc040b340,
0x265e5a51,
0xe9b6c7aa,
0xd62f105d,
0x2441453,
0xd8a1e681,
0xe7d3fbc8,
0x21e1cde6,
0xc33707d6,
0xf4d50d87,
0x455a14ed,
0xa9e3e905,
0xfcefa3f8,
0x676f02d9,
0x8d2a4c8a,
/* round 3 */
/*[32]*/0xfffa3942,
0x8771f681,
0x6d9d6122,
0xfde5380c,
0xa4beea44,
0x4bdecfa9,
0xf6bb4b60,
0xbebfbc70,
0x289b7ec6,
0xeaa127fa,
0xd4ef3085,
0x4881d05,
0xd9d4d039,
0xe6db99e5,
0x1fa27cf8,
0xc4ac5665,
/* round 4 */
/*[48]*/0xf4292244,
0x432aff97,
0xab9423a7,
0xfc93a039,
0x655b59c3,
0x8f0ccc92,
0xffeff47d,
0x85845dd1,
0x6fa87e4f,
0xfe2ce6e0,
0xa3014314,
0x4e0811a1,
0xf7537e82,
0xbd3af235,
0x2ad7d2bb,
0xeb86d391,
};
static void decode(u32int*, uchar*, ulong);
extern void _md5block(uchar *p, ulong len, u32int *s);
void
_md5block(uchar *p, ulong len, u32int *s)
{
u32int a, b, c, d, sh;
u32int *t;
uchar *end;
u32int x[16];
for(end = p+len; p < end; p += 64){
a = s[0];
b = s[1];
c = s[2];
d = s[3];
decode(x, p, 64);
t = md5tab;
sh = 0;
for(; sh != 16; t += 4){
a += ((c ^ d) & b) ^ d;
a += x[sh] + t[0];
a = (a << S11) | (a >> (32 - S11));
a += b;
d += ((b ^ c) & a) ^ c;
d += x[sh + 1] + t[1];
d = (d << S12) | (d >> (32 - S12));
d += a;
c += ((a ^ b) & d) ^ b;
c += x[sh + 2] + t[2];
c = (c << S13) | (c >> (32 - S13));
c += d;
b += ((d ^ a) & c) ^ a;
b += x[sh + 3] + t[3];
b = (b << S14) | (b >> (32 - S14));
b += c;
sh += 4;
}
sh = 1;
for(; sh != 1+20*4; t += 4){
a += ((b ^ c) & d) ^ c;
a += x[sh & 0xf] + t[0];
a = (a << S21) | (a >> (32 - S21));
a += b;
d += ((a ^ b) & c) ^ b;
d += x[(sh + 5) & 0xf] + t[1];
d = (d << S22) | (d >> (32 - S22));
d += a;
c += ((d ^ a) & b) ^ a;
c += x[(sh + 10) & 0xf] + t[2];
c = (c << S23) | (c >> (32 - S23));
c += d;
b += ((c ^ d) & a) ^ d;
b += x[(sh + 15) & 0xf] + t[3];
b = (b << S24) | (b >> (32 - S24));
b += c;
sh += 20;
}
sh = 5;
for(; sh != 5+12*4; t += 4){
a += b ^ c ^ d;
a += x[sh & 0xf] + t[0];
a = (a << S31) | (a >> (32 - S31));
a += b;
d += a ^ b ^ c;
d += x[(sh + 3) & 0xf] + t[1];
d = (d << S32) | (d >> (32 - S32));
d += a;
c += d ^ a ^ b;
c += x[(sh + 6) & 0xf] + t[2];
c = (c << S33) | (c >> (32 - S33));
c += d;
b += c ^ d ^ a;
b += x[(sh + 9) & 0xf] + t[3];
b = (b << S34) | (b >> (32 - S34));
b += c;
sh += 12;
}
sh = 0;
for(; sh != 28*4; t += 4){
a += c ^ (b | ~d);
a += x[sh & 0xf] + t[0];
a = (a << S41) | (a >> (32 - S41));
a += b;
d += b ^ (a | ~c);
d += x[(sh + 7) & 0xf] + t[1];
d = (d << S42) | (d >> (32 - S42));
d += a;
c += a ^ (d | ~b);
c += x[(sh + 14) & 0xf] + t[2];
c = (c << S43) | (c >> (32 - S43));
c += d;
b += d ^ (c | ~a);
b += x[(sh + 21) & 0xf] + t[3];
b = (b << S44) | (b >> (32 - S44));
b += c;
sh += 28;
}
s[0] += a;
s[1] += b;
s[2] += c;
s[3] += d;
}
}
/*
* decodes input (uchar) into output (u32int). Assumes len is
* a multiple of 4.
*/
static void
decode(u32int *output, uchar *input, ulong len)
{
uchar *e;
for(e = input+len; input < e; input += 4)
*output++ = input[0] | (input[1] << 8) |
(input[2] << 16) | (input[3] << 24);
}

37
libsec/md5pickle.c Normal file
View File

@ -0,0 +1,37 @@
#include "os.h"
#include <libsec.h>
char*
md5pickle(MD5state *s)
{
char *p;
int m, n;
m = 4*9+4*((s->blen+3)/3);
p = malloc(m);
if(p == nil)
return p;
n = sprint(p, "%8.8ux %8.8ux %8.8ux %8.8ux ",
s->state[0], s->state[1], s->state[2],
s->state[3]);
enc64(p+n, m-n, s->buf, s->blen);
return p;
}
MD5state*
md5unpickle(char *p)
{
MD5state *s;
s = malloc(sizeof(*s));
if(s == nil)
return nil;
s->state[0] = strtoul(p, &p, 16);
s->state[1] = strtoul(p, &p, 16);
s->state[2] = strtoul(p, &p, 16);
s->state[3] = strtoul(p, &p, 16);
s->blen = dec64(s->buf, sizeof(s->buf), p, strlen(p));
s->malloced = 1;
s->seeded = 1;
return s;
}

55
libsec/mkfile Normal file
View File

@ -0,0 +1,55 @@
<$DSRC/mkfile-$CONF
TARG=libsec.$L
OFILES=\
aes.$O\
blowfish.$O\
decodepem.$O\
des.$O\
des3CBC.$O\
des3ECB.$O\
desCBC.$O\
desECB.$O\
desmodes.$O\
dsaalloc.$O\
dsagen.$O\
dsaprimes.$O\
dsaprivtopub.$O\
dsasign.$O\
dsaverify.$O\
egalloc.$O\
egdecrypt.$O\
egencrypt.$O\
eggen.$O\
egprivtopub.$O\
egsign.$O\
egverify.$O\
fastrand.$O\
genprime.$O\
genrandom.$O\
gensafeprime.$O\
genstrongprime.$O\
hmac.$O\
md4.$O\
md5.$O\
md5block.$O\
md5pickle.$O\
nfastrand.$O\
prng.$O\
probably_prime.$O\
rc4.$O\
rsaalloc.$O\
rsadecrypt.$O\
rsaencrypt.$O\
rsafill.$O\
rsagen.$O\
rsaprivtopub.$O\
sha1.$O\
sha1block.$O\
sha1pickle.$O\
smallprimes.$O
HFILE=\
os.h
<$DSRC/mklib-$CONF

23
libsec/nfastrand.c Normal file
View File

@ -0,0 +1,23 @@
#include <u.h>
#include <libc.h>
#include <libsec.h>
#define Maxrand ((1UL<<31)-1)
ulong
nfastrand(ulong n)
{
ulong m, r;
/*
* set m to the maximum multiple of n <= 2^31-1
* so we want a random number < m.
*/
if(n > Maxrand)
abort();
m = Maxrand - Maxrand % n;
while((r = fastrand()) >= m)
;
return r%n;
}

2
libsec/os.h Normal file
View File

@ -0,0 +1,2 @@
#include <u.h>
#include <libc.h>

41
libsec/primetest.c Normal file
View File

@ -0,0 +1,41 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
void
main(void)
{
mpint *z = mpnew(0);
mpint *p = mpnew(0);
mpint *q = mpnew(0);
mpint *nine = mpnew(0);
fmtinstall('B', mpconv);
strtomp("2492491", nil, 16, z); // 38347921 = x*y = (2**28-9)/7,
// an example of 3**(n-1)=1 mod n
strtomp("15662C00E811", nil, 16, p);// 23528569104401, a prime
uitomp(9, nine);
if(probably_prime(z, 5) == 1)
fprint(2, "tricked primality test\n");
if(probably_prime(nine, 5) == 1)
fprint(2, "9 passed primality test!\n");
if(probably_prime(p, 25) == 1)
fprint(2, "ok\n");
DSAprimes(q, p, nil);
print("q=%B\np=%B\n", q, p);
exits(0);
}
// example output, checked with Maple:
// seed EB7B6E35F7CD37B511D96C67D6688CC4DD440E1E
// q=E0F0EF284E10796C5A2A511E94748BA03C795C13
// = 1284186945063585093695748280224501481698995297299
// p=C41CFBE4D4846F67A3DF7DE9921A49D3B42DC33728427AB159CEC8CBBDB12B5F0C244F1A734AEB9840804EA3C25036AD1B61AFF3ABBC247CD4B384224567A863A6F020E7EE9795554BCD08ABAD7321AF27E1E92E3DB1C6E7E94FAAE590AE9C48F96D93D178E809401ABE8A534A1EC44359733475A36A70C7B425125062B1142D
// = 137715385439333164327584575331308277462546592976152006175830654712456008630139443747529133857837818585400418619916530061955288983751958831927807888408309879880101870216437711393638413509484569804814373511469405934988856674935304074081350525593807908358867354528898618574659752879015380013845760006721861915693
// r=DF310F4E54A5FEC5D86D3E14863921E834113E060F90052AD332B3241CEF2497EFA0303D6344F7C819691A0F9C4A773815AF8EAECFB7EC1D98F039F17A32A7E887D97251A927D093F44A55577F4D70444AEBD06B9B45695EC23962B175F266895C67D21C4656848614D888A4
// = 107239359478548771267308764204625458348785444483302647285245969203446101233421655396874997253111222983406676955642093641709149748793954493558324738441197139556917622937892491175016280660608595599724194374948056515856812347094848443460715881455884639869144172708
// g=2F1C308DC46B9A44B52DF7DACCE1208CCEF72F69C743ADD4D2327173444ED6E65E074694246E07F9FD4AE26E0FDDD9F54F813C40CB9BCD4338EA6F242AB94CD410E676C290368A16B1A3594877437E516C53A6EEE5493A038A017E955E218E7819734E3E2A6E0BAE08B14258F8C03CC1B30E0DDADFCF7CEDF0727684D3D255F1
// = 33081848392740465806285326014906437543653045153885419334085917570615301913274531387168723847139029827598735376746057461417880810924280288611116213062512408829164220104555543445909528701551198146080221790002337033997295756585193926863581671466708482411159477816144226847280417522524922667065714073338662508017

15
libsec/prng.c Normal file
View File

@ -0,0 +1,15 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
//
// just use the libc prng to fill a buffer
//
void
prng(uchar *p, int n)
{
uchar *e;
for(e = p+n; p < e; p++)
*p = rand();
}

84
libsec/probably_prime.c Normal file
View File

@ -0,0 +1,84 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// Miller-Rabin probabilistic primality testing
// Knuth (1981) Seminumerical Algorithms, p.379
// Menezes et al () Handbook, p.39
// 0 if composite; 1 if almost surely prime, Pr(err)<1/4**nrep
int
probably_prime(mpint *n, int nrep)
{
int j, k, rep, nbits, isprime = 1;
mpint *nm1, *q, *x, *y, *r;
if(n->sign < 0)
sysfatal("negative prime candidate");
if(nrep <= 0)
nrep = 18;
k = mptoi(n);
if(k == 2) // 2 is prime
return 1;
if(k < 2) // 1 is not prime
return 0;
if((n->p[0] & 1) == 0) // even is not prime
return 0;
// test against small prime numbers
if(smallprimetest(n) < 0)
return 0;
// fermat test, 2^n mod n == 2 if p is prime
x = uitomp(2, nil);
y = mpnew(0);
mpexp(x, n, n, y);
k = mptoi(y);
if(k != 2){
mpfree(x);
mpfree(y);
return 0;
}
nbits = mpsignif(n);
nm1 = mpnew(nbits);
mpsub(n, mpone, nm1); // nm1 = n - 1 */
k = mplowbits0(nm1);
q = mpnew(0);
mpright(nm1, k, q); // q = (n-1)/2**k
for(rep = 0; rep < nrep; rep++){
// x = random in [2, n-2]
r = mprand(nbits, prng, nil);
mpmod(r, nm1, x);
mpfree(r);
if(mpcmp(x, mpone) <= 0)
continue;
// y = x**q mod n
mpexp(x, q, n, y);
if(mpcmp(y, mpone) == 0 || mpcmp(y, nm1) == 0)
goto done;
for(j = 1; j < k; j++){
mpmul(y, y, x);
mpmod(x, n, y); // y = y*y mod n
if(mpcmp(y, nm1) == 0)
goto done;
if(mpcmp(y, mpone) == 0){
isprime = 0;
goto done;
}
}
isprime = 0;
}
done:
mpfree(y);
mpfree(x);
mpfree(q);
mpfree(nm1);
return isprime;
}

BIN
libsec/ranlib.core Normal file

Binary file not shown.

104
libsec/rc4.c Normal file
View File

@ -0,0 +1,104 @@
#include "os.h"
#include <libsec.h>
void
setupRC4state(RC4state *key, uchar *start, int n)
{
int t;
int index2;
uchar *state;
uchar *p, *e, *sp, *se;
state = key->state;
se = &state[256];
for(sp = state; sp < se; sp++)
*sp = sp - state;
key->x = 0;
key->y = 0;
index2 = 0;
e = start + n;
p = start;
for(sp = state; sp < se; sp++)
{
t = *sp;
index2 = (*p + t + index2) & 255;
*sp = state[index2];
state[index2] = t;
if(++p >= e)
p = start;
}
}
void
rc4(RC4state *key, uchar *p, int len)
{
int tx, ty;
int x, y;
uchar *state;
uchar *e;
x = key->x;
y = key->y;
state = &key->state[0];
for(e = p + len; p < e; p++)
{
x = (x+1)&255;
tx = state[x];
y = (y+tx)&255;
ty = state[y];
state[x] = ty;
state[y] = tx;
*p ^= state[(tx+ty)&255];
}
key->x = x;
key->y = y;
}
void
rc4skip(RC4state *key, int len)
{
int tx, ty;
int x, y;
uchar *state;
int i;
x = key->x;
y = key->y;
state = &key->state[0];
for(i=0; i<len; i++)
{
x = (x+1)&255;
tx = state[x];
y = (y+tx)&255;
ty = state[y];
state[x] = ty;
state[y] = tx;
}
key->x = x;
key->y = y;
}
void
rc4back(RC4state *key, int len)
{
int tx, ty;
int x, y;
uchar *state;
int i;
x = key->x;
y = key->y;
state = &key->state[0];
for(i=0; i<len; i++)
{
ty = state[x];
tx = state[y];
state[y] = ty;
state[x] = tx;
y = (y-tx)&255;
x = (x-1)&255;
}
key->x = x;
key->y = y;
}

50
libsec/readcert.c Normal file
View File

@ -0,0 +1,50 @@
#include <u.h>
#include <libc.h>
#include <mp.h>
#include <libsec.h>
static char*
readfile(char *name)
{
int fd;
char *s;
Dir *d;
fd = open(name, OREAD);
if(fd < 0)
return nil;
if((d = dirfstat(fd)) == nil)
return nil;
s = malloc(d->length + 1);
if(s == nil || readn(fd, s, d->length) != d->length){
free(s);
free(d);
close(fd);
return nil;
}
close(fd);
s[d->length] = '\0';
free(d);
return s;
}
uchar*
readcert(char *filename, int *pcertlen)
{
char *pem;
uchar *binary;
pem = readfile(filename);
if(pem == nil){
werrstr("can't read %s", filename);
return nil;
}
binary = decodepem(pem, "CERTIFICATE", pcertlen);
free(pem);
if(binary == nil){
werrstr("can't parse %s", filename);
return nil;
}
return binary;
}

52
libsec/rsaalloc.c Normal file
View File

@ -0,0 +1,52 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
RSApub*
rsapuballoc(void)
{
RSApub *rsa;
rsa = mallocz(sizeof(*rsa), 1);
if(rsa == nil)
sysfatal("rsapuballoc");
return rsa;
}
void
rsapubfree(RSApub *rsa)
{
if(rsa == nil)
return;
mpfree(rsa->ek);
mpfree(rsa->n);
free(rsa);
}
RSApriv*
rsaprivalloc(void)
{
RSApriv *rsa;
rsa = mallocz(sizeof(*rsa), 1);
if(rsa == nil)
sysfatal("rsaprivalloc");
return rsa;
}
void
rsaprivfree(RSApriv *rsa)
{
if(rsa == nil)
return;
mpfree(rsa->pub.ek);
mpfree(rsa->pub.n);
mpfree(rsa->dk);
mpfree(rsa->p);
mpfree(rsa->q);
mpfree(rsa->kp);
mpfree(rsa->kq);
mpfree(rsa->c2);
free(rsa);
}

37
libsec/rsadecrypt.c Normal file
View File

@ -0,0 +1,37 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
// decrypt rsa using garner's algorithm for the chinese remainder theorem
// seminumerical algorithms, knuth, pp 253-254
// applied cryptography, menezes et al, pg 612
mpint*
rsadecrypt(RSApriv *rsa, mpint *in, mpint *out)
{
mpint *v1, *v2;
if(out == nil)
out = mpnew(0);
// convert in to modular representation
v1 = mpnew(0);
mpmod(in, rsa->p, v1);
v2 = mpnew(0);
mpmod(in, rsa->q, v2);
// exponentiate the modular rep
mpexp(v1, rsa->kp, rsa->p, v1);
mpexp(v2, rsa->kq, rsa->q, v2);
// out = v1 + p*((v2-v1)*c2 mod q)
mpsub(v2, v1, v2);
mpmul(v2, rsa->c2, v2);
mpmod(v2, rsa->q, v2);
mpmul(v2, rsa->p, out);
mpadd(v1, out, out);
mpfree(v1);
mpfree(v2);
return out;
}

12
libsec/rsaencrypt.c Normal file
View File

@ -0,0 +1,12 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
mpint*
rsaencrypt(RSApub *rsa, mpint *in, mpint *out)
{
if(out == nil)
out = mpnew(0);
mpexp(in, rsa->ek, rsa->n, out);
return out;
}

61
libsec/rsafill.c Normal file
View File

@ -0,0 +1,61 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
RSApriv*
rsafill(mpint *n, mpint *e, mpint *d, mpint *p, mpint *q)
{
mpint *c2, *kq, *kp, *x;
RSApriv *rsa;
// make sure we're not being hoodwinked
if(!probably_prime(p, 10) || !probably_prime(q, 10)){
werrstr("rsafill: p or q not prime");
return nil;
}
x = mpnew(0);
mpmul(p, q, x);
if(mpcmp(n, x) != 0){
werrstr("rsafill: n != p*q");
mpfree(x);
return nil;
}
c2 = mpnew(0);
mpsub(p, mpone, c2);
mpsub(q, mpone, x);
mpmul(c2, x, x);
mpmul(e, d, c2);
mpmod(c2, x, x);
if(mpcmp(x, mpone) != 0){
werrstr("rsafill: e*d != 1 mod (p-1)*(q-1)");
mpfree(x);
mpfree(c2);
return nil;
}
// compute chinese remainder coefficient
mpinvert(p, q, c2);
// for crt a**k mod p == (a**(k mod p-1)) mod p
kq = mpnew(0);
kp = mpnew(0);
mpsub(p, mpone, x);
mpmod(d, x, kp);
mpsub(q, mpone, x);
mpmod(d, x, kq);
rsa = rsaprivalloc();
rsa->pub.ek = mpcopy(e);
rsa->pub.n = mpcopy(n);
rsa->dk = mpcopy(d);
rsa->kp = kp;
rsa->kq = kq;
rsa->p = mpcopy(p);
rsa->q = mpcopy(q);
rsa->c2 = c2;
mpfree(x);
return rsa;
}

82
libsec/rsagen.c Normal file
View File

@ -0,0 +1,82 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
static void
genrand(mpint *p, int n)
{
mpdigit x;
// generate n random bits with high set
mpbits(p, n);
genrandom((uchar*)p->p, (n+7)/8);
p->top = (n+Dbits-1)/Dbits;
x = 1;
x <<= ((n-1)%Dbits);
p->p[p->top-1] &= (x-1);
p->p[p->top-1] |= x;
}
RSApriv*
rsagen(int nlen, int elen, int rounds)
{
mpint *p, *q, *e, *d, *phi, *n, *t1, *t2, *kp, *kq, *c2;
RSApriv *rsa;
p = mpnew(nlen/2);
q = mpnew(nlen/2);
n = mpnew(nlen);
e = mpnew(elen);
d = mpnew(0);
phi = mpnew(nlen);
// create the prime factors and euclid's function
genstrongprime(p, nlen/2, rounds);
genstrongprime(q, nlen - mpsignif(p) + 1, rounds);
mpmul(p, q, n);
mpsub(p, mpone, e);
mpsub(q, mpone, d);
mpmul(e, d, phi);
// find an e relatively prime to phi
t1 = mpnew(0);
t2 = mpnew(0);
genrand(e, elen);
for(;;){
mpextendedgcd(e, phi, d, t1, t2);
if(mpcmp(d, mpone) == 0)
break;
mpadd(mpone, e, e);
}
mpfree(t1);
mpfree(t2);
// d = e**-1 mod phi
mpinvert(e, phi, d);
// compute chinese remainder coefficient
c2 = mpnew(0);
mpinvert(p, q, c2);
// for crt a**k mod p == (a**(k mod p-1)) mod p
kq = mpnew(0);
kp = mpnew(0);
mpsub(p, mpone, phi);
mpmod(d, phi, kp);
mpsub(q, mpone, phi);
mpmod(d, phi, kq);
rsa = rsaprivalloc();
rsa->pub.ek = e;
rsa->pub.n = n;
rsa->dk = d;
rsa->kp = kp;
rsa->kq = kq;
rsa->p = p;
rsa->q = q;
rsa->c2 = c2;
mpfree(phi);
return rsa;
}

16
libsec/rsaprivtopub.c Normal file
View File

@ -0,0 +1,16 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
RSApub*
rsaprivtopub(RSApriv *priv)
{
RSApub *pub;
pub = rsapuballoc();
if(pub == nil)
return nil;
pub->n = mpcopy(priv->pub.n);
pub->ek = mpcopy(priv->pub.ek);
return pub;
}

57
libsec/rsatest.c Normal file
View File

@ -0,0 +1,57 @@
#include "os.h"
#include <mp.h>
#include <libsec.h>
#include <bio.h>
void
main(void)
{
RSApriv *rsa;
Biobuf b;
char *p;
int n;
mpint *clr, *enc, *clr2;
uchar buf[4096];
uchar *e;
vlong start;
fmtinstall('B', mpconv);
rsa = rsagen(1024, 16, 0);
if(rsa == nil)
sysfatal("rsagen");
Binit(&b, 0, OREAD);
clr = mpnew(0);
clr2 = mpnew(0);
enc = mpnew(0);
strtomp("123456789abcdef123456789abcdef123456789abcdef123456789abcdef", nil, 16, clr);
rsaencrypt(&rsa->pub, clr, enc);
start = nsec();
for(n = 0; n < 10; n++)
rsadecrypt(rsa, enc, clr);
print("%lld\n", nsec()-start);
start = nsec();
for(n = 0; n < 10; n++)
mpexp(enc, rsa->dk, rsa->pub.n, clr2);
print("%lld\n", nsec()-start);
if(mpcmp(clr, clr2) != 0)
print("%B != %B\n", clr, clr2);
print("> ");
while(p = Brdline(&b, '\n')){
n = Blinelen(&b);
letomp((uchar*)p, n, clr);
print("clr %B\n", clr);
rsaencrypt(&rsa->pub, clr, enc);
print("enc %B\n", enc);
rsadecrypt(rsa, enc, clr);
print("clr %B\n", clr);
n = mptole(clr, buf, sizeof(buf), nil);
write(1, buf, n);
print("> ");
}
}

127
libsec/sha1.c Normal file
View File

@ -0,0 +1,127 @@
#include "os.h"
#include <libsec.h>
static void encode(uchar*, u32int*, ulong);
extern void _sha1block(uchar*, ulong, u32int*);
/*
* we require len to be a multiple of 64 for all but
* the last call. There must be room in the input buffer
* to pad.
*/
SHA1state*
sha1(uchar *p, ulong len, uchar *digest, SHA1state *s)
{
uchar buf[128];
u32int x[16];
int i;
uchar *e;
if(s == nil){
s = malloc(sizeof(*s));
if(s == nil)
return nil;
memset(s, 0, sizeof(*s));
s->malloced = 1;
}
if(s->seeded == 0){
/* seed the state, these constants would look nicer big-endian */
s->state[0] = 0x67452301;
s->state[1] = 0xefcdab89;
s->state[2] = 0x98badcfe;
s->state[3] = 0x10325476;
s->state[4] = 0xc3d2e1f0;
s->seeded = 1;
}
/* fill out the partial 64 byte block from previous calls */
if(s->blen){
i = 64 - s->blen;
if(len < i)
i = len;
memmove(s->buf + s->blen, p, i);
len -= i;
s->blen += i;
p += i;
if(s->blen == 64){
_sha1block(s->buf, s->blen, s->state);
s->len += s->blen;
s->blen = 0;
}
}
/* do 64 byte blocks */
i = len & ~0x3f;
if(i){
_sha1block(p, i, s->state);
s->len += i;
len -= i;
p += i;
}
/* save the left overs if not last call */
if(digest == 0){
if(len){
memmove(s->buf, p, len);
s->blen += len;
}
return s;
}
/*
* this is the last time through, pad what's left with 0x80,
* 0's, and the input count to create a multiple of 64 bytes
*/
if(s->blen){
p = s->buf;
len = s->blen;
} else {
memmove(buf, p, len);
p = buf;
}
s->len += len;
e = p + len;
if(len < 56)
i = 56 - len;
else
i = 120 - len;
memset(e, 0, i);
*e = 0x80;
len += i;
/* append the count */
x[0] = s->len>>29;
x[1] = s->len<<3;
encode(p+len, x, 8);
/* digest the last part */
_sha1block(p, len+8, s->state);
s->len += len+8;
/* return result and free state */
encode(digest, s->state, SHA1dlen);
if(s->malloced == 1)
free(s);
return nil;
}
/*
* encodes input (ulong) into output (uchar). Assumes len is
* a multiple of 4.
*/
static void
encode(uchar *output, u32int *input, ulong len)
{
u32int x;
uchar *e;
for(e = output + len; output < e;) {
x = *input++;
*output++ = x >> 24;
*output++ = x >> 16;
*output++ = x >> 8;
*output++ = x;
}
}

187
libsec/sha1block.c Normal file
View File

@ -0,0 +1,187 @@
#include "os.h"
void
_sha1block(uchar *p, ulong len, u32int *s)
{
u32int a, b, c, d, e, x;
uchar *end;
u32int *wp, *wend;
u32int w[80];
/* at this point, we have a multiple of 64 bytes */
for(end = p+len; p < end;){
a = s[0];
b = s[1];
c = s[2];
d = s[3];
e = s[4];
wend = w + 15;
for(wp = w; wp < wend; wp += 5){
wp[0] = (p[0]<<24) | (p[1]<<16) | (p[2]<<8) | p[3];
e += ((a<<5) | (a>>27)) + wp[0];
e += 0x5a827999 + (((c^d)&b)^d);
b = (b<<30)|(b>>2);
wp[1] = (p[4]<<24) | (p[5]<<16) | (p[6]<<8) | p[7];
d += ((e<<5) | (e>>27)) + wp[1];
d += 0x5a827999 + (((b^c)&a)^c);
a = (a<<30)|(a>>2);
wp[2] = (p[8]<<24) | (p[9]<<16) | (p[10]<<8) | p[11];
c += ((d<<5) | (d>>27)) + wp[2];
c += 0x5a827999 + (((a^b)&e)^b);
e = (e<<30)|(e>>2);
wp[3] = (p[12]<<24) | (p[13]<<16) | (p[14]<<8) | p[15];
b += ((c<<5) | (c>>27)) + wp[3];
b += 0x5a827999 + (((e^a)&d)^a);
d = (d<<30)|(d>>2);
wp[4] = (p[16]<<24) | (p[17]<<16) | (p[18]<<8) | p[19];
a += ((b<<5) | (b>>27)) + wp[4];
a += 0x5a827999 + (((d^e)&c)^e);
c = (c<<30)|(c>>2);
p += 20;
}
wp[0] = (p[0]<<24) | (p[1]<<16) | (p[2]<<8) | p[3];
e += ((a<<5) | (a>>27)) + wp[0];
e += 0x5a827999 + (((c^d)&b)^d);
b = (b<<30)|(b>>2);
x = wp[-2] ^ wp[-7] ^ wp[-13] ^ wp[-15];
wp[1] = (x<<1) | (x>>31);
d += ((e<<5) | (e>>27)) + wp[1];
d += 0x5a827999 + (((b^c)&a)^c);
a = (a<<30)|(a>>2);
x = wp[-1] ^ wp[-6] ^ wp[-12] ^ wp[-14];
wp[2] = (x<<1) | (x>>31);
c += ((d<<5) | (d>>27)) + wp[2];
c += 0x5a827999 + (((a^b)&e)^b);
e = (e<<30)|(e>>2);
x = wp[0] ^ wp[-5] ^ wp[-11] ^ wp[-13];
wp[3] = (x<<1) | (x>>31);
b += ((c<<5) | (c>>27)) + wp[3];
b += 0x5a827999 + (((e^a)&d)^a);
d = (d<<30)|(d>>2);
x = wp[1] ^ wp[-4] ^ wp[-10] ^ wp[-12];
wp[4] = (x<<1) | (x>>31);
a += ((b<<5) | (b>>27)) + wp[4];
a += 0x5a827999 + (((d^e)&c)^e);
c = (c<<30)|(c>>2);
wp += 5;
p += 4;
wend = w + 40;
for(; wp < wend; wp += 5){
x = wp[-3] ^ wp[-8] ^ wp[-14] ^ wp[-16];
wp[0] = (x<<1) | (x>>31);
e += ((a<<5) | (a>>27)) + wp[0];
e += 0x6ed9eba1 + (b^c^d);
b = (b<<30)|(b>>2);
x = wp[-2] ^ wp[-7] ^ wp[-13] ^ wp[-15];
wp[1] = (x<<1) | (x>>31);
d += ((e<<5) | (e>>27)) + wp[1];
d += 0x6ed9eba1 + (a^b^c);
a = (a<<30)|(a>>2);
x = wp[-1] ^ wp[-6] ^ wp[-12] ^ wp[-14];
wp[2] = (x<<1) | (x>>31);
c += ((d<<5) | (d>>27)) + wp[2];
c += 0x6ed9eba1 + (e^a^b);
e = (e<<30)|(e>>2);
x = wp[0] ^ wp[-5] ^ wp[-11] ^ wp[-13];
wp[3] = (x<<1) | (x>>31);
b += ((c<<5) | (c>>27)) + wp[3];
b += 0x6ed9eba1 + (d^e^a);
d = (d<<30)|(d>>2);
x = wp[1] ^ wp[-4] ^ wp[-10] ^ wp[-12];
wp[4] = (x<<1) | (x>>31);
a += ((b<<5) | (b>>27)) + wp[4];
a += 0x6ed9eba1 + (c^d^e);
c = (c<<30)|(c>>2);
}
wend = w + 60;
for(; wp < wend; wp += 5){
x = wp[-3] ^ wp[-8] ^ wp[-14] ^ wp[-16];
wp[0] = (x<<1) | (x>>31);
e += ((a<<5) | (a>>27)) + wp[0];
e += 0x8f1bbcdc + ((b&c)|((b|c)&d));
b = (b<<30)|(b>>2);
x = wp[-2] ^ wp[-7] ^ wp[-13] ^ wp[-15];
wp[1] = (x<<1) | (x>>31);
d += ((e<<5) | (e>>27)) + wp[1];
d += 0x8f1bbcdc + ((a&b)|((a|b)&c));
a = (a<<30)|(a>>2);
x = wp[-1] ^ wp[-6] ^ wp[-12] ^ wp[-14];
wp[2] = (x<<1) | (x>>31);
c += ((d<<5) | (d>>27)) + wp[2];
c += 0x8f1bbcdc + ((e&a)|((e|a)&b));
e = (e<<30)|(e>>2);
x = wp[0] ^ wp[-5] ^ wp[-11] ^ wp[-13];
wp[3] = (x<<1) | (x>>31);
b += ((c<<5) | (c>>27)) + wp[3];
b += 0x8f1bbcdc + ((d&e)|((d|e)&a));
d = (d<<30)|(d>>2);
x = wp[1] ^ wp[-4] ^ wp[-10] ^ wp[-12];
wp[4] = (x<<1) | (x>>31);
a += ((b<<5) | (b>>27)) + wp[4];
a += 0x8f1bbcdc + ((c&d)|((c|d)&e));
c = (c<<30)|(c>>2);
}
wend = w + 80;
for(; wp < wend; wp += 5){
x = wp[-3] ^ wp[-8] ^ wp[-14] ^ wp[-16];
wp[0] = (x<<1) | (x>>31);
e += ((a<<5) | (a>>27)) + wp[0];
e += 0xca62c1d6 + (b^c^d);
b = (b<<30)|(b>>2);
x = wp[-2] ^ wp[-7] ^ wp[-13] ^ wp[-15];
wp[1] = (x<<1) | (x>>31);
d += ((e<<5) | (e>>27)) + wp[1];
d += 0xca62c1d6 + (a^b^c);
a = (a<<30)|(a>>2);
x = wp[-1] ^ wp[-6] ^ wp[-12] ^ wp[-14];
wp[2] = (x<<1) | (x>>31);
c += ((d<<5) | (d>>27)) + wp[2];
c += 0xca62c1d6 + (e^a^b);
e = (e<<30)|(e>>2);
x = wp[0] ^ wp[-5] ^ wp[-11] ^ wp[-13];
wp[3] = (x<<1) | (x>>31);
b += ((c<<5) | (c>>27)) + wp[3];
b += 0xca62c1d6 + (d^e^a);
d = (d<<30)|(d>>2);
x = wp[1] ^ wp[-4] ^ wp[-10] ^ wp[-12];
wp[4] = (x<<1) | (x>>31);
a += ((b<<5) | (b>>27)) + wp[4];
a += 0xca62c1d6 + (c^d^e);
c = (c<<30)|(c>>2);
}
/* save state */
s[0] += a;
s[1] += b;
s[2] += c;
s[3] += d;
s[4] += e;
}
}

38
libsec/sha1pickle.c Normal file
View File

@ -0,0 +1,38 @@
#include "os.h"
#include <libsec.h>
char*
sha1pickle(SHA1state *s)
{
char *p;
int m, n;
m = 5*9+4*((s->blen+3)/3);
p = malloc(m);
if(p == nil)
return p;
n = sprint(p, "%8.8ux %8.8ux %8.8ux %8.8ux %8.8ux ",
s->state[0], s->state[1], s->state[2],
s->state[3], s->state[4]);
enc64(p+n, m-n, s->buf, s->blen);
return p;
}
SHA1state*
sha1unpickle(char *p)
{
SHA1state *s;
s = malloc(sizeof(*s));
if(s == nil)
return nil;
s->state[0] = strtoul(p, &p, 16);
s->state[1] = strtoul(p, &p, 16);
s->state[2] = strtoul(p, &p, 16);
s->state[3] = strtoul(p, &p, 16);
s->state[4] = strtoul(p, &p, 16);
s->blen = dec64(s->buf, sizeof(s->buf), p, strlen(p));
s->malloced = 1;
s->seeded = 1;
return s;
}

1004
libsec/smallprimes.c Normal file

File diff suppressed because it is too large Load Diff

1039
libsec/smallprimetest.c Normal file

File diff suppressed because it is too large Load Diff

97
libsec/thumb.c Normal file
View File

@ -0,0 +1,97 @@
#include <u.h>
#include <libc.h>
#include <bio.h>
#include <auth.h>
#include <mp.h>
#include <libsec.h>
enum{ ThumbTab = 1<<10 };
static void *
emalloc(int n)
{
void *p;
if(n==0)
n=1;
p = malloc(n);
if(p == nil){
exits("out of memory");
}
memset(p, 0, n);
return p;
}
void
freeThumbprints(Thumbprint *table)
{
Thumbprint *hd, *p, *q;
for(hd = table; hd < table+ThumbTab; hd++){
for(p = hd->next; p; p = q){
q = p->next;
free(p);
}
}
free(table);
}
int
okThumbprint(uchar *sum, Thumbprint *table)
{
Thumbprint *p;
int i = ((sum[0]<<8) + sum[1]) & (ThumbTab-1);
for(p = table[i].next; p; p = p->next)
if(memcmp(sum, p->sha1, SHA1dlen) == 0)
return 1;
return 0;
}
static void
loadThumbprints(char *file, Thumbprint *table, Thumbprint *crltab)
{
Thumbprint *entry;
Biobuf *bin;
char *line, *field[50];
uchar sum[SHA1dlen];
int i;
bin = Bopen(file, OREAD);
if(bin == nil)
return;
for(; (line = Brdstr(bin, '\n', 1)) != 0; free(line)){
if(tokenize(line, field, nelem(field)) < 2)
continue;
if(strcmp(field[0], "#include") == 0){
loadThumbprints(field[1], table, crltab);
continue;
}
if(strcmp(field[0], "x509") != 0 || strncmp(field[1], "sha1=", strlen("sha1=")) != 0)
continue;
field[1] += strlen("sha1=");
dec16(sum, sizeof(sum), field[1], strlen(field[1]));
if(crltab && okThumbprint(sum, crltab))
continue;
entry = (Thumbprint*)emalloc(sizeof(*entry));
memcpy(entry->sha1, sum, SHA1dlen);
i = ((sum[0]<<8) + sum[1]) & (ThumbTab-1);
entry->next = table[i].next;
table[i].next = entry;
}
Bterm(bin);
}
Thumbprint *
initThumbprints(char *ok, char *crl)
{
Thumbprint *table, *crltab = nil;
if(crl){
crltab = emalloc(ThumbTab * sizeof(*table));
loadThumbprints(crl, crltab, nil);
}
table = emalloc(ThumbTab * sizeof(*table));
loadThumbprints(ok, table, crltab);
free(crltab);
return table;
}

2291
libsec/tlshand.c Normal file

File diff suppressed because it is too large Load Diff

2520
libsec/x509.c Normal file

File diff suppressed because it is too large Load Diff