aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorJussi Kivilinna <jussi.kivilinna@mbnet.fi>2011-09-01 18:45:07 -0400
committerHerbert Xu <herbert@gondor.apana.org.au>2011-09-22 07:25:25 -0400
commit52ba867c8c23dcb24865f80a95c191501e101b9f (patch)
tree421448ac9400c97e11a233769ae7993dcf36e70a
parentb2bac6acf86d05d8af0499f37d91ecac15722803 (diff)
crypto: blowfish - split generic and common c code
Patch splits up the blowfish crypto routine into a common part (key setup) which will be used by blowfish crypto modules (x86_64 assembly and generic-c). Also fixes errors/warnings reported by checkpatch. Signed-off-by: Jussi Kivilinna <jussi.kivilinna@mbnet.fi> Signed-off-by: Herbert Xu <herbert@gondor.apana.org.au>
-rw-r--r--crypto/Kconfig10
-rw-r--r--crypto/Makefile1
-rw-r--r--crypto/blowfish.c367
-rw-r--r--crypto/blowfish_common.c402
-rw-r--r--include/crypto/blowfish.h23
5 files changed, 448 insertions, 355 deletions
diff --git a/crypto/Kconfig b/crypto/Kconfig
index 55c50cd34690..108cb98e2170 100644
--- a/crypto/Kconfig
+++ b/crypto/Kconfig
@@ -600,6 +600,7 @@ config CRYPTO_ARC4
600config CRYPTO_BLOWFISH 600config CRYPTO_BLOWFISH
601 tristate "Blowfish cipher algorithm" 601 tristate "Blowfish cipher algorithm"
602 select CRYPTO_ALGAPI 602 select CRYPTO_ALGAPI
603 select CRYPTO_BLOWFISH_COMMON
603 help 604 help
604 Blowfish cipher algorithm, by Bruce Schneier. 605 Blowfish cipher algorithm, by Bruce Schneier.
605 606
@@ -610,6 +611,15 @@ config CRYPTO_BLOWFISH
610 See also: 611 See also:
611 <http://www.schneier.com/blowfish.html> 612 <http://www.schneier.com/blowfish.html>
612 613
614config CRYPTO_BLOWFISH_COMMON
615 tristate
616 help
617 Common parts of the Blowfish cipher algorithm shared by the
618 generic c and the assembler implementations.
619
620 See also:
621 <http://www.schneier.com/blowfish.html>
622
613config CRYPTO_CAMELLIA 623config CRYPTO_CAMELLIA
614 tristate "Camellia cipher algorithms" 624 tristate "Camellia cipher algorithms"
615 depends on CRYPTO 625 depends on CRYPTO
diff --git a/crypto/Makefile b/crypto/Makefile
index ce5a813d3639..495b79172ee2 100644
--- a/crypto/Makefile
+++ b/crypto/Makefile
@@ -61,6 +61,7 @@ obj-$(CONFIG_CRYPTO_CRYPTD) += cryptd.o
61obj-$(CONFIG_CRYPTO_DES) += des_generic.o 61obj-$(CONFIG_CRYPTO_DES) += des_generic.o
62obj-$(CONFIG_CRYPTO_FCRYPT) += fcrypt.o 62obj-$(CONFIG_CRYPTO_FCRYPT) += fcrypt.o
63obj-$(CONFIG_CRYPTO_BLOWFISH) += blowfish.o 63obj-$(CONFIG_CRYPTO_BLOWFISH) += blowfish.o
64obj-$(CONFIG_CRYPTO_BLOWFISH_COMMON) += blowfish_common.o
64obj-$(CONFIG_CRYPTO_TWOFISH) += twofish_generic.o 65obj-$(CONFIG_CRYPTO_TWOFISH) += twofish_generic.o
65obj-$(CONFIG_CRYPTO_TWOFISH_COMMON) += twofish_common.o 66obj-$(CONFIG_CRYPTO_TWOFISH_COMMON) += twofish_common.o
66obj-$(CONFIG_CRYPTO_SERPENT) += serpent.o 67obj-$(CONFIG_CRYPTO_SERPENT) += serpent.o
diff --git a/crypto/blowfish.c b/crypto/blowfish.c
index a67d52ee0580..0f86d31fbbd8 100644
--- a/crypto/blowfish.c
+++ b/crypto/blowfish.c
@@ -22,282 +22,7 @@
22#include <asm/byteorder.h> 22#include <asm/byteorder.h>
23#include <linux/crypto.h> 23#include <linux/crypto.h>
24#include <linux/types.h> 24#include <linux/types.h>
25 25#include <crypto/blowfish.h>
26#define BF_BLOCK_SIZE 8
27#define BF_MIN_KEY_SIZE 4
28#define BF_MAX_KEY_SIZE 56
29
30struct bf_ctx {
31 u32 p[18];
32 u32 s[1024];
33};
34
35static const u32 bf_pbox[16 + 2] = {
36 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
37 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
38 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
39 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
40 0x9216d5d9, 0x8979fb1b,
41};
42
43static const u32 bf_sbox[256 * 4] = {
44 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
45 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
46 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
47 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
48 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
49 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
50 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
51 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
52 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
53 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
54 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
55 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
56 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
57 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
58 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
59 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
60 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
61 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
62 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
63 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
64 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
65 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
66 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
67 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
68 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
69 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
70 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
71 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
72 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
73 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
74 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
75 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
76 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
77 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
78 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
79 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
80 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
81 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
82 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
83 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
84 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
85 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
86 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
87 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
88 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
89 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
90 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
91 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
92 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
93 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
94 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
95 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
96 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
97 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
98 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
99 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
100 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
101 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
102 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
103 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
104 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
105 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
106 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
107 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
108 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
109 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
110 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
111 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
112 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
113 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
114 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
115 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
116 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
117 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
118 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
119 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
120 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
121 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
122 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
123 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
124 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
125 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
126 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
127 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
128 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
129 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
130 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
131 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
132 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
133 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
134 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
135 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
136 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
137 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
138 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
139 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
140 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
141 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
142 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
143 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
144 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
145 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
146 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
147 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
148 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
149 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
150 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
151 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
152 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
153 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
154 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
155 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
156 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
157 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
158 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
159 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
160 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
161 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
162 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
163 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
164 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
165 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
166 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
167 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
168 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
169 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
170 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
171 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
172 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
173 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
174 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
175 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
176 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
177 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
178 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
179 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
180 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
181 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
182 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
183 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
184 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
185 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
186 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
187 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
188 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
189 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
190 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
191 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
192 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
193 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
194 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
195 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
196 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
197 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
198 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
199 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
200 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
201 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
202 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
203 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
204 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
205 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
206 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
207 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
208 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
209 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
210 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
211 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
212 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
213 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
214 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
215 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
216 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
217 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
218 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
219 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
220 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
221 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
222 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
223 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
224 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
225 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
226 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
227 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
228 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
229 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
230 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
231 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
232 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
233 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
234 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
235 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
236 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
237 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
238 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
239 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
240 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
241 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
242 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
243 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
244 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
245 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
246 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
247 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
248 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
249 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
250 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
251 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
252 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
253 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
254 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
255 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
256 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
257 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
258 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
259 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
260 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
261 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
262 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
263 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
264 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
265 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
266 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
267 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
268 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
269 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
270 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
271 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
272 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
273 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
274 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
275 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
276 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
277 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
278 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
279 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
280 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
281 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
282 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
283 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
284 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
285 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
286 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
287 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
288 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
289 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
290 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
291 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
292 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
293 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
294 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
295 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
296 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
297 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
298 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
299 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6,
300};
301 26
302/* 27/*
303 * Round loop unrolling macros, S is a pointer to a S-Box array 28 * Round loop unrolling macros, S is a pointer to a S-Box array
@@ -313,16 +38,15 @@ static const u32 bf_sbox[256 * 4] = {
313 38
314#define ROUND(a, b, n) b ^= P[n]; a ^= bf_F (b) 39#define ROUND(a, b, n) b ^= P[n]; a ^= bf_F (b)
315 40
316/* 41static void bf_encrypt(struct crypto_tfm *tfm, u8 *dst, const u8 *src)
317 * The blowfish encipher, processes 64-bit blocks.
318 * NOTE: This function MUSTN'T respect endianess
319 */
320static void encrypt_block(struct bf_ctx *bctx, u32 *dst, u32 *src)
321{ 42{
322 const u32 *P = bctx->p; 43 struct bf_ctx *ctx = crypto_tfm_ctx(tfm);
323 const u32 *S = bctx->s; 44 const __be32 *in_blk = (const __be32 *)src;
324 u32 yl = src[0]; 45 __be32 *const out_blk = (__be32 *)dst;
325 u32 yr = src[1]; 46 const u32 *P = ctx->p;
47 const u32 *S = ctx->s;
48 u32 yl = be32_to_cpu(in_blk[0]);
49 u32 yr = be32_to_cpu(in_blk[1]);
326 50
327 ROUND(yr, yl, 0); 51 ROUND(yr, yl, 0);
328 ROUND(yl, yr, 1); 52 ROUND(yl, yr, 1);
@@ -344,21 +68,8 @@ static void encrypt_block(struct bf_ctx *bctx, u32 *dst, u32 *src)
344 yl ^= P[16]; 68 yl ^= P[16];
345 yr ^= P[17]; 69 yr ^= P[17];
346 70
347 dst[0] = yr; 71 out_blk[0] = cpu_to_be32(yr);
348 dst[1] = yl; 72 out_blk[1] = cpu_to_be32(yl);
349}
350
351static void bf_encrypt(struct crypto_tfm *tfm, u8 *dst, const u8 *src)
352{
353 const __be32 *in_blk = (const __be32 *)src;
354 __be32 *const out_blk = (__be32 *)dst;
355 u32 in32[2], out32[2];
356
357 in32[0] = be32_to_cpu(in_blk[0]);
358 in32[1] = be32_to_cpu(in_blk[1]);
359 encrypt_block(crypto_tfm_ctx(tfm), out32, in32);
360 out_blk[0] = cpu_to_be32(out32[0]);
361 out_blk[1] = cpu_to_be32(out32[1]);
362} 73}
363 74
364static void bf_decrypt(struct crypto_tfm *tfm, u8 *dst, const u8 *src) 75static void bf_decrypt(struct crypto_tfm *tfm, u8 *dst, const u8 *src)
@@ -395,60 +106,6 @@ static void bf_decrypt(struct crypto_tfm *tfm, u8 *dst, const u8 *src)
395 out_blk[1] = cpu_to_be32(yl); 106 out_blk[1] = cpu_to_be32(yl);
396} 107}
397 108
398/*
399 * Calculates the blowfish S and P boxes for encryption and decryption.
400 */
401static int bf_setkey(struct crypto_tfm *tfm, const u8 *key, unsigned int keylen)
402{
403 struct bf_ctx *ctx = crypto_tfm_ctx(tfm);
404 u32 *P = ctx->p;
405 u32 *S = ctx->s;
406 short i, j, count;
407 u32 data[2], temp;
408
409 /* Copy the initialization s-boxes */
410 for (i = 0, count = 0; i < 256; i++)
411 for (j = 0; j < 4; j++, count++)
412 S[count] = bf_sbox[count];
413
414 /* Set the p-boxes */
415 for (i = 0; i < 16 + 2; i++)
416 P[i] = bf_pbox[i];
417
418 /* Actual subkey generation */
419 for (j = 0, i = 0; i < 16 + 2; i++) {
420 temp = (((u32)key[j] << 24) |
421 ((u32)key[(j + 1) % keylen] << 16) |
422 ((u32)key[(j + 2) % keylen] << 8) |
423 ((u32)key[(j + 3) % keylen]));
424
425 P[i] = P[i] ^ temp;
426 j = (j + 4) % keylen;
427 }
428
429 data[0] = 0x00000000;
430 data[1] = 0x00000000;
431
432 for (i = 0; i < 16 + 2; i += 2) {
433 encrypt_block((struct bf_ctx *)ctx, data, data);
434
435 P[i] = data[0];
436 P[i + 1] = data[1];
437 }
438
439 for (i = 0; i < 4; i++) {
440 for (j = 0, count = i * 256; j < 256; j += 2, count += 2) {
441 encrypt_block((struct bf_ctx *)ctx, data, data);
442
443 S[count] = data[0];
444 S[count + 1] = data[1];
445 }
446 }
447
448 /* Bruce says not to bother with the weak key check. */
449 return 0;
450}
451
452static struct crypto_alg alg = { 109static struct crypto_alg alg = {
453 .cra_name = "blowfish", 110 .cra_name = "blowfish",
454 .cra_flags = CRYPTO_ALG_TYPE_CIPHER, 111 .cra_flags = CRYPTO_ALG_TYPE_CIPHER,
@@ -460,7 +117,7 @@ static struct crypto_alg alg = {
460 .cra_u = { .cipher = { 117 .cra_u = { .cipher = {
461 .cia_min_keysize = BF_MIN_KEY_SIZE, 118 .cia_min_keysize = BF_MIN_KEY_SIZE,
462 .cia_max_keysize = BF_MAX_KEY_SIZE, 119 .cia_max_keysize = BF_MAX_KEY_SIZE,
463 .cia_setkey = bf_setkey, 120 .cia_setkey = blowfish_setkey,
464 .cia_encrypt = bf_encrypt, 121 .cia_encrypt = bf_encrypt,
465 .cia_decrypt = bf_decrypt } } 122 .cia_decrypt = bf_decrypt } }
466}; 123};
diff --git a/crypto/blowfish_common.c b/crypto/blowfish_common.c
new file mode 100644
index 000000000000..f636aab0209f
--- /dev/null
+++ b/crypto/blowfish_common.c
@@ -0,0 +1,402 @@
1/*
2 * Cryptographic API.
3 *
4 * Common Blowfish algorithm parts shared between the c and assembler
5 * implementations.
6 *
7 * Blowfish Cipher Algorithm, by Bruce Schneier.
8 * http://www.counterpane.com/blowfish.html
9 *
10 * Adapted from Kerneli implementation.
11 *
12 * Copyright (c) Herbert Valerio Riedel <hvr@hvrlab.org>
13 * Copyright (c) Kyle McMartin <kyle@debian.org>
14 * Copyright (c) 2002 James Morris <jmorris@intercode.com.au>
15 *
16 * This program is free software; you can redistribute it and/or modify
17 * it under the terms of the GNU General Public License as published by
18 * the Free Software Foundation; either version 2 of the License, or
19 * (at your option) any later version.
20 *
21 */
22#include <linux/init.h>
23#include <linux/module.h>
24#include <linux/mm.h>
25#include <asm/byteorder.h>
26#include <linux/crypto.h>
27#include <linux/types.h>
28#include <crypto/blowfish.h>
29
30static const u32 bf_pbox[16 + 2] = {
31 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
32 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
33 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
34 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
35 0x9216d5d9, 0x8979fb1b,
36};
37
38static const u32 bf_sbox[256 * 4] = {
39 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
40 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
41 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
42 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
43 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
44 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
45 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
46 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
47 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
48 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
49 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
50 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
51 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
52 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
53 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
54 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
55 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
56 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
57 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
58 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
59 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
60 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
61 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
62 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
63 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
64 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
65 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
66 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
67 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
68 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
69 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
70 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
71 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
72 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
73 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
74 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
75 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
76 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
77 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
78 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
79 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
80 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
81 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
82 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
83 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
84 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
85 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
86 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
87 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
88 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
89 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
90 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
91 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
92 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
93 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
94 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
95 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
96 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
97 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
98 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
99 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
100 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
101 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
102 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
103 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
104 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
105 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
106 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
107 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
108 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
109 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
110 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
111 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
112 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
113 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
114 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
115 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
116 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
117 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
118 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
119 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
120 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
121 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
122 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
123 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
124 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
125 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
126 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
127 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
128 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
129 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
130 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
131 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
132 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
133 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
134 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
135 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
136 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
137 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
138 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
139 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
140 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
141 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
142 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
143 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
144 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
145 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
146 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
147 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
148 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
149 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
150 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
151 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
152 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
153 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
154 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
155 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
156 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
157 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
158 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
159 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
160 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
161 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
162 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
163 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
164 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
165 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
166 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
167 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
168 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
169 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
170 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
171 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
172 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
173 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
174 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
175 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
176 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
177 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
178 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
179 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
180 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
181 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
182 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
183 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
184 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
185 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
186 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
187 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
188 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
189 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
190 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
191 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
192 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
193 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
194 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
195 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
196 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
197 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
198 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
199 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
200 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
201 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
202 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
203 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
204 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
205 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
206 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
207 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
208 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
209 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
210 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
211 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
212 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
213 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
214 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
215 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
216 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
217 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
218 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
219 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
220 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
221 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
222 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
223 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
224 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
225 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
226 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
227 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
228 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
229 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
230 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
231 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
232 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
233 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
234 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
235 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
236 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
237 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
238 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
239 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
240 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
241 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
242 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
243 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
244 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
245 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
246 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
247 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
248 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
249 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
250 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
251 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
252 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
253 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
254 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
255 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
256 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
257 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
258 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
259 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
260 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
261 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
262 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
263 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
264 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
265 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
266 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
267 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
268 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
269 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
270 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
271 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
272 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
273 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
274 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
275 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
276 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
277 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
278 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
279 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
280 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
281 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
282 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
283 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
284 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
285 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
286 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
287 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
288 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
289 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
290 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
291 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
292 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
293 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
294 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6,
295};
296
297/*
298 * Round loop unrolling macros, S is a pointer to a S-Box array
299 * organized in 4 unsigned longs at a row.
300 */
301#define GET32_3(x) (((x) & 0xff))
302#define GET32_2(x) (((x) >> (8)) & (0xff))
303#define GET32_1(x) (((x) >> (16)) & (0xff))
304#define GET32_0(x) (((x) >> (24)) & (0xff))
305
306#define bf_F(x) (((S[GET32_0(x)] + S[256 + GET32_1(x)]) ^ \
307 S[512 + GET32_2(x)]) + S[768 + GET32_3(x)])
308
309#define ROUND(a, b, n) ({ b ^= P[n]; a ^= bf_F(b); })
310
311/*
312 * The blowfish encipher, processes 64-bit blocks.
313 * NOTE: This function MUSTN'T respect endianess
314 */
315static void encrypt_block(struct bf_ctx *bctx, u32 *dst, u32 *src)
316{
317 const u32 *P = bctx->p;
318 const u32 *S = bctx->s;
319 u32 yl = src[0];
320 u32 yr = src[1];
321
322 ROUND(yr, yl, 0);
323 ROUND(yl, yr, 1);
324 ROUND(yr, yl, 2);
325 ROUND(yl, yr, 3);
326 ROUND(yr, yl, 4);
327 ROUND(yl, yr, 5);
328 ROUND(yr, yl, 6);
329 ROUND(yl, yr, 7);
330 ROUND(yr, yl, 8);
331 ROUND(yl, yr, 9);
332 ROUND(yr, yl, 10);
333 ROUND(yl, yr, 11);
334 ROUND(yr, yl, 12);
335 ROUND(yl, yr, 13);
336 ROUND(yr, yl, 14);
337 ROUND(yl, yr, 15);
338
339 yl ^= P[16];
340 yr ^= P[17];
341
342 dst[0] = yr;
343 dst[1] = yl;
344}
345
346/*
347 * Calculates the blowfish S and P boxes for encryption and decryption.
348 */
349int blowfish_setkey(struct crypto_tfm *tfm, const u8 *key, unsigned int keylen)
350{
351 struct bf_ctx *ctx = crypto_tfm_ctx(tfm);
352 u32 *P = ctx->p;
353 u32 *S = ctx->s;
354 short i, j, count;
355 u32 data[2], temp;
356
357 /* Copy the initialization s-boxes */
358 for (i = 0, count = 0; i < 256; i++)
359 for (j = 0; j < 4; j++, count++)
360 S[count] = bf_sbox[count];
361
362 /* Set the p-boxes */
363 for (i = 0; i < 16 + 2; i++)
364 P[i] = bf_pbox[i];
365
366 /* Actual subkey generation */
367 for (j = 0, i = 0; i < 16 + 2; i++) {
368 temp = (((u32)key[j] << 24) |
369 ((u32)key[(j + 1) % keylen] << 16) |
370 ((u32)key[(j + 2) % keylen] << 8) |
371 ((u32)key[(j + 3) % keylen]));
372
373 P[i] = P[i] ^ temp;
374 j = (j + 4) % keylen;
375 }
376
377 data[0] = 0x00000000;
378 data[1] = 0x00000000;
379
380 for (i = 0; i < 16 + 2; i += 2) {
381 encrypt_block((struct bf_ctx *)ctx, data, data);
382
383 P[i] = data[0];
384 P[i + 1] = data[1];
385 }
386
387 for (i = 0; i < 4; i++) {
388 for (j = 0, count = i * 256; j < 256; j += 2, count += 2) {
389 encrypt_block((struct bf_ctx *)ctx, data, data);
390
391 S[count] = data[0];
392 S[count + 1] = data[1];
393 }
394 }
395
396 /* Bruce says not to bother with the weak key check. */
397 return 0;
398}
399EXPORT_SYMBOL_GPL(blowfish_setkey);
400
401MODULE_LICENSE("GPL");
402MODULE_DESCRIPTION("Blowfish Cipher common functions");
diff --git a/include/crypto/blowfish.h b/include/crypto/blowfish.h
new file mode 100644
index 000000000000..1450d4a27980
--- /dev/null
+++ b/include/crypto/blowfish.h
@@ -0,0 +1,23 @@
1/*
2 * Common values for blowfish algorithms
3 */
4
5#ifndef _CRYPTO_BLOWFISH_H
6#define _CRYPTO_BLOWFISH_H
7
8#include <linux/types.h>
9#include <linux/crypto.h>
10
11#define BF_BLOCK_SIZE 8
12#define BF_MIN_KEY_SIZE 4
13#define BF_MAX_KEY_SIZE 56
14
15struct bf_ctx {
16 u32 p[18];
17 u32 s[1024];
18};
19
20int blowfish_setkey(struct crypto_tfm *tfm, const u8 *key,
21 unsigned int key_len);
22
23#endif