xref: /csrg-svn/lib/libc/gen/crypt.c (revision 47038)
1*47038Sbostic /*
2*47038Sbostic  * Copyright (c) 1989 The Regents of the University of California.
3*47038Sbostic  * All rights reserved.
4*47038Sbostic  *
5*47038Sbostic  * This code is derived from software contributed to Berkeley by
6*47038Sbostic  * Tom Truscott.
7*47038Sbostic  *
8*47038Sbostic  * Redistribution and use in source and binary forms are permitted
9*47038Sbostic  * provided that the above copyright notice and this paragraph are
10*47038Sbostic  * duplicated in all such forms and that any documentation,
11*47038Sbostic  * advertising materials, and other materials related to such
12*47038Sbostic  * distribution and use acknowledge that the software was developed
13*47038Sbostic  * by the University of California, Berkeley.  The name of the
14*47038Sbostic  * University may not be used to endorse or promote products derived
15*47038Sbostic  * from this software without specific prior written permission.
16*47038Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
17*47038Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18*47038Sbostic  * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19*47038Sbostic  */
20*47038Sbostic 
2126545Sdonn #if defined(LIBC_SCCS) && !defined(lint)
22*47038Sbostic static char sccsid[] = "@(#)crypt.c	5.5 (Berkeley) 03/06/91";
23*47038Sbostic #endif /* LIBC_SCCS and not lint */
2422083Smckusick 
25*47038Sbostic #include <sys/cdefs.h>
2646597Sdonn #include <unistd.h>
2746597Sdonn 
281958Swnj /*
29*47038Sbostic  * UNIX password, and DES, encryption.
30*47038Sbostic  * By Tom Truscott, trt@rti.rti.org,
31*47038Sbostic  * from algorithms by Robert W. Baldwin and James Gillogly.
32*47038Sbostic  *
33*47038Sbostic  * References:
34*47038Sbostic  * "Mathematical Cryptology for Computer Scientists and Mathematicians,"
35*47038Sbostic  * by Wayne Patterson, 1987, ISBN 0-8476-7438-X.
36*47038Sbostic  *
37*47038Sbostic  * "Password Security: A Case History," R. Morris and Ken Thompson,
38*47038Sbostic  * Communications of the ACM, vol. 22, pp. 594-597, Nov. 1979.
39*47038Sbostic  *
40*47038Sbostic  * "DES will be Totally Insecure within Ten Years," M.E. Hellman,
41*47038Sbostic  * IEEE Spectrum, vol. 16, pp. 32-39, July 1979.
421958Swnj  */
431958Swnj 
44*47038Sbostic /* =====  Configuration ==================== */
45*47038Sbostic 
461958Swnj /*
47*47038Sbostic  * define "MUST_ALIGN" if your compiler cannot load/store
48*47038Sbostic  * long integers at arbitrary (e.g. odd) memory locations.
49*47038Sbostic  * (Either that or never pass unaligned addresses to des_cipher!)
501958Swnj  */
51*47038Sbostic #if !defined(vax)
52*47038Sbostic #define	MUST_ALIGN
53*47038Sbostic #endif
541958Swnj 
551958Swnj /*
56*47038Sbostic  * define "LONG_IS_32_BITS" only if sizeof(long)==4.
57*47038Sbostic  * This avoids use of bit fields (your compiler may be sloppy with them).
581958Swnj  */
59*47038Sbostic #if !defined(cray)
60*47038Sbostic #define	LONG_IS_32_BITS
61*47038Sbostic #endif
621958Swnj 
631958Swnj /*
64*47038Sbostic  * define "B64" to be the declaration for a 64 bit integer.
65*47038Sbostic  * XXX this feature is currently unused, see "endian" comment below.
661958Swnj  */
67*47038Sbostic #if defined(cray)
68*47038Sbostic #define	B64	long
69*47038Sbostic #endif
70*47038Sbostic #if defined(convex)
71*47038Sbostic #define	B64	long long
72*47038Sbostic #endif
731958Swnj 
741958Swnj /*
75*47038Sbostic  * define "LARGEDATA" to get faster permutations, by using about 72 kilobytes
76*47038Sbostic  * of lookup tables.  This speeds up des_setkey() and des_cipher(), but has
77*47038Sbostic  * little effect on crypt().
781958Swnj  */
79*47038Sbostic #if defined(notdef)
80*47038Sbostic #define	LARGEDATA
81*47038Sbostic #endif
821958Swnj 
83*47038Sbostic /* comment out "static" when profiling */
84*47038Sbostic #define	STATIC	static
85*47038Sbostic STATIC init_des(), perminit(), permute();
86*47038Sbostic #ifdef DEBUG
87*47038Sbostic STATIC prtab();
88*47038Sbostic #endif
891958Swnj 
90*47038Sbostic /* ==================================== */
91*47038Sbostic 
921958Swnj /*
93*47038Sbostic  * Cipher-block representation (Bob Baldwin):
94*47038Sbostic  *
95*47038Sbostic  * DES operates on groups of 64 bits, numbered 1..64 (sigh).  One
96*47038Sbostic  * representation is to store one bit per byte in an array of bytes.  Bit N of
97*47038Sbostic  * the NBS spec is stored as the LSB of the Nth byte (index N-1) in the array.
98*47038Sbostic  * Another representation stores the 64 bits in 8 bytes, with bits 1..8 in the
99*47038Sbostic  * first byte, 9..16 in the second, and so on.  The DES spec apparently has
100*47038Sbostic  * bit 1 in the MSB of the first byte, but that is particularly noxious so we
101*47038Sbostic  * bit-reverse each byte so that bit 1 is the LSB of the first byte, bit 8 is
102*47038Sbostic  * the MSB of the first byte.  Specifically, the 64-bit input data and key are
103*47038Sbostic  * converted to LSB format, and the output 64-bit block is converted back into
104*47038Sbostic  * MSB format.
105*47038Sbostic  *
106*47038Sbostic  * DES operates internally on groups of 32 bits which are expanded to 48 bits
107*47038Sbostic  * by permutation E and shrunk back to 32 bits by the S boxes.  To speed up
108*47038Sbostic  * the computation, the expansion is applied only once, the expanded
109*47038Sbostic  * representation is maintained during the encryption, and a compression
110*47038Sbostic  * permutation is applied only at the end.  To speed up the S-box lookups,
111*47038Sbostic  * the 48 bits are maintained as eight 6 bit groups, one per byte, which
112*47038Sbostic  * directly feed the eight S-boxes.  Within each byte, the 6 bits are the
113*47038Sbostic  * most significant ones.  The low two bits of each byte are zero.  (Thus,
114*47038Sbostic  * bit 1 of the 48 bit E expansion is stored as the "4"-valued bit of the
115*47038Sbostic  * first byte in the eight byte representation, bit 2 of the 48 bit value is
116*47038Sbostic  * the "8"-valued bit, and so on.) In fact, a combined "SPE"-box lookup is
117*47038Sbostic  * used, in which the output is the 64 bit result of an S-box lookup which
118*47038Sbostic  * has been permuted by P and expanded by E, and is ready for use in the next
119*47038Sbostic  * iteration.  Two 32-bit wide tables, SPE[0] and SPE[1], are used for this
120*47038Sbostic  * lookup.  Since each byte in the 48 bit path is a multiple of four, indexed
121*47038Sbostic  * lookup of SPE[0] and SPE[1] is simple and fast.  The key schedule and
122*47038Sbostic  * "salt" are also converted to this 8*(6+2) format.  The SPE table size is
123*47038Sbostic  * 8*64*8 = 4K bytes.
124*47038Sbostic  *
125*47038Sbostic  * To speed up bit-parallel operations (such as XOR), the 8 byte
126*47038Sbostic  * representation is "union"ed with 32 bit values "i0" and "i1", and, on
127*47038Sbostic  * machines which support it, a 64 bit value "b64".  This data structure,
128*47038Sbostic  * "C_block", has two problems.  First, alignment restrictions must be
129*47038Sbostic  * honored.  Second, the byte-order (e.g. little-endian or big-endian) of
130*47038Sbostic  * the architecture becomes visible.
131*47038Sbostic  *
132*47038Sbostic  * The byte-order problem is unfortunate, since on the one hand it is good
133*47038Sbostic  * to have a machine-independent C_block representation (bits 1..8 in the
134*47038Sbostic  * first byte, etc.), and on the other hand it is good for the LSB of the
135*47038Sbostic  * first byte to be the LSB of i0.  We cannot have both these things, so we
136*47038Sbostic  * currently use the "little-endian" representation and avoid any multi-byte
137*47038Sbostic  * operations that depend on byte order.  This largely precludes use of the
138*47038Sbostic  * 64-bit datatype since the relative order of i0 and i1 are unknown.  It
139*47038Sbostic  * also inhibits grouping the SPE table to look up 12 bits at a time.  (The
140*47038Sbostic  * 12 bits can be stored in a 16-bit field with 3 low-order zeroes and 1
141*47038Sbostic  * high-order zero, providing fast indexing into a 64-bit wide SPE.) On the
142*47038Sbostic  * other hand, 64-bit datatypes are currently rare, and a 12-bit SPE lookup
143*47038Sbostic  * requires a 128 kilobyte table, so perhaps this is not a big loss.
144*47038Sbostic  *
145*47038Sbostic  * Permutation representation (Jim Gillogly):
146*47038Sbostic  *
147*47038Sbostic  * A transformation is defined by its effect on each of the 8 bytes of the
148*47038Sbostic  * 64-bit input.  For each byte we give a 64-bit output that has the bits in
149*47038Sbostic  * the input distributed appropriately.  The transformation is then the OR
150*47038Sbostic  * of the 8 sets of 64-bits.  This uses 8*256*8 = 16K bytes of storage for
151*47038Sbostic  * each transformation.  Unless LARGEDATA is defined, however, a more compact
152*47038Sbostic  * table is used which looks up 16 4-bit "chunks" rather than 8 8-bit chunks.
153*47038Sbostic  * The smaller table uses 16*16*8 = 2K bytes for each transformation.  This
154*47038Sbostic  * is slower but tolerable, particularly for password encryption in which
155*47038Sbostic  * the SPE transformation is iterated many times.  The small tables total 9K
156*47038Sbostic  * bytes, the large tables total 72K bytes.
157*47038Sbostic  *
158*47038Sbostic  * The transformations used are:
159*47038Sbostic  * IE3264: MSB->LSB conversion, initial permutation, and expansion.
160*47038Sbostic  *	This is done by collecting the 32 even-numbered bits and applying
161*47038Sbostic  *	a 32->64 bit transformation, and then collecting the 32 odd-numbered
162*47038Sbostic  *	bits and applying the same transformation.  Since there are only
163*47038Sbostic  *	32 input bits, the IE3264 transformation table is half the size of
164*47038Sbostic  *	the usual table.
165*47038Sbostic  * CF6464: Compression, final permutation, and LSB->MSB conversion.
166*47038Sbostic  *	This is done by two trivial 48->32 bit compressions to obtain
167*47038Sbostic  *	a 64-bit block (the bit numbering is given in the "CIFP" table)
168*47038Sbostic  *	followed by a 64->64 bit "cleanup" transformation.  (It would
169*47038Sbostic  *	be possible to group the bits in the 64-bit block so that 2
170*47038Sbostic  *	identical 32->32 bit transformations could be used instead,
171*47038Sbostic  *	saving a factor of 4 in space and possibly 2 in time, but
172*47038Sbostic  *	byte-ordering and other complications rear their ugly head.
173*47038Sbostic  *	Similar opportunities/problems arise in the key schedule
174*47038Sbostic  *	transforms.)
175*47038Sbostic  * PC1ROT: MSB->LSB, PC1 permutation, rotate, and PC2 permutation.
176*47038Sbostic  *	This admittedly baroque 64->64 bit transformation is used to
177*47038Sbostic  *	produce the first code (in 8*(6+2) format) of the key schedule.
178*47038Sbostic  * PC2ROT[0]: Inverse PC2 permutation, rotate, and PC2 permutation.
179*47038Sbostic  *	It would be possible to define 15 more transformations, each
180*47038Sbostic  *	with a different rotation, to generate the entire key schedule.
181*47038Sbostic  *	To save space, however, we instead permute each code into the
182*47038Sbostic  *	next by using a transformation that "undoes" the PC2 permutation,
183*47038Sbostic  *	rotates the code, and then applies PC2.  Unfortunately, PC2
184*47038Sbostic  *	transforms 56 bits into 48 bits, dropping 8 bits, so PC2 is not
185*47038Sbostic  *	invertible.  We get around that problem by using a modified PC2
186*47038Sbostic  *	which retains the 8 otherwise-lost bits in the unused low-order
187*47038Sbostic  *	bits of each byte.  The low-order bits are cleared when the
188*47038Sbostic  *	codes are stored into the key schedule.
189*47038Sbostic  * PC2ROT[1]: Same as PC2ROT[0], but with two rotations.
190*47038Sbostic  *	This is faster than applying PC2ROT[0] twice,
191*47038Sbostic  *
192*47038Sbostic  * The Bell Labs "salt" (Bob Baldwin):
193*47038Sbostic  *
194*47038Sbostic  * The salting is a simple permutation applied to the 48-bit result of E.
195*47038Sbostic  * Specifically, if bit i (1 <= i <= 24) of the salt is set then bits i and
196*47038Sbostic  * i+24 of the result are swapped.  The salt is thus a 24 bit number, with
197*47038Sbostic  * 16777216 possible values.  (The original salt was 12 bits and could not
198*47038Sbostic  * swap bits 13..24 with 36..48.)
199*47038Sbostic  *
200*47038Sbostic  * It is possible, but expensive and ugly, to warp the SPE table account for
201*47038Sbostic  * the salt permutation.  Fortunately, the conditional bit swapping requires
202*47038Sbostic  * only about four machine instructions and can be done on-the-fly with only
203*47038Sbostic  * a 2% performance penalty.
2041958Swnj  */
205*47038Sbostic typedef union {
206*47038Sbostic 	unsigned char b[8];
207*47038Sbostic 	struct {
208*47038Sbostic #if defined(LONG_IS_32_BITS)
209*47038Sbostic 		/* long is often faster than a 32-bit bit field */
210*47038Sbostic 		long	i0;
211*47038Sbostic 		long	i1;
212*47038Sbostic #else
213*47038Sbostic 		long	i0: 32;
214*47038Sbostic 		long	i1: 32;
215*47038Sbostic #endif
216*47038Sbostic 	} b32;
217*47038Sbostic #if defined(B64)
218*47038Sbostic 	B64	b64;
219*47038Sbostic #endif
220*47038Sbostic } C_block;
2211958Swnj 
2221958Swnj /*
223*47038Sbostic  * Convert twenty-four-bit long in host-order
224*47038Sbostic  * to six bits (and 2 low-order zeroes) per char little-endian format.
2251958Swnj  */
226*47038Sbostic #define	TO_SIX_BIT(rslt, src) {				\
227*47038Sbostic 		C_block cvt;				\
228*47038Sbostic 		cvt.b[0] = src; src >>= 6;		\
229*47038Sbostic 		cvt.b[1] = src; src >>= 6;		\
230*47038Sbostic 		cvt.b[2] = src; src >>= 6;		\
231*47038Sbostic 		cvt.b[3] = src;				\
232*47038Sbostic 		rslt = (cvt.b32.i0 & 0x3f3f3f3fL) << 2;	\
233*47038Sbostic 	}
2341958Swnj 
2351958Swnj /*
236*47038Sbostic  * These macros may someday permit efficient use of 64-bit integers.
23717337Sralph  */
238*47038Sbostic #define	ZERO(d,d0,d1)			d0 = 0, d1 = 0
239*47038Sbostic #define	LOAD(d,d0,d1,bl)		d0 = (bl).b32.i0, d1 = (bl).b32.i1
240*47038Sbostic #define	LOADREG(d,d0,d1,s,s0,s1)	d0 = s0, d1 = s1
241*47038Sbostic #define	OR(d,d0,d1,bl)			d0 |= (bl).b32.i0, d1 |= (bl).b32.i1
242*47038Sbostic #define	STORE(s,s0,s1,bl)		(bl).b32.i0 = s0, (bl).b32.i1 = s1
243*47038Sbostic #define	DCL_BLOCK(d,d0,d1)		long d0, d1
244*47038Sbostic 
245*47038Sbostic #if defined(LARGEDATA)
246*47038Sbostic 	/* Waste memory like crazy.  Also, do permutations in line */
247*47038Sbostic #define	LGCHUNKBITS	3
248*47038Sbostic #define	CHUNKBITS	(1<<LGCHUNKBITS)
249*47038Sbostic #define	PERM6464(d,d0,d1,cpp,p)				\
250*47038Sbostic 	LOAD(d,d0,d1,(p)[(0<<CHUNKBITS)+(cpp)[0]]);		\
251*47038Sbostic 	OR (d,d0,d1,(p)[(1<<CHUNKBITS)+(cpp)[1]]);		\
252*47038Sbostic 	OR (d,d0,d1,(p)[(2<<CHUNKBITS)+(cpp)[2]]);		\
253*47038Sbostic 	OR (d,d0,d1,(p)[(3<<CHUNKBITS)+(cpp)[3]]);		\
254*47038Sbostic 	OR (d,d0,d1,(p)[(4<<CHUNKBITS)+(cpp)[4]]);		\
255*47038Sbostic 	OR (d,d0,d1,(p)[(5<<CHUNKBITS)+(cpp)[5]]);		\
256*47038Sbostic 	OR (d,d0,d1,(p)[(6<<CHUNKBITS)+(cpp)[6]]);		\
257*47038Sbostic 	OR (d,d0,d1,(p)[(7<<CHUNKBITS)+(cpp)[7]]);
258*47038Sbostic #define	PERM3264(d,d0,d1,cpp,p)				\
259*47038Sbostic 	LOAD(d,d0,d1,(p)[(0<<CHUNKBITS)+(cpp)[0]]);		\
260*47038Sbostic 	OR (d,d0,d1,(p)[(1<<CHUNKBITS)+(cpp)[1]]);		\
261*47038Sbostic 	OR (d,d0,d1,(p)[(2<<CHUNKBITS)+(cpp)[2]]);		\
262*47038Sbostic 	OR (d,d0,d1,(p)[(3<<CHUNKBITS)+(cpp)[3]]);
263*47038Sbostic #else
264*47038Sbostic 	/* "small data" */
265*47038Sbostic #define	LGCHUNKBITS	2
266*47038Sbostic #define	CHUNKBITS	(1<<LGCHUNKBITS)
267*47038Sbostic #define	PERM6464(d,d0,d1,cpp,p)				\
268*47038Sbostic 	{ C_block tblk; permute(cpp,&tblk,p,8); LOAD (d,d0,d1,tblk); }
269*47038Sbostic #define	PERM3264(d,d0,d1,cpp,p)				\
270*47038Sbostic 	{ C_block tblk; permute(cpp,&tblk,p,4); LOAD (d,d0,d1,tblk); }
271*47038Sbostic 
272*47038Sbostic STATIC
273*47038Sbostic permute(cp, out, p, chars_in)
274*47038Sbostic 	unsigned char *cp;
275*47038Sbostic 	C_block *out;
276*47038Sbostic 	register C_block *p;
277*47038Sbostic 	int chars_in;
278*47038Sbostic {
279*47038Sbostic 	register DCL_BLOCK(D,D0,D1);
280*47038Sbostic 	register C_block *tp;
281*47038Sbostic 	register int t;
282*47038Sbostic 
283*47038Sbostic 	ZERO(D,D0,D1);
284*47038Sbostic 	do {
285*47038Sbostic 		t = *cp++;
286*47038Sbostic 		tp = &p[t&0xf]; OR(D,D0,D1,*tp); p += (1<<CHUNKBITS);
287*47038Sbostic 		tp = &p[t>>4];  OR(D,D0,D1,*tp); p += (1<<CHUNKBITS);
288*47038Sbostic 	} while (--chars_in > 0);
289*47038Sbostic 	STORE(D,D0,D1,*out);
290*47038Sbostic }
291*47038Sbostic #endif /* LARGEDATA */
292*47038Sbostic 
293*47038Sbostic 
294*47038Sbostic /* =====  (mostly) Standard DES Tables ==================== */
295*47038Sbostic 
296*47038Sbostic static unsigned char IP[] = {		/* initial permutation */
297*47038Sbostic 	58, 50, 42, 34, 26, 18, 10,  2,
298*47038Sbostic 	60, 52, 44, 36, 28, 20, 12,  4,
299*47038Sbostic 	62, 54, 46, 38, 30, 22, 14,  6,
300*47038Sbostic 	64, 56, 48, 40, 32, 24, 16,  8,
301*47038Sbostic 	57, 49, 41, 33, 25, 17,  9,  1,
302*47038Sbostic 	59, 51, 43, 35, 27, 19, 11,  3,
303*47038Sbostic 	61, 53, 45, 37, 29, 21, 13,  5,
304*47038Sbostic 	63, 55, 47, 39, 31, 23, 15,  7,
30517337Sralph };
30617337Sralph 
307*47038Sbostic /* The final permutation is the inverse of IP - no table is necessary */
308*47038Sbostic 
309*47038Sbostic static unsigned char ExpandTr[] = {	/* expansion operation */
310*47038Sbostic 	32,  1,  2,  3,  4,  5,
311*47038Sbostic 	 4,  5,  6,  7,  8,  9,
312*47038Sbostic 	 8,  9, 10, 11, 12, 13,
313*47038Sbostic 	12, 13, 14, 15, 16, 17,
314*47038Sbostic 	16, 17, 18, 19, 20, 21,
315*47038Sbostic 	20, 21, 22, 23, 24, 25,
316*47038Sbostic 	24, 25, 26, 27, 28, 29,
317*47038Sbostic 	28, 29, 30, 31, 32,  1,
318*47038Sbostic };
319*47038Sbostic 
320*47038Sbostic static unsigned char PC1[] = {		/* permuted choice table (key)  */
321*47038Sbostic 	57, 49, 41, 33, 25, 17,  9,
322*47038Sbostic 	 1, 58, 50, 42, 34, 26, 18,
323*47038Sbostic 	10,  2, 59, 51, 43, 35, 27,
324*47038Sbostic 	19, 11,  3, 60, 52, 44, 36,
325*47038Sbostic 
326*47038Sbostic 	63, 55, 47, 39, 31, 23, 15,
327*47038Sbostic 	 7, 62, 54, 46, 38, 30, 22,
328*47038Sbostic 	14,  6, 61, 53, 45, 37, 29,
329*47038Sbostic 	21, 13,  5, 28, 20, 12,  4,
330*47038Sbostic };
331*47038Sbostic 
332*47038Sbostic static unsigned char Rotates[] = {	/* number of rotations of PC1 */
333*47038Sbostic 	1, 1, 2, 2, 2, 2, 2, 2, 1, 2, 2, 2, 2, 2, 2, 1,
334*47038Sbostic };
335*47038Sbostic 
336*47038Sbostic /* note: each "row" of PC2 is left-padded with bits that make it invertible */
337*47038Sbostic static unsigned char PC2[] = {		/* permuted choice key (table)  */
338*47038Sbostic 	 9, 18,    14, 17, 11, 24,  1,  5,
339*47038Sbostic 	22, 25,     3, 28, 15,  6, 21, 10,
340*47038Sbostic 	35, 38,    23, 19, 12,  4, 26,  8,
341*47038Sbostic 	43, 54,    16,  7, 27, 20, 13,  2,
342*47038Sbostic 
343*47038Sbostic 	 0,  0,    41, 52, 31, 37, 47, 55,
344*47038Sbostic 	 0,  0,    30, 40, 51, 45, 33, 48,
345*47038Sbostic 	 0,  0,    44, 49, 39, 56, 34, 53,
346*47038Sbostic 	 0,  0,    46, 42, 50, 36, 29, 32,
347*47038Sbostic };
348*47038Sbostic 
349*47038Sbostic static unsigned char S[8][64] = {	/* 48->32 bit substitution tables */
350*47038Sbostic 					/* S[1]			*/
351*47038Sbostic 	14,  4, 13,  1,  2, 15, 11,  8,  3, 10,  6, 12,  5,  9,  0,  7,
352*47038Sbostic 	 0, 15,  7,  4, 14,  2, 13,  1, 10,  6, 12, 11,  9,  5,  3,  8,
353*47038Sbostic 	 4,  1, 14,  8, 13,  6,  2, 11, 15, 12,  9,  7,  3, 10,  5,  0,
354*47038Sbostic 	15, 12,  8,  2,  4,  9,  1,  7,  5, 11,  3, 14, 10,  0,  6, 13,
355*47038Sbostic 					/* S[2]			*/
356*47038Sbostic 	15,  1,  8, 14,  6, 11,  3,  4,  9,  7,  2, 13, 12,  0,  5, 10,
357*47038Sbostic 	 3, 13,  4,  7, 15,  2,  8, 14, 12,  0,  1, 10,  6,  9, 11,  5,
358*47038Sbostic 	 0, 14,  7, 11, 10,  4, 13,  1,  5,  8, 12,  6,  9,  3,  2, 15,
359*47038Sbostic 	13,  8, 10,  1,  3, 15,  4,  2, 11,  6,  7, 12,  0,  5, 14,  9,
360*47038Sbostic 					/* S[3]			*/
361*47038Sbostic 	10,  0,  9, 14,  6,  3, 15,  5,  1, 13, 12,  7, 11,  4,  2,  8,
362*47038Sbostic 	13,  7,  0,  9,  3,  4,  6, 10,  2,  8,  5, 14, 12, 11, 15,  1,
363*47038Sbostic 	13,  6,  4,  9,  8, 15,  3,  0, 11,  1,  2, 12,  5, 10, 14,  7,
364*47038Sbostic 	 1, 10, 13,  0,  6,  9,  8,  7,  4, 15, 14,  3, 11,  5,  2, 12,
365*47038Sbostic 					/* S[4]			*/
366*47038Sbostic 	 7, 13, 14,  3,  0,  6,  9, 10,  1,  2,  8,  5, 11, 12,  4, 15,
367*47038Sbostic 	13,  8, 11,  5,  6, 15,  0,  3,  4,  7,  2, 12,  1, 10, 14,  9,
368*47038Sbostic 	10,  6,  9,  0, 12, 11,  7, 13, 15,  1,  3, 14,  5,  2,  8,  4,
369*47038Sbostic 	 3, 15,  0,  6, 10,  1, 13,  8,  9,  4,  5, 11, 12,  7,  2, 14,
370*47038Sbostic 					/* S[5]			*/
371*47038Sbostic 	 2, 12,  4,  1,  7, 10, 11,  6,  8,  5,  3, 15, 13,  0, 14,  9,
372*47038Sbostic 	14, 11,  2, 12,  4,  7, 13,  1,  5,  0, 15, 10,  3,  9,  8,  6,
373*47038Sbostic 	 4,  2,  1, 11, 10, 13,  7,  8, 15,  9, 12,  5,  6,  3,  0, 14,
374*47038Sbostic 	11,  8, 12,  7,  1, 14,  2, 13,  6, 15,  0,  9, 10,  4,  5,  3,
375*47038Sbostic 					/* S[6]			*/
376*47038Sbostic 	12,  1, 10, 15,  9,  2,  6,  8,  0, 13,  3,  4, 14,  7,  5, 11,
377*47038Sbostic 	10, 15,  4,  2,  7, 12,  9,  5,  6,  1, 13, 14,  0, 11,  3,  8,
378*47038Sbostic 	 9, 14, 15,  5,  2,  8, 12,  3,  7,  0,  4, 10,  1, 13, 11,  6,
379*47038Sbostic 	 4,  3,  2, 12,  9,  5, 15, 10, 11, 14,  1,  7,  6,  0,  8, 13,
380*47038Sbostic 					/* S[7]			*/
381*47038Sbostic 	 4, 11,  2, 14, 15,  0,  8, 13,  3, 12,  9,  7,  5, 10,  6,  1,
382*47038Sbostic 	13,  0, 11,  7,  4,  9,  1, 10, 14,  3,  5, 12,  2, 15,  8,  6,
383*47038Sbostic 	 1,  4, 11, 13, 12,  3,  7, 14, 10, 15,  6,  8,  0,  5,  9,  2,
384*47038Sbostic 	 6, 11, 13,  8,  1,  4, 10,  7,  9,  5,  0, 15, 14,  2,  3, 12,
385*47038Sbostic 					/* S[8]			*/
386*47038Sbostic 	13,  2,  8,  4,  6, 15, 11,  1, 10,  9,  3, 14,  5,  0, 12,  7,
387*47038Sbostic 	 1, 15, 13,  8, 10,  3,  7,  4, 12,  5,  6, 11,  0, 14,  9,  2,
388*47038Sbostic 	 7, 11,  4,  1,  9, 12, 14,  2,  0,  6, 10, 13, 15,  3,  5,  8,
389*47038Sbostic 	 2,  1, 14,  7,  4, 10,  8, 13, 15, 12,  9,  0,  3,  5,  6, 11,
390*47038Sbostic };
391*47038Sbostic 
392*47038Sbostic static unsigned char P32Tr[] = {	/* 32-bit permutation function */
393*47038Sbostic 	16,  7, 20, 21,
394*47038Sbostic 	29, 12, 28, 17,
395*47038Sbostic 	 1, 15, 23, 26,
396*47038Sbostic 	 5, 18, 31, 10,
397*47038Sbostic 	 2,  8, 24, 14,
398*47038Sbostic 	32, 27,  3,  9,
399*47038Sbostic 	19, 13, 30,  6,
400*47038Sbostic 	22, 11,  4, 25,
401*47038Sbostic };
402*47038Sbostic 
403*47038Sbostic static unsigned char CIFP[] = {		/* compressed/interleaved permutation */
404*47038Sbostic 	 1,  2,  3,  4,   17, 18, 19, 20,
405*47038Sbostic 	 5,  6,  7,  8,   21, 22, 23, 24,
406*47038Sbostic 	 9, 10, 11, 12,   25, 26, 27, 28,
407*47038Sbostic 	13, 14, 15, 16,   29, 30, 31, 32,
408*47038Sbostic 
409*47038Sbostic 	33, 34, 35, 36,   49, 50, 51, 52,
410*47038Sbostic 	37, 38, 39, 40,   53, 54, 55, 56,
411*47038Sbostic 	41, 42, 43, 44,   57, 58, 59, 60,
412*47038Sbostic 	45, 46, 47, 48,   61, 62, 63, 64,
413*47038Sbostic };
414*47038Sbostic 
415*47038Sbostic static unsigned char itoa64[] =		/* 0..63 => ascii-64 */
416*47038Sbostic 	"./0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz";
417*47038Sbostic 
418*47038Sbostic 
419*47038Sbostic /* =====  Tables that are initialized at run time  ==================== */
420*47038Sbostic 
421*47038Sbostic 
422*47038Sbostic static unsigned char a64toi[128];	/* ascii-64 => 0..63 */
423*47038Sbostic 
424*47038Sbostic /* Initial key schedule permutation */
425*47038Sbostic static C_block	PC1ROT[64/CHUNKBITS][1<<CHUNKBITS];
426*47038Sbostic 
427*47038Sbostic /* Subsequent key schedule rotation permutations */
428*47038Sbostic static C_block	PC2ROT[2][64/CHUNKBITS][1<<CHUNKBITS];
429*47038Sbostic 
430*47038Sbostic /* Initial permutation/expansion table */
431*47038Sbostic static C_block	IE3264[32/CHUNKBITS][1<<CHUNKBITS];
432*47038Sbostic 
433*47038Sbostic /* Table that combines the S, P, and E operations.  */
434*47038Sbostic static long SPE[2][8][64];
435*47038Sbostic 
436*47038Sbostic /* compressed/interleaved => final permutation table */
437*47038Sbostic static C_block	CF6464[64/CHUNKBITS][1<<CHUNKBITS];
438*47038Sbostic 
439*47038Sbostic 
440*47038Sbostic /* ==================================== */
441*47038Sbostic 
442*47038Sbostic 
443*47038Sbostic static C_block	constdatablock;			/* encryption constant */
444*47038Sbostic static char	cryptresult[1+4+4+11+1];	/* encrypted result */
445*47038Sbostic 
44617337Sralph /*
447*47038Sbostic  * XXX need comment
4481958Swnj  */
449*47038Sbostic char *
450*47038Sbostic crypt(key, setting)
451*47038Sbostic 	register const char *key;
452*47038Sbostic 	register const char *setting;
4531958Swnj {
454*47038Sbostic 	register char *encp;
455*47038Sbostic 	register long i;
456*47038Sbostic 	long salt;
457*47038Sbostic 	int num_iter, salt_size, key_size;
458*47038Sbostic 	C_block keyblock, rsltblock;
4591958Swnj 
460*47038Sbostic 	for (i = 0; i < 8; i++)
461*47038Sbostic 		if ((keyblock.b[i] = 2*(unsigned char)(*key)) != 0)
462*47038Sbostic 			key++;
463*47038Sbostic 	des_setkey((char *)keyblock.b);	/* also initializes "a64toi" */
464*47038Sbostic 
465*47038Sbostic 	encp = &cryptresult[0];
466*47038Sbostic 	if (*setting != '_') {	/* old style */
467*47038Sbostic 		num_iter = 25;
468*47038Sbostic 		salt_size = 2;
469*47038Sbostic 		key_size = 8;
470*47038Sbostic 	}
471*47038Sbostic 	else {			/* new style */
472*47038Sbostic 		*encp++ = *setting++;
473*47038Sbostic 
474*47038Sbostic 		/* get iteration count */
475*47038Sbostic 		num_iter = 0;
476*47038Sbostic 		for (i = 4; --i >= 0; ) {
477*47038Sbostic 			num_iter = (num_iter<<6) |
478*47038Sbostic 				a64toi[(unsigned char)
479*47038Sbostic 					(encp[i] = (unsigned char)setting[i])];
480*47038Sbostic 		}
481*47038Sbostic 		setting += 4;
482*47038Sbostic 		encp += 4;
483*47038Sbostic 		salt_size = 4;
484*47038Sbostic 		key_size = 128;
485*47038Sbostic 	}
486*47038Sbostic 
487*47038Sbostic 	salt = 0;
488*47038Sbostic 	for (i = salt_size; --i >= 0; ) {
489*47038Sbostic 		salt = (salt<<6) |
490*47038Sbostic 			a64toi[(unsigned char)
491*47038Sbostic 				(encp[i] = (unsigned char)setting[i])];
492*47038Sbostic 	}
493*47038Sbostic 	encp += salt_size;
494*47038Sbostic 	des_cipher((char *)&constdatablock, (char *)&rsltblock, salt, num_iter);
495*47038Sbostic 
4961958Swnj 	/*
497*47038Sbostic 	 * encrypt the remainder of the password 8 characters at a time.
4981958Swnj 	 */
499*47038Sbostic 	while ((key_size -= 8) > 0 && *key) {
500*47038Sbostic 		C_block xdatablock;
501*47038Sbostic 
502*47038Sbostic 		for (i = 0; i < 8; i++)
503*47038Sbostic 			if ((keyblock.b[i] = 2*(unsigned char)(*key)) != 0)
504*47038Sbostic 				key++;
505*47038Sbostic 			else
506*47038Sbostic 				break;	/* pad out with previous key */
507*47038Sbostic 		des_setkey((char *)keyblock.b);
508*47038Sbostic 		des_cipher((char *)&constdatablock, (char *)&xdatablock, 0L, 1);
509*47038Sbostic 		rsltblock.b32.i0 ^= xdatablock.b32.i0;
510*47038Sbostic 		rsltblock.b32.i1 ^= xdatablock.b32.i1;
5111958Swnj 	}
512*47038Sbostic 
5131958Swnj 	/*
514*47038Sbostic 	 * Encode the 64 cipher bits as 11 ascii characters.
5151958Swnj 	 */
516*47038Sbostic 	i = ((long)((rsltblock.b[0]<<8) | rsltblock.b[1])<<8) | rsltblock.b[2];
517*47038Sbostic 	encp[3] = itoa64[i&0x3f];	i >>= 6;
518*47038Sbostic 	encp[2] = itoa64[i&0x3f];	i >>= 6;
519*47038Sbostic 	encp[1] = itoa64[i&0x3f];	i >>= 6;
520*47038Sbostic 	encp[0] = itoa64[i];		encp += 4;
521*47038Sbostic 	i = ((long)((rsltblock.b[3]<<8) | rsltblock.b[4])<<8) | rsltblock.b[5];
522*47038Sbostic 	encp[3] = itoa64[i&0x3f];	i >>= 6;
523*47038Sbostic 	encp[2] = itoa64[i&0x3f];	i >>= 6;
524*47038Sbostic 	encp[1] = itoa64[i&0x3f];	i >>= 6;
525*47038Sbostic 	encp[0] = itoa64[i];		encp += 4;
526*47038Sbostic 	i = ((long)((rsltblock.b[6])<<8) | rsltblock.b[7])<<2;
527*47038Sbostic 	encp[2] = itoa64[i&0x3f];	i >>= 6;
528*47038Sbostic 	encp[1] = itoa64[i&0x3f];	i >>= 6;
529*47038Sbostic 	encp[0] = itoa64[i];
530*47038Sbostic 
531*47038Sbostic 	encp[3] = 0;
532*47038Sbostic 	return(cryptresult);
533*47038Sbostic }
534*47038Sbostic 
535*47038Sbostic 
536*47038Sbostic /*
537*47038Sbostic  * The Key Schedule, filled in by des_setkey() or setkey().
538*47038Sbostic  */
539*47038Sbostic #define	KS_SIZE	16
540*47038Sbostic static C_block	KS[KS_SIZE];
541*47038Sbostic 
542*47038Sbostic /*
543*47038Sbostic  * Set up the key schedule from the key.
544*47038Sbostic  */
545*47038Sbostic void
546*47038Sbostic des_setkey(key)
547*47038Sbostic 	register const char *key;
548*47038Sbostic {
549*47038Sbostic 	register DCL_BLOCK(K, K0, K1);
550*47038Sbostic 	register C_block *ptabp;
551*47038Sbostic 	register int i;
552*47038Sbostic 	static int des_ready = 0;
553*47038Sbostic 
554*47038Sbostic 	if (!des_ready) {
555*47038Sbostic 		init_des();
556*47038Sbostic 		des_ready = 1;
5571958Swnj 	}
55817337Sralph 
559*47038Sbostic 	PERM6464(K,K0,K1,(unsigned char *)key,(C_block *)PC1ROT);
560*47038Sbostic 	key = (char *)&KS[0];
561*47038Sbostic 	STORE(K&0xfcfcfcfcL, K0&0xfcfcfcfcL, K1, *(C_block *)key);
562*47038Sbostic 	for (i = 1; i < 16; i++) {
563*47038Sbostic 		key += sizeof(C_block);
564*47038Sbostic 		STORE(K,K0,K1,*(C_block *)key);
565*47038Sbostic 		ptabp = (C_block *)PC2ROT[Rotates[i]-1];
566*47038Sbostic 		PERM6464(K,K0,K1,(unsigned char *)key,ptabp);
567*47038Sbostic 		STORE(K&0xfcfcfcfcL, K0&0xfcfcfcfcL, K1, *(C_block *)key);
568*47038Sbostic 	}
5691958Swnj }
5701958Swnj 
5711958Swnj /*
572*47038Sbostic  * Encrypt (or decrypt if num_iter < 0) the 8 chars at "in" with abs(num_iter)
573*47038Sbostic  * iterations of DES, using the the given 24-bit salt and the pre-computed key
574*47038Sbostic  * schedule, and store the resulting 8 chars at "out" (in == out is permitted).
575*47038Sbostic  *
576*47038Sbostic  * NOTE: the performance of this routine is critically dependent on your
577*47038Sbostic  * compiler and machine architecture.
5781958Swnj  */
579*47038Sbostic void
580*47038Sbostic des_cipher(in, out, salt, num_iter)
581*47038Sbostic 	const char *in;
582*47038Sbostic 	char *out;
583*47038Sbostic 	u_long salt;
584*47038Sbostic 	int num_iter;
585*47038Sbostic {
586*47038Sbostic 	/* variables that we want in registers, most important first */
587*47038Sbostic #if defined(pdp11)
588*47038Sbostic 	register int j;
589*47038Sbostic #endif
590*47038Sbostic 	register long L0, L1, R0, R1, k;
591*47038Sbostic 	register C_block *kp;
592*47038Sbostic 	register int ks_inc, loop_count;
593*47038Sbostic 	C_block B;
5941958Swnj 
595*47038Sbostic 	L0 = salt;
596*47038Sbostic 	TO_SIX_BIT(salt, L0);	/* convert to 8*(6+2) format */
5971958Swnj 
598*47038Sbostic #if defined(vax) || defined(pdp11)
599*47038Sbostic 	salt = ~salt;	/* "x &~ y" is faster than "x & y". */
600*47038Sbostic #define	SALT (~salt)
601*47038Sbostic #else
602*47038Sbostic #define	SALT salt
603*47038Sbostic #endif
6041958Swnj 
605*47038Sbostic #if defined(MUST_ALIGN)
606*47038Sbostic 	B.b[0] = in[0]; B.b[1] = in[1]; B.b[2] = in[2]; B.b[3] = in[3];
607*47038Sbostic 	B.b[4] = in[4]; B.b[5] = in[5]; B.b[6] = in[6]; B.b[7] = in[7];
608*47038Sbostic 	LOAD(L,L0,L1,B);
609*47038Sbostic #else
610*47038Sbostic 	LOAD(L,L0,L1,*(C_block *)in);
611*47038Sbostic #endif
612*47038Sbostic 	LOADREG(R,R0,R1,L,L0,L1);
613*47038Sbostic 	L0 &= 0x55555555L;
614*47038Sbostic 	L1 &= 0x55555555L;
615*47038Sbostic 	L0 = (L0 << 1) | L1;	/* L0 is the even-numbered input bits */
616*47038Sbostic 	R0 &= 0xaaaaaaaaL;
617*47038Sbostic 	R1 = (R1 >> 1) & 0x55555555L;
618*47038Sbostic 	L1 = R0 | R1;		/* L1 is the odd-numbered input bits */
619*47038Sbostic 	STORE(L,L0,L1,B);
620*47038Sbostic 	PERM3264(L,L0,L1,B.b,  (C_block *)IE3264);	/* even bits */
621*47038Sbostic 	PERM3264(R,R0,R1,B.b+4,(C_block *)IE3264);	/* odd bits */
6221958Swnj 
623*47038Sbostic 	if (num_iter >= 0)
624*47038Sbostic 	{		/* encryption */
625*47038Sbostic 		kp = &KS[0];
626*47038Sbostic 		ks_inc  = sizeof(*kp);
627*47038Sbostic 	}
628*47038Sbostic 	else
629*47038Sbostic 	{		/* decryption */
630*47038Sbostic 		num_iter = -num_iter;
631*47038Sbostic 		kp = &KS[KS_SIZE-1];
632*47038Sbostic 		ks_inc  = -sizeof(*kp);
633*47038Sbostic 	}
6341958Swnj 
635*47038Sbostic 	while (--num_iter >= 0) {
636*47038Sbostic 		loop_count = 8;
637*47038Sbostic 		do {
6381958Swnj 
639*47038Sbostic #define	BTAB(i)		(((unsigned char *)&B.b[0])[i])
640*47038Sbostic #define	SPTAB(t, i)	(*(long *)((unsigned char *)t \
641*47038Sbostic 				+ i*(sizeof(long)/4)))
642*47038Sbostic #if defined(gould)
643*47038Sbostic 			/* use this if BTAB(i) is evaluated just once ... */
644*47038Sbostic #define	DOXOR(a,b,i)	a^=SPTAB(SPE[0][i],BTAB(i));b^=SPTAB(SPE[1][i],BTAB(i));
645*47038Sbostic #else
646*47038Sbostic #if defined(pdp11)
647*47038Sbostic 			/* use this if your "long" int indexing is slow */
648*47038Sbostic #define	DOXOR(a,b,i)	j=BTAB(i); a^=SPTAB(SPE[0][i],j); b^=SPTAB(SPE[1][i],j);
649*47038Sbostic #else
650*47038Sbostic 			/* use this if "k" is allocated to a register ... */
651*47038Sbostic #define	DOXOR(a,b,i)	k=BTAB(i); a^=SPTAB(SPE[0][i],k); b^=SPTAB(SPE[1][i],k);
652*47038Sbostic #endif
653*47038Sbostic #endif
6541958Swnj 
655*47038Sbostic #define	CRUNCH(L0, L1, R0, R1)	\
656*47038Sbostic 			k = (R0 ^ R1) & SALT;	\
657*47038Sbostic 			B.b32.i0 = k ^ R0 ^ kp->b32.i0;		\
658*47038Sbostic 			B.b32.i1 = k ^ R1 ^ kp->b32.i1;		\
659*47038Sbostic 			kp = (C_block *)((char *)kp+ks_inc);	\
660*47038Sbostic 							\
661*47038Sbostic 			DOXOR(L0, L1, 0);		\
662*47038Sbostic 			DOXOR(L0, L1, 1);		\
663*47038Sbostic 			DOXOR(L0, L1, 2);		\
664*47038Sbostic 			DOXOR(L0, L1, 3);		\
665*47038Sbostic 			DOXOR(L0, L1, 4);		\
666*47038Sbostic 			DOXOR(L0, L1, 5);		\
667*47038Sbostic 			DOXOR(L0, L1, 6);		\
668*47038Sbostic 			DOXOR(L0, L1, 7);
6691958Swnj 
670*47038Sbostic 			CRUNCH(L0, L1, R0, R1);
671*47038Sbostic 			CRUNCH(R0, R1, L0, L1);
672*47038Sbostic 		} while (--loop_count != 0);
673*47038Sbostic 		kp = (C_block *)((char *)kp-(ks_inc*KS_SIZE));
6741958Swnj 
6751958Swnj 
676*47038Sbostic 		/* swap L and R */
677*47038Sbostic 		L0 ^= R0;  L1 ^= R1;
678*47038Sbostic 		R0 ^= L0;  R1 ^= L1;
679*47038Sbostic 		L0 ^= R0;  L1 ^= R1;
680*47038Sbostic 	}
6811958Swnj 
682*47038Sbostic 	/* store the encrypted (or decrypted) result */
683*47038Sbostic 	L0 = ((L0 >> 3) & 0x0f0f0f0fL) | ((L1 << 1) & 0xf0f0f0f0L);
684*47038Sbostic 	L1 = ((R0 >> 3) & 0x0f0f0f0fL) | ((R1 << 1) & 0xf0f0f0f0L);
685*47038Sbostic 	STORE(L,L0,L1,B);
686*47038Sbostic 	PERM6464(L,L0,L1,B.b, (C_block *)CF6464);
687*47038Sbostic #if defined(MUST_ALIGN)
688*47038Sbostic 	STORE(L,L0,L1,B);
689*47038Sbostic 	out[0] = B.b[0]; out[1] = B.b[1]; out[2] = B.b[2]; out[3] = B.b[3];
690*47038Sbostic 	out[4] = B.b[4]; out[5] = B.b[5]; out[6] = B.b[6]; out[7] = B.b[7];
691*47038Sbostic #else
692*47038Sbostic 	STORE(L,L0,L1,*(C_block *)out);
693*47038Sbostic #endif
694*47038Sbostic }
695*47038Sbostic 
696*47038Sbostic 
6971958Swnj /*
698*47038Sbostic  * Initialize various tables.  This need only be done once.  It could even be
699*47038Sbostic  * done at compile time, if the compiler were capable of that sort of thing.
7001958Swnj  */
701*47038Sbostic STATIC
702*47038Sbostic init_des()
7031958Swnj {
704*47038Sbostic 	register int i, j;
705*47038Sbostic 	register long k;
706*47038Sbostic 	register int tableno;
707*47038Sbostic 	static unsigned char perm[64], tmp32[32];	/* "static" for speed */
7081958Swnj 
7091958Swnj 	/*
710*47038Sbostic 	 * table that converts chars "./0-9A-Za-z"to integers 0-63.
7111958Swnj 	 */
712*47038Sbostic 	for (i = 0; i < 64; i++)
713*47038Sbostic 		a64toi[itoa64[i]] = i;
714*47038Sbostic 
7151958Swnj 	/*
716*47038Sbostic 	 * PC1ROT - bit reverse, then PC1, then Rotate, then PC2.
7171958Swnj 	 */
718*47038Sbostic 	for (i = 0; i < 64; i++)
719*47038Sbostic 		perm[i] = 0;
720*47038Sbostic 	for (i = 0; i < 64; i++) {
721*47038Sbostic 		if ((k = PC2[i]) == 0)
722*47038Sbostic 			continue;
723*47038Sbostic 		k += Rotates[0]-1;
724*47038Sbostic 		if ((k%28) < Rotates[0]) k -= 28;
725*47038Sbostic 		k = PC1[k];
726*47038Sbostic 		if (k > 0) {
727*47038Sbostic 			k--;
728*47038Sbostic 			k = (k|07) - (k&07);
729*47038Sbostic 			k++;
7301958Swnj 		}
731*47038Sbostic 		perm[i] = k;
7321958Swnj 	}
733*47038Sbostic #ifdef DEBUG
734*47038Sbostic 	prtab("pc1tab", perm, 8);
735*47038Sbostic #endif
736*47038Sbostic 	perminit(PC1ROT, perm, 8, 8);
737*47038Sbostic 
7381958Swnj 	/*
739*47038Sbostic 	 * PC2ROT - PC2 inverse, then Rotate (once or twice), then PC2.
7401958Swnj 	 */
741*47038Sbostic 	for (j = 0; j < 2; j++) {
742*47038Sbostic 		unsigned char pc2inv[64];
743*47038Sbostic 		for (i = 0; i < 64; i++)
744*47038Sbostic 			perm[i] = pc2inv[i] = 0;
745*47038Sbostic 		for (i = 0; i < 64; i++) {
746*47038Sbostic 			if ((k = PC2[i]) == 0)
747*47038Sbostic 				continue;
748*47038Sbostic 			pc2inv[k-1] = i+1;
749*47038Sbostic 		}
750*47038Sbostic 		for (i = 0; i < 64; i++) {
751*47038Sbostic 			if ((k = PC2[i]) == 0)
752*47038Sbostic 				continue;
753*47038Sbostic 			k += j;
754*47038Sbostic 			if ((k%28) <= j) k -= 28;
755*47038Sbostic 			perm[i] = pc2inv[k];
756*47038Sbostic 		}
757*47038Sbostic #ifdef DEBUG
758*47038Sbostic 		prtab("pc2tab", perm, 8);
759*47038Sbostic #endif
760*47038Sbostic 		perminit(PC2ROT[j], perm, 8, 8);
7611958Swnj 	}
762*47038Sbostic 
7631958Swnj 	/*
764*47038Sbostic 	 * Bit reverse, then initial permutation, then expansion.
7651958Swnj 	 */
766*47038Sbostic 	for (i = 0; i < 8; i++) {
767*47038Sbostic 		for (j = 0; j < 8; j++) {
768*47038Sbostic 			k = (j < 2)? 0: IP[ExpandTr[i*6+j-2]-1];
769*47038Sbostic 			if (k > 32)
770*47038Sbostic 				k -= 32;
771*47038Sbostic 			else if (k > 0)
772*47038Sbostic 				k--;
773*47038Sbostic 			if (k > 0) {
774*47038Sbostic 				k--;
775*47038Sbostic 				k = (k|07) - (k&07);
776*47038Sbostic 				k++;
777*47038Sbostic 			}
778*47038Sbostic 			perm[i*8+j] = k;
779*47038Sbostic 		}
780*47038Sbostic 	}
781*47038Sbostic #ifdef DEBUG
782*47038Sbostic 	prtab("ietab", perm, 8);
783*47038Sbostic #endif
784*47038Sbostic 	perminit(IE3264, perm, 4, 8);
785*47038Sbostic 
786*47038Sbostic 	/*
787*47038Sbostic 	 * Compression, then final permutation, then bit reverse.
788*47038Sbostic 	 */
789*47038Sbostic 	for (i = 0; i < 64; i++) {
790*47038Sbostic 		k = IP[CIFP[i]-1];
791*47038Sbostic 		if (k > 0) {
792*47038Sbostic 			k--;
793*47038Sbostic 			k = (k|07) - (k&07);
794*47038Sbostic 			k++;
795*47038Sbostic 		}
796*47038Sbostic 		perm[k-1] = i+1;
797*47038Sbostic 	}
798*47038Sbostic #ifdef DEBUG
799*47038Sbostic 	prtab("cftab", perm, 8);
800*47038Sbostic #endif
801*47038Sbostic 	perminit(CF6464, perm, 8, 8);
802*47038Sbostic 
803*47038Sbostic 	/*
804*47038Sbostic 	 * SPE table
805*47038Sbostic 	 */
806*47038Sbostic 	for (i = 0; i < 48; i++)
807*47038Sbostic 		perm[i] = P32Tr[ExpandTr[i]-1];
808*47038Sbostic 	for (tableno = 0; tableno < 8; tableno++) {
809*47038Sbostic 		for (j = 0; j < 64; j++)  {
810*47038Sbostic 			k = (((j >> 0) &01) << 5)|
811*47038Sbostic 			    (((j >> 1) &01) << 3)|
812*47038Sbostic 			    (((j >> 2) &01) << 2)|
813*47038Sbostic 			    (((j >> 3) &01) << 1)|
814*47038Sbostic 			    (((j >> 4) &01) << 0)|
815*47038Sbostic 			    (((j >> 5) &01) << 4);
816*47038Sbostic 			k = S[tableno][k];
817*47038Sbostic 			k = (((k >> 3)&01) << 0)|
818*47038Sbostic 			    (((k >> 2)&01) << 1)|
819*47038Sbostic 			    (((k >> 1)&01) << 2)|
820*47038Sbostic 			    (((k >> 0)&01) << 3);
821*47038Sbostic 			for (i = 0; i < 32; i++)
822*47038Sbostic 				tmp32[i] = 0;
823*47038Sbostic 			for (i = 0; i < 4; i++)
824*47038Sbostic 				tmp32[4 * tableno + i] = (k >> i) & 01;
825*47038Sbostic 			k = 0;
826*47038Sbostic 			for (i = 24; --i >= 0; )
827*47038Sbostic 				k = (k<<1) | tmp32[perm[i]-1];
828*47038Sbostic 			TO_SIX_BIT(SPE[0][tableno][j], k);
829*47038Sbostic 			k = 0;
830*47038Sbostic 			for (i = 24; --i >= 0; )
831*47038Sbostic 				k = (k<<1) | tmp32[perm[i+24]-1];
832*47038Sbostic 			TO_SIX_BIT(SPE[1][tableno][j], k);
833*47038Sbostic 		}
834*47038Sbostic 	}
8351958Swnj }
8361958Swnj 
837*47038Sbostic 
838*47038Sbostic /*
839*47038Sbostic  * XXX need comment
840*47038Sbostic  * "perm" must be all-zeroes on entry to this routine.
841*47038Sbostic  */
842*47038Sbostic STATIC
843*47038Sbostic perminit(perm, p, chars_in, chars_out)
844*47038Sbostic 	C_block perm[64/CHUNKBITS][1<<CHUNKBITS];
845*47038Sbostic 	unsigned char p[64];
846*47038Sbostic 	int chars_in, chars_out;
8471958Swnj {
848*47038Sbostic 	register int i, j, k, l;
84917337Sralph 
850*47038Sbostic 	for (k = 0; k < chars_out*8; k++) {	/* each output bit position */
851*47038Sbostic 		l = p[k] - 1;		/* where this bit comes from */
852*47038Sbostic 		if (l < 0)
853*47038Sbostic 			continue;	/* output bit is always 0 */
854*47038Sbostic 		i = l>>LGCHUNKBITS;	/* which chunk this bit comes from */
855*47038Sbostic 		l = 1<<(l&(CHUNKBITS-1));	/* mask for this bit */
856*47038Sbostic 		for (j = 0; j < (1<<CHUNKBITS); j++) {	/* each chunk value */
857*47038Sbostic 			if ((j & l) != 0)
858*47038Sbostic 				perm[i][j].b[k>>3] |= 1<<(k&07);
859*47038Sbostic 		}
8601958Swnj 	}
861*47038Sbostic }
8621958Swnj 
863*47038Sbostic /*
864*47038Sbostic  * "setkey" routine (for backwards compatibility)
865*47038Sbostic  */
866*47038Sbostic void
867*47038Sbostic setkey(key)
868*47038Sbostic 	register const char *key;
869*47038Sbostic {
870*47038Sbostic 	register int i, j, k;
871*47038Sbostic 	C_block keyblock;
872*47038Sbostic 
873*47038Sbostic 	for (i = 0; i < 8; i++) {
874*47038Sbostic 		k = 0;
875*47038Sbostic 		for (j = 0; j < 8; j++) {
876*47038Sbostic 			k <<= 1;
877*47038Sbostic 			k |= (unsigned char)*key++;
8781958Swnj 		}
879*47038Sbostic 		keyblock.b[i] = k;
8801958Swnj 	}
881*47038Sbostic 	des_setkey((char *)keyblock.b);
8821958Swnj }
883*47038Sbostic 
884*47038Sbostic /*
885*47038Sbostic  * "encrypt" routine (for backwards compatibility)
886*47038Sbostic  */
887*47038Sbostic void
888*47038Sbostic encrypt(block, flag)
889*47038Sbostic 	register char *block;
890*47038Sbostic 	int flag;
891*47038Sbostic {
892*47038Sbostic 	register int i, j, k;
893*47038Sbostic 	C_block cblock;
894*47038Sbostic 
895*47038Sbostic 	for (i = 0; i < 8; i++) {
896*47038Sbostic 		k = 0;
897*47038Sbostic 		for (j = 0; j < 8; j++) {
898*47038Sbostic 			k <<= 1;
899*47038Sbostic 			k |= (unsigned char)*block++;
900*47038Sbostic 		}
901*47038Sbostic 		cblock.b[i] = k;
902*47038Sbostic 	}
903*47038Sbostic 	des_cipher((char *)&cblock, (char *)&cblock, 0L, (flag? -1: 1));
904*47038Sbostic 	for (i = 7; i >= 0; i--) {
905*47038Sbostic 		k = cblock.b[i];
906*47038Sbostic 		for (j = 7; j >= 0; j--) {
907*47038Sbostic 			*--block = k&01;
908*47038Sbostic 			k >>= 1;
909*47038Sbostic 		}
910*47038Sbostic 	}
911*47038Sbostic }
912*47038Sbostic 
913*47038Sbostic #ifdef DEBUG
914*47038Sbostic STATIC
915*47038Sbostic prtab(s, t, num_rows)
916*47038Sbostic 	char *s;
917*47038Sbostic 	unsigned char *t;
918*47038Sbostic 	int num_rows;
919*47038Sbostic {
920*47038Sbostic 	register int i, j;
921*47038Sbostic 
922*47038Sbostic 	printf("%s:\n", s);
923*47038Sbostic 	for (i = 0; i < num_rows; i++) {
924*47038Sbostic 		for (j = 0; j < 8; j++) {
925*47038Sbostic 			 printf("%3d", t[i*8+j]);
926*47038Sbostic 		}
927*47038Sbostic 		printf("\n");
928*47038Sbostic 	}
929*47038Sbostic 	printf("\n");
930*47038Sbostic }
931*47038Sbostic #endif
932