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