Home | History | Annotate | Line # | Download | only in libcrypt
blowfish.c revision 1.1
      1  1.1  itojun /*	$NetBSD: blowfish.c,v 1.1 2002/05/24 04:02:49 itojun Exp $	*/
      2  1.1  itojun /* $OpenBSD: blowfish.c,v 1.16 2002/02/19 19:39:36 millert Exp $ */
      3  1.1  itojun /*
      4  1.1  itojun  * Blowfish block cipher for OpenBSD
      5  1.1  itojun  * Copyright 1997 Niels Provos <provos (at) physnet.uni-hamburg.de>
      6  1.1  itojun  * All rights reserved.
      7  1.1  itojun  *
      8  1.1  itojun  * Implementation advice by David Mazieres <dm (at) lcs.mit.edu>.
      9  1.1  itojun  *
     10  1.1  itojun  * Redistribution and use in source and binary forms, with or without
     11  1.1  itojun  * modification, are permitted provided that the following conditions
     12  1.1  itojun  * are met:
     13  1.1  itojun  * 1. Redistributions of source code must retain the above copyright
     14  1.1  itojun  *    notice, this list of conditions and the following disclaimer.
     15  1.1  itojun  * 2. Redistributions in binary form must reproduce the above copyright
     16  1.1  itojun  *    notice, this list of conditions and the following disclaimer in the
     17  1.1  itojun  *    documentation and/or other materials provided with the distribution.
     18  1.1  itojun  * 3. All advertising materials mentioning features or use of this software
     19  1.1  itojun  *    must display the following acknowledgement:
     20  1.1  itojun  *      This product includes software developed by Niels Provos.
     21  1.1  itojun  * 4. The name of the author may not be used to endorse or promote products
     22  1.1  itojun  *    derived from this software without specific prior written permission.
     23  1.1  itojun  *
     24  1.1  itojun  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
     25  1.1  itojun  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
     26  1.1  itojun  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
     27  1.1  itojun  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
     28  1.1  itojun  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
     29  1.1  itojun  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
     30  1.1  itojun  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
     31  1.1  itojun  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     32  1.1  itojun  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
     33  1.1  itojun  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     34  1.1  itojun  */
     35  1.1  itojun 
     36  1.1  itojun /*
     37  1.1  itojun  * This code is derived from section 14.3 and the given source
     38  1.1  itojun  * in section V of Applied Cryptography, second edition.
     39  1.1  itojun  * Blowfish is an unpatented fast block cipher designed by
     40  1.1  itojun  * Bruce Schneier.
     41  1.1  itojun  */
     42  1.1  itojun 
     43  1.1  itojun #if 0
     44  1.1  itojun #include <stdio.h>		/* used for debugging */
     45  1.1  itojun #include <string.h>
     46  1.1  itojun #endif
     47  1.1  itojun 
     48  1.1  itojun #include <sys/types.h>
     49  1.1  itojun #include "blf.h"
     50  1.1  itojun 
     51  1.1  itojun #undef inline
     52  1.1  itojun #ifdef __GNUC__
     53  1.1  itojun #define inline __inline
     54  1.1  itojun #else				/* !__GNUC__ */
     55  1.1  itojun #define inline
     56  1.1  itojun #endif				/* !__GNUC__ */
     57  1.1  itojun 
     58  1.1  itojun /* Function for Feistel Networks */
     59  1.1  itojun 
     60  1.1  itojun #define F(s, x) ((((s)[        (((x)>>24)&0xFF)]  \
     61  1.1  itojun 		 + (s)[0x100 + (((x)>>16)&0xFF)]) \
     62  1.1  itojun 		 ^ (s)[0x200 + (((x)>> 8)&0xFF)]) \
     63  1.1  itojun 		 + (s)[0x300 + ( (x)     &0xFF)])
     64  1.1  itojun 
     65  1.1  itojun #define BLFRND(s,p,i,j,n) (i ^= F(s,j) ^ (p)[n])
     66  1.1  itojun 
     67  1.1  itojun void
     68  1.1  itojun Blowfish_encipher(c, xl, xr)
     69  1.1  itojun 	blf_ctx *c;
     70  1.1  itojun 	u_int32_t *xl;
     71  1.1  itojun 	u_int32_t *xr;
     72  1.1  itojun {
     73  1.1  itojun 	u_int32_t Xl;
     74  1.1  itojun 	u_int32_t Xr;
     75  1.1  itojun 	u_int32_t *s = c->S[0];
     76  1.1  itojun 	u_int32_t *p = c->P;
     77  1.1  itojun 
     78  1.1  itojun 	Xl = *xl;
     79  1.1  itojun 	Xr = *xr;
     80  1.1  itojun 
     81  1.1  itojun 	Xl ^= p[0];
     82  1.1  itojun 	BLFRND(s, p, Xr, Xl, 1); BLFRND(s, p, Xl, Xr, 2);
     83  1.1  itojun 	BLFRND(s, p, Xr, Xl, 3); BLFRND(s, p, Xl, Xr, 4);
     84  1.1  itojun 	BLFRND(s, p, Xr, Xl, 5); BLFRND(s, p, Xl, Xr, 6);
     85  1.1  itojun 	BLFRND(s, p, Xr, Xl, 7); BLFRND(s, p, Xl, Xr, 8);
     86  1.1  itojun 	BLFRND(s, p, Xr, Xl, 9); BLFRND(s, p, Xl, Xr, 10);
     87  1.1  itojun 	BLFRND(s, p, Xr, Xl, 11); BLFRND(s, p, Xl, Xr, 12);
     88  1.1  itojun 	BLFRND(s, p, Xr, Xl, 13); BLFRND(s, p, Xl, Xr, 14);
     89  1.1  itojun 	BLFRND(s, p, Xr, Xl, 15); BLFRND(s, p, Xl, Xr, 16);
     90  1.1  itojun 
     91  1.1  itojun 	*xl = Xr ^ p[17];
     92  1.1  itojun 	*xr = Xl;
     93  1.1  itojun }
     94  1.1  itojun 
     95  1.1  itojun void
     96  1.1  itojun Blowfish_decipher(c, xl, xr)
     97  1.1  itojun 	blf_ctx *c;
     98  1.1  itojun 	u_int32_t *xl;
     99  1.1  itojun 	u_int32_t *xr;
    100  1.1  itojun {
    101  1.1  itojun 	u_int32_t Xl;
    102  1.1  itojun 	u_int32_t Xr;
    103  1.1  itojun 	u_int32_t *s = c->S[0];
    104  1.1  itojun 	u_int32_t *p = c->P;
    105  1.1  itojun 
    106  1.1  itojun 	Xl = *xl;
    107  1.1  itojun 	Xr = *xr;
    108  1.1  itojun 
    109  1.1  itojun 	Xl ^= p[17];
    110  1.1  itojun 	BLFRND(s, p, Xr, Xl, 16); BLFRND(s, p, Xl, Xr, 15);
    111  1.1  itojun 	BLFRND(s, p, Xr, Xl, 14); BLFRND(s, p, Xl, Xr, 13);
    112  1.1  itojun 	BLFRND(s, p, Xr, Xl, 12); BLFRND(s, p, Xl, Xr, 11);
    113  1.1  itojun 	BLFRND(s, p, Xr, Xl, 10); BLFRND(s, p, Xl, Xr, 9);
    114  1.1  itojun 	BLFRND(s, p, Xr, Xl, 8); BLFRND(s, p, Xl, Xr, 7);
    115  1.1  itojun 	BLFRND(s, p, Xr, Xl, 6); BLFRND(s, p, Xl, Xr, 5);
    116  1.1  itojun 	BLFRND(s, p, Xr, Xl, 4); BLFRND(s, p, Xl, Xr, 3);
    117  1.1  itojun 	BLFRND(s, p, Xr, Xl, 2); BLFRND(s, p, Xl, Xr, 1);
    118  1.1  itojun 
    119  1.1  itojun 	*xl = Xr ^ p[0];
    120  1.1  itojun 	*xr = Xl;
    121  1.1  itojun }
    122  1.1  itojun 
    123  1.1  itojun void
    124  1.1  itojun Blowfish_initstate(c)
    125  1.1  itojun 	blf_ctx *c;
    126  1.1  itojun {
    127  1.1  itojun 
    128  1.1  itojun /* P-box and S-box tables initialized with digits of Pi */
    129  1.1  itojun 
    130  1.1  itojun 	const blf_ctx initstate =
    131  1.1  itojun 
    132  1.1  itojun 	{ {
    133  1.1  itojun 		{
    134  1.1  itojun 			0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
    135  1.1  itojun 			0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
    136  1.1  itojun 			0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
    137  1.1  itojun 			0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
    138  1.1  itojun 			0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
    139  1.1  itojun 			0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
    140  1.1  itojun 			0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
    141  1.1  itojun 			0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
    142  1.1  itojun 			0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
    143  1.1  itojun 			0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
    144  1.1  itojun 			0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
    145  1.1  itojun 			0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
    146  1.1  itojun 			0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
    147  1.1  itojun 			0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
    148  1.1  itojun 			0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
    149  1.1  itojun 			0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
    150  1.1  itojun 			0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
    151  1.1  itojun 			0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
    152  1.1  itojun 			0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
    153  1.1  itojun 			0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
    154  1.1  itojun 			0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
    155  1.1  itojun 			0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
    156  1.1  itojun 			0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
    157  1.1  itojun 			0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
    158  1.1  itojun 			0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
    159  1.1  itojun 			0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
    160  1.1  itojun 			0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
    161  1.1  itojun 			0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
    162  1.1  itojun 			0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
    163  1.1  itojun 			0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
    164  1.1  itojun 			0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
    165  1.1  itojun 			0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
    166  1.1  itojun 			0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
    167  1.1  itojun 			0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
    168  1.1  itojun 			0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
    169  1.1  itojun 			0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
    170  1.1  itojun 			0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
    171  1.1  itojun 			0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
    172  1.1  itojun 			0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
    173  1.1  itojun 			0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
    174  1.1  itojun 			0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
    175  1.1  itojun 			0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
    176  1.1  itojun 			0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
    177  1.1  itojun 			0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
    178  1.1  itojun 			0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
    179  1.1  itojun 			0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
    180  1.1  itojun 			0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
    181  1.1  itojun 			0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
    182  1.1  itojun 			0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
    183  1.1  itojun 			0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
    184  1.1  itojun 			0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
    185  1.1  itojun 			0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
    186  1.1  itojun 			0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
    187  1.1  itojun 			0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
    188  1.1  itojun 			0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
    189  1.1  itojun 			0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
    190  1.1  itojun 			0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
    191  1.1  itojun 			0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
    192  1.1  itojun 			0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
    193  1.1  itojun 			0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
    194  1.1  itojun 			0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
    195  1.1  itojun 			0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
    196  1.1  itojun 			0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
    197  1.1  itojun 		0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a},
    198  1.1  itojun 		{
    199  1.1  itojun 			0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
    200  1.1  itojun 			0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
    201  1.1  itojun 			0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
    202  1.1  itojun 			0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
    203  1.1  itojun 			0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
    204  1.1  itojun 			0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
    205  1.1  itojun 			0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
    206  1.1  itojun 			0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
    207  1.1  itojun 			0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
    208  1.1  itojun 			0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
    209  1.1  itojun 			0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
    210  1.1  itojun 			0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
    211  1.1  itojun 			0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
    212  1.1  itojun 			0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
    213  1.1  itojun 			0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
    214  1.1  itojun 			0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
    215  1.1  itojun 			0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
    216  1.1  itojun 			0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
    217  1.1  itojun 			0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
    218  1.1  itojun 			0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
    219  1.1  itojun 			0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
    220  1.1  itojun 			0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
    221  1.1  itojun 			0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
    222  1.1  itojun 			0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
    223  1.1  itojun 			0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
    224  1.1  itojun 			0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
    225  1.1  itojun 			0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
    226  1.1  itojun 			0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
    227  1.1  itojun 			0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
    228  1.1  itojun 			0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
    229  1.1  itojun 			0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
    230  1.1  itojun 			0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
    231  1.1  itojun 			0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
    232  1.1  itojun 			0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
    233  1.1  itojun 			0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
    234  1.1  itojun 			0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
    235  1.1  itojun 			0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
    236  1.1  itojun 			0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
    237  1.1  itojun 			0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
    238  1.1  itojun 			0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
    239  1.1  itojun 			0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
    240  1.1  itojun 			0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
    241  1.1  itojun 			0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
    242  1.1  itojun 			0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
    243  1.1  itojun 			0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
    244  1.1  itojun 			0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
    245  1.1  itojun 			0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
    246  1.1  itojun 			0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
    247  1.1  itojun 			0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
    248  1.1  itojun 			0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
    249  1.1  itojun 			0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
    250  1.1  itojun 			0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
    251  1.1  itojun 			0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
    252  1.1  itojun 			0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
    253  1.1  itojun 			0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
    254  1.1  itojun 			0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
    255  1.1  itojun 			0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
    256  1.1  itojun 			0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
    257  1.1  itojun 			0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
    258  1.1  itojun 			0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
    259  1.1  itojun 			0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
    260  1.1  itojun 			0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
    261  1.1  itojun 			0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
    262  1.1  itojun 		0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7},
    263  1.1  itojun 		{
    264  1.1  itojun 			0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
    265  1.1  itojun 			0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
    266  1.1  itojun 			0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
    267  1.1  itojun 			0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
    268  1.1  itojun 			0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
    269  1.1  itojun 			0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
    270  1.1  itojun 			0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
    271  1.1  itojun 			0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
    272  1.1  itojun 			0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
    273  1.1  itojun 			0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
    274  1.1  itojun 			0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
    275  1.1  itojun 			0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
    276  1.1  itojun 			0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
    277  1.1  itojun 			0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
    278  1.1  itojun 			0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
    279  1.1  itojun 			0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
    280  1.1  itojun 			0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
    281  1.1  itojun 			0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
    282  1.1  itojun 			0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
    283  1.1  itojun 			0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
    284  1.1  itojun 			0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
    285  1.1  itojun 			0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
    286  1.1  itojun 			0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
    287  1.1  itojun 			0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
    288  1.1  itojun 			0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
    289  1.1  itojun 			0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
    290  1.1  itojun 			0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
    291  1.1  itojun 			0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
    292  1.1  itojun 			0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
    293  1.1  itojun 			0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
    294  1.1  itojun 			0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
    295  1.1  itojun 			0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
    296  1.1  itojun 			0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
    297  1.1  itojun 			0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
    298  1.1  itojun 			0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
    299  1.1  itojun 			0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
    300  1.1  itojun 			0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
    301  1.1  itojun 			0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
    302  1.1  itojun 			0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
    303  1.1  itojun 			0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
    304  1.1  itojun 			0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
    305  1.1  itojun 			0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
    306  1.1  itojun 			0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
    307  1.1  itojun 			0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
    308  1.1  itojun 			0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
    309  1.1  itojun 			0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
    310  1.1  itojun 			0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
    311  1.1  itojun 			0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
    312  1.1  itojun 			0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
    313  1.1  itojun 			0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
    314  1.1  itojun 			0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
    315  1.1  itojun 			0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
    316  1.1  itojun 			0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
    317  1.1  itojun 			0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
    318  1.1  itojun 			0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
    319  1.1  itojun 			0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
    320  1.1  itojun 			0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
    321  1.1  itojun 			0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
    322  1.1  itojun 			0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
    323  1.1  itojun 			0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
    324  1.1  itojun 			0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
    325  1.1  itojun 			0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
    326  1.1  itojun 			0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
    327  1.1  itojun 		0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0},
    328  1.1  itojun 		{
    329  1.1  itojun 			0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
    330  1.1  itojun 			0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
    331  1.1  itojun 			0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
    332  1.1  itojun 			0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
    333  1.1  itojun 			0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
    334  1.1  itojun 			0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
    335  1.1  itojun 			0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
    336  1.1  itojun 			0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
    337  1.1  itojun 			0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
    338  1.1  itojun 			0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
    339  1.1  itojun 			0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
    340  1.1  itojun 			0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
    341  1.1  itojun 			0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
    342  1.1  itojun 			0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
    343  1.1  itojun 			0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
    344  1.1  itojun 			0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
    345  1.1  itojun 			0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
    346  1.1  itojun 			0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
    347  1.1  itojun 			0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
    348  1.1  itojun 			0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
    349  1.1  itojun 			0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
    350  1.1  itojun 			0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
    351  1.1  itojun 			0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
    352  1.1  itojun 			0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
    353  1.1  itojun 			0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
    354  1.1  itojun 			0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
    355  1.1  itojun 			0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
    356  1.1  itojun 			0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
    357  1.1  itojun 			0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
    358  1.1  itojun 			0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
    359  1.1  itojun 			0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
    360  1.1  itojun 			0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
    361  1.1  itojun 			0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
    362  1.1  itojun 			0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
    363  1.1  itojun 			0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
    364  1.1  itojun 			0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
    365  1.1  itojun 			0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
    366  1.1  itojun 			0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
    367  1.1  itojun 			0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
    368  1.1  itojun 			0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
    369  1.1  itojun 			0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
    370  1.1  itojun 			0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
    371  1.1  itojun 			0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
    372  1.1  itojun 			0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
    373  1.1  itojun 			0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
    374  1.1  itojun 			0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
    375  1.1  itojun 			0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
    376  1.1  itojun 			0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
    377  1.1  itojun 			0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
    378  1.1  itojun 			0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
    379  1.1  itojun 			0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
    380  1.1  itojun 			0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
    381  1.1  itojun 			0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
    382  1.1  itojun 			0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
    383  1.1  itojun 			0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
    384  1.1  itojun 			0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
    385  1.1  itojun 			0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
    386  1.1  itojun 			0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
    387  1.1  itojun 			0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
    388  1.1  itojun 			0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
    389  1.1  itojun 			0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
    390  1.1  itojun 			0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
    391  1.1  itojun 			0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
    392  1.1  itojun 		0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6}
    393  1.1  itojun 	},
    394  1.1  itojun 	{
    395  1.1  itojun 		0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
    396  1.1  itojun 		0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
    397  1.1  itojun 		0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
    398  1.1  itojun 		0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
    399  1.1  itojun 		0x9216d5d9, 0x8979fb1b
    400  1.1  itojun 	} };
    401  1.1  itojun 
    402  1.1  itojun 	*c = initstate;
    403  1.1  itojun 
    404  1.1  itojun }
    405  1.1  itojun 
    406  1.1  itojun u_int32_t
    407  1.1  itojun Blowfish_stream2word(const u_int8_t *data, u_int16_t databytes, u_int16_t *current)
    408  1.1  itojun {
    409  1.1  itojun 	u_int8_t i;
    410  1.1  itojun 	u_int16_t j;
    411  1.1  itojun 	u_int32_t temp;
    412  1.1  itojun 
    413  1.1  itojun 	temp = 0x00000000;
    414  1.1  itojun 	j = *current;
    415  1.1  itojun 
    416  1.1  itojun 	for (i = 0; i < 4; i++, j++) {
    417  1.1  itojun 		if (j >= databytes)
    418  1.1  itojun 			j = 0;
    419  1.1  itojun 		temp = (temp << 8) | data[j];
    420  1.1  itojun 	}
    421  1.1  itojun 
    422  1.1  itojun 	*current = j;
    423  1.1  itojun 	return temp;
    424  1.1  itojun }
    425  1.1  itojun 
    426  1.1  itojun void
    427  1.1  itojun Blowfish_expand0state(blf_ctx *c, const u_int8_t *key, u_int16_t keybytes)
    428  1.1  itojun {
    429  1.1  itojun 	u_int16_t i;
    430  1.1  itojun 	u_int16_t j;
    431  1.1  itojun 	u_int16_t k;
    432  1.1  itojun 	u_int32_t temp;
    433  1.1  itojun 	u_int32_t datal;
    434  1.1  itojun 	u_int32_t datar;
    435  1.1  itojun 
    436  1.1  itojun 	j = 0;
    437  1.1  itojun 	for (i = 0; i < BLF_N + 2; i++) {
    438  1.1  itojun 		/* Extract 4 int8 to 1 int32 from keystream */
    439  1.1  itojun 		temp = Blowfish_stream2word(key, keybytes, &j);
    440  1.1  itojun 		c->P[i] = c->P[i] ^ temp;
    441  1.1  itojun 	}
    442  1.1  itojun 
    443  1.1  itojun 	j = 0;
    444  1.1  itojun 	datal = 0x00000000;
    445  1.1  itojun 	datar = 0x00000000;
    446  1.1  itojun 	for (i = 0; i < BLF_N + 2; i += 2) {
    447  1.1  itojun 		Blowfish_encipher(c, &datal, &datar);
    448  1.1  itojun 
    449  1.1  itojun 		c->P[i] = datal;
    450  1.1  itojun 		c->P[i + 1] = datar;
    451  1.1  itojun 	}
    452  1.1  itojun 
    453  1.1  itojun 	for (i = 0; i < 4; i++) {
    454  1.1  itojun 		for (k = 0; k < 256; k += 2) {
    455  1.1  itojun 			Blowfish_encipher(c, &datal, &datar);
    456  1.1  itojun 
    457  1.1  itojun 			c->S[i][k] = datal;
    458  1.1  itojun 			c->S[i][k + 1] = datar;
    459  1.1  itojun 		}
    460  1.1  itojun 	}
    461  1.1  itojun }
    462  1.1  itojun 
    463  1.1  itojun 
    464  1.1  itojun void
    465  1.1  itojun Blowfish_expandstate(blf_ctx *c, const u_int8_t *data, u_int16_t databytes,
    466  1.1  itojun 		     const u_int8_t *key, u_int16_t keybytes)
    467  1.1  itojun {
    468  1.1  itojun 	u_int16_t i;
    469  1.1  itojun 	u_int16_t j;
    470  1.1  itojun 	u_int16_t k;
    471  1.1  itojun 	u_int32_t temp;
    472  1.1  itojun 	u_int32_t datal;
    473  1.1  itojun 	u_int32_t datar;
    474  1.1  itojun 
    475  1.1  itojun 	j = 0;
    476  1.1  itojun 	for (i = 0; i < BLF_N + 2; i++) {
    477  1.1  itojun 		/* Extract 4 int8 to 1 int32 from keystream */
    478  1.1  itojun 		temp = Blowfish_stream2word(key, keybytes, &j);
    479  1.1  itojun 		c->P[i] = c->P[i] ^ temp;
    480  1.1  itojun 	}
    481  1.1  itojun 
    482  1.1  itojun 	j = 0;
    483  1.1  itojun 	datal = 0x00000000;
    484  1.1  itojun 	datar = 0x00000000;
    485  1.1  itojun 	for (i = 0; i < BLF_N + 2; i += 2) {
    486  1.1  itojun 		datal ^= Blowfish_stream2word(data, databytes, &j);
    487  1.1  itojun 		datar ^= Blowfish_stream2word(data, databytes, &j);
    488  1.1  itojun 		Blowfish_encipher(c, &datal, &datar);
    489  1.1  itojun 
    490  1.1  itojun 		c->P[i] = datal;
    491  1.1  itojun 		c->P[i + 1] = datar;
    492  1.1  itojun 	}
    493  1.1  itojun 
    494  1.1  itojun 	for (i = 0; i < 4; i++) {
    495  1.1  itojun 		for (k = 0; k < 256; k += 2) {
    496  1.1  itojun 			datal ^= Blowfish_stream2word(data, databytes, &j);
    497  1.1  itojun 			datar ^= Blowfish_stream2word(data, databytes, &j);
    498  1.1  itojun 			Blowfish_encipher(c, &datal, &datar);
    499  1.1  itojun 
    500  1.1  itojun 			c->S[i][k] = datal;
    501  1.1  itojun 			c->S[i][k + 1] = datar;
    502  1.1  itojun 		}
    503  1.1  itojun 	}
    504  1.1  itojun 
    505  1.1  itojun }
    506  1.1  itojun 
    507  1.1  itojun void
    508  1.1  itojun blf_key(blf_ctx *c, const u_int8_t *k, u_int16_t len)
    509  1.1  itojun {
    510  1.1  itojun 	/* Initialize S-boxes and subkeys with Pi */
    511  1.1  itojun 	Blowfish_initstate(c);
    512  1.1  itojun 
    513  1.1  itojun 	/* Transform S-boxes and subkeys with key */
    514  1.1  itojun 	Blowfish_expand0state(c, k, len);
    515  1.1  itojun }
    516  1.1  itojun 
    517  1.1  itojun void
    518  1.1  itojun blf_enc(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
    519  1.1  itojun {
    520  1.1  itojun 	u_int32_t *d;
    521  1.1  itojun 	u_int16_t i;
    522  1.1  itojun 
    523  1.1  itojun 	d = data;
    524  1.1  itojun 	for (i = 0; i < blocks; i++) {
    525  1.1  itojun 		Blowfish_encipher(c, d, d + 1);
    526  1.1  itojun 		d += 2;
    527  1.1  itojun 	}
    528  1.1  itojun }
    529  1.1  itojun 
    530  1.1  itojun void
    531  1.1  itojun blf_dec(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
    532  1.1  itojun {
    533  1.1  itojun 	u_int32_t *d;
    534  1.1  itojun 	u_int16_t i;
    535  1.1  itojun 
    536  1.1  itojun 	d = data;
    537  1.1  itojun 	for (i = 0; i < blocks; i++) {
    538  1.1  itojun 		Blowfish_decipher(c, d, d + 1);
    539  1.1  itojun 		d += 2;
    540  1.1  itojun 	}
    541  1.1  itojun }
    542  1.1  itojun 
    543  1.1  itojun void
    544  1.1  itojun blf_ecb_encrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
    545  1.1  itojun {
    546  1.1  itojun 	u_int32_t l, r;
    547  1.1  itojun 	u_int32_t i;
    548  1.1  itojun 
    549  1.1  itojun 	for (i = 0; i < len; i += 8) {
    550  1.1  itojun 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
    551  1.1  itojun 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
    552  1.1  itojun 		Blowfish_encipher(c, &l, &r);
    553  1.1  itojun 		data[0] = l >> 24 & 0xff;
    554  1.1  itojun 		data[1] = l >> 16 & 0xff;
    555  1.1  itojun 		data[2] = l >> 8 & 0xff;
    556  1.1  itojun 		data[3] = l & 0xff;
    557  1.1  itojun 		data[4] = r >> 24 & 0xff;
    558  1.1  itojun 		data[5] = r >> 16 & 0xff;
    559  1.1  itojun 		data[6] = r >> 8 & 0xff;
    560  1.1  itojun 		data[7] = r & 0xff;
    561  1.1  itojun 		data += 8;
    562  1.1  itojun 	}
    563  1.1  itojun }
    564  1.1  itojun 
    565  1.1  itojun void
    566  1.1  itojun blf_ecb_decrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
    567  1.1  itojun {
    568  1.1  itojun 	u_int32_t l, r;
    569  1.1  itojun 	u_int32_t i;
    570  1.1  itojun 
    571  1.1  itojun 	for (i = 0; i < len; i += 8) {
    572  1.1  itojun 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
    573  1.1  itojun 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
    574  1.1  itojun 		Blowfish_decipher(c, &l, &r);
    575  1.1  itojun 		data[0] = l >> 24 & 0xff;
    576  1.1  itojun 		data[1] = l >> 16 & 0xff;
    577  1.1  itojun 		data[2] = l >> 8 & 0xff;
    578  1.1  itojun 		data[3] = l & 0xff;
    579  1.1  itojun 		data[4] = r >> 24 & 0xff;
    580  1.1  itojun 		data[5] = r >> 16 & 0xff;
    581  1.1  itojun 		data[6] = r >> 8 & 0xff;
    582  1.1  itojun 		data[7] = r & 0xff;
    583  1.1  itojun 		data += 8;
    584  1.1  itojun 	}
    585  1.1  itojun }
    586  1.1  itojun 
    587  1.1  itojun void
    588  1.1  itojun blf_cbc_encrypt(blf_ctx *c, u_int8_t *iv, u_int8_t *data, u_int32_t len)
    589  1.1  itojun {
    590  1.1  itojun 	u_int32_t l, r;
    591  1.1  itojun 	u_int32_t i, j;
    592  1.1  itojun 
    593  1.1  itojun 	for (i = 0; i < len; i += 8) {
    594  1.1  itojun 		for (j = 0; j < 8; j++)
    595  1.1  itojun 			data[j] ^= iv[j];
    596  1.1  itojun 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
    597  1.1  itojun 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
    598  1.1  itojun 		Blowfish_encipher(c, &l, &r);
    599  1.1  itojun 		data[0] = l >> 24 & 0xff;
    600  1.1  itojun 		data[1] = l >> 16 & 0xff;
    601  1.1  itojun 		data[2] = l >> 8 & 0xff;
    602  1.1  itojun 		data[3] = l & 0xff;
    603  1.1  itojun 		data[4] = r >> 24 & 0xff;
    604  1.1  itojun 		data[5] = r >> 16 & 0xff;
    605  1.1  itojun 		data[6] = r >> 8 & 0xff;
    606  1.1  itojun 		data[7] = r & 0xff;
    607  1.1  itojun 		iv = data;
    608  1.1  itojun 		data += 8;
    609  1.1  itojun 	}
    610  1.1  itojun }
    611  1.1  itojun 
    612  1.1  itojun void
    613  1.1  itojun blf_cbc_decrypt(blf_ctx *c, u_int8_t *iva, u_int8_t *data, u_int32_t len)
    614  1.1  itojun {
    615  1.1  itojun 	u_int32_t l, r;
    616  1.1  itojun 	u_int8_t *iv;
    617  1.1  itojun 	u_int32_t i, j;
    618  1.1  itojun 
    619  1.1  itojun 	iv = data + len - 16;
    620  1.1  itojun 	data = data + len - 8;
    621  1.1  itojun 	for (i = len - 8; i >= 8; i -= 8) {
    622  1.1  itojun 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
    623  1.1  itojun 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
    624  1.1  itojun 		Blowfish_decipher(c, &l, &r);
    625  1.1  itojun 		data[0] = l >> 24 & 0xff;
    626  1.1  itojun 		data[1] = l >> 16 & 0xff;
    627  1.1  itojun 		data[2] = l >> 8 & 0xff;
    628  1.1  itojun 		data[3] = l & 0xff;
    629  1.1  itojun 		data[4] = r >> 24 & 0xff;
    630  1.1  itojun 		data[5] = r >> 16 & 0xff;
    631  1.1  itojun 		data[6] = r >> 8 & 0xff;
    632  1.1  itojun 		data[7] = r & 0xff;
    633  1.1  itojun 		for (j = 0; j < 8; j++)
    634  1.1  itojun 			data[j] ^= iv[j];
    635  1.1  itojun 		iv -= 8;
    636  1.1  itojun 		data -= 8;
    637  1.1  itojun 	}
    638  1.1  itojun 	l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
    639  1.1  itojun 	r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
    640  1.1  itojun 	Blowfish_decipher(c, &l, &r);
    641  1.1  itojun 	data[0] = l >> 24 & 0xff;
    642  1.1  itojun 	data[1] = l >> 16 & 0xff;
    643  1.1  itojun 	data[2] = l >> 8 & 0xff;
    644  1.1  itojun 	data[3] = l & 0xff;
    645  1.1  itojun 	data[4] = r >> 24 & 0xff;
    646  1.1  itojun 	data[5] = r >> 16 & 0xff;
    647  1.1  itojun 	data[6] = r >> 8 & 0xff;
    648  1.1  itojun 	data[7] = r & 0xff;
    649  1.1  itojun 	for (j = 0; j < 8; j++)
    650  1.1  itojun 		data[j] ^= iva[j];
    651  1.1  itojun }
    652  1.1  itojun 
    653  1.1  itojun #if 0
    654  1.1  itojun void
    655  1.1  itojun report(u_int32_t data[], u_int16_t len)
    656  1.1  itojun {
    657  1.1  itojun 	u_int16_t i;
    658  1.1  itojun 	for (i = 0; i < len; i += 2)
    659  1.1  itojun 		printf("Block %0hd: %08lx %08lx.\n",
    660  1.1  itojun 		    i / 2, data[i], data[i + 1]);
    661  1.1  itojun }
    662  1.1  itojun void
    663  1.1  itojun main(void)
    664  1.1  itojun {
    665  1.1  itojun 
    666  1.1  itojun 	blf_ctx c;
    667  1.1  itojun 	char    key[] = "AAAAA";
    668  1.1  itojun 	char    key2[] = "abcdefghijklmnopqrstuvwxyz";
    669  1.1  itojun 
    670  1.1  itojun 	u_int32_t data[10];
    671  1.1  itojun 	u_int32_t data2[] =
    672  1.1  itojun 	{0x424c4f57l, 0x46495348l};
    673  1.1  itojun 
    674  1.1  itojun 	u_int16_t i;
    675  1.1  itojun 
    676  1.1  itojun 	/* First test */
    677  1.1  itojun 	for (i = 0; i < 10; i++)
    678  1.1  itojun 		data[i] = i;
    679  1.1  itojun 
    680  1.1  itojun 	blf_key(&c, (u_int8_t *) key, 5);
    681  1.1  itojun 	blf_enc(&c, data, 5);
    682  1.1  itojun 	blf_dec(&c, data, 1);
    683  1.1  itojun 	blf_dec(&c, data + 2, 4);
    684  1.1  itojun 	printf("Should read as 0 - 9.\n");
    685  1.1  itojun 	report(data, 10);
    686  1.1  itojun 
    687  1.1  itojun 	/* Second test */
    688  1.1  itojun 	blf_key(&c, (u_int8_t *) key2, strlen(key2));
    689  1.1  itojun 	blf_enc(&c, data2, 1);
    690  1.1  itojun 	printf("\nShould read as: 0x324ed0fe 0xf413a203.\n");
    691  1.1  itojun 	report(data2, 2);
    692  1.1  itojun 	blf_dec(&c, data2, 1);
    693  1.1  itojun 	report(data2, 2);
    694  1.1  itojun }
    695  1.1  itojun #endif
    696