Add most of libsec.
diff --git a/src/libsec/port/blowfish.c b/src/libsec/port/blowfish.c
new file mode 100644
index 0000000..5dcc677
--- /dev/null
+++ b/src/libsec/port/blowfish.c
@@ -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, 
+};
+
+
diff --git a/src/libsec/port/decodepem.c b/src/libsec/port/decodepem.c
new file mode 100644
index 0000000..194a455
--- /dev/null
+++ b/src/libsec/port/decodepem.c
@@ -0,0 +1,61 @@
+#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;
+
+	*len = 0;
+
+	/*
+	 * 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;
+}
diff --git a/src/libsec/port/des3CBC.c b/src/libsec/port/des3CBC.c
new file mode 100644
index 0000000..2632930
--- /dev/null
+++ b/src/libsec/port/des3CBC.c
@@ -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++;
+	}
+}
diff --git a/src/libsec/port/des3ECB.c b/src/libsec/port/des3ECB.c
new file mode 100644
index 0000000..324254b
--- /dev/null
+++ b/src/libsec/port/des3ECB.c
@@ -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];
+	}
+}
diff --git a/src/libsec/port/desCBC.c b/src/libsec/port/desCBC.c
new file mode 100644
index 0000000..ecee29e
--- /dev/null
+++ b/src/libsec/port/desCBC.c
@@ -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++;
+	}
+}
diff --git a/src/libsec/port/desECB.c b/src/libsec/port/desECB.c
new file mode 100644
index 0000000..a9ad001
--- /dev/null
+++ b/src/libsec/port/desECB.c
@@ -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];
+	}
+}
diff --git a/src/libsec/port/dsaalloc.c b/src/libsec/port/dsaalloc.c
new file mode 100644
index 0000000..d82ab3d
--- /dev/null
+++ b/src/libsec/port/dsaalloc.c
@@ -0,0 +1,72 @@
+#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);
+	free(dsa);
+}
+
+
+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);
+	free(dsa);
+}
+
+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);
+	free(dsa);
+}
diff --git a/src/libsec/port/dsagen.c b/src/libsec/port/dsagen.c
new file mode 100644
index 0000000..46c369e
--- /dev/null
+++ b/src/libsec/port/dsagen.c
@@ -0,0 +1,58 @@
+#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.
+	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;
+}
diff --git a/src/libsec/port/dsaprimes.c b/src/libsec/port/dsaprimes.c
new file mode 100644
index 0000000..ff1dd5d
--- /dev/null
+++ b/src/libsec/port/dsaprimes.c
@@ -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);
+}
diff --git a/src/libsec/port/dsaprivtopub.c b/src/libsec/port/dsaprivtopub.c
new file mode 100644
index 0000000..e1790ca
--- /dev/null
+++ b/src/libsec/port/dsaprivtopub.c
@@ -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;
+}
diff --git a/src/libsec/port/dsasign.c b/src/libsec/port/dsasign.c
new file mode 100644
index 0000000..137134b
--- /dev/null
+++ b/src/libsec/port/dsasign.c
@@ -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, pub->q) >= 0))
+			continue;
+		mpextendedgcd(k, q, r, kinv, s);
+		if(mpcmp(r, mpone) != 0)
+			sysfatal("dsasign: pub->q not prime");
+		break;
+	}
+
+  	// make kinv positive
+	mpmod(kinv, pub->q, 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;
+}
diff --git a/src/libsec/port/dsaverify.c b/src/libsec/port/dsaverify.c
new file mode 100644
index 0000000..70e7f3c
--- /dev/null
+++ b/src/libsec/port/dsaverify.c
@@ -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(mpcmp(sig->r, mpone) < 0 || mpcmp(sig->r, pub->q) >= 0)
+		return rv;
+	if(mpcmp(sig->s, mpone) < 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;
+}
diff --git a/src/libsec/port/egalloc.c b/src/libsec/port/egalloc.c
new file mode 100644
index 0000000..3f0753d
--- /dev/null
+++ b/src/libsec/port/egalloc.c
@@ -0,0 +1,70 @@
+#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);
+	free(eg);
+}
+
+
+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);
+	free(eg);
+}
+
+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);
+	free(eg);
+}
diff --git a/src/libsec/port/egdecrypt.c b/src/libsec/port/egdecrypt.c
new file mode 100644
index 0000000..2457880
--- /dev/null
+++ b/src/libsec/port/egdecrypt.c
@@ -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;
+}
diff --git a/src/libsec/port/egencrypt.c b/src/libsec/port/egencrypt.c
new file mode 100644
index 0000000..9b6b12c
--- /dev/null
+++ b/src/libsec/port/egencrypt.c
@@ -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;
+}
diff --git a/src/libsec/port/eggen.c b/src/libsec/port/eggen.c
new file mode 100644
index 0000000..9ea7d99
--- /dev/null
+++ b/src/libsec/port/eggen.c
@@ -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;
+}
diff --git a/src/libsec/port/egprivtopub.c b/src/libsec/port/egprivtopub.c
new file mode 100644
index 0000000..e22c5c3
--- /dev/null
+++ b/src/libsec/port/egprivtopub.c
@@ -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;
+}
diff --git a/src/libsec/port/egsign.c b/src/libsec/port/egsign.c
new file mode 100644
index 0000000..1054004
--- /dev/null
+++ b/src/libsec/port/egsign.c
@@ -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;
+}
diff --git a/src/libsec/port/egtest.c b/src/libsec/port/egtest.c
new file mode 100644
index 0000000..41b438d
--- /dev/null
+++ b/src/libsec/port/egtest.c
@@ -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");
+}
diff --git a/src/libsec/port/egverify.c b/src/libsec/port/egverify.c
new file mode 100644
index 0000000..29a9515
--- /dev/null
+++ b/src/libsec/port/egverify.c
@@ -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;
+}
diff --git a/src/libsec/port/genprime.c b/src/libsec/port/genprime.c
new file mode 100644
index 0000000..c0e16d9
--- /dev/null
+++ b/src/libsec/port/genprime.c
@@ -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);
+	}
+}
diff --git a/src/libsec/port/gensafeprime.c b/src/libsec/port/gensafeprime.c
new file mode 100644
index 0000000..e95c94c
--- /dev/null
+++ b/src/libsec/port/gensafeprime.c
@@ -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);
+}
diff --git a/src/libsec/port/genstrongprime.c b/src/libsec/port/genstrongprime.c
new file mode 100644
index 0000000..27c43a9
--- /dev/null
+++ b/src/libsec/port/genstrongprime.c
@@ -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);
+}
diff --git a/src/libsec/port/hmac.c b/src/libsec/port/hmac.c
new file mode 100644
index 0000000..c723973
--- /dev/null
+++ b/src/libsec/port/hmac.c
@@ -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);
+}
diff --git a/src/libsec/port/hmactest.c b/src/libsec/port/hmactest.c
new file mode 100644
index 0000000..8c7d896
--- /dev/null
+++ b/src/libsec/port/hmactest.c
@@ -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");
+}
diff --git a/src/libsec/port/md4.c b/src/libsec/port/md4.c
new file mode 100644
index 0000000..c4a2f32
--- /dev/null
+++ b/src/libsec/port/md4.c
@@ -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);
+}
diff --git a/src/libsec/port/md4test.c b/src/libsec/port/md4test.c
new file mode 100644
index 0000000..417cb33
--- /dev/null
+++ b/src/libsec/port/md4test.c
@@ -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");
+	}
+}
diff --git a/src/libsec/port/md5pickle.c b/src/libsec/port/md5pickle.c
new file mode 100644
index 0000000..5b353b5
--- /dev/null
+++ b/src/libsec/port/md5pickle.c
@@ -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;
+}
diff --git a/src/libsec/port/nfastrand.c b/src/libsec/port/nfastrand.c
new file mode 100644
index 0000000..3ba7700
--- /dev/null
+++ b/src/libsec/port/nfastrand.c
@@ -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)
+		sysfatal("nfastrand: n too large");
+
+	m = Maxrand - Maxrand % n;
+	while((r = fastrand()) >= m)
+		;
+	return r%n;
+}
diff --git a/src/libsec/port/primetest.c b/src/libsec/port/primetest.c
new file mode 100644
index 0000000..2d082e6
--- /dev/null
+++ b/src/libsec/port/primetest.c
@@ -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
diff --git a/src/libsec/port/prng.c b/src/libsec/port/prng.c
new file mode 100644
index 0000000..fc2e508
--- /dev/null
+++ b/src/libsec/port/prng.c
@@ -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();
+}
diff --git a/src/libsec/port/probably_prime.c b/src/libsec/port/probably_prime.c
new file mode 100644
index 0000000..4eaccba
--- /dev/null
+++ b/src/libsec/port/probably_prime.c
@@ -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;
+}
diff --git a/src/libsec/port/rc4.c b/src/libsec/port/rc4.c
new file mode 100644
index 0000000..beafa48
--- /dev/null
+++ b/src/libsec/port/rc4.c
@@ -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;
+}
diff --git a/src/libsec/port/readcert.c b/src/libsec/port/readcert.c
new file mode 100644
index 0000000..9ba801f
--- /dev/null
+++ b/src/libsec/port/readcert.c
@@ -0,0 +1,51 @@
+#include <u.h>
+#include <libc.h>
+#include <auth.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;
+}
+
diff --git a/src/libsec/port/rsaalloc.c b/src/libsec/port/rsaalloc.c
new file mode 100644
index 0000000..0caa96d
--- /dev/null
+++ b/src/libsec/port/rsaalloc.c
@@ -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);
+}
diff --git a/src/libsec/port/rsadecrypt.c b/src/libsec/port/rsadecrypt.c
new file mode 100644
index 0000000..1e937be
--- /dev/null
+++ b/src/libsec/port/rsadecrypt.c
@@ -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;
+}
diff --git a/src/libsec/port/rsaencrypt.c b/src/libsec/port/rsaencrypt.c
new file mode 100644
index 0000000..ade686d
--- /dev/null
+++ b/src/libsec/port/rsaencrypt.c
@@ -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;
+}
diff --git a/src/libsec/port/rsafill.c b/src/libsec/port/rsafill.c
new file mode 100644
index 0000000..f514b07
--- /dev/null
+++ b/src/libsec/port/rsafill.c
@@ -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;
+}
+
diff --git a/src/libsec/port/rsagen.c b/src/libsec/port/rsagen.c
new file mode 100644
index 0000000..ebe1079
--- /dev/null
+++ b/src/libsec/port/rsagen.c
@@ -0,0 +1,70 @@
+#include "os.h"
+#include <mp.h>
+#include <libsec.h>
+
+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
+	genprime(p, nlen/2, rounds);
+	genprime(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);
+	mprand(elen, genrandom, e);
+	if(mpcmp(e,mptwo) <= 0)
+		itomp(3, e);
+	// See Menezes et al. p.291 "8.8 Note (selecting primes)" for discussion
+	// of the merits of various choices of primes and exponents.  e=3 is a
+	// common and recommended exponent, but doesn't necessarily work here
+	// because we chose strong rather than safe primes.
+	for(;;){
+		mpextendedgcd(e, phi, t1, d, t2);
+		if(mpcmp(t1, mpone) == 0)
+			break;
+		mpadd(mpone, e, e);
+	}
+	mpfree(t1);
+	mpfree(t2);
+
+	// 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;
+}
diff --git a/src/libsec/port/rsaprivtopub.c b/src/libsec/port/rsaprivtopub.c
new file mode 100644
index 0000000..d464c87
--- /dev/null
+++ b/src/libsec/port/rsaprivtopub.c
@@ -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;
+}
diff --git a/src/libsec/port/rsatest.c b/src/libsec/port/rsatest.c
new file mode 100644
index 0000000..9ff66b5
--- /dev/null
+++ b/src/libsec/port/rsatest.c
@@ -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("> ");
+	}
+}
diff --git a/src/libsec/port/sha1pickle.c b/src/libsec/port/sha1pickle.c
new file mode 100644
index 0000000..6139567
--- /dev/null
+++ b/src/libsec/port/sha1pickle.c
@@ -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;
+}
diff --git a/src/libsec/port/smallprimes.c b/src/libsec/port/smallprimes.c
new file mode 100644
index 0000000..ac23a2f
--- /dev/null
+++ b/src/libsec/port/smallprimes.c
@@ -0,0 +1,1004 @@
+#include "os.h"
+
+ulong smallprimes[1000] = {
+	2,
+	3,
+	5,
+	7,
+	11,
+	13,
+	17,
+	19,
+	23,
+	29,
+	31,
+	37,
+	41,
+	43,
+	47,
+	53,
+	59,
+	61,
+	67,
+	71,
+	73,
+	79,
+	83,
+	89,
+	97,
+	101,
+	103,
+	107,
+	109,
+	113,
+	127,
+	131,
+	137,
+	139,
+	149,
+	151,
+	157,
+	163,
+	167,
+	173,
+	179,
+	181,
+	191,
+	193,
+	197,
+	199,
+	211,
+	223,
+	227,
+	229,
+	233,
+	239,
+	241,
+	251,
+	257,
+	263,
+	269,
+	271,
+	277,
+	281,
+	283,
+	293,
+	307,
+	311,
+	313,
+	317,
+	331,
+	337,
+	347,
+	349,
+	353,
+	359,
+	367,
+	373,
+	379,
+	383,
+	389,
+	397,
+	401,
+	409,
+	419,
+	421,
+	431,
+	433,
+	439,
+	443,
+	449,
+	457,
+	461,
+	463,
+	467,
+	479,
+	487,
+	491,
+	499,
+	503,
+	509,
+	521,
+	523,
+	541,
+	547,
+	557,
+	563,
+	569,
+	571,
+	577,
+	587,
+	593,
+	599,
+	601,
+	607,
+	613,
+	617,
+	619,
+	631,
+	641,
+	643,
+	647,
+	653,
+	659,
+	661,
+	673,
+	677,
+	683,
+	691,
+	701,
+	709,
+	719,
+	727,
+	733,
+	739,
+	743,
+	751,
+	757,
+	761,
+	769,
+	773,
+	787,
+	797,
+	809,
+	811,
+	821,
+	823,
+	827,
+	829,
+	839,
+	853,
+	857,
+	859,
+	863,
+	877,
+	881,
+	883,
+	887,
+	907,
+	911,
+	919,
+	929,
+	937,
+	941,
+	947,
+	953,
+	967,
+	971,
+	977,
+	983,
+	991,
+	997,
+	1009,
+	1013,
+	1019,
+	1021,
+	1031,
+	1033,
+	1039,
+	1049,
+	1051,
+	1061,
+	1063,
+	1069,
+	1087,
+	1091,
+	1093,
+	1097,
+	1103,
+	1109,
+	1117,
+	1123,
+	1129,
+	1151,
+	1153,
+	1163,
+	1171,
+	1181,
+	1187,
+	1193,
+	1201,
+	1213,
+	1217,
+	1223,
+	1229,
+	1231,
+	1237,
+	1249,
+	1259,
+	1277,
+	1279,
+	1283,
+	1289,
+	1291,
+	1297,
+	1301,
+	1303,
+	1307,
+	1319,
+	1321,
+	1327,
+	1361,
+	1367,
+	1373,
+	1381,
+	1399,
+	1409,
+	1423,
+	1427,
+	1429,
+	1433,
+	1439,
+	1447,
+	1451,
+	1453,
+	1459,
+	1471,
+	1481,
+	1483,
+	1487,
+	1489,
+	1493,
+	1499,
+	1511,
+	1523,
+	1531,
+	1543,
+	1549,
+	1553,
+	1559,
+	1567,
+	1571,
+	1579,
+	1583,
+	1597,
+	1601,
+	1607,
+	1609,
+	1613,
+	1619,
+	1621,
+	1627,
+	1637,
+	1657,
+	1663,
+	1667,
+	1669,
+	1693,
+	1697,
+	1699,
+	1709,
+	1721,
+	1723,
+	1733,
+	1741,
+	1747,
+	1753,
+	1759,
+	1777,
+	1783,
+	1787,
+	1789,
+	1801,
+	1811,
+	1823,
+	1831,
+	1847,
+	1861,
+	1867,
+	1871,
+	1873,
+	1877,
+	1879,
+	1889,
+	1901,
+	1907,
+	1913,
+	1931,
+	1933,
+	1949,
+	1951,
+	1973,
+	1979,
+	1987,
+	1993,
+	1997,
+	1999,
+	2003,
+	2011,
+	2017,
+	2027,
+	2029,
+	2039,
+	2053,
+	2063,
+	2069,
+	2081,
+	2083,
+	2087,
+	2089,
+	2099,
+	2111,
+	2113,
+	2129,
+	2131,
+	2137,
+	2141,
+	2143,
+	2153,
+	2161,
+	2179,
+	2203,
+	2207,
+	2213,
+	2221,
+	2237,
+	2239,
+	2243,
+	2251,
+	2267,
+	2269,
+	2273,
+	2281,
+	2287,
+	2293,
+	2297,
+	2309,
+	2311,
+	2333,
+	2339,
+	2341,
+	2347,
+	2351,
+	2357,
+	2371,
+	2377,
+	2381,
+	2383,
+	2389,
+	2393,
+	2399,
+	2411,
+	2417,
+	2423,
+	2437,
+	2441,
+	2447,
+	2459,
+	2467,
+	2473,
+	2477,
+	2503,
+	2521,
+	2531,
+	2539,
+	2543,
+	2549,
+	2551,
+	2557,
+	2579,
+	2591,
+	2593,
+	2609,
+	2617,
+	2621,
+	2633,
+	2647,
+	2657,
+	2659,
+	2663,
+	2671,
+	2677,
+	2683,
+	2687,
+	2689,
+	2693,
+	2699,
+	2707,
+	2711,
+	2713,
+	2719,
+	2729,
+	2731,
+	2741,
+	2749,
+	2753,
+	2767,
+	2777,
+	2789,
+	2791,
+	2797,
+	2801,
+	2803,
+	2819,
+	2833,
+	2837,
+	2843,
+	2851,
+	2857,
+	2861,
+	2879,
+	2887,
+	2897,
+	2903,
+	2909,
+	2917,
+	2927,
+	2939,
+	2953,
+	2957,
+	2963,
+	2969,
+	2971,
+	2999,
+	3001,
+	3011,
+	3019,
+	3023,
+	3037,
+	3041,
+	3049,
+	3061,
+	3067,
+	3079,
+	3083,
+	3089,
+	3109,
+	3119,
+	3121,
+	3137,
+	3163,
+	3167,
+	3169,
+	3181,
+	3187,
+	3191,
+	3203,
+	3209,
+	3217,
+	3221,
+	3229,
+	3251,
+	3253,
+	3257,
+	3259,
+	3271,
+	3299,
+	3301,
+	3307,
+	3313,
+	3319,
+	3323,
+	3329,
+	3331,
+	3343,
+	3347,
+	3359,
+	3361,
+	3371,
+	3373,
+	3389,
+	3391,
+	3407,
+	3413,
+	3433,
+	3449,
+	3457,
+	3461,
+	3463,
+	3467,
+	3469,
+	3491,
+	3499,
+	3511,
+	3517,
+	3527,
+	3529,
+	3533,
+	3539,
+	3541,
+	3547,
+	3557,
+	3559,
+	3571,
+	3581,
+	3583,
+	3593,
+	3607,
+	3613,
+	3617,
+	3623,
+	3631,
+	3637,
+	3643,
+	3659,
+	3671,
+	3673,
+	3677,
+	3691,
+	3697,
+	3701,
+	3709,
+	3719,
+	3727,
+	3733,
+	3739,
+	3761,
+	3767,
+	3769,
+	3779,
+	3793,
+	3797,
+	3803,
+	3821,
+	3823,
+	3833,
+	3847,
+	3851,
+	3853,
+	3863,
+	3877,
+	3881,
+	3889,
+	3907,
+	3911,
+	3917,
+	3919,
+	3923,
+	3929,
+	3931,
+	3943,
+	3947,
+	3967,
+	3989,
+	4001,
+	4003,
+	4007,
+	4013,
+	4019,
+	4021,
+	4027,
+	4049,
+	4051,
+	4057,
+	4073,
+	4079,
+	4091,
+	4093,
+	4099,
+	4111,
+	4127,
+	4129,
+	4133,
+	4139,
+	4153,
+	4157,
+	4159,
+	4177,
+	4201,
+	4211,
+	4217,
+	4219,
+	4229,
+	4231,
+	4241,
+	4243,
+	4253,
+	4259,
+	4261,
+	4271,
+	4273,
+	4283,
+	4289,
+	4297,
+	4327,
+	4337,
+	4339,
+	4349,
+	4357,
+	4363,
+	4373,
+	4391,
+	4397,
+	4409,
+	4421,
+	4423,
+	4441,
+	4447,
+	4451,
+	4457,
+	4463,
+	4481,
+	4483,
+	4493,
+	4507,
+	4513,
+	4517,
+	4519,
+	4523,
+	4547,
+	4549,
+	4561,
+	4567,
+	4583,
+	4591,
+	4597,
+	4603,
+	4621,
+	4637,
+	4639,
+	4643,
+	4649,
+	4651,
+	4657,
+	4663,
+	4673,
+	4679,
+	4691,
+	4703,
+	4721,
+	4723,
+	4729,
+	4733,
+	4751,
+	4759,
+	4783,
+	4787,
+	4789,
+	4793,
+	4799,
+	4801,
+	4813,
+	4817,
+	4831,
+	4861,
+	4871,
+	4877,
+	4889,
+	4903,
+	4909,
+	4919,
+	4931,
+	4933,
+	4937,
+	4943,
+	4951,
+	4957,
+	4967,
+	4969,
+	4973,
+	4987,
+	4993,
+	4999,
+	5003,
+	5009,
+	5011,
+	5021,
+	5023,
+	5039,
+	5051,
+	5059,
+	5077,
+	5081,
+	5087,
+	5099,
+	5101,
+	5107,
+	5113,
+	5119,
+	5147,
+	5153,
+	5167,
+	5171,
+	5179,
+	5189,
+	5197,
+	5209,
+	5227,
+	5231,
+	5233,
+	5237,
+	5261,
+	5273,
+	5279,
+	5281,
+	5297,
+	5303,
+	5309,
+	5323,
+	5333,
+	5347,
+	5351,
+	5381,
+	5387,
+	5393,
+	5399,
+	5407,
+	5413,
+	5417,
+	5419,
+	5431,
+	5437,
+	5441,
+	5443,
+	5449,
+	5471,
+	5477,
+	5479,
+	5483,
+	5501,
+	5503,
+	5507,
+	5519,
+	5521,
+	5527,
+	5531,
+	5557,
+	5563,
+	5569,
+	5573,
+	5581,
+	5591,
+	5623,
+	5639,
+	5641,
+	5647,
+	5651,
+	5653,
+	5657,
+	5659,
+	5669,
+	5683,
+	5689,
+	5693,
+	5701,
+	5711,
+	5717,
+	5737,
+	5741,
+	5743,
+	5749,
+	5779,
+	5783,
+	5791,
+	5801,
+	5807,
+	5813,
+	5821,
+	5827,
+	5839,
+	5843,
+	5849,
+	5851,
+	5857,
+	5861,
+	5867,
+	5869,
+	5879,
+	5881,
+	5897,
+	5903,
+	5923,
+	5927,
+	5939,
+	5953,
+	5981,
+	5987,
+	6007,
+	6011,
+	6029,
+	6037,
+	6043,
+	6047,
+	6053,
+	6067,
+	6073,
+	6079,
+	6089,
+	6091,
+	6101,
+	6113,
+	6121,
+	6131,
+	6133,
+	6143,
+	6151,
+	6163,
+	6173,
+	6197,
+	6199,
+	6203,
+	6211,
+	6217,
+	6221,
+	6229,
+	6247,
+	6257,
+	6263,
+	6269,
+	6271,
+	6277,
+	6287,
+	6299,
+	6301,
+	6311,
+	6317,
+	6323,
+	6329,
+	6337,
+	6343,
+	6353,
+	6359,
+	6361,
+	6367,
+	6373,
+	6379,
+	6389,
+	6397,
+	6421,
+	6427,
+	6449,
+	6451,
+	6469,
+	6473,
+	6481,
+	6491,
+	6521,
+	6529,
+	6547,
+	6551,
+	6553,
+	6563,
+	6569,
+	6571,
+	6577,
+	6581,
+	6599,
+	6607,
+	6619,
+	6637,
+	6653,
+	6659,
+	6661,
+	6673,
+	6679,
+	6689,
+	6691,
+	6701,
+	6703,
+	6709,
+	6719,
+	6733,
+	6737,
+	6761,
+	6763,
+	6779,
+	6781,
+	6791,
+	6793,
+	6803,
+	6823,
+	6827,
+	6829,
+	6833,
+	6841,
+	6857,
+	6863,
+	6869,
+	6871,
+	6883,
+	6899,
+	6907,
+	6911,
+	6917,
+	6947,
+	6949,
+	6959,
+	6961,
+	6967,
+	6971,
+	6977,
+	6983,
+	6991,
+	6997,
+	7001,
+	7013,
+	7019,
+	7027,
+	7039,
+	7043,
+	7057,
+	7069,
+	7079,
+	7103,
+	7109,
+	7121,
+	7127,
+	7129,
+	7151,
+	7159,
+	7177,
+	7187,
+	7193,
+	7207,
+	7211,
+	7213,
+	7219,
+	7229,
+	7237,
+	7243,
+	7247,
+	7253,
+	7283,
+	7297,
+	7307,
+	7309,
+	7321,
+	7331,
+	7333,
+	7349,
+	7351,
+	7369,
+	7393,
+	7411,
+	7417,
+	7433,
+	7451,
+	7457,
+	7459,
+	7477,
+	7481,
+	7487,
+	7489,
+	7499,
+	7507,
+	7517,
+	7523,
+	7529,
+	7537,
+	7541,
+	7547,
+	7549,
+	7559,
+	7561,
+	7573,
+	7577,
+	7583,
+	7589,
+	7591,
+	7603,
+	7607,
+	7621,
+	7639,
+	7643,
+	7649,
+	7669,
+	7673,
+	7681,
+	7687,
+	7691,
+	7699,
+	7703,
+	7717,
+	7723,
+	7727,
+	7741,
+	7753,
+	7757,
+	7759,
+	7789,
+	7793,
+	7817,
+	7823,
+	7829,
+	7841,
+	7853,
+	7867,
+	7873,
+	7877,
+	7879,
+	7883,
+	7901,
+	7907,
+	7919,
+};
diff --git a/src/libsec/port/smallprimetest.c b/src/libsec/port/smallprimetest.c
new file mode 100644
index 0000000..cf94dac
--- /dev/null
+++ b/src/libsec/port/smallprimetest.c
@@ -0,0 +1,1039 @@
+#include "os.h"
+#include <mp.h>
+#include <libsec.h>
+
+static ulong smallprimes[] = {
+	2,	3,	5,	7,	11,	13,	17,	19,	23,	29,
+	31,	37,	41,	43,	47,	53,	59,	61,	67,	71,
+	73,	79,	83,	89,	97,	101,	103,	107,	109,	113,
+	127,	131,	137,	139,	149,	151,	157,	163,	167,	173,
+	179,	181,	191,	193,	197,	199,	211,	223,	227,	229,
+	233,	239,	241,	251,	257,	263,	269,	271,	277,	281,
+	283,	293,	307,	311,	313,	317,	331,	337,	347,	349,
+	353,	359,	367,	373,	379,	383,	389,	397,	401,	409,
+	419,	421,	431,	433,	439,	443,	449,	457,	461,	463,
+	467,	479,	487,	491,	499,	503,	509,	521,	523,	541,
+	547,	557,	563,	569,	571,	577,	587,	593,	599,	601,
+	607,	613,	617,	619,	631,	641,	643,	647,	653,	659,
+	661,	673,	677,	683,	691,	701,	709,	719,	727,	733,
+	739,	743,	751,	757,	761,	769,	773,	787,	797,	809,
+	811,	821,	823,	827,	829,	839,	853,	857,	859,	863,
+	877,	881,	883,	887,	907,	911,	919,	929,	937,	941,
+	947,	953,	967,	971,	977,	983,	991,	997,	1009,	1013,
+	1019,	1021,	1031,	1033,	1039,	1049,	1051,	1061,	1063,	1069,
+	1087,	1091,	1093,	1097,	1103,	1109,	1117,	1123,	1129,	1151,
+	1153,	1163,	1171,	1181,	1187,	1193,	1201,	1213,	1217,	1223,
+	1229,	1231,	1237,	1249,	1259,	1277,	1279,	1283,	1289,	1291,
+	1297,	1301,	1303,	1307,	1319,	1321,	1327,	1361,	1367,	1373,
+	1381,	1399,	1409,	1423,	1427,	1429,	1433,	1439,	1447,	1451,
+	1453,	1459,	1471,	1481,	1483,	1487,	1489,	1493,	1499,	1511,
+	1523,	1531,	1543,	1549,	1553,	1559,	1567,	1571,	1579,	1583,
+	1597,	1601,	1607,	1609,	1613,	1619,	1621,	1627,	1637,	1657,
+	1663,	1667,	1669,	1693,	1697,	1699,	1709,	1721,	1723,	1733,
+	1741,	1747,	1753,	1759,	1777,	1783,	1787,	1789,	1801,	1811,
+	1823,	1831,	1847,	1861,	1867,	1871,	1873,	1877,	1879,	1889,
+	1901,	1907,	1913,	1931,	1933,	1949,	1951,	1973,	1979,	1987,
+	1993,	1997,	1999,	2003,	2011,	2017,	2027,	2029,	2039,	2053,
+	2063,	2069,	2081,	2083,	2087,	2089,	2099,	2111,	2113,	2129,
+	2131,	2137,	2141,	2143,	2153,	2161,	2179,	2203,	2207,	2213,
+	2221,	2237,	2239,	2243,	2251,	2267,	2269,	2273,	2281,	2287,
+	2293,	2297,	2309,	2311,	2333,	2339,	2341,	2347,	2351,	2357,
+	2371,	2377,	2381,	2383,	2389,	2393,	2399,	2411,	2417,	2423,
+	2437,	2441,	2447,	2459,	2467,	2473,	2477,	2503,	2521,	2531,
+	2539,	2543,	2549,	2551,	2557,	2579,	2591,	2593,	2609,	2617,
+	2621,	2633,	2647,	2657,	2659,	2663,	2671,	2677,	2683,	2687,
+	2689,	2693,	2699,	2707,	2711,	2713,	2719,	2729,	2731,	2741,
+	2749,	2753,	2767,	2777,	2789,	2791,	2797,	2801,	2803,	2819,
+	2833,	2837,	2843,	2851,	2857,	2861,	2879,	2887,	2897,	2903,
+	2909,	2917,	2927,	2939,	2953,	2957,	2963,	2969,	2971,	2999,
+	3001,	3011,	3019,	3023,	3037,	3041,	3049,	3061,	3067,	3079,
+	3083,	3089,	3109,	3119,	3121,	3137,	3163,	3167,	3169,	3181,
+	3187,	3191,	3203,	3209,	3217,	3221,	3229,	3251,	3253,	3257,
+	3259,	3271,	3299,	3301,	3307,	3313,	3319,	3323,	3329,	3331,
+	3343,	3347,	3359,	3361,	3371,	3373,	3389,	3391,	3407,	3413,
+	3433,	3449,	3457,	3461,	3463,	3467,	3469,	3491,	3499,	3511,
+	3517,	3527,	3529,	3533,	3539,	3541,	3547,	3557,	3559,	3571,
+	3581,	3583,	3593,	3607,	3613,	3617,	3623,	3631,	3637,	3643,
+	3659,	3671,	3673,	3677,	3691,	3697,	3701,	3709,	3719,	3727,
+	3733,	3739,	3761,	3767,	3769,	3779,	3793,	3797,	3803,	3821,
+	3823,	3833,	3847,	3851,	3853,	3863,	3877,	3881,	3889,	3907,
+	3911,	3917,	3919,	3923,	3929,	3931,	3943,	3947,	3967,	3989,
+	4001,	4003,	4007,	4013,	4019,	4021,	4027,	4049,	4051,	4057,
+	4073,	4079,	4091,	4093,	4099,	4111,	4127,	4129,	4133,	4139,
+	4153,	4157,	4159,	4177,	4201,	4211,	4217,	4219,	4229,	4231,
+	4241,	4243,	4253,	4259,	4261,	4271,	4273,	4283,	4289,	4297,
+	4327,	4337,	4339,	4349,	4357,	4363,	4373,	4391,	4397,	4409,
+	4421,	4423,	4441,	4447,	4451,	4457,	4463,	4481,	4483,	4493,
+	4507,	4513,	4517,	4519,	4523,	4547,	4549,	4561,	4567,	4583,
+	4591,	4597,	4603,	4621,	4637,	4639,	4643,	4649,	4651,	4657,
+	4663,	4673,	4679,	4691,	4703,	4721,	4723,	4729,	4733,	4751,
+	4759,	4783,	4787,	4789,	4793,	4799,	4801,	4813,	4817,	4831,
+	4861,	4871,	4877,	4889,	4903,	4909,	4919,	4931,	4933,	4937,
+	4943,	4951,	4957,	4967,	4969,	4973,	4987,	4993,	4999,	5003,
+	5009,	5011,	5021,	5023,	5039,	5051,	5059,	5077,	5081,	5087,
+	5099,	5101,	5107,	5113,	5119,	5147,	5153,	5167,	5171,	5179,
+	5189,	5197,	5209,	5227,	5231,	5233,	5237,	5261,	5273,	5279,
+	5281,	5297,	5303,	5309,	5323,	5333,	5347,	5351,	5381,	5387,
+	5393,	5399,	5407,	5413,	5417,	5419,	5431,	5437,	5441,	5443,
+	5449,	5471,	5477,	5479,	5483,	5501,	5503,	5507,	5519,	5521,
+	5527,	5531,	5557,	5563,	5569,	5573,	5581,	5591,	5623,	5639,
+	5641,	5647,	5651,	5653,	5657,	5659,	5669,	5683,	5689,	5693,
+	5701,	5711,	5717,	5737,	5741,	5743,	5749,	5779,	5783,	5791,
+	5801,	5807,	5813,	5821,	5827,	5839,	5843,	5849,	5851,	5857,
+	5861,	5867,	5869,	5879,	5881,	5897,	5903,	5923,	5927,	5939,
+	5953,	5981,	5987,	6007,	6011,	6029,	6037,	6043,	6047,	6053,
+	6067,	6073,	6079,	6089,	6091,	6101,	6113,	6121,	6131,	6133,
+	6143,	6151,	6163,	6173,	6197,	6199,	6203,	6211,	6217,	6221,
+	6229,	6247,	6257,	6263,	6269,	6271,	6277,	6287,	6299,	6301,
+	6311,	6317,	6323,	6329,	6337,	6343,	6353,	6359,	6361,	6367,
+	6373,	6379,	6389,	6397,	6421,	6427,	6449,	6451,	6469,	6473,
+	6481,	6491,	6521,	6529,	6547,	6551,	6553,	6563,	6569,	6571,
+	6577,	6581,	6599,	6607,	6619,	6637,	6653,	6659,	6661,	6673,
+	6679,	6689,	6691,	6701,	6703,	6709,	6719,	6733,	6737,	6761,
+	6763,	6779,	6781,	6791,	6793,	6803,	6823,	6827,	6829,	6833,
+	6841,	6857,	6863,	6869,	6871,	6883,	6899,	6907,	6911,	6917,
+	6947,	6949,	6959,	6961,	6967,	6971,	6977,	6983,	6991,	6997,
+	7001,	7013,	7019,	7027,	7039,	7043,	7057,	7069,	7079,	7103,
+	7109,	7121,	7127,	7129,	7151,	7159,	7177,	7187,	7193,	7207,
+	7211,	7213,	7219,	7229,	7237,	7243,	7247,	7253,	7283,	7297,
+	7307,	7309,	7321,	7331,	7333,	7349,	7351,	7369,	7393,	7411,
+	7417,	7433,	7451,	7457,	7459,	7477,	7481,	7487,	7489,	7499,
+	7507,	7517,	7523,	7529,	7537,	7541,	7547,	7549,	7559,	7561,
+	7573,	7577,	7583,	7589,	7591,	7603,	7607,	7621,	7639,	7643,
+	7649,	7669,	7673,	7681,	7687,	7691,	7699,	7703,	7717,	7723,
+	7727,	7741,	7753,	7757,	7759,	7789,	7793,	7817,	7823,	7829,
+	7841,	7853,	7867,	7873,	7877,	7879,	7883,	7901,	7907,	7919,
+	7927,	7933,	7937,	7949,	7951,	7963,	7993,	8009,	8011,	8017,
+	8039,	8053,	8059,	8069,	8081,	8087,	8089,	8093,	8101,	8111,
+	8117,	8123,	8147,	8161,	8167,	8171,	8179,	8191,	8209,	8219,
+	8221,	8231,	8233,	8237,	8243,	8263,	8269,	8273,	8287,	8291,
+	8293,	8297,	8311,	8317,	8329,	8353,	8363,	8369,	8377,	8387,
+	8389,	8419,	8423,	8429,	8431,	8443,	8447,	8461,	8467,	8501,
+	8513,	8521,	8527,	8537,	8539,	8543,	8563,	8573,	8581,	8597,
+	8599,	8609,	8623,	8627,	8629,	8641,	8647,	8663,	8669,	8677,
+	8681,	8689,	8693,	8699,	8707,	8713,	8719,	8731,	8737,	8741,
+	8747,	8753,	8761,	8779,	8783,	8803,	8807,	8819,	8821,	8831,
+	8837,	8839,	8849,	8861,	8863,	8867,	8887,	8893,	8923,	8929,
+	8933,	8941,	8951,	8963,	8969,	8971,	8999,	9001,	9007,	9011,
+	9013,	9029,	9041,	9043,	9049,	9059,	9067,	9091,	9103,	9109,
+	9127,	9133,	9137,	9151,	9157,	9161,	9173,	9181,	9187,	9199,
+	9203,	9209,	9221,	9227,	9239,	9241,	9257,	9277,	9281,	9283,
+	9293,	9311,	9319,	9323,	9337,	9341,	9343,	9349,	9371,	9377,
+	9391,	9397,	9403,	9413,	9419,	9421,	9431,	9433,	9437,	9439,
+	9461,	9463,	9467,	9473,	9479,	9491,	9497,	9511,	9521,	9533,
+	9539,	9547,	9551,	9587,	9601,	9613,	9619,	9623,	9629,	9631,
+	9643,	9649,	9661,	9677,	9679,	9689,	9697,	9719,	9721,	9733,
+	9739,	9743,	9749,	9767,	9769,	9781,	9787,	9791,	9803,	9811,
+	9817,	9829,	9833,	9839,	9851,	9857,	9859,	9871,	9883,	9887,
+	9901,	9907,	9923,	9929,	9931,	9941,	9949,	9967,	9973,	10007,
+	10009,	10037,	10039,	10061,	10067,	10069,	10079,	10091,	10093,	10099,
+	10103,	10111,	10133,	10139,	10141,	10151,	10159,	10163,	10169,	10177,
+	10181,	10193,	10211,	10223,	10243,	10247,	10253,	10259,	10267,	10271,
+	10273,	10289,	10301,	10303,	10313,	10321,	10331,	10333,	10337,	10343,
+	10357,	10369,	10391,	10399,	10427,	10429,	10433,	10453,	10457,	10459,
+	10463,	10477,	10487,	10499,	10501,	10513,	10529,	10531,	10559,	10567,
+	10589,	10597,	10601,	10607,	10613,	10627,	10631,	10639,	10651,	10657,
+	10663,	10667,	10687,	10691,	10709,	10711,	10723,	10729,	10733,	10739,
+	10753,	10771,	10781,	10789,	10799,	10831,	10837,	10847,	10853,	10859,
+	10861,	10867,	10883,	10889,	10891,	10903,	10909,	10937,	10939,	10949,
+	10957,	10973,	10979,	10987,	10993,	11003,	11027,	11047,	11057,	11059,
+	11069,	11071,	11083,	11087,	11093,	11113,	11117,	11119,	11131,	11149,
+	11159,	11161,	11171,	11173,	11177,	11197,	11213,	11239,	11243,	11251,
+	11257,	11261,	11273,	11279,	11287,	11299,	11311,	11317,	11321,	11329,
+	11351,	11353,	11369,	11383,	11393,	11399,	11411,	11423,	11437,	11443,
+	11447,	11467,	11471,	11483,	11489,	11491,	11497,	11503,	11519,	11527,
+	11549,	11551,	11579,	11587,	11593,	11597,	11617,	11621,	11633,	11657,
+	11677,	11681,	11689,	11699,	11701,	11717,	11719,	11731,	11743,	11777,
+	11779,	11783,	11789,	11801,	11807,	11813,	11821,	11827,	11831,	11833,
+	11839,	11863,	11867,	11887,	11897,	11903,	11909,	11923,	11927,	11933,
+	11939,	11941,	11953,	11959,	11969,	11971,	11981,	11987,	12007,	12011,
+	12037,	12041,	12043,	12049,	12071,	12073,	12097,	12101,	12107,	12109,
+	12113,	12119,	12143,	12149,	12157,	12161,	12163,	12197,	12203,	12211,
+	12227,	12239,	12241,	12251,	12253,	12263,	12269,	12277,	12281,	12289,
+	12301,	12323,	12329,	12343,	12347,	12373,	12377,	12379,	12391,	12401,
+	12409,	12413,	12421,	12433,	12437,	12451,	12457,	12473,	12479,	12487,
+	12491,	12497,	12503,	12511,	12517,	12527,	12539,	12541,	12547,	12553,
+	12569,	12577,	12583,	12589,	12601,	12611,	12613,	12619,	12637,	12641,
+	12647,	12653,	12659,	12671,	12689,	12697,	12703,	12713,	12721,	12739,
+	12743,	12757,	12763,	12781,	12791,	12799,	12809,	12821,	12823,	12829,
+	12841,	12853,	12889,	12893,	12899,	12907,	12911,	12917,	12919,	12923,
+	12941,	12953,	12959,	12967,	12973,	12979,	12983,	13001,	13003,	13007,
+	13009,	13033,	13037,	13043,	13049,	13063,	13093,	13099,	13103,	13109,
+	13121,	13127,	13147,	13151,	13159,	13163,	13171,	13177,	13183,	13187,
+	13217,	13219,	13229,	13241,	13249,	13259,	13267,	13291,	13297,	13309,
+	13313,	13327,	13331,	13337,	13339,	13367,	13381,	13397,	13399,	13411,
+	13417,	13421,	13441,	13451,	13457,	13463,	13469,	13477,	13487,	13499,
+	13513,	13523,	13537,	13553,	13567,	13577,	13591,	13597,	13613,	13619,
+	13627,	13633,	13649,	13669,	13679,	13681,	13687,	13691,	13693,	13697,
+	13709,	13711,	13721,	13723,	13729,	13751,	13757,	13759,	13763,	13781,
+	13789,	13799,	13807,	13829,	13831,	13841,	13859,	13873,	13877,	13879,
+	13883,	13901,	13903,	13907,	13913,	13921,	13931,	13933,	13963,	13967,
+	13997,	13999,	14009,	14011,	14029,	14033,	14051,	14057,	14071,	14081,
+	14083,	14087,	14107,	14143,	14149,	14153,	14159,	14173,	14177,	14197,
+	14207,	14221,	14243,	14249,	14251,	14281,	14293,	14303,	14321,	14323,
+	14327,	14341,	14347,	14369,	14387,	14389,	14401,	14407,	14411,	14419,
+	14423,	14431,	14437,	14447,	14449,	14461,	14479,	14489,	14503,	14519,
+	14533,	14537,	14543,	14549,	14551,	14557,	14561,	14563,	14591,	14593,
+	14621,	14627,	14629,	14633,	14639,	14653,	14657,	14669,	14683,	14699,
+	14713,	14717,	14723,	14731,	14737,	14741,	14747,	14753,	14759,	14767,
+	14771,	14779,	14783,	14797,	14813,	14821,	14827,	14831,	14843,	14851,
+	14867,	14869,	14879,	14887,	14891,	14897,	14923,	14929,	14939,	14947,
+	14951,	14957,	14969,	14983,	15013,	15017,	15031,	15053,	15061,	15073,
+	15077,	15083,	15091,	15101,	15107,	15121,	15131,	15137,	15139,	15149,
+	15161,	15173,	15187,	15193,	15199,	15217,	15227,	15233,	15241,	15259,
+	15263,	15269,	15271,	15277,	15287,	15289,	15299,	15307,	15313,	15319,
+	15329,	15331,	15349,	15359,	15361,	15373,	15377,	15383,	15391,	15401,
+	15413,	15427,	15439,	15443,	15451,	15461,	15467,	15473,	15493,	15497,
+	15511,	15527,	15541,	15551,	15559,	15569,	15581,	15583,	15601,	15607,
+	15619,	15629,	15641,	15643,	15647,	15649,	15661,	15667,	15671,	15679,
+	15683,	15727,	15731,	15733,	15737,	15739,	15749,	15761,	15767,	15773,
+	15787,	15791,	15797,	15803,	15809,	15817,	15823,	15859,	15877,	15881,
+	15887,	15889,	15901,	15907,	15913,	15919,	15923,	15937,	15959,	15971,
+	15973,	15991,	16001,	16007,	16033,	16057,	16061,	16063,	16067,	16069,
+	16073,	16087,	16091,	16097,	16103,	16111,	16127,	16139,	16141,	16183,
+	16187,	16189,	16193,	16217,	16223,	16229,	16231,	16249,	16253,	16267,
+	16273,	16301,	16319,	16333,	16339,	16349,	16361,	16363,	16369,	16381,
+	16411,	16417,	16421,	16427,	16433,	16447,	16451,	16453,	16477,	16481,
+	16487,	16493,	16519,	16529,	16547,	16553,	16561,	16567,	16573,	16603,
+	16607,	16619,	16631,	16633,	16649,	16651,	16657,	16661,	16673,	16691,
+	16693,	16699,	16703,	16729,	16741,	16747,	16759,	16763,	16787,	16811,
+	16823,	16829,	16831,	16843,	16871,	16879,	16883,	16889,	16901,	16903,
+	16921,	16927,	16931,	16937,	16943,	16963,	16979,	16981,	16987,	16993,
+	17011,	17021,	17027,	17029,	17033,	17041,	17047,	17053,	17077,	17093,
+	17099,	17107,	17117,	17123,	17137,	17159,	17167,	17183,	17189,	17191,
+	17203,	17207,	17209,	17231,	17239,	17257,	17291,	17293,	17299,	17317,
+	17321,	17327,	17333,	17341,	17351,	17359,	17377,	17383,	17387,	17389,
+	17393,	17401,	17417,	17419,	17431,	17443,	17449,	17467,	17471,	17477,
+	17483,	17489,	17491,	17497,	17509,	17519,	17539,	17551,	17569,	17573,
+	17579,	17581,	17597,	17599,	17609,	17623,	17627,	17657,	17659,	17669,
+	17681,	17683,	17707,	17713,	17729,	17737,	17747,	17749,	17761,	17783,
+	17789,	17791,	17807,	17827,	17837,	17839,	17851,	17863,	17881,	17891,
+	17903,	17909,	17911,	17921,	17923,	17929,	17939,	17957,	17959,	17971,
+	17977,	17981,	17987,	17989,	18013,	18041,	18043,	18047,	18049,	18059,
+	18061,	18077,	18089,	18097,	18119,	18121,	18127,	18131,	18133,	18143,
+	18149,	18169,	18181,	18191,	18199,	18211,	18217,	18223,	18229,	18233,
+	18251,	18253,	18257,	18269,	18287,	18289,	18301,	18307,	18311,	18313,
+	18329,	18341,	18353,	18367,	18371,	18379,	18397,	18401,	18413,	18427,
+	18433,	18439,	18443,	18451,	18457,	18461,	18481,	18493,	18503,	18517,
+	18521,	18523,	18539,	18541,	18553,	18583,	18587,	18593,	18617,	18637,
+	18661,	18671,	18679,	18691,	18701,	18713,	18719,	18731,	18743,	18749,
+	18757,	18773,	18787,	18793,	18797,	18803,	18839,	18859,	18869,	18899,
+	18911,	18913,	18917,	18919,	18947,	18959,	18973,	18979,	19001,	19009,
+	19013,	19031,	19037,	19051,	19069,	19073,	19079,	19081,	19087,	19121,
+	19139,	19141,	19157,	19163,	19181,	19183,	19207,	19211,	19213,	19219,
+	19231,	19237,	19249,	19259,	19267,	19273,	19289,	19301,	19309,	19319,
+	19333,	19373,	19379,	19381,	19387,	19391,	19403,	19417,	19421,	19423,
+	19427,	19429,	19433,	19441,	19447,	19457,	19463,	19469,	19471,	19477,
+	19483,	19489,	19501,	19507,	19531,	19541,	19543,	19553,	19559,	19571,
+	19577,	19583,	19597,	19603,	19609,	19661,	19681,	19687,	19697,	19699,
+	19709,	19717,	19727,	19739,	19751,	19753,	19759,	19763,	19777,	19793,
+	19801,	19813,	19819,	19841,	19843,	19853,	19861,	19867,	19889,	19891,
+	19913,	19919,	19927,	19937,	19949,	19961,	19963,	19973,	19979,	19991,
+	19993,	19997,	20011,	20021,	20023,	20029,	20047,	20051,	20063,	20071,
+	20089,	20101,	20107,	20113,	20117,	20123,	20129,	20143,	20147,	20149,
+	20161,	20173,	20177,	20183,	20201,	20219,	20231,	20233,	20249,	20261,
+	20269,	20287,	20297,	20323,	20327,	20333,	20341,	20347,	20353,	20357,
+	20359,	20369,	20389,	20393,	20399,	20407,	20411,	20431,	20441,	20443,
+	20477,	20479,	20483,	20507,	20509,	20521,	20533,	20543,	20549,	20551,
+	20563,	20593,	20599,	20611,	20627,	20639,	20641,	20663,	20681,	20693,
+	20707,	20717,	20719,	20731,	20743,	20747,	20749,	20753,	20759,	20771,
+	20773,	20789,	20807,	20809,	20849,	20857,	20873,	20879,	20887,	20897,
+	20899,	20903,	20921,	20929,	20939,	20947,	20959,	20963,	20981,	20983,
+	21001,	21011,	21013,	21017,	21019,	21023,	21031,	21059,	21061,	21067,
+	21089,	21101,	21107,	21121,	21139,	21143,	21149,	21157,	21163,	21169,
+	21179,	21187,	21191,	21193,	21211,	21221,	21227,	21247,	21269,	21277,
+	21283,	21313,	21317,	21319,	21323,	21341,	21347,	21377,	21379,	21383,
+	21391,	21397,	21401,	21407,	21419,	21433,	21467,	21481,	21487,	21491,
+	21493,	21499,	21503,	21517,	21521,	21523,	21529,	21557,	21559,	21563,
+	21569,	21577,	21587,	21589,	21599,	21601,	21611,	21613,	21617,	21647,
+	21649,	21661,	21673,	21683,	21701,	21713,	21727,	21737,	21739,	21751,
+	21757,	21767,	21773,	21787,	21799,	21803,	21817,	21821,	21839,	21841,
+	21851,	21859,	21863,	21871,	21881,	21893,	21911,	21929,	21937,	21943,
+	21961,	21977,	21991,	21997,	22003,	22013,	22027,	22031,	22037,	22039,
+	22051,	22063,	22067,	22073,	22079,	22091,	22093,	22109,	22111,	22123,
+	22129,	22133,	22147,	22153,	22157,	22159,	22171,	22189,	22193,	22229,
+	22247,	22259,	22271,	22273,	22277,	22279,	22283,	22291,	22303,	22307,
+	22343,	22349,	22367,	22369,	22381,	22391,	22397,	22409,	22433,	22441,
+	22447,	22453,	22469,	22481,	22483,	22501,	22511,	22531,	22541,	22543,
+	22549,	22567,	22571,	22573,	22613,	22619,	22621,	22637,	22639,	22643,
+	22651,	22669,	22679,	22691,	22697,	22699,	22709,	22717,	22721,	22727,
+	22739,	22741,	22751,	22769,	22777,	22783,	22787,	22807,	22811,	22817,
+	22853,	22859,	22861,	22871,	22877,	22901,	22907,	22921,	22937,	22943,
+	22961,	22963,	22973,	22993,	23003,	23011,	23017,	23021,	23027,	23029,
+	23039,	23041,	23053,	23057,	23059,	23063,	23071,	23081,	23087,	23099,
+	23117,	23131,	23143,	23159,	23167,	23173,	23189,	23197,	23201,	23203,
+	23209,	23227,	23251,	23269,	23279,	23291,	23293,	23297,	23311,	23321,
+	23327,	23333,	23339,	23357,	23369,	23371,	23399,	23417,	23431,	23447,
+	23459,	23473,	23497,	23509,	23531,	23537,	23539,	23549,	23557,	23561,
+	23563,	23567,	23581,	23593,	23599,	23603,	23609,	23623,	23627,	23629,
+	23633,	23663,	23669,	23671,	23677,	23687,	23689,	23719,	23741,	23743,
+	23747,	23753,	23761,	23767,	23773,	23789,	23801,	23813,	23819,	23827,
+	23831,	23833,	23857,	23869,	23873,	23879,	23887,	23893,	23899,	23909,
+	23911,	23917,	23929,	23957,	23971,	23977,	23981,	23993,	24001,	24007,
+	24019,	24023,	24029,	24043,	24049,	24061,	24071,	24077,	24083,	24091,
+	24097,	24103,	24107,	24109,	24113,	24121,	24133,	24137,	24151,	24169,
+	24179,	24181,	24197,	24203,	24223,	24229,	24239,	24247,	24251,	24281,
+	24317,	24329,	24337,	24359,	24371,	24373,	24379,	24391,	24407,	24413,
+	24419,	24421,	24439,	24443,	24469,	24473,	24481,	24499,	24509,	24517,
+	24527,	24533,	24547,	24551,	24571,	24593,	24611,	24623,	24631,	24659,
+	24671,	24677,	24683,	24691,	24697,	24709,	24733,	24749,	24763,	24767,
+	24781,	24793,	24799,	24809,	24821,	24841,	24847,	24851,	24859,	24877,
+	24889,	24907,	24917,	24919,	24923,	24943,	24953,	24967,	24971,	24977,
+	24979,	24989,	25013,	25031,	25033,	25037,	25057,	25073,	25087,	25097,
+	25111,	25117,	25121,	25127,	25147,	25153,	25163,	25169,	25171,	25183,
+	25189,	25219,	25229,	25237,	25243,	25247,	25253,	25261,	25301,	25303,
+	25307,	25309,	25321,	25339,	25343,	25349,	25357,	25367,	25373,	25391,
+	25409,	25411,	25423,	25439,	25447,	25453,	25457,	25463,	25469,	25471,
+	25523,	25537,	25541,	25561,	25577,	25579,	25583,	25589,	25601,	25603,
+	25609,	25621,	25633,	25639,	25643,	25657,	25667,	25673,	25679,	25693,
+	25703,	25717,	25733,	25741,	25747,	25759,	25763,	25771,	25793,	25799,
+	25801,	25819,	25841,	25847,	25849,	25867,	25873,	25889,	25903,	25913,
+	25919,	25931,	25933,	25939,	25943,	25951,	25969,	25981,	25997,	25999,
+	26003,	26017,	26021,	26029,	26041,	26053,	26083,	26099,	26107,	26111,
+	26113,	26119,	26141,	26153,	26161,	26171,	26177,	26183,	26189,	26203,
+	26209,	26227,	26237,	26249,	26251,	26261,	26263,	26267,	26293,	26297,
+	26309,	26317,	26321,	26339,	26347,	26357,	26371,	26387,	26393,	26399,
+	26407,	26417,	26423,	26431,	26437,	26449,	26459,	26479,	26489,	26497,
+	26501,	26513,	26539,	26557,	26561,	26573,	26591,	26597,	26627,	26633,
+	26641,	26647,	26669,	26681,	26683,	26687,	26693,	26699,	26701,	26711,
+	26713,	26717,	26723,	26729,	26731,	26737,	26759,	26777,	26783,	26801,
+	26813,	26821,	26833,	26839,	26849,	26861,	26863,	26879,	26881,	26891,
+	26893,	26903,	26921,	26927,	26947,	26951,	26953,	26959,	26981,	26987,
+	26993,	27011,	27017,	27031,	27043,	27059,	27061,	27067,	27073,	27077,
+	27091,	27103,	27107,	27109,	27127,	27143,	27179,	27191,	27197,	27211,
+	27239,	27241,	27253,	27259,	27271,	27277,	27281,	27283,	27299,	27329,
+	27337,	27361,	27367,	27397,	27407,	27409,	27427,	27431,	27437,	27449,
+	27457,	27479,	27481,	27487,	27509,	27527,	27529,	27539,	27541,	27551,
+	27581,	27583,	27611,	27617,	27631,	27647,	27653,	27673,	27689,	27691,
+	27697,	27701,	27733,	27737,	27739,	27743,	27749,	27751,	27763,	27767,
+	27773,	27779,	27791,	27793,	27799,	27803,	27809,	27817,	27823,	27827,
+	27847,	27851,	27883,	27893,	27901,	27917,	27919,	27941,	27943,	27947,
+	27953,	27961,	27967,	27983,	27997,	28001,	28019,	28027,	28031,	28051,
+	28057,	28069,	28081,	28087,	28097,	28099,	28109,	28111,	28123,	28151,
+	28163,	28181,	28183,	28201,	28211,	28219,	28229,	28277,	28279,	28283,
+	28289,	28297,	28307,	28309,	28319,	28349,	28351,	28387,	28393,	28403,
+	28409,	28411,	28429,	28433,	28439,	28447,	28463,	28477,	28493,	28499,
+	28513,	28517,	28537,	28541,	28547,	28549,	28559,	28571,	28573,	28579,
+	28591,	28597,	28603,	28607,	28619,	28621,	28627,	28631,	28643,	28649,
+	28657,	28661,	28663,	28669,	28687,	28697,	28703,	28711,	28723,	28729,
+	28751,	28753,	28759,	28771,	28789,	28793,	28807,	28813,	28817,	28837,
+	28843,	28859,	28867,	28871,	28879,	28901,	28909,	28921,	28927,	28933,
+	28949,	28961,	28979,	29009,	29017,	29021,	29023,	29027,	29033,	29059,
+	29063,	29077,	29101,	29123,	29129,	29131,	29137,	29147,	29153,	29167,
+	29173,	29179,	29191,	29201,	29207,	29209,	29221,	29231,	29243,	29251,
+	29269,	29287,	29297,	29303,	29311,	29327,	29333,	29339,	29347,	29363,
+	29383,	29387,	29389,	29399,	29401,	29411,	29423,	29429,	29437,	29443,
+	29453,	29473,	29483,	29501,	29527,	29531,	29537,	29567,	29569,	29573,
+	29581,	29587,	29599,	29611,	29629,	29633,	29641,	29663,	29669,	29671,
+	29683,	29717,	29723,	29741,	29753,	29759,	29761,	29789,	29803,	29819,
+	29833,	29837,	29851,	29863,	29867,	29873,	29879,	29881,	29917,	29921,
+	29927,	29947,	29959,	29983,	29989,	30011,	30013,	30029,	30047,	30059,
+	30071,	30089,	30091,	30097,	30103,	30109,	30113,	30119,	30133,	30137,
+	30139,	30161,	30169,	30181,	30187,	30197,	30203,	30211,	30223,	30241,
+	30253,	30259,	30269,	30271,	30293,	30307,	30313,	30319,	30323,	30341,
+	30347,	30367,	30389,	30391,	30403,	30427,	30431,	30449,	30467,	30469,
+	30491,	30493,	30497,	30509,	30517,	30529,	30539,	30553,	30557,	30559,
+	30577,	30593,	30631,	30637,	30643,	30649,	30661,	30671,	30677,	30689,
+	30697,	30703,	30707,	30713,	30727,	30757,	30763,	30773,	30781,	30803,
+	30809,	30817,	30829,	30839,	30841,	30851,	30853,	30859,	30869,	30871,
+	30881,	30893,	30911,	30931,	30937,	30941,	30949,	30971,	30977,	30983,
+	31013,	31019,	31033,	31039,	31051,	31063,	31069,	31079,	31081,	31091,
+	31121,	31123,	31139,	31147,	31151,	31153,	31159,	31177,	31181,	31183,
+	31189,	31193,	31219,	31223,	31231,	31237,	31247,	31249,	31253,	31259,
+	31267,	31271,	31277,	31307,	31319,	31321,	31327,	31333,	31337,	31357,
+	31379,	31387,	31391,	31393,	31397,	31469,	31477,	31481,	31489,	31511,
+	31513,	31517,	31531,	31541,	31543,	31547,	31567,	31573,	31583,	31601,
+	31607,	31627,	31643,	31649,	31657,	31663,	31667,	31687,	31699,	31721,
+	31723,	31727,	31729,	31741,	31751,	31769,	31771,	31793,	31799,	31817,
+	31847,	31849,	31859,	31873,	31883,	31891,	31907,	31957,	31963,	31973,
+	31981,	31991,	32003,	32009,	32027,	32029,	32051,	32057,	32059,	32063,
+	32069,	32077,	32083,	32089,	32099,	32117,	32119,	32141,	32143,	32159,
+	32173,	32183,	32189,	32191,	32203,	32213,	32233,	32237,	32251,	32257,
+	32261,	32297,	32299,	32303,	32309,	32321,	32323,	32327,	32341,	32353,
+	32359,	32363,	32369,	32371,	32377,	32381,	32401,	32411,	32413,	32423,
+	32429,	32441,	32443,	32467,	32479,	32491,	32497,	32503,	32507,	32531,
+	32533,	32537,	32561,	32563,	32569,	32573,	32579,	32587,	32603,	32609,
+	32611,	32621,	32633,	32647,	32653,	32687,	32693,	32707,	32713,	32717,
+	32719,	32749,	32771,	32779,	32783,	32789,	32797,	32801,	32803,	32831,
+	32833,	32839,	32843,	32869,	32887,	32909,	32911,	32917,	32933,	32939,
+	32941,	32957,	32969,	32971,	32983,	32987,	32993,	32999,	33013,	33023,
+	33029,	33037,	33049,	33053,	33071,	33073,	33083,	33091,	33107,	33113,
+	33119,	33149,	33151,	33161,	33179,	33181,	33191,	33199,	33203,	33211,
+	33223,	33247,	33287,	33289,	33301,	33311,	33317,	33329,	33331,	33343,
+	33347,	33349,	33353,	33359,	33377,	33391,	33403,	33409,	33413,	33427,
+	33457,	33461,	33469,	33479,	33487,	33493,	33503,	33521,	33529,	33533,
+	33547,	33563,	33569,	33577,	33581,	33587,	33589,	33599,	33601,	33613,
+	33617,	33619,	33623,	33629,	33637,	33641,	33647,	33679,	33703,	33713,
+	33721,	33739,	33749,	33751,	33757,	33767,	33769,	33773,	33791,	33797,
+	33809,	33811,	33827,	33829,	33851,	33857,	33863,	33871,	33889,	33893,
+	33911,	33923,	33931,	33937,	33941,	33961,	33967,	33997,	34019,	34031,
+	34033,	34039,	34057,	34061,	34123,	34127,	34129,	34141,	34147,	34157,
+	34159,	34171,	34183,	34211,	34213,	34217,	34231,	34253,	34259,	34261,
+	34267,	34273,	34283,	34297,	34301,	34303,	34313,	34319,	34327,	34337,
+	34351,	34361,	34367,	34369,	34381,	34403,	34421,	34429,	34439,	34457,
+	34469,	34471,	34483,	34487,	34499,	34501,	34511,	34513,	34519,	34537,
+	34543,	34549,	34583,	34589,	34591,	34603,	34607,	34613,	34631,	34649,
+	34651,	34667,	34673,	34679,	34687,	34693,	34703,	34721,	34729,	34739,
+	34747,	34757,	34759,	34763,	34781,	34807,	34819,	34841,	34843,	34847,
+	34849,	34871,	34877,	34883,	34897,	34913,	34919,	34939,	34949,	34961,
+	34963,	34981,	35023,	35027,	35051,	35053,	35059,	35069,	35081,	35083,
+	35089,	35099,	35107,	35111,	35117,	35129,	35141,	35149,	35153,	35159,
+	35171,	35201,	35221,	35227,	35251,	35257,	35267,	35279,	35281,	35291,
+	35311,	35317,	35323,	35327,	35339,	35353,	35363,	35381,	35393,	35401,
+	35407,	35419,	35423,	35437,	35447,	35449,	35461,	35491,	35507,	35509,
+	35521,	35527,	35531,	35533,	35537,	35543,	35569,	35573,	35591,	35593,
+	35597,	35603,	35617,	35671,	35677,	35729,	35731,	35747,	35753,	35759,
+	35771,	35797,	35801,	35803,	35809,	35831,	35837,	35839,	35851,	35863,
+	35869,	35879,	35897,	35899,	35911,	35923,	35933,	35951,	35963,	35969,
+	35977,	35983,	35993,	35999,	36007,	36011,	36013,	36017,	36037,	36061,
+	36067,	36073,	36083,	36097,	36107,	36109,	36131,	36137,	36151,	36161,
+	36187,	36191,	36209,	36217,	36229,	36241,	36251,	36263,	36269,	36277,
+	36293,	36299,	36307,	36313,	36319,	36341,	36343,	36353,	36373,	36383,
+	36389,	36433,	36451,	36457,	36467,	36469,	36473,	36479,	36493,	36497,
+	36523,	36527,	36529,	36541,	36551,	36559,	36563,	36571,	36583,	36587,
+	36599,	36607,	36629,	36637,	36643,	36653,	36671,	36677,	36683,	36691,
+	36697,	36709,	36713,	36721,	36739,	36749,	36761,	36767,	36779,	36781,
+	36787,	36791,	36793,	36809,	36821,	36833,	36847,	36857,	36871,	36877,
+	36887,	36899,	36901,	36913,	36919,	36923,	36929,	36931,	36943,	36947,
+	36973,	36979,	36997,	37003,	37013,	37019,	37021,	37039,	37049,	37057,
+	37061,	37087,	37097,	37117,	37123,	37139,	37159,	37171,	37181,	37189,
+	37199,	37201,	37217,	37223,	37243,	37253,	37273,	37277,	37307,	37309,
+	37313,	37321,	37337,	37339,	37357,	37361,	37363,	37369,	37379,	37397,
+	37409,	37423,	37441,	37447,	37463,	37483,	37489,	37493,	37501,	37507,
+	37511,	37517,	37529,	37537,	37547,	37549,	37561,	37567,	37571,	37573,
+	37579,	37589,	37591,	37607,	37619,	37633,	37643,	37649,	37657,	37663,
+	37691,	37693,	37699,	37717,	37747,	37781,	37783,	37799,	37811,	37813,
+	37831,	37847,	37853,	37861,	37871,	37879,	37889,	37897,	37907,	37951,
+	37957,	37963,	37967,	37987,	37991,	37993,	37997,	38011,	38039,	38047,
+	38053,	38069,	38083,	38113,	38119,	38149,	38153,	38167,	38177,	38183,
+	38189,	38197,	38201,	38219,	38231,	38237,	38239,	38261,	38273,	38281,
+	38287,	38299,	38303,	38317,	38321,	38327,	38329,	38333,	38351,	38371,
+	38377,	38393,	38431,	38447,	38449,	38453,	38459,	38461,	38501,	38543,
+	38557,	38561,	38567,	38569,	38593,	38603,	38609,	38611,	38629,	38639,
+	38651,	38653,	38669,	38671,	38677,	38693,	38699,	38707,	38711,	38713,
+	38723,	38729,	38737,	38747,	38749,	38767,	38783,	38791,	38803,	38821,
+	38833,	38839,	38851,	38861,	38867,	38873,	38891,	38903,	38917,	38921,
+	38923,	38933,	38953,	38959,	38971,	38977,	38993,	39019,	39023,	39041,
+	39043,	39047,	39079,	39089,	39097,	39103,	39107,	39113,	39119,	39133,
+	39139,	39157,	39161,	39163,	39181,	39191,	39199,	39209,	39217,	39227,
+	39229,	39233,	39239,	39241,	39251,	39293,	39301,	39313,	39317,	39323,
+	39341,	39343,	39359,	39367,	39371,	39373,	39383,	39397,	39409,	39419,
+	39439,	39443,	39451,	39461,	39499,	39503,	39509,	39511,	39521,	39541,
+	39551,	39563,	39569,	39581,	39607,	39619,	39623,	39631,	39659,	39667,
+	39671,	39679,	39703,	39709,	39719,	39727,	39733,	39749,	39761,	39769,
+	39779,	39791,	39799,	39821,	39827,	39829,	39839,	39841,	39847,	39857,
+	39863,	39869,	39877,	39883,	39887,	39901,	39929,	39937,	39953,	39971,
+	39979,	39983,	39989,	40009,	40013,	40031,	40037,	40039,	40063,	40087,
+	40093,	40099,	40111,	40123,	40127,	40129,	40151,	40153,	40163,	40169,
+	40177,	40189,	40193,	40213,	40231,	40237,	40241,	40253,	40277,	40283,
+	40289,	40343,	40351,	40357,	40361,	40387,	40423,	40427,	40429,	40433,
+	40459,	40471,	40483,	40487,	40493,	40499,	40507,	40519,	40529,	40531,
+	40543,	40559,	40577,	40583,	40591,	40597,	40609,	40627,	40637,	40639,
+	40693,	40697,	40699,	40709,	40739,	40751,	40759,	40763,	40771,	40787,
+	40801,	40813,	40819,	40823,	40829,	40841,	40847,	40849,	40853,	40867,
+	40879,	40883,	40897,	40903,	40927,	40933,	40939,	40949,	40961,	40973,
+	40993,	41011,	41017,	41023,	41039,	41047,	41051,	41057,	41077,	41081,
+	41113,	41117,	41131,	41141,	41143,	41149,	41161,	41177,	41179,	41183,
+	41189,	41201,	41203,	41213,	41221,	41227,	41231,	41233,	41243,	41257,
+	41263,	41269,	41281,	41299,	41333,	41341,	41351,	41357,	41381,	41387,
+	41389,	41399,	41411,	41413,	41443,	41453,	41467,	41479,	41491,	41507,
+	41513,	41519,	41521,	41539,	41543,	41549,	41579,	41593,	41597,	41603,
+	41609,	41611,	41617,	41621,	41627,	41641,	41647,	41651,	41659,	41669,
+	41681,	41687,	41719,	41729,	41737,	41759,	41761,	41771,	41777,	41801,
+	41809,	41813,	41843,	41849,	41851,	41863,	41879,	41887,	41893,	41897,
+	41903,	41911,	41927,	41941,	41947,	41953,	41957,	41959,	41969,	41981,
+	41983,	41999,	42013,	42017,	42019,	42023,	42043,	42061,	42071,	42073,
+	42083,	42089,	42101,	42131,	42139,	42157,	42169,	42179,	42181,	42187,
+	42193,	42197,	42209,	42221,	42223,	42227,	42239,	42257,	42281,	42283,
+	42293,	42299,	42307,	42323,	42331,	42337,	42349,	42359,	42373,	42379,
+	42391,	42397,	42403,	42407,	42409,	42433,	42437,	42443,	42451,	42457,
+	42461,	42463,	42467,	42473,	42487,	42491,	42499,	42509,	42533,	42557,
+	42569,	42571,	42577,	42589,	42611,	42641,	42643,	42649,	42667,	42677,
+	42683,	42689,	42697,	42701,	42703,	42709,	42719,	42727,	42737,	42743,
+	42751,	42767,	42773,	42787,	42793,	42797,	42821,	42829,	42839,	42841,
+	42853,	42859,	42863,	42899,	42901,	42923,	42929,	42937,	42943,	42953,
+	42961,	42967,	42979,	42989,	43003,	43013,	43019,	43037,	43049,	43051,
+	43063,	43067,	43093,	43103,	43117,	43133,	43151,	43159,	43177,	43189,
+	43201,	43207,	43223,	43237,	43261,	43271,	43283,	43291,	43313,	43319,
+	43321,	43331,	43391,	43397,	43399,	43403,	43411,	43427,	43441,	43451,
+	43457,	43481,	43487,	43499,	43517,	43541,	43543,	43573,	43577,	43579,
+	43591,	43597,	43607,	43609,	43613,	43627,	43633,	43649,	43651,	43661,
+	43669,	43691,	43711,	43717,	43721,	43753,	43759,	43777,	43781,	43783,
+	43787,	43789,	43793,	43801,	43853,	43867,	43889,	43891,	43913,	43933,
+	43943,	43951,	43961,	43963,	43969,	43973,	43987,	43991,	43997,	44017,
+	44021,	44027,	44029,	44041,	44053,	44059,	44071,	44087,	44089,	44101,
+	44111,	44119,	44123,	44129,	44131,	44159,	44171,	44179,	44189,	44201,
+	44203,	44207,	44221,	44249,	44257,	44263,	44267,	44269,	44273,	44279,
+	44281,	44293,	44351,	44357,	44371,	44381,	44383,	44389,	44417,	44449,
+	44453,	44483,	44491,	44497,	44501,	44507,	44519,	44531,	44533,	44537,
+	44543,	44549,	44563,	44579,	44587,	44617,	44621,	44623,	44633,	44641,
+	44647,	44651,	44657,	44683,	44687,	44699,	44701,	44711,	44729,	44741,
+	44753,	44771,	44773,	44777,	44789,	44797,	44809,	44819,	44839,	44843,
+	44851,	44867,	44879,	44887,	44893,	44909,	44917,	44927,	44939,	44953,
+	44959,	44963,	44971,	44983,	44987,	45007,	45013,	45053,	45061,	45077,
+	45083,	45119,	45121,	45127,	45131,	45137,	45139,	45161,	45179,	45181,
+	45191,	45197,	45233,	45247,	45259,	45263,	45281,	45289,	45293,	45307,
+	45317,	45319,	45329,	45337,	45341,	45343,	45361,	45377,	45389,	45403,
+	45413,	45427,	45433,	45439,	45481,	45491,	45497,	45503,	45523,	45533,
+	45541,	45553,	45557,	45569,	45587,	45589,	45599,	45613,	45631,	45641,
+	45659,	45667,	45673,	45677,	45691,	45697,	45707,	45737,	45751,	45757,
+	45763,	45767,	45779,	45817,	45821,	45823,	45827,	45833,	45841,	45853,
+	45863,	45869,	45887,	45893,	45943,	45949,	45953,	45959,	45971,	45979,
+	45989,	46021,	46027,	46049,	46051,	46061,	46073,	46091,	46093,	46099,
+	46103,	46133,	46141,	46147,	46153,	46171,	46181,	46183,	46187,	46199,
+	46219,	46229,	46237,	46261,	46271,	46273,	46279,	46301,	46307,	46309,
+	46327,	46337,	46349,	46351,	46381,	46399,	46411,	46439,	46441,	46447,
+	46451,	46457,	46471,	46477,	46489,	46499,	46507,	46511,	46523,	46549,
+	46559,	46567,	46573,	46589,	46591,	46601,	46619,	46633,	46639,	46643,
+	46649,	46663,	46679,	46681,	46687,	46691,	46703,	46723,	46727,	46747,
+	46751,	46757,	46769,	46771,	46807,	46811,	46817,	46819,	46829,	46831,
+	46853,	46861,	46867,	46877,	46889,	46901,	46919,	46933,	46957,	46993,
+	46997,	47017,	47041,	47051,	47057,	47059,	47087,	47093,	47111,	47119,
+	47123,	47129,	47137,	47143,	47147,	47149,	47161,	47189,	47207,	47221,
+	47237,	47251,	47269,	47279,	47287,	47293,	47297,	47303,	47309,	47317,
+	47339,	47351,	47353,	47363,	47381,	47387,	47389,	47407,	47417,	47419,
+	47431,	47441,	47459,	47491,	47497,	47501,	47507,	47513,	47521,	47527,
+	47533,	47543,	47563,	47569,	47581,	47591,	47599,	47609,	47623,	47629,
+	47639,	47653,	47657,	47659,	47681,	47699,	47701,	47711,	47713,	47717,
+	47737,	47741,	47743,	47777,	47779,	47791,	47797,	47807,	47809,	47819,
+	47837,	47843,	47857,	47869,	47881,	47903,	47911,	47917,	47933,	47939,
+	47947,	47951,	47963,	47969,	47977,	47981,	48017,	48023,	48029,	48049,
+	48073,	48079,	48091,	48109,	48119,	48121,	48131,	48157,	48163,	48179,
+	48187,	48193,	48197,	48221,	48239,	48247,	48259,	48271,	48281,	48299,
+	48311,	48313,	48337,	48341,	48353,	48371,	48383,	48397,	48407,	48409,
+	48413,	48437,	48449,	48463,	48473,	48479,	48481,	48487,	48491,	48497,
+	48523,	48527,	48533,	48539,	48541,	48563,	48571,	48589,	48593,	48611,
+	48619,	48623,	48647,	48649,	48661,	48673,	48677,	48679,	48731,	48733,
+	48751,	48757,	48761,	48767,	48779,	48781,	48787,	48799,	48809,	48817,
+	48821,	48823,	48847,	48857,	48859,	48869,	48871,	48883,	48889,	48907,
+	48947,	48953,	48973,	48989,	48991,	49003,	49009,	49019,	49031,	49033,
+	49037,	49043,	49057,	49069,	49081,	49103,	49109,	49117,	49121,	49123,
+	49139,	49157,	49169,	49171,	49177,	49193,	49199,	49201,	49207,	49211,
+	49223,	49253,	49261,	49277,	49279,	49297,	49307,	49331,	49333,	49339,
+	49363,	49367,	49369,	49391,	49393,	49409,	49411,	49417,	49429,	49433,
+	49451,	49459,	49463,	49477,	49481,	49499,	49523,	49529,	49531,	49537,
+	49547,	49549,	49559,	49597,	49603,	49613,	49627,	49633,	49639,	49663,
+	49667,	49669,	49681,	49697,	49711,	49727,	49739,	49741,	49747,	49757,
+	49783,	49787,	49789,	49801,	49807,	49811,	49823,	49831,	49843,	49853,
+	49871,	49877,	49891,	49919,	49921,	49927,	49937,	49939,	49943,	49957,
+	49991,	49993,	49999,	50021,	50023,	50033,	50047,	50051,	50053,	50069,
+	50077,	50087,	50093,	50101,	50111,	50119,	50123,	50129,	50131,	50147,
+	50153,	50159,	50177,	50207,	50221,	50227,	50231,	50261,	50263,	50273,
+	50287,	50291,	50311,	50321,	50329,	50333,	50341,	50359,	50363,	50377,
+	50383,	50387,	50411,	50417,	50423,	50441,	50459,	50461,	50497,	50503,
+	50513,	50527,	50539,	50543,	50549,	50551,	50581,	50587,	50591,	50593,
+	50599,	50627,	50647,	50651,	50671,	50683,	50707,	50723,	50741,	50753,
+	50767,	50773,	50777,	50789,	50821,	50833,	50839,	50849,	50857,	50867,
+	50873,	50891,	50893,	50909,	50923,	50929,	50951,	50957,	50969,	50971,
+	50989,	50993,	51001,	51031,	51043,	51047,	51059,	51061,	51071,	51109,
+	51131,	51133,	51137,	51151,	51157,	51169,	51193,	51197,	51199,	51203,
+	51217,	51229,	51239,	51241,	51257,	51263,	51283,	51287,	51307,	51329,
+	51341,	51343,	51347,	51349,	51361,	51383,	51407,	51413,	51419,	51421,
+	51427,	51431,	51437,	51439,	51449,	51461,	51473,	51479,	51481,	51487,
+	51503,	51511,	51517,	51521,	51539,	51551,	51563,	51577,	51581,	51593,
+	51599,	51607,	51613,	51631,	51637,	51647,	51659,	51673,	51679,	51683,
+	51691,	51713,	51719,	51721,	51749,	51767,	51769,	51787,	51797,	51803,
+	51817,	51827,	51829,	51839,	51853,	51859,	51869,	51871,	51893,	51899,
+	51907,	51913,	51929,	51941,	51949,	51971,	51973,	51977,	51991,	52009,
+	52021,	52027,	52051,	52057,	52067,	52069,	52081,	52103,	52121,	52127,
+	52147,	52153,	52163,	52177,	52181,	52183,	52189,	52201,	52223,	52237,
+	52249,	52253,	52259,	52267,	52289,	52291,	52301,	52313,	52321,	52361,
+	52363,	52369,	52379,	52387,	52391,	52433,	52453,	52457,	52489,	52501,
+	52511,	52517,	52529,	52541,	52543,	52553,	52561,	52567,	52571,	52579,
+	52583,	52609,	52627,	52631,	52639,	52667,	52673,	52691,	52697,	52709,
+	52711,	52721,	52727,	52733,	52747,	52757,	52769,	52783,	52807,	52813,
+	52817,	52837,	52859,	52861,	52879,	52883,	52889,	52901,	52903,	52919,
+	52937,	52951,	52957,	52963,	52967,	52973,	52981,	52999,	53003,	53017,
+	53047,	53051,	53069,	53077,	53087,	53089,	53093,	53101,	53113,	53117,
+	53129,	53147,	53149,	53161,	53171,	53173,	53189,	53197,	53201,	53231,
+	53233,	53239,	53267,	53269,	53279,	53281,	53299,	53309,	53323,	53327,
+	53353,	53359,	53377,	53381,	53401,	53407,	53411,	53419,	53437,	53441,
+	53453,	53479,	53503,	53507,	53527,	53549,	53551,	53569,	53591,	53593,
+	53597,	53609,	53611,	53617,	53623,	53629,	53633,	53639,	53653,	53657,
+	53681,	53693,	53699,	53717,	53719,	53731,	53759,	53773,	53777,	53783,
+	53791,	53813,	53819,	53831,	53849,	53857,	53861,	53881,	53887,	53891,
+	53897,	53899,	53917,	53923,	53927,	53939,	53951,	53959,	53987,	53993,
+	54001,	54011,	54013,	54037,	54049,	54059,	54083,	54091,	54101,	54121,
+	54133,	54139,	54151,	54163,	54167,	54181,	54193,	54217,	54251,	54269,
+	54277,	54287,	54293,	54311,	54319,	54323,	54331,	54347,	54361,	54367,
+	54371,	54377,	54401,	54403,	54409,	54413,	54419,	54421,	54437,	54443,
+	54449,	54469,	54493,	54497,	54499,	54503,	54517,	54521,	54539,	54541,
+	54547,	54559,	54563,	54577,	54581,	54583,	54601,	54617,	54623,	54629,
+	54631,	54647,	54667,	54673,	54679,	54709,	54713,	54721,	54727,	54751,
+	54767,	54773,	54779,	54787,	54799,	54829,	54833,	54851,	54869,	54877,
+	54881,	54907,	54917,	54919,	54941,	54949,	54959,	54973,	54979,	54983,
+	55001,	55009,	55021,	55049,	55051,	55057,	55061,	55073,	55079,	55103,
+	55109,	55117,	55127,	55147,	55163,	55171,	55201,	55207,	55213,	55217,
+	55219,	55229,	55243,	55249,	55259,	55291,	55313,	55331,	55333,	55337,
+	55339,	55343,	55351,	55373,	55381,	55399,	55411,	55439,	55441,	55457,
+	55469,	55487,	55501,	55511,	55529,	55541,	55547,	55579,	55589,	55603,
+	55609,	55619,	55621,	55631,	55633,	55639,	55661,	55663,	55667,	55673,
+	55681,	55691,	55697,	55711,	55717,	55721,	55733,	55763,	55787,	55793,
+	55799,	55807,	55813,	55817,	55819,	55823,	55829,	55837,	55843,	55849,
+	55871,	55889,	55897,	55901,	55903,	55921,	55927,	55931,	55933,	55949,
+	55967,	55987,	55997,	56003,	56009,	56039,	56041,	56053,	56081,	56087,
+	56093,	56099,	56101,	56113,	56123,	56131,	56149,	56167,	56171,	56179,
+	56197,	56207,	56209,	56237,	56239,	56249,	56263,	56267,	56269,	56299,
+	56311,	56333,	56359,	56369,	56377,	56383,	56393,	56401,	56417,	56431,
+	56437,	56443,	56453,	56467,	56473,	56477,	56479,	56489,	56501,	56503,
+	56509,	56519,	56527,	56531,	56533,	56543,	56569,	56591,	56597,	56599,
+	56611,	56629,	56633,	56659,	56663,	56671,	56681,	56687,	56701,	56711,
+	56713,	56731,	56737,	56747,	56767,	56773,	56779,	56783,	56807,	56809,
+	56813,	56821,	56827,	56843,	56857,	56873,	56891,	56893,	56897,	56909,
+	56911,	56921,	56923,	56929,	56941,	56951,	56957,	56963,	56983,	56989,
+	56993,	56999,	57037,	57041,	57047,	57059,	57073,	57077,	57089,	57097,
+	57107,	57119,	57131,	57139,	57143,	57149,	57163,	57173,	57179,	57191,
+	57193,	57203,	57221,	57223,	57241,	57251,	57259,	57269,	57271,	57283,
+	57287,	57301,	57329,	57331,	57347,	57349,	57367,	57373,	57383,	57389,
+	57397,	57413,	57427,	57457,	57467,	57487,	57493,	57503,	57527,	57529,
+	57557,	57559,	57571,	57587,	57593,	57601,	57637,	57641,	57649,	57653,
+	57667,	57679,	57689,	57697,	57709,	57713,	57719,	57727,	57731,	57737,
+	57751,	57773,	57781,	57787,	57791,	57793,	57803,	57809,	57829,	57839,
+	57847,	57853,	57859,	57881,	57899,	57901,	57917,	57923,	57943,	57947,
+	57973,	57977,	57991,	58013,	58027,	58031,	58043,	58049,	58057,	58061,
+	58067,	58073,	58099,	58109,	58111,	58129,	58147,	58151,	58153,	58169,
+	58171,	58189,	58193,	58199,	58207,	58211,	58217,	58229,	58231,	58237,
+	58243,	58271,	58309,	58313,	58321,	58337,	58363,	58367,	58369,	58379,
+	58391,	58393,	58403,	58411,	58417,	58427,	58439,	58441,	58451,	58453,
+	58477,	58481,	58511,	58537,	58543,	58549,	58567,	58573,	58579,	58601,
+	58603,	58613,	58631,	58657,	58661,	58679,	58687,	58693,	58699,	58711,
+	58727,	58733,	58741,	58757,	58763,	58771,	58787,	58789,	58831,	58889,
+	58897,	58901,	58907,	58909,	58913,	58921,	58937,	58943,	58963,	58967,
+	58979,	58991,	58997,	59009,	59011,	59021,	59023,	59029,	59051,	59053,
+	59063,	59069,	59077,	59083,	59093,	59107,	59113,	59119,	59123,	59141,
+	59149,	59159,	59167,	59183,	59197,	59207,	59209,	59219,	59221,	59233,
+	59239,	59243,	59263,	59273,	59281,	59333,	59341,	59351,	59357,	59359,
+	59369,	59377,	59387,	59393,	59399,	59407,	59417,	59419,	59441,	59443,
+	59447,	59453,	59467,	59471,	59473,	59497,	59509,	59513,	59539,	59557,
+	59561,	59567,	59581,	59611,	59617,	59621,	59627,	59629,	59651,	59659,
+	59663,	59669,	59671,	59693,	59699,	59707,	59723,	59729,	59743,	59747,
+	59753,	59771,	59779,	59791,	59797,	59809,	59833,	59863,	59879,	59887,
+	59921,	59929,	59951,	59957,	59971,	59981,	59999,	60013,	60017,	60029,
+	60037,	60041,	60077,	60083,	60089,	60091,	60101,	60103,	60107,	60127,
+	60133,	60139,	60149,	60161,	60167,	60169,	60209,	60217,	60223,	60251,
+	60257,	60259,	60271,	60289,	60293,	60317,	60331,	60337,	60343,	60353,
+	60373,	60383,	60397,	60413,	60427,	60443,	60449,	60457,	60493,	60497,
+	60509,	60521,	60527,	60539,	60589,	60601,	60607,	60611,	60617,	60623,
+	60631,	60637,	60647,	60649,	60659,	60661,	60679,	60689,	60703,	60719,
+	60727,	60733,	60737,	60757,	60761,	60763,	60773,	60779,	60793,	60811,
+	60821,	60859,	60869,	60887,	60889,	60899,	60901,	60913,	60917,	60919,
+	60923,	60937,	60943,	60953,	60961,	61001,	61007,	61027,	61031,	61043,
+	61051,	61057,	61091,	61099,	61121,	61129,	61141,	61151,	61153,	61169,
+	61211,	61223,	61231,	61253,	61261,	61283,	61291,	61297,	61331,	61333,
+	61339,	61343,	61357,	61363,	61379,	61381,	61403,	61409,	61417,	61441,
+	61463,	61469,	61471,	61483,	61487,	61493,	61507,	61511,	61519,	61543,
+	61547,	61553,	61559,	61561,	61583,	61603,	61609,	61613,	61627,	61631,
+	61637,	61643,	61651,	61657,	61667,	61673,	61681,	61687,	61703,	61717,
+	61723,	61729,	61751,	61757,	61781,	61813,	61819,	61837,	61843,	61861,
+	61871,	61879,	61909,	61927,	61933,	61949,	61961,	61967,	61979,	61981,
+	61987,	61991,	62003,	62011,	62017,	62039,	62047,	62053,	62057,	62071,
+	62081,	62099,	62119,	62129,	62131,	62137,	62141,	62143,	62171,	62189,
+	62191,	62201,	62207,	62213,	62219,	62233,	62273,	62297,	62299,	62303,
+	62311,	62323,	62327,	62347,	62351,	62383,	62401,	62417,	62423,	62459,
+	62467,	62473,	62477,	62483,	62497,	62501,	62507,	62533,	62539,	62549,
+	62563,	62581,	62591,	62597,	62603,	62617,	62627,	62633,	62639,	62653,
+	62659,	62683,	62687,	62701,	62723,	62731,	62743,	62753,	62761,	62773,
+	62791,	62801,	62819,	62827,	62851,	62861,	62869,	62873,	62897,	62903,
+	62921,	62927,	62929,	62939,	62969,	62971,	62981,	62983,	62987,	62989,
+	63029,	63031,	63059,	63067,	63073,	63079,	63097,	63103,	63113,	63127,
+	63131,	63149,	63179,	63197,	63199,	63211,	63241,	63247,	63277,	63281,
+	63299,	63311,	63313,	63317,	63331,	63337,	63347,	63353,	63361,	63367,
+	63377,	63389,	63391,	63397,	63409,	63419,	63421,	63439,	63443,	63463,
+	63467,	63473,	63487,	63493,	63499,	63521,	63527,	63533,	63541,	63559,
+	63577,	63587,	63589,	63599,	63601,	63607,	63611,	63617,	63629,	63647,
+	63649,	63659,	63667,	63671,	63689,	63691,	63697,	63703,	63709,	63719,
+	63727,	63737,	63743,	63761,	63773,	63781,	63793,	63799,	63803,	63809,
+	63823,	63839,	63841,	63853,	63857,	63863,	63901,	63907,	63913,	63929,
+	63949,	63977,	63997,	64007,	64013,	64019,	64033,	64037,	64063,	64067,
+	64081,	64091,	64109,	64123,	64151,	64153,	64157,	64171,	64187,	64189,
+	64217,	64223,	64231,	64237,	64271,	64279,	64283,	64301,	64303,	64319,
+	64327,	64333,	64373,	64381,	64399,	64403,	64433,	64439,	64451,	64453,
+	64483,	64489,	64499,	64513,	64553,	64567,	64577,	64579,	64591,	64601,
+	64609,	64613,	64621,	64627,	64633,	64661,	64663,	64667,	64679,	64693,
+	64709,	64717,	64747,	64763,	64781,	64783,	64793,	64811,	64817,	64849,
+	64853,	64871,	64877,	64879,	64891,	64901,	64919,	64921,	64927,	64937,
+	64951,	64969,	64997,	65003,	65011,	65027,	65029,	65033,	65053,	65063,
+	65071,	65089,	65099,	65101,	65111,	65119,	65123,	65129,	65141,	65147,
+	65167,	65171,	65173,	65179,	65183,	65203,	65213,	65239,	65257,	65267,
+	65269,	65287,	65293,	65309,	65323,	65327,	65353,	65357,	65371,	65381,
+	65393,	65407,	65413,	65419,	65423,	65437,	65447,	65449,	65479,	65497,
+	65519,	65521,	65537,	65539,	65543,	65551,	65557,	65563,	65579,	65581,
+	65587,	65599,	65609,	65617,	65629,	65633,	65647,	65651,	65657,	65677,
+	65687,	65699,	65701,	65707,	65713,	65717,	65719,	65729,	65731,	65761,
+	65777,	65789,	65809,	65827,	65831,	65837,	65839,	65843,	65851,	65867,
+	65881,	65899,	65921,	65927,	65929,	65951,	65957,	65963,	65981,	65983,
+	65993,	66029,	66037,	66041,	66047,	66067,	66071,	66083,	66089,	66103,
+	66107,	66109,	66137,	66161,	66169,	66173,	66179,	66191,	66221,	66239,
+	66271,	66293,	66301,	66337,	66343,	66347,	66359,	66361,	66373,	66377,
+	66383,	66403,	66413,	66431,	66449,	66457,	66463,	66467,	66491,	66499,
+	66509,	66523,	66529,	66533,	66541,	66553,	66569,	66571,	66587,	66593,
+	66601,	66617,	66629,	66643,	66653,	66683,	66697,	66701,	66713,	66721,
+	66733,	66739,	66749,	66751,	66763,	66791,	66797,	66809,	66821,	66841,
+	66851,	66853,	66863,	66877,	66883,	66889,	66919,	66923,	66931,	66943,
+	66947,	66949,	66959,	66973,	66977,	67003,	67021,	67033,	67043,	67049,
+	67057,	67061,	67073,	67079,	67103,	67121,	67129,	67139,	67141,	67153,
+	67157,	67169,	67181,	67187,	67189,	67211,	67213,	67217,	67219,	67231,
+	67247,	67261,	67271,	67273,	67289,	67307,	67339,	67343,	67349,	67369,
+	67391,	67399,	67409,	67411,	67421,	67427,	67429,	67433,	67447,	67453,
+	67477,	67481,	67489,	67493,	67499,	67511,	67523,	67531,	67537,	67547,
+	67559,	67567,	67577,	67579,	67589,	67601,	67607,	67619,	67631,	67651,
+	67679,	67699,	67709,	67723,	67733,	67741,	67751,	67757,	67759,	67763,
+	67777,	67783,	67789,	67801,	67807,	67819,	67829,	67843,	67853,	67867,
+	67883,	67891,	67901,	67927,	67931,	67933,	67939,	67943,	67957,	67961,
+	67967,	67979,	67987,	67993,	68023,	68041,	68053,	68059,	68071,	68087,
+	68099,	68111,	68113,	68141,	68147,	68161,	68171,	68207,	68209,	68213,
+	68219,	68227,	68239,	68261,	68279,	68281,	68311,	68329,	68351,	68371,
+	68389,	68399,	68437,	68443,	68447,	68449,	68473,	68477,	68483,	68489,
+	68491,	68501,	68507,	68521,	68531,	68539,	68543,	68567,	68581,	68597,
+	68611,	68633,	68639,	68659,	68669,	68683,	68687,	68699,	68711,	68713,
+	68729,	68737,	68743,	68749,	68767,	68771,	68777,	68791,	68813,	68819,
+	68821,	68863,	68879,	68881,	68891,	68897,	68899,	68903,	68909,	68917,
+	68927,	68947,	68963,	68993,	69001,	69011,	69019,	69029,	69031,	69061,
+	69067,	69073,	69109,	69119,	69127,	69143,	69149,	69151,	69163,	69191,
+	69193,	69197,	69203,	69221,	69233,	69239,	69247,	69257,	69259,	69263,
+	69313,	69317,	69337,	69341,	69371,	69379,	69383,	69389,	69401,	69403,
+	69427,	69431,	69439,	69457,	69463,	69467,	69473,	69481,	69491,	69493,
+	69497,	69499,	69539,	69557,	69593,	69623,	69653,	69661,	69677,	69691,
+	69697,	69709,	69737,	69739,	69761,	69763,	69767,	69779,	69809,	69821,
+	69827,	69829,	69833,	69847,	69857,	69859,	69877,	69899,	69911,	69929,
+	69931,	69941,	69959,	69991,	69997,	70001,	70003,	70009,	70019,	70039,
+	70051,	70061,	70067,	70079,	70099,	70111,	70117,	70121,	70123,	70139,
+	70141,	70157,	70163,	70177,	70181,	70183,	70199,	70201,	70207,	70223,
+	70229,	70237,	70241,	70249,	70271,	70289,	70297,	70309,	70313,	70321,
+	70327,	70351,	70373,	70379,	70381,	70393,	70423,	70429,	70439,	70451,
+	70457,	70459,	70481,	70487,	70489,	70501,	70507,	70529,	70537,	70549,
+	70571,	70573,	70583,	70589,	70607,	70619,	70621,	70627,	70639,	70657,
+	70663,	70667,	70687,	70709,	70717,	70729,	70753,	70769,	70783,	70793,
+	70823,	70841,	70843,	70849,	70853,	70867,	70877,	70879,	70891,	70901,
+	70913,	70919,	70921,	70937,	70949,	70951,	70957,	70969,	70979,	70981,
+	70991,	70997,	70999,	71011,	71023,	71039,	71059,	71069,	71081,	71089,
+	71119,	71129,	71143,	71147,	71153,	71161,	71167,	71171,	71191,	71209,
+	71233,	71237,	71249,	71257,	71261,	71263,	71287,	71293,	71317,	71327,
+	71329,	71333,	71339,	71341,	71347,	71353,	71359,	71363,	71387,	71389,
+	71399,	71411,	71413,	71419,	71429,	71437,	71443,	71453,	71471,	71473,
+	71479,	71483,	71503,	71527,	71537,	71549,	71551,	71563,	71569,	71593,
+	71597,	71633,	71647,	71663,	71671,	71693,	71699,	71707,	71711,	71713,
+	71719,	71741,	71761,	71777,	71789,	71807,	71809,	71821,	71837,	71843,
+	71849,	71861,	71867,	71879,	71881,	71887,	71899,	71909,	71917,	71933,
+	71941,	71947,	71963,	71971,	71983,	71987,	71993,	71999,	72019,	72031,
+	72043,	72047,	72053,	72073,	72077,	72089,	72091,	72101,	72103,	72109,
+	72139,	72161,	72167,	72169,	72173,	72211,	72221,	72223,	72227,	72229,
+	72251,	72253,	72269,	72271,	72277,	72287,	72307,	72313,	72337,	72341,
+	72353,	72367,	72379,	72383,	72421,	72431,	72461,	72467,	72469,	72481,
+	72493,	72497,	72503,	72533,	72547,	72551,	72559,	72577,	72613,	72617,
+	72623,	72643,	72647,	72649,	72661,	72671,	72673,	72679,	72689,	72701,
+	72707,	72719,	72727,	72733,	72739,	72763,	72767,	72797,	72817,	72823,
+	72859,	72869,	72871,	72883,	72889,	72893,	72901,	72907,	72911,	72923,
+	72931,	72937,	72949,	72953,	72959,	72973,	72977,	72997,	73009,	73013,
+	73019,	73037,	73039,	73043,	73061,	73063,	73079,	73091,	73121,	73127,
+	73133,	73141,	73181,	73189,	73237,	73243,	73259,	73277,	73291,	73303,
+	73309,	73327,	73331,	73351,	73361,	73363,	73369,	73379,	73387,	73417,
+	73421,	73433,	73453,	73459,	73471,	73477,	73483,	73517,	73523,	73529,
+	73547,	73553,	73561,	73571,	73583,	73589,	73597,	73607,	73609,	73613,
+	73637,	73643,	73651,	73673,	73679,	73681,	73693,	73699,	73709,	73721,
+	73727,	73751,	73757,	73771,	73783,	73819,	73823,	73847,	73849,	73859,
+	73867,	73877,	73883,	73897,	73907,	73939,	73943,	73951,	73961,	73973,
+	73999,	74017,	74021,	74027,	74047,	74051,	74071,	74077,	74093,	74099,
+	74101,	74131,	74143,	74149,	74159,	74161,	74167,	74177,	74189,	74197,
+	74201,	74203,	74209,	74219,	74231,	74257,	74279,	74287,	74293,	74297,
+	74311,	74317,	74323,	74353,	74357,	74363,	74377,	74381,	74383,	74411,
+	74413,	74419,	74441,	74449,	74453,	74471,	74489,	74507,	74509,	74521,
+	74527,	74531,	74551,	74561,	74567,	74573,	74587,	74597,	74609,	74611,
+	74623,	74653,	74687,	74699,	74707,	74713,	74717,	74719,	74729,	74731,
+	74747,	74759,	74761,	74771,	74779,	74797,	74821,	74827,	74831,	74843,
+	74857,	74861,	74869,	74873,	74887,	74891,	74897,	74903,	74923,	74929,
+	74933,	74941,	74959,	75011,	75013,	75017,	75029,	75037,	75041,	75079,
+	75083,	75109,	75133,	75149,	75161,	75167,	75169,	75181,	75193,	75209,
+	75211,	75217,	75223,	75227,	75239,	75253,	75269,	75277,	75289,	75307,
+	75323,	75329,	75337,	75347,	75353,	75367,	75377,	75389,	75391,	75401,
+	75403,	75407,	75431,	75437,	75479,	75503,	75511,	75521,	75527,	75533,
+	75539,	75541,	75553,	75557,	75571,	75577,	75583,	75611,	75617,	75619,
+	75629,	75641,	75653,	75659,	75679,	75683,	75689,	75703,	75707,	75709,
+	75721,	75731,	75743,	75767,	75773,	75781,	75787,	75793,	75797,	75821,
+	75833,	75853,	75869,	75883,	75913,	75931,	75937,	75941,	75967,	75979,
+	75983,	75989,	75991,	75997,	76001,	76003,	76031,	76039,	76079,	76081,
+	76091,	76099,	76103,	76123,	76129,	76147,	76157,	76159,	76163,	76207,
+	76213,	76231,	76243,	76249,	76253,	76259,	76261,	76283,	76289,	76303,
+	76333,	76343,	76367,	76369,	76379,	76387,	76403,	76421,	76423,	76441,
+	76463,	76471,	76481,	76487,	76493,	76507,	76511,	76519,	76537,	76541,
+	76543,	76561,	76579,	76597,	76603,	76607,	76631,	76649,	76651,	76667,
+	76673,	76679,	76697,	76717,	76733,	76753,	76757,	76771,	76777,	76781,
+	76801,	76819,	76829,	76831,	76837,	76847,	76871,	76873,	76883,	76907,
+	76913,	76919,	76943,	76949,	76961,	76963,	76991,	77003,	77017,	77023,
+	77029,	77041,	77047,	77069,	77081,	77093,	77101,	77137,	77141,	77153,
+	77167,	77171,	77191,	77201,	77213,	77237,	77239,	77243,	77249,	77261,
+	77263,	77267,	77269,	77279,	77291,	77317,	77323,	77339,	77347,	77351,
+	77359,	77369,	77377,	77383,	77417,	77419,	77431,	77447,	77471,	77477,
+	77479,	77489,	77491,	77509,	77513,	77521,	77527,	77543,	77549,	77551,
+	77557,	77563,	77569,	77573,	77587,	77591,	77611,	77617,	77621,	77641,
+	77647,	77659,	77681,	77687,	77689,	77699,	77711,	77713,	77719,	77723,
+	77731,	77743,	77747,	77761,	77773,	77783,	77797,	77801,	77813,	77839,
+	77849,	77863,	77867,	77893,	77899,	77929,	77933,	77951,	77969,	77977,
+	77983,	77999,	78007,	78017,	78031,	78041,	78049,	78059,	78079,	78101,
+	78121,	78137,	78139,	78157,	78163,	78167,	78173,	78179,	78191,	78193,
+	78203,	78229,	78233,	78241,	78259,	78277,	78283,	78301,	78307,	78311,
+	78317,	78341,	78347,	78367,	78401,	78427,	78437,	78439,	78467,	78479,
+	78487,	78497,	78509,	78511,	78517,	78539,	78541,	78553,	78569,	78571,
+	78577,	78583,	78593,	78607,	78623,	78643,	78649,	78653,	78691,	78697,
+	78707,	78713,	78721,	78737,	78779,	78781,	78787,	78791,	78797,	78803,
+	78809,	78823,	78839,	78853,	78857,	78877,	78887,	78889,	78893,	78901,
+	78919,	78929,	78941,	78977,	78979,	78989,	79031,	79039,	79043,	79063,
+	79087,	79103,	79111,	79133,	79139,	79147,	79151,	79153,	79159,	79181,
+	79187,	79193,	79201,	79229,	79231,	79241,	79259,	79273,	79279,	79283,
+	79301,	79309,	79319,	79333,	79337,	79349,	79357,	79367,	79379,	79393,
+	79397,	79399,	79411,	79423,	79427,	79433,	79451,	79481,	79493,	79531,
+	79537,	79549,	79559,	79561,	79579,	79589,	79601,	79609,	79613,	79621,
+	79627,	79631,	79633,	79657,	79669,	79687,	79691,	79693,	79697,	79699,
+	79757,	79769,	79777,	79801,	79811,	79813,	79817,	79823,	79829,	79841,
+	79843,	79847,	79861,	79867,	79873,	79889,	79901,	79903,	79907,	79939,
+	79943,	79967,	79973,	79979,	79987,	79997,	79999,	80021,	80039,	80051,
+	80071,	80077,	80107,	80111,	80141,	80147,	80149,	80153,	80167,	80173,
+	80177,	80191,	80207,	80209,	80221,	80231,	80233,	80239,	80251,	80263,
+	80273,	80279,	80287,	80309,	80317,	80329,	80341,	80347,	80363,	80369,
+	80387,	80407,	80429,	80447,	80449,	80471,	80473,	80489,	80491,	80513,
+	80527,	80537,	80557,	80567,	80599,	80603,	80611,	80621,	80627,	80629,
+	80651,	80657,	80669,	80671,	80677,	80681,	80683,	80687,	80701,	80713,
+	80737,	80747,	80749,	80761,	80777,	80779,	80783,	80789,	80803,	80809,
+	80819,	80831,	80833,	80849,	80863,	80897,	80909,	80911,	80917,	80923,
+	80929,	80933,	80953,	80963,	80989,	81001,	81013,	81017,	81019,	81023,
+	81031,	81041,	81043,	81047,	81049,	81071,	81077,	81083,	81097,	81101,
+	81119,	81131,	81157,	81163,	81173,	81181,	81197,	81199,	81203,	81223,
+	81233,	81239,	81281,	81283,	81293,	81299,	81307,	81331,	81343,	81349,
+	81353,	81359,	81371,	81373,	81401,	81409,	81421,	81439,	81457,	81463,
+	81509,	81517,	81527,	81533,	81547,	81551,	81553,	81559,	81563,	81569,
+	81611,	81619,	81629,	81637,	81647,	81649,	81667,	81671,	81677,	81689,
+	81701,	81703,	81707,	81727,	81737,	81749,	81761,	81769,	81773,	81799,
+	81817,	81839,	81847,	81853,	81869,	81883,	81899,	81901,	81919,	81929,
+	81931,	81937,	81943,	81953,	81967,	81971,	81973,	82003,	82007,	82009,
+	82013,	82021,	82031,	82037,	82039,	82051,	82067,	82073,	82129,	82139,
+	82141,	82153,	82163,	82171,	82183,	82189,	82193,	82207,	82217,	82219,
+	82223,	82231,	82237,	82241,	82261,	82267,	82279,	82301,	82307,	82339,
+	82349,	82351,	82361,	82373,	82387,	82393,	82421,	82457,	82463,	82469,
+	82471,	82483,	82487,	82493,	82499,	82507,	82529,	82531,	82549,	82559,
+	82561,	82567,	82571,	82591,	82601,	82609,	82613,	82619,	82633,	82651,
+	82657,	82699,	82721,	82723,	82727,	82729,	82757,	82759,	82763,	82781,
+	82787,	82793,	82799,	82811,	82813,	82837,	82847,	82883,	82889,	82891,
+	82903,	82913,	82939,	82963,	82981,	82997,	83003,	83009,	83023,	83047,
+	83059,	83063,	83071,	83077,	83089,	83093,	83101,	83117,	83137,	83177,
+	83203,	83207,	83219,	83221,	83227,	83231,	83233,	83243,	83257,	83267,
+	83269,	83273,	83299,	83311,	83339,	83341,	83357,	83383,	83389,	83399,
+	83401,	83407,	83417,	83423,	83431,	83437,	83443,	83449,	83459,	83471,
+	83477,	83497,	83537,	83557,	83561,	83563,	83579,	83591,	83597,	83609,
+	83617,	83621,	83639,	83641,	83653,	83663,	83689,	83701,	83717,	83719,
+	83737,	83761,	83773,	83777,	83791,	83813,	83833,	83843,	83857,	83869,
+	83873,	83891,	83903,	83911,	83921,	83933,	83939,	83969,	83983,	83987,
+	84011,	84017,	84047,	84053,	84059,	84061,	84067,	84089,	84121,	84127,
+	84131,	84137,	84143,	84163,	84179,	84181,	84191,	84199,	84211,	84221,
+	84223,	84229,	84239,	84247,	84263,	84299,	84307,	84313,	84317,	84319,
+	84347,	84349,	84377,	84389,	84391,	84401,	84407,	84421,	84431,	84437,
+	84443,	84449,	84457,	84463,	84467,	84481,	84499,	84503,	84509,	84521,
+	84523,	84533,	84551,	84559,	84589,	84629,	84631,	84649,	84653,	84659,
+	84673,	84691,	84697,	84701,	84713,	84719,	84731,	84737,	84751,	84761,
+	84787,	84793,	84809,	84811,	84827,	84857,	84859,	84869,	84871,	84913,
+	84919,	84947,	84961,	84967,	84977,	84979,	84991,	85009,	85021,	85027,
+	85037,	85049,	85061,	85081,	85087,	85091,	85093,	85103,	85109,	85121,
+	85133,	85147,	85159,	85193,	85199,	85201,	85213,	85223,	85229,	85237,
+	85243,	85247,	85259,	85297,	85303,	85313,	85331,	85333,	85361,	85363,
+	85369,	85381,	85411,	85427,	85429,	85439,	85447,	85451,	85453,	85469,
+	85487,	85513,	85517,	85523,	85531,	85549,	85571,	85577,	85597,	85601,
+	85607,	85619,	85621,	85627,	85639,	85643,	85661,	85667,	85669,	85691,
+	85703,	85711,	85717,	85733,	85751,	85781,	85793,	85817,	85819,	85829,
+	85831,	85837,	85843,	85847,	85853,	85889,	85903,	85909,	85931,	85933,
+	85991,	85999,	86011,	86017,	86027,	86029,	86069,	86077,	86083,	86111,
+	86113,	86117,	86131,	86137,	86143,	86161,	86171,	86179,	86183,	86197,
+	86201,	86209,	86239,	86243,	86249,	86257,	86263,	86269,	86287,	86291,
+	86293,	86297,	86311,	86323,	86341,	86351,	86353,	86357,	86369,	86371,
+	86381,	86389,	86399,	86413,	86423,	86441,	86453,	86461,	86467,	86477,
+	86491,	86501,	86509,	86531,	86533,	86539,	86561,	86573,	86579,	86587,
+	86599,	86627,	86629,	86677,	86689,	86693,	86711,	86719,	86729,	86743,
+	86753,	86767,	86771,	86783,	86813,	86837,	86843,	86851,	86857,	86861,
+	86869,	86923,	86927,	86929,	86939,	86951,	86959,	86969,	86981,	86993,
+	87011,	87013,	87037,	87041,	87049,	87071,	87083,	87103,	87107,	87119,
+	87121,	87133,	87149,	87151,	87179,	87181,	87187,	87211,	87221,	87223,
+	87251,	87253,	87257,	87277,	87281,	87293,	87299,	87313,	87317,	87323,
+	87337,	87359,	87383,	87403,	87407,	87421,	87427,	87433,	87443,	87473,
+	87481,	87491,	87509,	87511,	87517,	87523,	87539,	87541,	87547,	87553,
+	87557,	87559,	87583,	87587,	87589,	87613,	87623,	87629,	87631,	87641,
+	87643,	87649,	87671,	87679,	87683,	87691,	87697,	87701,	87719,	87721,
+	87739,	87743,	87751,	87767,	87793,	87797,	87803,	87811,	87833,	87853,
+	87869,	87877,	87881,	87887,	87911,	87917,	87931,	87943,	87959,	87961,
+	87973,	87977,	87991,	88001,	88003,	88007,	88019,	88037,	88069,	88079,
+	88093,	88117,	88129,	88169,	88177,	88211,	88223,	88237,	88241,	88259,
+	88261,	88289,	88301,	88321,	88327,	88337,	88339,	88379,	88397,	88411,
+	88423,	88427,	88463,	88469,	88471,	88493,	88499,	88513,	88523,	88547,
+	88589,	88591,	88607,	88609,	88643,	88651,	88657,	88661,	88663,	88667,
+	88681,	88721,	88729,	88741,	88747,	88771,	88789,	88793,	88799,	88801,
+	88807,	88811,	88813,	88817,	88819,	88843,	88853,	88861,	88867,	88873,
+	88883,	88897,	88903,	88919,	88937,	88951,	88969,	88993,	88997,	89003,
+	89009,	89017,	89021,	89041,	89051,	89057,	89069,	89071,	89083,	89087,
+	89101,	89107,	89113,	89119,	89123,	89137,	89153,	89189,	89203,	89209,
+	89213,	89227,	89231,	89237,	89261,	89269,	89273,	89293,	89303,	89317,
+	89329,	89363,	89371,	89381,	89387,	89393,	89399,	89413,	89417,	89431,
+	89443,	89449,	89459,	89477,	89491,	89501,	89513,	89519,	89521,	89527,
+	89533,	89561,	89563,	89567,	89591,	89597,	89599,	89603,	89611,	89627,
+	89633,	89653,	89657,	89659,	89669,	89671,	89681,	89689,	89753,	89759,
+	89767,	89779,	89783,	89797,	89809,	89819,	89821,	89833,	89839,	89849,
+	89867,	89891,	89897,	89899,	89909,	89917,	89923,	89939,	89959,	89963,
+	89977,	89983,	89989,	90001,	90007,	90011,	90017,	90019,	90023,	90031,
+	90053,	90059,	90067,	90071,	90073,	90089,	90107,	90121,	90127,	90149,
+	90163,	90173,	90187,	90191,	90197,	90199,	90203,	90217,	90227,	90239,
+	90247,	90263,	90271,	90281,	90289,	90313,	90353,	90359,	90371,	90373,
+	90379,	90397,	90401,	90403,	90407,	90437,	90439,	90469,	90473,	90481,
+	90499,	90511,	90523,	90527,	90529,	90533,	90547,	90583,	90599,	90617,
+	90619,	90631,	90641,	90647,	90659,	90677,	90679,	90697,	90703,	90709,
+	90731,	90749,	90787,	90793,	90803,	90821,	90823,	90833,	90841,	90847,
+	90863,	90887,	90901,	90907,	90911,	90917,	90931,	90947,	90971,	90977,
+	90989,	90997,	91009,	91019,	91033,	91079,	91081,	91097,	91099,	91121,
+	91127,	91129,	91139,	91141,	91151,	91153,	91159,	91163,	91183,	91193,
+	91199,	91229,	91237,	91243,	91249,	91253,	91283,	91291,	91297,	91303,
+	91309,	91331,	91367,	91369,	91373,	91381,	91387,	91393,	91397,	91411,
+	91423,	91433,	91453,	91457,	91459,	91463,	91493,	91499,	91513,	91529,
+	91541,	91571,	91573,	91577,	91583,	91591,	91621,	91631,	91639,	91673,
+	91691,	91703,	91711,	91733,	91753,	91757,	91771,	91781,	91801,	91807,
+	91811,	91813,	91823,	91837,	91841,	91867,	91873,	91909,	91921,	91939,
+	91943,	91951,	91957,	91961,	91967,	91969,	91997,	92003,	92009,	92033,
+	92041,	92051,	92077,	92083,	92107,	92111,	92119,	92143,	92153,	92173,
+	92177,	92179,	92189,	92203,	92219,	92221,	92227,	92233,	92237,	92243,
+	92251,	92269,	92297,	92311,	92317,	92333,	92347,	92353,	92357,	92363,
+	92369,	92377,	92381,	92383,	92387,	92399,	92401,	92413,	92419,	92431,
+	92459,	92461,	92467,	92479,	92489,	92503,	92507,	92551,	92557,	92567,
+	92569,	92581,	92593,	92623,	92627,	92639,	92641,	92647,	92657,	92669,
+	92671,	92681,	92683,	92693,	92699,	92707,	92717,	92723,	92737,	92753,
+	92761,	92767,	92779,	92789,	92791,	92801,	92809,	92821,	92831,	92849,
+	92857,	92861,	92863,	92867,	92893,	92899,	92921,	92927,	92941,	92951,
+	92957,	92959,	92987,	92993,	93001,	93047,	93053,	93059,	93077,	93083,
+	93089,	93097,	93103,	93113,	93131,	93133,	93139,	93151,	93169,	93179,
+	93187,	93199,	93229,	93239,	93241,	93251,	93253,	93257,	93263,	93281,
+	93283,	93287,	93307,	93319,	93323,	93329,	93337,	93371,	93377,	93383,
+	93407,	93419,	93427,	93463,	93479,	93481,	93487,	93491,	93493,	93497,
+	93503,	93523,	93529,	93553,	93557,	93559,	93563,	93581,	93601,	93607,
+	93629,	93637,	93683,	93701,	93703,	93719,	93739,	93761,	93763,	93787,
+	93809,	93811,	93827,	93851,	93871,	93887,	93889,	93893,	93901,	93911,
+	93913,	93923,	93937,	93941,	93949,	93967,	93971,	93979,	93983,	93997,
+	94007,	94009,	94033,	94049,	94057,	94063,	94079,	94099,	94109,	94111,
+	94117,	94121,	94151,	94153,	94169,	94201,	94207,	94219,	94229,	94253,
+	94261,	94273,	94291,	94307,	94309,	94321,	94327,	94331,	94343,	94349,
+	94351,	94379,	94397,	94399,	94421,	94427,	94433,	94439,	94441,	94447,
+	94463,	94477,	94483,	94513,	94529,	94531,	94541,	94543,	94547,	94559,
+	94561,	94573,	94583,	94597,	94603,	94613,	94621,	94649,	94651,	94687,
+	94693,	94709,	94723,	94727,	94747,	94771,	94777,	94781,	94789,	94793,
+	94811,	94819,	94823,	94837,	94841,	94847,	94849,	94873,	94889,	94903,
+	94907,	94933,	94949,	94951,	94961,	94993,	94999,	95003,	95009,	95021,
+	95027,	95063,	95071,	95083,	95087,	95089,	95093,	95101,	95107,	95111,
+	95131,	95143,	95153,	95177,	95189,	95191,	95203,	95213,	95219,	95231,
+	95233,	95239,	95257,	95261,	95267,	95273,	95279,	95287,	95311,	95317,
+	95327,	95339,	95369,	95383,	95393,	95401,	95413,	95419,	95429,	95441,
+	95443,	95461,	95467,	95471,	95479,	95483,	95507,	95527,	95531,	95539,
+	95549,	95561,	95569,	95581,	95597,	95603,	95617,	95621,	95629,	95633,
+	95651,	95701,	95707,	95713,	95717,	95723,	95731,	95737,	95747,	95773,
+	95783,	95789,	95791,	95801,	95803,	95813,	95819,	95857,	95869,	95873,
+	95881,	95891,	95911,	95917,	95923,	95929,	95947,	95957,	95959,	95971,
+	95987,	95989,	96001,	96013,	96017,	96043,	96053,	96059,	96079,	96097,
+	96137,	96149,	96157,	96167,	96179,	96181,	96199,	96211,	96221,	96223,
+	96233,	96259,	96263,	96269,	96281,	96289,	96293,	96323,	96329,	96331,
+	96337,	96353,	96377,	96401,	96419,	96431,	96443,	96451,	96457,	96461,
+	96469,	96479,	96487,	96493,	96497,	96517,	96527,	96553,	96557,	96581,
+	96587,	96589,	96601,	96643,	96661,	96667,	96671,	96697,	96703,	96731,
+	96737,	96739,	96749,	96757,	96763,	96769,	96779,	96787,	96797,	96799,
+	96821,	96823,	96827,	96847,	96851,	96857,	96893,	96907,	96911,	96931,
+	96953,	96959,	96973,	96979,	96989,	96997,	97001,	97003,	97007,	97021,
+	97039,	97073,	97081,	97103,	97117,	97127,	97151,	97157,	97159,	97169,
+	97171,	97177,	97187,	97213,	97231,	97241,	97259,	97283,	97301,	97303,
+	97327,	97367,	97369,	97373,	97379,	97381,	97387,	97397,	97423,	97429,
+	97441,	97453,	97459,	97463,	97499,	97501,	97511,	97523,	97547,	97549,
+	97553,	97561,	97571,	97577,	97579,	97583,	97607,	97609,	97613,	97649,
+	97651,	97673,	97687,	97711,	97729,	97771,	97777,	97787,	97789,	97813,
+	97829,	97841,	97843,	97847,	97849,	97859,	97861,	97871,	97879,	97883,
+	97919,	97927,	97931,	97943,	97961,	97967,	97973,	97987,	98009,	98011,
+	98017,	98041,	98047,	98057,	98081,	98101,	98123,	98129,	98143,	98179,
+	98207,	98213,	98221,	98227,	98251,	98257,	98269,	98297,	98299,	98317,
+	98321,	98323,	98327,	98347,	98369,	98377,	98387,	98389,	98407,	98411,
+	98419,	98429,	98443,	98453,	98459,	98467,	98473,	98479,	98491,	98507,
+	98519,	98533,	98543,	98561,	98563,	98573,	98597,	98621,	98627,	98639,
+	98641,	98663,	98669,	98689,	98711,	98713,	98717,	98729,	98731,	98737,
+	98773,	98779,	98801,	98807,	98809,	98837,	98849,	98867,	98869,	98873,
+	98887,	98893,	98897,	98899,	98909,	98911,	98927,	98929,	98939,	98947,
+	98953,	98963,	98981,	98993,	98999,	99013,	99017,	99023,	99041,	99053,
+	99079,	99083,	99089,	99103,	99109,	99119,	99131,	99133,	99137,	99139,
+	99149,	99173,	99181,	99191,	99223,	99233,	99241,	99251,	99257,	99259,
+	99277,	99289,	99317,	99347,	99349,	99367,	99371,	99377,	99391,	99397,
+	99401,	99409,	99431,	99439,	99469,	99487,	99497,	99523,	99527,	99529,
+	99551,	99559,	99563,	99571,	99577,	99581,	99607,	99611,	99623,	99643,
+	99661,	99667,	99679,	99689,	99707,	99709,	99713,	99719,	99721,	99733,
+	99761,	99767,	99787,	99793,	99809,	99817,	99823,	99829,	99833,	99839,
+	99859,	99871,	99877,	99881,	99901,	99907,	99923,	99929,	99961,	99971,
+	99989,	99991,	100003,	100019,	100043,	100049,	100057,	100069,	100103,	100109,
+	100129,	100151,	100153,	100169,	100183,	100189,	100193,	100207,	100213,	100237,
+	100267,	100271,	100279,	100291,	100297,	100313,	100333,	100343,	100357,	100361,
+	100363,	100379,	100391,	100393,	100403,	100411,	100417,	100447,	100459,	100469,
+	100483,	100493,	100501,	100511,	100517,	100519,	100523,	100537,	100547,	100549,
+	100559,	100591,	100609,	100613,	100621,	100649,	100669,	100673,	100693,	100699,
+	100703,	100733,	100741,	100747,	100769,	100787,	100799,	100801,	100811,	100823,
+	100829,	100847,	100853,	100907,	100913,	100927,	100931,	100937,	100943,	100957,
+	100981,	100987,	100999,	101009,	101021,	101027,	101051,	101063,	101081,	101089,
+	101107,	101111,	101113,	101117,	101119,	101141,	101149,	101159,	101161,	101173,
+	101183,	101197,	101203,	101207,	101209,	101221,	101267,	101273,	101279,	101281,
+	101287,	101293,	101323,	101333,	101341,	101347,	101359,	101363,	101377,	101383,
+	101399,	101411,	101419,	101429,	101449,	101467,	101477,	101483,	101489,	101501,
+	101503,	101513,	101527,	101531,	101533,	101537,	101561,	101573,	101581,	101599,
+	101603,	101611,	101627,	101641,	101653,	101663,	101681,	101693,	101701,	101719,
+	101723,	101737,	101741,	101747,	101749,	101771,	101789,	101797,	101807,	101833,
+	101837,	101839,	101863,	101869,	101873,	101879,	101891,	101917,	101921,	101929,
+	101939,	101957,	101963,	101977,	101987,	101999,	102001,	102013,	102019,	102023,
+	102031,	102043,	102059,	102061,	102071,	102077,	102079,	102101,	102103,	102107,
+	102121,	102139,	102149,	102161,	102181,	102191,	102197,	102199,	102203,	102217,
+	102229,	102233,	102241,	102251,	102253,	102259,	102293,	102299,	102301,	102317,
+	102329,	102337,	102359,	102367,	102397,	102407,	102409,	102433,	102437,	102451,
+	102461,	102481,	102497,	102499,	102503,	102523,	102533,	102539,	102547,	102551,
+	102559,	102563,	102587,	102593,	102607,	102611,	102643,	102647,	102653,	102667,
+	102673,	102677,	102679,	102701,	102761,	102763,	102769,	102793,	102797,	102811,
+	102829,	102841,	102859,	102871,	102877,	102881,	102911,	102913,	102929,	102931,
+	102953,	102967,	102983,	103001,	103007,	103043,	103049,	103067,	103069,	103079,
+	103087,	103091,	103093,	103099,	103123,	103141,	103171,	103177,	103183,	103217,
+	103231,	103237,	103289,	103291,	103307,	103319,	103333,	103349,	103357,	103387,
+	103391,	103393,	103399,	103409,	103421,	103423,	103451,	103457,	103471,	103483,
+	103511,	103529,	103549,	103553,	103561,	103567,	103573,	103577,	103583,	103591,
+	103613,	103619,	103643,	103651,	103657,	103669,	103681,	103687,	103699,	103703,
+	103723,	103769,	103787,	103801,	103811,	103813,	103837,	103841,	103843,	103867,
+	103889,	103903,	103913,	103919,	103951,	103963,	103967,	103969,	103979,	103981,
+	103991,	103993,	103997,	104003,	104009,	104021,	104033,	104047,	104053,	104059,
+	104087,	104089,	104107,	104113,	104119,	104123,	104147,	104149,	104161,	104173,
+	104179,	104183,	104207,	104231,	104233,	104239,	104243,	104281,	104287,	104297,
+	104309,	104311,	104323,	104327,	104347,	104369,	104381,	104383,	104393,	104399,
+	104417,	104459,	104471,	104473,	104479,	104491,	104513,	104527,	104537,	104543,
+	104549,	104551,	104561,	104579,	104593,	104597,	104623,	104639,	104651,	104659,
+	104677,	104681,	104683,	104693,	104701,	104707,	104711,	104717,	104723,	104729,
+};
+
+//  return 1 if p is divisable by sp, 0 otherwise
+static int
+divides(mpint *dividend, ulong divisor)
+{
+	mpdigit d[2], q;
+	int i;
+
+	d[1] = 0;
+	for(i = dividend->top-1; i >= 0; i--){
+		d[0] = dividend->p[i];
+		mpdigdiv(d, divisor, &q);
+		d[1] = d[0] - divisor*q;
+	}
+	return d[1] == 0;
+}
+
+//  return -1 if p is divisable by one of the small primes, 0 otherwise
+int
+smallprimetest(mpint *p)
+{
+	int i;
+	ulong sp;
+
+	for(i = 0; i < nelem(smallprimes); i++){
+		sp = smallprimes[i];
+		if(p->top == 1 && p->p[0] <= sp)
+			break;
+		if(divides(p, sp))
+			return -1;
+	}
+	return 0;
+}
diff --git a/src/libsec/port/thumb.c b/src/libsec/port/thumb.c
new file mode 100644
index 0000000..cac95a4
--- /dev/null
+++ b/src/libsec/port/thumb.c
@@ -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;
+}
+
diff --git a/src/libsec/port/tlshand.c b/src/libsec/port/tlshand.c
new file mode 100644
index 0000000..68c9808
--- /dev/null
+++ b/src/libsec/port/tlshand.c
@@ -0,0 +1,2291 @@
+#include <u.h>
+#include <libc.h>
+#include <bio.h>
+#include <auth.h>
+#include <mp.h>
+#include <libsec.h>
+
+// The main groups of functions are:
+//		client/server - main handshake protocol definition
+//		message functions - formating handshake messages
+//		cipher choices - catalog of digest and encrypt algorithms
+//		security functions - PKCS#1, sslHMAC, session keygen
+//		general utility functions - malloc, serialization
+// The handshake protocol builds on the TLS/SSL3 record layer protocol,
+// which is implemented in kernel device #a.  See also /lib/rfc/rfc2246.
+
+enum {
+	TLSFinishedLen = 12,
+	SSL3FinishedLen = MD5dlen+SHA1dlen,
+	MaxKeyData = 104,	// amount of secret we may need
+	MaxChunk = 1<<14,
+	RandomSize = 32,
+	SidSize = 32,
+	MasterSecretSize = 48,
+	AQueue = 0,
+	AFlush = 1,
+};
+
+typedef struct TlsSec TlsSec;
+
+typedef struct Bytes{
+	int len;
+	uchar data[1];  // [len]
+} Bytes;
+
+typedef struct Ints{
+	int len;
+	int data[1];  // [len]
+} Ints;
+
+typedef struct Algs{
+	char *enc;
+	char *digest;
+	int nsecret;
+	int tlsid;
+	int ok;
+} Algs;
+
+typedef struct Finished{
+	uchar verify[SSL3FinishedLen];
+	int n;
+} Finished;
+
+typedef struct TlsConnection{
+	TlsSec *sec;	// security management goo
+	int hand, ctl;	// record layer file descriptors
+	int erred;		// set when tlsError called
+	int (*trace)(char*fmt, ...); // for debugging
+	int version;	// protocol we are speaking
+	int verset;		// version has been set
+	int ver2hi;		// server got a version 2 hello
+	int isClient;	// is this the client or server?
+	Bytes *sid;		// SessionID
+	Bytes *cert;	// only last - no chain
+
+	Lock statelk;
+	int state;		// must be set using setstate
+
+	// input buffer for handshake messages
+	uchar buf[MaxChunk+2048];
+	uchar *rp, *ep;
+
+	uchar crandom[RandomSize];	// client random
+	uchar srandom[RandomSize];	// server random
+	int clientVersion;	// version in ClientHello
+	char *digest;	// name of digest algorithm to use
+	char *enc;		// name of encryption algorithm to use
+	int nsecret;	// amount of secret data to init keys
+
+	// for finished messages
+	MD5state	hsmd5;	// handshake hash
+	SHAstate	hssha1;	// handshake hash
+	Finished	finished;
+} TlsConnection;
+
+typedef struct Msg{
+	int tag;
+	union {
+		struct {
+			int version;
+			uchar 	random[RandomSize];
+			Bytes*	sid;
+			Ints*	ciphers;
+			Bytes*	compressors;
+		} clientHello;
+		struct {
+			int version;
+			uchar 	random[RandomSize];
+			Bytes*	sid;
+			int cipher;
+			int compressor;
+		} serverHello;
+		struct {
+			int ncert;
+			Bytes **certs;
+		} certificate;
+		struct {
+			Bytes *types;
+			int nca;
+			Bytes **cas;
+		} certificateRequest;
+		struct {
+			Bytes *key;
+		} clientKeyExchange;
+		Finished finished;
+	} u;
+} Msg;
+
+struct TlsSec{
+	char *server;	// name of remote; nil for server
+	int ok;	// <0 killed; ==0 in progress; >0 reusable
+	RSApub *rsapub;
+	AuthRpc *rpc;	// factotum for rsa private key
+	uchar sec[MasterSecretSize];	// master secret
+	uchar crandom[RandomSize];	// client random
+	uchar srandom[RandomSize];	// server random
+	int clientVers;		// version in ClientHello
+	int vers;			// final version
+	// byte generation and handshake checksum
+	void (*prf)(uchar*, int, uchar*, int, char*, uchar*, int, uchar*, int);
+	void (*setFinished)(TlsSec*, MD5state, SHAstate, uchar*, int);
+	int nfin;
+};
+
+
+enum {
+	TLSVersion = 0x0301,
+	SSL3Version = 0x0300,
+	ProtocolVersion = 0x0301,	// maximum version we speak
+	MinProtoVersion = 0x0300,	// limits on version we accept
+	MaxProtoVersion	= 0x03ff,
+};
+
+// handshake type
+enum {
+	HHelloRequest,
+	HClientHello,
+	HServerHello,
+	HSSL2ClientHello = 9,  /* local convention;  see devtls.c */
+	HCertificate = 11,
+	HServerKeyExchange,
+	HCertificateRequest,
+	HServerHelloDone,
+	HCertificateVerify,
+	HClientKeyExchange,
+	HFinished = 20,
+	HMax
+};
+
+// alerts
+enum {
+	ECloseNotify = 0,
+	EUnexpectedMessage = 10,
+	EBadRecordMac = 20,
+	EDecryptionFailed = 21,
+	ERecordOverflow = 22,
+	EDecompressionFailure = 30,
+	EHandshakeFailure = 40,
+	ENoCertificate = 41,
+	EBadCertificate = 42,
+	EUnsupportedCertificate = 43,
+	ECertificateRevoked = 44,
+	ECertificateExpired = 45,
+	ECertificateUnknown = 46,
+	EIllegalParameter = 47,
+	EUnknownCa = 48,
+	EAccessDenied = 49,
+	EDecodeError = 50,
+	EDecryptError = 51,
+	EExportRestriction = 60,
+	EProtocolVersion = 70,
+	EInsufficientSecurity = 71,
+	EInternalError = 80,
+	EUserCanceled = 90,
+	ENoRenegotiation = 100,
+	EMax = 256
+};
+
+// cipher suites
+enum {
+	TLS_NULL_WITH_NULL_NULL	 		= 0x0000,
+	TLS_RSA_WITH_NULL_MD5 			= 0x0001,
+	TLS_RSA_WITH_NULL_SHA 			= 0x0002,
+	TLS_RSA_EXPORT_WITH_RC4_40_MD5 		= 0x0003,
+	TLS_RSA_WITH_RC4_128_MD5 		= 0x0004,
+	TLS_RSA_WITH_RC4_128_SHA 		= 0x0005,
+	TLS_RSA_EXPORT_WITH_RC2_CBC_40_MD5	= 0X0006,
+	TLS_RSA_WITH_IDEA_CBC_SHA 		= 0X0007,
+	TLS_RSA_EXPORT_WITH_DES40_CBC_SHA	= 0X0008,
+	TLS_RSA_WITH_DES_CBC_SHA		= 0X0009,
+	TLS_RSA_WITH_3DES_EDE_CBC_SHA		= 0X000A,
+	TLS_DH_DSS_EXPORT_WITH_DES40_CBC_SHA	= 0X000B,
+	TLS_DH_DSS_WITH_DES_CBC_SHA		= 0X000C,
+	TLS_DH_DSS_WITH_3DES_EDE_CBC_SHA	= 0X000D,
+	TLS_DH_RSA_EXPORT_WITH_DES40_CBC_SHA	= 0X000E,
+	TLS_DH_RSA_WITH_DES_CBC_SHA		= 0X000F,
+	TLS_DH_RSA_WITH_3DES_EDE_CBC_SHA	= 0X0010,
+	TLS_DHE_DSS_EXPORT_WITH_DES40_CBC_SHA	= 0X0011,
+	TLS_DHE_DSS_WITH_DES_CBC_SHA		= 0X0012,
+	TLS_DHE_DSS_WITH_3DES_EDE_CBC_SHA	= 0X0013,	// ZZZ must be implemented for tls1.0 compliance
+	TLS_DHE_RSA_EXPORT_WITH_DES40_CBC_SHA	= 0X0014,
+	TLS_DHE_RSA_WITH_DES_CBC_SHA		= 0X0015,
+	TLS_DHE_RSA_WITH_3DES_EDE_CBC_SHA	= 0X0016,
+	TLS_DH_anon_EXPORT_WITH_RC4_40_MD5	= 0x0017,
+	TLS_DH_anon_WITH_RC4_128_MD5 		= 0x0018,
+	TLS_DH_anon_EXPORT_WITH_DES40_CBC_SHA	= 0X0019,
+	TLS_DH_anon_WITH_DES_CBC_SHA		= 0X001A,
+	TLS_DH_anon_WITH_3DES_EDE_CBC_SHA	= 0X001B,
+
+	TLS_RSA_WITH_AES_128_CBC_SHA		= 0X002f,	// aes, aka rijndael with 128 bit blocks
+	TLS_DH_DSS_WITH_AES_128_CBC_SHA		= 0X0030,
+	TLS_DH_RSA_WITH_AES_128_CBC_SHA		= 0X0031,
+	TLS_DHE_DSS_WITH_AES_128_CBC_SHA	= 0X0032,
+	TLS_DHE_RSA_WITH_AES_128_CBC_SHA	= 0X0033,
+	TLS_DH_anon_WITH_AES_128_CBC_SHA	= 0X0034,
+	TLS_RSA_WITH_AES_256_CBC_SHA		= 0X0035,
+	TLS_DH_DSS_WITH_AES_256_CBC_SHA		= 0X0036,
+	TLS_DH_RSA_WITH_AES_256_CBC_SHA		= 0X0037,
+	TLS_DHE_DSS_WITH_AES_256_CBC_SHA	= 0X0038,
+	TLS_DHE_RSA_WITH_AES_256_CBC_SHA	= 0X0039,
+	TLS_DH_anon_WITH_AES_256_CBC_SHA	= 0X003A,
+	CipherMax
+};
+
+// compression methods
+enum {
+	CompressionNull = 0,
+	CompressionMax
+};
+
+static Algs cipherAlgs[] = {
+	{"rc4_128", "md5",	2 * (16 + MD5dlen), TLS_RSA_WITH_RC4_128_MD5},
+	{"rc4_128", "sha1",	2 * (16 + SHA1dlen), TLS_RSA_WITH_RC4_128_SHA},
+	{"3des_ede_cbc","sha1",2*(4*8+SHA1dlen), TLS_RSA_WITH_3DES_EDE_CBC_SHA},
+};
+
+static uchar compressors[] = {
+	CompressionNull,
+};
+
+static TlsConnection *tlsServer2(int ctl, int hand, uchar *cert, int ncert, int (*trace)(char*fmt, ...));
+static TlsConnection *tlsClient2(int ctl, int hand, uchar *csid, int ncsid, int (*trace)(char*fmt, ...));
+
+static void	msgClear(Msg *m);
+static char* msgPrint(char *buf, int n, Msg *m);
+static int	msgRecv(TlsConnection *c, Msg *m);
+static int	msgSend(TlsConnection *c, Msg *m, int act);
+static void	tlsError(TlsConnection *c, int err, char *msg, ...);
+/* #pragma	varargck argpos	tlsError 3*/
+static int setVersion(TlsConnection *c, int version);
+static int finishedMatch(TlsConnection *c, Finished *f);
+static void tlsConnectionFree(TlsConnection *c);
+
+static int setAlgs(TlsConnection *c, int a);
+static int okCipher(Ints *cv);
+static int okCompression(Bytes *cv);
+static int initCiphers(void);
+static Ints* makeciphers(void);
+
+static TlsSec* tlsSecInits(int cvers, uchar *csid, int ncsid, uchar *crandom, uchar *ssid, int *nssid, uchar *srandom);
+static int	tlsSecSecrets(TlsSec *sec, int vers, uchar *epm, int nepm, uchar *kd, int nkd);
+static TlsSec*	tlsSecInitc(int cvers, uchar *crandom);
+static int	tlsSecSecretc(TlsSec *sec, uchar *sid, int nsid, uchar *srandom, uchar *cert, int ncert, int vers, uchar **epm, int *nepm, uchar *kd, int nkd);
+static int	tlsSecFinished(TlsSec *sec, MD5state md5, SHAstate sha1, uchar *fin, int nfin, int isclient);
+static void	tlsSecOk(TlsSec *sec);
+static void	tlsSecKill(TlsSec *sec);
+static void	tlsSecClose(TlsSec *sec);
+static void	setMasterSecret(TlsSec *sec, Bytes *pm);
+static void	serverMasterSecret(TlsSec *sec, uchar *epm, int nepm);
+static void	setSecrets(TlsSec *sec, uchar *kd, int nkd);
+static int	clientMasterSecret(TlsSec *sec, RSApub *pub, uchar **epm, int *nepm);
+static Bytes *pkcs1_encrypt(Bytes* data, RSApub* key, int blocktype);
+static Bytes *pkcs1_decrypt(TlsSec *sec, uchar *epm, int nepm);
+static void	tlsSetFinished(TlsSec *sec, MD5state hsmd5, SHAstate hssha1, uchar *finished, int isClient);
+static void	sslSetFinished(TlsSec *sec, MD5state hsmd5, SHAstate hssha1, uchar *finished, int isClient);
+static void	sslPRF(uchar *buf, int nbuf, uchar *key, int nkey, char *label,
+			uchar *seed0, int nseed0, uchar *seed1, int nseed1);
+static int setVers(TlsSec *sec, int version);
+
+static AuthRpc* factotum_rsa_open(uchar *cert, int certlen);
+static mpint* factotum_rsa_decrypt(AuthRpc *rpc, mpint *cipher);
+static void factotum_rsa_close(AuthRpc*rpc);
+
+static void* emalloc(int);
+static void* erealloc(void*, int);
+static void put32(uchar *p, u32int);
+static void put24(uchar *p, int);
+static void put16(uchar *p, int);
+static u32int get32(uchar *p);
+static int get24(uchar *p);
+static int get16(uchar *p);
+static Bytes* newbytes(int len);
+static Bytes* makebytes(uchar* buf, int len);
+static void freebytes(Bytes* b);
+static Ints* newints(int len);
+static Ints* makeints(int* buf, int len);
+static void freeints(Ints* b);
+
+//================= client/server ========================
+
+//	push TLS onto fd, returning new (application) file descriptor
+//		or -1 if error.
+int
+tlsServer(int fd, TLSconn *conn)
+{
+	char buf[8];
+	char dname[64];
+	int n, data, ctl, hand;
+	TlsConnection *tls;
+
+	if(conn == nil)
+		return -1;
+	ctl = open("#a/tls/clone", ORDWR);
+	if(ctl < 0)
+		return -1;
+	n = read(ctl, buf, sizeof(buf)-1);
+	if(n < 0){
+		close(ctl);
+		return -1;
+	}
+	buf[n] = 0;
+	sprint(conn->dir, "#a/tls/%s", buf);
+	sprint(dname, "#a/tls/%s/hand", buf);
+	hand = open(dname, ORDWR);
+	if(hand < 0){
+		close(ctl);
+		return -1;
+	}
+	fprint(ctl, "fd %d 0x%x", fd, ProtocolVersion);
+	tls = tlsServer2(ctl, hand, conn->cert, conn->certlen, conn->trace);
+	sprint(dname, "#a/tls/%s/data", buf);
+	data = open(dname, ORDWR);
+	close(fd);
+	close(hand);
+	close(ctl);
+	if(data < 0){
+		return -1;
+	}
+	if(tls == nil){
+		close(data);
+		return -1;
+	}
+	if(conn->cert)
+		free(conn->cert);
+	conn->cert = 0;  // client certificates are not yet implemented
+	conn->certlen = 0;
+	conn->sessionIDlen = tls->sid->len;
+	conn->sessionID = emalloc(conn->sessionIDlen);
+	memcpy(conn->sessionID, tls->sid->data, conn->sessionIDlen);
+	tlsConnectionFree(tls);
+	return data;
+}
+
+//	push TLS onto fd, returning new (application) file descriptor
+//		or -1 if error.
+int
+tlsClient(int fd, TLSconn *conn)
+{
+	char buf[8];
+	char dname[64];
+	int n, data, ctl, hand;
+	TlsConnection *tls;
+
+	if(!conn)
+		return -1;
+	ctl = open("#a/tls/clone", ORDWR);
+	if(ctl < 0)
+		return -1;
+	n = read(ctl, buf, sizeof(buf)-1);
+	if(n < 0){
+		close(ctl);
+		return -1;
+	}
+	buf[n] = 0;
+	sprint(conn->dir, "#a/tls/%s", buf);
+	sprint(dname, "#a/tls/%s/hand", buf);
+	hand = open(dname, ORDWR);
+	if(hand < 0){
+		close(ctl);
+		return -1;
+	}
+	sprint(dname, "#a/tls/%s/data", buf);
+	data = open(dname, ORDWR);
+	if(data < 0)
+		return -1;
+	fprint(ctl, "fd %d 0x%x", fd, ProtocolVersion);
+	tls = tlsClient2(ctl, hand, conn->sessionID, conn->sessionIDlen, conn->trace);
+	close(fd);
+	close(hand);
+	close(ctl);
+	if(tls == nil){
+		close(data);
+		return -1;
+	}
+	conn->certlen = tls->cert->len;
+	conn->cert = emalloc(conn->certlen);
+	memcpy(conn->cert, tls->cert->data, conn->certlen);
+	conn->sessionIDlen = tls->sid->len;
+	conn->sessionID = emalloc(conn->sessionIDlen);
+	memcpy(conn->sessionID, tls->sid->data, conn->sessionIDlen);
+	tlsConnectionFree(tls);
+	return data;
+}
+
+static TlsConnection *
+tlsServer2(int ctl, int hand, uchar *cert, int ncert, int (*trace)(char*fmt, ...))
+{
+	TlsConnection *c;
+	Msg m;
+	Bytes *csid;
+	uchar sid[SidSize], kd[MaxKeyData];
+	char *secrets;
+	int cipher, compressor, nsid, rv;
+
+	if(trace)
+		trace("tlsServer2\n");
+	if(!initCiphers())
+		return nil;
+	c = emalloc(sizeof(TlsConnection));
+	c->ctl = ctl;
+	c->hand = hand;
+	c->trace = trace;
+	c->version = ProtocolVersion;
+
+	memset(&m, 0, sizeof(m));
+	if(!msgRecv(c, &m)){
+		if(trace)
+			trace("initial msgRecv failed\n");
+		goto Err;
+	}
+	if(m.tag != HClientHello) {
+		tlsError(c, EUnexpectedMessage, "expected a client hello");
+		goto Err;
+	}
+	c->clientVersion = m.u.clientHello.version;
+	if(trace)
+		trace("ClientHello version %x\n", c->clientVersion);
+	if(setVersion(c, m.u.clientHello.version) < 0) {
+		tlsError(c, EIllegalParameter, "incompatible version");
+		goto Err;
+	}
+
+	memmove(c->crandom, m.u.clientHello.random, RandomSize);
+	cipher = okCipher(m.u.clientHello.ciphers);
+	if(cipher < 0) {
+		// reply with EInsufficientSecurity if we know that's the case
+		if(cipher == -2)
+			tlsError(c, EInsufficientSecurity, "cipher suites too weak");
+		else
+			tlsError(c, EHandshakeFailure, "no matching cipher suite");
+		goto Err;
+	}
+	if(!setAlgs(c, cipher)){
+		tlsError(c, EHandshakeFailure, "no matching cipher suite");
+		goto Err;
+	}
+	compressor = okCompression(m.u.clientHello.compressors);
+	if(compressor < 0) {
+		tlsError(c, EHandshakeFailure, "no matching compressor");
+		goto Err;
+	}
+
+	csid = m.u.clientHello.sid;
+	if(trace)
+		trace("  cipher %d, compressor %d, csidlen %d\n", cipher, compressor, csid->len);
+	c->sec = tlsSecInits(c->clientVersion, csid->data, csid->len, c->crandom, sid, &nsid, c->srandom);
+	if(c->sec == nil){
+		tlsError(c, EHandshakeFailure, "can't initialize security: %r");
+		goto Err;
+	}
+	c->sec->rpc = factotum_rsa_open(cert, ncert);
+	if(c->sec->rpc == nil){
+		tlsError(c, EHandshakeFailure, "factotum_rsa_open: %r");
+		goto Err;
+	}
+	c->sec->rsapub = X509toRSApub(cert, ncert, nil, 0);
+	msgClear(&m);
+
+	m.tag = HServerHello;
+	m.u.serverHello.version = c->version;
+	memmove(m.u.serverHello.random, c->srandom, RandomSize);
+	m.u.serverHello.cipher = cipher;
+	m.u.serverHello.compressor = compressor;
+	c->sid = makebytes(sid, nsid);
+	m.u.serverHello.sid = makebytes(c->sid->data, c->sid->len);
+	if(!msgSend(c, &m, AQueue))
+		goto Err;
+	msgClear(&m);
+
+	m.tag = HCertificate;
+	m.u.certificate.ncert = 1;
+	m.u.certificate.certs = emalloc(m.u.certificate.ncert * sizeof(Bytes));
+	m.u.certificate.certs[0] = makebytes(cert, ncert);
+	if(!msgSend(c, &m, AQueue))
+		goto Err;
+	msgClear(&m);
+
+	m.tag = HServerHelloDone;
+	if(!msgSend(c, &m, AFlush))
+		goto Err;
+	msgClear(&m);
+
+	if(!msgRecv(c, &m))
+		goto Err;
+	if(m.tag != HClientKeyExchange) {
+		tlsError(c, EUnexpectedMessage, "expected a client key exchange");
+		goto Err;
+	}
+	if(tlsSecSecrets(c->sec, c->version, m.u.clientKeyExchange.key->data, m.u.clientKeyExchange.key->len, kd, c->nsecret) < 0){
+		tlsError(c, EHandshakeFailure, "couldn't set secrets: %r");
+		goto Err;
+	}
+	if(trace)
+		trace("tls secrets\n");
+	secrets = (char*)emalloc(2*c->nsecret);
+	enc64(secrets, 2*c->nsecret, kd, c->nsecret);
+	rv = fprint(c->ctl, "secret %s %s 0 %s", c->digest, c->enc, secrets);
+	memset(secrets, 0, 2*c->nsecret);
+	free(secrets);
+	memset(kd, 0, c->nsecret);
+	if(rv < 0){
+		tlsError(c, EHandshakeFailure, "can't set keys: %r");
+		goto Err;
+	}
+	msgClear(&m);
+
+	/* no CertificateVerify; skip to Finished */
+	if(tlsSecFinished(c->sec, c->hsmd5, c->hssha1, c->finished.verify, c->finished.n, 1) < 0){
+		tlsError(c, EInternalError, "can't set finished: %r");
+		goto Err;
+	}
+	if(!msgRecv(c, &m))
+		goto Err;
+	if(m.tag != HFinished) {
+		tlsError(c, EUnexpectedMessage, "expected a finished");
+		goto Err;
+	}
+	if(!finishedMatch(c, &m.u.finished)) {
+		tlsError(c, EHandshakeFailure, "finished verification failed");
+		goto Err;
+	}
+	msgClear(&m);
+
+	/* change cipher spec */
+	if(fprint(c->ctl, "changecipher") < 0){
+		tlsError(c, EInternalError, "can't enable cipher: %r");
+		goto Err;
+	}
+
+	if(tlsSecFinished(c->sec, c->hsmd5, c->hssha1, c->finished.verify, c->finished.n, 0) < 0){
+		tlsError(c, EInternalError, "can't set finished: %r");
+		goto Err;
+	}
+	m.tag = HFinished;
+	m.u.finished = c->finished;
+	if(!msgSend(c, &m, AFlush))
+		goto Err;
+	msgClear(&m);
+	if(trace)
+		trace("tls finished\n");
+
+	if(fprint(c->ctl, "opened") < 0)
+		goto Err;
+	tlsSecOk(c->sec);
+	return c;
+
+Err:
+	msgClear(&m);
+	tlsConnectionFree(c);
+	return 0;
+}
+
+static TlsConnection *
+tlsClient2(int ctl, int hand, uchar *csid, int ncsid, int (*trace)(char*fmt, ...))
+{
+	TlsConnection *c;
+	Msg m;
+	uchar kd[MaxKeyData], *epm;
+	char *secrets;
+	int creq, nepm, rv;
+
+	if(!initCiphers())
+		return nil;
+	epm = nil;
+	c = emalloc(sizeof(TlsConnection));
+	c->version = ProtocolVersion;
+	c->ctl = ctl;
+	c->hand = hand;
+	c->trace = trace;
+	c->isClient = 1;
+	c->clientVersion = c->version;
+
+	c->sec = tlsSecInitc(c->clientVersion, c->crandom);
+	if(c->sec == nil)
+		goto Err;
+
+	/* client hello */
+	memset(&m, 0, sizeof(m));
+	m.tag = HClientHello;
+	m.u.clientHello.version = c->clientVersion;
+	memmove(m.u.clientHello.random, c->crandom, RandomSize);
+	m.u.clientHello.sid = makebytes(csid, ncsid);
+	m.u.clientHello.ciphers = makeciphers();
+	m.u.clientHello.compressors = makebytes(compressors,sizeof(compressors));
+	if(!msgSend(c, &m, AFlush))
+		goto Err;
+	msgClear(&m);
+
+	/* server hello */
+	if(!msgRecv(c, &m))
+		goto Err;
+	if(m.tag != HServerHello) {
+		tlsError(c, EUnexpectedMessage, "expected a server hello");
+		goto Err;
+	}
+	if(setVersion(c, m.u.serverHello.version) < 0) {
+		tlsError(c, EIllegalParameter, "incompatible version %r");
+		goto Err;
+	}
+	memmove(c->srandom, m.u.serverHello.random, RandomSize);
+	c->sid = makebytes(m.u.serverHello.sid->data, m.u.serverHello.sid->len);
+	if(c->sid->len != 0 && c->sid->len != SidSize) {
+		tlsError(c, EIllegalParameter, "invalid server session identifier");
+		goto Err;
+	}
+	if(!setAlgs(c, m.u.serverHello.cipher)) {
+		tlsError(c, EIllegalParameter, "invalid cipher suite");
+		goto Err;
+	}
+	if(m.u.serverHello.compressor != CompressionNull) {
+		tlsError(c, EIllegalParameter, "invalid compression");
+		goto Err;
+	}
+	msgClear(&m);
+
+	/* certificate */
+	if(!msgRecv(c, &m) || m.tag != HCertificate) {
+		tlsError(c, EUnexpectedMessage, "expected a certificate");
+		goto Err;
+	}
+	if(m.u.certificate.ncert < 1) {
+		tlsError(c, EIllegalParameter, "runt certificate");
+		goto Err;
+	}
+	c->cert = makebytes(m.u.certificate.certs[0]->data, m.u.certificate.certs[0]->len);
+	msgClear(&m);
+
+	/* server key exchange (optional) */
+	if(!msgRecv(c, &m))
+		goto Err;
+	if(m.tag == HServerKeyExchange) {
+		tlsError(c, EUnexpectedMessage, "got an server key exchange");
+		goto Err;
+		// If implementing this later, watch out for rollback attack
+		// described in Wagner Schneier 1996, section 4.4.
+	}
+
+	/* certificate request (optional) */
+	creq = 0;
+	if(m.tag == HCertificateRequest) {
+		creq = 1;
+		msgClear(&m);
+		if(!msgRecv(c, &m))
+			goto Err;
+	}
+
+	if(m.tag != HServerHelloDone) {
+		tlsError(c, EUnexpectedMessage, "expected a server hello done");
+		goto Err;
+	}
+	msgClear(&m);
+
+	if(tlsSecSecretc(c->sec, c->sid->data, c->sid->len, c->srandom,
+			c->cert->data, c->cert->len, c->version, &epm, &nepm,
+			kd, c->nsecret) < 0){
+		tlsError(c, EBadCertificate, "invalid x509/rsa certificate");
+		goto Err;
+	}
+	secrets = (char*)emalloc(2*c->nsecret);
+	enc64(secrets, 2*c->nsecret, kd, c->nsecret);
+	rv = fprint(c->ctl, "secret %s %s 1 %s", c->digest, c->enc, secrets);
+	memset(secrets, 0, 2*c->nsecret);
+	free(secrets);
+	memset(kd, 0, c->nsecret);
+	if(rv < 0){
+		tlsError(c, EHandshakeFailure, "can't set keys: %r");
+		goto Err;
+	}
+
+	if(creq) {
+		/* send a zero length certificate */
+		m.tag = HCertificate;
+		if(!msgSend(c, &m, AFlush))
+			goto Err;
+		msgClear(&m);
+	}
+
+	/* client key exchange */
+	m.tag = HClientKeyExchange;
+	m.u.clientKeyExchange.key = makebytes(epm, nepm);
+	free(epm);
+	epm = nil;
+	if(m.u.clientKeyExchange.key == nil) {
+		tlsError(c, EHandshakeFailure, "can't set secret: %r");
+		goto Err;
+	}
+	if(!msgSend(c, &m, AFlush))
+		goto Err;
+	msgClear(&m);
+
+	/* change cipher spec */
+	if(fprint(c->ctl, "changecipher") < 0){
+		tlsError(c, EInternalError, "can't enable cipher: %r");
+		goto Err;
+	}
+
+	// Cipherchange must occur immediately before Finished to avoid
+	// potential hole;  see section 4.3 of Wagner Schneier 1996.
+	if(tlsSecFinished(c->sec, c->hsmd5, c->hssha1, c->finished.verify, c->finished.n, 1) < 0){
+		tlsError(c, EInternalError, "can't set finished 1: %r");
+		goto Err;
+	}
+	m.tag = HFinished;
+	m.u.finished = c->finished;
+
+	if(!msgSend(c, &m, AFlush)) {
+		fprint(2, "tlsClient nepm=%d\n", nepm);
+		tlsError(c, EInternalError, "can't flush after client Finished: %r");
+		goto Err;
+	}
+	msgClear(&m);
+
+	if(tlsSecFinished(c->sec, c->hsmd5, c->hssha1, c->finished.verify, c->finished.n, 0) < 0){
+		fprint(2, "tlsClient nepm=%d\n", nepm);
+		tlsError(c, EInternalError, "can't set finished 0: %r");
+		goto Err;
+	}
+	if(!msgRecv(c, &m)) {
+		fprint(2, "tlsClient nepm=%d\n", nepm);
+		tlsError(c, EInternalError, "can't read server Finished: %r");
+		goto Err;
+	}
+	if(m.tag != HFinished) {
+		fprint(2, "tlsClient nepm=%d\n", nepm);
+		tlsError(c, EUnexpectedMessage, "expected a Finished msg from server");
+		goto Err;
+	}
+
+	if(!finishedMatch(c, &m.u.finished)) {
+		tlsError(c, EHandshakeFailure, "finished verification failed");
+		goto Err;
+	}
+	msgClear(&m);
+
+	if(fprint(c->ctl, "opened") < 0){
+		if(trace)
+			trace("unable to do final open: %r\n");
+		goto Err;
+	}
+	tlsSecOk(c->sec);
+	return c;
+
+Err:
+	free(epm);
+	msgClear(&m);
+	tlsConnectionFree(c);
+	return 0;
+}
+
+
+//================= message functions ========================
+
+static uchar sendbuf[9000], *sendp;
+
+static int
+msgSend(TlsConnection *c, Msg *m, int act)
+{
+	uchar *p; // sendp = start of new message;  p = write pointer
+	int nn, n, i;
+
+	if(sendp == nil)
+		sendp = sendbuf;
+	p = sendp;
+	if(c->trace)
+		c->trace("send %s", msgPrint((char*)p, (sizeof sendbuf) - (p-sendbuf), m));
+
+	p[0] = m->tag;	// header - fill in size later
+	p += 4;
+
+	switch(m->tag) {
+	default:
+		tlsError(c, EInternalError, "can't encode a %d", m->tag);
+		goto Err;
+	case HClientHello:
+		// version
+		put16(p, m->u.clientHello.version);
+		p += 2;
+
+		// random
+		memmove(p, m->u.clientHello.random, RandomSize);
+		p += RandomSize;
+
+		// sid
+		n = m->u.clientHello.sid->len;
+		assert(n < 256);
+		p[0] = n;
+		memmove(p+1, m->u.clientHello.sid->data, n);
+		p += n+1;
+
+		n = m->u.clientHello.ciphers->len;
+		assert(n > 0 && n < 200);
+		put16(p, n*2);
+		p += 2;
+		for(i=0; i<n; i++) {
+			put16(p, m->u.clientHello.ciphers->data[i]);
+			p += 2;
+		}
+
+		n = m->u.clientHello.compressors->len;
+		assert(n > 0);
+		p[0] = n;
+		memmove(p+1, m->u.clientHello.compressors->data, n);
+		p += n+1;
+		break;
+	case HServerHello:
+		put16(p, m->u.serverHello.version);
+		p += 2;
+
+		// random
+		memmove(p, m->u.serverHello.random, RandomSize);
+		p += RandomSize;
+
+		// sid
+		n = m->u.serverHello.sid->len;
+		assert(n < 256);
+		p[0] = n;
+		memmove(p+1, m->u.serverHello.sid->data, n);
+		p += n+1;
+
+		put16(p, m->u.serverHello.cipher);
+		p += 2;
+		p[0] = m->u.serverHello.compressor;
+		p += 1;
+		break;
+	case HServerHelloDone:
+		break;
+	case HCertificate:
+		nn = 0;
+		for(i = 0; i < m->u.certificate.ncert; i++)
+			nn += 3 + m->u.certificate.certs[i]->len;
+		if(p + 3 + nn - sendbuf > sizeof(sendbuf)) {
+			tlsError(c, EInternalError, "output buffer too small for certificate");
+			goto Err;
+		}
+		put24(p, nn);
+		p += 3;
+		for(i = 0; i < m->u.certificate.ncert; i++){
+			put24(p, m->u.certificate.certs[i]->len);
+			p += 3;
+			memmove(p, m->u.certificate.certs[i]->data, m->u.certificate.certs[i]->len);
+			p += m->u.certificate.certs[i]->len;
+		}
+		break;
+	case HClientKeyExchange:
+		n = m->u.clientKeyExchange.key->len;
+		if(c->version != SSL3Version){
+			put16(p, n);
+			p += 2;
+		}
+		memmove(p, m->u.clientKeyExchange.key->data, n);
+		p += n;
+		break;
+	case HFinished:
+		memmove(p, m->u.finished.verify, m->u.finished.n);
+		p += m->u.finished.n;
+		break;
+	}
+
+	// go back and fill in size
+	n = p-sendp;
+	assert(p <= sendbuf+sizeof(sendbuf));
+	put24(sendp+1, n-4);
+
+	// remember hash of Handshake messages
+	if(m->tag != HHelloRequest) {
+		md5(sendp, n, 0, &c->hsmd5);
+		sha1(sendp, n, 0, &c->hssha1);
+	}
+
+	sendp = p;
+	if(act == AFlush){
+		sendp = sendbuf;
+		if(write(c->hand, sendbuf, p-sendbuf) < 0){
+			fprint(2, "write error: %r\n");
+			goto Err;
+		}
+	}
+	msgClear(m);
+	return 1;
+Err:
+	msgClear(m);
+	return 0;
+}
+
+static uchar*
+tlsReadN(TlsConnection *c, int n)
+{
+	uchar *p;
+	int nn, nr;
+
+	nn = c->ep - c->rp;
+	if(nn < n){
+		if(c->rp != c->buf){
+			memmove(c->buf, c->rp, nn);
+			c->rp = c->buf;
+			c->ep = &c->buf[nn];
+		}
+		for(; nn < n; nn += nr) {
+			nr = read(c->hand, &c->rp[nn], n - nn);
+			if(nr <= 0)
+				return nil;
+			c->ep += nr;
+		}
+	}
+	p = c->rp;
+	c->rp += n;
+	return p;
+}
+
+static int
+msgRecv(TlsConnection *c, Msg *m)
+{
+	uchar *p;
+	int type, n, nn, i, nsid, nrandom, nciph;
+
+	for(;;) {
+		p = tlsReadN(c, 4);
+		if(p == nil)
+			return 0;
+		type = p[0];
+		n = get24(p+1);
+
+		if(type != HHelloRequest)
+			break;
+		if(n != 0) {
+			tlsError(c, EDecodeError, "invalid hello request during handshake");
+			return 0;
+		}
+	}
+
+	if(n > sizeof(c->buf)) {
+		tlsError(c, EDecodeError, "handshake message too long %d %d", n, sizeof(c->buf));
+		return 0;
+	}
+
+	if(type == HSSL2ClientHello){
+		/* Cope with an SSL3 ClientHello expressed in SSL2 record format.
+			This is sent by some clients that we must interoperate
+			with, such as Java's JSSE and Microsoft's Internet Explorer. */
+		p = tlsReadN(c, n);
+		if(p == nil)
+			return 0;
+		md5(p, n, 0, &c->hsmd5);
+		sha1(p, n, 0, &c->hssha1);
+		m->tag = HClientHello;
+		if(n < 22)
+			goto Short;
+		m->u.clientHello.version = get16(p+1);
+		p += 3;
+		n -= 3;
+		nn = get16(p); /* cipher_spec_len */
+		nsid = get16(p + 2);
+		nrandom = get16(p + 4);
+		p += 6;
+		n -= 6;
+		if(nsid != 0 	/* no sid's, since shouldn't restart using ssl2 header */
+				|| nrandom < 16 || nn % 3)
+			goto Err;
+		if(c->trace && (n - nrandom != nn))
+			c->trace("n-nrandom!=nn: n=%d nrandom=%d nn=%d\n", n, nrandom, nn);
+		/* ignore ssl2 ciphers and look for {0x00, ssl3 cipher} */
+		nciph = 0;
+		for(i = 0; i < nn; i += 3)
+			if(p[i] == 0)
+				nciph++;
+		m->u.clientHello.ciphers = newints(nciph);
+		nciph = 0;
+		for(i = 0; i < nn; i += 3)
+			if(p[i] == 0)
+				m->u.clientHello.ciphers->data[nciph++] = get16(&p[i + 1]);
+		p += nn;
+		m->u.clientHello.sid = makebytes(nil, 0);
+		if(nrandom > RandomSize)
+			nrandom = RandomSize;
+		memset(m->u.clientHello.random, 0, RandomSize - nrandom);
+		memmove(&m->u.clientHello.random[RandomSize - nrandom], p, nrandom);
+		m->u.clientHello.compressors = newbytes(1);
+		m->u.clientHello.compressors->data[0] = CompressionNull;
+		goto Ok;
+	}
+
+	md5(p, 4, 0, &c->hsmd5);
+	sha1(p, 4, 0, &c->hssha1);
+
+	p = tlsReadN(c, n);
+	if(p == nil)
+		return 0;
+
+	md5(p, n, 0, &c->hsmd5);
+	sha1(p, n, 0, &c->hssha1);
+
+	m->tag = type;
+
+	switch(type) {
+	default:
+		tlsError(c, EUnexpectedMessage, "can't decode a %d", type);
+		goto Err;
+	case HClientHello:
+		if(n < 2)
+			goto Short;
+		m->u.clientHello.version = get16(p);
+		p += 2;
+		n -= 2;
+
+		if(n < RandomSize)
+			goto Short;
+		memmove(m->u.clientHello.random, p, RandomSize);
+		p += RandomSize;
+		n -= RandomSize;
+		if(n < 1 || n < p[0]+1)
+			goto Short;
+		m->u.clientHello.sid = makebytes(p+1, p[0]);
+		p += m->u.clientHello.sid->len+1;
+		n -= m->u.clientHello.sid->len+1;
+
+		if(n < 2)
+			goto Short;
+		nn = get16(p);
+		p += 2;
+		n -= 2;
+
+		if((nn & 1) || n < nn || nn < 2)
+			goto Short;
+		m->u.clientHello.ciphers = newints(nn >> 1);
+		for(i = 0; i < nn; i += 2)
+			m->u.clientHello.ciphers->data[i >> 1] = get16(&p[i]);
+		p += nn;
+		n -= nn;
+
+		if(n < 1 || n < p[0]+1 || p[0] == 0)
+			goto Short;
+		nn = p[0];
+		m->u.clientHello.compressors = newbytes(nn);
+		memmove(m->u.clientHello.compressors->data, p+1, nn);
+		n -= nn + 1;
+		break;
+	case HServerHello:
+		if(n < 2)
+			goto Short;
+		m->u.serverHello.version = get16(p);
+		p += 2;
+		n -= 2;
+
+		if(n < RandomSize)
+			goto Short;
+		memmove(m->u.serverHello.random, p, RandomSize);
+		p += RandomSize;
+		n -= RandomSize;
+
+		if(n < 1 || n < p[0]+1)
+			goto Short;
+		m->u.serverHello.sid = makebytes(p+1, p[0]);
+		p += m->u.serverHello.sid->len+1;
+		n -= m->u.serverHello.sid->len+1;
+
+		if(n < 3)
+			goto Short;
+		m->u.serverHello.cipher = get16(p);
+		m->u.serverHello.compressor = p[2];
+		n -= 3;
+		break;
+	case HCertificate:
+		if(n < 3)
+			goto Short;
+		nn = get24(p);
+		p += 3;
+		n -= 3;
+		if(n != nn)
+			goto Short;
+		/* certs */
+		i = 0;
+		while(n > 0) {
+			if(n < 3)
+				goto Short;
+			nn = get24(p);
+			p += 3;
+			n -= 3;
+			if(nn > n)
+				goto Short;
+			m->u.certificate.ncert = i+1;
+			m->u.certificate.certs = erealloc(m->u.certificate.certs, (i+1)*sizeof(Bytes));
+			m->u.certificate.certs[i] = makebytes(p, nn);
+			p += nn;
+			n -= nn;
+			i++;
+		}
+		break;
+	case HCertificateRequest:
+		if(n < 2)
+			goto Short;
+		nn = get16(p);
+		p += 2;
+		n -= 2;
+		if(nn < 1 || nn > n)
+			goto Short;
+		m->u.certificateRequest.types = makebytes(p, nn);
+		nn = get24(p);
+		p += 3;
+		n -= 3;
+		if(nn == 0 || n != nn)
+			goto Short;
+		/* cas */
+		i = 0;
+		while(n > 0) {
+			if(n < 2)
+				goto Short;
+			nn = get16(p);
+			p += 2;
+			n -= 2;
+			if(nn < 1 || nn > n)
+				goto Short;
+			m->u.certificateRequest.nca = i+1;
+			m->u.certificateRequest.cas = erealloc(m->u.certificateRequest.cas, (i+1)*sizeof(Bytes));
+			m->u.certificateRequest.cas[i] = makebytes(p, nn);
+			p += nn;
+			n -= nn;
+			i++;
+		}
+		break;
+	case HServerHelloDone:
+		break;
+	case HClientKeyExchange:
+		/*
+		 * this message depends upon the encryption selected
+		 * assume rsa.
+		 */
+		if(c->version == SSL3Version)
+			nn = n;
+		else{
+			if(n < 2)
+				goto Short;
+			nn = get16(p);
+			p += 2;
+			n -= 2;
+		}
+		if(n < nn)
+			goto Short;
+		m->u.clientKeyExchange.key = makebytes(p, nn);
+		n -= nn;
+		break;
+	case HFinished:
+		m->u.finished.n = c->finished.n;
+		if(n < m->u.finished.n)
+			goto Short;
+		memmove(m->u.finished.verify, p, m->u.finished.n);
+		n -= m->u.finished.n;
+		break;
+	}
+
+	if(type != HClientHello && n != 0)
+		goto Short;
+Ok:
+	if(c->trace){
+		char buf[8000];
+		c->trace("recv %s", msgPrint(buf, sizeof buf, m));
+	}
+	return 1;
+Short:
+	tlsError(c, EDecodeError, "handshake message has invalid length");
+Err:
+	msgClear(m);
+	return 0;
+}
+
+static void
+msgClear(Msg *m)
+{
+	int i;
+
+	switch(m->tag) {
+	default:
+		sysfatal("msgClear: unknown message type: %d\n", m->tag);
+	case HHelloRequest:
+		break;
+	case HClientHello:
+		freebytes(m->u.clientHello.sid);
+		freeints(m->u.clientHello.ciphers);
+		freebytes(m->u.clientHello.compressors);
+		break;
+	case HServerHello:
+		freebytes(m->u.clientHello.sid);
+		break;
+	case HCertificate:
+		for(i=0; i<m->u.certificate.ncert; i++)
+			freebytes(m->u.certificate.certs[i]);
+		free(m->u.certificate.certs);
+		break;
+	case HCertificateRequest:
+		freebytes(m->u.certificateRequest.types);
+		for(i=0; i<m->u.certificateRequest.nca; i++)
+			freebytes(m->u.certificateRequest.cas[i]);
+		free(m->u.certificateRequest.cas);
+		break;
+	case HServerHelloDone:
+		break;
+	case HClientKeyExchange:
+		freebytes(m->u.clientKeyExchange.key);
+		break;
+	case HFinished:
+		break;
+	}
+	memset(m, 0, sizeof(Msg));
+}
+
+static char *
+bytesPrint(char *bs, char *be, char *s0, Bytes *b, char *s1)
+{
+	int i;
+
+	if(s0)
+		bs = seprint(bs, be, "%s", s0);
+	bs = seprint(bs, be, "[");
+	if(b == nil)
+		bs = seprint(bs, be, "nil");
+	else
+		for(i=0; i<b->len; i++)
+			bs = seprint(bs, be, "%.2x ", b->data[i]);
+	bs = seprint(bs, be, "]");
+	if(s1)
+		bs = seprint(bs, be, "%s", s1);
+	return bs;
+}
+
+static char *
+intsPrint(char *bs, char *be, char *s0, Ints *b, char *s1)
+{
+	int i;
+
+	if(s0)
+		bs = seprint(bs, be, "%s", s0);
+	bs = seprint(bs, be, "[");
+	if(b == nil)
+		bs = seprint(bs, be, "nil");
+	else
+		for(i=0; i<b->len; i++)
+			bs = seprint(bs, be, "%x ", b->data[i]);
+	bs = seprint(bs, be, "]");
+	if(s1)
+		bs = seprint(bs, be, "%s", s1);
+	return bs;
+}
+
+static char*
+msgPrint(char *buf, int n, Msg *m)
+{
+	int i;
+	char *bs = buf, *be = buf+n;
+
+	switch(m->tag) {
+	default:
+		bs = seprint(bs, be, "unknown %d\n", m->tag);
+		break;
+	case HClientHello:
+		bs = seprint(bs, be, "ClientHello\n");
+		bs = seprint(bs, be, "\tversion: %.4x\n", m->u.clientHello.version);
+		bs = seprint(bs, be, "\trandom: ");
+		for(i=0; i<RandomSize; i++)
+			bs = seprint(bs, be, "%.2x", m->u.clientHello.random[i]);
+		bs = seprint(bs, be, "\n");
+		bs = bytesPrint(bs, be, "\tsid: ", m->u.clientHello.sid, "\n");
+		bs = intsPrint(bs, be, "\tciphers: ", m->u.clientHello.ciphers, "\n");
+		bs = bytesPrint(bs, be, "\tcompressors: ", m->u.clientHello.compressors, "\n");
+		break;
+	case HServerHello:
+		bs = seprint(bs, be, "ServerHello\n");
+		bs = seprint(bs, be, "\tversion: %.4x\n", m->u.serverHello.version);
+		bs = seprint(bs, be, "\trandom: ");
+		for(i=0; i<RandomSize; i++)
+			bs = seprint(bs, be, "%.2x", m->u.serverHello.random[i]);
+		bs = seprint(bs, be, "\n");
+		bs = bytesPrint(bs, be, "\tsid: ", m->u.serverHello.sid, "\n");
+		bs = seprint(bs, be, "\tcipher: %.4x\n", m->u.serverHello.cipher);
+		bs = seprint(bs, be, "\tcompressor: %.2x\n", m->u.serverHello.compressor);
+		break;
+	case HCertificate:
+		bs = seprint(bs, be, "Certificate\n");
+		for(i=0; i<m->u.certificate.ncert; i++)
+			bs = bytesPrint(bs, be, "\t", m->u.certificate.certs[i], "\n");
+		break;
+	case HCertificateRequest:
+		bs = seprint(bs, be, "CertificateRequest\n");
+		bs = bytesPrint(bs, be, "\ttypes: ", m->u.certificateRequest.types, "\n");
+		bs = seprint(bs, be, "\tcertificateauthorities\n");
+		for(i=0; i<m->u.certificateRequest.nca; i++)
+			bs = bytesPrint(bs, be, "\t\t", m->u.certificateRequest.cas[i], "\n");
+		break;
+	case HServerHelloDone:
+		bs = seprint(bs, be, "ServerHelloDone\n");
+		break;
+	case HClientKeyExchange:
+		bs = seprint(bs, be, "HClientKeyExchange\n");
+		bs = bytesPrint(bs, be, "\tkey: ", m->u.clientKeyExchange.key, "\n");
+		break;
+	case HFinished:
+		bs = seprint(bs, be, "HFinished\n");
+		for(i=0; i<m->u.finished.n; i++)
+			bs = seprint(bs, be, "%.2x", m->u.finished.verify[i]);
+		bs = seprint(bs, be, "\n");
+		break;
+	}
+	USED(bs);
+	return buf;
+}
+
+static void
+tlsError(TlsConnection *c, int err, char *fmt, ...)
+{
+	char msg[512];
+	va_list arg;
+
+	va_start(arg, fmt);
+	vseprint(msg, msg+sizeof(msg), fmt, arg);
+	va_end(arg);
+	if(c->trace)
+		c->trace("tlsError: %s\n", msg);
+	else if(c->erred)
+		fprint(2, "double error: %r, %s", msg);
+	else
+		werrstr("tls: local %s", msg);
+	c->erred = 1;
+	fprint(c->ctl, "alert %d", err);
+}
+
+// commit to specific version number
+static int
+setVersion(TlsConnection *c, int version)
+{
+	if(c->verset || version > MaxProtoVersion || version < MinProtoVersion)
+		return -1;
+	if(version > c->version)
+		version = c->version;
+	if(version == SSL3Version) {
+		c->version = version;
+		c->finished.n = SSL3FinishedLen;
+	}else if(version == TLSVersion){
+		c->version = version;
+		c->finished.n = TLSFinishedLen;
+	}else
+		return -1;
+	c->verset = 1;
+	return fprint(c->ctl, "version 0x%x", version);
+}
+
+// confirm that received Finished message matches the expected value
+static int
+finishedMatch(TlsConnection *c, Finished *f)
+{
+	return memcmp(f->verify, c->finished.verify, f->n) == 0;
+}
+
+// free memory associated with TlsConnection struct
+//		(but don't close the TLS channel itself)
+static void
+tlsConnectionFree(TlsConnection *c)
+{
+	tlsSecClose(c->sec);
+	freebytes(c->sid);
+	freebytes(c->cert);
+	memset(c, 0, sizeof(c));
+	free(c);
+}
+
+
+//================= cipher choices ========================
+
+static int weakCipher[CipherMax] =
+{
+	1,	/* TLS_NULL_WITH_NULL_NULL */
+	1,	/* TLS_RSA_WITH_NULL_MD5 */
+	1,	/* TLS_RSA_WITH_NULL_SHA */
+	1,	/* TLS_RSA_EXPORT_WITH_RC4_40_MD5 */
+	0,	/* TLS_RSA_WITH_RC4_128_MD5 */
+	0,	/* TLS_RSA_WITH_RC4_128_SHA */
+	1,	/* TLS_RSA_EXPORT_WITH_RC2_CBC_40_MD5 */
+	0,	/* TLS_RSA_WITH_IDEA_CBC_SHA */
+	1,	/* TLS_RSA_EXPORT_WITH_DES40_CBC_SHA */
+	0,	/* TLS_RSA_WITH_DES_CBC_SHA */
+	0,	/* TLS_RSA_WITH_3DES_EDE_CBC_SHA */
+	1,	/* TLS_DH_DSS_EXPORT_WITH_DES40_CBC_SHA */
+	0,	/* TLS_DH_DSS_WITH_DES_CBC_SHA */
+	0,	/* TLS_DH_DSS_WITH_3DES_EDE_CBC_SHA */
+	1,	/* TLS_DH_RSA_EXPORT_WITH_DES40_CBC_SHA */
+	0,	/* TLS_DH_RSA_WITH_DES_CBC_SHA */
+	0,	/* TLS_DH_RSA_WITH_3DES_EDE_CBC_SHA */
+	1,	/* TLS_DHE_DSS_EXPORT_WITH_DES40_CBC_SHA */
+	0,	/* TLS_DHE_DSS_WITH_DES_CBC_SHA */
+	0,	/* TLS_DHE_DSS_WITH_3DES_EDE_CBC_SHA */
+	1,	/* TLS_DHE_RSA_EXPORT_WITH_DES40_CBC_SHA */
+	0,	/* TLS_DHE_RSA_WITH_DES_CBC_SHA */
+	0,	/* TLS_DHE_RSA_WITH_3DES_EDE_CBC_SHA */
+	1,	/* TLS_DH_anon_EXPORT_WITH_RC4_40_MD5 */
+	1,	/* TLS_DH_anon_WITH_RC4_128_MD5 */
+	1,	/* TLS_DH_anon_EXPORT_WITH_DES40_CBC_SHA */
+	1,	/* TLS_DH_anon_WITH_DES_CBC_SHA */
+	1,	/* TLS_DH_anon_WITH_3DES_EDE_CBC_SHA */
+};
+
+static int
+setAlgs(TlsConnection *c, int a)
+{
+	int i;
+
+	for(i = 0; i < nelem(cipherAlgs); i++){
+		if(cipherAlgs[i].tlsid == a){
+			c->enc = cipherAlgs[i].enc;
+			c->digest = cipherAlgs[i].digest;
+			c->nsecret = cipherAlgs[i].nsecret;
+			if(c->nsecret > MaxKeyData)
+				return 0;
+			return 1;
+		}
+	}
+	return 0;
+}
+
+static int
+okCipher(Ints *cv)
+{
+	int weak, i, j, c;
+
+	weak = 1;
+	for(i = 0; i < cv->len; i++) {
+		c = cv->data[i];
+		if(c >= CipherMax)
+			weak = 0;
+		else
+			weak &= weakCipher[c];
+		for(j = 0; j < nelem(cipherAlgs); j++)
+			if(cipherAlgs[j].ok && cipherAlgs[j].tlsid == c)
+				return c;
+	}
+	if(weak)
+		return -2;
+	return -1;
+}
+
+static int
+okCompression(Bytes *cv)
+{
+	int i, j, c;
+
+	for(i = 0; i < cv->len; i++) {
+		c = cv->data[i];
+		for(j = 0; j < nelem(compressors); j++) {
+			if(compressors[j] == c)
+				return c;
+		}
+	}
+	return -1;
+}
+
+static Lock	ciphLock;
+static int	nciphers;
+
+static int
+initCiphers(void)
+{
+	enum {MaxAlgF = 1024, MaxAlgs = 10};
+	char s[MaxAlgF], *flds[MaxAlgs];
+	int i, j, n, ok;
+
+	lock(&ciphLock);
+	if(nciphers){
+		unlock(&ciphLock);
+		return nciphers;
+	}
+	j = open("#a/tls/encalgs", OREAD);
+	if(j < 0){
+		werrstr("can't open #a/tls/encalgs: %r");
+		return 0;
+	}
+	n = read(j, s, MaxAlgF-1);
+	close(j);
+	if(n <= 0){
+		werrstr("nothing in #a/tls/encalgs: %r");
+		return 0;
+	}
+	s[n] = 0;
+	n = getfields(s, flds, MaxAlgs, 1, " \t\r\n");
+	for(i = 0; i < nelem(cipherAlgs); i++){
+		ok = 0;
+		for(j = 0; j < n; j++){
+			if(strcmp(cipherAlgs[i].enc, flds[j]) == 0){
+				ok = 1;
+				break;
+			}
+		}
+		cipherAlgs[i].ok = ok;
+	}
+
+	j = open("#a/tls/hashalgs", OREAD);
+	if(j < 0){
+		werrstr("can't open #a/tls/hashalgs: %r");
+		return 0;
+	}
+	n = read(j, s, MaxAlgF-1);
+	close(j);
+	if(n <= 0){
+		werrstr("nothing in #a/tls/hashalgs: %r");
+		return 0;
+	}
+	s[n] = 0;
+	n = getfields(s, flds, MaxAlgs, 1, " \t\r\n");
+	for(i = 0; i < nelem(cipherAlgs); i++){
+		ok = 0;
+		for(j = 0; j < n; j++){
+			if(strcmp(cipherAlgs[i].digest, flds[j]) == 0){
+				ok = 1;
+				break;
+			}
+		}
+		cipherAlgs[i].ok &= ok;
+		if(cipherAlgs[i].ok)
+			nciphers++;
+	}
+	unlock(&ciphLock);
+	return nciphers;
+}
+
+static Ints*
+makeciphers(void)
+{
+	Ints *is;
+	int i, j;
+
+	is = newints(nciphers);
+	j = 0;
+	for(i = 0; i < nelem(cipherAlgs); i++){
+		if(cipherAlgs[i].ok)
+			is->data[j++] = cipherAlgs[i].tlsid;
+	}
+	return is;
+}
+
+
+
+//================= security functions ========================
+
+// given X.509 certificate, set up connection to factotum
+//	for using corresponding private key
+static AuthRpc*
+factotum_rsa_open(uchar *cert, int certlen)
+{
+	int afd;
+	char *s;
+	mpint *pub = nil;
+	RSApub *rsapub;
+	AuthRpc *rpc;
+
+	// start talking to factotum
+	if((afd = open("/mnt/factotum/rpc", ORDWR)) < 0)
+		return nil;
+	if((rpc = auth_allocrpc(afd)) == nil){
+		close(afd);
+		return nil;
+	}
+	s = "proto=rsa service=tls role=client";
+	if(auth_rpc(rpc, "start", s, strlen(s)) != ARok){
+		factotum_rsa_close(rpc);
+		return nil;
+	}
+
+	// roll factotum keyring around to match certificate
+	rsapub = X509toRSApub(cert, certlen, nil, 0);
+	while(1){
+		if(auth_rpc(rpc, "read", nil, 0) != ARok){
+			factotum_rsa_close(rpc);
+			rpc = nil;
+			goto done;
+		}
+		pub = strtomp(rpc->arg, nil, 16, nil);
+		assert(pub != nil);
+		if(mpcmp(pub,rsapub->n) == 0)
+			break;
+	}
+done:
+	mpfree(pub);
+	rsapubfree(rsapub);
+	return rpc;
+}
+
+static mpint*
+factotum_rsa_decrypt(AuthRpc *rpc, mpint *cipher)
+{
+	char *p;
+	int rv;
+
+	if((p = mptoa(cipher, 16, nil, 0)) == nil)
+		return nil;
+	rv = auth_rpc(rpc, "write", p, strlen(p));
+	free(p);
+	if(rv != ARok || auth_rpc(rpc, "read", nil, 0) != ARok)
+		return nil;
+	mpfree(cipher);
+	return strtomp(rpc->arg, nil, 16, nil);
+}
+
+static void
+factotum_rsa_close(AuthRpc*rpc)
+{
+	if(!rpc)
+		return;
+	close(rpc->afd);
+	auth_freerpc(rpc);
+}
+
+static void
+tlsPmd5(uchar *buf, int nbuf, uchar *key, int nkey, uchar *label, int nlabel, uchar *seed0, int nseed0, uchar *seed1, int nseed1)
+{
+	uchar ai[MD5dlen], tmp[MD5dlen];
+	int i, n;
+	MD5state *s;
+
+	// generate a1
+	s = hmac_md5(label, nlabel, key, nkey, nil, nil);
+	s = hmac_md5(seed0, nseed0, key, nkey, nil, s);
+	hmac_md5(seed1, nseed1, key, nkey, ai, s);
+
+	while(nbuf > 0) {
+		s = hmac_md5(ai, MD5dlen, key, nkey, nil, nil);
+		s = hmac_md5(label, nlabel, key, nkey, nil, s);
+		s = hmac_md5(seed0, nseed0, key, nkey, nil, s);
+		hmac_md5(seed1, nseed1, key, nkey, tmp, s);
+		n = MD5dlen;
+		if(n > nbuf)
+			n = nbuf;
+		for(i = 0; i < n; i++)
+			buf[i] ^= tmp[i];
+		buf += n;
+		nbuf -= n;
+		hmac_md5(ai, MD5dlen, key, nkey, tmp, nil);
+		memmove(ai, tmp, MD5dlen);
+	}
+}
+
+static void
+tlsPsha1(uchar *buf, int nbuf, uchar *key, int nkey, uchar *label, int nlabel, uchar *seed0, int nseed0, uchar *seed1, int nseed1)
+{
+	uchar ai[SHA1dlen], tmp[SHA1dlen];
+	int i, n;
+	SHAstate *s;
+
+	// generate a1
+	s = hmac_sha1(label, nlabel, key, nkey, nil, nil);
+	s = hmac_sha1(seed0, nseed0, key, nkey, nil, s);
+	hmac_sha1(seed1, nseed1, key, nkey, ai, s);
+
+	while(nbuf > 0) {
+		s = hmac_sha1(ai, SHA1dlen, key, nkey, nil, nil);
+		s = hmac_sha1(label, nlabel, key, nkey, nil, s);
+		s = hmac_sha1(seed0, nseed0, key, nkey, nil, s);
+		hmac_sha1(seed1, nseed1, key, nkey, tmp, s);
+		n = SHA1dlen;
+		if(n > nbuf)
+			n = nbuf;
+		for(i = 0; i < n; i++)
+			buf[i] ^= tmp[i];
+		buf += n;
+		nbuf -= n;
+		hmac_sha1(ai, SHA1dlen, key, nkey, tmp, nil);
+		memmove(ai, tmp, SHA1dlen);
+	}
+}
+
+// fill buf with md5(args)^sha1(args)
+static void
+tlsPRF(uchar *buf, int nbuf, uchar *key, int nkey, char *label, uchar *seed0, int nseed0, uchar *seed1, int nseed1)
+{
+	int i;
+	int nlabel = strlen(label);
+	int n = (nkey + 1) >> 1;
+
+	for(i = 0; i < nbuf; i++)
+		buf[i] = 0;
+	tlsPmd5(buf, nbuf, key, n, (uchar*)label, nlabel, seed0, nseed0, seed1, nseed1);
+	tlsPsha1(buf, nbuf, key+nkey-n, n, (uchar*)label, nlabel, seed0, nseed0, seed1, nseed1);
+}
+
+/*
+ * for setting server session id's
+ */
+static Lock	sidLock;
+static long	maxSid = 1;
+
+/* the keys are verified to have the same public components
+ * and to function correctly with pkcs 1 encryption and decryption. */
+static TlsSec*
+tlsSecInits(int cvers, uchar *csid, int ncsid, uchar *crandom, uchar *ssid, int *nssid, uchar *srandom)
+{
+	TlsSec *sec = emalloc(sizeof(*sec));
+
+	USED(csid); USED(ncsid);  // ignore csid for now
+
+	memmove(sec->crandom, crandom, RandomSize);
+	sec->clientVers = cvers;
+
+	put32(sec->srandom, time(0));
+	genrandom(sec->srandom+4, RandomSize-4);
+	memmove(srandom, sec->srandom, RandomSize);
+
+	/*
+	 * make up a unique sid: use our pid, and and incrementing id
+	 * can signal no sid by setting nssid to 0.
+	 */
+	memset(ssid, 0, SidSize);
+	put32(ssid, getpid());
+	lock(&sidLock);
+	put32(ssid+4, maxSid++);
+	unlock(&sidLock);
+	*nssid = SidSize;
+	return sec;
+}
+
+static int
+tlsSecSecrets(TlsSec *sec, int vers, uchar *epm, int nepm, uchar *kd, int nkd)
+{
+	if(epm != nil){
+		if(setVers(sec, vers) < 0)
+			goto Err;
+		serverMasterSecret(sec, epm, nepm);
+	}else if(sec->vers != vers){
+		werrstr("mismatched session versions");
+		goto Err;
+	}
+	setSecrets(sec, kd, nkd);
+	return 0;
+Err:
+	sec->ok = -1;
+	return -1;
+}
+
+static TlsSec*
+tlsSecInitc(int cvers, uchar *crandom)
+{
+	TlsSec *sec = emalloc(sizeof(*sec));
+	sec->clientVers = cvers;
+	put32(sec->crandom, time(0));
+	genrandom(sec->crandom+4, RandomSize-4);
+	memmove(crandom, sec->crandom, RandomSize);
+	return sec;
+}
+
+static int
+tlsSecSecretc(TlsSec *sec, uchar *sid, int nsid, uchar *srandom, uchar *cert, int ncert, int vers, uchar **epm, int *nepm, uchar *kd, int nkd)
+{
+	RSApub *pub;
+
+	pub = nil;
+
+	USED(sid);
+	USED(nsid);
+	
+	memmove(sec->srandom, srandom, RandomSize);
+
+	if(setVers(sec, vers) < 0)
+		goto Err;
+
+	pub = X509toRSApub(cert, ncert, nil, 0);
+	if(pub == nil){
+		werrstr("invalid x509/rsa certificate");
+		goto Err;
+	}
+	if(clientMasterSecret(sec, pub, epm, nepm) < 0)
+		goto Err;
+	rsapubfree(pub);
+	setSecrets(sec, kd, nkd);
+	return 0;
+
+Err:
+	if(pub != nil)
+		rsapubfree(pub);
+	sec->ok = -1;
+	return -1;
+}
+
+static int
+tlsSecFinished(TlsSec *sec, MD5state md5, SHAstate sha1, uchar *fin, int nfin, int isclient)
+{
+	if(sec->nfin != nfin){
+		sec->ok = -1;
+		werrstr("invalid finished exchange");
+		return -1;
+	}
+	md5.malloced = 0;
+	sha1.malloced = 0;
+	(*sec->setFinished)(sec, md5, sha1, fin, isclient);
+	return 1;
+}
+
+static void
+tlsSecOk(TlsSec *sec)
+{
+	if(sec->ok == 0)
+		sec->ok = 1;
+}
+
+static void
+tlsSecKill(TlsSec *sec)
+{
+	if(!sec)
+		return;
+	factotum_rsa_close(sec->rpc);
+	sec->ok = -1;
+}
+
+static void
+tlsSecClose(TlsSec *sec)
+{
+	if(!sec)
+		return;
+	factotum_rsa_close(sec->rpc);
+	free(sec->server);
+	free(sec);
+}
+
+static int
+setVers(TlsSec *sec, int v)
+{
+	if(v == SSL3Version){
+		sec->setFinished = sslSetFinished;
+		sec->nfin = SSL3FinishedLen;
+		sec->prf = sslPRF;
+	}else if(v == TLSVersion){
+		sec->setFinished = tlsSetFinished;
+		sec->nfin = TLSFinishedLen;
+		sec->prf = tlsPRF;
+	}else{
+		werrstr("invalid version");
+		return -1;
+	}
+	sec->vers = v;
+	return 0;
+}
+
+/*
+ * generate secret keys from the master secret.
+ *
+ * different crypto selections will require different amounts
+ * of key expansion and use of key expansion data,
+ * but it's all generated using the same function.
+ */
+static void
+setSecrets(TlsSec *sec, uchar *kd, int nkd)
+{
+	(*sec->prf)(kd, nkd, sec->sec, MasterSecretSize, "key expansion",
+			sec->srandom, RandomSize, sec->crandom, RandomSize);
+}
+
+/*
+ * set the master secret from the pre-master secret.
+ */
+static void
+setMasterSecret(TlsSec *sec, Bytes *pm)
+{
+	(*sec->prf)(sec->sec, MasterSecretSize, pm->data, MasterSecretSize, "master secret",
+			sec->crandom, RandomSize, sec->srandom, RandomSize);
+}
+
+static void
+serverMasterSecret(TlsSec *sec, uchar *epm, int nepm)
+{
+	Bytes *pm;
+
+	pm = pkcs1_decrypt(sec, epm, nepm);
+
+	// if the client messed up, just continue as if everything is ok,
+	// to prevent attacks to check for correctly formatted messages.
+	// Hence the fprint(2,) can't be replaced by tlsError(), which sends an Alert msg to the client.
+	if(sec->ok < 0 || pm == nil || get16(pm->data) != sec->clientVers){
+		fprint(2, "serverMasterSecret failed ok=%d pm=%p pmvers=%x cvers=%x nepm=%d\n",
+			sec->ok, pm, pm ? get16(pm->data) : -1, sec->clientVers, nepm);
+		sec->ok = -1;
+		if(pm != nil)
+			freebytes(pm);
+		pm = newbytes(MasterSecretSize);
+		genrandom(pm->data, MasterSecretSize);
+	}
+	setMasterSecret(sec, pm);
+	memset(pm->data, 0, pm->len);	
+	freebytes(pm);
+}
+
+static int
+clientMasterSecret(TlsSec *sec, RSApub *pub, uchar **epm, int *nepm)
+{
+	Bytes *pm, *key;
+
+	pm = newbytes(MasterSecretSize);
+	put16(pm->data, sec->clientVers);
+	genrandom(pm->data+2, MasterSecretSize - 2);
+
+	setMasterSecret(sec, pm);
+
+	key = pkcs1_encrypt(pm, pub, 2);
+	memset(pm->data, 0, pm->len);
+	freebytes(pm);
+	if(key == nil){
+		werrstr("tls pkcs1_encrypt failed");
+		return -1;
+	}
+
+	*nepm = key->len;
+	*epm = malloc(*nepm);
+	if(*epm == nil){
+		freebytes(key);
+		werrstr("out of memory");
+		return -1;
+	}
+	memmove(*epm, key->data, *nepm);
+
+	freebytes(key);
+
+	return 1;
+}
+
+static void
+sslSetFinished(TlsSec *sec, MD5state hsmd5, SHAstate hssha1, uchar *finished, int isClient)
+{
+	DigestState *s;
+	uchar h0[MD5dlen], h1[SHA1dlen], pad[48];
+	char *label;
+
+	if(isClient)
+		label = "CLNT";
+	else
+		label = "SRVR";
+
+	md5((uchar*)label, 4, nil, &hsmd5);
+	md5(sec->sec, MasterSecretSize, nil, &hsmd5);
+	memset(pad, 0x36, 48);
+	md5(pad, 48, nil, &hsmd5);
+	md5(nil, 0, h0, &hsmd5);
+	memset(pad, 0x5C, 48);
+	s = md5(sec->sec, MasterSecretSize, nil, nil);
+	s = md5(pad, 48, nil, s);
+	md5(h0, MD5dlen, finished, s);
+
+	sha1((uchar*)label, 4, nil, &hssha1);
+	sha1(sec->sec, MasterSecretSize, nil, &hssha1);
+	memset(pad, 0x36, 40);
+	sha1(pad, 40, nil, &hssha1);
+	sha1(nil, 0, h1, &hssha1);
+	memset(pad, 0x5C, 40);
+	s = sha1(sec->sec, MasterSecretSize, nil, nil);
+	s = sha1(pad, 40, nil, s);
+	sha1(h1, SHA1dlen, finished + MD5dlen, s);
+}
+
+// fill "finished" arg with md5(args)^sha1(args)
+static void
+tlsSetFinished(TlsSec *sec, MD5state hsmd5, SHAstate hssha1, uchar *finished, int isClient)
+{
+	uchar h0[MD5dlen], h1[SHA1dlen];
+	char *label;
+
+	// get current hash value, but allow further messages to be hashed in
+	md5(nil, 0, h0, &hsmd5);
+	sha1(nil, 0, h1, &hssha1);
+
+	if(isClient)
+		label = "client finished";
+	else
+		label = "server finished";
+	tlsPRF(finished, TLSFinishedLen, sec->sec, MasterSecretSize, label, h0, MD5dlen, h1, SHA1dlen);
+}
+
+static void
+sslPRF(uchar *buf, int nbuf, uchar *key, int nkey, char *label, uchar *seed0, int nseed0, uchar *seed1, int nseed1)
+{
+	DigestState *s;
+	uchar sha1dig[SHA1dlen], md5dig[MD5dlen], tmp[26];
+	int i, n, len;
+
+	USED(label);
+	len = 1;
+	while(nbuf > 0){
+		if(len > 26)
+			return;
+		for(i = 0; i < len; i++)
+			tmp[i] = 'A' - 1 + len;
+		s = sha1(tmp, len, nil, nil);
+		s = sha1(key, nkey, nil, s);
+		s = sha1(seed0, nseed0, nil, s);
+		sha1(seed1, nseed1, sha1dig, s);
+		s = md5(key, nkey, nil, nil);
+		md5(sha1dig, SHA1dlen, md5dig, s);
+		n = MD5dlen;
+		if(n > nbuf)
+			n = nbuf;
+		memmove(buf, md5dig, n);
+		buf += n;
+		nbuf -= n;
+		len++;
+	}
+}
+
+static mpint*
+bytestomp(Bytes* bytes)
+{
+	mpint* ans;
+
+	ans = betomp(bytes->data, bytes->len, nil);
+	return ans;
+}
+
+/*
+ * Convert mpint* to Bytes, putting high order byte first.
+ */
+static Bytes*
+mptobytes(mpint* big)
+{
+	int n, m;
+	uchar *a;
+	Bytes* ans;
+
+	n = (mpsignif(big)+7)/8;
+	m = mptobe(big, nil, n, &a);
+	ans = makebytes(a, m);
+	return ans;
+}
+
+// Do RSA computation on block according to key, and pad
+// result on left with zeros to make it modlen long.
+static Bytes*
+rsacomp(Bytes* block, RSApub* key, int modlen)
+{
+	mpint *x, *y;
+	Bytes *a, *ybytes;
+	int ylen;
+
+	x = bytestomp(block);
+	y = rsaencrypt(key, x, nil);
+	mpfree(x);
+	ybytes = mptobytes(y);
+	ylen = ybytes->len;
+
+	if(ylen < modlen) {
+		a = newbytes(modlen);
+		memset(a->data, 0, modlen-ylen);
+		memmove(a->data+modlen-ylen, ybytes->data, ylen);
+		freebytes(ybytes);
+		ybytes = a;
+	}
+	else if(ylen > modlen) {
+		// assume it has leading zeros (mod should make it so)
+		a = newbytes(modlen);
+		memmove(a->data, ybytes->data, modlen);
+		freebytes(ybytes);
+		ybytes = a;
+	}
+	mpfree(y);
+	return ybytes;
+}
+
+// encrypt data according to PKCS#1, /lib/rfc/rfc2437 9.1.2.1
+static Bytes*
+pkcs1_encrypt(Bytes* data, RSApub* key, int blocktype)
+{
+	Bytes *pad, *eb, *ans;
+	int i, dlen, padlen, modlen;
+
+	modlen = (mpsignif(key->n)+7)/8;
+	dlen = data->len;
+	if(modlen < 12 || dlen > modlen - 11)
+		return nil;
+	padlen = modlen - 3 - dlen;
+	pad = newbytes(padlen);
+	genrandom(pad->data, padlen);
+	for(i = 0; i < padlen; i++) {
+		if(blocktype == 0)
+			pad->data[i] = 0;
+		else if(blocktype == 1)
+			pad->data[i] = 255;
+		else if(pad->data[i] == 0)
+			pad->data[i] = 1;
+	}
+	eb = newbytes(modlen);
+	eb->data[0] = 0;
+	eb->data[1] = blocktype;
+	memmove(eb->data+2, pad->data, padlen);
+	eb->data[padlen+2] = 0;
+	memmove(eb->data+padlen+3, data->data, dlen);
+	ans = rsacomp(eb, key, modlen);
+	freebytes(eb);
+	freebytes(pad);
+	return ans;
+}
+
+// decrypt data according to PKCS#1, with given key.
+// expect a block type of 2.
+static Bytes*
+pkcs1_decrypt(TlsSec *sec, uchar *epm, int nepm)
+{
+	Bytes *eb, *ans = nil;
+	int i, modlen;
+	mpint *x, *y;
+
+	modlen = (mpsignif(sec->rsapub->n)+7)/8;
+	if(nepm != modlen)
+		return nil;
+	x = betomp(epm, nepm, nil);
+	y = factotum_rsa_decrypt(sec->rpc, x);
+	if(y == nil)
+		return nil;
+	eb = mptobytes(y);
+	if(eb->len < modlen){ // pad on left with zeros
+		ans = newbytes(modlen);
+		memset(ans->data, 0, modlen-eb->len);
+		memmove(ans->data+modlen-eb->len, eb->data, eb->len);
+		freebytes(eb);
+		eb = ans;
+	}
+	if(eb->data[0] == 0 && eb->data[1] == 2) {
+		for(i = 2; i < modlen; i++)
+			if(eb->data[i] == 0)
+				break;
+		if(i < modlen - 1)
+			ans = makebytes(eb->data+i+1, modlen-(i+1));
+	}
+	freebytes(eb);
+	return ans;
+}
+
+
+//================= general utility functions ========================
+
+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;
+}
+
+static void *
+erealloc(void *ReallocP, int ReallocN)
+{
+	if(ReallocN == 0)
+		ReallocN = 1;
+	if(!ReallocP)
+		ReallocP = emalloc(ReallocN);
+	else if(!(ReallocP = realloc(ReallocP, ReallocN))){
+		exits("out of memory");
+	}
+	return(ReallocP);
+}
+
+static void
+put32(uchar *p, u32int x)
+{
+	p[0] = x>>24;
+	p[1] = x>>16;
+	p[2] = x>>8;
+	p[3] = x;
+}
+
+static void
+put24(uchar *p, int x)
+{
+	p[0] = x>>16;
+	p[1] = x>>8;
+	p[2] = x;
+}
+
+static void
+put16(uchar *p, int x)
+{
+	p[0] = x>>8;
+	p[1] = x;
+}
+
+static u32int
+get32(uchar *p)
+{
+	return (p[0]<<24)|(p[1]<<16)|(p[2]<<8)|p[3];
+}
+
+static int
+get24(uchar *p)
+{
+	return (p[0]<<16)|(p[1]<<8)|p[2];
+}
+
+static int
+get16(uchar *p)
+{
+	return (p[0]<<8)|p[1];
+}
+
+/* ANSI offsetof() */
+#define OFFSET(x, s) ((int)(&(((s*)0)->x)))
+
+/*
+ * malloc and return a new Bytes structure capable of
+ * holding len bytes. (len >= 0)
+ * Used to use crypt_malloc, which aborts if malloc fails.
+ */
+static Bytes*
+newbytes(int len)
+{
+	Bytes* ans;
+
+	ans = (Bytes*)malloc(OFFSET(data[0], Bytes) + len);
+	ans->len = len;
+	return ans;
+}
+
+/*
+ * newbytes(len), with data initialized from buf
+ */
+static Bytes*
+makebytes(uchar* buf, int len)
+{
+	Bytes* ans;
+
+	ans = newbytes(len);
+	memmove(ans->data, buf, len);
+	return ans;
+}
+
+static void
+freebytes(Bytes* b)
+{
+	if(b != nil)
+		free(b);
+}
+
+/* len is number of ints */
+static Ints*
+newints(int len)
+{
+	Ints* ans;
+
+	ans = (Ints*)malloc(OFFSET(data[0], Ints) + len*sizeof(int));
+	ans->len = len;
+	return ans;
+}
+
+static Ints*
+makeints(int* buf, int len)
+{
+	Ints* ans;
+
+	ans = newints(len);
+	if(len > 0)
+		memmove(ans->data, buf, len*sizeof(int));
+	return ans;
+}
+
+static void
+freeints(Ints* b)
+{
+	if(b != nil)
+		free(b);
+}
diff --git a/src/libsec/port/x509.c b/src/libsec/port/x509.c
new file mode 100644
index 0000000..7aa0dd7
--- /dev/null
+++ b/src/libsec/port/x509.c
@@ -0,0 +1,2524 @@
+#include <u.h>
+#include <libc.h>
+#include <mp.h>
+#include <libsec.h>
+
+typedef DigestState*(*DigestFun)(uchar*,ulong,uchar*,DigestState*);
+
+/* ANSI offsetof, backwards. */
+#define	OFFSETOF(a, b)	offsetof(b, a)
+
+/*=============================================================*/
+/*  general ASN1 declarations and parsing
+ *
+ *  For now, this is used only for extracting the key from an
+ *  X509 certificate, so the entire collection is hidden.  But
+ *  someday we should probably make the functions visible and
+ *  give them their own man page.
+ */
+typedef struct Elem Elem;
+typedef struct Tag Tag;
+typedef struct Value Value;
+typedef struct Bytes Bytes;
+typedef struct Ints Ints;
+typedef struct Bits Bits;
+typedef struct Elist Elist;
+
+/* tag classes */
+#define Universal 0
+#define Context 0x80
+
+/* universal tags */
+#define BOOLEAN 1
+#define INTEGER 2
+#define BIT_STRING 3
+#define OCTET_STRING 4
+#define NULLTAG 5
+#define OBJECT_ID 6
+#define ObjectDescriptor 7
+#define EXTERNAL 8
+#define REAL 9
+#define ENUMERATED 10
+#define EMBEDDED_PDV 11
+#define SEQUENCE 16		/* also SEQUENCE OF */
+#define SETOF 17				/* also SETOF OF */
+#define NumericString 18
+#define PrintableString 19
+#define TeletexString 20
+#define VideotexString 21
+#define IA5String 22
+#define UTCTime 23
+#define GeneralizedTime 24
+#define GraphicString 25
+#define VisibleString 26
+#define GeneralString 27
+#define UniversalString 28
+#define BMPString 30
+
+struct Bytes {
+	int	len;
+	uchar	data[1];
+};
+
+struct Ints {
+	int	len;
+	int	data[1];
+};
+
+struct Bits {
+	int	len;		/* number of bytes */
+	int	unusedbits;	/* unused bits in last byte */
+	uchar	data[1];	/* most-significant bit first */
+};
+
+struct Tag {
+	int	class;
+	int	num;
+};
+
+enum { VBool, VInt, VOctets, VBigInt, VReal, VOther,
+	VBitString, VNull, VEOC, VObjId, VString, VSeq, VSet };
+struct Value {
+	int	tag;		/* VBool, etc. */
+	union {
+		int	boolval;
+		int	intval;
+		Bytes*	octetsval;
+		Bytes*	bigintval;
+		Bytes*	realval;	/* undecoded; hardly ever used */
+		Bytes*	otherval;
+		Bits*	bitstringval;
+		Ints*	objidval;
+		char*	stringval;
+		Elist*	seqval;
+		Elist*	setval;
+	} u;  /* (Don't use anonymous unions, for ease of porting) */
+};
+
+struct Elem {
+	Tag	tag;
+	Value	val;
+};
+
+struct Elist {
+	Elist*	tl;
+	Elem	hd;
+};
+
+/* decoding errors */
+enum { ASN_OK, ASN_ESHORT, ASN_ETOOBIG, ASN_EVALLEN,
+		ASN_ECONSTR, ASN_EPRIM, ASN_EINVAL, ASN_EUNIMPL };
+
+
+/* here are the functions to consider making extern someday */
+static Bytes*	newbytes(int len);
+static Bytes*	makebytes(uchar* buf, int len);
+static void	freebytes(Bytes* b);
+static Bytes*	catbytes(Bytes* b1, Bytes* b2);
+static Ints*	newints(int len);
+static Ints*	makeints(int* buf, int len);
+static void	freeints(Ints* b);
+static Bits*	newbits(int len);
+static Bits*	makebits(uchar* buf, int len, int unusedbits);
+static void	freebits(Bits* b);
+static Elist*	mkel(Elem e, Elist* tail);
+static void	freeelist(Elist* el);
+static int	elistlen(Elist* el);
+static int	is_seq(Elem* pe, Elist** pseq);
+static int	is_set(Elem* pe, Elist** pset);
+static int	is_int(Elem* pe, int* pint);
+static int	is_bigint(Elem* pe, Bytes** pbigint);
+static int	is_bitstring(Elem* pe, Bits** pbits);
+static int	is_octetstring(Elem* pe, Bytes** poctets);
+static int	is_oid(Elem* pe, Ints** poid);
+static int	is_string(Elem* pe, char** pstring);
+static int	is_time(Elem* pe, char** ptime);
+static int	decode(uchar* a, int alen, Elem* pelem);
+static int	decode_seq(uchar* a, int alen, Elist** pelist);
+static int	decode_value(uchar* a, int alen, int kind, int isconstr, Value* pval);
+static int	encode(Elem e, Bytes** pbytes);
+static int	oid_lookup(Ints* o, Ints** tab);
+static void	freevalfields(Value* v);
+static mpint	*asn1mpint(Elem *e);
+
+
+
+#define TAG_MASK 0x1F
+#define CONSTR_MASK 0x20
+#define CLASS_MASK 0xC0
+#define MAXOBJIDLEN 20
+
+static int ber_decode(uchar** pp, uchar* pend, Elem* pelem);
+static int tag_decode(uchar** pp, uchar* pend, Tag* ptag, int* pisconstr);
+static int length_decode(uchar** pp, uchar* pend, int* plength);
+static int value_decode(uchar** pp, uchar* pend, int length, int kind, int isconstr, Value* pval);
+static int int_decode(uchar** pp, uchar* pend, int count, int unsgned, int* pint);
+static int uint7_decode(uchar** pp, uchar* pend, int* pint);
+static int octet_decode(uchar** pp, uchar* pend, int length, int isconstr, Bytes** pbytes);
+static int seq_decode(uchar** pp, uchar* pend, int length, int isconstr, Elist** pelist);
+static int enc(uchar** pp, Elem e, int lenonly);
+static int val_enc(uchar** pp, Elem e, int *pconstr, int lenonly);
+static void uint7_enc(uchar** pp, int num, int lenonly);
+static void int_enc(uchar** pp, int num, int unsgned, int lenonly);
+
+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;
+}
+
+static char*
+estrdup(char *s)
+{
+	char *d, *d0;
+
+	if(!s)
+		return 0;
+	d = d0 = emalloc(strlen(s)+1);
+	while(*d++ = *s++)
+		;
+	return d0;
+}
+
+
+/*
+ * Decode a[0..len] as a BER encoding of an ASN1 type.
+ * The return value is one of ASN_OK, etc.
+ * Depending on the error, the returned elem may or may not
+ * be nil.
+ */
+static int
+decode(uchar* a, int alen, Elem* pelem)
+{
+	uchar* p = a;
+
+	return  ber_decode(&p, &a[alen], pelem);
+}
+
+/*
+ * Like decode, but continue decoding after first element
+ * of array ends.
+ */
+static int
+decode_seq(uchar* a, int alen, Elist** pelist)
+{
+	uchar* p = a;
+
+	return seq_decode(&p, &a[alen], -1, 1, pelist);
+}
+
+/*
+ * Decode the whole array as a BER encoding of an ASN1 value,
+ * (i.e., the part after the tag and length).
+ * Assume the value is encoded as universal tag "kind".
+ * The constr arg is 1 if the value is constructed, 0 if primitive.
+ * If there's an error, the return string will contain the error.
+ * Depending on the error, the returned value may or may not
+ * be nil.
+ */
+static int
+decode_value(uchar* a, int alen, int kind, int isconstr, Value* pval)
+{
+	uchar* p = a;
+
+	return value_decode(&p, &a[alen], alen, kind, isconstr, pval);
+}
+
+/*
+ * All of the following decoding routines take arguments:
+ *	uchar **pp;
+ *	uchar *pend;
+ * Where parsing is supposed to start at **pp, and when parsing
+ * is done, *pp is updated to point at next char to be parsed.
+ * The pend pointer is just past end of string; an error should
+ * be returned parsing hasn't finished by then.
+ *
+ * The returned int is ASN_OK if all went fine, else ASN_ESHORT, etc.
+ * The remaining argument(s) are pointers to where parsed entity goes.
+ */
+
+/* Decode an ASN1 'Elem' (tag, length, value) */
+static int
+ber_decode(uchar** pp, uchar* pend, Elem* pelem)
+{
+	int err;
+	int isconstr;
+	int length;
+	Tag tag;
+	Value val;
+
+	err = tag_decode(pp, pend, &tag, &isconstr);
+	if(err == ASN_OK) {
+		err = length_decode(pp, pend, &length);
+		if(err == ASN_OK) {
+			if(tag.class == Universal)
+				err = value_decode(pp, pend, length, tag.num, isconstr, &val);
+			else
+				err = value_decode(pp, pend, length, OCTET_STRING, 0, &val);
+			if(err == ASN_OK) {
+				pelem->tag = tag;
+				pelem->val = val;
+			}
+		}
+	}
+	return err;
+}
+
+/* Decode a tag field */
+static int
+tag_decode(uchar** pp, uchar* pend, Tag* ptag, int* pisconstr)
+{
+	int err;
+	int v;
+	uchar* p;
+
+	err = ASN_OK;
+	p = *pp;
+	if(pend-p >= 2) {
+		v = *p++;
+		ptag->class = v&CLASS_MASK;
+		if(v&CONSTR_MASK)
+			*pisconstr = 1;
+		else
+			*pisconstr = 0;
+		v &= TAG_MASK;
+		if(v == TAG_MASK)
+			err = uint7_decode(&p, pend, &v);
+		ptag->num = v;
+	}
+	else
+		err = ASN_ESHORT;
+	*pp = p;
+	return err;
+}
+
+/* Decode a length field */
+static int
+length_decode(uchar** pp, uchar* pend, int* plength)
+{
+	int err;
+	int num;
+	int v;
+	uchar* p;
+
+	err = ASN_OK;
+	num = 0;
+	p = *pp;
+	if(p < pend) {
+		v = *p++;
+		if(v&0x80)
+			err = int_decode(&p, pend, v&0x7F, 1, &num);
+		else
+			num = v;
+	}
+	else
+		err = ASN_ESHORT;
+	*pp = p;
+	*plength = num;
+	return err;
+}
+
+/* Decode a value field  */
+static int
+value_decode(uchar** pp, uchar* pend, int length, int kind, int isconstr, Value* pval)
+{
+	int err;
+	Bytes* va;
+	int num;
+	int bitsunused;
+	int subids[MAXOBJIDLEN];
+	int isubid;
+	Elist*	vl;
+	uchar* p;
+	uchar* pe;
+
+	err = ASN_OK;
+	p = *pp;
+	if(length == -1) {	/* "indefinite" length spec */
+		if(!isconstr)
+			err = ASN_EINVAL;
+	}
+	else if(p + length > pend)
+		err = ASN_EVALLEN;
+	if(err != ASN_OK)
+		return err;
+
+	switch(kind) {
+	case 0:
+		/* marker for end of indefinite constructions */
+		if(length == 0)
+			pval->tag = VNull;
+		else
+			err = ASN_EINVAL;
+		break;
+
+	case BOOLEAN:
+		if(isconstr)
+			err = ASN_ECONSTR;
+		else if(length != 1)
+			err = ASN_EVALLEN;
+		else {
+			pval->tag = VBool;
+			pval->u.boolval = (*p++ != 0);
+		}
+		break;
+
+	case INTEGER:
+	case ENUMERATED:
+		if(isconstr)
+			err = ASN_ECONSTR;
+		else if(length <= 4) {
+			err = int_decode(&p, pend, length, 0, &num);
+			if(err == ASN_OK) {
+				pval->tag = VInt;
+				pval->u.intval = num;
+			}
+		}
+		else {
+			pval->tag = VBigInt;
+			pval->u.bigintval = makebytes(p, length);
+			p += length;
+		}
+		break;
+
+	case BIT_STRING:
+		pval->tag = VBitString;
+		if(isconstr) {
+			if(length == -1 && p + 2 <= pend && *p == 0 && *(p+1) ==0) {
+				pval->u.bitstringval = makebits(0, 0, 0);
+				p += 2;
+			}
+			else
+				/* TODO: recurse and concat results */
+				err = ASN_EUNIMPL;
+		}
+		else {
+			if(length < 2) {
+				if(length == 1 && *p == 0) {
+					pval->u.bitstringval = makebits(0, 0, 0);
+					p++;
+				}
+				else
+					err = ASN_EINVAL;
+			}
+			else {
+				bitsunused = *p;
+				if(bitsunused > 7)
+					err = ASN_EINVAL;
+				else if(length > 0x0FFFFFFF)
+					err = ASN_ETOOBIG;
+				else {
+					pval->u.bitstringval = makebits(p+1, length-1, bitsunused);
+					p += length;
+				}
+			}
+		}
+		break;
+
+	case OCTET_STRING:
+	case ObjectDescriptor:
+		err = octet_decode(&p, pend, length, isconstr, &va);
+		if(err == ASN_OK) {
+			pval->tag = VOctets;
+			pval->u.octetsval = va;
+		}
+		break;
+
+	case NULLTAG:
+		if(isconstr)
+			err = ASN_ECONSTR;
+		else if(length != 0)
+			err = ASN_EVALLEN;
+		else
+			pval->tag = VNull;
+		break;
+
+	case OBJECT_ID:
+		if(isconstr)
+			err = ASN_ECONSTR;
+		else if(length == 0)
+			err = ASN_EVALLEN;
+		else {
+			isubid = 0;
+			pe = p+length;
+			while(p < pe && isubid < MAXOBJIDLEN) {
+				err = uint7_decode(&p, pend, &num);
+				if(err != ASN_OK)
+					break;
+				if(isubid == 0) {
+					subids[isubid++] = num / 40;
+					subids[isubid++] = num % 40;
+				}
+				else
+					subids[isubid++] = num;
+			}
+			if(err == ASN_OK) {
+				if(p != pe)
+					err = ASN_EVALLEN;
+				else {
+					pval->tag = VObjId;
+					pval->u.objidval = makeints(subids, isubid);
+				}
+			}
+		}
+		break;
+
+	case EXTERNAL:
+	case EMBEDDED_PDV:
+		/* TODO: parse this internally */
+		if(p+length > pend)
+			err = ASN_EVALLEN;
+		else {
+			pval->tag = VOther;
+			pval->u.otherval = makebytes(p, length);
+			p += length;
+		}
+		break;
+
+	case REAL:
+		/* Let the application decode */
+		if(isconstr)
+			err = ASN_ECONSTR;
+		else if(p+length > pend)
+			err = ASN_EVALLEN;
+		else {
+			pval->tag = VReal;
+			pval->u.realval = makebytes(p, length);
+			p += length;
+		}
+		break;
+
+	case SEQUENCE:
+		err = seq_decode(&p, pend, length, isconstr, &vl);
+		if(err == ASN_OK) {
+			pval->tag = VSeq ;
+			pval->u.seqval = vl;
+		}
+		break;
+
+	case SETOF:
+		err = seq_decode(&p, pend, length, isconstr, &vl);
+		if(err == ASN_OK) {
+			pval->tag = VSet;
+			pval->u.setval = vl;
+		}
+		break;
+
+	case NumericString:
+	case PrintableString:
+	case TeletexString:
+	case VideotexString:
+	case IA5String:
+	case UTCTime:
+	case GeneralizedTime:
+	case GraphicString:
+	case VisibleString:
+	case GeneralString:
+	case UniversalString:
+	case BMPString:
+		/* TODO: figure out when character set conversion is necessary */
+		err = octet_decode(&p, pend, length, isconstr, &va);
+		if(err == ASN_OK) {
+			pval->tag = VString;
+			pval->u.stringval = (char*)emalloc(va->len+1);
+			memmove(pval->u.stringval, va->data, va->len);
+			pval->u.stringval[va->len] = 0;
+			free(va);
+		}
+		break;
+
+	default:
+		if(p+length > pend)
+			err = ASN_EVALLEN;
+		else {
+			pval->tag = VOther;
+			pval->u.otherval = makebytes(p, length);
+			p += length;
+		}
+		break;
+	}
+	*pp = p;
+	return err;
+}
+
+/*
+ * Decode an int in format where count bytes are
+ * concatenated to form value.
+ * Although ASN1 allows any size integer, we return
+ * an error if the result doesn't fit in a 32-bit int.
+ * If unsgned is not set, make sure to propagate sign bit.
+ */
+static int
+int_decode(uchar** pp, uchar* pend, int count, int unsgned, int* pint)
+{
+	int err;
+	int num;
+	uchar* p;
+
+	p = *pp;
+	err = ASN_OK;
+	num = 0;
+	if(p+count <= pend) {
+		if((count > 4) || (unsgned && count == 4 && (*p&0x80)))
+			err = ASN_ETOOBIG;
+		else {
+			if(!unsgned && count > 0 && count < 4 && (*p&0x80))
+				num = -1;		// set all bits, initially
+			while(count--)
+				num = (num << 8)|(*p++);
+		}
+	}
+	else
+		err = ASN_ESHORT;
+	*pint = num;
+	*pp = p;
+	return err;
+}
+
+/*
+ * Decode an unsigned int in format where each
+ * byte except last has high bit set, and remaining
+ * seven bits of each byte are concatenated to form value.
+ * Although ASN1 allows any size integer, we return
+ * an error if the result doesn't fit in a 32 bit int.
+ */
+static int
+uint7_decode(uchar** pp, uchar* pend, int* pint)
+{
+	int err;
+	int num;
+	int more;
+	int v;
+	uchar* p;
+
+	p = *pp;
+	err = ASN_OK;
+	num = 0;
+	more = 1;
+	while(more && p < pend) {
+		v = *p++;
+		if(num&0x7F000000) {
+			err = ASN_ETOOBIG;
+			break;
+		}
+		num <<= 7;
+		more = v&0x80;
+		num |= (v&0x7F);
+	}
+	if(p == pend)
+		err = ASN_ESHORT;
+	*pint = num;
+	*pp = p;
+	return err;
+}
+
+/*
+ * Decode an octet string, recursively if isconstr.
+ * We've already checked that length==-1 implies isconstr==1,
+ * and otherwise that specified length fits within (*pp..pend)
+ */
+static int
+octet_decode(uchar** pp, uchar* pend, int length, int isconstr, Bytes** pbytes)
+{
+	int err;
+	uchar* p;
+	Bytes* ans;
+	Bytes* newans;
+	uchar* pstart;
+	uchar* pold;
+	Elem	elem;
+
+	err = ASN_OK;
+	p = *pp;
+	ans = nil;
+	if(length >= 0 && !isconstr) {
+		ans = makebytes(p, length);
+		p += length;
+	}
+	else {
+		/* constructed, either definite or indefinite length */
+		pstart = p;
+		for(;;) {
+			if(length >= 0 && p >= pstart + length) {
+				if(p != pstart + length)
+					err = ASN_EVALLEN;
+				break;
+			}
+			pold = p;
+			err = ber_decode(&p, pend, &elem);
+			if(err != ASN_OK)
+				break;
+			switch(elem.val.tag) {
+			case VOctets:
+				newans = catbytes(ans, elem.val.u.octetsval);
+				freebytes(ans);
+				ans = newans;
+				break;
+
+			case VEOC:
+				if(length != -1) {
+					p = pold;
+					err = ASN_EINVAL;
+				}
+				goto cloop_done;
+
+			default:
+				p = pold;
+				err = ASN_EINVAL;
+				goto cloop_done;
+			}
+		}
+cloop_done:
+		;
+	}
+	*pp = p;
+	*pbytes = ans;
+	return err;
+}
+
+/*
+ * Decode a sequence or set.
+ * We've already checked that length==-1 implies isconstr==1,
+ * and otherwise that specified length fits within (*p..pend)
+ */
+static int
+seq_decode(uchar** pp, uchar* pend, int length, int isconstr, Elist** pelist)
+{
+	int err;
+	uchar* p;
+	uchar* pstart;
+	uchar* pold;
+	Elist* ans;
+	Elem elem;
+	Elist* lve;
+	Elist* lveold;
+
+	err = ASN_OK;
+	ans = nil;
+	p = *pp;
+	if(!isconstr)
+		err = ASN_EPRIM;
+	else {
+		/* constructed, either definite or indefinite length */
+		lve = nil;
+		pstart = p;
+		for(;;) {
+			if(length >= 0 && p >= pstart + length) {
+				if(p != pstart + length)
+					err = ASN_EVALLEN;
+				break;
+			}
+			pold = p;
+			err = ber_decode(&p, pend, &elem);
+			if(err != ASN_OK)
+				break;
+			if(elem.val.tag == VEOC) {
+				if(length != -1) {
+					p = pold;
+					err = ASN_EINVAL;
+				}
+				break;
+			}
+			else
+				lve = mkel(elem, lve);
+		}
+		if(err == ASN_OK) {
+			/* reverse back to original order */
+			while(lve != nil) {
+				lveold = lve;
+				lve = lve->tl;
+				lveold->tl = ans;
+				ans = lveold;
+			}
+		}
+	}
+	*pp = p;
+	*pelist = ans;
+	return err;
+}
+
+/*
+ * Encode e by BER rules, putting answer in *pbytes.
+ * This is done by first calling enc with lenonly==1
+ * to get the length of the needed buffer,
+ * then allocating the buffer and using enc again to fill it up.
+ */
+static int
+encode(Elem e, Bytes** pbytes)
+{
+	uchar* p;
+	Bytes* ans;
+	int err;
+	uchar uc;
+
+	p = &uc;
+	err = enc(&p, e, 1);
+	if(err == ASN_OK) {
+		ans = newbytes(p-&uc);
+		p = ans->data;
+		err = enc(&p, e, 0);
+		*pbytes = ans;
+	}
+	return err;
+}
+
+/*
+ * The various enc functions take a pointer to a pointer
+ * into a buffer, and encode their entity starting there,
+ * updating the pointer afterwards.
+ * If lenonly is 1, only the pointer update is done,
+ * allowing enc to be called first to calculate the needed
+ * buffer length.
+ * If lenonly is 0, it is assumed that the answer will fit.
+ */
+
+static int
+enc(uchar** pp, Elem e, int lenonly)
+{
+	int err;
+	int vlen;
+	int constr;
+	Tag tag;
+	int v;
+	int ilen;
+	uchar* p;
+	uchar* psave;
+
+	p = *pp;
+	err = val_enc(&p, e, &constr, 1);
+	if(err != ASN_OK)
+		return err;
+	vlen = p - *pp;
+	p = *pp;
+	tag = e.tag;
+	v = tag.class|constr;
+	if(tag.num < 31) {
+		if(!lenonly)
+			*p = (v|tag.num);
+		p++;
+	}
+	else {
+		if(!lenonly)
+			*p = (v|31);
+		p++;
+		if(tag.num < 0)
+			return ASN_EINVAL;
+		uint7_enc(&p, tag.num, lenonly);
+	}
+	if(vlen < 0x80) {
+		if(!lenonly)
+			*p = vlen;
+		p++;
+	}
+	else {
+		psave = p;
+		int_enc(&p, vlen, 1, 1);
+		ilen = p-psave;
+		p = psave;
+		if(!lenonly) {
+			*p++ = (0x80 | ilen);
+			int_enc(&p, vlen, 1, 0);
+		}
+		else
+			p += 1 + ilen;
+	}
+	if(!lenonly)
+		val_enc(&p, e, &constr, 0);
+	else
+		p += vlen;
+	*pp = p;
+	return err;
+}
+
+static int
+val_enc(uchar** pp, Elem e, int *pconstr, int lenonly)
+{
+	int err;
+	uchar* p;
+	int kind;
+	int cl;
+	int v;
+	Bytes* bb = nil;
+	Bits* bits;
+	Ints* oid;
+	int k;
+	Elist* el;
+	char* s;
+
+	p = *pp;
+	err = ASN_OK;
+	kind = e.tag.num;
+	cl = e.tag.class;
+	*pconstr = 0;
+	if(cl != Universal) {
+		switch(e.val.tag) {
+		case VBool:
+			kind = BOOLEAN;
+			break;
+		case VInt:
+			kind = INTEGER;
+			break;
+		case VBigInt:
+			kind = INTEGER;
+			break;
+		case VOctets:
+			kind = OCTET_STRING;
+			break;
+		case VReal:
+			kind = REAL;
+			break;
+		case VOther:
+			kind = OCTET_STRING;
+			break;
+		case VBitString:
+			kind = BIT_STRING;
+			break;
+		case VNull:
+			kind = NULLTAG;
+			break;
+		case VObjId:
+			kind = OBJECT_ID;
+			break;
+		case VString:
+			kind = UniversalString;
+			break;
+		case VSeq:
+			kind = SEQUENCE;
+			break;
+		case VSet:
+			kind = SETOF;
+			break;
+		}
+	}
+	switch(kind) {
+	case BOOLEAN:
+		if(is_int(&e, &v)) {
+			if(v != 0)
+				v = 255;
+			 int_enc(&p, v, 1, lenonly);
+		}
+		else
+			err = ASN_EINVAL;
+		break;
+
+	case INTEGER:
+	case ENUMERATED:
+		if(is_int(&e, &v))
+			int_enc(&p, v, 0, lenonly);
+		else {
+			if(is_bigint(&e, &bb)) {
+				if(!lenonly)
+					memmove(p, bb->data, bb->len);
+				p += bb->len;
+			}
+			else
+				err = ASN_EINVAL;
+		}
+		break;
+
+	case BIT_STRING:
+		if(is_bitstring(&e, &bits)) {
+			if(bits->len == 0) {
+				if(!lenonly)
+					*p = 0;
+				p++;
+			}
+			else {
+				v = bits->unusedbits;
+				if(v < 0 || v > 7)
+					err = ASN_EINVAL;
+				else {
+					if(!lenonly) {
+						*p = v;
+						memmove(p+1, bits->data, bits->len);
+					}
+					p += 1 + bits->len;
+				}
+			}
+		}
+		else
+			err = ASN_EINVAL;
+		break;
+
+	case OCTET_STRING:
+	case ObjectDescriptor:
+	case EXTERNAL:
+	case REAL:
+	case EMBEDDED_PDV:
+		bb = nil;
+		switch(e.val.tag) {
+		case VOctets:
+			bb = e.val.u.octetsval;
+			break;
+		case VReal:
+			bb = e.val.u.realval;
+			break;
+		case VOther:
+			bb = e.val.u.otherval;
+			break;
+		}
+		if(bb != nil) {
+			if(!lenonly)
+				memmove(p, bb->data, bb->len);
+			p += bb->len;
+		}
+			else
+				err = ASN_EINVAL;
+		break;
+
+	case NULLTAG:
+		break;
+
+	case OBJECT_ID:
+		if(is_oid(&e, &oid)) {
+			for(k = 0; k < oid->len; k++) {
+				v = oid->data[k];
+				if(k == 0) {
+					v *= 40;
+					if(oid->len > 1)
+						v += oid->data[++k];
+				}
+				uint7_enc(&p, v, lenonly);
+			}
+		}
+		else
+			err = ASN_EINVAL;
+		break;
+
+	case SEQUENCE:
+	case SETOF:
+		el = nil;
+		if(e.val.tag == VSeq)
+			el = e.val.u.seqval;
+		else if(e.val.tag == VSet)
+			el = e.val.u.setval;
+		else
+			err = ASN_EINVAL;
+		if(el != nil) {
+			*pconstr = CONSTR_MASK;
+			for(; el != nil; el = el->tl) {
+				err = enc(&p, el->hd, lenonly);
+				if(err != ASN_OK)
+					break;
+			}
+		}
+		break;
+
+	case NumericString:
+	case PrintableString:
+	case TeletexString:
+	case VideotexString:
+	case IA5String:
+	case UTCTime:
+	case GeneralizedTime:
+	case GraphicString:
+	case VisibleString:
+	case GeneralString:
+	case UniversalString:
+	case BMPString:
+		if(e.val.tag == VString) {
+			s = e.val.u.stringval;
+			if(s != nil) {
+				v = strlen(s);
+				if(!lenonly)
+					memmove(p, s, v);
+				p += v;
+			}
+		}
+		else
+			err = ASN_EINVAL;
+		break;
+
+	default:
+		err = ASN_EINVAL;
+	}
+	*pp = p;
+	return err;
+}
+
+/*
+ * Encode num as unsigned 7 bit values with top bit 1 on all bytes
+ * except last, only putting in bytes if !lenonly.
+ */
+static void
+uint7_enc(uchar** pp, int num, int lenonly)
+{
+	int n;
+	int v;
+	int k;
+	uchar* p;
+
+	p = *pp;
+	n = 1;
+	v = num >> 7;
+	while(v > 0) {
+		v >>= 7;
+		n++;
+	}
+	if(lenonly)
+		p += n;
+	else {
+		for(k = (n - 1)*7; k > 0; k -= 7)
+			*p++= ((num >> k)|0x80);
+		*p++ = (num&0x7F);
+	}
+	*pp = p;
+}
+
+/*
+ * Encode num as unsigned or signed integer,
+ * only putting in bytes if !lenonly.
+ * Encoding is length followed by bytes to concatenate.
+ */
+static void
+int_enc(uchar** pp, int num, int unsgned, int lenonly)
+{
+	int v;
+	int n;
+	int prevv;
+	int k;
+	uchar* p;
+
+	p = *pp;
+	v = num;
+	if(v < 0)
+		v = -(v + 1);
+	n = 1;
+	prevv = v;
+	v >>= 8;
+	while(v > 0) {
+		prevv = v;
+		v >>= 8;
+		n++;
+	}
+	if(!unsgned && (prevv&0x80))
+		n++;
+	if(lenonly)
+		p += n;
+	else {
+		for(k = (n - 1)*8; k >= 0; k -= 8)
+			*p++ = (num >> k);
+	}
+	*pp = p;
+}
+
+static int
+ints_eq(Ints* a, Ints* b)
+{
+	int	alen;
+	int	i;
+
+	alen = a->len;
+	if(alen != b->len)
+		return 0;
+	for(i = 0; i < alen; i++)
+		if(a->data[i] != b->data[i])
+			return 0;
+	return 1;
+}
+
+/*
+ * Look up o in tab (which must have nil entry to terminate).
+ * Return index of matching entry, or -1 if none.
+ */
+static int
+oid_lookup(Ints* o, Ints** tab)
+{
+	int i;
+
+	for(i = 0; tab[i] != nil; i++)
+		if(ints_eq(o, tab[i]))
+			return  i;
+	return -1;
+}
+
+/*
+ * Return true if *pe is a SEQUENCE, and set *pseq to
+ * the value of the sequence if so.
+ */
+static int
+is_seq(Elem* pe, Elist** pseq)
+{
+	if(pe->tag.class == Universal && pe->tag.num == SEQUENCE && pe->val.tag == VSeq) {
+		*pseq = pe->val.u.seqval;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_set(Elem* pe, Elist** pset)
+{
+	if(pe->tag.class == Universal && pe->tag.num == SETOF && pe->val.tag == VSet) {
+		*pset = pe->val.u.setval;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_int(Elem* pe, int* pint)
+{
+	if(pe->tag.class == Universal) {
+		if(pe->tag.num == INTEGER && pe->val.tag == VInt) {
+			*pint = pe->val.u.intval;
+			return 1;
+		}
+		else if(pe->tag.num == BOOLEAN && pe->val.tag == VBool) {
+			*pint = pe->val.u.boolval;
+			return 1;
+		}
+	}
+	return 0;
+}
+
+/*
+ * for convience, all VInt's are readable via this routine,
+ * as well as all VBigInt's
+ */
+static int
+is_bigint(Elem* pe, Bytes** pbigint)
+{
+	int v, n, i;
+
+	if(pe->tag.class == Universal && pe->tag.num == INTEGER) {
+		if(pe->val.tag == VBigInt)
+			*pbigint = pe->val.u.bigintval;
+		else if(pe->val.tag == VInt){
+			v = pe->val.u.intval;
+			for(n = 1; n < 4; n++)
+				if((1 << (8 * n)) > v)
+					break;
+			*pbigint = newbytes(n);
+			for(i = 0; i < n; i++)
+				(*pbigint)->data[i] = (v >> ((n - 1 - i) * 8));
+		}else
+			return 0;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_bitstring(Elem* pe, Bits** pbits)
+{
+	if(pe->tag.class == Universal && pe->tag.num == BIT_STRING && pe->val.tag == VBitString) {
+		*pbits = pe->val.u.bitstringval;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_octetstring(Elem* pe, Bytes** poctets)
+{
+	if(pe->tag.class == Universal && pe->tag.num == OCTET_STRING && pe->val.tag == VOctets) {
+		*poctets = pe->val.u.octetsval;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_oid(Elem* pe, Ints** poid)
+{
+	if(pe->tag.class == Universal && pe->tag.num == OBJECT_ID && pe->val.tag == VObjId) {
+		*poid = pe->val.u.objidval;
+		return 1;
+	}
+	return 0;
+}
+
+static int
+is_string(Elem* pe, char** pstring)
+{
+	if(pe->tag.class == Universal) {
+		switch(pe->tag.num) {
+		case NumericString:
+		case PrintableString:
+		case TeletexString:
+		case VideotexString:
+		case IA5String:
+		case GraphicString:
+		case VisibleString:
+		case GeneralString:
+		case UniversalString:
+		case BMPString:
+			if(pe->val.tag == VString) {
+				*pstring = pe->val.u.stringval;
+				return 1;
+			}
+		}
+	}
+	return 0;
+}
+
+static int
+is_time(Elem* pe, char** ptime)
+{
+	if(pe->tag.class == Universal
+	   && (pe->tag.num == UTCTime || pe->tag.num == GeneralizedTime)
+	   && pe->val.tag == VString) {
+		*ptime = pe->val.u.stringval;
+		return 1;
+	}
+	return 0;
+}
+
+
+/*
+ * malloc and return a new Bytes structure capable of
+ * holding len bytes. (len >= 0)
+ */
+static Bytes*
+newbytes(int len)
+{
+	Bytes* ans;
+
+	ans = (Bytes*)emalloc(OFFSETOF(data[0], Bytes) + len);
+	ans->len = len;
+	return ans;
+}
+
+/*
+ * newbytes(len), with data initialized from buf
+ */
+static Bytes*
+makebytes(uchar* buf, int len)
+{
+	Bytes* ans;
+
+	ans = newbytes(len);
+	memmove(ans->data, buf, len);
+	return ans;
+}
+
+static void
+freebytes(Bytes* b)
+{
+	if(b != nil)
+		free(b);
+}
+
+/*
+ * Make a new Bytes, containing bytes of b1 followed by those of b2.
+ * Either b1 or b2 or both can be nil.
+ */
+static Bytes*
+catbytes(Bytes* b1, Bytes* b2)
+{
+	Bytes* ans;
+	int n;
+
+	if(b1 == nil) {
+		if(b2 == nil)
+			ans = newbytes(0);
+		else
+			ans = makebytes(b2->data, b2->len);
+	}
+	else if(b2 == nil) {
+		ans = makebytes(b1->data, b1->len);
+	}
+	else {
+		n = b1->len + b2->len;
+		ans = newbytes(n);
+		ans->len = n;
+		memmove(ans->data, b1->data, b1->len);
+		memmove(ans->data+b1->len, b2->data, b2->len);
+	}
+	return ans;
+}
+
+/* len is number of ints */
+static Ints*
+newints(int len)
+{
+	Ints* ans;
+
+	ans = (Ints*)emalloc(OFFSETOF(data[0], Ints) + len*sizeof(int));
+	ans->len = len;
+	return ans;
+}
+
+static Ints*
+makeints(int* buf, int len)
+{
+	Ints* ans;
+
+	ans = newints(len);
+	if(len > 0)
+		memmove(ans->data, buf, len*sizeof(int));
+	return ans;
+}
+
+static void
+freeints(Ints* b)
+{
+	if(b != nil)
+		free(b);
+}
+
+/* len is number of bytes */
+static Bits*
+newbits(int len)
+{
+	Bits* ans;
+
+	ans = (Bits*)emalloc(OFFSETOF(data[0], Bits) + len);
+	ans->len = len;
+	ans->unusedbits = 0;
+	return ans;
+}
+
+static Bits*
+makebits(uchar* buf, int len, int unusedbits)
+{
+	Bits* ans;
+
+	ans = newbits(len);
+	memmove(ans->data, buf, len);
+	ans->unusedbits = unusedbits;
+	return ans;
+}
+
+static void
+freebits(Bits* b)
+{
+	if(b != nil)
+		free(b);
+}
+
+static Elist*
+mkel(Elem e, Elist* tail)
+{
+	Elist* el;
+
+	el = (Elist*)emalloc(sizeof(Elist));
+	el->hd = e;
+	el->tl = tail;
+	return el;
+}
+
+static int
+elistlen(Elist* el)
+{
+	int ans = 0;
+	while(el != nil) {
+		ans++;
+		el = el->tl;
+	}
+	return ans;
+}
+
+/* Frees elist, but not fields inside values of constituent elems */
+static void
+freeelist(Elist* el)
+{
+	Elist* next;
+
+	while(el != nil) {
+		next = el->tl;
+		free(el);
+		el = next;
+	}
+}
+
+/* free any allocated structures inside v (recursively freeing Elists) */
+static void
+freevalfields(Value* v)
+{
+	Elist* el;
+	Elist* l;
+	if(v == nil)
+		return;
+	switch(v->tag) {
+ 	case VOctets:
+		freebytes(v->u.octetsval);
+		break;
+	case VBigInt:
+		freebytes(v->u.bigintval);
+		break;
+	case VReal:
+		freebytes(v->u.realval);
+		break;
+	case VOther:
+		freebytes(v->u.otherval);
+		break;
+	case VBitString:
+		freebits(v->u.bitstringval);
+		break;
+	case VObjId:
+		freeints(v->u.objidval);
+		break;
+	case VString:
+		if (v->u.stringval)
+			free(v->u.stringval);
+		break;
+	case VSeq:
+		el = v->u.seqval;
+		for(l = el; l != nil; l = l->tl)
+			freevalfields(&l->hd.val);
+		if (el)
+			freeelist(el);
+		break;
+	case VSet:
+		el = v->u.setval;
+		for(l = el; l != nil; l = l->tl)
+			freevalfields(&l->hd.val);
+		if (el)
+			freeelist(el);
+		break;
+	}
+}
+
+/* end of general ASN1 functions */
+
+
+
+
+
+/*=============================================================*/
+/*
+ * Decode and parse an X.509 Certificate, defined by this ASN1:
+ *	Certificate ::= SEQUENCE {
+ *		certificateInfo CertificateInfo,
+ *		signatureAlgorithm AlgorithmIdentifier,
+ *		signature BIT STRING }
+ *
+ *	CertificateInfo ::= SEQUENCE {
+ *		version [0] INTEGER DEFAULT v1 (0),
+ *		serialNumber INTEGER,
+ *		signature AlgorithmIdentifier,
+ *		issuer Name,
+ *		validity Validity,
+ *		subject Name,
+ *		subjectPublicKeyInfo SubjectPublicKeyInfo }
+ *	(version v2 has two more fields, optional unique identifiers for
+ *  issuer and subject; since we ignore these anyway, we won't parse them)
+ *
+ *	Validity ::= SEQUENCE {
+ *		notBefore UTCTime,
+ *		notAfter UTCTime }
+ *
+ *	SubjectPublicKeyInfo ::= SEQUENCE {
+ *		algorithm AlgorithmIdentifier,
+ *		subjectPublicKey BIT STRING }
+ *
+ *	AlgorithmIdentifier ::= SEQUENCE {
+ *		algorithm OBJECT IDENTIFER,
+ *		parameters ANY DEFINED BY ALGORITHM OPTIONAL }
+ *
+ *	Name ::= SEQUENCE OF RelativeDistinguishedName
+ *
+ *	RelativeDistinguishedName ::= SETOF SIZE(1..MAX) OF AttributeTypeAndValue
+ *
+ *	AttributeTypeAndValue ::= SEQUENCE {
+ *		type OBJECT IDENTIFER,
+ *		value DirectoryString }
+ *	(selected attributes have these Object Ids:
+ *		commonName {2 5 4 3}
+ *		countryName {2 5 4 6}
+ *		localityName {2 5 4 7}
+ *		stateOrProvinceName {2 5 4 8}
+ *		organizationName {2 5 4 10}
+ *		organizationalUnitName {2 5 4 11}
+ *	)
+ *
+ *	DirectoryString ::= CHOICE {
+ *		teletexString TeletexString,
+ *		printableString PrintableString,
+ *		universalString UniversalString }
+ *
+ *  See rfc1423, rfc2437 for AlgorithmIdentifier, subjectPublicKeyInfo, signature.
+ *
+ *  Not yet implemented:
+ *   CertificateRevocationList ::= SIGNED SEQUENCE{
+ *           signature       AlgorithmIdentifier,
+ *           issuer          Name,
+ *           lastUpdate      UTCTime,
+ *           nextUpdate      UTCTime,
+ *           revokedCertificates
+ *                           SEQUENCE OF CRLEntry OPTIONAL}
+ *   CRLEntry ::= SEQUENCE{
+ *           userCertificate SerialNumber,
+ *           revocationDate UTCTime}
+ */
+
+typedef struct CertX509 {
+	int	serial;
+	char*	issuer;
+	char*	validity_start;
+	char*	validity_end;
+	char*	subject;
+	int	publickey_alg;
+	Bytes*	publickey;
+	int	signature_alg;
+	Bytes*	signature;
+} CertX509;
+
+/* Algorithm object-ids */
+enum {
+	ALG_rsaEncryption,
+	ALG_md2WithRSAEncryption,
+	ALG_md4WithRSAEncryption,
+	ALG_md5WithRSAEncryption,
+	ALG_sha1WithRSAEncryption,
+	ALG_md5,
+	NUMALGS
+};
+typedef struct Ints7 {
+	int		len;
+	int		data[7];
+} Ints7;
+static Ints7 oid_rsaEncryption = {7, 1, 2, 840, 113549, 1, 1, 1 };
+static Ints7 oid_md2WithRSAEncryption = {7, 1, 2, 840, 113549, 1, 1, 2 };
+static Ints7 oid_md4WithRSAEncryption = {7, 1, 2, 840, 113549, 1, 1, 3 };
+static Ints7 oid_md5WithRSAEncryption = {7, 1, 2, 840, 113549, 1, 1, 4 };
+static Ints7 oid_sha1WithRSAEncryption ={7, 1, 2, 840, 113549, 1, 1, 5 };
+static Ints7 oid_md5 ={6, 1, 2, 840, 113549, 2, 5, 0 };
+static Ints *alg_oid_tab[NUMALGS+1] = {
+	(Ints*)&oid_rsaEncryption,
+	(Ints*)&oid_md2WithRSAEncryption,
+	(Ints*)&oid_md4WithRSAEncryption,
+	(Ints*)&oid_md5WithRSAEncryption,
+	(Ints*)&oid_sha1WithRSAEncryption,
+	(Ints*)&oid_md5,
+	nil
+};
+static DigestFun digestalg[NUMALGS+1] = { md5, md5, md5, md5, sha1, md5, nil };
+
+static void
+freecert(CertX509* c)
+{
+	if (!c) return;
+	if(c->issuer != nil)
+		free(c->issuer);
+	if(c->validity_start != nil)
+		free(c->validity_start);
+	if(c->validity_end != nil)
+		free(c->validity_end);
+	if(c->subject != nil)
+		free(c->subject);
+	freebytes(c->publickey);
+	freebytes(c->signature);
+}
+
+/*
+ * Parse the Name ASN1 type.
+ * The sequence of RelativeDistinguishedName's gives a sort of pathname,
+ * from most general to most specific.  Each element of the path can be
+ * one or more (but usually just one) attribute-value pair, such as
+ * countryName="US".
+ * We'll just form a "postal-style" address string by concatenating the elements
+ * from most specific to least specific, separated by commas.
+ * Return name-as-string (which must be freed by caller).
+ */
+static char*
+parse_name(Elem* e)
+{
+	Elist* el;
+	Elem* es;
+	Elist* esetl;
+	Elem* eat;
+	Elist* eatl;
+	char* s;
+	enum { MAXPARTS = 100 };
+	char* parts[MAXPARTS];
+	int i;
+	int plen;
+	char* ans = nil;
+
+	if(!is_seq(e, &el))
+		goto errret;
+	i = 0;
+	plen = 0;
+	while(el != nil) {
+		es = &el->hd;
+		if(!is_set(es, &esetl))
+			goto errret;
+		while(esetl != nil) {
+			eat = &esetl->hd;
+			if(!is_seq(eat, &eatl) || elistlen(eatl) != 2)
+				goto errret;
+			if(!is_string(&eatl->tl->hd, &s) || i>=MAXPARTS)
+				goto errret;
+			parts[i++] = s;
+			plen += strlen(s) + 2;		/* room for ", " after */
+			esetl = esetl->tl;
+		}
+		el = el->tl;
+	}
+	if(i > 0) {
+		ans = (char*)emalloc(plen);
+		*ans = '\0';
+		while(--i >= 0) {
+			s = parts[i];
+			strcat(ans, s);
+			if(i > 0)
+				strcat(ans, ", ");
+		}
+	}
+
+errret:
+	return ans;
+}
+
+/*
+ * Parse an AlgorithmIdentifer ASN1 type.
+ * Look up the oid in oid_tab and return one of OID_rsaEncryption, etc..,
+ * or -1 if not found.
+ * For now, ignore parameters, since none of our algorithms need them.
+ */
+static int
+parse_alg(Elem* e)
+{
+	Elist* el;
+	Ints* oid;
+
+	if(!is_seq(e, &el) || el == nil || !is_oid(&el->hd, &oid))
+		return -1;
+	return oid_lookup(oid, alg_oid_tab);
+}
+
+static CertX509*
+decode_cert(Bytes* a)
+{
+	int ok = 0;
+	int n;
+	CertX509* c = nil;
+	Elem  ecert;
+	Elem* ecertinfo;
+	Elem* esigalg;
+	Elem* esig;
+	Elem* eserial;
+	Elem* eissuer;
+	Elem* evalidity;
+	Elem* esubj;
+	Elem* epubkey;
+	Elist* el;
+	Elist* elcert = nil;
+	Elist* elcertinfo = nil;
+	Elist* elvalidity = nil;
+	Elist* elpubkey = nil;
+	Bits* bits = nil;
+	Bytes* b;
+	Elem* e;
+
+	if(decode(a->data, a->len, &ecert) != ASN_OK)
+		goto errret;
+
+	c = (CertX509*)emalloc(sizeof(CertX509));
+	c->serial = -1;
+	c->issuer = nil;
+	c->validity_start = nil;
+	c->validity_end = nil;
+	c->subject = nil;
+	c->publickey_alg = -1;
+	c->publickey = nil;
+	c->signature_alg = -1;
+	c->signature = nil;
+
+	/* Certificate */
+ 	if(!is_seq(&ecert, &elcert) || elistlen(elcert) !=3)
+		goto errret;
+ 	ecertinfo = &elcert->hd;
+ 	el = elcert->tl;
+ 	esigalg = &el->hd;
+	c->signature_alg = parse_alg(esigalg);
+ 	el = el->tl;
+ 	esig = &el->hd;
+
+	/* Certificate Info */
+	if(!is_seq(ecertinfo, &elcertinfo))
+		goto errret;
+	n = elistlen(elcertinfo);
+  	if(n < 6)
+		goto errret;
+	eserial =&elcertinfo->hd;
+ 	el = elcertinfo->tl;
+ 	/* check for optional version, marked by explicit context tag 0 */
+	if(eserial->tag.class == Context && eserial->tag.num == 0) {
+ 		eserial = &el->hd;
+ 		if(n < 7)
+ 			goto errret;
+ 		el = el->tl;
+ 	}
+
+	if(parse_alg(&el->hd) != c->signature_alg)
+		goto errret;
+ 	el = el->tl;
+ 	eissuer = &el->hd;
+ 	el = el->tl;
+ 	evalidity = &el->hd;
+ 	el = el->tl;
+ 	esubj = &el->hd;
+ 	el = el->tl;
+ 	epubkey = &el->hd;
+ 	if(!is_int(eserial, &c->serial)) {
+		if(!is_bigint(eserial, &b))
+			goto errret;
+		c->serial = -1;	/* else we have to change cert struct */
+  	}
+	c->issuer = parse_name(eissuer);
+	if(c->issuer == nil)
+		goto errret;
+	/* Validity */
+  	if(!is_seq(evalidity, &elvalidity))
+		goto errret;
+	if(elistlen(elvalidity) != 2)
+		goto errret;
+	e = &elvalidity->hd;
+	if(!is_time(e, &c->validity_start))
+		goto errret;
+	e->val.u.stringval = nil;	/* string ownership transfer */
+	e = &elvalidity->tl->hd;
+ 	if(!is_time(e, &c->validity_end))
+		goto errret;
+	e->val.u.stringval = nil;	/* string ownership transfer */
+
+	/* resume CertificateInfo */
+ 	c->subject = parse_name(esubj);
+	if(c->subject == nil)
+		goto errret;
+
+	/* SubjectPublicKeyInfo */
+ 	if(!is_seq(epubkey, &elpubkey))
+		goto errret;
+	if(elistlen(elpubkey) != 2)
+		goto errret;
+
+	c->publickey_alg = parse_alg(&elpubkey->hd);
+	if(c->publickey_alg < 0)
+		goto errret;
+  	if(!is_bitstring(&elpubkey->tl->hd, &bits))
+		goto errret;
+	if(bits->unusedbits != 0)
+		goto errret;
+ 	c->publickey = makebytes(bits->data, bits->len);
+
+	/*resume Certificate */
+	if(c->signature_alg < 0)
+		goto errret;
+ 	if(!is_bitstring(esig, &bits))
+		goto errret;
+ 	c->signature = makebytes(bits->data, bits->len);
+	ok = 1;
+
+errret:
+	freevalfields(&ecert.val);	/* recurses through lists, too */
+	if(!ok){
+		freecert(c);
+		c = nil;
+	}
+	return c;
+}
+
+/*
+ *	RSAPublickKey :: SEQUENCE {
+ *		modulus INTEGER,
+ *		publicExponent INTEGER
+ *	}
+ */
+static RSApub*
+decode_rsapubkey(Bytes* a)
+{
+	Elem e;
+	Elist *el;
+	mpint *mp;
+	RSApub* key;
+
+	key = rsapuballoc();
+	if(decode(a->data, a->len, &e) != ASN_OK)
+		goto errret;
+	if(!is_seq(&e, &el) || elistlen(el) != 2)
+		goto errret;
+
+	key->n = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->ek = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+	return key;
+errret:
+	rsapubfree(key);
+	return nil;
+}
+
+/*
+ *	RSAPrivateKey ::= SEQUENCE {
+ *		version Version,
+ *		modulus INTEGER, -- n
+ *		publicExponent INTEGER, -- e
+ *		privateExponent INTEGER, -- d
+ *		prime1 INTEGER, -- p
+ *		prime2 INTEGER, -- q
+ *		exponent1 INTEGER, -- d mod (p-1)
+ *		exponent2 INTEGER, -- d mod (q-1)
+ *		coefficient INTEGER -- (inverse of q) mod p }
+ */
+static RSApriv*
+decode_rsaprivkey(Bytes* a)
+{
+	int version;
+	Elem e;
+	Elist *el;
+	mpint *mp;
+	RSApriv* key;
+
+	key = rsaprivalloc();
+	if(decode(a->data, a->len, &e) != ASN_OK)
+		goto errret;
+	if(!is_seq(&e, &el) || elistlen(el) != 9)
+		goto errret;
+	if(!is_int(&el->hd, &version) || version != 0)
+		goto errret;
+
+	el = el->tl;
+	key->pub.n = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->pub.ek = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->dk = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->q = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->p = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->kq = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->kp = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	el = el->tl;
+	key->c2 = mp = asn1mpint(&el->hd);
+	if(mp == nil)
+		goto errret;
+
+	return key;
+errret:
+	rsaprivfree(key);
+	return nil;
+}
+
+static mpint*
+asn1mpint(Elem *e)
+{
+	Bytes *b;
+	mpint *mp;
+	int v;
+
+	if(is_int(e, &v))
+		return itomp(v, nil);
+	if(is_bigint(e, &b)) {
+		mp = betomp(b->data, b->len, nil);
+		freebytes(b);
+		return mp;
+	}
+	return nil;
+}
+
+static mpint*
+pkcs1pad(Bytes *b, mpint *modulus)
+{
+	int n = (mpsignif(modulus)+7)/8;
+	int pm1, i;
+	uchar *p;
+	mpint *mp;
+
+	pm1 = n - 1 - b->len;
+	p = (uchar*)emalloc(n);
+	p[0] = 0;
+	p[1] = 1;
+	for(i = 2; i < pm1; i++)
+		p[i] = 0xFF;
+	p[pm1] = 0;
+	memcpy(&p[pm1+1], b->data, b->len);
+	mp = betomp(p, n, nil);
+	free(p);
+	return mp;
+}
+
+RSApriv*
+asn1toRSApriv(uchar *kd, int kn)
+{
+	Bytes *b;
+	RSApriv *key;
+
+	b = makebytes(kd, kn);
+	key = decode_rsaprivkey(b);
+	freebytes(b);
+	return key;
+}
+
+/*
+ * digest(CertificateInfo)
+ * Our ASN.1 library doesn't return pointers into the original
+ * data array, so we need to do a little hand decoding.
+ */
+static void
+digest_certinfo(Bytes *cert, DigestFun digestfun, uchar *digest)
+{
+	uchar *info, *p, *pend;
+	ulong infolen;
+	int isconstr, length;
+	Tag tag;
+	Elem elem;
+
+	p = cert->data;
+	pend = cert->data + cert->len;
+	if(tag_decode(&p, pend, &tag, &isconstr) != ASN_OK ||
+	   tag.class != Universal || tag.num != SEQUENCE ||
+	   length_decode(&p, pend, &length) != ASN_OK ||
+	   p+length > pend ||
+	   p+length < p)
+		return;
+	info = p;
+	if(ber_decode(&p, pend, &elem) != ASN_OK || elem.tag.num != SEQUENCE)
+		return;
+	infolen = p - info;
+	(*digestfun)(info, infolen, digest, nil);
+}
+
+static char*
+verify_signature(Bytes* signature, RSApub *pk, uchar *edigest, Elem **psigalg)
+{
+	Elem e;
+	Elist *el;
+	Bytes *digest;
+	uchar *pkcs1buf, *buf;
+	int buflen;
+	mpint *pkcs1;
+	int nlen;
+
+	/* one less than the byte length of the modulus */
+	nlen = (mpsignif(pk->n)-1)/8;
+
+	/* see 9.2.1 of rfc2437 */
+	pkcs1 = betomp(signature->data, signature->len, nil);
+	mpexp(pkcs1, pk->ek, pk->n, pkcs1);
+	pkcs1buf = nil;
+	buflen = mptobe(pkcs1, nil, 0, &pkcs1buf);
+	buf = pkcs1buf;
+	if(buflen != nlen || buf[0] != 1)
+		return "expected 1";
+	buf++;
+	while(buf[0] == 0xff)
+		buf++;
+	if(buf[0] != 0)
+		return "expected 0";
+	buf++;
+	buflen -= buf-pkcs1buf;
+	if(decode(buf, buflen, &e) != ASN_OK || !is_seq(&e, &el) || elistlen(el) != 2 ||
+			!is_octetstring(&el->tl->hd, &digest))
+		return "signature parse error";
+	*psigalg = &el->hd;
+	if(memcmp(digest->data, edigest, digest->len) == 0)
+		return nil;
+	return "digests did not match";
+}
+	
+RSApub*
+X509toRSApub(uchar *cert, int ncert, char *name, int nname)
+{
+	char *e;
+	Bytes *b;
+	CertX509 *c;
+	RSApub *pk;
+
+	b = makebytes(cert, ncert);
+	c = decode_cert(b);
+	freebytes(b);
+	if(c == nil)
+		return nil;
+	if(name != nil && c->subject != nil){
+		e = strchr(c->subject, ',');
+		if(e != nil)
+			*e = 0;  // take just CN part of Distinguished Name
+		strncpy(name, c->subject, nname);
+	}
+	pk = decode_rsapubkey(c->publickey);
+	freecert(c);
+	return pk;
+}
+
+char*
+X509verify(uchar *cert, int ncert, RSApub *pk)
+{
+	char *e;
+	Bytes *b;
+	CertX509 *c;
+	uchar digest[SHA1dlen];
+	Elem *sigalg;
+
+	b = makebytes(cert, ncert);
+	c = decode_cert(b);
+	if(c != nil)
+		digest_certinfo(b, digestalg[c->signature_alg], digest);
+	freebytes(b);
+	if(c == nil)
+		return "cannot decode cert";
+	e = verify_signature(c->signature, pk, digest, &sigalg);
+	freecert(c);
+	return e;
+}
+
+/* ------- Elem constructors ---------- */
+static Elem
+Null(void)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = NULLTAG;
+	e.val.tag = VNull;
+	return e;
+}
+
+static Elem
+mkint(int j)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = INTEGER;
+	e.val.tag = VInt;
+	e.val.u.intval = j;
+	return e;
+}
+
+static Elem
+mkbigint(mpint *p)
+{
+	Elem e;
+	uchar *buf;
+	int buflen;
+
+	e.tag.class = Universal;
+	e.tag.num = INTEGER;
+	e.val.tag = VBigInt;
+	buflen = mptobe(p, nil, 0, &buf);
+	e.val.u.bigintval = makebytes(buf, buflen);
+	free(buf);
+	return e;
+}
+
+static Elem
+mkstring(char *s)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = IA5String;
+	e.val.tag = VString;
+	e.val.u.stringval = estrdup(s);
+	return e;
+}
+
+static Elem
+mkoctet(uchar *buf, int buflen)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = OCTET_STRING;
+	e.val.tag = VOctets;
+	e.val.u.octetsval = makebytes(buf, buflen);
+	return e;
+}
+
+static Elem
+mkbits(uchar *buf, int buflen)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = BIT_STRING;
+	e.val.tag = VBitString;
+	e.val.u.bitstringval = makebits(buf, buflen, 0);
+	return e;
+}
+
+static Elem
+mkutc(long t)
+{
+	Elem e;
+	char utc[50];
+	Tm *tm = gmtime(t);
+
+	e.tag.class = Universal;
+	e.tag.num = UTCTime;
+	e.val.tag = VString;
+	snprint(utc, 50, "%.2d%.2d%.2d%.2d%.2d%.2dZ",
+		tm->year % 100, tm->mon+1, tm->mday, tm->hour, tm->min, tm->sec);
+	e.val.u.stringval = estrdup(utc);
+	return e;
+}
+
+static Elem
+mkoid(Ints *oid)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = OBJECT_ID;
+	e.val.tag = VObjId;
+	e.val.u.objidval = makeints(oid->data, oid->len);
+	return e;
+}
+
+static Elem
+mkseq(Elist *el)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = SEQUENCE;
+	e.val.tag = VSeq;
+	e.val.u.seqval = el;
+	return e;
+}
+
+static Elem
+mkset(Elist *el)
+{
+	Elem e;
+
+	e.tag.class = Universal;
+	e.tag.num = SETOF;
+	e.val.tag = VSet;
+	e.val.u.setval = el;
+	return e;
+}
+
+static Elem
+mkalg(int alg)
+{
+	return mkseq(mkel(mkoid(alg_oid_tab[alg]), mkel(Null(), nil)));
+}
+
+typedef struct Ints7pref {
+	int		len;
+	int		data[7];
+	char	prefix[4];
+} Ints7pref;
+Ints7pref DN_oid[] = {
+	{4, 2, 5, 4, 6, 0, 0, 0,  "C="},
+	{4, 2, 5, 4, 8, 0, 0, 0,  "ST="},
+	{4, 2, 5, 4, 7, 0, 0, 0,  "L="},
+	{4, 2, 5, 4, 10, 0, 0, 0, "O="},
+	{4, 2, 5, 4, 11, 0, 0, 0, "OU="},
+	{4, 2, 5, 4, 3, 0, 0, 0,  "CN="},
+ 	{7, 1,2,840,113549,1,9,1, "E="},
+};
+
+static Elem
+mkname(Ints7pref *oid, char *subj)
+{
+	return mkset(mkel(mkseq(mkel(mkoid((Ints*)oid), mkel(mkstring(subj), nil))), nil));
+}
+
+static Elem
+mkDN(char *dn)
+{
+	int i, j, nf;
+	char *f[20], *prefix, *d2 = estrdup(dn);
+	Elist* el = nil;
+
+	nf = tokenize(d2, f, nelem(f));
+	for(i=nf-1; i>=0; i--){
+		for(j=0; j<nelem(DN_oid); j++){
+			prefix = DN_oid[j].prefix;
+			if(strncmp(f[i],prefix,strlen(prefix))==0){
+				el = mkel(mkname(&DN_oid[j],f[i]+strlen(prefix)), el);
+				break;
+			}
+		}
+	}
+	free(d2);
+	return mkseq(el);
+}
+
+
+uchar*
+X509gen(RSApriv *priv, char *subj, ulong valid[2], int *certlen)
+{
+	int serial = 0;
+	uchar *cert = nil;
+	RSApub *pk = rsaprivtopub(priv);
+	Bytes *certbytes, *pkbytes, *certinfobytes, *sigbytes;
+	Elem e, certinfo, issuer, subject, pubkey, validity, sig;
+	uchar digest[MD5dlen], *buf;
+	int buflen;
+	mpint *pkcs1;
+
+	e.val.tag = VInt;  /* so freevalfields at errret is no-op */
+	issuer = mkDN(subj);
+	subject = mkDN(subj);
+	pubkey = mkseq(mkel(mkbigint(pk->n),mkel(mkint(mptoi(pk->ek)),nil)));
+	if(encode(pubkey, &pkbytes) != ASN_OK)
+		goto errret;
+	freevalfields(&pubkey.val);
+	pubkey = mkseq(
+		mkel(mkalg(ALG_rsaEncryption),
+		mkel(mkbits(pkbytes->data, pkbytes->len),
+		nil)));
+	freebytes(pkbytes);
+	validity = mkseq(
+		mkel(mkutc(valid[0]),
+		mkel(mkutc(valid[1]),
+		nil)));
+	certinfo = mkseq(
+		mkel(mkint(serial),
+		mkel(mkalg(ALG_md5WithRSAEncryption),
+		mkel(issuer,
+		mkel(validity,
+		mkel(subject,
+		mkel(pubkey,
+		nil)))))));
+	if(encode(certinfo, &certinfobytes) != ASN_OK)
+		goto errret;
+	md5(certinfobytes->data, certinfobytes->len, digest, 0);
+	freebytes(certinfobytes);
+	sig = mkseq(
+		mkel(mkalg(ALG_md5),
+		mkel(mkoctet(digest, MD5dlen),
+		nil)));
+	if(encode(sig, &sigbytes) != ASN_OK)
+		goto errret;
+	pkcs1 = pkcs1pad(sigbytes, pk->n);
+	freebytes(sigbytes);
+	rsadecrypt(priv, pkcs1, pkcs1);
+	buflen = mptobe(pkcs1, nil, 0, &buf);
+	mpfree(pkcs1);
+	e = mkseq(
+		mkel(certinfo,
+		mkel(mkalg(ALG_md5WithRSAEncryption),
+		mkel(mkbits(buf, buflen),
+		nil))));
+	free(buf);
+	if(encode(e, &certbytes) != ASN_OK)
+		goto errret;
+	if(certlen)
+		*certlen = certbytes->len;
+	cert = certbytes->data;
+errret:
+	freevalfields(&e.val);
+	return cert;
+}
+
+uchar*
+X509req(RSApriv *priv, char *subj, int *certlen)
+{
+	/* RFC 2314, PKCS #10 Certification Request Syntax */
+	int version = 0;
+	uchar *cert = nil;
+	RSApub *pk = rsaprivtopub(priv);
+	Bytes *certbytes, *pkbytes, *certinfobytes, *sigbytes;
+	Elem e, certinfo, subject, pubkey, sig;
+	uchar digest[MD5dlen], *buf;
+	int buflen;
+	mpint *pkcs1;
+
+	e.val.tag = VInt;  /* so freevalfields at errret is no-op */
+	subject = mkDN(subj);
+	pubkey = mkseq(mkel(mkbigint(pk->n),mkel(mkint(mptoi(pk->ek)),nil)));
+	if(encode(pubkey, &pkbytes) != ASN_OK)
+		goto errret;
+	freevalfields(&pubkey.val);
+	pubkey = mkseq(
+		mkel(mkalg(ALG_rsaEncryption),
+		mkel(mkbits(pkbytes->data, pkbytes->len),
+		nil)));
+	freebytes(pkbytes);
+	certinfo = mkseq(
+		mkel(mkint(version),
+		mkel(subject,
+		mkel(pubkey,
+		nil))));
+	if(encode(certinfo, &certinfobytes) != ASN_OK)
+		goto errret;
+	md5(certinfobytes->data, certinfobytes->len, digest, 0);
+	freebytes(certinfobytes);
+	sig = mkseq(
+		mkel(mkalg(ALG_md5),
+		mkel(mkoctet(digest, MD5dlen),
+		nil)));
+	if(encode(sig, &sigbytes) != ASN_OK)
+		goto errret;
+	pkcs1 = pkcs1pad(sigbytes, pk->n);
+	freebytes(sigbytes);
+	rsadecrypt(priv, pkcs1, pkcs1);
+	buflen = mptobe(pkcs1, nil, 0, &buf);
+	mpfree(pkcs1);
+	e = mkseq(
+		mkel(certinfo,
+		mkel(mkalg(ALG_md5),
+		mkel(mkbits(buf, buflen),
+		nil))));
+	free(buf);
+	if(encode(e, &certbytes) != ASN_OK)
+		goto errret;
+	if(certlen)
+		*certlen = certbytes->len;
+	cert = certbytes->data;
+errret:
+	freevalfields(&e.val);
+	return cert;
+}
+
+static char*
+tagdump(Tag tag)
+{
+	if(tag.class != Universal)
+		return smprint("class%d,num%d", tag.class, tag.num);
+	switch(tag.num){
+		case BOOLEAN: return "BOOLEAN"; break;
+		case INTEGER: return "INTEGER"; break;
+		case BIT_STRING: return "BIT STRING"; break;
+		case OCTET_STRING: return "OCTET STRING"; break;
+		case NULLTAG: return "NULLTAG"; break;
+		case OBJECT_ID: return "OID"; break;
+		case ObjectDescriptor: return "OBJECT_DES"; break;
+		case EXTERNAL: return "EXTERNAL"; break;
+		case REAL: return "REAL"; break;
+		case ENUMERATED: return "ENUMERATED"; break;
+		case EMBEDDED_PDV: return "EMBEDDED PDV"; break;
+		case SEQUENCE: return "SEQUENCE"; break;
+		case SETOF: return "SETOF"; break;
+		case NumericString: return "NumericString"; break;
+		case PrintableString: return "PrintableString"; break;
+		case TeletexString: return "TeletexString"; break;
+		case VideotexString: return "VideotexString"; break;
+		case IA5String: return "IA5String"; break;
+		case UTCTime: return "UTCTime"; break;
+		case GeneralizedTime: return "GeneralizedTime"; break;
+		case GraphicString: return "GraphicString"; break;
+		case VisibleString: return "VisibleString"; break;
+		case GeneralString: return "GeneralString"; break;
+		case UniversalString: return "UniversalString"; break;
+		case BMPString: return "BMPString"; break;
+		default:
+			return smprint("Universal,num%d", tag.num);
+	}
+}
+
+static void
+edump(Elem e)
+{
+	Value v;
+	Elist *el;
+	int i;
+
+	print("%s{", tagdump(e.tag));
+	v = e.val;
+	switch(v.tag){
+	case VBool: print("Bool %d",v.u.boolval); break;
+	case VInt: print("Int %d",v.u.intval); break;
+	case VOctets: print("Octets[%d] %.2x%.2x...",v.u.octetsval->len,v.u.octetsval->data[0],v.u.octetsval->data[1]); break;
+	case VBigInt: print("BigInt[%d] %.2x%.2x...",v.u.bigintval->len,v.u.bigintval->data[0],v.u.bigintval->data[1]); break;
+	case VReal: print("Real..."); break;
+	case VOther: print("Other..."); break;
+	case VBitString: print("BitString..."); break;
+	case VNull: print("Null"); break;
+	case VEOC: print("EOC..."); break;
+	case VObjId: print("ObjId");
+		for(i = 0; i<v.u.objidval->len; i++)
+			print(" %d", v.u.objidval->data[i]);
+		break;
+	case VString: print("String \"%s\"",v.u.stringval); break;
+	case VSeq: print("Seq\n");
+		for(el = v.u.seqval; el!=nil; el = el->tl)
+			edump(el->hd);
+		break;
+	case VSet: print("Set\n");
+		for(el = v.u.setval; el!=nil; el = el->tl)
+			edump(el->hd);
+		break;
+	}
+	print("}\n");
+}
+
+void
+asn1dump(uchar *der, int len)
+{
+	Elem e;
+
+	if(decode(der, len, &e) != ASN_OK){
+		print("didn't parse\n");
+		exits("didn't parse");
+	}
+	edump(e);
+}
+
+void
+X509dump(uchar *cert, int ncert)
+{
+	char *e;
+	Bytes *b;
+	CertX509 *c;
+	RSApub *pk;
+	uchar digest[SHA1dlen];
+	Elem *sigalg;
+
+	print("begin X509dump\n");
+	b = makebytes(cert, ncert);
+	c = decode_cert(b);
+	if(c != nil)
+		digest_certinfo(b, digestalg[c->signature_alg], digest);
+	freebytes(b);
+	if(c == nil){
+		print("cannot decode cert");
+		return;
+	}
+
+	print("serial %d\n", c->serial);
+	print("issuer %s\n", c->issuer);
+	print("validity %s %s\n", c->validity_start, c->validity_end);
+	print("subject %s\n", c->subject);
+	pk = decode_rsapubkey(c->publickey);
+	print("pubkey e=%B n(%d)=%B\n", pk->ek, mpsignif(pk->n), pk->n);
+
+	print("sigalg=%d digest=%.*H\n", c->signature_alg, MD5dlen, digest);
+	e = verify_signature(c->signature, pk, digest, &sigalg);
+	if(e==nil){
+		e = "nil (meaning ok)";
+		print("sigalg=\n");
+		if(sigalg)
+			edump(*sigalg);
+	}
+	print("self-signed verify_signature returns: %s\n", e);
+
+	rsapubfree(pk);
+	freecert(c);
+	print("end X509dump\n");
+}