linux/drivers/isdn/mISDN/dsp_blowfish.c
<<
>>
Prefs
   1/*
   2 * Blowfish encryption/decryption for mISDN_dsp.
   3 *
   4 * Copyright Andreas Eversberg (jolly@eversberg.eu)
   5 *
   6 * This software may be used and distributed according to the terms
   7 * of the GNU General Public License, incorporated herein by reference.
   8 *
   9 */
  10
  11#include <linux/mISDNif.h>
  12#include <linux/mISDNdsp.h>
  13#include "core.h"
  14#include "dsp.h"
  15
  16/*
  17 * how to encode a sample stream to 64-bit blocks that will be encryped
  18 *
  19 * first of all, data is collected until a block of 9 samples are received.
  20 * of course, a packet may have much more than 9 sample, but is may have
  21 * not excacly the multiple of 9 samples. if there is a rest, the next
  22 * received data will complete the block.
  23 *
  24 * the block is then converted to 9 uLAW samples without the least sigificant
  25 * bit. the result is a 7-bit encoded sample.
  26 *
  27 * the samples will be reoganised to form 8 bytes of data:
  28 * (5(6) means: encoded sample no. 5, bit 6)
  29 *
  30 * 0(6) 0(5) 0(4) 0(3) 0(2) 0(1) 0(0) 1(6)
  31 * 1(5) 1(4) 1(3) 1(2) 1(1) 1(0) 2(6) 2(5)
  32 * 2(4) 2(3) 2(2) 2(1) 2(0) 3(6) 3(5) 3(4)
  33 * 3(3) 3(2) 3(1) 3(0) 4(6) 4(5) 4(4) 4(3)
  34 * 4(2) 4(1) 4(0) 5(6) 5(5) 5(4) 5(3) 5(2)
  35 * 5(1) 5(0) 6(6) 6(5) 6(4) 6(3) 6(2) 6(1)
  36 * 6(0) 7(6) 7(5) 7(4) 7(3) 7(2) 7(1) 7(0)
  37 * 8(6) 8(5) 8(4) 8(3) 8(2) 8(1) 8(0)
  38 *
  39 * the missing bit 0 of the last byte is filled with some
  40 * random noise, to fill all 8 bytes.
  41 *
  42 * the 8 bytes will be encrypted using blowfish.
  43 *
  44 * the result will be converted into 9 bytes. the bit 7 is used for
  45 * checksumme (CS) for sync (0, 1) and for the last bit:
  46 * (5(6) means: crypted byte 5, bit 6)
  47 *
  48 * 1    0(7) 0(6) 0(5) 0(4) 0(3) 0(2) 0(1)
  49 * 0    0(0) 1(7) 1(6) 1(5) 1(4) 1(3) 1(2)
  50 * 0    1(1) 1(0) 2(7) 2(6) 2(5) 2(4) 2(3)
  51 * 0    2(2) 2(1) 2(0) 3(7) 3(6) 3(5) 3(4)
  52 * 0    3(3) 3(2) 3(1) 3(0) 4(7) 4(6) 4(5)
  53 * CS   4(4) 4(3) 4(2) 4(1) 4(0) 5(7) 5(6)
  54 * CS   5(5) 5(4) 5(3) 5(2) 5(1) 5(0) 6(7)
  55 * CS   6(6) 6(5) 6(4) 6(3) 6(2) 6(1) 6(0)
  56 * 7(0) 7(6) 7(5) 7(4) 7(3) 7(2) 7(1) 7(0)
  57 *
  58 * the checksum is used to detect transmission errors and frame drops.
  59 *
  60 * synchronisation of received block is done by shifting the upper bit of each
  61 * byte (bit 7) to a shift register. if the rigister has the first five bits
  62 * (10000), this is used to find the sync. only if sync has been found, the
  63 * current block of 9 received bytes are decrypted. before that the check
  64 * sum is calculated. if it is incorrect the block is dropped.
  65 * this will avoid loud noise due to corrupt encrypted data.
  66 *
  67 * if the last block is corrupt, the current decoded block is repeated
  68 * until a valid block has been received.
  69 */
  70
  71/*
  72 *  some blowfish parts are taken from the
  73 * crypto-api for faster implementation
  74 */
  75
  76struct bf_ctx {
  77        u32 p[18];
  78        u32 s[1024];
  79};
  80
  81static const u32 bf_pbox[16 + 2] = {
  82        0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
  83        0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
  84        0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
  85        0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
  86        0x9216d5d9, 0x8979fb1b,
  87};
  88
  89static const u32 bf_sbox[256 * 4] = {
  90        0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
  91        0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
  92        0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
  93        0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
  94        0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
  95        0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
  96        0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
  97        0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
  98        0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
  99        0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
 100        0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
 101        0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
 102        0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
 103        0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
 104        0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
 105        0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
 106        0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
 107        0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
 108        0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
 109        0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
 110        0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
 111        0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
 112        0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
 113        0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
 114        0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
 115        0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
 116        0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
 117        0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
 118        0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
 119        0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
 120        0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
 121        0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
 122        0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
 123        0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
 124        0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
 125        0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
 126        0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
 127        0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
 128        0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
 129        0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
 130        0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
 131        0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
 132        0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
 133        0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
 134        0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
 135        0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
 136        0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
 137        0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
 138        0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
 139        0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
 140        0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
 141        0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
 142        0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
 143        0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
 144        0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
 145        0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
 146        0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
 147        0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
 148        0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
 149        0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
 150        0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
 151        0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
 152        0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
 153        0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
 154        0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
 155        0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
 156        0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
 157        0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
 158        0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
 159        0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
 160        0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
 161        0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
 162        0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
 163        0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
 164        0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
 165        0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
 166        0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
 167        0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
 168        0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
 169        0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
 170        0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
 171        0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
 172        0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
 173        0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
 174        0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
 175        0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
 176        0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
 177        0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
 178        0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
 179        0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
 180        0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
 181        0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
 182        0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
 183        0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
 184        0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
 185        0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
 186        0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
 187        0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
 188        0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
 189        0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
 190        0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
 191        0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
 192        0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
 193        0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
 194        0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
 195        0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
 196        0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
 197        0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
 198        0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
 199        0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
 200        0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
 201        0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
 202        0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
 203        0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
 204        0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
 205        0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
 206        0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
 207        0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
 208        0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
 209        0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
 210        0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
 211        0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
 212        0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
 213        0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
 214        0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
 215        0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
 216        0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
 217        0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
 218        0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
 219        0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
 220        0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
 221        0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
 222        0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
 223        0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
 224        0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
 225        0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
 226        0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
 227        0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
 228        0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
 229        0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
 230        0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
 231        0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
 232        0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
 233        0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
 234        0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
 235        0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
 236        0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
 237        0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
 238        0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
 239        0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
 240        0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
 241        0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
 242        0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
 243        0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
 244        0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
 245        0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
 246        0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
 247        0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
 248        0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
 249        0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
 250        0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
 251        0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
 252        0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
 253        0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
 254        0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
 255        0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
 256        0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
 257        0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
 258        0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
 259        0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
 260        0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
 261        0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
 262        0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
 263        0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
 264        0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
 265        0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
 266        0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
 267        0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
 268        0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
 269        0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
 270        0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
 271        0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
 272        0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
 273        0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
 274        0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
 275        0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
 276        0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
 277        0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
 278        0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
 279        0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
 280        0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
 281        0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
 282        0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
 283        0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
 284        0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
 285        0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
 286        0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
 287        0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
 288        0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
 289        0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
 290        0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
 291        0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
 292        0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
 293        0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
 294        0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
 295        0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
 296        0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
 297        0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
 298        0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
 299        0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
 300        0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
 301        0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
 302        0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
 303        0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
 304        0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
 305        0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
 306        0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
 307        0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
 308        0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
 309        0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
 310        0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
 311        0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
 312        0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
 313        0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
 314        0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
 315        0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
 316        0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
 317        0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
 318        0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
 319        0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
 320        0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
 321        0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
 322        0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
 323        0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
 324        0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
 325        0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
 326        0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
 327        0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
 328        0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
 329        0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
 330        0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
 331        0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
 332        0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
 333        0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
 334        0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
 335        0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
 336        0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
 337        0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
 338        0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
 339        0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
 340        0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
 341        0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
 342        0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
 343        0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
 344        0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
 345        0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6,
 346};
 347
 348/*
 349 * Round loop unrolling macros, S is a pointer to a S-Box array
 350 * organized in 4 unsigned longs at a row.
 351 */
 352#define GET32_3(x) (((x) & 0xff))
 353#define GET32_2(x) (((x) >> (8)) & (0xff))
 354#define GET32_1(x) (((x) >> (16)) & (0xff))
 355#define GET32_0(x) (((x) >> (24)) & (0xff))
 356
 357#define bf_F(x) (((S[GET32_0(x)] + S[256 + GET32_1(x)]) ^ \
 358    S[512 + GET32_2(x)]) + S[768 + GET32_3(x)])
 359
 360#define EROUND(a, b, n)  do { b ^= P[n]; a ^= bf_F(b); } while (0)
 361#define DROUND(a, b, n)  do { a ^= bf_F(b); b ^= P[n]; } while (0)
 362
 363
 364/*
 365 * encrypt isdn data frame
 366 * every block with 9 samples is encrypted
 367 */
 368void
 369dsp_bf_encrypt(struct dsp *dsp, u8 *data, int len)
 370{
 371        int i = 0, j = dsp->bf_crypt_pos;
 372        u8 *bf_data_in = dsp->bf_data_in;
 373        u8 *bf_crypt_out = dsp->bf_crypt_out;
 374        u32 *P = dsp->bf_p;
 375        u32 *S = dsp->bf_s;
 376        u32 yl, yr;
 377        u32 cs;
 378        u8 nibble;
 379
 380        while (i < len) {
 381                /* collect a block of 9 samples */
 382                if (j < 9) {
 383                        bf_data_in[j] = *data;
 384                        *data++ = bf_crypt_out[j++];
 385                        i++;
 386                        continue;
 387                }
 388                j = 0;
 389                /* transcode 9 samples xlaw to 8 bytes */
 390                yl = dsp_audio_law2seven[bf_data_in[0]];
 391                yl = (yl<<7) | dsp_audio_law2seven[bf_data_in[1]];
 392                yl = (yl<<7) | dsp_audio_law2seven[bf_data_in[2]];
 393                yl = (yl<<7) | dsp_audio_law2seven[bf_data_in[3]];
 394                nibble = dsp_audio_law2seven[bf_data_in[4]];
 395                yr = nibble;
 396                yl = (yl<<4) | (nibble>>3);
 397                yr = (yr<<7) | dsp_audio_law2seven[bf_data_in[5]];
 398                yr = (yr<<7) | dsp_audio_law2seven[bf_data_in[6]];
 399                yr = (yr<<7) | dsp_audio_law2seven[bf_data_in[7]];
 400                yr = (yr<<7) | dsp_audio_law2seven[bf_data_in[8]];
 401                yr = (yr<<1) | (bf_data_in[0] & 1);
 402
 403                /* fill unused bit with random noise of audio input */
 404                /* encrypt */
 405
 406                EROUND(yr, yl, 0);
 407                EROUND(yl, yr, 1);
 408                EROUND(yr, yl, 2);
 409                EROUND(yl, yr, 3);
 410                EROUND(yr, yl, 4);
 411                EROUND(yl, yr, 5);
 412                EROUND(yr, yl, 6);
 413                EROUND(yl, yr, 7);
 414                EROUND(yr, yl, 8);
 415                EROUND(yl, yr, 9);
 416                EROUND(yr, yl, 10);
 417                EROUND(yl, yr, 11);
 418                EROUND(yr, yl, 12);
 419                EROUND(yl, yr, 13);
 420                EROUND(yr, yl, 14);
 421                EROUND(yl, yr, 15);
 422                yl ^= P[16];
 423                yr ^= P[17];
 424
 425                /* calculate 3-bit checksumme */
 426                cs = yl ^ (yl>>3) ^ (yl>>6) ^ (yl>>9) ^ (yl>>12) ^ (yl>>15)
 427                        ^ (yl>>18) ^ (yl>>21) ^ (yl>>24) ^ (yl>>27) ^ (yl>>30)
 428                        ^ (yr<<2) ^ (yr>>1) ^ (yr>>4) ^ (yr>>7) ^ (yr>>10)
 429                        ^ (yr>>13) ^ (yr>>16) ^ (yr>>19) ^ (yr>>22) ^ (yr>>25)
 430                        ^ (yr>>28) ^ (yr>>31);
 431
 432                /*
 433                 * transcode 8 crypted bytes to 9 data bytes with sync
 434                 * and checksum information
 435                 */
 436                bf_crypt_out[0] = (yl>>25) | 0x80;
 437                bf_crypt_out[1] = (yl>>18) & 0x7f;
 438                bf_crypt_out[2] = (yl>>11) & 0x7f;
 439                bf_crypt_out[3] = (yl>>4) & 0x7f;
 440                bf_crypt_out[4] = ((yl<<3) & 0x78) | ((yr>>29) & 0x07);
 441                bf_crypt_out[5] = ((yr>>22) & 0x7f) | ((cs<<5) & 0x80);
 442                bf_crypt_out[6] = ((yr>>15) & 0x7f) | ((cs<<6) & 0x80);
 443                bf_crypt_out[7] = ((yr>>8) & 0x7f) | (cs<<7);
 444                bf_crypt_out[8] = yr;
 445        }
 446
 447        /* write current count */
 448        dsp->bf_crypt_pos = j;
 449
 450}
 451
 452
 453/*
 454 * decrypt isdn data frame
 455 * every block with 9 bytes is decrypted
 456 */
 457void
 458dsp_bf_decrypt(struct dsp *dsp, u8 *data, int len)
 459{
 460        int i = 0;
 461        u8 j = dsp->bf_decrypt_in_pos;
 462        u8 k = dsp->bf_decrypt_out_pos;
 463        u8 *bf_crypt_inring = dsp->bf_crypt_inring;
 464        u8 *bf_data_out = dsp->bf_data_out;
 465        u16 sync = dsp->bf_sync;
 466        u32 *P = dsp->bf_p;
 467        u32 *S = dsp->bf_s;
 468        u32 yl, yr;
 469        u8 nibble;
 470        u8 cs, cs0, cs1, cs2;
 471
 472        while (i < len) {
 473                /*
 474                 * shift upper bit and rotate data to buffer ring
 475                 * send current decrypted data
 476                 */
 477                sync = (sync<<1) | ((*data)>>7);
 478                bf_crypt_inring[j++ & 15] = *data;
 479                *data++ = bf_data_out[k++];
 480                i++;
 481                if (k == 9)
 482                        k = 0; /* repeat if no sync has been found */
 483                /* check if not in sync */
 484                if ((sync&0x1f0) != 0x100)
 485                        continue;
 486                j -= 9;
 487                /* transcode receive data to 64 bit block of encrypted data */
 488                yl = bf_crypt_inring[j++ & 15];
 489                yl = (yl<<7) | bf_crypt_inring[j++ & 15]; /* bit7 = 0 */
 490                yl = (yl<<7) | bf_crypt_inring[j++ & 15]; /* bit7 = 0 */
 491                yl = (yl<<7) | bf_crypt_inring[j++ & 15]; /* bit7 = 0 */
 492                nibble = bf_crypt_inring[j++ & 15]; /* bit7 = 0 */
 493                yr = nibble;
 494                yl = (yl<<4) | (nibble>>3);
 495                cs2 = bf_crypt_inring[j++ & 15];
 496                yr = (yr<<7) | (cs2 & 0x7f);
 497                cs1 = bf_crypt_inring[j++ & 15];
 498                yr = (yr<<7) | (cs1 & 0x7f);
 499                cs0 = bf_crypt_inring[j++ & 15];
 500                yr = (yr<<7) | (cs0 & 0x7f);
 501                yr = (yr<<8) | bf_crypt_inring[j++ & 15];
 502
 503                /* calculate 3-bit checksumme */
 504                cs = yl ^ (yl>>3) ^ (yl>>6) ^ (yl>>9) ^ (yl>>12) ^ (yl>>15)
 505                        ^ (yl>>18) ^ (yl>>21) ^ (yl>>24) ^ (yl>>27) ^ (yl>>30)
 506                        ^ (yr<<2) ^ (yr>>1) ^ (yr>>4) ^ (yr>>7) ^ (yr>>10)
 507                        ^ (yr>>13) ^ (yr>>16) ^ (yr>>19) ^ (yr>>22) ^ (yr>>25)
 508                        ^ (yr>>28) ^ (yr>>31);
 509
 510                /* check if frame is valid */
 511                if ((cs&0x7) != (((cs2>>5)&4) | ((cs1>>6)&2) | (cs0 >> 7))) {
 512                        if (dsp_debug & DEBUG_DSP_BLOWFISH)
 513                                printk(KERN_DEBUG
 514                                    "DSP BLOWFISH: received corrupt frame, "
 515                                    "checksumme is not correct\n");
 516                        continue;
 517                }
 518
 519                /* decrypt */
 520                yr ^= P[17];
 521                yl ^= P[16];
 522                DROUND(yl, yr, 15);
 523                DROUND(yr, yl, 14);
 524                DROUND(yl, yr, 13);
 525                DROUND(yr, yl, 12);
 526                DROUND(yl, yr, 11);
 527                DROUND(yr, yl, 10);
 528                DROUND(yl, yr, 9);
 529                DROUND(yr, yl, 8);
 530                DROUND(yl, yr, 7);
 531                DROUND(yr, yl, 6);
 532                DROUND(yl, yr, 5);
 533                DROUND(yr, yl, 4);
 534                DROUND(yl, yr, 3);
 535                DROUND(yr, yl, 2);
 536                DROUND(yl, yr, 1);
 537                DROUND(yr, yl, 0);
 538
 539                /* transcode 8 crypted bytes to 9 sample bytes */
 540                bf_data_out[0] = dsp_audio_seven2law[(yl>>25) & 0x7f];
 541                bf_data_out[1] = dsp_audio_seven2law[(yl>>18) & 0x7f];
 542                bf_data_out[2] = dsp_audio_seven2law[(yl>>11) & 0x7f];
 543                bf_data_out[3] = dsp_audio_seven2law[(yl>>4) & 0x7f];
 544                bf_data_out[4] = dsp_audio_seven2law[((yl<<3) & 0x78) |
 545                    ((yr>>29) & 0x07)];
 546
 547                bf_data_out[5] = dsp_audio_seven2law[(yr>>22) & 0x7f];
 548                bf_data_out[6] = dsp_audio_seven2law[(yr>>15) & 0x7f];
 549                bf_data_out[7] = dsp_audio_seven2law[(yr>>8) & 0x7f];
 550                bf_data_out[8] = dsp_audio_seven2law[(yr>>1) & 0x7f];
 551                k = 0; /* start with new decoded frame */
 552        }
 553
 554        /* write current count and sync */
 555        dsp->bf_decrypt_in_pos = j;
 556        dsp->bf_decrypt_out_pos = k;
 557        dsp->bf_sync = sync;
 558}
 559
 560
 561/* used to encrypt S and P boxes */
 562static inline void
 563encrypt_block(const u32 *P, const u32 *S, u32 *dst, u32 *src)
 564{
 565        u32 yl = src[0];
 566        u32 yr = src[1];
 567
 568        EROUND(yr, yl, 0);
 569        EROUND(yl, yr, 1);
 570        EROUND(yr, yl, 2);
 571        EROUND(yl, yr, 3);
 572        EROUND(yr, yl, 4);
 573        EROUND(yl, yr, 5);
 574        EROUND(yr, yl, 6);
 575        EROUND(yl, yr, 7);
 576        EROUND(yr, yl, 8);
 577        EROUND(yl, yr, 9);
 578        EROUND(yr, yl, 10);
 579        EROUND(yl, yr, 11);
 580        EROUND(yr, yl, 12);
 581        EROUND(yl, yr, 13);
 582        EROUND(yr, yl, 14);
 583        EROUND(yl, yr, 15);
 584
 585        yl ^= P[16];
 586        yr ^= P[17];
 587
 588        dst[0] = yr;
 589        dst[1] = yl;
 590}
 591
 592/*
 593 * initialize the dsp for encryption and decryption using the same key
 594 * Calculates the blowfish S and P boxes for encryption and decryption.
 595 * The margin of keylen must be 4-56 bytes.
 596 * returns 0 if ok.
 597 */
 598int
 599dsp_bf_init(struct dsp *dsp, const u8 *key, uint keylen)
 600{
 601        short i, j, count;
 602        u32 data[2], temp;
 603        u32 *P = (u32 *)dsp->bf_p;
 604        u32 *S = (u32 *)dsp->bf_s;
 605
 606        if (keylen < 4 || keylen > 56)
 607                return 1;
 608
 609        /* Set dsp states */
 610        i = 0;
 611        while (i < 9) {
 612                dsp->bf_crypt_out[i] = 0xff;
 613                dsp->bf_data_out[i] = dsp_silence;
 614                i++;
 615        }
 616        dsp->bf_crypt_pos = 0;
 617        dsp->bf_decrypt_in_pos = 0;
 618        dsp->bf_decrypt_out_pos = 0;
 619        dsp->bf_sync = 0x1ff;
 620        dsp->bf_enable = 1;
 621
 622        /* Copy the initialization s-boxes */
 623        for (i = 0, count = 0; i < 256; i++)
 624                for (j = 0; j < 4; j++, count++)
 625                        S[count] = bf_sbox[count];
 626
 627        /* Set the p-boxes */
 628        for (i = 0; i < 16 + 2; i++)
 629                P[i] = bf_pbox[i];
 630
 631        /* Actual subkey generation */
 632        for (j = 0, i = 0; i < 16 + 2; i++) {
 633                temp = (((u32)key[j] << 24) |
 634                    ((u32)key[(j + 1) % keylen] << 16) |
 635                    ((u32)key[(j + 2) % keylen] << 8) |
 636                    ((u32)key[(j + 3) % keylen]));
 637
 638                P[i] = P[i] ^ temp;
 639                j = (j + 4) % keylen;
 640        }
 641
 642        data[0] = 0x00000000;
 643        data[1] = 0x00000000;
 644
 645        for (i = 0; i < 16 + 2; i += 2) {
 646                encrypt_block(P, S, data, data);
 647
 648                P[i] = data[0];
 649                P[i + 1] = data[1];
 650        }
 651
 652        for (i = 0; i < 4; i++) {
 653                for (j = 0, count = i * 256; j < 256; j += 2, count += 2) {
 654                        encrypt_block(P, S, data, data);
 655
 656                        S[count] = data[0];
 657                        S[count + 1] = data[1];
 658                }
 659        }
 660
 661        return 0;
 662}
 663
 664
 665/*
 666 * turn encryption off
 667 */
 668void
 669dsp_bf_cleanup(struct dsp *dsp)
 670{
 671        dsp->bf_enable = 0;
 672}
 673