Commit initial NetBSD port of the OpenCrypto Framework (OCF). This

code is derived from Sam Leffler's FreeBSD port of OCF, which is in
turn a port of Angelos Keromytis's OpenBSD work.
Credit to Sam and Angelos, any blame for the NetBSD port to me.
This commit is contained in:
jonathan 2003-07-25 21:12:39 +00:00
parent 0f6cc2d0c8
commit cdfce9ce5e
27 changed files with 9111 additions and 1 deletions

View File

@ -1,4 +1,4 @@
# $NetBSD: files,v 1.620 2003/07/25 10:00:51 itojun Exp $ # $NetBSD: files,v 1.621 2003/07/25 21:12:39 jonathan Exp $
# @(#)files.newconf 7.5 (Berkeley) 5/10/93 # @(#)files.newconf 7.5 (Berkeley) 5/10/93
@ -1265,3 +1265,6 @@ device joy
file dev/ic/joy.c joy needs-flag file dev/ic/joy.c joy needs-flag
file dev/ieee1394/fwiso.c fwiso needs-count file dev/ieee1394/fwiso.c fwiso needs-count
#
include "opencrypto/files.opencrypto"
include "netipsec/files.ipsec"

16
sys/netipsec/files.ipsec Normal file
View File

@ -0,0 +1,16 @@
# $Id: files.ipsec,v 1.1 2003/07/25 21:12:40 jonathan Exp $
#
#
defflag fast_ipsec
file netipsec/ipsec.c fast_ipsec
file netipsec/ipsec_input.c fast_ipsec
file netipsec/ipsec_mbuf.c fast_ipsec
file netipsec/ipsec_output.c fast_ipsec
file netipsec/key.c fast_ipsec
file netipsec/key_debug.c fast_ipsec
file netipsec/keysock.c fast_ipsec
file netipsec/xform_ah.c fast_ipsec
file netipsec/xform_esp.c fast_ipsec
file netipsec/xform_ipcomp.c fast_ipsec
file netipsec/xform_ipip.c fast_ipsec

668
sys/opencrypto/blf.c Normal file
View File

@ -0,0 +1,668 @@
/* $NetBSD: blf.c,v 1.1 2003/07/25 21:12:41 jonathan Exp $ */
/* $OpenBSD: blf.c,v 1.4 2002/03/15 18:19:52 millert Exp $ */
/*
* Blowfish block cipher for OpenBSD
* Copyright 1997 Niels Provos <provos@physnet.uni-hamburg.de>
* All rights reserved.
*
* Implementation advice by David Mazieres <dm@lcs.mit.edu>.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by Niels Provos.
* 4. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
/*
* This code is derived from section 14.3 and the given source
* in section V of Applied Cryptography, second edition.
* Blowfish is an unpatented fast block cipher designed by
* Bruce Schneier.
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: blf.c,v 1.1 2003/07/25 21:12:41 jonathan Exp $");
#include <sys/param.h>
#include <sys/systm.h>
#include <opencrypto/blf.h>
#undef inline
#ifdef __GNUC__
#define inline __inline
#else /* !__GNUC__ */
#define inline
#endif /* !__GNUC__ */
/* Function for Feistel Networks */
#define F(s, x) ((((s)[ (((x)>>24)&0xFF)] \
+ (s)[0x100 + (((x)>>16)&0xFF)]) \
^ (s)[0x200 + (((x)>> 8)&0xFF)]) \
+ (s)[0x300 + ( (x) &0xFF)])
#define BLFRND(s,p,i,j,n) (i ^= F(s,j) ^ (p)[n])
void
Blowfish_encipher(c, x)
blf_ctx *c;
u_int32_t *x;
{
u_int32_t Xl;
u_int32_t Xr;
u_int32_t *s = c->S[0];
u_int32_t *p = c->P;
Xl = x[0];
Xr = x[1];
Xl ^= p[0];
BLFRND(s, p, Xr, Xl, 1); BLFRND(s, p, Xl, Xr, 2);
BLFRND(s, p, Xr, Xl, 3); BLFRND(s, p, Xl, Xr, 4);
BLFRND(s, p, Xr, Xl, 5); BLFRND(s, p, Xl, Xr, 6);
BLFRND(s, p, Xr, Xl, 7); BLFRND(s, p, Xl, Xr, 8);
BLFRND(s, p, Xr, Xl, 9); BLFRND(s, p, Xl, Xr, 10);
BLFRND(s, p, Xr, Xl, 11); BLFRND(s, p, Xl, Xr, 12);
BLFRND(s, p, Xr, Xl, 13); BLFRND(s, p, Xl, Xr, 14);
BLFRND(s, p, Xr, Xl, 15); BLFRND(s, p, Xl, Xr, 16);
x[0] = Xr ^ p[17];
x[1] = Xl;
}
void
Blowfish_decipher(c, x)
blf_ctx *c;
u_int32_t *x;
{
u_int32_t Xl;
u_int32_t Xr;
u_int32_t *s = c->S[0];
u_int32_t *p = c->P;
Xl = x[0];
Xr = x[1];
Xl ^= p[17];
BLFRND(s, p, Xr, Xl, 16); BLFRND(s, p, Xl, Xr, 15);
BLFRND(s, p, Xr, Xl, 14); BLFRND(s, p, Xl, Xr, 13);
BLFRND(s, p, Xr, Xl, 12); BLFRND(s, p, Xl, Xr, 11);
BLFRND(s, p, Xr, Xl, 10); BLFRND(s, p, Xl, Xr, 9);
BLFRND(s, p, Xr, Xl, 8); BLFRND(s, p, Xl, Xr, 7);
BLFRND(s, p, Xr, Xl, 6); BLFRND(s, p, Xl, Xr, 5);
BLFRND(s, p, Xr, Xl, 4); BLFRND(s, p, Xl, Xr, 3);
BLFRND(s, p, Xr, Xl, 2); BLFRND(s, p, Xl, Xr, 1);
x[0] = Xr ^ p[0];
x[1] = Xl;
}
void
Blowfish_initstate(c)
blf_ctx *c;
{
/* P-box and S-box tables initialized with digits of Pi */
const blf_ctx initstate =
{ {
{
0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a},
{
0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7},
{
0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0},
{
0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6}
},
{
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
0x9216d5d9, 0x8979fb1b
} };
*c = initstate;
}
u_int32_t
Blowfish_stream2word(const u_int8_t *data, u_int16_t databytes, u_int16_t *current)
{
u_int8_t i;
u_int16_t j;
u_int32_t temp;
temp = 0x00000000;
j = *current;
for (i = 0; i < 4; i++, j++) {
if (j >= databytes)
j = 0;
temp = (temp << 8) | data[j];
}
*current = j;
return temp;
}
void
Blowfish_expand0state(blf_ctx *c, const u_int8_t *key, u_int16_t keybytes)
{
u_int16_t i;
u_int16_t j;
u_int16_t k;
u_int32_t temp;
u_int32_t data[2];
j = 0;
for (i = 0; i < BLF_N + 2; i++) {
/* Extract 4 int8 to 1 int32 from keystream */
temp = Blowfish_stream2word(key, keybytes, &j);
c->P[i] = c->P[i] ^ temp;
}
j = 0;
data[0] = 0x00000000;
data[1] = 0x00000000;
for (i = 0; i < BLF_N + 2; i += 2) {
Blowfish_encipher(c, data);
c->P[i] = data[0];
c->P[i + 1] = data[1];
}
for (i = 0; i < 4; i++) {
for (k = 0; k < 256; k += 2) {
Blowfish_encipher(c, data);
c->S[i][k] = data[0];
c->S[i][k + 1] = data[1];
}
}
}
void
Blowfish_expandstate(blf_ctx *c, const u_int8_t *data, u_int16_t databytes,
const u_int8_t *key, u_int16_t keybytes)
{
u_int16_t i;
u_int16_t j;
u_int16_t k;
u_int32_t temp;
u_int32_t d[2];
j = 0;
for (i = 0; i < BLF_N + 2; i++) {
/* Extract 4 int8 to 1 int32 from keystream */
temp = Blowfish_stream2word(key, keybytes, &j);
c->P[i] = c->P[i] ^ temp;
}
j = 0;
d[0] = 0x00000000;
d[1] = 0x00000000;
for (i = 0; i < BLF_N + 2; i += 2) {
d[0] ^= Blowfish_stream2word(data, databytes, &j);
d[1] ^= Blowfish_stream2word(data, databytes, &j);
Blowfish_encipher(c, d);
c->P[i] = d[0];
c->P[i + 1] = d[1];
}
for (i = 0; i < 4; i++) {
for (k = 0; k < 256; k += 2) {
d[0]^= Blowfish_stream2word(data, databytes, &j);
d[1] ^= Blowfish_stream2word(data, databytes, &j);
Blowfish_encipher(c, d);
c->S[i][k] = d[0];
c->S[i][k + 1] = d[1];
}
}
}
void
blf_key(blf_ctx *c, const u_int8_t *k, u_int16_t len)
{
/* Initalize S-boxes and subkeys with Pi */
Blowfish_initstate(c);
/* Transform S-boxes and subkeys with key */
Blowfish_expand0state(c, k, len);
}
void
blf_enc(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
{
u_int32_t *d;
u_int16_t i;
d = data;
for (i = 0; i < blocks; i++) {
Blowfish_encipher(c, d);
d += 2;
}
}
void
blf_dec(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
{
u_int32_t *d;
u_int16_t i;
d = data;
for (i = 0; i < blocks; i++) {
Blowfish_decipher(c, d);
d += 2;
}
}
void
blf_ecb_encrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
{
u_int32_t l, r, d[2];
u_int32_t i;
for (i = 0; i < len; i += 8) {
l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
d[0] = l;
d[1] = r;
Blowfish_encipher(c, d);
l = d[0];
r = d[1];
data[0] = l >> 24 & 0xff;
data[1] = l >> 16 & 0xff;
data[2] = l >> 8 & 0xff;
data[3] = l & 0xff;
data[4] = r >> 24 & 0xff;
data[5] = r >> 16 & 0xff;
data[6] = r >> 8 & 0xff;
data[7] = r & 0xff;
data += 8;
}
}
void
blf_ecb_decrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
{
u_int32_t l, r, d[2];
u_int32_t i;
for (i = 0; i < len; i += 8) {
l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
d[0] = l;
d[1] = r;
Blowfish_decipher(c, d);
l = d[0];
r = d[1];
data[0] = l >> 24 & 0xff;
data[1] = l >> 16 & 0xff;
data[2] = l >> 8 & 0xff;
data[3] = l & 0xff;
data[4] = r >> 24 & 0xff;
data[5] = r >> 16 & 0xff;
data[6] = r >> 8 & 0xff;
data[7] = r & 0xff;
data += 8;
}
}
void
blf_cbc_encrypt(blf_ctx *c, u_int8_t *iv, u_int8_t *data, u_int32_t len)
{
u_int32_t l, r, d[2];
u_int32_t i, j;
for (i = 0; i < len; i += 8) {
for (j = 0; j < 8; j++)
data[j] ^= iv[j];
l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
d[0] = l;
d[1] = r;
Blowfish_encipher(c, d);
l = d[0];
r = d[1];
data[0] = l >> 24 & 0xff;
data[1] = l >> 16 & 0xff;
data[2] = l >> 8 & 0xff;
data[3] = l & 0xff;
data[4] = r >> 24 & 0xff;
data[5] = r >> 16 & 0xff;
data[6] = r >> 8 & 0xff;
data[7] = r & 0xff;
iv = data;
data += 8;
}
}
void
blf_cbc_decrypt(blf_ctx *c, u_int8_t *iva, u_int8_t *data, u_int32_t len)
{
u_int32_t l, r, d[2];
u_int8_t *iv;
u_int32_t i, j;
iv = data + len - 16;
data = data + len - 8;
for (i = len - 8; i >= 8; i -= 8) {
l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
d[0] = l;
d[1] = r;
Blowfish_decipher(c, d);
l = d[0];
r = d[1];
data[0] = l >> 24 & 0xff;
data[1] = l >> 16 & 0xff;
data[2] = l >> 8 & 0xff;
data[3] = l & 0xff;
data[4] = r >> 24 & 0xff;
data[5] = r >> 16 & 0xff;
data[6] = r >> 8 & 0xff;
data[7] = r & 0xff;
for (j = 0; j < 8; j++)
data[j] ^= iv[j];
iv -= 8;
data -= 8;
}
l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
d[0] = l;
d[1] = r;
Blowfish_decipher(c, d);
l = d[0];
r = d[1];
data[0] = l >> 24 & 0xff;
data[1] = l >> 16 & 0xff;
data[2] = l >> 8 & 0xff;
data[3] = l & 0xff;
data[4] = r >> 24 & 0xff;
data[5] = r >> 16 & 0xff;
data[6] = r >> 8 & 0xff;
data[7] = r & 0xff;
for (j = 0; j < 8; j++)
data[j] ^= iva[j];
}

82
sys/opencrypto/blf.h Normal file
View File

@ -0,0 +1,82 @@
/* $NetBSD: blf.h,v 1.1 2003/07/25 21:12:42 jonathan Exp $ */
/* $OpenBSD: blf.h,v 1.5 2002/07/02 19:38:54 nate Exp $ */
/*
* Blowfish - a fast block cipher designed by Bruce Schneier
*
* Copyright 1997 Niels Provos <provos@physnet.uni-hamburg.de>
* All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by Niels Provos.
* 4. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef _BLF_H_
#define _BLF_H_
/* Schneier states the maximum key length to be 56 bytes.
* The way how the subkeys are initialized by the key up
* to (N+2)*4 i.e. 72 bytes are utilized.
* Warning: For normal blowfish encryption only 56 bytes
* of the key affect all cipherbits.
*/
#define BLF_N 16 /* Number of Subkeys */
#define BLF_MAXKEYLEN ((BLF_N-2)*4) /* 448 bits */
/* Blowfish context */
typedef struct BlowfishContext {
u_int32_t S[4][256]; /* S-Boxes */
u_int32_t P[BLF_N + 2]; /* Subkeys */
} blf_ctx;
/* Raw access to customized Blowfish
* blf_key is just:
* Blowfish_initstate( state )
* Blowfish_expand0state( state, key, keylen )
*/
void Blowfish_encipher(blf_ctx *, u_int32_t *);
void Blowfish_decipher(blf_ctx *, u_int32_t *);
void Blowfish_initstate(blf_ctx *);
void Blowfish_expand0state(blf_ctx *, const u_int8_t *, u_int16_t);
void Blowfish_expandstate(blf_ctx *, const u_int8_t *, u_int16_t, const u_int8_t *, u_int16_t);
/* Standard Blowfish */
void blf_key(blf_ctx *, const u_int8_t *, u_int16_t);
void blf_enc(blf_ctx *, u_int32_t *, u_int16_t);
void blf_dec(blf_ctx *, u_int32_t *, u_int16_t);
/* Converts u_int8_t to u_int32_t */
u_int32_t Blowfish_stream2word(const u_int8_t *, u_int16_t ,
u_int16_t *);
void blf_ecb_encrypt(blf_ctx *, u_int8_t *, u_int32_t);
void blf_ecb_decrypt(blf_ctx *, u_int8_t *, u_int32_t);
void blf_cbc_encrypt(blf_ctx *, u_int8_t *, u_int8_t *, u_int32_t);
void blf_cbc_decrypt(blf_ctx *, u_int8_t *, u_int8_t *, u_int32_t);
#endif

246
sys/opencrypto/cast.c Normal file
View File

@ -0,0 +1,246 @@
/* $NetBSD: cast.c,v 1.1 2003/07/25 21:12:42 jonathan Exp $ */
/* $OpenBSD: cast.c,v 1.2 2000/06/06 06:49:47 deraadt Exp $ */
/*
* CAST-128 in C
* Written by Steve Reid <sreid@sea-to-sky.net>
* 100% Public Domain - no warranty
* Released 1997.10.11
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: cast.c,v 1.1 2003/07/25 21:12:42 jonathan Exp $");
#include <sys/types.h>
#include <opencrypto/cast.h>
#include <opencrypto/castsb.h>
/* Macros to access 8-bit bytes out of a 32-bit word */
#define U_INT8_Ta(x) ( (u_int8_t) (x>>24) )
#define U_INT8_Tb(x) ( (u_int8_t) ((x>>16)&255) )
#define U_INT8_Tc(x) ( (u_int8_t) ((x>>8)&255) )
#define U_INT8_Td(x) ( (u_int8_t) ((x)&255) )
/* Circular left shift */
#define ROL(x, n) ( ((x)<<(n)) | ((x)>>(32-(n))) )
/* CAST-128 uses three different round functions */
#define F1(l, r, i) \
t = ROL(key->xkey[i] + r, key->xkey[i+16]); \
l ^= ((cast_sbox1[U_INT8_Ta(t)] ^ cast_sbox2[U_INT8_Tb(t)]) - \
cast_sbox3[U_INT8_Tc(t)]) + cast_sbox4[U_INT8_Td(t)];
#define F2(l, r, i) \
t = ROL(key->xkey[i] ^ r, key->xkey[i+16]); \
l ^= ((cast_sbox1[U_INT8_Ta(t)] - cast_sbox2[U_INT8_Tb(t)]) + \
cast_sbox3[U_INT8_Tc(t)]) ^ cast_sbox4[U_INT8_Td(t)];
#define F3(l, r, i) \
t = ROL(key->xkey[i] - r, key->xkey[i+16]); \
l ^= ((cast_sbox1[U_INT8_Ta(t)] + cast_sbox2[U_INT8_Tb(t)]) ^ \
cast_sbox3[U_INT8_Tc(t)]) - cast_sbox4[U_INT8_Td(t)];
/***** Encryption Function *****/
void cast_encrypt(cast_key* key, u_int8_t* inblock, u_int8_t* outblock)
{
u_int32_t t, l, r;
/* Get inblock into l,r */
l = ((u_int32_t)inblock[0] << 24) | ((u_int32_t)inblock[1] << 16) |
((u_int32_t)inblock[2] << 8) | (u_int32_t)inblock[3];
r = ((u_int32_t)inblock[4] << 24) | ((u_int32_t)inblock[5] << 16) |
((u_int32_t)inblock[6] << 8) | (u_int32_t)inblock[7];
/* Do the work */
F1(l, r, 0);
F2(r, l, 1);
F3(l, r, 2);
F1(r, l, 3);
F2(l, r, 4);
F3(r, l, 5);
F1(l, r, 6);
F2(r, l, 7);
F3(l, r, 8);
F1(r, l, 9);
F2(l, r, 10);
F3(r, l, 11);
/* Only do full 16 rounds if key length > 80 bits */
if (key->rounds > 12) {
F1(l, r, 12);
F2(r, l, 13);
F3(l, r, 14);
F1(r, l, 15);
}
/* Put l,r into outblock */
outblock[0] = U_INT8_Ta(r);
outblock[1] = U_INT8_Tb(r);
outblock[2] = U_INT8_Tc(r);
outblock[3] = U_INT8_Td(r);
outblock[4] = U_INT8_Ta(l);
outblock[5] = U_INT8_Tb(l);
outblock[6] = U_INT8_Tc(l);
outblock[7] = U_INT8_Td(l);
/* Wipe clean */
t = l = r = 0;
}
/***** Decryption Function *****/
void cast_decrypt(cast_key* key, u_int8_t* inblock, u_int8_t* outblock)
{
u_int32_t t, l, r;
/* Get inblock into l,r */
r = ((u_int32_t)inblock[0] << 24) | ((u_int32_t)inblock[1] << 16) |
((u_int32_t)inblock[2] << 8) | (u_int32_t)inblock[3];
l = ((u_int32_t)inblock[4] << 24) | ((u_int32_t)inblock[5] << 16) |
((u_int32_t)inblock[6] << 8) | (u_int32_t)inblock[7];
/* Do the work */
/* Only do full 16 rounds if key length > 80 bits */
if (key->rounds > 12) {
F1(r, l, 15);
F3(l, r, 14);
F2(r, l, 13);
F1(l, r, 12);
}
F3(r, l, 11);
F2(l, r, 10);
F1(r, l, 9);
F3(l, r, 8);
F2(r, l, 7);
F1(l, r, 6);
F3(r, l, 5);
F2(l, r, 4);
F1(r, l, 3);
F3(l, r, 2);
F2(r, l, 1);
F1(l, r, 0);
/* Put l,r into outblock */
outblock[0] = U_INT8_Ta(l);
outblock[1] = U_INT8_Tb(l);
outblock[2] = U_INT8_Tc(l);
outblock[3] = U_INT8_Td(l);
outblock[4] = U_INT8_Ta(r);
outblock[5] = U_INT8_Tb(r);
outblock[6] = U_INT8_Tc(r);
outblock[7] = U_INT8_Td(r);
/* Wipe clean */
t = l = r = 0;
}
/***** Key Schedual *****/
void cast_setkey(cast_key* key, u_int8_t* rawkey, int keybytes)
{
u_int32_t t[4], z[4], x[4];
int i;
/* Set number of rounds to 12 or 16, depending on key length */
key->rounds = (keybytes <= 10 ? 12 : 16);
/* Copy key to workspace x */
for (i = 0; i < 4; i++) {
x[i] = 0;
if ((i*4+0) < keybytes) x[i] = (u_int32_t)rawkey[i*4+0] << 24;
if ((i*4+1) < keybytes) x[i] |= (u_int32_t)rawkey[i*4+1] << 16;
if ((i*4+2) < keybytes) x[i] |= (u_int32_t)rawkey[i*4+2] << 8;
if ((i*4+3) < keybytes) x[i] |= (u_int32_t)rawkey[i*4+3];
}
/* Generate 32 subkeys, four at a time */
for (i = 0; i < 32; i+=4) {
switch (i & 4) {
case 0:
t[0] = z[0] = x[0] ^ cast_sbox5[U_INT8_Tb(x[3])] ^
cast_sbox6[U_INT8_Td(x[3])] ^ cast_sbox7[U_INT8_Ta(x[3])] ^
cast_sbox8[U_INT8_Tc(x[3])] ^ cast_sbox7[U_INT8_Ta(x[2])];
t[1] = z[1] = x[2] ^ cast_sbox5[U_INT8_Ta(z[0])] ^
cast_sbox6[U_INT8_Tc(z[0])] ^ cast_sbox7[U_INT8_Tb(z[0])] ^
cast_sbox8[U_INT8_Td(z[0])] ^ cast_sbox8[U_INT8_Tc(x[2])];
t[2] = z[2] = x[3] ^ cast_sbox5[U_INT8_Td(z[1])] ^
cast_sbox6[U_INT8_Tc(z[1])] ^ cast_sbox7[U_INT8_Tb(z[1])] ^
cast_sbox8[U_INT8_Ta(z[1])] ^ cast_sbox5[U_INT8_Tb(x[2])];
t[3] = z[3] = x[1] ^ cast_sbox5[U_INT8_Tc(z[2])] ^
cast_sbox6[U_INT8_Tb(z[2])] ^ cast_sbox7[U_INT8_Td(z[2])] ^
cast_sbox8[U_INT8_Ta(z[2])] ^ cast_sbox6[U_INT8_Td(x[2])];
break;
case 4:
t[0] = x[0] = z[2] ^ cast_sbox5[U_INT8_Tb(z[1])] ^
cast_sbox6[U_INT8_Td(z[1])] ^ cast_sbox7[U_INT8_Ta(z[1])] ^
cast_sbox8[U_INT8_Tc(z[1])] ^ cast_sbox7[U_INT8_Ta(z[0])];
t[1] = x[1] = z[0] ^ cast_sbox5[U_INT8_Ta(x[0])] ^
cast_sbox6[U_INT8_Tc(x[0])] ^ cast_sbox7[U_INT8_Tb(x[0])] ^
cast_sbox8[U_INT8_Td(x[0])] ^ cast_sbox8[U_INT8_Tc(z[0])];
t[2] = x[2] = z[1] ^ cast_sbox5[U_INT8_Td(x[1])] ^
cast_sbox6[U_INT8_Tc(x[1])] ^ cast_sbox7[U_INT8_Tb(x[1])] ^
cast_sbox8[U_INT8_Ta(x[1])] ^ cast_sbox5[U_INT8_Tb(z[0])];
t[3] = x[3] = z[3] ^ cast_sbox5[U_INT8_Tc(x[2])] ^
cast_sbox6[U_INT8_Tb(x[2])] ^ cast_sbox7[U_INT8_Td(x[2])] ^
cast_sbox8[U_INT8_Ta(x[2])] ^ cast_sbox6[U_INT8_Td(z[0])];
break;
}
switch (i & 12) {
case 0:
case 12:
key->xkey[i+0] = cast_sbox5[U_INT8_Ta(t[2])] ^ cast_sbox6[U_INT8_Tb(t[2])] ^
cast_sbox7[U_INT8_Td(t[1])] ^ cast_sbox8[U_INT8_Tc(t[1])];
key->xkey[i+1] = cast_sbox5[U_INT8_Tc(t[2])] ^ cast_sbox6[U_INT8_Td(t[2])] ^
cast_sbox7[U_INT8_Tb(t[1])] ^ cast_sbox8[U_INT8_Ta(t[1])];
key->xkey[i+2] = cast_sbox5[U_INT8_Ta(t[3])] ^ cast_sbox6[U_INT8_Tb(t[3])] ^
cast_sbox7[U_INT8_Td(t[0])] ^ cast_sbox8[U_INT8_Tc(t[0])];
key->xkey[i+3] = cast_sbox5[U_INT8_Tc(t[3])] ^ cast_sbox6[U_INT8_Td(t[3])] ^
cast_sbox7[U_INT8_Tb(t[0])] ^ cast_sbox8[U_INT8_Ta(t[0])];
break;
case 4:
case 8:
key->xkey[i+0] = cast_sbox5[U_INT8_Td(t[0])] ^ cast_sbox6[U_INT8_Tc(t[0])] ^
cast_sbox7[U_INT8_Ta(t[3])] ^ cast_sbox8[U_INT8_Tb(t[3])];
key->xkey[i+1] = cast_sbox5[U_INT8_Tb(t[0])] ^ cast_sbox6[U_INT8_Ta(t[0])] ^
cast_sbox7[U_INT8_Tc(t[3])] ^ cast_sbox8[U_INT8_Td(t[3])];
key->xkey[i+2] = cast_sbox5[U_INT8_Td(t[1])] ^ cast_sbox6[U_INT8_Tc(t[1])] ^
cast_sbox7[U_INT8_Ta(t[2])] ^ cast_sbox8[U_INT8_Tb(t[2])];
key->xkey[i+3] = cast_sbox5[U_INT8_Tb(t[1])] ^ cast_sbox6[U_INT8_Ta(t[1])] ^
cast_sbox7[U_INT8_Tc(t[2])] ^ cast_sbox8[U_INT8_Td(t[2])];
break;
}
switch (i & 12) {
case 0:
key->xkey[i+0] ^= cast_sbox5[U_INT8_Tc(z[0])];
key->xkey[i+1] ^= cast_sbox6[U_INT8_Tc(z[1])];
key->xkey[i+2] ^= cast_sbox7[U_INT8_Tb(z[2])];
key->xkey[i+3] ^= cast_sbox8[U_INT8_Ta(z[3])];
break;
case 4:
key->xkey[i+0] ^= cast_sbox5[U_INT8_Ta(x[2])];
key->xkey[i+1] ^= cast_sbox6[U_INT8_Tb(x[3])];
key->xkey[i+2] ^= cast_sbox7[U_INT8_Td(x[0])];
key->xkey[i+3] ^= cast_sbox8[U_INT8_Td(x[1])];
break;
case 8:
key->xkey[i+0] ^= cast_sbox5[U_INT8_Tb(z[2])];
key->xkey[i+1] ^= cast_sbox6[U_INT8_Ta(z[3])];
key->xkey[i+2] ^= cast_sbox7[U_INT8_Tc(z[0])];
key->xkey[i+3] ^= cast_sbox8[U_INT8_Tc(z[1])];
break;
case 12:
key->xkey[i+0] ^= cast_sbox5[U_INT8_Td(x[0])];
key->xkey[i+1] ^= cast_sbox6[U_INT8_Td(x[1])];
key->xkey[i+2] ^= cast_sbox7[U_INT8_Ta(x[2])];
key->xkey[i+3] ^= cast_sbox8[U_INT8_Tb(x[3])];
break;
}
if (i >= 16) {
key->xkey[i+0] &= 31;
key->xkey[i+1] &= 31;
key->xkey[i+2] &= 31;
key->xkey[i+3] &= 31;
}
}
/* Wipe clean */
for (i = 0; i < 4; i++) {
t[i] = x[i] = z[i] = 0;
}
}
/* Made in Canada */

23
sys/opencrypto/cast.h Normal file
View File

@ -0,0 +1,23 @@
/* $NetBSD: cast.h,v 1.1 2003/07/25 21:12:42 jonathan Exp $ */
/* $OpenBSD: cast.h,v 1.2 2002/03/14 01:26:51 millert Exp $ */
/*
* CAST-128 in C
* Written by Steve Reid <sreid@sea-to-sky.net>
* 100% Public Domain - no warranty
* Released 1997.10.11
*/
#ifndef _CAST_H_
#define _CAST_H_
typedef struct {
u_int32_t xkey[32]; /* Key, after expansion */
int rounds; /* Number of rounds to use, 12 or 16 */
} cast_key;
void cast_setkey(cast_key * key, u_int8_t * rawkey, int keybytes);
void cast_encrypt(cast_key * key, u_int8_t * inblock, u_int8_t * outblock);
void cast_decrypt(cast_key * key, u_int8_t * inblock, u_int8_t * outblock);
#endif /* ifndef _CAST_H_ */

546
sys/opencrypto/castsb.h Normal file
View File

@ -0,0 +1,546 @@
/* $NetBSD: castsb.h,v 1.1 2003/07/25 21:12:42 jonathan Exp $ */
/* $OpenBSD: castsb.h,v 1.1 2000/02/28 23:13:04 deraadt Exp $ */
/*
* CAST-128 in C
* Written by Steve Reid <sreid@sea-to-sky.net>
* 100% Public Domain - no warranty
* Released 1997.10.11
*/
static const u_int32_t cast_sbox1[256] = {
0x30FB40D4, 0x9FA0FF0B, 0x6BECCD2F, 0x3F258C7A,
0x1E213F2F, 0x9C004DD3, 0x6003E540, 0xCF9FC949,
0xBFD4AF27, 0x88BBBDB5, 0xE2034090, 0x98D09675,
0x6E63A0E0, 0x15C361D2, 0xC2E7661D, 0x22D4FF8E,
0x28683B6F, 0xC07FD059, 0xFF2379C8, 0x775F50E2,
0x43C340D3, 0xDF2F8656, 0x887CA41A, 0xA2D2BD2D,
0xA1C9E0D6, 0x346C4819, 0x61B76D87, 0x22540F2F,
0x2ABE32E1, 0xAA54166B, 0x22568E3A, 0xA2D341D0,
0x66DB40C8, 0xA784392F, 0x004DFF2F, 0x2DB9D2DE,
0x97943FAC, 0x4A97C1D8, 0x527644B7, 0xB5F437A7,
0xB82CBAEF, 0xD751D159, 0x6FF7F0ED, 0x5A097A1F,
0x827B68D0, 0x90ECF52E, 0x22B0C054, 0xBC8E5935,
0x4B6D2F7F, 0x50BB64A2, 0xD2664910, 0xBEE5812D,
0xB7332290, 0xE93B159F, 0xB48EE411, 0x4BFF345D,
0xFD45C240, 0xAD31973F, 0xC4F6D02E, 0x55FC8165,
0xD5B1CAAD, 0xA1AC2DAE, 0xA2D4B76D, 0xC19B0C50,
0x882240F2, 0x0C6E4F38, 0xA4E4BFD7, 0x4F5BA272,
0x564C1D2F, 0xC59C5319, 0xB949E354, 0xB04669FE,
0xB1B6AB8A, 0xC71358DD, 0x6385C545, 0x110F935D,
0x57538AD5, 0x6A390493, 0xE63D37E0, 0x2A54F6B3,
0x3A787D5F, 0x6276A0B5, 0x19A6FCDF, 0x7A42206A,
0x29F9D4D5, 0xF61B1891, 0xBB72275E, 0xAA508167,
0x38901091, 0xC6B505EB, 0x84C7CB8C, 0x2AD75A0F,
0x874A1427, 0xA2D1936B, 0x2AD286AF, 0xAA56D291,
0xD7894360, 0x425C750D, 0x93B39E26, 0x187184C9,
0x6C00B32D, 0x73E2BB14, 0xA0BEBC3C, 0x54623779,
0x64459EAB, 0x3F328B82, 0x7718CF82, 0x59A2CEA6,
0x04EE002E, 0x89FE78E6, 0x3FAB0950, 0x325FF6C2,
0x81383F05, 0x6963C5C8, 0x76CB5AD6, 0xD49974C9,
0xCA180DCF, 0x380782D5, 0xC7FA5CF6, 0x8AC31511,
0x35E79E13, 0x47DA91D0, 0xF40F9086, 0xA7E2419E,
0x31366241, 0x051EF495, 0xAA573B04, 0x4A805D8D,
0x548300D0, 0x00322A3C, 0xBF64CDDF, 0xBA57A68E,
0x75C6372B, 0x50AFD341, 0xA7C13275, 0x915A0BF5,
0x6B54BFAB, 0x2B0B1426, 0xAB4CC9D7, 0x449CCD82,
0xF7FBF265, 0xAB85C5F3, 0x1B55DB94, 0xAAD4E324,
0xCFA4BD3F, 0x2DEAA3E2, 0x9E204D02, 0xC8BD25AC,
0xEADF55B3, 0xD5BD9E98, 0xE31231B2, 0x2AD5AD6C,
0x954329DE, 0xADBE4528, 0xD8710F69, 0xAA51C90F,
0xAA786BF6, 0x22513F1E, 0xAA51A79B, 0x2AD344CC,
0x7B5A41F0, 0xD37CFBAD, 0x1B069505, 0x41ECE491,
0xB4C332E6, 0x032268D4, 0xC9600ACC, 0xCE387E6D,
0xBF6BB16C, 0x6A70FB78, 0x0D03D9C9, 0xD4DF39DE,
0xE01063DA, 0x4736F464, 0x5AD328D8, 0xB347CC96,
0x75BB0FC3, 0x98511BFB, 0x4FFBCC35, 0xB58BCF6A,
0xE11F0ABC, 0xBFC5FE4A, 0xA70AEC10, 0xAC39570A,
0x3F04442F, 0x6188B153, 0xE0397A2E, 0x5727CB79,
0x9CEB418F, 0x1CACD68D, 0x2AD37C96, 0x0175CB9D,
0xC69DFF09, 0xC75B65F0, 0xD9DB40D8, 0xEC0E7779,
0x4744EAD4, 0xB11C3274, 0xDD24CB9E, 0x7E1C54BD,
0xF01144F9, 0xD2240EB1, 0x9675B3FD, 0xA3AC3755,
0xD47C27AF, 0x51C85F4D, 0x56907596, 0xA5BB15E6,
0x580304F0, 0xCA042CF1, 0x011A37EA, 0x8DBFAADB,
0x35BA3E4A, 0x3526FFA0, 0xC37B4D09, 0xBC306ED9,
0x98A52666, 0x5648F725, 0xFF5E569D, 0x0CED63D0,
0x7C63B2CF, 0x700B45E1, 0xD5EA50F1, 0x85A92872,
0xAF1FBDA7, 0xD4234870, 0xA7870BF3, 0x2D3B4D79,
0x42E04198, 0x0CD0EDE7, 0x26470DB8, 0xF881814C,
0x474D6AD7, 0x7C0C5E5C, 0xD1231959, 0x381B7298,
0xF5D2F4DB, 0xAB838653, 0x6E2F1E23, 0x83719C9E,
0xBD91E046, 0x9A56456E, 0xDC39200C, 0x20C8C571,
0x962BDA1C, 0xE1E696FF, 0xB141AB08, 0x7CCA89B9,
0x1A69E783, 0x02CC4843, 0xA2F7C579, 0x429EF47D,
0x427B169C, 0x5AC9F049, 0xDD8F0F00, 0x5C8165BF
};
static const u_int32_t cast_sbox2[256] = {
0x1F201094, 0xEF0BA75B, 0x69E3CF7E, 0x393F4380,
0xFE61CF7A, 0xEEC5207A, 0x55889C94, 0x72FC0651,
0xADA7EF79, 0x4E1D7235, 0xD55A63CE, 0xDE0436BA,
0x99C430EF, 0x5F0C0794, 0x18DCDB7D, 0xA1D6EFF3,
0xA0B52F7B, 0x59E83605, 0xEE15B094, 0xE9FFD909,
0xDC440086, 0xEF944459, 0xBA83CCB3, 0xE0C3CDFB,
0xD1DA4181, 0x3B092AB1, 0xF997F1C1, 0xA5E6CF7B,
0x01420DDB, 0xE4E7EF5B, 0x25A1FF41, 0xE180F806,
0x1FC41080, 0x179BEE7A, 0xD37AC6A9, 0xFE5830A4,
0x98DE8B7F, 0x77E83F4E, 0x79929269, 0x24FA9F7B,
0xE113C85B, 0xACC40083, 0xD7503525, 0xF7EA615F,
0x62143154, 0x0D554B63, 0x5D681121, 0xC866C359,
0x3D63CF73, 0xCEE234C0, 0xD4D87E87, 0x5C672B21,
0x071F6181, 0x39F7627F, 0x361E3084, 0xE4EB573B,
0x602F64A4, 0xD63ACD9C, 0x1BBC4635, 0x9E81032D,
0x2701F50C, 0x99847AB4, 0xA0E3DF79, 0xBA6CF38C,
0x10843094, 0x2537A95E, 0xF46F6FFE, 0xA1FF3B1F,
0x208CFB6A, 0x8F458C74, 0xD9E0A227, 0x4EC73A34,
0xFC884F69, 0x3E4DE8DF, 0xEF0E0088, 0x3559648D,
0x8A45388C, 0x1D804366, 0x721D9BFD, 0xA58684BB,
0xE8256333, 0x844E8212, 0x128D8098, 0xFED33FB4,
0xCE280AE1, 0x27E19BA5, 0xD5A6C252, 0xE49754BD,
0xC5D655DD, 0xEB667064, 0x77840B4D, 0xA1B6A801,
0x84DB26A9, 0xE0B56714, 0x21F043B7, 0xE5D05860,
0x54F03084, 0x066FF472, 0xA31AA153, 0xDADC4755,
0xB5625DBF, 0x68561BE6, 0x83CA6B94, 0x2D6ED23B,
0xECCF01DB, 0xA6D3D0BA, 0xB6803D5C, 0xAF77A709,
0x33B4A34C, 0x397BC8D6, 0x5EE22B95, 0x5F0E5304,
0x81ED6F61, 0x20E74364, 0xB45E1378, 0xDE18639B,
0x881CA122, 0xB96726D1, 0x8049A7E8, 0x22B7DA7B,
0x5E552D25, 0x5272D237, 0x79D2951C, 0xC60D894C,
0x488CB402, 0x1BA4FE5B, 0xA4B09F6B, 0x1CA815CF,
0xA20C3005, 0x8871DF63, 0xB9DE2FCB, 0x0CC6C9E9,
0x0BEEFF53, 0xE3214517, 0xB4542835, 0x9F63293C,
0xEE41E729, 0x6E1D2D7C, 0x50045286, 0x1E6685F3,
0xF33401C6, 0x30A22C95, 0x31A70850, 0x60930F13,
0x73F98417, 0xA1269859, 0xEC645C44, 0x52C877A9,
0xCDFF33A6, 0xA02B1741, 0x7CBAD9A2, 0x2180036F,
0x50D99C08, 0xCB3F4861, 0xC26BD765, 0x64A3F6AB,
0x80342676, 0x25A75E7B, 0xE4E6D1FC, 0x20C710E6,
0xCDF0B680, 0x17844D3B, 0x31EEF84D, 0x7E0824E4,
0x2CCB49EB, 0x846A3BAE, 0x8FF77888, 0xEE5D60F6,
0x7AF75673, 0x2FDD5CDB, 0xA11631C1, 0x30F66F43,
0xB3FAEC54, 0x157FD7FA, 0xEF8579CC, 0xD152DE58,
0xDB2FFD5E, 0x8F32CE19, 0x306AF97A, 0x02F03EF8,
0x99319AD5, 0xC242FA0F, 0xA7E3EBB0, 0xC68E4906,
0xB8DA230C, 0x80823028, 0xDCDEF3C8, 0xD35FB171,
0x088A1BC8, 0xBEC0C560, 0x61A3C9E8, 0xBCA8F54D,
0xC72FEFFA, 0x22822E99, 0x82C570B4, 0xD8D94E89,
0x8B1C34BC, 0x301E16E6, 0x273BE979, 0xB0FFEAA6,
0x61D9B8C6, 0x00B24869, 0xB7FFCE3F, 0x08DC283B,
0x43DAF65A, 0xF7E19798, 0x7619B72F, 0x8F1C9BA4,
0xDC8637A0, 0x16A7D3B1, 0x9FC393B7, 0xA7136EEB,
0xC6BCC63E, 0x1A513742, 0xEF6828BC, 0x520365D6,
0x2D6A77AB, 0x3527ED4B, 0x821FD216, 0x095C6E2E,
0xDB92F2FB, 0x5EEA29CB, 0x145892F5, 0x91584F7F,
0x5483697B, 0x2667A8CC, 0x85196048, 0x8C4BACEA,
0x833860D4, 0x0D23E0F9, 0x6C387E8A, 0x0AE6D249,
0xB284600C, 0xD835731D, 0xDCB1C647, 0xAC4C56EA,
0x3EBD81B3, 0x230EABB0, 0x6438BC87, 0xF0B5B1FA,
0x8F5EA2B3, 0xFC184642, 0x0A036B7A, 0x4FB089BD,
0x649DA589, 0xA345415E, 0x5C038323, 0x3E5D3BB9,
0x43D79572, 0x7E6DD07C, 0x06DFDF1E, 0x6C6CC4EF,
0x7160A539, 0x73BFBE70, 0x83877605, 0x4523ECF1
};
static const u_int32_t cast_sbox3[256] = {
0x8DEFC240, 0x25FA5D9F, 0xEB903DBF, 0xE810C907,
0x47607FFF, 0x369FE44B, 0x8C1FC644, 0xAECECA90,
0xBEB1F9BF, 0xEEFBCAEA, 0xE8CF1950, 0x51DF07AE,
0x920E8806, 0xF0AD0548, 0xE13C8D83, 0x927010D5,
0x11107D9F, 0x07647DB9, 0xB2E3E4D4, 0x3D4F285E,
0xB9AFA820, 0xFADE82E0, 0xA067268B, 0x8272792E,
0x553FB2C0, 0x489AE22B, 0xD4EF9794, 0x125E3FBC,
0x21FFFCEE, 0x825B1BFD, 0x9255C5ED, 0x1257A240,
0x4E1A8302, 0xBAE07FFF, 0x528246E7, 0x8E57140E,
0x3373F7BF, 0x8C9F8188, 0xA6FC4EE8, 0xC982B5A5,
0xA8C01DB7, 0x579FC264, 0x67094F31, 0xF2BD3F5F,
0x40FFF7C1, 0x1FB78DFC, 0x8E6BD2C1, 0x437BE59B,
0x99B03DBF, 0xB5DBC64B, 0x638DC0E6, 0x55819D99,
0xA197C81C, 0x4A012D6E, 0xC5884A28, 0xCCC36F71,
0xB843C213, 0x6C0743F1, 0x8309893C, 0x0FEDDD5F,
0x2F7FE850, 0xD7C07F7E, 0x02507FBF, 0x5AFB9A04,
0xA747D2D0, 0x1651192E, 0xAF70BF3E, 0x58C31380,
0x5F98302E, 0x727CC3C4, 0x0A0FB402, 0x0F7FEF82,
0x8C96FDAD, 0x5D2C2AAE, 0x8EE99A49, 0x50DA88B8,
0x8427F4A0, 0x1EAC5790, 0x796FB449, 0x8252DC15,
0xEFBD7D9B, 0xA672597D, 0xADA840D8, 0x45F54504,
0xFA5D7403, 0xE83EC305, 0x4F91751A, 0x925669C2,
0x23EFE941, 0xA903F12E, 0x60270DF2, 0x0276E4B6,
0x94FD6574, 0x927985B2, 0x8276DBCB, 0x02778176,
0xF8AF918D, 0x4E48F79E, 0x8F616DDF, 0xE29D840E,
0x842F7D83, 0x340CE5C8, 0x96BBB682, 0x93B4B148,
0xEF303CAB, 0x984FAF28, 0x779FAF9B, 0x92DC560D,
0x224D1E20, 0x8437AA88, 0x7D29DC96, 0x2756D3DC,
0x8B907CEE, 0xB51FD240, 0xE7C07CE3, 0xE566B4A1,
0xC3E9615E, 0x3CF8209D, 0x6094D1E3, 0xCD9CA341,
0x5C76460E, 0x00EA983B, 0xD4D67881, 0xFD47572C,
0xF76CEDD9, 0xBDA8229C, 0x127DADAA, 0x438A074E,
0x1F97C090, 0x081BDB8A, 0x93A07EBE, 0xB938CA15,
0x97B03CFF, 0x3DC2C0F8, 0x8D1AB2EC, 0x64380E51,
0x68CC7BFB, 0xD90F2788, 0x12490181, 0x5DE5FFD4,
0xDD7EF86A, 0x76A2E214, 0xB9A40368, 0x925D958F,
0x4B39FFFA, 0xBA39AEE9, 0xA4FFD30B, 0xFAF7933B,
0x6D498623, 0x193CBCFA, 0x27627545, 0x825CF47A,
0x61BD8BA0, 0xD11E42D1, 0xCEAD04F4, 0x127EA392,
0x10428DB7, 0x8272A972, 0x9270C4A8, 0x127DE50B,
0x285BA1C8, 0x3C62F44F, 0x35C0EAA5, 0xE805D231,
0x428929FB, 0xB4FCDF82, 0x4FB66A53, 0x0E7DC15B,
0x1F081FAB, 0x108618AE, 0xFCFD086D, 0xF9FF2889,
0x694BCC11, 0x236A5CAE, 0x12DECA4D, 0x2C3F8CC5,
0xD2D02DFE, 0xF8EF5896, 0xE4CF52DA, 0x95155B67,
0x494A488C, 0xB9B6A80C, 0x5C8F82BC, 0x89D36B45,
0x3A609437, 0xEC00C9A9, 0x44715253, 0x0A874B49,
0xD773BC40, 0x7C34671C, 0x02717EF6, 0x4FEB5536,
0xA2D02FFF, 0xD2BF60C4, 0xD43F03C0, 0x50B4EF6D,
0x07478CD1, 0x006E1888, 0xA2E53F55, 0xB9E6D4BC,
0xA2048016, 0x97573833, 0xD7207D67, 0xDE0F8F3D,
0x72F87B33, 0xABCC4F33, 0x7688C55D, 0x7B00A6B0,
0x947B0001, 0x570075D2, 0xF9BB88F8, 0x8942019E,
0x4264A5FF, 0x856302E0, 0x72DBD92B, 0xEE971B69,
0x6EA22FDE, 0x5F08AE2B, 0xAF7A616D, 0xE5C98767,
0xCF1FEBD2, 0x61EFC8C2, 0xF1AC2571, 0xCC8239C2,
0x67214CB8, 0xB1E583D1, 0xB7DC3E62, 0x7F10BDCE,
0xF90A5C38, 0x0FF0443D, 0x606E6DC6, 0x60543A49,
0x5727C148, 0x2BE98A1D, 0x8AB41738, 0x20E1BE24,
0xAF96DA0F, 0x68458425, 0x99833BE5, 0x600D457D,
0x282F9350, 0x8334B362, 0xD91D1120, 0x2B6D8DA0,
0x642B1E31, 0x9C305A00, 0x52BCE688, 0x1B03588A,
0xF7BAEFD5, 0x4142ED9C, 0xA4315C11, 0x83323EC5,
0xDFEF4636, 0xA133C501, 0xE9D3531C, 0xEE353783
};
static const u_int32_t cast_sbox4[256] = {
0x9DB30420, 0x1FB6E9DE, 0xA7BE7BEF, 0xD273A298,
0x4A4F7BDB, 0x64AD8C57, 0x85510443, 0xFA020ED1,
0x7E287AFF, 0xE60FB663, 0x095F35A1, 0x79EBF120,
0xFD059D43, 0x6497B7B1, 0xF3641F63, 0x241E4ADF,
0x28147F5F, 0x4FA2B8CD, 0xC9430040, 0x0CC32220,
0xFDD30B30, 0xC0A5374F, 0x1D2D00D9, 0x24147B15,
0xEE4D111A, 0x0FCA5167, 0x71FF904C, 0x2D195FFE,
0x1A05645F, 0x0C13FEFE, 0x081B08CA, 0x05170121,
0x80530100, 0xE83E5EFE, 0xAC9AF4F8, 0x7FE72701,
0xD2B8EE5F, 0x06DF4261, 0xBB9E9B8A, 0x7293EA25,
0xCE84FFDF, 0xF5718801, 0x3DD64B04, 0xA26F263B,
0x7ED48400, 0x547EEBE6, 0x446D4CA0, 0x6CF3D6F5,
0x2649ABDF, 0xAEA0C7F5, 0x36338CC1, 0x503F7E93,
0xD3772061, 0x11B638E1, 0x72500E03, 0xF80EB2BB,
0xABE0502E, 0xEC8D77DE, 0x57971E81, 0xE14F6746,
0xC9335400, 0x6920318F, 0x081DBB99, 0xFFC304A5,
0x4D351805, 0x7F3D5CE3, 0xA6C866C6, 0x5D5BCCA9,
0xDAEC6FEA, 0x9F926F91, 0x9F46222F, 0x3991467D,
0xA5BF6D8E, 0x1143C44F, 0x43958302, 0xD0214EEB,
0x022083B8, 0x3FB6180C, 0x18F8931E, 0x281658E6,
0x26486E3E, 0x8BD78A70, 0x7477E4C1, 0xB506E07C,
0xF32D0A25, 0x79098B02, 0xE4EABB81, 0x28123B23,
0x69DEAD38, 0x1574CA16, 0xDF871B62, 0x211C40B7,
0xA51A9EF9, 0x0014377B, 0x041E8AC8, 0x09114003,
0xBD59E4D2, 0xE3D156D5, 0x4FE876D5, 0x2F91A340,
0x557BE8DE, 0x00EAE4A7, 0x0CE5C2EC, 0x4DB4BBA6,
0xE756BDFF, 0xDD3369AC, 0xEC17B035, 0x06572327,
0x99AFC8B0, 0x56C8C391, 0x6B65811C, 0x5E146119,
0x6E85CB75, 0xBE07C002, 0xC2325577, 0x893FF4EC,
0x5BBFC92D, 0xD0EC3B25, 0xB7801AB7, 0x8D6D3B24,
0x20C763EF, 0xC366A5FC, 0x9C382880, 0x0ACE3205,
0xAAC9548A, 0xECA1D7C7, 0x041AFA32, 0x1D16625A,
0x6701902C, 0x9B757A54, 0x31D477F7, 0x9126B031,
0x36CC6FDB, 0xC70B8B46, 0xD9E66A48, 0x56E55A79,
0x026A4CEB, 0x52437EFF, 0x2F8F76B4, 0x0DF980A5,
0x8674CDE3, 0xEDDA04EB, 0x17A9BE04, 0x2C18F4DF,
0xB7747F9D, 0xAB2AF7B4, 0xEFC34D20, 0x2E096B7C,
0x1741A254, 0xE5B6A035, 0x213D42F6, 0x2C1C7C26,
0x61C2F50F, 0x6552DAF9, 0xD2C231F8, 0x25130F69,
0xD8167FA2, 0x0418F2C8, 0x001A96A6, 0x0D1526AB,
0x63315C21, 0x5E0A72EC, 0x49BAFEFD, 0x187908D9,
0x8D0DBD86, 0x311170A7, 0x3E9B640C, 0xCC3E10D7,
0xD5CAD3B6, 0x0CAEC388, 0xF73001E1, 0x6C728AFF,
0x71EAE2A1, 0x1F9AF36E, 0xCFCBD12F, 0xC1DE8417,
0xAC07BE6B, 0xCB44A1D8, 0x8B9B0F56, 0x013988C3,
0xB1C52FCA, 0xB4BE31CD, 0xD8782806, 0x12A3A4E2,
0x6F7DE532, 0x58FD7EB6, 0xD01EE900, 0x24ADFFC2,
0xF4990FC5, 0x9711AAC5, 0x001D7B95, 0x82E5E7D2,
0x109873F6, 0x00613096, 0xC32D9521, 0xADA121FF,
0x29908415, 0x7FBB977F, 0xAF9EB3DB, 0x29C9ED2A,
0x5CE2A465, 0xA730F32C, 0xD0AA3FE8, 0x8A5CC091,
0xD49E2CE7, 0x0CE454A9, 0xD60ACD86, 0x015F1919,
0x77079103, 0xDEA03AF6, 0x78A8565E, 0xDEE356DF,
0x21F05CBE, 0x8B75E387, 0xB3C50651, 0xB8A5C3EF,
0xD8EEB6D2, 0xE523BE77, 0xC2154529, 0x2F69EFDF,
0xAFE67AFB, 0xF470C4B2, 0xF3E0EB5B, 0xD6CC9876,
0x39E4460C, 0x1FDA8538, 0x1987832F, 0xCA007367,
0xA99144F8, 0x296B299E, 0x492FC295, 0x9266BEAB,
0xB5676E69, 0x9BD3DDDA, 0xDF7E052F, 0xDB25701C,
0x1B5E51EE, 0xF65324E6, 0x6AFCE36C, 0x0316CC04,
0x8644213E, 0xB7DC59D0, 0x7965291F, 0xCCD6FD43,
0x41823979, 0x932BCDF6, 0xB657C34D, 0x4EDFD282,
0x7AE5290C, 0x3CB9536B, 0x851E20FE, 0x9833557E,
0x13ECF0B0, 0xD3FFB372, 0x3F85C5C1, 0x0AEF7ED2
};
static const u_int32_t cast_sbox5[256] = {
0x7EC90C04, 0x2C6E74B9, 0x9B0E66DF, 0xA6337911,
0xB86A7FFF, 0x1DD358F5, 0x44DD9D44, 0x1731167F,
0x08FBF1FA, 0xE7F511CC, 0xD2051B00, 0x735ABA00,
0x2AB722D8, 0x386381CB, 0xACF6243A, 0x69BEFD7A,
0xE6A2E77F, 0xF0C720CD, 0xC4494816, 0xCCF5C180,
0x38851640, 0x15B0A848, 0xE68B18CB, 0x4CAADEFF,
0x5F480A01, 0x0412B2AA, 0x259814FC, 0x41D0EFE2,
0x4E40B48D, 0x248EB6FB, 0x8DBA1CFE, 0x41A99B02,
0x1A550A04, 0xBA8F65CB, 0x7251F4E7, 0x95A51725,
0xC106ECD7, 0x97A5980A, 0xC539B9AA, 0x4D79FE6A,
0xF2F3F763, 0x68AF8040, 0xED0C9E56, 0x11B4958B,
0xE1EB5A88, 0x8709E6B0, 0xD7E07156, 0x4E29FEA7,
0x6366E52D, 0x02D1C000, 0xC4AC8E05, 0x9377F571,
0x0C05372A, 0x578535F2, 0x2261BE02, 0xD642A0C9,
0xDF13A280, 0x74B55BD2, 0x682199C0, 0xD421E5EC,
0x53FB3CE8, 0xC8ADEDB3, 0x28A87FC9, 0x3D959981,
0x5C1FF900, 0xFE38D399, 0x0C4EFF0B, 0x062407EA,
0xAA2F4FB1, 0x4FB96976, 0x90C79505, 0xB0A8A774,
0xEF55A1FF, 0xE59CA2C2, 0xA6B62D27, 0xE66A4263,
0xDF65001F, 0x0EC50966, 0xDFDD55BC, 0x29DE0655,
0x911E739A, 0x17AF8975, 0x32C7911C, 0x89F89468,
0x0D01E980, 0x524755F4, 0x03B63CC9, 0x0CC844B2,
0xBCF3F0AA, 0x87AC36E9, 0xE53A7426, 0x01B3D82B,
0x1A9E7449, 0x64EE2D7E, 0xCDDBB1DA, 0x01C94910,
0xB868BF80, 0x0D26F3FD, 0x9342EDE7, 0x04A5C284,
0x636737B6, 0x50F5B616, 0xF24766E3, 0x8ECA36C1,
0x136E05DB, 0xFEF18391, 0xFB887A37, 0xD6E7F7D4,
0xC7FB7DC9, 0x3063FCDF, 0xB6F589DE, 0xEC2941DA,
0x26E46695, 0xB7566419, 0xF654EFC5, 0xD08D58B7,
0x48925401, 0xC1BACB7F, 0xE5FF550F, 0xB6083049,
0x5BB5D0E8, 0x87D72E5A, 0xAB6A6EE1, 0x223A66CE,
0xC62BF3CD, 0x9E0885F9, 0x68CB3E47, 0x086C010F,
0xA21DE820, 0xD18B69DE, 0xF3F65777, 0xFA02C3F6,
0x407EDAC3, 0xCBB3D550, 0x1793084D, 0xB0D70EBA,
0x0AB378D5, 0xD951FB0C, 0xDED7DA56, 0x4124BBE4,
0x94CA0B56, 0x0F5755D1, 0xE0E1E56E, 0x6184B5BE,
0x580A249F, 0x94F74BC0, 0xE327888E, 0x9F7B5561,
0xC3DC0280, 0x05687715, 0x646C6BD7, 0x44904DB3,
0x66B4F0A3, 0xC0F1648A, 0x697ED5AF, 0x49E92FF6,
0x309E374F, 0x2CB6356A, 0x85808573, 0x4991F840,
0x76F0AE02, 0x083BE84D, 0x28421C9A, 0x44489406,
0x736E4CB8, 0xC1092910, 0x8BC95FC6, 0x7D869CF4,
0x134F616F, 0x2E77118D, 0xB31B2BE1, 0xAA90B472,
0x3CA5D717, 0x7D161BBA, 0x9CAD9010, 0xAF462BA2,
0x9FE459D2, 0x45D34559, 0xD9F2DA13, 0xDBC65487,
0xF3E4F94E, 0x176D486F, 0x097C13EA, 0x631DA5C7,
0x445F7382, 0x175683F4, 0xCDC66A97, 0x70BE0288,
0xB3CDCF72, 0x6E5DD2F3, 0x20936079, 0x459B80A5,
0xBE60E2DB, 0xA9C23101, 0xEBA5315C, 0x224E42F2,
0x1C5C1572, 0xF6721B2C, 0x1AD2FFF3, 0x8C25404E,
0x324ED72F, 0x4067B7FD, 0x0523138E, 0x5CA3BC78,
0xDC0FD66E, 0x75922283, 0x784D6B17, 0x58EBB16E,
0x44094F85, 0x3F481D87, 0xFCFEAE7B, 0x77B5FF76,
0x8C2302BF, 0xAAF47556, 0x5F46B02A, 0x2B092801,
0x3D38F5F7, 0x0CA81F36, 0x52AF4A8A, 0x66D5E7C0,
0xDF3B0874, 0x95055110, 0x1B5AD7A8, 0xF61ED5AD,
0x6CF6E479, 0x20758184, 0xD0CEFA65, 0x88F7BE58,
0x4A046826, 0x0FF6F8F3, 0xA09C7F70, 0x5346ABA0,
0x5CE96C28, 0xE176EDA3, 0x6BAC307F, 0x376829D2,
0x85360FA9, 0x17E3FE2A, 0x24B79767, 0xF5A96B20,
0xD6CD2595, 0x68FF1EBF, 0x7555442C, 0xF19F06BE,
0xF9E0659A, 0xEEB9491D, 0x34010718, 0xBB30CAB8,
0xE822FE15, 0x88570983, 0x750E6249, 0xDA627E55,
0x5E76FFA8, 0xB1534546, 0x6D47DE08, 0xEFE9E7D4
};
static const u_int32_t cast_sbox6[256] = {
0xF6FA8F9D, 0x2CAC6CE1, 0x4CA34867, 0xE2337F7C,
0x95DB08E7, 0x016843B4, 0xECED5CBC, 0x325553AC,
0xBF9F0960, 0xDFA1E2ED, 0x83F0579D, 0x63ED86B9,
0x1AB6A6B8, 0xDE5EBE39, 0xF38FF732, 0x8989B138,
0x33F14961, 0xC01937BD, 0xF506C6DA, 0xE4625E7E,
0xA308EA99, 0x4E23E33C, 0x79CBD7CC, 0x48A14367,
0xA3149619, 0xFEC94BD5, 0xA114174A, 0xEAA01866,
0xA084DB2D, 0x09A8486F, 0xA888614A, 0x2900AF98,
0x01665991, 0xE1992863, 0xC8F30C60, 0x2E78EF3C,
0xD0D51932, 0xCF0FEC14, 0xF7CA07D2, 0xD0A82072,
0xFD41197E, 0x9305A6B0, 0xE86BE3DA, 0x74BED3CD,
0x372DA53C, 0x4C7F4448, 0xDAB5D440, 0x6DBA0EC3,
0x083919A7, 0x9FBAEED9, 0x49DBCFB0, 0x4E670C53,
0x5C3D9C01, 0x64BDB941, 0x2C0E636A, 0xBA7DD9CD,
0xEA6F7388, 0xE70BC762, 0x35F29ADB, 0x5C4CDD8D,
0xF0D48D8C, 0xB88153E2, 0x08A19866, 0x1AE2EAC8,
0x284CAF89, 0xAA928223, 0x9334BE53, 0x3B3A21BF,
0x16434BE3, 0x9AEA3906, 0xEFE8C36E, 0xF890CDD9,
0x80226DAE, 0xC340A4A3, 0xDF7E9C09, 0xA694A807,
0x5B7C5ECC, 0x221DB3A6, 0x9A69A02F, 0x68818A54,
0xCEB2296F, 0x53C0843A, 0xFE893655, 0x25BFE68A,
0xB4628ABC, 0xCF222EBF, 0x25AC6F48, 0xA9A99387,
0x53BDDB65, 0xE76FFBE7, 0xE967FD78, 0x0BA93563,
0x8E342BC1, 0xE8A11BE9, 0x4980740D, 0xC8087DFC,
0x8DE4BF99, 0xA11101A0, 0x7FD37975, 0xDA5A26C0,
0xE81F994F, 0x9528CD89, 0xFD339FED, 0xB87834BF,
0x5F04456D, 0x22258698, 0xC9C4C83B, 0x2DC156BE,
0x4F628DAA, 0x57F55EC5, 0xE2220ABE, 0xD2916EBF,
0x4EC75B95, 0x24F2C3C0, 0x42D15D99, 0xCD0D7FA0,
0x7B6E27FF, 0xA8DC8AF0, 0x7345C106, 0xF41E232F,
0x35162386, 0xE6EA8926, 0x3333B094, 0x157EC6F2,
0x372B74AF, 0x692573E4, 0xE9A9D848, 0xF3160289,
0x3A62EF1D, 0xA787E238, 0xF3A5F676, 0x74364853,
0x20951063, 0x4576698D, 0xB6FAD407, 0x592AF950,
0x36F73523, 0x4CFB6E87, 0x7DA4CEC0, 0x6C152DAA,
0xCB0396A8, 0xC50DFE5D, 0xFCD707AB, 0x0921C42F,
0x89DFF0BB, 0x5FE2BE78, 0x448F4F33, 0x754613C9,
0x2B05D08D, 0x48B9D585, 0xDC049441, 0xC8098F9B,
0x7DEDE786, 0xC39A3373, 0x42410005, 0x6A091751,
0x0EF3C8A6, 0x890072D6, 0x28207682, 0xA9A9F7BE,
0xBF32679D, 0xD45B5B75, 0xB353FD00, 0xCBB0E358,
0x830F220A, 0x1F8FB214, 0xD372CF08, 0xCC3C4A13,
0x8CF63166, 0x061C87BE, 0x88C98F88, 0x6062E397,
0x47CF8E7A, 0xB6C85283, 0x3CC2ACFB, 0x3FC06976,
0x4E8F0252, 0x64D8314D, 0xDA3870E3, 0x1E665459,
0xC10908F0, 0x513021A5, 0x6C5B68B7, 0x822F8AA0,
0x3007CD3E, 0x74719EEF, 0xDC872681, 0x073340D4,
0x7E432FD9, 0x0C5EC241, 0x8809286C, 0xF592D891,
0x08A930F6, 0x957EF305, 0xB7FBFFBD, 0xC266E96F,
0x6FE4AC98, 0xB173ECC0, 0xBC60B42A, 0x953498DA,
0xFBA1AE12, 0x2D4BD736, 0x0F25FAAB, 0xA4F3FCEB,
0xE2969123, 0x257F0C3D, 0x9348AF49, 0x361400BC,
0xE8816F4A, 0x3814F200, 0xA3F94043, 0x9C7A54C2,
0xBC704F57, 0xDA41E7F9, 0xC25AD33A, 0x54F4A084,
0xB17F5505, 0x59357CBE, 0xEDBD15C8, 0x7F97C5AB,
0xBA5AC7B5, 0xB6F6DEAF, 0x3A479C3A, 0x5302DA25,
0x653D7E6A, 0x54268D49, 0x51A477EA, 0x5017D55B,
0xD7D25D88, 0x44136C76, 0x0404A8C8, 0xB8E5A121,
0xB81A928A, 0x60ED5869, 0x97C55B96, 0xEAEC991B,
0x29935913, 0x01FDB7F1, 0x088E8DFA, 0x9AB6F6F5,
0x3B4CBF9F, 0x4A5DE3AB, 0xE6051D35, 0xA0E1D855,
0xD36B4CF1, 0xF544EDEB, 0xB0E93524, 0xBEBB8FBD,
0xA2D762CF, 0x49C92F54, 0x38B5F331, 0x7128A454,
0x48392905, 0xA65B1DB8, 0x851C97BD, 0xD675CF2F
};
static const u_int32_t cast_sbox7[256] = {
0x85E04019, 0x332BF567, 0x662DBFFF, 0xCFC65693,
0x2A8D7F6F, 0xAB9BC912, 0xDE6008A1, 0x2028DA1F,
0x0227BCE7, 0x4D642916, 0x18FAC300, 0x50F18B82,
0x2CB2CB11, 0xB232E75C, 0x4B3695F2, 0xB28707DE,
0xA05FBCF6, 0xCD4181E9, 0xE150210C, 0xE24EF1BD,
0xB168C381, 0xFDE4E789, 0x5C79B0D8, 0x1E8BFD43,
0x4D495001, 0x38BE4341, 0x913CEE1D, 0x92A79C3F,
0x089766BE, 0xBAEEADF4, 0x1286BECF, 0xB6EACB19,
0x2660C200, 0x7565BDE4, 0x64241F7A, 0x8248DCA9,
0xC3B3AD66, 0x28136086, 0x0BD8DFA8, 0x356D1CF2,
0x107789BE, 0xB3B2E9CE, 0x0502AA8F, 0x0BC0351E,
0x166BF52A, 0xEB12FF82, 0xE3486911, 0xD34D7516,
0x4E7B3AFF, 0x5F43671B, 0x9CF6E037, 0x4981AC83,
0x334266CE, 0x8C9341B7, 0xD0D854C0, 0xCB3A6C88,
0x47BC2829, 0x4725BA37, 0xA66AD22B, 0x7AD61F1E,
0x0C5CBAFA, 0x4437F107, 0xB6E79962, 0x42D2D816,
0x0A961288, 0xE1A5C06E, 0x13749E67, 0x72FC081A,
0xB1D139F7, 0xF9583745, 0xCF19DF58, 0xBEC3F756,
0xC06EBA30, 0x07211B24, 0x45C28829, 0xC95E317F,
0xBC8EC511, 0x38BC46E9, 0xC6E6FA14, 0xBAE8584A,
0xAD4EBC46, 0x468F508B, 0x7829435F, 0xF124183B,
0x821DBA9F, 0xAFF60FF4, 0xEA2C4E6D, 0x16E39264,
0x92544A8B, 0x009B4FC3, 0xABA68CED, 0x9AC96F78,
0x06A5B79A, 0xB2856E6E, 0x1AEC3CA9, 0xBE838688,
0x0E0804E9, 0x55F1BE56, 0xE7E5363B, 0xB3A1F25D,
0xF7DEBB85, 0x61FE033C, 0x16746233, 0x3C034C28,
0xDA6D0C74, 0x79AAC56C, 0x3CE4E1AD, 0x51F0C802,
0x98F8F35A, 0x1626A49F, 0xEED82B29, 0x1D382FE3,
0x0C4FB99A, 0xBB325778, 0x3EC6D97B, 0x6E77A6A9,
0xCB658B5C, 0xD45230C7, 0x2BD1408B, 0x60C03EB7,
0xB9068D78, 0xA33754F4, 0xF430C87D, 0xC8A71302,
0xB96D8C32, 0xEBD4E7BE, 0xBE8B9D2D, 0x7979FB06,
0xE7225308, 0x8B75CF77, 0x11EF8DA4, 0xE083C858,
0x8D6B786F, 0x5A6317A6, 0xFA5CF7A0, 0x5DDA0033,
0xF28EBFB0, 0xF5B9C310, 0xA0EAC280, 0x08B9767A,
0xA3D9D2B0, 0x79D34217, 0x021A718D, 0x9AC6336A,
0x2711FD60, 0x438050E3, 0x069908A8, 0x3D7FEDC4,
0x826D2BEF, 0x4EEB8476, 0x488DCF25, 0x36C9D566,
0x28E74E41, 0xC2610ACA, 0x3D49A9CF, 0xBAE3B9DF,
0xB65F8DE6, 0x92AEAF64, 0x3AC7D5E6, 0x9EA80509,
0xF22B017D, 0xA4173F70, 0xDD1E16C3, 0x15E0D7F9,
0x50B1B887, 0x2B9F4FD5, 0x625ABA82, 0x6A017962,
0x2EC01B9C, 0x15488AA9, 0xD716E740, 0x40055A2C,
0x93D29A22, 0xE32DBF9A, 0x058745B9, 0x3453DC1E,
0xD699296E, 0x496CFF6F, 0x1C9F4986, 0xDFE2ED07,
0xB87242D1, 0x19DE7EAE, 0x053E561A, 0x15AD6F8C,
0x66626C1C, 0x7154C24C, 0xEA082B2A, 0x93EB2939,
0x17DCB0F0, 0x58D4F2AE, 0x9EA294FB, 0x52CF564C,
0x9883FE66, 0x2EC40581, 0x763953C3, 0x01D6692E,
0xD3A0C108, 0xA1E7160E, 0xE4F2DFA6, 0x693ED285,
0x74904698, 0x4C2B0EDD, 0x4F757656, 0x5D393378,
0xA132234F, 0x3D321C5D, 0xC3F5E194, 0x4B269301,
0xC79F022F, 0x3C997E7E, 0x5E4F9504, 0x3FFAFBBD,
0x76F7AD0E, 0x296693F4, 0x3D1FCE6F, 0xC61E45BE,
0xD3B5AB34, 0xF72BF9B7, 0x1B0434C0, 0x4E72B567,
0x5592A33D, 0xB5229301, 0xCFD2A87F, 0x60AEB767,
0x1814386B, 0x30BCC33D, 0x38A0C07D, 0xFD1606F2,
0xC363519B, 0x589DD390, 0x5479F8E6, 0x1CB8D647,
0x97FD61A9, 0xEA7759F4, 0x2D57539D, 0x569A58CF,
0xE84E63AD, 0x462E1B78, 0x6580F87E, 0xF3817914,
0x91DA55F4, 0x40A230F3, 0xD1988F35, 0xB6E318D2,
0x3FFA50BC, 0x3D40F021, 0xC3C0BDAE, 0x4958C24C,
0x518F36B2, 0x84B1D370, 0x0FEDCE83, 0x878DDADA,
0xF2A279C7, 0x94E01BE8, 0x90716F4B, 0x954B8AA3
};
static const u_int32_t cast_sbox8[256] = {
0xE216300D, 0xBBDDFFFC, 0xA7EBDABD, 0x35648095,
0x7789F8B7, 0xE6C1121B, 0x0E241600, 0x052CE8B5,
0x11A9CFB0, 0xE5952F11, 0xECE7990A, 0x9386D174,
0x2A42931C, 0x76E38111, 0xB12DEF3A, 0x37DDDDFC,
0xDE9ADEB1, 0x0A0CC32C, 0xBE197029, 0x84A00940,
0xBB243A0F, 0xB4D137CF, 0xB44E79F0, 0x049EEDFD,
0x0B15A15D, 0x480D3168, 0x8BBBDE5A, 0x669DED42,
0xC7ECE831, 0x3F8F95E7, 0x72DF191B, 0x7580330D,
0x94074251, 0x5C7DCDFA, 0xABBE6D63, 0xAA402164,
0xB301D40A, 0x02E7D1CA, 0x53571DAE, 0x7A3182A2,
0x12A8DDEC, 0xFDAA335D, 0x176F43E8, 0x71FB46D4,
0x38129022, 0xCE949AD4, 0xB84769AD, 0x965BD862,
0x82F3D055, 0x66FB9767, 0x15B80B4E, 0x1D5B47A0,
0x4CFDE06F, 0xC28EC4B8, 0x57E8726E, 0x647A78FC,
0x99865D44, 0x608BD593, 0x6C200E03, 0x39DC5FF6,
0x5D0B00A3, 0xAE63AFF2, 0x7E8BD632, 0x70108C0C,
0xBBD35049, 0x2998DF04, 0x980CF42A, 0x9B6DF491,
0x9E7EDD53, 0x06918548, 0x58CB7E07, 0x3B74EF2E,
0x522FFFB1, 0xD24708CC, 0x1C7E27CD, 0xA4EB215B,
0x3CF1D2E2, 0x19B47A38, 0x424F7618, 0x35856039,
0x9D17DEE7, 0x27EB35E6, 0xC9AFF67B, 0x36BAF5B8,
0x09C467CD, 0xC18910B1, 0xE11DBF7B, 0x06CD1AF8,
0x7170C608, 0x2D5E3354, 0xD4DE495A, 0x64C6D006,
0xBCC0C62C, 0x3DD00DB3, 0x708F8F34, 0x77D51B42,
0x264F620F, 0x24B8D2BF, 0x15C1B79E, 0x46A52564,
0xF8D7E54E, 0x3E378160, 0x7895CDA5, 0x859C15A5,
0xE6459788, 0xC37BC75F, 0xDB07BA0C, 0x0676A3AB,
0x7F229B1E, 0x31842E7B, 0x24259FD7, 0xF8BEF472,
0x835FFCB8, 0x6DF4C1F2, 0x96F5B195, 0xFD0AF0FC,
0xB0FE134C, 0xE2506D3D, 0x4F9B12EA, 0xF215F225,
0xA223736F, 0x9FB4C428, 0x25D04979, 0x34C713F8,
0xC4618187, 0xEA7A6E98, 0x7CD16EFC, 0x1436876C,
0xF1544107, 0xBEDEEE14, 0x56E9AF27, 0xA04AA441,
0x3CF7C899, 0x92ECBAE6, 0xDD67016D, 0x151682EB,
0xA842EEDF, 0xFDBA60B4, 0xF1907B75, 0x20E3030F,
0x24D8C29E, 0xE139673B, 0xEFA63FB8, 0x71873054,
0xB6F2CF3B, 0x9F326442, 0xCB15A4CC, 0xB01A4504,
0xF1E47D8D, 0x844A1BE5, 0xBAE7DFDC, 0x42CBDA70,
0xCD7DAE0A, 0x57E85B7A, 0xD53F5AF6, 0x20CF4D8C,
0xCEA4D428, 0x79D130A4, 0x3486EBFB, 0x33D3CDDC,
0x77853B53, 0x37EFFCB5, 0xC5068778, 0xE580B3E6,
0x4E68B8F4, 0xC5C8B37E, 0x0D809EA2, 0x398FEB7C,
0x132A4F94, 0x43B7950E, 0x2FEE7D1C, 0x223613BD,
0xDD06CAA2, 0x37DF932B, 0xC4248289, 0xACF3EBC3,
0x5715F6B7, 0xEF3478DD, 0xF267616F, 0xC148CBE4,
0x9052815E, 0x5E410FAB, 0xB48A2465, 0x2EDA7FA4,
0xE87B40E4, 0xE98EA084, 0x5889E9E1, 0xEFD390FC,
0xDD07D35B, 0xDB485694, 0x38D7E5B2, 0x57720101,
0x730EDEBC, 0x5B643113, 0x94917E4F, 0x503C2FBA,
0x646F1282, 0x7523D24A, 0xE0779695, 0xF9C17A8F,
0x7A5B2121, 0xD187B896, 0x29263A4D, 0xBA510CDF,
0x81F47C9F, 0xAD1163ED, 0xEA7B5965, 0x1A00726E,
0x11403092, 0x00DA6D77, 0x4A0CDD61, 0xAD1F4603,
0x605BDFB0, 0x9EEDC364, 0x22EBE6A8, 0xCEE7D28A,
0xA0E736A0, 0x5564A6B9, 0x10853209, 0xC7EB8F37,
0x2DE705CA, 0x8951570F, 0xDF09822B, 0xBD691A6C,
0xAA12E4F2, 0x87451C0F, 0xE0F6A27A, 0x3ADA4819,
0x4CF1764F, 0x0D771C2B, 0x67CDB156, 0x350D8384,
0x5938FA0F, 0x42399EF3, 0x36997B07, 0x0E84093D,
0x4AA93E61, 0x8360D87B, 0x1FA98B0C, 0x1149382C,
0xE97625A5, 0x0614D1B7, 0x0E25244B, 0x0C768347,
0x589E8D82, 0x0D2059D1, 0xA466BB1E, 0xF8DA0A82,
0x04F19130, 0xBA6E4EC0, 0x99265164, 0x1EE7230D,
0x50B2AD80, 0xEAEE6801, 0x8DB2A283, 0xEA8BF59E
};

219
sys/opencrypto/criov.c Normal file
View File

@ -0,0 +1,219 @@
/* $NetBSD: criov.c,v 1.1 2003/07/25 21:12:43 jonathan Exp $ */
/* $OpenBSD: criov.c,v 1.11 2002/06/10 19:36:43 espie Exp $ */
/*
* Copyright (c) 1999 Theo de Raadt
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: criov.c,v 1.1 2003/07/25 21:12:43 jonathan Exp $");
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/proc.h>
#include <sys/errno.h>
#include <sys/malloc.h>
#include <sys/kernel.h>
#include <sys/mbuf.h>
#include <uvm/uvm_extern.h>
#include <opencrypto/cryptodev.h>
int cuio_getindx(struct uio *uio, int loc, int *off);
void
cuio_copydata(uio, off, len, cp)
struct uio *uio;
int off, len;
caddr_t cp;
{
struct iovec *iov = uio->uio_iov;
int iol = uio->uio_iovcnt;
unsigned count;
if (off < 0)
panic("cuio_copydata: off %d < 0", off);
if (len < 0)
panic("cuio_copydata: len %d < 0", len);
while (off > 0) {
if (iol == 0)
panic("iov_copydata: empty in skip");
if (off < iov->iov_len)
break;
off -= iov->iov_len;
iol--;
iov++;
}
while (len > 0) {
if (iol == 0)
panic("cuio_copydata: empty");
count = min(iov->iov_len - off, len);
bcopy(((caddr_t)iov->iov_base) + off, cp, count);
len -= count;
cp += count;
off = 0;
iol--;
iov++;
}
}
void
cuio_copyback(uio, off, len, cp)
struct uio *uio;
int off, len;
caddr_t cp;
{
struct iovec *iov = uio->uio_iov;
int iol = uio->uio_iovcnt;
unsigned count;
if (off < 0)
panic("cuio_copyback: off %d < 0", off);
if (len < 0)
panic("cuio_copyback: len %d < 0", len);
while (off > 0) {
if (iol == 0)
panic("cuio_copyback: empty in skip");
if (off < iov->iov_len)
break;
off -= iov->iov_len;
iol--;
iov++;
}
while (len > 0) {
if (iol == 0)
panic("uio_copyback: empty");
count = min(iov->iov_len - off, len);
bcopy(cp, ((caddr_t)iov->iov_base) + off, count);
len -= count;
cp += count;
off = 0;
iol--;
iov++;
}
}
/*
* Return a pointer to iov/offset of location in iovec list.
*/
#ifdef __FreeBSD__
struct iovec *
cuio_getptr(struct uio *uio, int loc, int *off)
{
struct iovec *iov = uio->uio_iov;
int iol = uio->uio_iovcnt;
while (loc >= 0) {
/* Normal end of search */
if (loc < iov->iov_len) {
*off = loc;
return (iov);
}
loc -= iov->iov_len;
if (iol == 0) {
if (loc == 0) {
/* Point at the end of valid data */
*off = iov->iov_len;
return (iov);
} else
return (NULL);
} else {
iov++, iol--;
}
}
return (NULL);
}
#else
int
cuio_getptr(struct uio *uio, int loc, int *off)
{
int ind, len;
ind = 0;
while (loc >= 0 && ind < uio->uio_iovcnt) {
len = uio->uio_iov[ind].iov_len;
if (len > loc) {
*off = loc;
return (ind);
}
loc -= len;
ind++;
}
if (ind > 0 && loc == 0) {
ind--;
*off = uio->uio_iov[ind].iov_len;
return (ind);
}
return (-1);
}
#endif
int
cuio_apply(struct uio *uio, int off, int len,
int (*f)(caddr_t, caddr_t, unsigned int), caddr_t fstate)
{
int rval, ind, uiolen;
unsigned int count;
if (len < 0)
panic("%s: len %d < 0", __func__, len);
if (off < 0)
panic("%s: off %d < 0", __func__, off);
ind = 0;
while (off > 0) {
if (ind >= uio->uio_iovcnt)
panic("m_apply: null mbuf in skip");
uiolen = uio->uio_iov[ind].iov_len;
if (off < uiolen)
break;
off -= uiolen;
ind++;
}
while (len > 0) {
if (ind >= uio->uio_iovcnt)
panic("m_apply: null mbuf");
count = min(uio->uio_iov[ind].iov_len - off, len);
rval = f(fstate,
((caddr_t)uio->uio_iov[ind].iov_base + off), count);
if (rval)
return (rval);
len -= count;
off = 0;
ind++;
}
return (0);
}

1231
sys/opencrypto/crypto.c Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,124 @@
/* $NetBSD: crypto_mbuf.c,v 1.1 2003/07/25 21:12:44 jonathan Exp $ */
/* $FreeBSD: crmbuf.c,v 1.1 2002/10/04 20:31:22 sam Exp $ */
/*
* Copyright (c) 2002 Somebody. All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the University of
* California, Berkeley and its contributors.
* 4. Neither the name of the University nor the names of its contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*
* $FreeBSD: src/sys/opencrypto/crmbuf.c,v 1.1 2002/10/04 20:31:22 sam Exp $
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: crypto_mbuf.c,v 1.1 2003/07/25 21:12:44 jonathan Exp $");
/*#include "opt_param.h"*/
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/mbuf.h>
#include <sys/kernel.h>
/*
* Miscellaneous mbuf routines that belong in uipc_mbuf.c but
* are kept private to the crypto support for now.
*/
extern int m_apply(struct mbuf *m, int off, int len,
int (*f)(caddr_t, caddr_t, unsigned int), caddr_t fstate);
extern struct mbuf * m_getptr(struct mbuf *m, int loc, int *off);
/*
* Apply function f to the data in an mbuf chain starting "off" bytes from the
* beginning, continuing for "len" bytes.
*/
int
m_apply(struct mbuf *m, int off, int len, int (*f)(caddr_t, caddr_t, unsigned int), caddr_t fstate)
{
int rval;
unsigned int count;
if (len < 0)
panic("m_apply: len %d < 0", len);
if (off < 0)
panic("m_apply: off %d < 0", off);
while (off > 0) {
if (m == NULL)
panic("m_apply: null mbuf in skip");
if (off < m->m_len)
break;
off -= m->m_len;
m = m->m_next;
}
while (len > 0) {
if (m == NULL)
panic("m_apply: null mbuf");
count = min(m->m_len - off, len);
rval = f(fstate, mtod(m, caddr_t) + off, count);
if (rval)
return (rval);
len -= count;
off = 0;
m = m->m_next;
}
return (0);
}
/*
* Return a pointer to mbuf/offset of location in mbuf chain.
*/
struct mbuf *
m_getptr(struct mbuf *m, int loc, int *off)
{
while (loc >= 0) {
/* Normal end of search */
if (m->m_len > loc) {
*off = loc;
return (m);
}
else {
loc -= m->m_len;
if (m->m_next == NULL) {
if (loc == 0) {
/* Point at the end of valid data */
*off = m->m_len;
return (m);
}
else
return (NULL);
}
else
m = m->m_next;
}
}
return (NULL);
}

797
sys/opencrypto/cryptodev.c Normal file
View File

@ -0,0 +1,797 @@
/* $NetBSD: cryptodev.c,v 1.1 2003/07/25 21:12:44 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/cryptodev.c,v 1.4.2.3 2003/02/26 00:14:05 sam Exp $ */
/* $OpenBSD: cryptodev.c,v 1.53 2002/07/10 22:21:30 mickey Exp $ */
/*
* Copyright (c) 2001 Theo de Raadt
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*
* Effort sponsored in part by the Defense Advanced Research Projects
* Agency (DARPA) and Air Force Research Laboratory, Air Force
* Materiel Command, USAF, under agreement number F30602-01-2-0537.
*
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: cryptodev.c,v 1.1 2003/07/25 21:12:44 jonathan Exp $");
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/malloc.h>
#include <sys/mbuf.h>
#include <sys/sysctl.h>
#include <sys/file.h>
#include <sys/filedesc.h>
#include <sys/errno.h>
#include <sys/md5k.h>
#include <sys/sha1.h>
#include <dev/rndvar.h>
#include <sys/conf.h>
#include <sys/device.h>
#include <opencrypto/rmd160.h>
#include <opencrypto/cast.h>
#include <opencrypto/skipjack.h>
#include <opencrypto/blf.h>
#include <opencrypto/cryptodev.h>
#include <opencrypto/xform.h>
#ifdef __NetBSD__
#define splcrypto splnet
#endif
struct csession {
TAILQ_ENTRY(csession) next;
u_int64_t sid;
u_int32_t ses;
u_int32_t cipher;
struct enc_xform *txform;
u_int32_t mac;
struct auth_hash *thash;
caddr_t key;
int keylen;
u_char tmp_iv[EALG_MAX_BLOCK_LEN];
caddr_t mackey;
int mackeylen;
u_char tmp_mac[CRYPTO_MAX_MAC_LEN];
struct iovec iovec[IOV_MAX];
struct uio uio;
int error;
};
struct fcrypt {
TAILQ_HEAD(csessionlist, csession) csessions;
int sesn;
};
/* Declaration of master device (fd-cloning/ctxt-allocating) entrypoints */
static int cryptoopen(dev_t dev, int flag, int mode, struct proc *p);
static int cryptoread(dev_t dev, struct uio *uio, int ioflag);
static int cryptowrite(dev_t dev, struct uio *uio, int ioflag);
static int cryptoioctl(dev_t dev, u_long cmd, caddr_t data, int flag, struct proc *p);
static int cryptoselect(dev_t dev, int rw, struct proc *p);
/* Declaration of cloned-device (per-ctxt) entrypoints */
static int cryptof_read(struct file *, off_t *, struct uio *, struct ucred *, int);
static int cryptof_write(struct file *, off_t *, struct uio *, struct ucred *, int);
static int cryptof_ioctl(struct file *, u_long, void*, struct proc *p);
static int cryptof_fcntl(struct file *, u_int, void*, struct proc *p);
static int cryptof_poll(struct file *, int, struct proc *);
static int cryptof_kqfilter(struct file *, struct knote *);
static int cryptof_stat(struct file *, struct stat *, struct proc *);
static int cryptof_close(struct file *, struct proc *);
static struct fileops cryptofops = {
cryptof_read,
cryptof_write,
cryptof_ioctl,
cryptof_fcntl,
cryptof_poll,
cryptof_stat,
cryptof_close,
cryptof_kqfilter
};
static struct csession *csefind(struct fcrypt *, u_int);
static int csedelete(struct fcrypt *, struct csession *);
static struct csession *cseadd(struct fcrypt *, struct csession *);
static struct csession *csecreate(struct fcrypt *, u_int64_t, caddr_t, u_int64_t,
caddr_t, u_int64_t, u_int32_t, u_int32_t, struct enc_xform *,
struct auth_hash *);
static int csefree(struct csession *);
static int cryptodev_op(struct csession *, struct crypt_op *, struct proc *);
static int cryptodev_key(struct crypt_kop *);
int cryptodev_dokey(struct crypt_kop *kop, struct crparam kvp[]);
static int cryptodev_cb(void *);
static int cryptodevkey_cb(void *);
int usercrypto = 1; /* userland may do crypto requests */
int userasymcrypto = 1; /* userland may do asymmetric crypto reqs */
int cryptodevallowsoft = 1; /* only use hardware crypto */
/* ARGSUSED */
int
cryptof_read(struct file *fp, off_t *poff, struct uio *uio,
struct ucred *cred, int flags)
{
return (EIO);
}
/* ARGSUSED */
int
cryptof_write(struct file *fp, off_t *poff, struct uio *uio,
struct ucred *cred, int flags)
{
return (EIO);
}
/* ARGSUSED */
int
cryptof_ioctl(struct file *fp, u_long cmd, void* data, struct proc *p)
{
struct cryptoini cria, crie;
struct fcrypt *fcr = (struct fcrypt *)fp->f_data;
struct csession *cse;
struct session_op *sop;
struct crypt_op *cop;
struct enc_xform *txform = NULL;
struct auth_hash *thash = NULL;
u_int64_t sid;
u_int32_t ses;
int error = 0;
switch (cmd) {
case CIOCGSESSION:
sop = (struct session_op *)data;
switch (sop->cipher) {
case 0:
break;
case CRYPTO_DES_CBC:
txform = &enc_xform_des;
break;
case CRYPTO_3DES_CBC:
txform = &enc_xform_3des;
break;
case CRYPTO_BLF_CBC:
txform = &enc_xform_blf;
break;
case CRYPTO_CAST_CBC:
txform = &enc_xform_cast5;
break;
case CRYPTO_SKIPJACK_CBC:
txform = &enc_xform_skipjack;
break;
case CRYPTO_AES_CBC:
txform = &enc_xform_rijndael128;
break;
case CRYPTO_NULL_CBC:
txform = &enc_xform_null;
break;
case CRYPTO_ARC4:
txform = &enc_xform_arc4;
break;
default:
return (EINVAL);
}
switch (sop->mac) {
case 0:
break;
case CRYPTO_MD5_HMAC:
thash = &auth_hash_hmac_md5_96;
break;
case CRYPTO_SHA1_HMAC:
thash = &auth_hash_hmac_sha1_96;
break;
case CRYPTO_SHA2_HMAC:
if (sop->mackeylen == auth_hash_hmac_sha2_256.keysize)
thash = &auth_hash_hmac_sha2_256;
else if (sop->mackeylen == auth_hash_hmac_sha2_384.keysize)
thash = &auth_hash_hmac_sha2_384;
else if (sop->mackeylen == auth_hash_hmac_sha2_512.keysize)
thash = &auth_hash_hmac_sha2_512;
else
return (EINVAL);
break;
case CRYPTO_RIPEMD160_HMAC:
thash = &auth_hash_hmac_ripemd_160_96;
break;
#ifdef notdef
case CRYPTO_MD5:
thash = &auth_hash_md5;
break;
case CRYPTO_SHA1:
thash = &auth_hash_sha1;
break;
#endif
case CRYPTO_NULL_HMAC:
thash = &auth_hash_null;
break;
default:
return (EINVAL);
}
bzero(&crie, sizeof(crie));
bzero(&cria, sizeof(cria));
if (txform) {
crie.cri_alg = txform->type;
crie.cri_klen = sop->keylen * 8;
if (sop->keylen > txform->maxkey ||
sop->keylen < txform->minkey) {
error = EINVAL;
goto bail;
}
MALLOC(crie.cri_key, u_int8_t *,
crie.cri_klen / 8, M_XDATA, M_WAITOK);
if ((error = copyin(sop->key, crie.cri_key,
crie.cri_klen / 8)))
goto bail;
if (thash)
crie.cri_next = &cria;
}
if (thash) {
cria.cri_alg = thash->type;
cria.cri_klen = sop->mackeylen * 8;
if (sop->mackeylen != thash->keysize) {
error = EINVAL;
goto bail;
}
if (cria.cri_klen) {
MALLOC(cria.cri_key, u_int8_t *,
cria.cri_klen / 8, M_XDATA, M_WAITOK);
if ((error = copyin(sop->mackey, cria.cri_key,
cria.cri_klen / 8)))
goto bail;
}
}
error = crypto_newsession(&sid, (txform ? &crie : &cria),
0);
if (error) {
/* this is an auditable security event? */
printf("SIOCSESSION violates kernel parameters\n");
goto bail;
}
cse = csecreate(fcr, sid, crie.cri_key, crie.cri_klen,
cria.cri_key, cria.cri_klen, sop->cipher, sop->mac, txform,
thash);
if (cse == NULL) {
crypto_freesession(sid);
error = EINVAL;
goto bail;
}
sop->ses = cse->ses;
bail:
if (error) {
if (crie.cri_key)
FREE(crie.cri_key, M_XDATA);
if (cria.cri_key)
FREE(cria.cri_key, M_XDATA);
}
break;
case CIOCFSESSION:
ses = *(u_int32_t *)data;
cse = csefind(fcr, ses);
if (cse == NULL)
return (EINVAL);
csedelete(fcr, cse);
error = csefree(cse);
break;
case CIOCCRYPT:
cop = (struct crypt_op *)data;
cse = csefind(fcr, cop->ses);
if (cse == NULL)
return (EINVAL);
error = cryptodev_op(cse, cop, p);
break;
case CIOCKEY:
error = cryptodev_key((struct crypt_kop *)data);
break;
case CIOCASYMFEAT:
error = crypto_getfeat((int *)data);
break;
default:
error = EINVAL;
}
return (error);
}
/* ARGSUSED */
int
cryptof_fcntl(struct file *fp, u_int cmd, void *data, struct proc *p)
{
return (0);
}
static int
cryptodev_op(struct csession *cse, struct crypt_op *cop, struct proc *p)
{
struct cryptop *crp = NULL;
struct cryptodesc *crde = NULL, *crda = NULL;
int i, error, s;
if (cop->len > 256*1024-4)
return (E2BIG);
if (cse->txform && (cop->len % cse->txform->blocksize) != 0)
return (EINVAL);
bzero(&cse->uio, sizeof(cse->uio));
cse->uio.uio_iovcnt = 1;
cse->uio.uio_resid = 0;
cse->uio.uio_segflg = UIO_SYSSPACE;
cse->uio.uio_rw = UIO_WRITE;
cse->uio.uio_procp = p;
cse->uio.uio_iov = cse->iovec;
bzero(&cse->iovec, sizeof(cse->iovec));
cse->uio.uio_iov[0].iov_len = cop->len;
cse->uio.uio_iov[0].iov_base = malloc(cop->len, M_XDATA, M_WAITOK);
for (i = 0; i < cse->uio.uio_iovcnt; i++)
cse->uio.uio_resid += cse->uio.uio_iov[0].iov_len;
crp = crypto_getreq((cse->txform != NULL) + (cse->thash != NULL));
if (crp == NULL) {
error = ENOMEM;
goto bail;
}
if (cse->thash) {
crda = crp->crp_desc;
if (cse->txform)
crde = crda->crd_next;
} else {
if (cse->txform)
crde = crp->crp_desc;
else {
error = EINVAL;
goto bail;
}
}
if ((error = copyin(cop->src, cse->uio.uio_iov[0].iov_base, cop->len)))
goto bail;
if (crda) {
crda->crd_skip = 0;
crda->crd_len = cop->len;
crda->crd_inject = 0; /* ??? */
crda->crd_alg = cse->mac;
crda->crd_key = cse->mackey;
crda->crd_klen = cse->mackeylen * 8;
}
if (crde) {
if (cop->op == COP_ENCRYPT)
crde->crd_flags |= CRD_F_ENCRYPT;
else
crde->crd_flags &= ~CRD_F_ENCRYPT;
crde->crd_len = cop->len;
crde->crd_inject = 0;
crde->crd_alg = cse->cipher;
crde->crd_key = cse->key;
crde->crd_klen = cse->keylen * 8;
}
crp->crp_ilen = cop->len;
crp->crp_flags = CRYPTO_F_IOV | CRYPTO_F_CBIMM
| (cop->flags & COP_F_BATCH);
crp->crp_buf = (caddr_t)&cse->uio;
crp->crp_callback = (int (*) (struct cryptop *)) cryptodev_cb;
crp->crp_sid = cse->sid;
crp->crp_opaque = (void *)cse;
if (cop->iv) {
if (crde == NULL) {
error = EINVAL;
goto bail;
}
if (cse->cipher == CRYPTO_ARC4) { /* XXX use flag? */
error = EINVAL;
goto bail;
}
if ((error = copyin(cop->iv, cse->tmp_iv, cse->txform->blocksize)))
goto bail;
bcopy(cse->tmp_iv, crde->crd_iv, cse->txform->blocksize);
crde->crd_flags |= CRD_F_IV_EXPLICIT | CRD_F_IV_PRESENT;
crde->crd_skip = 0;
} else if (cse->cipher == CRYPTO_ARC4) { /* XXX use flag? */
crde->crd_skip = 0;
} else if (crde) {
crde->crd_flags |= CRD_F_IV_PRESENT;
crde->crd_skip = cse->txform->blocksize;
crde->crd_len -= cse->txform->blocksize;
}
if (cop->mac) {
if (crda == NULL) {
error = EINVAL;
goto bail;
}
crp->crp_mac=cse->tmp_mac;
}
s = splcrypto(); /* NB: only needed with CRYPTO_F_CBIMM */
error = crypto_dispatch(crp);
if (error == 0) {
error = tsleep(crp, PSOCK, "crydev", 0);
}
splx(s);
if (error) {
goto bail;
}
if (crp->crp_etype != 0) {
error = crp->crp_etype;
goto bail;
}
if (cse->error) {
error = cse->error;
goto bail;
}
if (cop->dst &&
(error = copyout(cse->uio.uio_iov[0].iov_base, cop->dst, cop->len)))
goto bail;
if (cop->mac &&
(error = copyout(crp->crp_mac, cop->mac, cse->thash->authsize)))
goto bail;
bail:
if (crp)
crypto_freereq(crp);
if (cse->uio.uio_iov[0].iov_base)
free(cse->uio.uio_iov[0].iov_base, M_XDATA);
return (error);
}
static int
cryptodev_cb(void *op)
{
struct cryptop *crp = (struct cryptop *) op;
struct csession *cse = (struct csession *)crp->crp_opaque;
cse->error = crp->crp_etype;
if (crp->crp_etype == EAGAIN)
return crypto_dispatch(crp);
wakeup_one(crp);
return (0);
}
static int
cryptodevkey_cb(void *op)
{
struct cryptkop *krp = (struct cryptkop *) op;
wakeup_one(krp);
return (0);
}
static int
cryptodev_key(struct crypt_kop *kop)
{
struct cryptkop *krp = NULL;
int error = EINVAL;
int in, out, size, i;
if (kop->crk_iparams + kop->crk_oparams > CRK_MAXPARAM) {
return (EFBIG);
}
in = kop->crk_iparams;
out = kop->crk_oparams;
switch (kop->crk_op) {
case CRK_MOD_EXP:
if (in == 3 && out == 1)
break;
return (EINVAL);
case CRK_MOD_EXP_CRT:
if (in == 6 && out == 1)
break;
return (EINVAL);
case CRK_DSA_SIGN:
if (in == 5 && out == 2)
break;
return (EINVAL);
case CRK_DSA_VERIFY:
if (in == 7 && out == 0)
break;
return (EINVAL);
case CRK_DH_COMPUTE_KEY:
if (in == 3 && out == 1)
break;
return (EINVAL);
default:
return (EINVAL);
}
krp = (struct cryptkop *)malloc(sizeof *krp, M_XDATA, M_WAITOK);
if (!krp)
return (ENOMEM);
bzero(krp, sizeof *krp);
krp->krp_op = kop->crk_op;
krp->krp_status = kop->crk_status;
krp->krp_iparams = kop->crk_iparams;
krp->krp_oparams = kop->crk_oparams;
krp->krp_status = 0;
krp->krp_callback = (int (*) (struct cryptkop *)) cryptodevkey_cb;
for (i = 0; i < CRK_MAXPARAM; i++)
krp->krp_param[i].crp_nbits = kop->crk_param[i].crp_nbits;
for (i = 0; i < krp->krp_iparams + krp->krp_oparams; i++) {
size = (krp->krp_param[i].crp_nbits + 7) / 8;
if (size == 0)
continue;
MALLOC(krp->krp_param[i].crp_p, caddr_t, size, M_XDATA, M_WAITOK);
if (i >= krp->krp_iparams)
continue;
error = copyin(kop->crk_param[i].crp_p, krp->krp_param[i].crp_p, size);
if (error)
goto fail;
}
error = crypto_kdispatch(krp);
if (error == 0)
error = tsleep(krp, PSOCK, "crydev", 0);
if (error)
goto fail;
if (krp->krp_status != 0) {
error = krp->krp_status;
goto fail;
}
for (i = krp->krp_iparams; i < krp->krp_iparams + krp->krp_oparams; i++) {
size = (krp->krp_param[i].crp_nbits + 7) / 8;
if (size == 0)
continue;
error = copyout(krp->krp_param[i].crp_p, kop->crk_param[i].crp_p, size);
if (error)
goto fail;
}
fail:
if (krp) {
kop->crk_status = krp->krp_status;
for (i = 0; i < CRK_MAXPARAM; i++) {
if (krp->krp_param[i].crp_p)
FREE(krp->krp_param[i].crp_p, M_XDATA);
}
free(krp, M_XDATA);
}
return (error);
}
/* ARGSUSED */
static int
cryptof_poll(struct file *fp, int which, struct proc *p)
{
return (0);
}
/* ARGSUSED */
static int
cryptof_kqfilter(struct file *fp, struct knote *kn)
{
return (0);
}
/* ARGSUSED */
static int
cryptof_stat(struct file *fp, struct stat *sb, struct proc *p)
{
return (EOPNOTSUPP);
}
/* ARGSUSED */
static int
cryptof_close(struct file *fp, struct proc *p)
{
struct fcrypt *fcr = (struct fcrypt *)fp->f_data;
struct csession *cse;
while ((cse = TAILQ_FIRST(&fcr->csessions))) {
TAILQ_REMOVE(&fcr->csessions, cse, next);
(void)csefree(cse);
}
FREE(fcr, M_XDATA);
/* close() stolen from sys/kern/kern_ktrace.c */
fp->f_data = NULL;
#if 0
FILE_UNUSE(fp, p); /* release file */
fdrelease(p, fd); /* release fd table slot */
#endif
return 0;
}
static struct csession *
csefind(struct fcrypt *fcr, u_int ses)
{
struct csession *cse;
TAILQ_FOREACH(cse, &fcr->csessions, next)
if (cse->ses == ses)
return (cse);
return (NULL);
}
static int
csedelete(struct fcrypt *fcr, struct csession *cse_del)
{
struct csession *cse;
TAILQ_FOREACH(cse, &fcr->csessions, next) {
if (cse == cse_del) {
TAILQ_REMOVE(&fcr->csessions, cse, next);
return (1);
}
}
return (0);
}
static struct csession *
cseadd(struct fcrypt *fcr, struct csession *cse)
{
TAILQ_INSERT_TAIL(&fcr->csessions, cse, next);
cse->ses = fcr->sesn++;
return (cse);
}
static struct csession *
csecreate(struct fcrypt *fcr, u_int64_t sid, caddr_t key, u_int64_t keylen,
caddr_t mackey, u_int64_t mackeylen, u_int32_t cipher, u_int32_t mac,
struct enc_xform *txform, struct auth_hash *thash)
{
struct csession *cse;
MALLOC(cse, struct csession *, sizeof(struct csession),
M_XDATA, M_NOWAIT);
if (cse == NULL)
return NULL;
cse->key = key;
cse->keylen = keylen/8;
cse->mackey = mackey;
cse->mackeylen = mackeylen/8;
cse->sid = sid;
cse->cipher = cipher;
cse->mac = mac;
cse->txform = txform;
cse->thash = thash;
cseadd(fcr, cse);
return (cse);
}
static int
csefree(struct csession *cse)
{
int error;
error = crypto_freesession(cse->sid);
if (cse->key)
FREE(cse->key, M_XDATA);
if (cse->mackey)
FREE(cse->mackey, M_XDATA);
FREE(cse, M_XDATA);
return (error);
}
static int
cryptoopen(dev_t dev, int flag, int mode, struct proc *p)
{
if (crypto_usercrypto == 0)
return (ENXIO);
return (0);
}
static int
cryptoread(dev_t dev, struct uio *uio, int ioflag)
{
return (EIO);
}
static int
cryptowrite(dev_t dev, struct uio *uio, int ioflag)
{
return (EIO);
}
static int
cryptoioctl(dev_t dev, u_long cmd, caddr_t data, int flag, struct proc *p)
{
struct file *f;
struct fcrypt *fcr;
int fd, error;
switch (cmd) {
case CRIOGET:
MALLOC(fcr, struct fcrypt *,
sizeof(struct fcrypt), M_XDATA, M_WAITOK);
TAILQ_INIT(&fcr->csessions);
fcr->sesn = 0;
error = falloc(p, &f, &fd);
if (error) {
FREE(fcr, M_XDATA);
return (error);
}
f->f_flag = FREAD | FWRITE;
f->f_type = DTYPE_CRYPTO;
f->f_ops = &cryptofops;
f->f_data = (caddr_t) fcr;
*(u_int32_t *)data = fd;
FILE_SET_MATURE(f);
FILE_UNUSE(f, p);
break;
default:
error = EINVAL;
break;
}
return (error);
}
int
cryptoselect(dev_t dev, int rw, struct proc *p)
{
return (0);
}
#define CRYPTO_MAJOR 70 /* from openbsd */
/*static*/
struct cdevsw crypto_cdevsw = {
/* open */ cryptoopen,
/* close */ nullclose,
/* read */ cryptoread,
/* write */ cryptowrite,
/* ioctl */ cryptoioctl,
/* ttstop?*/ nostop,
/* ??*/ notty,
/* poll */ cryptoselect /*nopoll*/,
/* mmap */ nommap,
/* kqfilter */ nokqfilter,
};

392
sys/opencrypto/cryptodev.h Normal file
View File

@ -0,0 +1,392 @@
/* $NetBSD: cryptodev.h,v 1.1 2003/07/25 21:12:44 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/cryptodev.h,v 1.2.2.4 2003/02/26 00:14:05 sam Exp $ */
/* $OpenBSD: cryptodev.h,v 1.33 2002/07/17 23:52:39 art Exp $ */
/*
* The author of this code is Angelos D. Keromytis (angelos@cis.upenn.edu)
*
* This code was written by Angelos D. Keromytis in Athens, Greece, in
* February 2000. Network Security Technologies Inc. (NSTI) kindly
* supported the development of this code.
*
* Copyright (c) 2000 Angelos D. Keromytis
*
* Permission to use, copy, and modify this software with or without fee
* is hereby granted, provided that this entire notice is included in
* all source code copies of any software which is or includes a copy or
* modification of this software.
*
* THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR
* IMPLIED WARRANTY. IN PARTICULAR, NONE OF THE AUTHORS MAKES ANY
* REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE
* MERCHANTABILITY OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR
* PURPOSE.
*
* Copyright (c) 2001 Theo de Raadt
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*
* Effort sponsored in part by the Defense Advanced Research Projects
* Agency (DARPA) and Air Force Research Laboratory, Air Force
* Materiel Command, USAF, under agreement number F30602-01-2-0537.
*
*/
#ifndef _CRYPTO_CRYPTO_H_
#define _CRYPTO_CRYPTO_H_
#include <sys/ioccom.h>
/* Some initial values */
#define CRYPTO_DRIVERS_INITIAL 4
#define CRYPTO_SW_SESSIONS 32
/* HMAC values */
#define HMAC_BLOCK_LEN 64
#define HMAC_IPAD_VAL 0x36
#define HMAC_OPAD_VAL 0x5C
/* Encryption algorithm block sizes */
#define DES_BLOCK_LEN 8
#define DES3_BLOCK_LEN 8
#define BLOWFISH_BLOCK_LEN 8
#define SKIPJACK_BLOCK_LEN 8
#define CAST128_BLOCK_LEN 8
#define RIJNDAEL128_BLOCK_LEN 16
#define EALG_MAX_BLOCK_LEN 16 /* Keep this updated */
/* Maximum hash algorithm result length */
#define AALG_MAX_RESULT_LEN 64 /* Keep this updated */
#define CRYPTO_ALGORITHM_MIN 1
#define CRYPTO_DES_CBC 1
#define CRYPTO_3DES_CBC 2
#define CRYPTO_BLF_CBC 3
#define CRYPTO_CAST_CBC 4
#define CRYPTO_SKIPJACK_CBC 5
#define CRYPTO_MD5_HMAC 6
#define CRYPTO_SHA1_HMAC 7
#define CRYPTO_RIPEMD160_HMAC 8
#define CRYPTO_MD5_KPDK 9
#define CRYPTO_SHA1_KPDK 10
#define CRYPTO_RIJNDAEL128_CBC 11 /* 128 bit blocksize */
#define CRYPTO_AES_CBC 11 /* 128 bit blocksize -- the same as above */
#define CRYPTO_ARC4 12
#define CRYPTO_MD5 13
#define CRYPTO_SHA1 14
#define CRYPTO_SHA2_HMAC 15
#define CRYPTO_NULL_HMAC 16
#define CRYPTO_NULL_CBC 17
#define CRYPTO_DEFLATE_COMP 18 /* Deflate compression algorithm */
#define CRYPTO_ALGORITHM_MAX 18 /* Keep updated - see below */
/* Algorithm flags */
#define CRYPTO_ALG_FLAG_SUPPORTED 0x01 /* Algorithm is supported */
#define CRYPTO_ALG_FLAG_RNG_ENABLE 0x02 /* Has HW RNG for DH/DSA */
#define CRYPTO_ALG_FLAG_DSA_SHA 0x04 /* Can do SHA on msg */
struct session_op {
u_int32_t cipher; /* ie. CRYPTO_DES_CBC */
u_int32_t mac; /* ie. CRYPTO_MD5_HMAC */
u_int32_t keylen; /* cipher key */
caddr_t key;
int mackeylen; /* mac key */
caddr_t mackey;
u_int32_t ses; /* returns: session # */
};
struct crypt_op {
u_int32_t ses;
u_int16_t op; /* i.e. COP_ENCRYPT */
#define COP_ENCRYPT 1
#define COP_DECRYPT 2
u_int16_t flags;
#define COP_F_BATCH 0x0008 /* Dispatch as quickly as possible */
u_int len;
caddr_t src, dst; /* become iov[] inside kernel */
caddr_t mac; /* must be big enough for chosen MAC */
caddr_t iv;
};
#define CRYPTO_MAX_MAC_LEN 20
/* bignum parameter, in packed bytes, ... */
struct crparam {
caddr_t crp_p;
u_int crp_nbits;
};
#define CRK_MAXPARAM 8
struct crypt_kop {
u_int crk_op; /* ie. CRK_MOD_EXP or other */
u_int crk_status; /* return status */
u_short crk_iparams; /* # of input parameters */
u_short crk_oparams; /* # of output parameters */
u_int crk_pad1;
struct crparam crk_param[CRK_MAXPARAM];
};
#define CRK_ALGORITM_MIN 0
#define CRK_MOD_EXP 0
#define CRK_MOD_EXP_CRT 1
#define CRK_DSA_SIGN 2
#define CRK_DSA_VERIFY 3
#define CRK_DH_COMPUTE_KEY 4
#define CRK_ALGORITHM_MAX 4 /* Keep updated - see below */
#define CRF_MOD_EXP (1 << CRK_MOD_EXP)
#define CRF_MOD_EXP_CRT (1 << CRK_MOD_EXP_CRT)
#define CRF_DSA_SIGN (1 << CRK_DSA_SIGN)
#define CRF_DSA_VERIFY (1 << CRK_DSA_VERIFY)
#define CRF_DH_COMPUTE_KEY (1 << CRK_DH_COMPUTE_KEY)
/*
* done against open of /dev/crypto, to get a cloned descriptor.
* Please use F_SETFD against the cloned descriptor.
*/
#define CRIOGET _IOWR('c', 100, u_int32_t)
/* the following are done against the cloned descriptor */
#define CIOCGSESSION _IOWR('c', 101, struct session_op)
#define CIOCFSESSION _IOW('c', 102, u_int32_t)
#define CIOCCRYPT _IOWR('c', 103, struct crypt_op)
#define CIOCKEY _IOWR('c', 104, struct crypt_kop)
#define CIOCASYMFEAT _IOR('c', 105, u_int32_t)
struct cryptotstat {
struct timespec acc; /* total accumulated time */
struct timespec min; /* max time */
struct timespec max; /* max time */
u_int32_t count; /* number of observations */
};
struct cryptostats {
u_int32_t cs_ops; /* symmetric crypto ops submitted */
u_int32_t cs_errs; /* symmetric crypto ops that failed */
u_int32_t cs_kops; /* asymetric/key ops submitted */
u_int32_t cs_kerrs; /* asymetric/key ops that failed */
u_int32_t cs_intrs; /* crypto swi thread activations */
u_int32_t cs_rets; /* crypto return thread activations */
u_int32_t cs_blocks; /* symmetric op driver block */
u_int32_t cs_kblocks; /* symmetric op driver block */
/*
* When CRYPTO_TIMING is defined at compile time and the
* sysctl debug.crypto is set to 1, the crypto system will
* accumulate statistics about how long it takes to process
* crypto requests at various points during processing.
*/
struct cryptotstat cs_invoke; /* crypto_dipsatch -> crypto_invoke */
struct cryptotstat cs_done; /* crypto_invoke -> crypto_done */
struct cryptotstat cs_cb; /* crypto_done -> callback */
struct cryptotstat cs_finis; /* callback -> callback return */
};
#ifdef _KERNEL
/* Standard initialization structure beginning */
struct cryptoini {
int cri_alg; /* Algorithm to use */
int cri_klen; /* Key length, in bits */
int cri_rnd; /* Algorithm rounds, where relevant */
caddr_t cri_key; /* key to use */
u_int8_t cri_iv[EALG_MAX_BLOCK_LEN]; /* IV to use */
struct cryptoini *cri_next;
};
/* Describe boundaries of a single crypto operation */
struct cryptodesc {
int crd_skip; /* How many bytes to ignore from start */
int crd_len; /* How many bytes to process */
int crd_inject; /* Where to inject results, if applicable */
int crd_flags;
#define CRD_F_ENCRYPT 0x01 /* Set when doing encryption */
#define CRD_F_IV_PRESENT 0x02 /* When encrypting, IV is already in
place, so don't copy. */
#define CRD_F_IV_EXPLICIT 0x04 /* IV explicitly provided */
#define CRD_F_DSA_SHA_NEEDED 0x08 /* Compute SHA-1 of buffer for DSA */
#define CRD_F_COMP 0x0f /* Set when doing compression */
struct cryptoini CRD_INI; /* Initialization/context data */
#define crd_iv CRD_INI.cri_iv
#define crd_key CRD_INI.cri_key
#define crd_rnd CRD_INI.cri_rnd
#define crd_alg CRD_INI.cri_alg
#define crd_klen CRD_INI.cri_klen
struct cryptodesc *crd_next;
};
/* Structure describing complete operation */
struct cryptop {
TAILQ_ENTRY(cryptop) crp_next;
u_int64_t crp_sid; /* Session ID */
int crp_ilen; /* Input data total length */
int crp_olen; /* Result total length */
int crp_etype; /*
* Error type (zero means no error).
* All error codes except EAGAIN
* indicate possible data corruption (as in,
* the data have been touched). On all
* errors, the crp_sid may have changed
* (reset to a new one), so the caller
* should always check and use the new
* value on future requests.
*/
int crp_flags;
#define CRYPTO_F_IMBUF 0x0001 /* Input/output are mbuf chains, otherwise contig */
#define CRYPTO_F_IOV 0x0002 /* Input/output are uio */
#define CRYPTO_F_REL 0x0004 /* Must return data in same place */
#define CRYPTO_F_BATCH 0x0008 /* Batch op if possible possible */
#define CRYPTO_F_CBIMM 0x0010 /* Do callback immediately */
caddr_t crp_buf; /* Data to be processed */
caddr_t crp_opaque; /* Opaque pointer, passed along */
struct cryptodesc *crp_desc; /* Linked list of processing descriptors */
int (*crp_callback)(struct cryptop *); /* Callback function */
caddr_t crp_mac;
struct timespec crp_tstamp; /* performance time stamp */
};
#define CRYPTO_BUF_CONTIG 0x0
#define CRYPTO_BUF_IOV 0x1
#define CRYPTO_BUF_MBUF 0x2
#define CRYPTO_OP_DECRYPT 0x0
#define CRYPTO_OP_ENCRYPT 0x1
/*
* Hints passed to process methods.
*/
#define CRYPTO_HINT_MORE 0x1 /* more ops coming shortly */
struct cryptkop {
TAILQ_ENTRY(cryptkop) krp_next;
u_int krp_op; /* ie. CRK_MOD_EXP or other */
u_int krp_status; /* return status */
u_short krp_iparams; /* # of input parameters */
u_short krp_oparams; /* # of output parameters */
u_int32_t krp_hid;
struct crparam krp_param[CRK_MAXPARAM]; /* kvm */
int (*krp_callback)(struct cryptkop *);
};
/* Crypto capabilities structure */
struct cryptocap {
u_int32_t cc_sessions;
/*
* Largest possible operator length (in bits) for each type of
* encryption algorithm.
*/
u_int16_t cc_max_op_len[CRYPTO_ALGORITHM_MAX + 1];
u_int8_t cc_alg[CRYPTO_ALGORITHM_MAX + 1];
u_int8_t cc_kalg[CRK_ALGORITHM_MAX + 1];
u_int8_t cc_flags;
u_int8_t cc_qblocked; /* symmetric q blocked */
u_int8_t cc_kqblocked; /* asymmetric q blocked */
#define CRYPTOCAP_F_CLEANUP 0x1
#define CRYPTOCAP_F_SOFTWARE 0x02
void *cc_arg; /* callback argument */
int (*cc_newsession)(void*, u_int32_t*, struct cryptoini*);
int (*cc_process) (void*, struct cryptop *, int);
int (*cc_freesession) (void*, u_int64_t);
void *cc_karg; /* callback argument */
int (*cc_kprocess) (void*, struct cryptkop *, int);
};
MALLOC_DECLARE(M_CRYPTO_DATA);
extern int crypto_newsession(u_int64_t *sid, struct cryptoini *cri, int hard);
extern int crypto_freesession(u_int64_t sid);
extern int32_t crypto_get_driverid(u_int32_t flags);
extern int crypto_register(u_int32_t driverid, int alg, u_int16_t maxoplen,
u_int32_t flags,
int (*newses)(void*, u_int32_t*, struct cryptoini*),
int (*freeses)(void*, u_int64_t),
int (*process)(void*, struct cryptop *, int),
void *arg);
extern int crypto_kregister(u_int32_t, int, u_int32_t,
int (*)(void*, struct cryptkop *, int),
void *arg);
extern int crypto_unregister(u_int32_t driverid, int alg);
extern int crypto_unregister_all(u_int32_t driverid);
extern int crypto_dispatch(struct cryptop *crp);
extern int crypto_kdispatch(struct cryptkop *);
#define CRYPTO_SYMQ 0x1
#define CRYPTO_ASYMQ 0x2
extern int crypto_unblock(u_int32_t, int);
extern void crypto_done(struct cryptop *crp);
extern void crypto_kdone(struct cryptkop *);
extern int crypto_getfeat(int *);
void cuio_copydata(struct uio *, int, int, caddr_t);
void cuio_copyback(struct uio *, int, int, caddr_t);
int cuio_apply(struct uio *, int, int,
int (*f)(caddr_t, caddr_t, unsigned int), caddr_t);
extern void crypto_freereq(struct cryptop *crp);
extern struct cryptop *crypto_getreq(int num);
extern int crypto_usercrypto; /* userland may do crypto requests */
extern int crypto_userasymcrypto; /* userland may do asym crypto reqs */
extern int crypto_devallowsoft; /* only use hardware crypto */
/*
* Crypto-related utility routines used mainly by drivers.
*
* XXX these don't really belong here; but for now they're
* kept apart from the rest of the system.
*/
struct mbuf;
struct mbuf *m_getptr(struct mbuf *, int, int *);
struct uio;
extern void cuio_copydata(struct uio* uio, int off, int len, caddr_t cp);
extern void cuio_copyback(struct uio* uio, int off, int len, caddr_t cp);
#ifdef __FreeBSD__
extern struct iovec *cuio_getptr(struct uio *uio, int loc, int *off);
#else
extern int cuio_getptr(struct uio *, int loc, int *off);
#endif
extern int m_apply(struct mbuf *m, int off, int len,
int (*f)(caddr_t, caddr_t, unsigned int), caddr_t fstate);
extern struct mbuf * m_getptr(struct mbuf *m, int loc, int *off);
#endif /* _KERNEL */
#endif /* _CRYPTO_CRYPTO_H_ */

1158
sys/opencrypto/cryptosoft.c Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,66 @@
/* $NetBSD: cryptosoft.h,v 1.1 2003/07/25 21:12:45 jonathan Exp $ */
/* $OpenBSD: cryptosoft.h,v 1.10 2002/04/22 23:10:09 deraadt Exp $ */
/*
* The author of this code is Angelos D. Keromytis (angelos@cis.upenn.edu)
*
* This code was written by Angelos D. Keromytis in Athens, Greece, in
* February 2000. Network Security Technologies Inc. (NSTI) kindly
* supported the development of this code.
*
* Copyright (c) 2000 Angelos D. Keromytis
*
* Permission to use, copy, and modify this software with or without fee
* is hereby granted, provided that this entire notice is included in
* all source code copies of any software which is or includes a copy or
* modification of this software.
*
* THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR
* IMPLIED WARRANTY. IN PARTICULAR, NONE OF THE AUTHORS MAKES ANY
* REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE
* MERCHANTABILITY OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR
* PURPOSE.
*/
#ifndef _CRYPTO_CRYPTOSOFT_H_
#define _CRYPTO_CRYPTOSOFT_H_
/* Software session entry */
struct swcr_data {
int sw_alg; /* Algorithm */
union {
struct {
u_int8_t *SW_ictx;
u_int8_t *SW_octx;
u_int32_t SW_klen;
struct auth_hash *SW_axf;
} SWCR_AUTH;
struct {
u_int8_t *SW_kschedule;
struct enc_xform *SW_exf;
} SWCR_ENC;
struct {
u_int32_t SW_size;
struct comp_algo *SW_cxf;
} SWCR_COMP;
} SWCR_UN;
#define sw_ictx SWCR_UN.SWCR_AUTH.SW_ictx
#define sw_octx SWCR_UN.SWCR_AUTH.SW_octx
#define sw_klen SWCR_UN.SWCR_AUTH.SW_klen
#define sw_axf SWCR_UN.SWCR_AUTH.SW_axf
#define sw_kschedule SWCR_UN.SWCR_ENC.SW_kschedule
#define sw_exf SWCR_UN.SWCR_ENC.SW_exf
#define sw_size SWCR_UN.SWCR_COMP.SW_size
#define sw_cxf SWCR_UN.SWCR_COMP.SW_cxf
struct swcr_data *sw_next;
};
#ifdef _KERNEL
extern u_int8_t hmac_ipad_buffer[64];
extern u_int8_t hmac_opad_buffer[64];
void swcr_init(void);
#endif /* _KERNEL */
#endif /* _CRYPTO_CRYPTO_H_ */

193
sys/opencrypto/deflate.c Normal file
View File

@ -0,0 +1,193 @@
/* $NetBSD: deflate.c,v 1.1 2003/07/25 21:12:45 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/deflate.c,v 1.1.2.1 2002/11/21 23:34:23 sam Exp $ */
/* $OpenBSD: deflate.c,v 1.3 2001/08/20 02:45:22 hugh Exp $ */
/*
* Copyright (c) 2001 Jean-Jacques Bernard-Gundol (jj@wabbitt.org)
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
/*
* This file contains a wrapper around the deflate algo compression
* functions using the zlib library (see net/zlib.{c,h})
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: deflate.c,v 1.1 2003/07/25 21:12:45 jonathan Exp $");
#include <sys/types.h>
#include <sys/malloc.h>
#include <sys/param.h>
#include <sys/systm.h>
#include <net/zlib.h>
#include <opencrypto/cryptodev.h>
#include <opencrypto/deflate.h>
int window_inflate = -1 * MAX_WBITS;
int window_deflate = -12;
/*
* This function takes a block of data and (de)compress it using the deflate
* algorithm
*/
u_int32_t
deflate_global(data, size, decomp, out)
u_int8_t *data;
u_int32_t size;
int decomp;
u_int8_t **out;
{
/* decomp indicates whether we compress (0) or decompress (1) */
z_stream zbuf;
u_int8_t *output;
u_int32_t count, result;
int error, i = 0, j;
struct deflate_buf buf[ZBUF];
bzero(&zbuf, sizeof(z_stream));
for (j = 0; j < ZBUF; j++)
buf[j].flag = 0;
zbuf.next_in = data; /* data that is going to be processed */
zbuf.zalloc = z_alloc;
zbuf.zfree = z_free;
zbuf.opaque = Z_NULL;
zbuf.avail_in = size; /* Total length of data to be processed */
if (!decomp) {
MALLOC(buf[i].out, u_int8_t *, (u_long) size, M_CRYPTO_DATA,
M_NOWAIT);
if (buf[i].out == NULL)
goto bad;
buf[i].size = size;
buf[i].flag = 1;
i++;
} else {
/*
* Choose a buffer with 4x the size of the input buffer
* for the size of the output buffer in the case of
* decompression. If it's not sufficient, it will need to be
* updated while the decompression is going on
*/
MALLOC(buf[i].out, u_int8_t *, (u_long) (size * 4),
M_CRYPTO_DATA, M_NOWAIT);
if (buf[i].out == NULL)
goto bad;
buf[i].size = size * 4;
buf[i].flag = 1;
i++;
}
zbuf.next_out = buf[0].out;
zbuf.avail_out = buf[0].size;
error = decomp ? inflateInit2(&zbuf, window_inflate) :
deflateInit2(&zbuf, Z_DEFAULT_COMPRESSION, Z_METHOD,
window_deflate, Z_MEMLEVEL, Z_DEFAULT_STRATEGY);
if (error != Z_OK)
goto bad;
for (;;) {
error = decomp ? inflate(&zbuf, Z_PARTIAL_FLUSH) :
deflate(&zbuf, Z_PARTIAL_FLUSH);
if (error != Z_OK && error != Z_STREAM_END)
goto bad;
else if (zbuf.avail_in == 0 && zbuf.avail_out != 0)
goto end;
else if (zbuf.avail_out == 0 && i < (ZBUF - 1)) {
/* we need more output space, allocate size */
MALLOC(buf[i].out, u_int8_t *, (u_long) size,
M_CRYPTO_DATA, M_NOWAIT);
if (buf[i].out == NULL)
goto bad;
zbuf.next_out = buf[i].out;
buf[i].size = size;
buf[i].flag = 1;
zbuf.avail_out = buf[i].size;
i++;
} else
goto bad;
}
end:
result = count = zbuf.total_out;
MALLOC(*out, u_int8_t *, (u_long) result, M_CRYPTO_DATA, M_NOWAIT);
if (*out == NULL)
goto bad;
if (decomp)
inflateEnd(&zbuf);
else
deflateEnd(&zbuf);
output = *out;
for (j = 0; buf[j].flag != 0; j++) {
if (count > buf[j].size) {
bcopy(buf[j].out, *out, buf[j].size);
*out += buf[j].size;
FREE(buf[j].out, M_CRYPTO_DATA);
count -= buf[j].size;
} else {
/* it should be the last buffer */
bcopy(buf[j].out, *out, count);
*out += count;
FREE(buf[j].out, M_CRYPTO_DATA);
count = 0;
}
}
*out = output;
return result;
bad:
*out = NULL;
for (j = 0; buf[j].flag != 0; j++)
FREE(buf[j].out, M_CRYPTO_DATA);
if (decomp)
inflateEnd(&zbuf);
else
deflateEnd(&zbuf);
return 0;
}
void *
z_alloc(nil, type, size)
void *nil;
u_int type, size;
{
void *ptr;
ptr = malloc(type *size, M_CRYPTO_DATA, M_NOWAIT);
return ptr;
}
void
z_free(nil, ptr)
void *nil, *ptr;
{
free(ptr, M_CRYPTO_DATA);
}

57
sys/opencrypto/deflate.h Normal file
View File

@ -0,0 +1,57 @@
/* $NetBSD: deflate.h,v 1.1 2003/07/25 21:12:46 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/deflate.h,v 1.1.2.1 2002/11/21 23:34:23 sam Exp $ */
/* $OpenBSD: deflate.h,v 1.3 2002/03/14 01:26:51 millert Exp $ */
/*
* Copyright (c) 2001 Jean-Jacques Bernard-Gundol (jj@wabbitt.org)
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
/*
* Definition for the wrapper around the deflate compression
* algorithm used in /sys/crypto
*/
#ifndef _CRYPTO_DEFLATE_H_
#define _CRYPTO_DEFLATE_H_
#include <net/zlib.h>
#define Z_METHOD 8
#define Z_MEMLEVEL 8
#define MINCOMP 2 /* won't be used, but must be defined */
#define ZBUF 10
u_int32_t deflate_global(u_int8_t *, u_int32_t, int, u_int8_t **);
void *z_alloc(void *, u_int, u_int);
void z_free(void *, void *);
struct deflate_buf {
u_int8_t *out;
u_int32_t size;
int flag;
};
#endif /* _CRYPTO_DEFLATE_H_ */

254
sys/opencrypto/des.h Normal file
View File

@ -0,0 +1,254 @@
/* $NetBSD: des.h,v 1.1 2003/07/25 21:12:46 jonathan Exp $ */
/* $OpenBSD: des.h,v 1.1 2000/02/28 23:13:04 deraadt Exp $ */
/* lib/des/des.h */
/* Copyright (C) 1995 Eric Young (eay@mincom.oz.au)
* All rights reserved.
*
* This file is part of an SSL implementation written
* by Eric Young (eay@mincom.oz.au).
* The implementation was written so as to conform with Netscapes SSL
* specification. This library and applications are
* FREE FOR COMMERCIAL AND NON-COMMERCIAL USE
* as long as the following conditions are aheared to.
*
* Copyright remains Eric Young's, and as such any Copyright notices in
* the code are not to be removed. If this code is used in a product,
* Eric Young should be given attribution as the author of the parts used.
* This can be in the form of a textual message at program startup or
* in documentation (online or textual) provided with the package.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by Eric Young (eay@mincom.oz.au)
*
* THIS SOFTWARE IS PROVIDED BY ERIC YOUNG ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*
* The licence and distribution terms for any publically available version or
* derivative of this code cannot be changed. i.e. this code cannot simply be
* copied and put under another distribution licence
* [including the GNU Public Licence.]
*/
#ifndef HEADER_DES_H
#define HEADER_DES_H
#ifndef _KERNEL
#include <stdio.h>
#endif
typedef unsigned char des_cblock[8];
typedef struct des_ks_struct
{
union {
des_cblock _;
/* make sure things are correct size on machines with
* 8 byte longs */
unsigned long pad[2];
} ks;
#undef _
#define _ ks._
} des_key_schedule[16];
#define DES_KEY_SZ (sizeof(des_cblock))
#define DES_SCHEDULE_SZ (sizeof(des_key_schedule))
#define DES_ENCRYPT 1
#define DES_DECRYPT 0
#define DES_CBC_MODE 0
#define DES_PCBC_MODE 1
#define des_ecb2_encrypt(i,o,k1,k2,e) \
des_ecb3_encrypt((i),(o),(k1),(k2),(k1),(e))
#define des_ede2_cbc_encrypt(i,o,l,k1,k2,iv,e) \
des_ede3_cbc_encrypt((i),(o),(l),(k1),(k2),(k1),(iv),(e))
#define des_ede2_cfb64_encrypt(i,o,l,k1,k2,iv,n,e) \
des_ede3_cfb64_encrypt((i),(o),(l),(k1),(k2),(k1),(iv),(n),(e))
#define des_ede2_ofb64_encrypt(i,o,l,k1,k2,iv,n) \
des_ede3_ofb64_encrypt((i),(o),(l),(k1),(k2),(k1),(iv),(n))
#define C_Block des_cblock
#define Key_schedule des_key_schedule
#define ENCRYPT DES_ENCRYPT
#define DECRYPT DES_DECRYPT
#define KEY_SZ DES_KEY_SZ
#define string_to_key des_string_to_key
#define read_pw_string des_read_pw_string
#define random_key des_random_key
#define pcbc_encrypt des_pcbc_encrypt
#define set_key des_set_key
#define key_sched des_key_sched
#define ecb_encrypt des_ecb_encrypt
#define cbc_encrypt des_cbc_encrypt
#define ncbc_encrypt des_ncbc_encrypt
#define cbc_cksum des_cbc_cksum
#define quad_cksum des_quad_cksum
/* For compatibility with the MIT lib - eay 20/05/92 */
typedef struct des_key_schedule bit_64;
#define des_fixup_key_parity des_set_odd_parity
#define des_check_key_parity check_parity
extern int des_check_key; /* defaults to false */
extern int des_rw_mode; /* defaults to DES_PCBC_MODE */
/* The next line is used to disable full ANSI prototypes, if your
* compiler has problems with the prototypes, make sure this line always
* evaluates to true :-) */
#if defined(MSDOS) || defined(__STDC__)
#undef PROTO
#define PROTO
#endif
#ifdef PROTO
void des_ecb3_encrypt(des_cblock *input,des_cblock *output,
des_key_schedule ks1,des_key_schedule ks2,
des_key_schedule ks3, int enc);
unsigned long des_cbc_cksum(des_cblock *input,des_cblock *output,
long length,des_key_schedule schedule,des_cblock *ivec);
void des_cbc_encrypt(des_cblock *input,des_cblock *output,long length,
des_key_schedule schedule,des_cblock *ivec,int enc);
void des_ncbc_encrypt(des_cblock *input,des_cblock *output,long length,
des_key_schedule schedule,des_cblock *ivec,int enc);
void des_3cbc_encrypt(des_cblock *input,des_cblock *output,long length,
des_key_schedule sk1,des_key_schedule sk2,
des_cblock *ivec1,des_cblock *ivec2,int enc);
void des_cfb_encrypt(unsigned char *in,unsigned char *out,int numbits,
long length,des_key_schedule schedule,des_cblock *ivec,int enc);
void des_ecb_encrypt(des_cblock *input,des_cblock *output,
des_key_schedule ks,int enc);
void des_encrypt(unsigned long *data,des_key_schedule ks, int enc);
void des_encrypt2(unsigned long *data,des_key_schedule ks, int enc);
void des_ede3_cbc_encrypt(des_cblock *input, des_cblock *output,
long length, des_key_schedule ks1, des_key_schedule ks2,
des_key_schedule ks3, des_cblock *ivec, int enc);
void des_ede3_cfb64_encrypt(unsigned char *in, unsigned char *out,
long length, des_key_schedule ks1, des_key_schedule ks2,
des_key_schedule ks3, des_cblock *ivec, int *num, int encrypt);
void des_ede3_ofb64_encrypt(unsigned char *in, unsigned char *out,
long length, des_key_schedule ks1, des_key_schedule ks2,
des_key_schedule ks3, des_cblock *ivec, int *num);
int des_enc_read(int fd,char *buf,int len,des_key_schedule sched,
des_cblock *iv);
int des_enc_write(int fd,char *buf,int len,des_key_schedule sched,
des_cblock *iv);
#ifdef PERL5
char *des_crypt(const char *buf,const char *salt);
#else
/* some stupid compilers complain because I have declared char instead
* of const char */
#ifdef HEADER_DES_LOCL_H
char *crypt(const char *buf,const char *salt);
#else
char *crypt();
#endif
#endif
void des_ofb_encrypt(unsigned char *in,unsigned char *out,
int numbits,long length,des_key_schedule schedule,des_cblock *ivec);
void des_pcbc_encrypt(des_cblock *input,des_cblock *output,long length,
des_key_schedule schedule,des_cblock *ivec,int enc);
unsigned long des_quad_cksum(des_cblock *input,des_cblock *output,
long length,int out_count,des_cblock *seed);
void des_random_seed(des_cblock key);
void des_random_key(des_cblock ret);
int des_read_password(des_cblock *key,char *prompt,int verify);
int des_read_2passwords(des_cblock *key1,des_cblock *key2,
char *prompt,int verify);
int des_read_pw_string(char *buf,int length,char *prompt,int verify);
void des_set_odd_parity(des_cblock *key);
int des_is_weak_key(des_cblock *key);
int des_set_key(des_cblock *key,des_key_schedule schedule);
int des_key_sched(des_cblock *key,des_key_schedule schedule);
void des_string_to_key(char *str,des_cblock *key);
void des_string_to_2keys(char *str,des_cblock *key1,des_cblock *key2);
void des_cfb64_encrypt(unsigned char *in, unsigned char *out, long length,
des_key_schedule schedule, des_cblock *ivec, int *num, int enc);
void des_ofb64_encrypt(unsigned char *in, unsigned char *out, long length,
des_key_schedule schedule, des_cblock *ivec, int *num);
/*
* Extra functions from Mark Murray <mark@grondar.za>
* The following functions are not in the normal unix build or the
* SSLeay build. When using the SSLeay build, use RAND_seed()
* and RAND_bytes() instead.
*/
int des_new_random_key(des_cblock *key);
void des_init_random_number_generator(des_cblock *key);
void des_set_random_generator_seed(des_cblock *key);
void des_set_sequence_number(des_cblock new_sequence_number);
void des_generate_random_block(des_cblock *block);
#else
void des_ecb3_encrypt();
unsigned long des_cbc_cksum();
void des_cbc_encrypt();
void des_ncbc_encrypt();
void des_3cbc_encrypt();
void des_cfb_encrypt();
void des_ede3_cfb64_encrypt();
void des_ede3_ofb64_encrypt();
void des_ecb_encrypt();
void des_encrypt();
void des_encrypt2();
void des_ede3_cbc_encrypt();
int des_enc_read();
int des_enc_write();
#ifdef PERL5
char *des_crypt();
#else
char *crypt();
#endif
void des_ofb_encrypt();
void des_pcbc_encrypt();
unsigned long des_quad_cksum();
void des_random_seed();
void des_random_key();
int des_read_password();
int des_read_2passwords();
int des_read_pw_string();
void des_set_odd_parity();
int des_is_weak_key();
int des_set_key();
int des_key_sched();
void des_string_to_key();
void des_string_to_2keys();
void des_cfb64_encrypt();
void des_ofb64_encrypt();
/*
* Extra functions from Mark Murray <mark@grondar.za>
* The following functions are not in the normal unix build or the
* SSLeay build. When using the SSLeay build, use RAND_seed()
* and RAND_bytes() instead.
*/
int des_new_random_key();
void des_init_random_number_generator();
void des_set_random_generator_seed();
void des_set_sequence_number();
void des_generate_random_block();
#endif
#endif

255
sys/opencrypto/des_locl.h Normal file
View File

@ -0,0 +1,255 @@
/* $NetBSD: des_locl.h,v 1.1 2003/07/25 21:12:46 jonathan Exp $ */
/* $OpenBSD: des_locl.h,v 1.1 2000/02/28 23:13:04 deraadt Exp $ */
/* lib/des/des_locl.h */
/* Copyright (C) 1995 Eric Young (eay@mincom.oz.au)
* All rights reserved.
*
* This file is part of an SSL implementation written
* by Eric Young (eay@mincom.oz.au).
* The implementation was written so as to conform with Netscapes SSL
* specification. This library and applications are
* FREE FOR COMMERCIAL AND NON-COMMERCIAL USE
* as long as the following conditions are aheared to.
*
* Copyright remains Eric Young's, and as such any Copyright notices in
* the code are not to be removed. If this code is used in a product,
* Eric Young should be given attribution as the author of the parts used.
* This can be in the form of a textual message at program startup or
* in documentation (online or textual) provided with the package.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by Eric Young (eay@mincom.oz.au)
*
* THIS SOFTWARE IS PROVIDED BY ERIC YOUNG ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*
* The licence and distribution terms for any publically available version or
* derivative of this code cannot be changed. i.e. this code cannot simply be
* copied and put under another distribution licence
* [including the GNU Public Licence.]
*/
#ifndef HEADER_DES_LOCL_H
#define HEADER_DES_LOCL_H
#include <sys/cdefs.h>
#include <sys/types.h>
#include <sys/systm.h>
#include "des.h"
/* the following is tweaked from a config script, that is why it is a
* protected undef/define */
#ifndef DES_USE_PTR
#undef DES_USE_PTR
#endif
#ifndef RAND
#define RAND
#endif
#if defined(NOCONST)
#define const
#endif
#ifdef __STDC__
#undef PROTO
#define PROTO
#endif
#ifdef RAND
#define srandom(s) srand(s)
#define random rand
#endif
#define ITERATIONS 16
#define HALF_ITERATIONS 8
/* used in des_read and des_write */
#define MAXWRITE (1024*16)
#define BSIZE (MAXWRITE+4)
#define c2l(c,l) (l =((unsigned long)(*((c)++))) , \
l|=((unsigned long)(*((c)++)))<< 8L, \
l|=((unsigned long)(*((c)++)))<<16L, \
l|=((unsigned long)(*((c)++)))<<24L)
/* NOTE - c is not incremented as per c2l */
#define c2ln(c,l1,l2,n) { \
c+=n; \
l1=l2=0; \
switch (n) { \
case 8: l2 =((unsigned long)(*(--(c))))<<24L; \
case 7: l2|=((unsigned long)(*(--(c))))<<16L; \
case 6: l2|=((unsigned long)(*(--(c))))<< 8L; \
case 5: l2|=((unsigned long)(*(--(c)))); \
case 4: l1 =((unsigned long)(*(--(c))))<<24L; \
case 3: l1|=((unsigned long)(*(--(c))))<<16L; \
case 2: l1|=((unsigned long)(*(--(c))))<< 8L; \
case 1: l1|=((unsigned long)(*(--(c)))); \
} \
}
#define l2c(l,c) (*((c)++)=(unsigned char)(((l) )&0xff), \
*((c)++)=(unsigned char)(((l)>> 8L)&0xff), \
*((c)++)=(unsigned char)(((l)>>16L)&0xff), \
*((c)++)=(unsigned char)(((l)>>24L)&0xff))
/* replacements for htonl and ntohl since I have no idea what to do
* when faced with machines with 8 byte longs. */
#define HDRSIZE 4
#define n2l(c,l) (l =((unsigned long)(*((c)++)))<<24L, \
l|=((unsigned long)(*((c)++)))<<16L, \
l|=((unsigned long)(*((c)++)))<< 8L, \
l|=((unsigned long)(*((c)++))))
#define l2n(l,c) (*((c)++)=(unsigned char)(((l)>>24L)&0xff), \
*((c)++)=(unsigned char)(((l)>>16L)&0xff), \
*((c)++)=(unsigned char)(((l)>> 8L)&0xff), \
*((c)++)=(unsigned char)(((l) )&0xff))
/* NOTE - c is not incremented as per l2c */
#define l2cn(l1,l2,c,n) { \
c+=n; \
switch (n) { \
case 8: *(--(c))=(unsigned char)(((l2)>>24L)&0xff); \
case 7: *(--(c))=(unsigned char)(((l2)>>16L)&0xff); \
case 6: *(--(c))=(unsigned char)(((l2)>> 8L)&0xff); \
case 5: *(--(c))=(unsigned char)(((l2) )&0xff); \
case 4: *(--(c))=(unsigned char)(((l1)>>24L)&0xff); \
case 3: *(--(c))=(unsigned char)(((l1)>>16L)&0xff); \
case 2: *(--(c))=(unsigned char)(((l1)>> 8L)&0xff); \
case 1: *(--(c))=(unsigned char)(((l1) )&0xff); \
} \
}
/* The changes to this macro may help or hinder, depending on the
* compiler and the achitecture. gcc2 always seems to do well :-).
* Inspired by Dana How <how@isl.stanford.edu>
* DO NOT use the alternative version on machines with 8 byte longs. */
#ifdef DES_USR_PTR
#define D_ENCRYPT(L,R,S) { \
u=((R^s[S ])<<2); \
t= R^s[S+1]; \
t=((t>>2)+(t<<30)); \
L^= \
*(unsigned long *)(des_SP+0x0100+((t )&0xfc))+ \
*(unsigned long *)(des_SP+0x0300+((t>> 8)&0xfc))+ \
*(unsigned long *)(des_SP+0x0500+((t>>16)&0xfc))+ \
*(unsigned long *)(des_SP+0x0700+((t>>24)&0xfc))+ \
*(unsigned long *)(des_SP+ ((u )&0xfc))+ \
*(unsigned long *)(des_SP+0x0200+((u>> 8)&0xfc))+ \
*(unsigned long *)(des_SP+0x0400+((u>>16)&0xfc))+ \
*(unsigned long *)(des_SP+0x0600+((u>>24)&0xfc)); }
#else /* original version */
#ifdef MSDOS
#define D_ENCRYPT(L,R,S) \
U.l=R^s[S+1]; \
T.s[0]=((U.s[0]>>4)|(U.s[1]<<12))&0x3f3f; \
T.s[1]=((U.s[1]>>4)|(U.s[0]<<12))&0x3f3f; \
U.l=(R^s[S ])&0x3f3f3f3fL; \
L^= des_SPtrans[1][(T.c[0])]| \
des_SPtrans[3][(T.c[1])]| \
des_SPtrans[5][(T.c[2])]| \
des_SPtrans[7][(T.c[3])]| \
des_SPtrans[0][(U.c[0])]| \
des_SPtrans[2][(U.c[1])]| \
des_SPtrans[4][(U.c[2])]| \
des_SPtrans[6][(U.c[3])];
#else
#define D_ENCRYPT(Q,R,S) {\
u=(R^s[S ]); \
t=R^s[S+1]; \
t=((t>>4L)+(t<<28L)); \
Q^= des_SPtrans[1][(t )&0x3f]| \
des_SPtrans[3][(t>> 8L)&0x3f]| \
des_SPtrans[5][(t>>16L)&0x3f]| \
des_SPtrans[7][(t>>24L)&0x3f]| \
des_SPtrans[0][(u )&0x3f]| \
des_SPtrans[2][(u>> 8L)&0x3f]| \
des_SPtrans[4][(u>>16L)&0x3f]| \
des_SPtrans[6][(u>>24L)&0x3f]; }
#endif
#endif
/* IP and FP
* The problem is more of a geometric problem that random bit fiddling.
0 1 2 3 4 5 6 7 62 54 46 38 30 22 14 6
8 9 10 11 12 13 14 15 60 52 44 36 28 20 12 4
16 17 18 19 20 21 22 23 58 50 42 34 26 18 10 2
24 25 26 27 28 29 30 31 to 56 48 40 32 24 16 8 0
32 33 34 35 36 37 38 39 63 55 47 39 31 23 15 7
40 41 42 43 44 45 46 47 61 53 45 37 29 21 13 5
48 49 50 51 52 53 54 55 59 51 43 35 27 19 11 3
56 57 58 59 60 61 62 63 57 49 41 33 25 17 9 1
The output has been subject to swaps of the form
0 1 -> 3 1 but the odd and even bits have been put into
2 3 2 0
different words. The main trick is to remember that
t=((l>>size)^r)&(mask);
r^=t;
l^=(t<<size);
can be used to swap and move bits between words.
So l = 0 1 2 3 r = 16 17 18 19
4 5 6 7 20 21 22 23
8 9 10 11 24 25 26 27
12 13 14 15 28 29 30 31
becomes (for size == 2 and mask == 0x3333)
t = 2^16 3^17 -- -- l = 0 1 16 17 r = 2 3 18 19
6^20 7^21 -- -- 4 5 20 21 6 7 22 23
10^24 11^25 -- -- 8 9 24 25 10 11 24 25
14^28 15^29 -- -- 12 13 28 29 14 15 28 29
Thanks for hints from Richard Outerbridge - he told me IP&FP
could be done in 15 xor, 10 shifts and 5 ands.
When I finally started to think of the problem in 2D
I first got ~42 operations without xors. When I remembered
how to use xors :-) I got it to its final state.
*/
#define PERM_OP(a,b,t,n,m) ((t)=((((a)>>(n))^(b))&(m)),\
(b)^=(t),\
(a)^=((t)<<(n)))
#define IP(l,r) \
{ \
register unsigned long tt; \
PERM_OP(r,l,tt, 4,0x0f0f0f0fL); \
PERM_OP(l,r,tt,16,0x0000ffffL); \
PERM_OP(r,l,tt, 2,0x33333333L); \
PERM_OP(l,r,tt, 8,0x00ff00ffL); \
PERM_OP(r,l,tt, 1,0x55555555L); \
}
#define FP(l,r) \
{ \
register unsigned long tt; \
PERM_OP(l,r,tt, 1,0x55555555L); \
PERM_OP(r,l,tt, 8,0x00ff00ffL); \
PERM_OP(l,r,tt, 2,0x33333333L); \
PERM_OP(r,l,tt,16,0x0000ffffL); \
PERM_OP(l,r,tt, 4,0x0f0f0f0fL); \
}
#endif

View File

@ -0,0 +1,26 @@
# $NetBSD: files.opencrypto,v 1.1 2003/07/25 21:12:47 jonathan Exp $
#
#
defpseudo opencrypto
file opencrypto/criov.c opencrypto
file opencrypto/cryptodev.c opencrypto
file opencrypto/cryptosoft.c opencrypto
file opencrypto/xform.c opencrypto
file opencrypto/crypto.c opencrypto
file opencrypto/crypto_mbuf.c opencrypto
# crypto algorithms
file opencrypto/blf.c opencrypto
file crypto/sha2/sha2.c opencrypto
file opencrypto/skipjack.c opencrypto
file opencrypto/rmd160.c opencrypto
file opencrypto/cast.c opencrypto
file opencrypto/rijndael.c opencrypto
file opencrypto/deflate.c opencrypto
# old pre-OpenCryptoFramework/fast-ipsec crypto hooks.
#file crypto/des/des_ecb.c opencrypto
#file crypto/des/des_setkey.c opencrypto

1247
sys/opencrypto/rijndael.c Normal file

File diff suppressed because it is too large Load Diff

52
sys/opencrypto/rijndael.h Normal file
View File

@ -0,0 +1,52 @@
/* $NetBSD: rijndael.h,v 1.1 2003/07/25 21:12:47 jonathan Exp $ */
/* $OpenBSD: rijndael.h,v 1.7 2001/12/19 17:42:24 markus Exp $ */
/**
* rijndael-alg-fst.h
*
* @version 3.0 (December 2000)
*
* Optimised ANSI C code for the Rijndael cipher (now AES)
*
* @author Vincent Rijmen <vincent.rijmen@esat.kuleuven.ac.be>
* @author Antoon Bosselaers <antoon.bosselaers@esat.kuleuven.ac.be>
* @author Paulo Barreto <paulo.barreto@terra.com.br>
*
* This code is hereby placed in the public domain.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHORS ''AS IS'' AND ANY EXPRESS
* OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
* WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE
* LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
* CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
* SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR
* BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY,
* WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE
* OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE,
* EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef __RIJNDAEL_H
#define __RIJNDAEL_H
#define MAXKC (256/32)
#define MAXKB (256/8)
#define MAXNR 14
typedef unsigned char u8;
typedef unsigned short u16;
typedef unsigned int u32;
/* The structure for key information */
typedef struct {
int decrypt;
int Nr; /* key-length-dependent number of rounds */
u32 ek[4*(MAXNR + 1)]; /* encrypt key schedule */
u32 dk[4*(MAXNR + 1)]; /* decrypt key schedule */
} rijndael_ctx;
void rijndael_set_key(rijndael_ctx *, u_char *, int, int);
void rijndael_decrypt(rijndael_ctx *, u_char *, u_char *);
void rijndael_encrypt(rijndael_ctx *, u_char *, u_char *);
#endif /* __RIJNDAEL_H */

368
sys/opencrypto/rmd160.c Normal file
View File

@ -0,0 +1,368 @@
/* $NetBSD: rmd160.c,v 1.1 2003/07/25 21:12:47 jonathan Exp $ */
/* $OpenBSD: rmd160.c,v 1.3 2001/09/26 21:40:13 markus Exp $ */
/*
* Copyright (c) 2001 Markus Friedl. All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
/*
* Preneel, Bosselaers, Dobbertin, "The Cryptographic Hash Function RIPEMD-160",
* RSA Laboratories, CryptoBytes, Volume 3, Number 2, Autumn 1997,
* ftp://ftp.rsasecurity.com/pub/cryptobytes/crypto3n2.pdf
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: rmd160.c,v 1.1 2003/07/25 21:12:47 jonathan Exp $");
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/endian.h>
#include <opencrypto/rmd160.h>
#define PUT_64BIT_LE(cp, value) do { \
(cp)[7] = (value) >> 56; \
(cp)[6] = (value) >> 48; \
(cp)[5] = (value) >> 40; \
(cp)[4] = (value) >> 32; \
(cp)[3] = (value) >> 24; \
(cp)[2] = (value) >> 16; \
(cp)[1] = (value) >> 8; \
(cp)[0] = (value); } while (0)
#define PUT_32BIT_LE(cp, value) do { \
(cp)[3] = (value) >> 24; \
(cp)[2] = (value) >> 16; \
(cp)[1] = (value) >> 8; \
(cp)[0] = (value); } while (0)
#define H0 0x67452301U
#define H1 0xEFCDAB89U
#define H2 0x98BADCFEU
#define H3 0x10325476U
#define H4 0xC3D2E1F0U
#define K0 0x00000000U
#define K1 0x5A827999U
#define K2 0x6ED9EBA1U
#define K3 0x8F1BBCDCU
#define K4 0xA953FD4EU
#define KK0 0x50A28BE6U
#define KK1 0x5C4DD124U
#define KK2 0x6D703EF3U
#define KK3 0x7A6D76E9U
#define KK4 0x00000000U
/* rotate x left n bits. */
#define ROL(n, x) (((x) << (n)) | ((x) >> (32-(n))))
#define F0(x, y, z) ((x) ^ (y) ^ (z))
#define F1(x, y, z) (((x) & (y)) | ((~x) & (z)))
#define F2(x, y, z) (((x) | (~y)) ^ (z))
#define F3(x, y, z) (((x) & (z)) | ((y) & (~z)))
#define F4(x, y, z) ((x) ^ ((y) | (~z)))
#define R(a, b, c, d, e, Fj, Kj, sj, rj) \
do { \
a = ROL(sj, a + Fj(b,c,d) + X(rj) + Kj) + e; \
c = ROL(10, c); \
} while(0)
#define X(i) x[i]
static u_char PADDING[64] = {
0x80, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0
};
void
RMD160Init(RMD160_CTX *ctx)
{
ctx->count = 0;
ctx->state[0] = H0;
ctx->state[1] = H1;
ctx->state[2] = H2;
ctx->state[3] = H3;
ctx->state[4] = H4;
}
void
RMD160Update(RMD160_CTX *ctx, const u_char *input, u_int32_t len)
{
u_int32_t have, off, need;
have = (ctx->count/8) % 64;
need = 64 - have;
ctx->count += 8 * len;
off = 0;
if (len >= need) {
if (have) {
memcpy(ctx->buffer + have, input, need);
RMD160Transform(ctx->state, ctx->buffer);
off = need;
have = 0;
}
/* now the buffer is empty */
while (off + 64 <= len) {
RMD160Transform(ctx->state, input+off);
off += 64;
}
}
if (off < len)
memcpy(ctx->buffer + have, input+off, len-off);
}
void
RMD160Final(u_char digest[20], RMD160_CTX *ctx)
{
int i;
u_char size[8];
u_int32_t padlen;
PUT_64BIT_LE(size, ctx->count);
/*
* pad to 64 byte blocks, at least one byte from PADDING plus 8 bytes
* for the size
*/
padlen = 64 - ((ctx->count/8) % 64);
if (padlen < 1 + 8)
padlen += 64;
RMD160Update(ctx, PADDING, padlen - 8); /* padlen - 8 <= 64 */
RMD160Update(ctx, size, 8);
if (digest != NULL)
for (i = 0; i < 5; i++)
PUT_32BIT_LE(digest + i*4, ctx->state[i]);
memset(ctx, 0, sizeof (*ctx));
}
void
RMD160Transform(u_int32_t state[5], const u_char block[64])
{
u_int32_t a, b, c, d, e, aa, bb, cc, dd, ee, t, x[16];
#if BYTE_ORDER == LITTLE_ENDIAN
memcpy(x, block, 64);
#else
int i;
for (i = 0; i < 16; i++)
x[i] = swap32(*(u_int32_t*)(block+i*4));
#endif
a = state[0];
b = state[1];
c = state[2];
d = state[3];
e = state[4];
/* Round 1 */
R(a, b, c, d, e, F0, K0, 11, 0);
R(e, a, b, c, d, F0, K0, 14, 1);
R(d, e, a, b, c, F0, K0, 15, 2);
R(c, d, e, a, b, F0, K0, 12, 3);
R(b, c, d, e, a, F0, K0, 5, 4);
R(a, b, c, d, e, F0, K0, 8, 5);
R(e, a, b, c, d, F0, K0, 7, 6);
R(d, e, a, b, c, F0, K0, 9, 7);
R(c, d, e, a, b, F0, K0, 11, 8);
R(b, c, d, e, a, F0, K0, 13, 9);
R(a, b, c, d, e, F0, K0, 14, 10);
R(e, a, b, c, d, F0, K0, 15, 11);
R(d, e, a, b, c, F0, K0, 6, 12);
R(c, d, e, a, b, F0, K0, 7, 13);
R(b, c, d, e, a, F0, K0, 9, 14);
R(a, b, c, d, e, F0, K0, 8, 15); /* #15 */
/* Round 2 */
R(e, a, b, c, d, F1, K1, 7, 7);
R(d, e, a, b, c, F1, K1, 6, 4);
R(c, d, e, a, b, F1, K1, 8, 13);
R(b, c, d, e, a, F1, K1, 13, 1);
R(a, b, c, d, e, F1, K1, 11, 10);
R(e, a, b, c, d, F1, K1, 9, 6);
R(d, e, a, b, c, F1, K1, 7, 15);
R(c, d, e, a, b, F1, K1, 15, 3);
R(b, c, d, e, a, F1, K1, 7, 12);
R(a, b, c, d, e, F1, K1, 12, 0);
R(e, a, b, c, d, F1, K1, 15, 9);
R(d, e, a, b, c, F1, K1, 9, 5);
R(c, d, e, a, b, F1, K1, 11, 2);
R(b, c, d, e, a, F1, K1, 7, 14);
R(a, b, c, d, e, F1, K1, 13, 11);
R(e, a, b, c, d, F1, K1, 12, 8); /* #31 */
/* Round 3 */
R(d, e, a, b, c, F2, K2, 11, 3);
R(c, d, e, a, b, F2, K2, 13, 10);
R(b, c, d, e, a, F2, K2, 6, 14);
R(a, b, c, d, e, F2, K2, 7, 4);
R(e, a, b, c, d, F2, K2, 14, 9);
R(d, e, a, b, c, F2, K2, 9, 15);
R(c, d, e, a, b, F2, K2, 13, 8);
R(b, c, d, e, a, F2, K2, 15, 1);
R(a, b, c, d, e, F2, K2, 14, 2);
R(e, a, b, c, d, F2, K2, 8, 7);
R(d, e, a, b, c, F2, K2, 13, 0);
R(c, d, e, a, b, F2, K2, 6, 6);
R(b, c, d, e, a, F2, K2, 5, 13);
R(a, b, c, d, e, F2, K2, 12, 11);
R(e, a, b, c, d, F2, K2, 7, 5);
R(d, e, a, b, c, F2, K2, 5, 12); /* #47 */
/* Round 4 */
R(c, d, e, a, b, F3, K3, 11, 1);
R(b, c, d, e, a, F3, K3, 12, 9);
R(a, b, c, d, e, F3, K3, 14, 11);
R(e, a, b, c, d, F3, K3, 15, 10);
R(d, e, a, b, c, F3, K3, 14, 0);
R(c, d, e, a, b, F3, K3, 15, 8);
R(b, c, d, e, a, F3, K3, 9, 12);
R(a, b, c, d, e, F3, K3, 8, 4);
R(e, a, b, c, d, F3, K3, 9, 13);
R(d, e, a, b, c, F3, K3, 14, 3);
R(c, d, e, a, b, F3, K3, 5, 7);
R(b, c, d, e, a, F3, K3, 6, 15);
R(a, b, c, d, e, F3, K3, 8, 14);
R(e, a, b, c, d, F3, K3, 6, 5);
R(d, e, a, b, c, F3, K3, 5, 6);
R(c, d, e, a, b, F3, K3, 12, 2); /* #63 */
/* Round 5 */
R(b, c, d, e, a, F4, K4, 9, 4);
R(a, b, c, d, e, F4, K4, 15, 0);
R(e, a, b, c, d, F4, K4, 5, 5);
R(d, e, a, b, c, F4, K4, 11, 9);
R(c, d, e, a, b, F4, K4, 6, 7);
R(b, c, d, e, a, F4, K4, 8, 12);
R(a, b, c, d, e, F4, K4, 13, 2);
R(e, a, b, c, d, F4, K4, 12, 10);
R(d, e, a, b, c, F4, K4, 5, 14);
R(c, d, e, a, b, F4, K4, 12, 1);
R(b, c, d, e, a, F4, K4, 13, 3);
R(a, b, c, d, e, F4, K4, 14, 8);
R(e, a, b, c, d, F4, K4, 11, 11);
R(d, e, a, b, c, F4, K4, 8, 6);
R(c, d, e, a, b, F4, K4, 5, 15);
R(b, c, d, e, a, F4, K4, 6, 13); /* #79 */
aa = a ; bb = b; cc = c; dd = d; ee = e;
a = state[0];
b = state[1];
c = state[2];
d = state[3];
e = state[4];
/* Parallel round 1 */
R(a, b, c, d, e, F4, KK0, 8, 5);
R(e, a, b, c, d, F4, KK0, 9, 14);
R(d, e, a, b, c, F4, KK0, 9, 7);
R(c, d, e, a, b, F4, KK0, 11, 0);
R(b, c, d, e, a, F4, KK0, 13, 9);
R(a, b, c, d, e, F4, KK0, 15, 2);
R(e, a, b, c, d, F4, KK0, 15, 11);
R(d, e, a, b, c, F4, KK0, 5, 4);
R(c, d, e, a, b, F4, KK0, 7, 13);
R(b, c, d, e, a, F4, KK0, 7, 6);
R(a, b, c, d, e, F4, KK0, 8, 15);
R(e, a, b, c, d, F4, KK0, 11, 8);
R(d, e, a, b, c, F4, KK0, 14, 1);
R(c, d, e, a, b, F4, KK0, 14, 10);
R(b, c, d, e, a, F4, KK0, 12, 3);
R(a, b, c, d, e, F4, KK0, 6, 12); /* #15 */
/* Parallel round 2 */
R(e, a, b, c, d, F3, KK1, 9, 6);
R(d, e, a, b, c, F3, KK1, 13, 11);
R(c, d, e, a, b, F3, KK1, 15, 3);
R(b, c, d, e, a, F3, KK1, 7, 7);
R(a, b, c, d, e, F3, KK1, 12, 0);
R(e, a, b, c, d, F3, KK1, 8, 13);
R(d, e, a, b, c, F3, KK1, 9, 5);
R(c, d, e, a, b, F3, KK1, 11, 10);
R(b, c, d, e, a, F3, KK1, 7, 14);
R(a, b, c, d, e, F3, KK1, 7, 15);
R(e, a, b, c, d, F3, KK1, 12, 8);
R(d, e, a, b, c, F3, KK1, 7, 12);
R(c, d, e, a, b, F3, KK1, 6, 4);
R(b, c, d, e, a, F3, KK1, 15, 9);
R(a, b, c, d, e, F3, KK1, 13, 1);
R(e, a, b, c, d, F3, KK1, 11, 2); /* #31 */
/* Parallel round 3 */
R(d, e, a, b, c, F2, KK2, 9, 15);
R(c, d, e, a, b, F2, KK2, 7, 5);
R(b, c, d, e, a, F2, KK2, 15, 1);
R(a, b, c, d, e, F2, KK2, 11, 3);
R(e, a, b, c, d, F2, KK2, 8, 7);
R(d, e, a, b, c, F2, KK2, 6, 14);
R(c, d, e, a, b, F2, KK2, 6, 6);
R(b, c, d, e, a, F2, KK2, 14, 9);
R(a, b, c, d, e, F2, KK2, 12, 11);
R(e, a, b, c, d, F2, KK2, 13, 8);
R(d, e, a, b, c, F2, KK2, 5, 12);
R(c, d, e, a, b, F2, KK2, 14, 2);
R(b, c, d, e, a, F2, KK2, 13, 10);
R(a, b, c, d, e, F2, KK2, 13, 0);
R(e, a, b, c, d, F2, KK2, 7, 4);
R(d, e, a, b, c, F2, KK2, 5, 13); /* #47 */
/* Parallel round 4 */
R(c, d, e, a, b, F1, KK3, 15, 8);
R(b, c, d, e, a, F1, KK3, 5, 6);
R(a, b, c, d, e, F1, KK3, 8, 4);
R(e, a, b, c, d, F1, KK3, 11, 1);
R(d, e, a, b, c, F1, KK3, 14, 3);
R(c, d, e, a, b, F1, KK3, 14, 11);
R(b, c, d, e, a, F1, KK3, 6, 15);
R(a, b, c, d, e, F1, KK3, 14, 0);
R(e, a, b, c, d, F1, KK3, 6, 5);
R(d, e, a, b, c, F1, KK3, 9, 12);
R(c, d, e, a, b, F1, KK3, 12, 2);
R(b, c, d, e, a, F1, KK3, 9, 13);
R(a, b, c, d, e, F1, KK3, 12, 9);
R(e, a, b, c, d, F1, KK3, 5, 7);
R(d, e, a, b, c, F1, KK3, 15, 10);
R(c, d, e, a, b, F1, KK3, 8, 14); /* #63 */
/* Parallel round 5 */
R(b, c, d, e, a, F0, KK4, 8, 12);
R(a, b, c, d, e, F0, KK4, 5, 15);
R(e, a, b, c, d, F0, KK4, 12, 10);
R(d, e, a, b, c, F0, KK4, 9, 4);
R(c, d, e, a, b, F0, KK4, 12, 1);
R(b, c, d, e, a, F0, KK4, 5, 5);
R(a, b, c, d, e, F0, KK4, 14, 8);
R(e, a, b, c, d, F0, KK4, 6, 7);
R(d, e, a, b, c, F0, KK4, 8, 6);
R(c, d, e, a, b, F0, KK4, 13, 2);
R(b, c, d, e, a, F0, KK4, 6, 13);
R(a, b, c, d, e, F0, KK4, 5, 14);
R(e, a, b, c, d, F0, KK4, 15, 0);
R(d, e, a, b, c, F0, KK4, 13, 3);
R(c, d, e, a, b, F0, KK4, 11, 9);
R(b, c, d, e, a, F0, KK4, 11, 11); /* #79 */
t = state[1] + cc + d;
state[1] = state[2] + dd + e;
state[2] = state[3] + ee + a;
state[3] = state[4] + aa + b;
state[4] = state[0] + bb + c;
state[0] = t;
}

41
sys/opencrypto/rmd160.h Normal file
View File

@ -0,0 +1,41 @@
/* $NetBSD: rmd160.h,v 1.1 2003/07/25 21:12:48 jonathan Exp $ */
/* $OpenBSD: rmd160.h,v 1.3 2002/03/14 01:26:51 millert Exp $ */
/*
* Copyright (c) 2001 Markus Friedl. All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef _RMD160_H
#define _RMD160_H
/* RMD160 context. */
typedef struct RMD160Context {
u_int32_t state[5]; /* state */
u_int64_t count; /* number of bits, modulo 2^64 */
u_char buffer[64]; /* input buffer */
} RMD160_CTX;
void RMD160Init(RMD160_CTX *);
void RMD160Transform(u_int32_t [5], const u_char [64]);
void RMD160Update(RMD160_CTX *, const u_char *, u_int32_t);
void RMD160Final(u_char [20], RMD160_CTX *);
#endif /* _RMD160_H */

262
sys/opencrypto/skipjack.c Normal file
View File

@ -0,0 +1,262 @@
/* $NetBSD: skipjack.c,v 1.1 2003/07/25 21:12:48 jonathan Exp $ */
/* $OpenBSD: skipjack.c,v 1.3 2001/05/05 00:31:34 angelos Exp $ */
/*
* Further optimized test implementation of SKIPJACK algorithm
* Mark Tillotson <markt@chaos.org.uk>, 25 June 98
* Optimizations suit RISC (lots of registers) machine best.
*
* based on unoptimized implementation of
* Panu Rissanen <bande@lut.fi> 960624
*
* SKIPJACK and KEA Algorithm Specifications
* Version 2.0
* 29 May 1998
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: skipjack.c,v 1.1 2003/07/25 21:12:48 jonathan Exp $");
#include <sys/param.h>
#include <opencrypto/skipjack.h>
#include <sys/malloc.h>
#include <opencrypto/cryptodev.h>
static const u_int8_t ftable[0x100] =
{
0xa3, 0xd7, 0x09, 0x83, 0xf8, 0x48, 0xf6, 0xf4,
0xb3, 0x21, 0x15, 0x78, 0x99, 0xb1, 0xaf, 0xf9,
0xe7, 0x2d, 0x4d, 0x8a, 0xce, 0x4c, 0xca, 0x2e,
0x52, 0x95, 0xd9, 0x1e, 0x4e, 0x38, 0x44, 0x28,
0x0a, 0xdf, 0x02, 0xa0, 0x17, 0xf1, 0x60, 0x68,
0x12, 0xb7, 0x7a, 0xc3, 0xe9, 0xfa, 0x3d, 0x53,
0x96, 0x84, 0x6b, 0xba, 0xf2, 0x63, 0x9a, 0x19,
0x7c, 0xae, 0xe5, 0xf5, 0xf7, 0x16, 0x6a, 0xa2,
0x39, 0xb6, 0x7b, 0x0f, 0xc1, 0x93, 0x81, 0x1b,
0xee, 0xb4, 0x1a, 0xea, 0xd0, 0x91, 0x2f, 0xb8,
0x55, 0xb9, 0xda, 0x85, 0x3f, 0x41, 0xbf, 0xe0,
0x5a, 0x58, 0x80, 0x5f, 0x66, 0x0b, 0xd8, 0x90,
0x35, 0xd5, 0xc0, 0xa7, 0x33, 0x06, 0x65, 0x69,
0x45, 0x00, 0x94, 0x56, 0x6d, 0x98, 0x9b, 0x76,
0x97, 0xfc, 0xb2, 0xc2, 0xb0, 0xfe, 0xdb, 0x20,
0xe1, 0xeb, 0xd6, 0xe4, 0xdd, 0x47, 0x4a, 0x1d,
0x42, 0xed, 0x9e, 0x6e, 0x49, 0x3c, 0xcd, 0x43,
0x27, 0xd2, 0x07, 0xd4, 0xde, 0xc7, 0x67, 0x18,
0x89, 0xcb, 0x30, 0x1f, 0x8d, 0xc6, 0x8f, 0xaa,
0xc8, 0x74, 0xdc, 0xc9, 0x5d, 0x5c, 0x31, 0xa4,
0x70, 0x88, 0x61, 0x2c, 0x9f, 0x0d, 0x2b, 0x87,
0x50, 0x82, 0x54, 0x64, 0x26, 0x7d, 0x03, 0x40,
0x34, 0x4b, 0x1c, 0x73, 0xd1, 0xc4, 0xfd, 0x3b,
0xcc, 0xfb, 0x7f, 0xab, 0xe6, 0x3e, 0x5b, 0xa5,
0xad, 0x04, 0x23, 0x9c, 0x14, 0x51, 0x22, 0xf0,
0x29, 0x79, 0x71, 0x7e, 0xff, 0x8c, 0x0e, 0xe2,
0x0c, 0xef, 0xbc, 0x72, 0x75, 0x6f, 0x37, 0xa1,
0xec, 0xd3, 0x8e, 0x62, 0x8b, 0x86, 0x10, 0xe8,
0x08, 0x77, 0x11, 0xbe, 0x92, 0x4f, 0x24, 0xc5,
0x32, 0x36, 0x9d, 0xcf, 0xf3, 0xa6, 0xbb, 0xac,
0x5e, 0x6c, 0xa9, 0x13, 0x57, 0x25, 0xb5, 0xe3,
0xbd, 0xa8, 0x3a, 0x01, 0x05, 0x59, 0x2a, 0x46
};
/*
* For each key byte generate a table to represent the function
* ftable [in ^ keybyte]
*
* These tables used to save an XOR in each stage of the G-function
* the tables are hopefully pointed to by register allocated variables
* k0, k1..k9
*/
void
subkey_table_gen (u_int8_t *key, u_int8_t **key_tables)
{
int i, k;
for (k = 0; k < 10; k++) {
u_int8_t key_byte = key [k];
u_int8_t * table = key_tables[k];
for (i = 0; i < 0x100; i++)
table [i] = ftable [i ^ key_byte];
}
}
#define g(k0, k1, k2, k3, ih, il, oh, ol) \
{ \
oh = k##k0 [il] ^ ih; \
ol = k##k1 [oh] ^ il; \
oh = k##k2 [ol] ^ oh; \
ol = k##k3 [oh] ^ ol; \
}
#define g0(ih, il, oh, ol) g(0, 1, 2, 3, ih, il, oh, ol)
#define g4(ih, il, oh, ol) g(4, 5, 6, 7, ih, il, oh, ol)
#define g8(ih, il, oh, ol) g(8, 9, 0, 1, ih, il, oh, ol)
#define g2(ih, il, oh, ol) g(2, 3, 4, 5, ih, il, oh, ol)
#define g6(ih, il, oh, ol) g(6, 7, 8, 9, ih, il, oh, ol)
#define g_inv(k0, k1, k2, k3, ih, il, oh, ol) \
{ \
ol = k##k3 [ih] ^ il; \
oh = k##k2 [ol] ^ ih; \
ol = k##k1 [oh] ^ ol; \
oh = k##k0 [ol] ^ oh; \
}
#define g0_inv(ih, il, oh, ol) g_inv(0, 1, 2, 3, ih, il, oh, ol)
#define g4_inv(ih, il, oh, ol) g_inv(4, 5, 6, 7, ih, il, oh, ol)
#define g8_inv(ih, il, oh, ol) g_inv(8, 9, 0, 1, ih, il, oh, ol)
#define g2_inv(ih, il, oh, ol) g_inv(2, 3, 4, 5, ih, il, oh, ol)
#define g6_inv(ih, il, oh, ol) g_inv(6, 7, 8, 9, ih, il, oh, ol)
/* optimized version of Skipjack algorithm
*
* the appropriate g-function is inlined for each round
*
* the data movement is minimized by rotating the names of the
* variables w1..w4, not their contents (saves 3 moves per round)
*
* the loops are completely unrolled (needed to staticize choice of g)
*
* compiles to about 470 instructions on a Sparc (gcc -O)
* which is about 58 instructions per byte, 14 per round.
* gcc seems to leave in some unnecessary and with 0xFF operations
* but only in the latter part of the functions. Perhaps it
* runs out of resources to properly optimize long inlined function?
* in theory should get about 11 instructions per round, not 14
*/
void
skipjack_forwards(u_int8_t *plain, u_int8_t *cipher, u_int8_t **key_tables)
{
u_int8_t wh1 = plain[0]; u_int8_t wl1 = plain[1];
u_int8_t wh2 = plain[2]; u_int8_t wl2 = plain[3];
u_int8_t wh3 = plain[4]; u_int8_t wl3 = plain[5];
u_int8_t wh4 = plain[6]; u_int8_t wl4 = plain[7];
u_int8_t * k0 = key_tables [0];
u_int8_t * k1 = key_tables [1];
u_int8_t * k2 = key_tables [2];
u_int8_t * k3 = key_tables [3];
u_int8_t * k4 = key_tables [4];
u_int8_t * k5 = key_tables [5];
u_int8_t * k6 = key_tables [6];
u_int8_t * k7 = key_tables [7];
u_int8_t * k8 = key_tables [8];
u_int8_t * k9 = key_tables [9];
/* first 8 rounds */
g0 (wh1,wl1, wh1,wl1); wl4 ^= wl1 ^ 1; wh4 ^= wh1;
g4 (wh4,wl4, wh4,wl4); wl3 ^= wl4 ^ 2; wh3 ^= wh4;
g8 (wh3,wl3, wh3,wl3); wl2 ^= wl3 ^ 3; wh2 ^= wh3;
g2 (wh2,wl2, wh2,wl2); wl1 ^= wl2 ^ 4; wh1 ^= wh2;
g6 (wh1,wl1, wh1,wl1); wl4 ^= wl1 ^ 5; wh4 ^= wh1;
g0 (wh4,wl4, wh4,wl4); wl3 ^= wl4 ^ 6; wh3 ^= wh4;
g4 (wh3,wl3, wh3,wl3); wl2 ^= wl3 ^ 7; wh2 ^= wh3;
g8 (wh2,wl2, wh2,wl2); wl1 ^= wl2 ^ 8; wh1 ^= wh2;
/* second 8 rounds */
wh2 ^= wh1; wl2 ^= wl1 ^ 9 ; g2 (wh1,wl1, wh1,wl1);
wh1 ^= wh4; wl1 ^= wl4 ^ 10; g6 (wh4,wl4, wh4,wl4);
wh4 ^= wh3; wl4 ^= wl3 ^ 11; g0 (wh3,wl3, wh3,wl3);
wh3 ^= wh2; wl3 ^= wl2 ^ 12; g4 (wh2,wl2, wh2,wl2);
wh2 ^= wh1; wl2 ^= wl1 ^ 13; g8 (wh1,wl1, wh1,wl1);
wh1 ^= wh4; wl1 ^= wl4 ^ 14; g2 (wh4,wl4, wh4,wl4);
wh4 ^= wh3; wl4 ^= wl3 ^ 15; g6 (wh3,wl3, wh3,wl3);
wh3 ^= wh2; wl3 ^= wl2 ^ 16; g0 (wh2,wl2, wh2,wl2);
/* third 8 rounds */
g4 (wh1,wl1, wh1,wl1); wl4 ^= wl1 ^ 17; wh4 ^= wh1;
g8 (wh4,wl4, wh4,wl4); wl3 ^= wl4 ^ 18; wh3 ^= wh4;
g2 (wh3,wl3, wh3,wl3); wl2 ^= wl3 ^ 19; wh2 ^= wh3;
g6 (wh2,wl2, wh2,wl2); wl1 ^= wl2 ^ 20; wh1 ^= wh2;
g0 (wh1,wl1, wh1,wl1); wl4 ^= wl1 ^ 21; wh4 ^= wh1;
g4 (wh4,wl4, wh4,wl4); wl3 ^= wl4 ^ 22; wh3 ^= wh4;
g8 (wh3,wl3, wh3,wl3); wl2 ^= wl3 ^ 23; wh2 ^= wh3;
g2 (wh2,wl2, wh2,wl2); wl1 ^= wl2 ^ 24; wh1 ^= wh2;
/* last 8 rounds */
wh2 ^= wh1; wl2 ^= wl1 ^ 25; g6 (wh1,wl1, wh1,wl1);
wh1 ^= wh4; wl1 ^= wl4 ^ 26; g0 (wh4,wl4, wh4,wl4);
wh4 ^= wh3; wl4 ^= wl3 ^ 27; g4 (wh3,wl3, wh3,wl3);
wh3 ^= wh2; wl3 ^= wl2 ^ 28; g8 (wh2,wl2, wh2,wl2);
wh2 ^= wh1; wl2 ^= wl1 ^ 29; g2 (wh1,wl1, wh1,wl1);
wh1 ^= wh4; wl1 ^= wl4 ^ 30; g6 (wh4,wl4, wh4,wl4);
wh4 ^= wh3; wl4 ^= wl3 ^ 31; g0 (wh3,wl3, wh3,wl3);
wh3 ^= wh2; wl3 ^= wl2 ^ 32; g4 (wh2,wl2, wh2,wl2);
/* pack into byte vector */
cipher [0] = wh1; cipher [1] = wl1;
cipher [2] = wh2; cipher [3] = wl2;
cipher [4] = wh3; cipher [5] = wl3;
cipher [6] = wh4; cipher [7] = wl4;
}
void
skipjack_backwards (u_int8_t *cipher, u_int8_t *plain, u_int8_t **key_tables)
{
/* setup 4 16-bit portions */
u_int8_t wh1 = cipher[0]; u_int8_t wl1 = cipher[1];
u_int8_t wh2 = cipher[2]; u_int8_t wl2 = cipher[3];
u_int8_t wh3 = cipher[4]; u_int8_t wl3 = cipher[5];
u_int8_t wh4 = cipher[6]; u_int8_t wl4 = cipher[7];
u_int8_t * k0 = key_tables [0];
u_int8_t * k1 = key_tables [1];
u_int8_t * k2 = key_tables [2];
u_int8_t * k3 = key_tables [3];
u_int8_t * k4 = key_tables [4];
u_int8_t * k5 = key_tables [5];
u_int8_t * k6 = key_tables [6];
u_int8_t * k7 = key_tables [7];
u_int8_t * k8 = key_tables [8];
u_int8_t * k9 = key_tables [9];
/* first 8 rounds */
g4_inv (wh2,wl2, wh2,wl2); wl3 ^= wl2 ^ 32; wh3 ^= wh2;
g0_inv (wh3,wl3, wh3,wl3); wl4 ^= wl3 ^ 31; wh4 ^= wh3;
g6_inv (wh4,wl4, wh4,wl4); wl1 ^= wl4 ^ 30; wh1 ^= wh4;
g2_inv (wh1,wl1, wh1,wl1); wl2 ^= wl1 ^ 29; wh2 ^= wh1;
g8_inv (wh2,wl2, wh2,wl2); wl3 ^= wl2 ^ 28; wh3 ^= wh2;
g4_inv (wh3,wl3, wh3,wl3); wl4 ^= wl3 ^ 27; wh4 ^= wh3;
g0_inv (wh4,wl4, wh4,wl4); wl1 ^= wl4 ^ 26; wh1 ^= wh4;
g6_inv (wh1,wl1, wh1,wl1); wl2 ^= wl1 ^ 25; wh2 ^= wh1;
/* second 8 rounds */
wh1 ^= wh2; wl1 ^= wl2 ^ 24; g2_inv (wh2,wl2, wh2,wl2);
wh2 ^= wh3; wl2 ^= wl3 ^ 23; g8_inv (wh3,wl3, wh3,wl3);
wh3 ^= wh4; wl3 ^= wl4 ^ 22; g4_inv (wh4,wl4, wh4,wl4);
wh4 ^= wh1; wl4 ^= wl1 ^ 21; g0_inv (wh1,wl1, wh1,wl1);
wh1 ^= wh2; wl1 ^= wl2 ^ 20; g6_inv (wh2,wl2, wh2,wl2);
wh2 ^= wh3; wl2 ^= wl3 ^ 19; g2_inv (wh3,wl3, wh3,wl3);
wh3 ^= wh4; wl3 ^= wl4 ^ 18; g8_inv (wh4,wl4, wh4,wl4);
wh4 ^= wh1; wl4 ^= wl1 ^ 17; g4_inv (wh1,wl1, wh1,wl1);
/* third 8 rounds */
g0_inv (wh2,wl2, wh2,wl2); wl3 ^= wl2 ^ 16; wh3 ^= wh2;
g6_inv (wh3,wl3, wh3,wl3); wl4 ^= wl3 ^ 15; wh4 ^= wh3;
g2_inv (wh4,wl4, wh4,wl4); wl1 ^= wl4 ^ 14; wh1 ^= wh4;
g8_inv (wh1,wl1, wh1,wl1); wl2 ^= wl1 ^ 13; wh2 ^= wh1;
g4_inv (wh2,wl2, wh2,wl2); wl3 ^= wl2 ^ 12; wh3 ^= wh2;
g0_inv (wh3,wl3, wh3,wl3); wl4 ^= wl3 ^ 11; wh4 ^= wh3;
g6_inv (wh4,wl4, wh4,wl4); wl1 ^= wl4 ^ 10; wh1 ^= wh4;
g2_inv (wh1,wl1, wh1,wl1); wl2 ^= wl1 ^ 9; wh2 ^= wh1;
/* last 8 rounds */
wh1 ^= wh2; wl1 ^= wl2 ^ 8; g8_inv (wh2,wl2, wh2,wl2);
wh2 ^= wh3; wl2 ^= wl3 ^ 7; g4_inv (wh3,wl3, wh3,wl3);
wh3 ^= wh4; wl3 ^= wl4 ^ 6; g0_inv (wh4,wl4, wh4,wl4);
wh4 ^= wh1; wl4 ^= wl1 ^ 5; g6_inv (wh1,wl1, wh1,wl1);
wh1 ^= wh2; wl1 ^= wl2 ^ 4; g2_inv (wh2,wl2, wh2,wl2);
wh2 ^= wh3; wl2 ^= wl3 ^ 3; g8_inv (wh3,wl3, wh3,wl3);
wh3 ^= wh4; wl3 ^= wl4 ^ 2; g4_inv (wh4,wl4, wh4,wl4);
wh4 ^= wh1; wl4 ^= wl1 ^ 1; g0_inv (wh1,wl1, wh1,wl1);
/* pack into byte vector */
plain [0] = wh1; plain [1] = wl1;
plain [2] = wh2; plain [3] = wl2;
plain [4] = wh3; plain [5] = wl3;
plain [6] = wh4; plain [7] = wl4;
}

19
sys/opencrypto/skipjack.h Normal file
View File

@ -0,0 +1,19 @@
/* $NetBSD: skipjack.h,v 1.1 2003/07/25 21:12:48 jonathan Exp $ */
/* $OpenBSD: skipjack.h,v 1.3 2002/03/14 01:26:51 millert Exp $ */
/*
* Further optimized test implementation of SKIPJACK algorithm
* Mark Tillotson <markt@chaos.org.uk>, 25 June 98
* Optimizations suit RISC (lots of registers) machine best.
*
* based on unoptimized implementation of
* Panu Rissanen <bande@lut.fi> 960624
*
* SKIPJACK and KEA Algorithm Specifications
* Version 2.0
* 29 May 1998
*/
extern void skipjack_forwards(u_int8_t *plain, u_int8_t *cipher, u_int8_t **key);
extern void skipjack_backwards(u_int8_t *cipher, u_int8_t *plain, u_int8_t **key);
extern void subkey_table_gen(u_int8_t *key, u_int8_t **key_tables);

660
sys/opencrypto/xform.c Normal file
View File

@ -0,0 +1,660 @@
/* $NetBSD: xform.c,v 1.1 2003/07/25 21:12:49 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/xform.c,v 1.1.2.1 2002/11/21 23:34:23 sam Exp $ */
/* $OpenBSD: xform.c,v 1.19 2002/08/16 22:47:25 dhartmei Exp $ */
/*
* The authors of this code are John Ioannidis (ji@tla.org),
* Angelos D. Keromytis (kermit@csd.uch.gr) and
* Niels Provos (provos@physnet.uni-hamburg.de).
*
* This code was written by John Ioannidis for BSD/OS in Athens, Greece,
* in November 1995.
*
* Ported to OpenBSD and NetBSD, with additional transforms, in December 1996,
* by Angelos D. Keromytis.
*
* Additional transforms and features in 1997 and 1998 by Angelos D. Keromytis
* and Niels Provos.
*
* Additional features in 1999 by Angelos D. Keromytis.
*
* Copyright (C) 1995, 1996, 1997, 1998, 1999 by John Ioannidis,
* Angelos D. Keromytis and Niels Provos.
*
* Copyright (C) 2001, Angelos D. Keromytis.
*
* Permission to use, copy, and modify this software with or without fee
* is hereby granted, provided that this entire notice is included in
* all copies of any software which is or includes a copy or
* modification of this software.
* You may use this code under the GNU public license if you so wish. Please
* contribute changes back to the authors under this freer than GPL license
* so that we may further the use of strong encryption without limitations to
* all.
*
* THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR
* IMPLIED WARRANTY. IN PARTICULAR, NONE OF THE AUTHORS MAKES ANY
* REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE
* MERCHANTABILITY OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR
* PURPOSE.
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: xform.c,v 1.1 2003/07/25 21:12:49 jonathan Exp $");
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/malloc.h>
#include <sys/sysctl.h>
#include <sys/errno.h>
#include <sys/time.h>
#include <sys/kernel.h>
#include <machine/cpu.h>
#include <crypto/blowfish/blowfish.h>
#include <crypto/des/des.h>
#include <opencrypto/rmd160.h>
#include <opencrypto/blf.h>
#include <opencrypto/cast.h>
#include <opencrypto/deflate.h>
#include <opencrypto/rijndael.h>
#include <opencrypto/skipjack.h>
#include <sys/md5k.h>
#include <sys/sha1.h>
#include <opencrypto/cryptodev.h>
#include <opencrypto/xform.h>
static void null_encrypt(caddr_t, u_int8_t *);
static void null_decrypt(caddr_t, u_int8_t *);
static int null_setkey(u_int8_t **, u_int8_t *, int);
static void null_zerokey(u_int8_t **);
static int des1_setkey(u_int8_t **, u_int8_t *, int);
static int des3_setkey(u_int8_t **, u_int8_t *, int);
static int blf_setkey(u_int8_t **, u_int8_t *, int);
static int cast5_setkey(u_int8_t **, u_int8_t *, int);
static int skipjack_setkey(u_int8_t **, u_int8_t *, int);
static int rijndael128_setkey(u_int8_t **, u_int8_t *, int);
static void des1_encrypt(caddr_t, u_int8_t *);
static void des3_encrypt(caddr_t, u_int8_t *);
static void blf_encrypt(caddr_t, u_int8_t *);
static void cast5_encrypt(caddr_t, u_int8_t *);
static void skipjack_encrypt(caddr_t, u_int8_t *);
static void rijndael128_encrypt(caddr_t, u_int8_t *);
static void des1_decrypt(caddr_t, u_int8_t *);
static void des3_decrypt(caddr_t, u_int8_t *);
static void blf_decrypt(caddr_t, u_int8_t *);
static void cast5_decrypt(caddr_t, u_int8_t *);
static void skipjack_decrypt(caddr_t, u_int8_t *);
static void rijndael128_decrypt(caddr_t, u_int8_t *);
static void des1_zerokey(u_int8_t **);
static void des3_zerokey(u_int8_t **);
static void blf_zerokey(u_int8_t **);
static void cast5_zerokey(u_int8_t **);
static void skipjack_zerokey(u_int8_t **);
static void rijndael128_zerokey(u_int8_t **);
static void null_init(void *);
static int null_update(void *, u_int8_t *, u_int16_t);
static void null_final(u_int8_t *, void *);
static int MD5Update_int(void *, u_int8_t *, u_int16_t);
static void SHA1Init_int(void *);
static int SHA1Update_int(void *, u_int8_t *, u_int16_t);
static void SHA1Final_int(u_int8_t *, void *);
static int RMD160Update_int(void *, u_int8_t *, u_int16_t);
static int SHA1Update_int(void *, u_int8_t *, u_int16_t);
static void SHA1Final_int(u_int8_t *, void *);
static int RMD160Update_int(void *, u_int8_t *, u_int16_t);
static int SHA256Update_int(void *, u_int8_t *, u_int16_t);
static int SHA384Update_int(void *, u_int8_t *, u_int16_t);
static int SHA512Update_int(void *, u_int8_t *, u_int16_t);
static u_int32_t deflate_compress(u_int8_t *, u_int32_t, u_int8_t **);
static u_int32_t deflate_decompress(u_int8_t *, u_int32_t, u_int8_t **);
MALLOC_DEFINE(M_XDATA, "xform", "xform data buffers");
/* Encryption instances */
struct enc_xform enc_xform_null = {
CRYPTO_NULL_CBC, "NULL",
/* NB: blocksize of 4 is to generate a properly aligned ESP header */
4, 0, 256, /* 2048 bits, max key */
null_encrypt,
null_decrypt,
null_setkey,
null_zerokey,
};
struct enc_xform enc_xform_des = {
CRYPTO_DES_CBC, "DES",
8, 8, 8,
des1_encrypt,
des1_decrypt,
des1_setkey,
des1_zerokey,
};
struct enc_xform enc_xform_3des = {
CRYPTO_3DES_CBC, "3DES",
8, 24, 24,
des3_encrypt,
des3_decrypt,
des3_setkey,
des3_zerokey
};
struct enc_xform enc_xform_blf = {
CRYPTO_BLF_CBC, "Blowfish",
8, 5, 56 /* 448 bits, max key */,
blf_encrypt,
blf_decrypt,
blf_setkey,
blf_zerokey
};
struct enc_xform enc_xform_cast5 = {
CRYPTO_CAST_CBC, "CAST-128",
8, 5, 16,
cast5_encrypt,
cast5_decrypt,
cast5_setkey,
cast5_zerokey
};
struct enc_xform enc_xform_skipjack = {
CRYPTO_SKIPJACK_CBC, "Skipjack",
8, 10, 10,
skipjack_encrypt,
skipjack_decrypt,
skipjack_setkey,
skipjack_zerokey
};
struct enc_xform enc_xform_rijndael128 = {
CRYPTO_RIJNDAEL128_CBC, "Rijndael-128/AES",
16, 8, 32,
rijndael128_encrypt,
rijndael128_decrypt,
rijndael128_setkey,
rijndael128_zerokey,
};
struct enc_xform enc_xform_arc4 = {
CRYPTO_ARC4, "ARC4",
1, 1, 32,
NULL,
NULL,
NULL,
NULL,
};
/* Authentication instances */
struct auth_hash auth_hash_null = {
CRYPTO_NULL_HMAC, "NULL-HMAC",
0, 0, 12, sizeof(int), /* NB: context isn't used */
null_init, null_update, null_final
};
struct auth_hash auth_hash_hmac_md5_96 = {
CRYPTO_MD5_HMAC, "HMAC-MD5",
16, 16, 12, sizeof(MD5_CTX),
(void (*) (void *)) MD5Init, MD5Update_int,
(void (*) (u_int8_t *, void *)) MD5Final
};
struct auth_hash auth_hash_hmac_sha1_96 = {
CRYPTO_SHA1_HMAC, "HMAC-SHA1",
20, 20, 12, sizeof(SHA1_CTX),
SHA1Init_int, SHA1Update_int, SHA1Final_int
};
struct auth_hash auth_hash_hmac_ripemd_160_96 = {
CRYPTO_RIPEMD160_HMAC, "HMAC-RIPEMD-160",
20, 20, 12, sizeof(RMD160_CTX),
(void (*)(void *)) RMD160Init, RMD160Update_int,
(void (*)(u_int8_t *, void *)) RMD160Final
};
struct auth_hash auth_hash_key_md5 = {
CRYPTO_MD5_KPDK, "Keyed MD5",
0, 16, 12, sizeof(MD5_CTX),
(void (*)(void *)) MD5Init, MD5Update_int,
(void (*)(u_int8_t *, void *)) MD5Final
};
struct auth_hash auth_hash_key_sha1 = {
CRYPTO_SHA1_KPDK, "Keyed SHA1",
0, 20, 12, sizeof(SHA1_CTX),
SHA1Init_int, SHA1Update_int, SHA1Final_int
};
struct auth_hash auth_hash_md5 = {
CRYPTO_MD5, "MD5",
0, 16, 16, sizeof(MD5_CTX),
(void (*) (void *)) MD5Init, MD5Update_int,
(void (*) (u_int8_t *, void *)) MD5Final
};
struct auth_hash auth_hash_sha1 = {
CRYPTO_SHA1, "SHA1",
0, 20, 20, sizeof(SHA1_CTX),
(void (*)(void *)) SHA1Init, SHA1Update_int,
(void (*)(u_int8_t *, void *)) SHA1Final
};
struct auth_hash auth_hash_hmac_sha2_256 = {
CRYPTO_SHA2_HMAC, "HMAC-SHA2",
32, 32, 12, sizeof(SHA256_CTX),
(void (*)(void *)) SHA256_Init, SHA256Update_int,
(void (*)(u_int8_t *, void *)) SHA256_Final
};
struct auth_hash auth_hash_hmac_sha2_384 = {
CRYPTO_SHA2_HMAC, "HMAC-SHA2-384",
48, 48, 12, sizeof(SHA384_CTX),
(void (*)(void *)) SHA384_Init, SHA384Update_int,
(void (*)(u_int8_t *, void *)) SHA384_Final
};
struct auth_hash auth_hash_hmac_sha2_512 = {
CRYPTO_SHA2_HMAC, "HMAC-SHA2-512",
64, 64, 12, sizeof(SHA512_CTX),
(void (*)(void *)) SHA512_Init, SHA512Update_int,
(void (*)(u_int8_t *, void *)) SHA512_Final
};
/* Compression instance */
struct comp_algo comp_algo_deflate = {
CRYPTO_DEFLATE_COMP, "Deflate",
90, deflate_compress,
deflate_decompress
};
/*
* Encryption wrapper routines.
*/
static void
null_encrypt(caddr_t key, u_int8_t *blk)
{
}
static void
null_decrypt(caddr_t key, u_int8_t *blk)
{
}
static int
null_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
*sched = NULL;
return 0;
}
static void
null_zerokey(u_int8_t **sched)
{
*sched = NULL;
}
static void
des1_encrypt(caddr_t key, u_int8_t *blk)
{
des_cblock *cb = (des_cblock *) blk;
des_key_schedule *p = (des_key_schedule *) key;
des_ecb_encrypt(cb, cb, p[0], DES_ENCRYPT);
}
static void
des1_decrypt(caddr_t key, u_int8_t *blk)
{
des_cblock *cb = (des_cblock *) blk;
des_key_schedule *p = (des_key_schedule *) key;
des_ecb_encrypt(cb, cb, p[0], DES_DECRYPT);
}
static int
des1_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
des_key_schedule *p;
int err;
MALLOC(p, des_key_schedule *, sizeof (des_key_schedule),
M_CRYPTO_DATA, M_NOWAIT);
if (p != NULL) {
bzero(p, sizeof(des_key_schedule));
des_set_key((des_cblock *) key, p[0]);
err = 0;
} else
err = ENOMEM;
*sched = (u_int8_t *) p;
return err;
}
static void
des1_zerokey(u_int8_t **sched)
{
bzero(*sched, sizeof (des_key_schedule));
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
static void
des3_encrypt(caddr_t key, u_int8_t *blk)
{
des_cblock *cb = (des_cblock *) blk;
des_key_schedule *p = (des_key_schedule *) key;
des_ecb3_encrypt(cb, cb, p[0], p[1], p[2], DES_ENCRYPT);
}
static void
des3_decrypt(caddr_t key, u_int8_t *blk)
{
des_cblock *cb = (des_cblock *) blk;
des_key_schedule *p = (des_key_schedule *) key;
des_ecb3_encrypt(cb, cb, p[0], p[1], p[2], DES_DECRYPT);
}
static int
des3_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
des_key_schedule *p;
int err;
MALLOC(p, des_key_schedule *, 3*sizeof (des_key_schedule),
M_CRYPTO_DATA, M_NOWAIT);
if (p != NULL) {
bzero(p, 3*sizeof(des_key_schedule));
des_set_key((des_cblock *)(key + 0), p[0]);
des_set_key((des_cblock *)(key + 8), p[1]);
des_set_key((des_cblock *)(key + 16), p[2]);
err = 0;
} else
err = ENOMEM;
*sched = (u_int8_t *) p;
return err;
}
static void
des3_zerokey(u_int8_t **sched)
{
bzero(*sched, 3*sizeof (des_key_schedule));
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
static void
blf_encrypt(caddr_t key, u_int8_t *blk)
{
blf_ecb_encrypt((blf_ctx *) key, blk, 8);
}
static void
blf_decrypt(caddr_t key, u_int8_t *blk)
{
blf_ecb_decrypt((blf_ctx *) key, blk, 8);
}
static int
blf_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
int err;
#ifdef __FreeBSD__
#define BLF_SIZ sizeof(BF_KEY)
#else
#define BLF_SIZ sizeof(blf_ctx)
#endif
MALLOC(*sched, u_int8_t *, BLF_SIZ,
M_CRYPTO_DATA, M_NOWAIT);
if (*sched != NULL) {
bzero(*sched, BLF_SIZ);
#ifdef _FreeBSD__
BF_set_key((BF_KEY *) *sched, len, key);
#else
blf_key((blf_ctx *)*sched, key, len);
#endif
err = 0;
} else
err = ENOMEM;
return err;
}
static void
blf_zerokey(u_int8_t **sched)
{
bzero(*sched, BLF_SIZ);
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
static void
cast5_encrypt(caddr_t key, u_int8_t *blk)
{
cast_encrypt((cast_key *) key, blk, blk);
}
static void
cast5_decrypt(caddr_t key, u_int8_t *blk)
{
cast_decrypt((cast_key *) key, blk, blk);
}
static int
cast5_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
int err;
MALLOC(*sched, u_int8_t *, sizeof(cast_key), M_CRYPTO_DATA,
M_NOWAIT);
if (*sched != NULL) {
bzero(*sched, sizeof(cast_key));
cast_setkey((cast_key *)*sched, key, len);
err = 0;
} else
err = ENOMEM;
return err;
}
static void
cast5_zerokey(u_int8_t **sched)
{
bzero(*sched, sizeof(cast_key));
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
static void
skipjack_encrypt(caddr_t key, u_int8_t *blk)
{
skipjack_forwards(blk, blk, (u_int8_t **) key);
}
static void
skipjack_decrypt(caddr_t key, u_int8_t *blk)
{
skipjack_backwards(blk, blk, (u_int8_t **) key);
}
static int
skipjack_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
int err;
/* NB: allocate all the memory that's needed at once */
/* XXX assumes bytes are aligned on sizeof(u_char) == 1 boundaries.
* Will this break a pdp-10, Cray-1, or GE-645 port?
*/
MALLOC(*sched, u_int8_t *, 10 * (sizeof(u_int8_t *) + 0x100),
M_CRYPTO_DATA, M_NOWAIT);
if (*sched != NULL) {
u_int8_t** key_tables = (u_int8_t**) *sched;
u_int8_t* table = (u_int8_t*) &key_tables[10];
int k;
bzero(*sched, 10 * sizeof(u_int8_t *)+0x100);
for (k = 0; k < 10; k++) {
key_tables[k] = table;
table += 0x100;
}
subkey_table_gen(key, (u_int8_t **) *sched);
err = 0;
} else
err = ENOMEM;
return err;
}
static void
skipjack_zerokey(u_int8_t **sched)
{
bzero(*sched, 10 * (sizeof(u_int8_t *) + 0x100));
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
static void
rijndael128_encrypt(caddr_t key, u_int8_t *blk)
{
rijndael_encrypt((rijndael_ctx *) key, (u_char *) blk, (u_char *) blk);
}
static void
rijndael128_decrypt(caddr_t key, u_int8_t *blk)
{
rijndael_decrypt(((rijndael_ctx *) key) + 1, (u_char *) blk,
(u_char *) blk);
}
static int
rijndael128_setkey(u_int8_t **sched, u_int8_t *key, int len)
{
int err;
MALLOC(*sched, u_int8_t *, 2 * sizeof(rijndael_ctx), M_CRYPTO_DATA,
M_WAITOK);
if (*sched != NULL) {
bzero(*sched, 2 * sizeof(rijndael_ctx));
rijndael_set_key((rijndael_ctx *) *sched, (u_char *) key, len * 8, 1);
rijndael_set_key(((rijndael_ctx *) *sched) + 1, (u_char *) key,
len * 8, 0);
err = 0;
} else
err = ENOMEM;
return err;
}
static void
rijndael128_zerokey(u_int8_t **sched)
{
bzero(*sched, 2 * sizeof(rijndael_ctx));
FREE(*sched, M_CRYPTO_DATA);
*sched = NULL;
}
/*
* And now for auth.
*/
static void
null_init(void *ctx)
{
}
static int
null_update(void *ctx, u_int8_t *buf, u_int16_t len)
{
return 0;
}
static void
null_final(u_int8_t *buf, void *ctx)
{
if (buf != (u_int8_t *) 0)
bzero(buf, 12);
}
static int
RMD160Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
RMD160Update(ctx, buf, len);
return 0;
}
static int
MD5Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
MD5Update(ctx, buf, len);
return 0;
}
static void
SHA1Init_int(void *ctx)
{
SHA1Init(ctx);
}
static int
SHA1Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
SHA1Update(ctx, buf, len);
return 0;
}
static void
SHA1Final_int(u_int8_t *blk, void *ctx)
{
SHA1Final(blk, ctx);
}
static int
SHA256Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
SHA256_Update(ctx, buf, len);
return 0;
}
static int
SHA384Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
SHA384_Update(ctx, buf, len);
return 0;
}
static int
SHA512Update_int(void *ctx, u_int8_t *buf, u_int16_t len)
{
SHA512_Update(ctx, buf, len);
return 0;
}
/*
* And compression
*/
static u_int32_t
deflate_compress(data, size, out)
u_int8_t *data;
u_int32_t size;
u_int8_t **out;
{
return deflate_global(data, size, 0, out);
}
static u_int32_t
deflate_decompress(data, size, out)
u_int8_t *data;
u_int32_t size;
u_int8_t **out;
{
return deflate_global(data, size, 1, out);
}

105
sys/opencrypto/xform.h Normal file
View File

@ -0,0 +1,105 @@
/* $NetBSD: xform.h,v 1.1 2003/07/25 21:12:49 jonathan Exp $ */
/* $FreeBSD: src/sys/opencrypto/xform.h,v 1.1.2.1 2002/11/21 23:34:23 sam Exp $ */
/* $OpenBSD: xform.h,v 1.10 2002/04/22 23:10:09 deraadt Exp $ */
/*
* The author of this code is Angelos D. Keromytis (angelos@cis.upenn.edu)
*
* This code was written by Angelos D. Keromytis in Athens, Greece, in
* February 2000. Network Security Technologies Inc. (NSTI) kindly
* supported the development of this code.
*
* Copyright (c) 2000 Angelos D. Keromytis
*
* Permission to use, copy, and modify this software with or without fee
* is hereby granted, provided that this entire notice is included in
* all source code copies of any software which is or includes a copy or
* modification of this software.
*
* THIS SOFTWARE IS BEING PROVIDED "AS IS", WITHOUT ANY EXPRESS OR
* IMPLIED WARRANTY. IN PARTICULAR, NONE OF THE AUTHORS MAKES ANY
* REPRESENTATION OR WARRANTY OF ANY KIND CONCERNING THE
* MERCHANTABILITY OF THIS SOFTWARE OR ITS FITNESS FOR ANY PARTICULAR
* PURPOSE.
*/
#ifndef _CRYPTO_XFORM_H_
#define _CRYPTO_XFORM_H_
#include <sys/md5k.h>
#include <sys/sha1.h>
#include <crypto/sha2/sha2.h>
#include <opencrypto/rmd160.h>
/* Declarations */
struct auth_hash {
int type;
char *name;
u_int16_t keysize;
u_int16_t hashsize;
u_int16_t authsize;
u_int16_t ctxsize;
void (*Init) (void *);
int (*Update) (void *, u_int8_t *, u_int16_t);
void (*Final) (u_int8_t *, void *);
};
/* Provide array-limit for clients (e.g., netipsec) */
#define AH_ALEN_MAX 20 /* max authenticator hash length */
struct enc_xform {
int type;
char *name;
u_int16_t blocksize;
u_int16_t minkey, maxkey;
void (*encrypt) (caddr_t, u_int8_t *);
void (*decrypt) (caddr_t, u_int8_t *);
int (*setkey) (u_int8_t **, u_int8_t *, int len);
void (*zerokey) (u_int8_t **);
};
struct comp_algo {
int type;
char *name;
size_t minlen;
u_int32_t (*compress) (u_int8_t *, u_int32_t, u_int8_t **);
u_int32_t (*decompress) (u_int8_t *, u_int32_t, u_int8_t **);
};
union authctx {
MD5_CTX md5ctx;
SHA1_CTX sha1ctx;
RMD160_CTX rmd160ctx;
SHA256_CTX sha256ctx;
SHA384_CTX sha384ctx;
SHA512_CTX sha512ctx;
};
extern struct enc_xform enc_xform_null;
extern struct enc_xform enc_xform_des;
extern struct enc_xform enc_xform_3des;
extern struct enc_xform enc_xform_blf;
extern struct enc_xform enc_xform_cast5;
extern struct enc_xform enc_xform_skipjack;
extern struct enc_xform enc_xform_rijndael128;
extern struct enc_xform enc_xform_arc4;
extern struct auth_hash auth_hash_null;
extern struct auth_hash auth_hash_md5;
extern struct auth_hash auth_hash_sha1;
extern struct auth_hash auth_hash_key_md5;
extern struct auth_hash auth_hash_key_sha1;
extern struct auth_hash auth_hash_hmac_md5_96;
extern struct auth_hash auth_hash_hmac_sha1_96;
extern struct auth_hash auth_hash_hmac_ripemd_160_96;
extern struct auth_hash auth_hash_hmac_sha2_256;
extern struct auth_hash auth_hash_hmac_sha2_384;
extern struct auth_hash auth_hash_hmac_sha2_512;
extern struct comp_algo comp_algo_deflate;
#ifdef _KERNEL
#include <sys/malloc.h>
MALLOC_DECLARE(M_XDATA);
#endif
#endif /* _CRYPTO_XFORM_H_ */