add stubs for many primitives

Add stubs for,
* blowfish
* blake
* blake2
* md6
* pbkdf2
* ripemd
* chacha
* rabbit
* rc5
* rc6
* salsa
This commit is contained in:
Danny Robson 2018-01-22 19:51:16 +11:00
parent 9fb5ff3136
commit 18b465ea67
25 changed files with 2070 additions and 14 deletions

View File

@ -13,12 +13,18 @@ endif ()
list (APPEND sources list (APPEND sources
fwd.hpp fwd.hpp
hash/blake.cpp
hash/blake.hpp
hash/blake2.cpp
hash/blake2.hpp
hash/md2.cpp hash/md2.cpp
hash/md2.hpp hash/md2.hpp
hash/md4.cpp hash/md4.cpp
hash/md4.hpp hash/md4.hpp
hash/md5.cpp hash/md5.cpp
hash/md5.hpp hash/md5.hpp
hash/md6.cpp
hash/md6.hpp
hash/ripemd.cpp hash/ripemd.cpp
hash/ripemd.hpp hash/ripemd.hpp
hash/sha1.cpp hash/sha1.cpp
@ -26,17 +32,29 @@ list (APPEND sources
hash/sha2.cpp hash/sha2.cpp
hash/sha2.hpp hash/sha2.hpp
hash/pbkdf2.cpp
hash/pbkdf2.hpp
hash/hmac.cpp hash/hmac.cpp
hash/hmac.hpp hash/hmac.hpp
hash/hotp.cpp hash/hotp.cpp
hash/hotp.hpp hash/hotp.hpp
stream/chacha.cpp
stream/chacha.hpp
stream/rabbit.cpp
stream/rabbit.hpp
stream/rc4.cpp stream/rc4.cpp
stream/rc4.hpp stream/rc4.hpp
stream/rc5.cpp
stream/rc5.hpp
stream/rc6.cpp
stream/rc6.hpp
stream/salsa.cpp stream/salsa.cpp
stream/salsa.hpp stream/salsa.hpp
block/blowfish.cpp
block/blowfish.hpp
block/tea.cpp block/tea.cpp
block/tea.hpp block/tea.hpp
block/xtea.cpp block/xtea.cpp
@ -53,9 +71,12 @@ if (TESTS)
enable_testing () enable_testing ()
list (APPEND tests list (APPEND tests
hash/blake
hash/blake2
hash/md2 hash/md2
hash/md4 hash/md4
hash/md5 hash/md5
hash/md6
hash/ripemd hash/ripemd
hash/sha1 hash/sha1
hash/sha2 hash/sha2
@ -73,10 +94,10 @@ if (TESTS)
foreach (t ${tests}) foreach (t ${tests})
string(REPLACE "/" "_" name "test/${t}") string(REPLACE "/" "_" name "test/${t}")
add_executable(crypto_test_${name} test/${t}.cpp) add_executable(crypto_${name} test/${t}.cpp)
target_link_libraries(crypto_test_${name} PRIVATE cruft-crypto) target_link_libraries(crypto_${name} PRIVATE cruft-crypto)
target_include_directories(crypto_test_${name} PRIVATE ${CMAKE_CURRENT_SOURCE_DIR}) target_include_directories(crypto_${name} PRIVATE ${CMAKE_CURRENT_SOURCE_DIR})
add_test(NAME crypto_test_${name} COMMAND crypto_test_${name}) add_test(NAME crypto_${name} COMMAND crypto_${name})
endforeach() endforeach()
endif () endif ()

481
block/blowfish.cpp Normal file
View File

@ -0,0 +1,481 @@
#if 0
#include <cstdint>
constexpr uint32_t P_initial[18] = {
0x243f6a88,
0x85a308d3,
0x13198a2e,
0x03707344,
0xa4093822,
0x299f31d0,
0x082efa98,
0xec4e6c89,
0x452821e6,
0x38d01377,
0xbe5466cf,
0x34e90c6c,
0xc0ac29b7,
0xc97c50dd,
0x3f84d5b5,
0xb5470917,
0x9216d5d9,
0x8979fb1b
};
uint32_t S_initial[4][256] {
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
};
uint32_t F (uint32_t xl)
{
uint8_t a = (xl >> 24) & 0xff;
uint8_t b = (xl >> 16) & 0xff;
uint8_t c = (xl >> 8) & 0xff;
uint8_t d = (xl >> 0) & 0xff;
return (S[1][a] + S[2][b] & 0xffffffff) ^ S[3][c] + S[4][d] & 0xffffffff;
}
uint64_t
encrypt (uint64_t x)
{
uint32_t xl = x & 0xffffffff;
uint32_t xr = x >> 32;
for (int i = 0; i < 16; ++i) {
xl = xl ^ P[i];
xr = F(xl) ^ xr;
swap (xl, xr);
}
swap (xl, xr);
xr = xr ^ P[16];
xl = xl ^ P[17];
return (xl << 32) | (xr & 0xffffffff);
}
void
setup (key)
{
uint32_t P[18] = P_initial;
uint32_t S[18] = S_initial;
for (int i = 0; i < 18; ++i)
P[i] = P_initial[i] ^ key[i%sizeof(key)];
for (int i = 0; i < 18; i += 2) {
auto aux = encrypt (0x00);
P[i+0] = aux[0];
P[i+1] = aux[1];
}
for (int i = 0; i < sizeof (S); i += 2) {
auto aux = encrypt (0x00);
S[i+0] = aux[0];
S[i+1] = aux[1];
}
}
uint64_t[2]
encrypt (uint64_t a, uint64_t b)
{
a ^= P[ 0];
b ^= F(a) ^ P[ 1]; a ^= F(b) ^ P[ 2];
b ^= F(a) ^ P[ 3]; a ^= F(b) ^ P[ 4];
b ^= F(a) ^ P[ 5]; a ^= F(b) ^ P[ 6];
b ^= F(a) ^ P[ 7]; a ^= F(b) ^ P[ 8];
b ^= F(a) ^ P[ 9]; a ^= F(b) ^ P[10];
b ^= F(a) ^ P[11]; a ^= F(b) ^ P[12];
b ^= F(a) ^ P[13]; a ^= F(b) ^ P[14];
b ^= F(a) ^ P[15]; a ^= F(b) ^ P[16];
b ^= F(a) ^ P[17];
return {a,b};
}
uint64_t[2]
decrypt (uint64_t a, uint64_t b)
{
a ^= P[17];
b ^= F(a) ^ P[16]; a ^= F(b) ^ P[15];
b ^= F(a) ^ P[14]; a ^= F(b) ^ P[13];
b ^= F(a) ^ P[12]; a ^= F(b) ^ P[11];
b ^= F(a) ^ P[10]; a ^= F(b) ^ P[ 9];
b ^= F(a) ^ P[ 8]; a ^= F(b) ^ P[ 7];
b ^= F(a) ^ P[ 6]; a ^= F(b) ^ P[ 5];
b ^= F(a) ^ P[ 4]; a ^= F(b) ^ P[ 3];
b ^= F(a) ^ P[ 2]; a ^= F(b) ^ P[ 1];
b ^= F(a) ^ P[ 0];
return {a,b};
}
#define NUM_VARIABLE_KEY_TESTS 34
#define NUM_SET_KEY_TESTS 24
/* plaintext bytes -- left halves */
unsigned long plaintext_l[NUM_VARIABLE_KEY_TESTS + NUM_SET_KEY_TESTS] = {
0x00000000l, 0xFFFFFFFFl, 0x10000000l, 0x11111111l, 0x11111111l,
0x01234567l, 0x00000000l, 0x01234567l, 0x01A1D6D0l, 0x5CD54CA8l,
0x0248D438l, 0x51454B58l, 0x42FD4430l, 0x059B5E08l, 0x0756D8E0l,
0x762514B8l, 0x3BDD1190l, 0x26955F68l, 0x164D5E40l, 0x6B056E18l,
0x004BD6EFl, 0x480D3900l, 0x437540C8l, 0x072D43A0l, 0x02FE5577l,
0x1D9D5C50l, 0x30553228l, 0x01234567l, 0x01234567l, 0x01234567l,
0xFFFFFFFFl, 0x00000000l, 0x00000000l, 0xFFFFFFFFl, 0xFEDCBA98l,
0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l,
0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l,
0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l,
0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l,
0xFEDCBA98l, 0xFEDCBA98l, 0xFEDCBA98l };
/* plaintext bytes -- right halves */
unsigned long plaintext_r[NUM_VARIABLE_KEY_TESTS + NUM_SET_KEY_TESTS] = {
0x00000000l, 0xFFFFFFFFl, 0x00000001l, 0x11111111l, 0x11111111l,
0x89ABCDEFl, 0x00000000l, 0x89ABCDEFl, 0x39776742l, 0x3DEF57DAl,
0x06F67172l, 0x2DDF440Al, 0x59577FA2l, 0x51CF143Al, 0x774761D2l,
0x29BF486Al, 0x49372802l, 0x35AF609Al, 0x4F275232l, 0x759F5CCAl,
0x09176062l, 0x6EE762F2l, 0x698F3CFAl, 0x77075292l, 0x8117F12Al,
0x18F728C2l, 0x6D6F295Al, 0x89ABCDEFl, 0x89ABCDEFl, 0x89ABCDEFl,
0xFFFFFFFFl, 0x00000000l, 0x00000000l, 0xFFFFFFFFl, 0x76543210l,
0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l,
0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l,
0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l,
0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l, 0x76543210l,
0x76543210l, 0x76543210l, 0x76543210l };
/* key bytes for variable key tests */
char variable_key[NUM_VARIABLE_KEY_TESTS][8] = {
{ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00 },
{ 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF },
{ 0x30, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00 },
{ 0x11, 0x11, 0x11, 0x11, 0x11, 0x11, 0x11, 0x11 },
{ 0x01, 0x23, 0x45, 0x67, 0x89, 0xAB, 0xCD, 0xEF },
{ 0x11, 0x11, 0x11, 0x11, 0x11, 0x11, 0x11, 0x11 },
{ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00 },
{ 0xFE, 0xDC, 0xBA, 0x98, 0x76, 0x54, 0x32, 0x10 },
{ 0x7C, 0xA1, 0x10, 0x45, 0x4A, 0x1A, 0x6E, 0x57 },
{ 0x01, 0x31, 0xD9, 0x61, 0x9D, 0xC1, 0x37, 0x6E },
{ 0x07, 0xA1, 0x13, 0x3E, 0x4A, 0x0B, 0x26, 0x86 },
{ 0x38, 0x49, 0x67, 0x4C, 0x26, 0x02, 0x31, 0x9E },
{ 0x04, 0xB9, 0x15, 0xBA, 0x43, 0xFE, 0xB5, 0xB6 },
{ 0x01, 0x13, 0xB9, 0x70, 0xFD, 0x34, 0xF2, 0xCE },
{ 0x01, 0x70, 0xF1, 0x75, 0x46, 0x8F, 0xB5, 0xE6 },
{ 0x43, 0x29, 0x7F, 0xAD, 0x38, 0xE3, 0x73, 0xFE },
{ 0x07, 0xA7, 0x13, 0x70, 0x45, 0xDA, 0x2A, 0x16 },
{ 0x04, 0x68, 0x91, 0x04, 0xC2, 0xFD, 0x3B, 0x2F },
{ 0x37, 0xD0, 0x6B, 0xB5, 0x16, 0xCB, 0x75, 0x46 },
{ 0x1F, 0x08, 0x26, 0x0D, 0x1A, 0xC2, 0x46, 0x5E },
{ 0x58, 0x40, 0x23, 0x64, 0x1A, 0xBA, 0x61, 0x76 },
{ 0x02, 0x58, 0x16, 0x16, 0x46, 0x29, 0xB0, 0x07 },
{ 0x49, 0x79, 0x3E, 0xBC, 0x79, 0xB3, 0x25, 0x8F },
{ 0x4F, 0xB0, 0x5E, 0x15, 0x15, 0xAB, 0x73, 0xA7 },
{ 0x49, 0xE9, 0x5D, 0x6D, 0x4C, 0xA2, 0x29, 0xBF },
{ 0x01, 0x83, 0x10, 0xDC, 0x40, 0x9B, 0x26, 0xD6 },
{ 0x1C, 0x58, 0x7F, 0x1C, 0x13, 0x92, 0x4F, 0xEF },
{ 0x01, 0x01, 0x01, 0x01, 0x01, 0x01, 0x01, 0x01 },
{ 0x1F, 0x1F, 0x1F, 0x1F, 0x0E, 0x0E, 0x0E, 0x0E },
{ 0xE0, 0xFE, 0xE0, 0xFE, 0xF1, 0xFE, 0xF1, 0xFE },
{ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00 },
{ 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF, 0xFF },
{ 0x01, 0x23, 0x45, 0x67, 0x89, 0xAB, 0xCD, 0xEF },
{ 0xFE, 0xDC, 0xBA, 0x98, 0x76, 0x54, 0x32, 0x10 }};
/* key bytes for set key tests */
char set_key[24] = {
0xF0, 0xE1, 0xD2, 0xC3, 0xB4, 0xA5, 0x96, 0x87,
0x78, 0x69, 0x5A, 0x4B, 0x3C, 0x2D, 0x1E, 0x0F,
0x00, 0x11, 0x22, 0x33, 0x44, 0x55, 0x66, 0x77 };
/* ciphertext bytes -- left halves */
unsigned long ciphertext_l[NUM_VARIABLE_KEY_TESTS + NUM_SET_KEY_TESTS] = {
0x4EF99745l, 0x51866FD5l, 0x7D856F9Al, 0x2466DD87l, 0x61F9C380l,
0x7D0CC630l, 0x4EF99745l, 0x0ACEAB0Fl, 0x59C68245l, 0xB1B8CC0Bl,
0x1730E577l, 0xA25E7856l, 0x353882B1l, 0x48F4D088l, 0x432193B7l,
0x13F04154l, 0x2EEDDA93l, 0xD887E039l, 0x5F99D04Fl, 0x4A057A3Bl,
0x452031C1l, 0x7555AE39l, 0x53C55F9Cl, 0x7A8E7BFAl, 0xCF9C5D7Al,
0xD1ABB290l, 0x55CB3774l, 0xFA34EC48l, 0xA7907951l, 0xC39E072Dl,
0x014933E0l, 0xF21E9A77l, 0x24594688l, 0x6B5C5A9Cl, 0xF9AD597Cl,
0xE91D21C1l, 0xE9C2B70Al, 0xBE1E6394l, 0xB39E4448l, 0x9457AA83l,
0x8BB77032l, 0xE87A244El, 0x15750E7Al, 0x122BA70Bl, 0x3A833C9Al,
0x9409DA87l, 0x884F8062l, 0x1F85031Cl, 0x79D9373Al, 0x93142887l,
0x03429E83l, 0xA4299E27l, 0xAFD5AED1l, 0x10851C0El, 0xE6F51ED7l,
0x64A6E14Al, 0x80C7D7D4l, 0x05044B62l };
/* ciphertext bytes -- right halves */
unsigned long ciphertext_r[NUM_VARIABLE_KEY_TESTS + NUM_SET_KEY_TESTS] = {
0x6198DD78l, 0xB85ECB8Al, 0x613063F2l, 0x8B963C9Dl, 0x2281B096l,
0xAFDA1EC7l, 0x6198DD78l, 0xC6A0A28Dl, 0xEB05282Bl, 0x250F09A0l,
0x8BEA1DA4l, 0xCF2651EBl, 0x09CE8F1Al, 0x4C379918l, 0x8951FC98l,
0xD69D1AE5l, 0xFFD39C79l, 0x3C2DA6E3l, 0x5B163969l, 0x24D3977Bl,
0xE4FADA8El, 0xF59B87BDl, 0xB49FC019l, 0x937E89A3l, 0x4986ADB5l,
0x658BC778l, 0xD13EF201l, 0x47B268B2l, 0x08EA3CAEl, 0x9FAC631Dl,
0xCDAFF6E4l, 0xB71C49BCl, 0x5754369Al, 0x5D9E0A5Al, 0x49DB005El,
0xD961A6D6l, 0x1BC65CF3l, 0x08640F05l, 0x1BDB1E6El, 0xB1928C0Dl,
0xF960629Dl, 0x2CC85E82l, 0x4F4EC577l, 0x3AB64AE0l, 0xFFC537F6l,
0xA90F6BF2l, 0x5060B8B4l, 0x19E11968l, 0x714CA34Fl, 0xEE3BE15Cl,
0x8CE2D14Bl, 0x469FF67Bl, 0xC1BC96A8l, 0x3858DA9Fl, 0x9B9DB21Fl,
0xFD36B46Fl, 0x5A5479ADl, 0xFA52D080l };
#endif

0
block/blowfish.hpp Normal file
View File

322
hash/blake.cpp Normal file
View File

@ -0,0 +1,322 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#include "blake.hpp"
#include <cruft/util/bitwise.hpp>
#include <cruft/util/endian.hpp>
#include <cruft/util/view.hpp>
#include <array>
#include <cstdint>
using cruft::crypto::hash::blake;
using cruft::crypto::hash::traits;
///////////////////////////////////////////////////////////////////////////////
const std::array<traits<256>::word_t,8>
traits<256>::iv
{
0x6A09E667, // frac(sqrt( 2))
0xBB67AE85, // frac(sqrt( 3))
0x3C6EF372, // frac(sqrt( 5))
0xA54FF53A, // frac(sqrt( 7))
0x510E527F, // frac(sqrt(11))
0x9B05688C, // frac(sqrt(13))
0x1F83D9AB, // frac(sqrt(17))
0x5BE0CD19, // frac(sqrt(19))
};
//-----------------------------------------------------------------------------
const std::array<traits<256>::word_t,16>
traits<256>::pi
{
0x243F6A88,
0x85A308D3,
0x13198A2E,
0x03707344,
0xA4093822,
0x299F31D0,
0x082EFA98,
0xEC4E6C89,
0x452821E6,
0x38D01377,
0xBE5466CF,
0x34E90C6C,
0xC0AC29B7,
0xC97C50DD,
0x3F84D5B5,
0xB5470917,
};
//-----------------------------------------------------------------------------
const std::array<int,4>
traits<256>::rotations {
16, 12, 8, 7
};
///////////////////////////////////////////////////////////////////////////////
const std::array<traits<512>::word_t,8>
traits<512>::iv {
0x6A09E667F3BCC908,
0xBB67AE8584CAA73B,
0x3C6EF372FE94F82B,
0xA54FF53A5F1D36F1,
0x510E527FADE682D1,
0x9B05688C2B3E6C1F,
0x1F83D9ABFB41BD6B,
0x5BE0CD19137E2179,
};
//-----------------------------------------------------------------------------
const std::array<traits<512>::word_t,16>
traits<512>::pi {
0x243F6A8885A308D3,
0x13198A2E03707344,
0xA4093822299F31D0,
0x082EFA98EC4E6C89,
0x452821E638D01377,
0xBE5466CF34E90C6C,
0xC0AC29B7C97C50DD,
0x3F84D5B5B5470917,
0x9216D5D98979FB1B,
0xD1310BA698DFB5AC,
0x2FFD72DBD01ADFB7,
0xB8E1AFED6A267E96,
0xBA7C9045F12C7F99,
0x24A19947B3916CF7,
0x0801F2E2858EFC16,
0x636920D871574E69,
};
//-----------------------------------------------------------------------------
const std::array<int,4> traits<512>::rotations { 32, 25, 16, 11 };
///////////////////////////////////////////////////////////////////////////////
// the last six rows are repeats of the first two rows. this allows us to cut
// out a pretty frequent modulus operation.
static constexpr
int
permute[16][16] = {
{ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, },
{ 14, 10, 4, 8, 9, 15, 13, 6, 1, 12, 0, 2, 11, 7, 5, 3, },
{ 11, 8, 12, 0, 5, 2, 15, 13, 10, 14, 3, 6, 7, 1, 9, 4, },
{ 7, 9, 3, 1, 13, 12, 11, 14, 2, 6, 5, 10, 4, 0, 15, 8, },
{ 9, 0, 5, 7, 2, 4, 10, 15, 14, 1, 11, 12, 6, 8, 3, 13, },
{ 2, 12, 6, 10, 0, 11, 8, 3, 4, 13, 7, 5, 15, 14, 1, 9, },
{ 12, 5, 1, 15, 14, 13, 4, 10, 0, 7, 6, 3, 9, 2, 8, 11, },
{ 13, 11, 7, 14, 12, 1, 3, 9, 5, 0, 15, 4, 8, 6, 2, 10, },
{ 6, 15, 14, 9, 11, 3, 0, 8, 12, 2, 13, 7, 1, 4, 10, 5, },
{ 10, 2, 8, 4, 7, 6, 1, 5, 15, 11, 9, 14, 3, 12, 13, 0, },
{ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, },
{ 14, 10, 4, 8, 9, 15, 13, 6, 1, 12, 0, 2, 11, 7, 5, 3, },
{ 11, 8, 12, 0, 5, 2, 15, 13, 10, 14, 3, 6, 7, 1, 9, 4, },
{ 7, 9, 3, 1, 13, 12, 11, 14, 2, 6, 5, 10, 4, 0, 15, 8, },
{ 9, 0, 5, 7, 2, 4, 10, 15, 14, 1, 11, 12, 6, 8, 3, 13, },
{ 2, 12, 6, 10, 0, 11, 8, 3, 4, 13, 7, 5, 15, 14, 1, 9, },
};
///////////////////////////////////////////////////////////////////////////////
template <int width>
void
G (int i,
int r,
typename traits<width>::word_t &a,
typename traits<width>::word_t &b,
typename traits<width>::word_t &c,
typename traits<width>::word_t &d,
const typename traits<width>::word_t m[]
) {
const auto j = permute[r][2 * i ];
const auto k = permute[r][2 * i + 1];
a = a + b + (m[j] ^ traits<width>::pi[k]);
d = util::rotater (d ^ a, traits<width>::rotations[0]);
c = c + d;
b = util::rotater (b ^ c, traits<width>::rotations[1]);
a = a + b + (m[k] ^ traits<width>::pi[j]);
d = util::rotater (d ^ a, traits<width>::rotations[2]);
c = c + d;
b = util::rotater (b ^ c, traits<width>::rotations[3]);
}
///////////////////////////////////////////////////////////////////////////////
template <int width>
std::array<typename traits<width>::word_t,8>
compress (
std::array<typename traits<width>::word_t,8> h,
const typename traits<width>::word_t m[16],
const std::array<typename traits<width>::word_t,4> s,
uint64_t t
) {
typename traits<width>::word_t t0 = t & 0xffffffff;
typename traits<width>::word_t t1 = (t >> 32u) & 0xffffffff;
typename traits<width>::word_t v[16] = {
h[0], h[1], h[2], h[3],
h[4], h[5], h[6], h[7],
s[0] ^ traits<width>::pi[0],
s[1] ^ traits<width>::pi[1],
s[2] ^ traits<width>::pi[2],
s[3] ^ traits<width>::pi[3],
t0 ^ traits<width>::pi[4],
t0 ^ traits<width>::pi[5],
t1 ^ traits<width>::pi[6],
t1 ^ traits<width>::pi[7],
};
for (int r = 0; r < traits<width>::rounds; ++r) {
G<width> (0, r, v[ 0], v[ 4], v[ 8], v[12], m);
G<width> (1, r, v[ 1], v[ 5], v[ 9], v[13], m);
G<width> (2, r, v[ 2], v[ 6], v[10], v[14], m);
G<width> (3, r, v[ 3], v[ 7], v[11], v[15], m);
G<width> (4, r, v[ 0], v[ 5], v[10], v[15], m);
G<width> (5, r, v[ 1], v[ 6], v[11], v[12], m);
G<width> (6, r, v[ 2], v[ 7], v[ 8], v[13], m);
G<width> (7, r, v[ 3], v[ 4], v[ 9], v[14], m);
}
for (int i = 0; i < 8; ++i)
h[i] = h[i] ^ s[i % 4] ^ v[i] ^ v[8 + i];
return h;
}
///////////////////////////////////////////////////////////////////////////////
template <int width>
typename blake<width>::digest_t
blake<width>::operator() (
util::view<const uint8_t *> data,
const std::array<typename traits<width>::word_t, 4> salt
) const noexcept {
auto h = traits<width>::iv;
// bounce the message data through d08/dw so we can perform endian
// conversion.
//
// however: this should probably be done in the compression function
// instead, because it may be possible to optimise that implementation
// more than simple calls to hton would allow.
union {
word_t dw[16];
uint8_t d08[16*sizeof(word_t)];
};
uint64_t t = 0;
auto cursor = data.cbegin ();
// perform the simple case where we're consuming whole blocks
for (auto last = data.cend ();
(unsigned)(last - cursor) >= sizeof (dw);
cursor += sizeof (dw))
{
t+= BLOCK_SIZE;
memcpy (d08, cursor, sizeof (d08));
std::transform (
std::cbegin (dw),
std::cend (dw),
std::begin (dw),
util::ntoh<word_t>
);
h = compress<width> (h, dw, salt, t);
}
// perform the messsage padding.
//
// * drain the buffer. this is guaranteed to fit into the bounce buffer.
// * always append a 1 bit
// * append enough 0 bits to give block_size-8 bytes
// * set the last bit as 1
// * append the two halves of the timer
// * hash again
//
// if we need more space for padding then rehash
// if at any point no message bits contributed then pass a zero counter
{
auto tail = std::copy (cursor, data.cend (), d08);
t += (data.cend () - cursor) * 8;
*tail = 0x80;
bool empty = cursor == data.cend ();
const auto last = std::end (d08) - 8 - 1;
// we're _just_ within the space limits. set the high bit in place.
if (tail == last) {
*tail++ |= 0x01;
// we're going to overflow
} else if (tail > last) {
std::fill (tail + 1, std::end (d08), 0);
std::transform (
std::cbegin (dw),
std::cend (dw),
std::begin (dw),
util::ntoh<word_t>
);
h = compress<width> (h, dw, salt, t);
empty = true;
tail = last;
std::fill (std::begin (d08), tail, 0);
*tail++ = 0x01;
// the simple case of appending zeros and a one
} else {
std::fill (tail+1, last, 0);
tail = last;
*tail++ = 0x01;
}
dw[14] = t>>32;
dw[15] = t&0xffffffff;
std::transform (
std::cbegin (dw),
std::cend (dw) - 2,
std::begin (dw),
util::ntoh<word_t>
);
h = compress<width> (h, dw, salt, empty ? 0 : t);
}
std::transform (std::cbegin (h), std::cend (h), std::begin (h), util::hton<word_t>);
digest_t d;
memcpy (d.data (), h.data (), sizeof (d));
return d;
}
///////////////////////////////////////////////////////////////////////////////
template class cruft::crypto::hash::blake<256>;
template class cruft::crypto::hash::blake<512>;

79
hash/blake.hpp Normal file
View File

@ -0,0 +1,79 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#ifndef CRUFT_CRYPTO_HASH_BLAKE_HPP
#define CRUFT_CRYPTO_HASH_BLAKE_HPP
#include <cruft/util/view.hpp>
#include <array>
#include <cstdint>
#include <cstdlib>
///////////////////////////////////////////////////////////////////////////////
namespace cruft::crypto::hash {
///////////////////////////////////////////////////////////////////////////
template <int>
struct traits {};
//-------------------------------------------------------------------------
template <>
struct traits<256>
{
using word_t = uint32_t;
static const std::array<word_t,8> iv;
static const std::array<word_t,16> pi;
static const std::array<int,4> rotations;
static constexpr int rounds = 14;
};
//-------------------------------------------------------------------------
template <>
struct traits<512>
{
using word_t = uint64_t;
static const std::array<word_t,8> iv;
static const std::array<word_t,16> pi;
static const std::array<int,4> rotations;
static constexpr int rounds = 16;
};
template <int width>
class blake {
public:
using word_t = typename traits<width>::word_t;
using digest_t = std::array<uint8_t,32>;
static const size_t BLOCK_SIZE = 512;
static const size_t DIGEST_SIZE = sizeof (digest_t);
digest_t operator() (util::view<const uint8_t*> data,
const std::array<word_t,4> salt) const noexcept;
digest_t operator() (util::view<const uint8_t*> data) const noexcept
{
return (*this) (data, {0,0,0,0});
}
};
}
#endif

187
hash/blake2.cpp Normal file
View File

@ -0,0 +1,187 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#include "blake2.hpp"
#include <cruft/util/bitwise.hpp>
#include <cruft/util/debug.hpp>
#include <cruft/util/endian.hpp>
#include <cruft/util/types.hpp>
using cruft::crypto::hash::blake2;
///////////////////////////////////////////////////////////////////////////////
// blake2b: uint64_t
struct traits {
static constexpr int word_bits = 64;
using word_t = typename util::bits_type<word_bits>::uint;
static constexpr int F_rounds = 12;
static constexpr int block_bytes = 128; // bb
static constexpr int max_hash_bytes = 64; // nn
static constexpr int max_key_bytes = 64; // kk
//static constexpr int max_input_bytes = 2**128; // ll
static constexpr int rotations[4] = { 32, 24, 16, 63 };
static constexpr
std::array<word_t,8> iv {
0x6A09E667F3BCC908, 0xBB67AE8584CAA73B,
0x3C6EF372FE94F82B, 0xA54FF53A5F1D36F1,
0x510E527FADE682D1, 0x9B05688C2B3E6C1F,
0x1F83D9ABFB41BD6B, 0x5BE0CD19137E2179
};
};
using word_t = traits::word_t;
static constexpr
int
sigma[12][16] {
{ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, },
{ 14, 10, 4, 8, 9, 15, 13, 6, 1, 12, 0, 2, 11, 7, 5, 3, },
{ 11, 8, 12, 0, 5, 2, 15, 13, 10, 14, 3, 6, 7, 1, 9, 4, },
{ 7, 9, 3, 1, 13, 12, 11, 14, 2, 6, 5, 10, 4, 0, 15, 8, },
{ 9, 0, 5, 7, 2, 4, 10, 15, 14, 1, 11, 12, 6, 8, 3, 13, },
{ 2, 12, 6, 10, 0, 11, 8, 3, 4, 13, 7, 5, 15, 14, 1, 9, },
{ 12, 5, 1, 15, 14, 13, 4, 10, 0, 7, 6, 3, 9, 2, 8, 11, },
{ 13, 11, 7, 14, 12, 1, 3, 9, 5, 0, 15, 4, 8, 6, 2, 10, },
{ 6, 15, 14, 9, 11, 3, 0, 8, 12, 2, 13, 7, 1, 4, 10, 5, },
{ 10, 2, 8, 4, 7, 6, 1, 5, 15, 11, 9, 14, 3, 12, 13, 0, },
{ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, },
{ 14, 10, 4, 8, 9, 15, 13, 6, 1, 12, 0, 2, 11, 7, 5, 3, },
};
///////////////////////////////////////////////////////////////////////////////
// mixing function
static constexpr
void
G (std::array<word_t,16> &v, int a, int b, int c, int d, word_t x, word_t y)
{
v[a] = v[a] + v[b] + x;
v[d] = util::rotater (v[d] ^ v[a], traits::rotations[0]);
v[c] = v[c] + v[d];
v[b] = util::rotater (v[b] ^ v[c], traits::rotations[1]);
v[a] = v[a] + v[b] + y;
v[d] = util::rotater (v[d] ^ v[a], traits::rotations[2]);
v[c] = v[c] + v[d];
v[b] = util::rotater (v[b] ^ v[c], traits::rotations[3]);
}
//-----------------------------------------------------------------------------
// compression function
std::array<word_t,8>
F (std::array<word_t,8> h, const word_t m[16], uint64_t t, bool f)
{
std::array<word_t,16> v {
h[0], h[1], h[2], h[3],
h[4], h[5], h[6], h[7],
traits::iv[0], traits::iv[1],
traits::iv[2], traits::iv[3],
traits::iv[4], traits::iv[5],
traits::iv[6], traits::iv[7],
};
v[12] ^= t;
v[13] ^= 0;
if (f)
v[14] ^= ~0;
for (int i = 0; i < traits::F_rounds; ++i) {
const auto *s = sigma[i];
G (v, 0, 4, 8, 12, m[s[ 0]], m[s[ 1]]);
G (v, 1, 5, 9, 13, m[s[ 2]], m[s[ 3]]);
G (v, 2, 6, 10, 14, m[s[ 4]], m[s[ 5]]);
G (v, 3, 7, 11, 15, m[s[ 6]], m[s[ 7]]);
G (v, 0, 5, 10, 15, m[s[ 8]], m[s[ 9]]);
G (v, 1, 6, 11, 12, m[s[10]], m[s[11]]);
G (v, 2, 7, 8, 13, m[s[12]], m[s[13]]);
G (v, 3, 4, 9, 14, m[s[14]], m[s[15]]);
}
for (int i = 0; i < 8; ++i)
h[i] ^= v[i] ^ v[i + 8];
return h;
}
///////////////////////////////////////////////////////////////////////////////
blake2::blake2 () noexcept:
blake2 (util::view<const uint8_t*>{nullptr})
{ ; }
//-----------------------------------------------------------------------------
blake2::blake2 (util::view<const uint8_t *> key)
{
// don't give the user flexibility to provide too much key
if (key.size () > traits::max_key_bytes)
throw std::invalid_argument ("key is too large");
std::fill (m_salt.begin (), m_salt.end (), 0);
memcpy (m_salt.data (), key.data (), key.size ());
m_keylen = key.size ();
}
//-----------------------------------------------------------------------------
blake2::digest_t
blake2::operator() (util::view<const uint8_t *> data) const noexcept
{
auto h = traits::iv;
h[0] ^= 0x01010000 ^ (m_keylen << 8) ^ sizeof (digest_t);
if (m_keylen)
h = F (h, reinterpret_cast<const word_t*> (m_salt.data ()), traits::block_bytes, data.empty ());
// special case for the empty key and empty data
if (!m_keylen && data.empty ()) {
std::array<word_t,16> zeroes {};
h = F (h, zeroes.data (), 0, true);
}
uint64_t counter = m_keylen?traits::block_bytes:0;
auto cursor = data.begin ();
while (cursor + traits::block_bytes < data.end ()) {
counter += traits::block_bytes;
h = F (h, reinterpret_cast<const word_t*> (cursor), counter, false);
cursor += traits::block_bytes;
}
if (cursor != data.cend ()) {
std::array<uint64_t,16> tail {};
memcpy (tail.data(), data.data (), data.cend () - cursor);
counter += data.end () - cursor;
h = F (h, tail.data (), counter, true);
}
digest_t d;
memcpy (&d, h.data (), sizeof (d));
return d;
}

50
hash/blake2.hpp Normal file
View File

@ -0,0 +1,50 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#ifndef CRUFT_CRYPTO_HASH_BLAKE2_HPP
#define CRUFT_CRYPTO_HASH_BLAKE2_HPP
#include <cruft/util/view.hpp>
#include <array>
namespace cruft::crypto::hash {
// RFC7693: The BLAKE2 Cryptographic Hash and Message Authentication Code
class blake2 {
public:
using salt_t = std::array<uint8_t,64>;
using digest_t = std::array<uint8_t,64>;
blake2 () noexcept;
blake2 (const salt_t&) noexcept;
blake2 (util::view<const uint8_t*> key);
digest_t operator() (util::view<const uint8_t*>) const noexcept;
private:
using state_t = std::array<uint64_t,8>;
// we store zero padded salt because it simplifies later state
// updates, not because it's a functional requirement. either way we
// need to copy at least 64 bytes, so the user shouldn't be copying
// these too much regardless.
std::array<uint8_t,128> m_salt;
uint64_t m_keylen;
};
};
#endif

37
hash/md6.cpp Normal file
View File

@ -0,0 +1,37 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#include "md6.hpp"
using cruft::crypto::hash::MD6;
///////////////////////////////////////////////////////////////////////////////
#if 0
MD6::digest_t
MD6::operator() (util::view<const uint8_t*> data) const noexcept
{
static constexpr int rounds = 40 + digest_size / 4;
static constexpr int mode_control = 64;
static constexpr int key_size = 0;
static_assert (key_size >= 0 && key_size <= 64);
static_assert (mode_control >= 0 && mode_control <= 64);
digest_t d;
return d;
};
#endif

36
hash/md6.hpp Normal file
View File

@ -0,0 +1,36 @@
/*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*
* Copyright 2018 Danny Robson <danny@nerdcruft.net>
*/
#ifndef CRUFT_CRYPTO_HASH_MD6_HPP
#define CRUFT_CRYPTO_HASH_MD6_HPP
#include <cruft/util/view.hpp>
#include <array>
namespace cruft::crypto::hash {
class MD6 {
public:
static constexpr int digest_size = 256;
using digest_t = std::array<uint8_t,digest_size/8>;
digest_t operator() (util::view<const uint8_t*> data) const noexcept;
};
};
#endif

0
hash/pbkdf2.cpp Normal file
View File

74
hash/pbkdf2.hpp Normal file
View File

@ -0,0 +1,74 @@
#include <cstdint>
// rfc2898
auto F (func (auto,auto), password, salt, iterators, index)
{
auto aux = f (password, salt || htob<uint32_t> (index));
for (int i = 0; i < iterations; ++i) {
aux ^= f (password, aux);
}
return aux;
}
auto
pbkdf2 (func (auto,auto), password, salt, iterations, output_length)
{
vector out = {};
for (int i = 0; out < dklen; ++i)
out += F (func, password, salt, iterators, i);
return out.trunc (output_length);
}
// WPA = PBKDF2(HMAC-SHA1, passphrase, ssid, 4096, 256);
// rfc6070: test vectors
static const struct {
const char *password;
const char *salt;
int iterations;
int size;
std::vector<uint8_t> output;
} TESTS[] = {
{
.password = "password",
.salt = "salt",
.iterations = 1,
.size = 20,
.output = { 0x0c, 0x60, 0xc8, 0x0f, 0x96, 0x1f, 0x0e, 0x71, 0xf3, 0xa9, 0xb5, 0x24, 0xaf, 0x60, 0x12, 0x06, 0x2f, 0xe0, 0x37, 0xa6 }
}, {
.password = "password",
.salt = "salt",
.iterations = 2,
.size = 20,
.output = { 0xea, 0x6c, 0x01, 0x4d, 0xc7, 0x2d, 0x6f, 0x8c, 0xcd, 0x1e, 0xd9, 0x2a, 0xce, 0x1d, 0x41, 0xf0, 0xd8, 0xde, 0x89, 0x57 },
}, {
.password = "password",
.salt = "salt",
.iterations = 4096,
.size = 20,
.output = { 0x4b, 0x00, 0x79, 0x01, 0xb7, 0x65, 0x48, 0x9a, 0xbe, 0xad, 0x49, 0xd9, 0x26, 0xf7, 0x21, 0xd0, 0x65, 0xa4, 0x29, 0xc1 },
}, {
.password = "password",
.salt = "salt",
.iterations = 16777216,
.size = 20,
.output = { 0xee, 0xfe, 0x3d, 0x61, 0xcd, 0x4d, 0xa4, 0xe4, 0xe9, 0x94, 0x5b, 0x3d, 0x6b, 0xa2, 0x15, 0x8c, 0x26, 0x34, 0xe9, 0x84 },
}, }
.password = "passwordPASSWORDpassword",
.salt = "saltSALTsaltSALTsaltSALTsaltSALTsalt",
.iterations = 4096,
.size = 25,
.output = { 0x3d, 0x2e, 0xec, 0x4f, 0xe4, 0x1c, 0x84, 0x9b, 0x80, 0xc8, 0xd8, 0x36, 0x62, 0xc0, 0xe4, 0x4a, 0x8b, 0x29, 0x1a, 0x96, 0x4c, 0xf2, 0xf0, 0x70, 0x38 },
}, {
.password = "pass\0word",
.salt = "sa\0lt",
.iterations = 4096,
.size = 16,
.output = { 0x56, 0xfa, 0x6a, 0xa7, 0x55, 0x48, 0x09, 0x9d, 0xcc, 0x37, 0xd7, 0xf0, 0x34, 0x25, 0xe0, 0xc3 },
}
};

View File

@ -396,7 +396,7 @@ RIPEMD::operator() (const util::view<const uint8_t*> data)
size_t offset = sizeof(d08) - remaining; size_t offset = sizeof(d08) - remaining;
std::copy_n (d08 + offset, remaining, m_buffer.d08 + offset); std::copy_n (d08 + offset, remaining, m_buffer.d08 + offset);
m_length += remaining; //m_length += remaining;
m_buffer.size += remaining; m_buffer.size += remaining;
transform (m_state, m_buffer.d32); transform (m_state, m_buffer.d32);
m_buffer.size = 0; m_buffer.size = 0;

33
stream/chacha.cpp Normal file
View File

@ -0,0 +1,33 @@
#if 0
#include <cstdint>
uint32_t R(a,b,c,k)
{
b += c;
a ^= b;
return rotatel (a, k);
}
void quarter (a, b, c, d)
{
a += b; d ^= a; rotatel (d, 16);
c += d; b ^= c; rotatel (b, 12);
a += b; d ^= a; rotatel (d, 8);
c += d; b ^= c; rotatel (b, 7);
}
void double_round ()
{
QR (0, 4, 8, 12)
QR (1, 5, 9, 13)
QR (2, 6, 10, 14)
QR (3, 7, 11, 15)
QR (0, 5, 10, 15)
QR (1, 6, 11, 12)
QR (2, 7, 8, 13)
QR (3, 4, 9, 14)
}
#endif

0
stream/chacha.hpp Normal file
View File

102
stream/rabbit.cpp Normal file
View File

@ -0,0 +1,102 @@
#if 0
#include <cstdint>
// rabbit, rfc4503
struct state {
state () {
// key setup
for (int j = 0; j < 8; ++j) {
if (j % 2 == 0) {
X[j] = K[(j + 1) % 8] << 16 | K[j];
C[j] = K[(j + 4) % 8] << 16 | K[(j + 5) % 8];
} else {
X[j] = K[(j + 5) % 8] << 16 | K[(j+4) % 8];
C[j] = K[j] << 16 | K[(j+1) % 8];
}
}
for (int i = 0; i < 4; ++i) {
update_counter ();
next_state ();
}
for (int j = 0; j < 8; ++j)
C[j] = C[j] ^ X[(j+4) % 8];
// iv setup, optional? uint16_t IV[4];
// 15...0: 0
// 31..16: 1
// 47..32: 2
// 63..48: 3
C[0] = C[0] ^ cat(IV[1], IV[0]);
C[1] = C[1] ^ cat(IV[3], IV[1]);
C[2] = C[2] ^ cat(IV[3], IV[2]);
C[3] = C[3] ^ cat(IV[2], IV[0]);
C[4] = C[4] ^ cat(IV[1], IV[0]);
C[5] = C[5] ^ cat(IV[3], IV[1]);
C[6] = C[6] ^ cat(IV[3], IV[2]);
C[7] = C[7] ^ cat(IV[2], IV[0]);
}
void update_counter (void) {
A[0] = 0x4D34D34D;
A[1] = 0xD34D34D3;
A[2] = 0x34D34D34;
A[3] = 0x4D34D34D;
A[4] = 0xD34D34D3;
A[5] = 0x34D34D34;
A[6] = 0x4D34D34D;
A[7] = 0xD34D34D3;
for (int j = 0; j < 8; ++j) {
uint32_t temp = C[j] + A[j] + b;
b = temp / WORDSIZE;
C[j] = temp % WORDSIZE;
}
}
auto square (auto v) { return (v % WORDSIZE) * (v % WORDSIZE); }
auto g (auto u, auto v) {
return LSW (square (u+v) ^ MSW (square (u+v)));
}
void next_state (void) {
for (int j = 0; j < 8; ++j)
G[j] = g(X[j], C[j]);
X[0] = G[0] + rotatel (G[7], 16) + rotatel (G[6], 16) % WORDSIZE;
X[1] = G[1] + rotatel (G[0], 8) + G[7] % WORDSIZE;
X[2] = G[2] + rotatel (G[1], 16) + rotatel (G[0], 16) % WORDSIZE;
X[3] = G[3] + rotatel (G[2], 8) + G[1] % WORDSIZE;
X[4] = G[4] + rotatel (G[3], 16) + rotatel (G[2], 16) % WORDSIZE;
X[5] = G[5] + rotatel (G[4], 8) + G[3] % WORDSIZE;
X[6] = G[6] + rotatel (G[5], 16) + rotatel (G[4], 16) % WORDSIZE;
X[7] = G[7] + rotatel (G[6], 8) + G[5] % WORDSIZE;
}
void extract (uint16_t S[8])
{
S[0] = LO(X[0]) ^ HI(X[5]);
S[1] = HI(X[0]) ^ LO(X[3]);
S[2] = LO(X[2]) ^ HI(X[7]);
S[3] = HI(X[2]) ^ LO(X[5]);
S[4] = LO(X[4]) ^ HI(X[1]);
S[5] = HI(X[4]) ^ LO(X[7]);
S[6] = LO(X[6]) ^ HI(X[3]);
S[7] = HI(X[6]) ^ LO(X[1]);
}
uint32_t X[8]; // state
uint32_t C[8]; // counter
uint32_t b = 0; // carry bit
};
struct key {
uint16_t k[8];
};
#endif

0
stream/rabbit.hpp Normal file
View File

307
stream/rc5.cpp Normal file
View File

@ -0,0 +1,307 @@
#if 0
#include <cstdint>
// rfc2040
// w: word_size (in bits)
// u: word_size (in bytes)
// b: key_length (in bytes)
// K[]: key
// c: key_length (in words), or 1 if b==0
// L[]: schedule_temp
// r: rounds
// t: 2(r+1) round_subkeys
// S[]: subkey_words
// P_w: 1st magic, Odd((e-2)*2**w)
// w=16 -> 0xb7e1
// w=32 -> 0xb7e15163
// w=64 -> 0xB7E151628AED2A6B
// Q_w: 2nd magic, Odd((phi-1)*2**w)
// w=64 -> 0x9E3779B97F4A7C15
std::array<word_t,t>
generate_subkeys ()
{
std::array<word_t,t> S;
auto c = ceil (max (b, 1) / u);
for (int i = b - 1; i >= 0; --i)
L[i/u] = (L[i/u] << u) + K[i];
S[0] = P_w;
for (int i = 1; i < S.size (); ++i)
S[i] = S[i-1] + Q_w;
int i = 0;
int j = 0;
int A = 0;
int B = 0;
for (int times = 3*max (t, c); times; --times) {
A = S[i] = (S[i] + A + B) <<< 3;
B = L[j] = (L[j] + A + B) <<< (A + B);
i = (i + 1) % t;
j = (j + 1) % t;
}
return S;
}
word_t[2]
encrypt (word_t A, word_t B)
{
A += S[0];
B += S[1];
for (int i = 1; i <= r; ++i) {
A = ((A ^ B) <<< B) + S[2 * i];
B = ((B ^ A) <<< A) + S[2 * i + 1];
}
return {A,B};
}
word_t[2]
decrypt (word_t A, word_t B)
{
for (int i = r; r > 0; --i) {
B = ((B - S[2*i+1]) >>> A) ^ A;
A = ((A - S[2*i ]) >>> B) ^ B;
}
return A, B;
}
// The RC5 Encryption Algorithm, Rivest '94
//
// key = 00.00 O0 O0 O0 O0 O0 O0 O0 O0 O0 O0 O0 O0 O0 O0
// plaintext 00000000 00000000
// ciphertext EEDBA521 6D8F4B15
//
// key = 91 5F 46 19 BE 41 B2 51 63 55 A5 01 10 A9 CE 91
// plaintext EEDBA521 6D8F4B15
// ciphertext ACI3COF7 52892B5B
//
// key = 78 33 48 E7 5A EB OF 2F D7 B1 69 BB 8D Ci 67 87
// plaintext ACI3COF7 52892B5B
// ciphertext B7B3422F 92FC6903
//
// key = DC 49 DB 13 75 A5 58 4F 64 85 B4 13 B5 FI 2B AF
// plaintext B7B3422F 92FC6903
// ciphertext B278C165 CC97D184
//
// key = 52 69 F1 49 D4 IB AO 15 24 97 57 4D 7F 15 31 25
// plaintext B278C165 CC97D184
// ciphertext 15E444EB 249831DA
// RC5_CBC
// R = 0
// Key = 00
// IV = 0000000000000000
// P = 0000000000000000
// C = 7a7bba4d79111d1e
//
// RC5_CBC
// R = 0
// Key = 00
// IV = 0000000000000000
// P = ffffffffffffffff
// C = 797bba4d78111d1e
//
// RC5_CBC
// R = 0
// Key = 00
// IV = 0000000000000001
// P = 0000000000000000
// C = 7a7bba4d79111d1f
//
// RC5_CBC
// R = 0
// Key = 00
// IV = 0000000000000000
// P = 0000000000000001
// C = 7a7bba4d79111d1f
//
// RC5_CBC
// R = 0
// Key = 00
// IV = 0102030405060708
// P = 1020304050607080
// C = 8b9ded91ce7794a6
//
// RC5_CBC
// R = 1
// Key = 11
// IV = 0000000000000000
// P = 0000000000000000
// C = 2f759fe7ad86a378
//
// RC5_CBC
// R = 2
// Key = 00
// IV = 0000000000000000
// P = 0000000000000000
// C = dca2694bf40e0788
//
// RC5_CBC
// R = 2
// Key = 00000000
// IV = 0000000000000000
// P = 0000000000000000
// C = dca2694bf40e0788
//
// RC5_CBC
// R = 8
// Key = 00
// IV = 0000000000000000
// P = 0000000000000000
// C = dcfe098577eca5ff
//
// RC5_CBC
// R = 8
// Key = 00
// IV = 0102030405060708
// P = 1020304050607080
// C = 9646fb77638f9ca8
//
// RC5_CBC
// R = 12
// Key = 00
// IV = 0102030405060708
// P = 1020304050607080
// C = b2b3209db6594da4
//
// RC5_CBC
// R = 16
// Key = 00
// IV = 0102030405060708
// P = 1020304050607080
// C = 545f7f32a5fc3836
//
// RC5_CBC
// R = 8
// Key = 01020304
// IV = 0000000000000000
// P = ffffffffffffffff
// C = 8285e7c1b5bc7402
//
// RC5_CBC
// R = 12
// Key = 01020304
// IV = 0000000000000000
// P = ffffffffffffffff
// C = fc586f92f7080934
//
// RC5_CBC
// R = 16
// Key = 01020304
// IV = 0000000000000000
// P = ffffffffffffffff
// C = cf270ef9717ff7c4
//
// RC5_CBC
// R = 12
// Key = 0102030405060708
// IV = 0000000000000000
// P = ffffffffffffffff
// C = e493f1c1bb4d6e8c
//
// RC5_CBC
// R = 8
// Key = 0102030405060708
// IV = 0102030405060708
// P = 1020304050607080
// C = 5c4c041e0f217ac3
//
// RC5_CBC
// R = 12
// Key = 0102030405060708
// IV = 0102030405060708
// P = 1020304050607080
// C = 921f12485373b4f7
//
// RC5_CBC
// R = 16
// Key = 0102030405060708
// IV = 0102030405060708
// P = 1020304050607080
// C = 5ba0ca6bbe7f5fad
//
// RC5_CBC
// R = 8
// Key = 01020304050607081020304050607080
// IV = 0102030405060708
// P = 1020304050607080
// C = c533771cd0110e63
//
// RC5_CBC
// R = 12
// Key = 01020304050607081020304050607080
// IV = 0102030405060708
// P = 1020304050607080
// C = 294ddb46b3278d60
//
// RC5_CBC
// R = 16
// Key = 01020304050607081020304050607080
// IV = 0102030405060708
// P = 1020304050607080
// C = dad6bda9dfe8f7e8
//
// RC5_CBC
// R = 12
// Key = 0102030405
// IV = 0000000000000000
// P = ffffffffffffffff
// C = 97e0787837ed317f
//
// RC5_CBC
// R = 8
// Key = 0102030405
// IV = 0000000000000000
// P = ffffffffffffffff
// C = 7875dbf6738c6478
//
// RC5_CBC
// R = 8
// Key = 0102030405
// IV = 7875dbf6738c6478
// P = 0808080808080808
// C = 8f34c3c681c99695
//
// RC5_CBC_Pad
// R = 8
// Key = 0102030405
// IV = 0000000000000000
// P = ffffffffffffffff
// C = 7875dbf6738c64788f34c3c681c99695
//
// RC5_CBC
// R = 8
// Key = 0102030405
// IV = 0000000000000000
// P = 0000000000000000
// C = 7cb3f1df34f94811
//
// RC5_CBC
// R = 8
// Key = 0102030405
// IV = 7cb3f1df34f94811
// P = 1122334455667701
// C = 7fd1a023a5bba217
//
// RC5_CBC_Pad
// R = 8
// Key = 0102030405
// IV = 0000000000000000
// P = ffffffffffffffff7875dbf6738c647811223344556677
// C = 7875dbf6738c64787cb3f1df34f948117fd1a023a5bba217
#endif

0
stream/rc5.hpp Normal file
View File

72
stream/rc6.cpp Normal file
View File

@ -0,0 +1,72 @@
#if 0
#include <cstdint>
word_t[4]
encrypt (word_t ABCD[4])
{
B += S[0];
D += S[1];
for (int i = 1; i <= r; ++i) {
t = (B * (2*B+1)) <<< lg w;
u = (D * (2*D+1)) <<< lg w;
A = ((A ^ t) <<< u) + S[2*i];
C = ((C ^ u) <<< t) + S[2*i+1];
A,B,C,D = B,C,D,A;
}
A += S[2*r+2];
A += S[2*r+2];
return ABCD;
}
word_t[4]
decrypt (word_t ABCD[4])
{
C -= S[2*r+3];
A -= S[2*r+2];
for (int i = r; i > 0; ++i) {
A,B,C,D = D,A,B,C;
u = (D*(2*D+1)) <<< lg w;
t = (B*(2*B+1)) <<< lg w;
C = ((C - S[2*i+1]) >>> t) ^ u;
A = ((A - S[2*i ]) >>> u) ^ t;
}
D -= S[1];
B -= S[0];
return ABCD;
}
// plaintext 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// user key 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// ciphertext 8f c3 a5 36 56 b1 f7 78 c1 29 df 4e 98 48 a4 1e
//
// plaintext 02 13 24 35 46 57 68 79 8a 9b ac bd ce df e0 f1
// user key 01 23 45 67 89 ab cd ef 01 12 23 34 45 56 67 78
// ciphertext 52 4e 19 2f 47 15 c6 23 1f 51 f6 36 7e a4 3f 18
//
// plaintext 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// user key 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// ciphertext 6c d6 1b cb 19 0b 30 38 4e 8a 3f 16 86 90 ae 82
//
// plaintext 02 13 24 35 46 57 68 79 8a 9b ac bd ce df e0 f1
// user key 01 23 45 67 89 ab cd ef 01 12 23 34 45 56 67 78 89 9a ab bc cd de ef f0
// ciphertext 68 83 29 d0 19 e5 05 04 1e 52 e9 2a f9 52 91 d4
//
// plaintext 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// user key 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
// ciphertext 8f 5f bd 05 10 d1 5f a8 93 fa 3f da 6e 85 7e c2
//
// plaintext 02 13 24 35 46 57 68 79 8a 9b ac bd ce df e0 f1
// user key 01 23 45 67 89 ab cd ef 01 12 23 34 45 56 67 78 89 9a ab bc cd de ef f0 10 32 54 76 98 ba dc fe
// ciphertext c8 24 18 16 f0 d7 e4 89 20 ad 16 a1 67 4e
#endif

0
stream/rc6.hpp Normal file
View File

View File

@ -57,10 +57,10 @@ namespace cruft::crypto::stream::salsa {
std::array<uint32_t,16> std::array<uint32_t,16>
row (const std::array<uint32_t,16> y) noexcept row (const std::array<uint32_t,16> y) noexcept
{ {
const auto [z00, z01, z02, z03] = quarter ({y[ 0], y[ 1], y[ 2], y[ 3]}); const auto &[z00, z01, z02, z03] = quarter ({y[ 0], y[ 1], y[ 2], y[ 3]});
const auto [z05, z06, z07, z04] = quarter ({y[ 5], y[ 6], y[ 7], y[ 4]}); const auto &[z05, z06, z07, z04] = quarter ({y[ 5], y[ 6], y[ 7], y[ 4]});
const auto [z10, z11, z08, z09] = quarter ({y[10], y[11], y[ 8], y[ 9]}); const auto &[z10, z11, z08, z09] = quarter ({y[10], y[11], y[ 8], y[ 9]});
const auto [z15, z12, z13, z14] = quarter ({y[15], y[12], y[13], y[14]}); const auto &[z15, z12, z13, z14] = quarter ({y[15], y[12], y[13], y[14]});
return { return {
z00, z01, z02, z03, z00, z01, z02, z03,
@ -76,10 +76,10 @@ namespace cruft::crypto::stream::salsa {
std::array<uint32_t,16> std::array<uint32_t,16>
col (const std::array<uint32_t,16> x) noexcept col (const std::array<uint32_t,16> x) noexcept
{ {
const auto [y00, y04, y08, y12] = quarter ({x[ 0], x[ 4], x[ 8], x[12]}); const auto &[y00, y04, y08, y12] = quarter ({x[ 0], x[ 4], x[ 8], x[12]});
const auto [y05, y09, y13, y01] = quarter ({x[ 5], x[ 9], x[13], x[ 1]}); const auto &[y05, y09, y13, y01] = quarter ({x[ 5], x[ 9], x[13], x[ 1]});
const auto [y10, y14, y02, y06] = quarter ({x[10], x[14], x[ 2], x[ 6]}); const auto &[y10, y14, y02, y06] = quarter ({x[10], x[14], x[ 2], x[ 6]});
const auto [y15, y03, y07, y11] = quarter ({x[15], x[ 3], x[ 7], x[11]}); const auto &[y15, y03, y07, y11] = quarter ({x[15], x[ 3], x[ 7], x[11]});
return { return {
y00, y01, y02, y03, y00, y01, y02, y03,

108
test/hash/blake.cpp Normal file
View File

@ -0,0 +1,108 @@
///////////////////////////////////////////////////////////////////////////////
#include "hash/blake.hpp"
#include <cruft/util/ascii.hpp>
#include <cruft/util/tap.hpp>
using cruft::crypto::hash::blake;
///////////////////////////////////////////////////////////////////////////////
static blake<256>::digest_t
operator"" _digest (const char *str, size_t len)
{
blake<256>::digest_t res;
for (size_t i = 0; i < len; i += 2)
res[i/2] = util::ascii::from_hex (str[i]) << 4 | util::ascii::from_hex (str[i+1]);
return res;
}
//-----------------------------------------------------------------------------
std::vector<uint8_t>
operator"" _u8s (const char *str, size_t len)
{
std::vector<uint8_t> res;
res.resize (len);
std::copy_n (str, len, std::begin (res));
return res;
}
///////////////////////////////////////////////////////////////////////////////
static const struct {
std::vector<uint8_t> data;
std::vector<uint8_t,16> salt;
blake<256>::digest_t digest;
const char *message;
} TESTS[] = {
{
{},
{},
"716f6e863f744b9ac22c97ec7b76ea5f"
"5908bc5b2f67c61510bfc4751384ea7a"_digest,
"empty, default salt"
}, {
{ 0x00 },
{ },
"0ce8d4ef4dd7cd8d62dfded9d4edb0a774ae6a41929a74da23109e8f11139c87"_digest,
"NIST 8 bit zeros, default salt",
}, {
"0123456789abcdef"_u8s,
{},
"9dc03986e7cc2973fd21f0c0c804922ef160313d3b4e52c187a1661c5e89877c"_digest,
"16 bytes, default salt"
}, {
"0123456789abcdef0123456789abcdef0123456789abcdef0123456"_u8s,
{},
"f58834fc24e109248d33194551a28852cd3d2d6ed4aba9ab3562bb5a97ce76e1"_digest,
"exactly pre-padding size, default salt"
}, {
std::vector<uint8_t> (576/8, 0),
{},
"d419bad32d504fb7d44d460c42c5593fe544fa4c135dec31e21bd9abdcc22d41"_digest,
"NIST 576 bit zeros, default salt",
}, {
"0123456789abcdef0123456789abcdef0123456789abcdef0123456789abcde"_u8s,
{ },
"c455dcfcf5c77950b92ff055e7e4f8139acac4cbd18dbed0b1383d95e4f1726c"_digest,
"almost block size, default salt"
}, {
"0123456789abcdef0123456789abcdef0123456789abcdef0123456789abcdef"_u8s,
{ },
"e25d021064a61d7af53cefaa0819bb6a351db1d760ed1f85fee671bc18ab7886"_digest,
"exactly block size, default salt",
},
};
//-----------------------------------------------------------------------------
// million 'a':
// 224: 738443f8093ae703ebe4fe991b4f00208701e2e7be1275fd1bd84ef1
// 256: 22be6de4aa4214c9403f10598f0a6b0e834570251a13bc27589437f7139a5d44
// 384: 22ccce05b0ac1ceda1b0b0dc0021e6a3957779260cd2fae8a21c3d5432ce204f1df2d62a00d8f505cae6e70e3be18701
// 512: e5d3ecf60cbf8ed8b44307ae6606f4c8eae0a602c2a393f529cf405a1384c791c3ce58f54838a76b89a6455e988d63f98222ea82bf26e11e970516fb7c62b41d
int
main ()
{
util::TAP::logger tap;
for (const auto &t: TESTS) {
blake<256> h256;
const auto d = h256 (t.data, t.salt);
tap.expect_eq (d, t.digest, "%s", t.message);
}
{
blake<256> h256;
std::vector<uint8_t> data (1'000'000, 'a');
tap.expect_eq (
h256 (data),
"22be6de4aa4214c9403f10598f0a6b0e834570251a13bc27589437f7139a5d44"_digest,
"million 'a', 256"
);
}
return tap.status ();
}

144
test/hash/blake2.cpp Normal file
View File

@ -0,0 +1,144 @@
#include <cruft/util/ascii.hpp>
#include <cruft/util/tap.hpp>
#include "hash/blake2.hpp"
using cruft::crypto::hash::blake2;
///////////////////////////////////////////////////////////////////////////////
static const struct {
std::vector<uint8_t> data;
std::vector<uint8_t> salt;
blake2::digest_t digest;
const char *message;
} TESTS2b[] = {
{
{},
{},
"786a02f742015903c6c6fd852552d272"
"912f4740e15847618a86e217f71f5419"
"d25e1031afee585313896444934eb04b"
"903a685b1448b755d56f701afe9be2ce"_hex2array,
"empty"
},
{
{},
"00"_hex2u8,
"aaf42280524929171e417e77be67f9ed"
"ec3a8461bbe7b5c2bd1d9a3d0928f1db"
"bd1f6600bb866b72f0e3b3e22282c145"
"f69873a3d250ddc43c423685d1247657"_hex2array,
"empty, 0x00 salt",
},
{
{},
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e"_hex2u8,
"e350b6f7642eea11bb1bd9c6393f9e89"
"a0d10f9e38a754ca5f61838117ba0dd9"
"6af3f3dbc092acc89e8a8390aee233f0"
"d2b0adf32f009073352264ba5d317f2d"_hex2array,
"empty, 63 byte salt",
},
{
{},
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e3f"_hex2u8,
"10ebb67700b1868efb4417987acf4690"
"ae9d972fb7a590c2f02871799aaa4786"
"b5e996e8f0f4eb981fc214b005f42d2f"
"f4233499391653df7aefcbc13fc51568"_hex2array,
"empty, 64 byte salt",
},
{
"00"_hex2u8,
{},
"2fa3f686df876995167e7c2e5d74c4c7"
"b6e48f8068fe0e44208344d480f7904c"
"36963e44115fe3eb2a3ac8694c28bcb4"
"f5a0f3276f2e79487d8219057a506e4b"_hex2array,
"0x00, no salt"
},
{
"000102"_hex2u8,
{},
"40a374727302d9a4769c17b5f409ff32"
"f58aa24ff122d7603e4fda1509e919d4"
"107a52c57570a6d94e50967aea573b11"
"f86f473f537565c66f7039830a85d186"_hex2array,
"0x000102, no salt"
},
{
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e"_hex2u8,
{},
"d10bf9a15b1c9fc8d41f89bb140bf0be"
"08d2f3666176d13baac4d381358ad074"
"c9d4748c300520eb026daeaea7c5b158"
"892fde4e8ec17dc998dcd507df26eb63"_hex2array,
"almost block size, no salt",
},
{
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e3f"_hex2u8,
{},
"2fc6e69fa26a89a5ed269092cb9b2a44"
"9a4409a7a44011eecad13d7c4b045660"
"2d402fa5844f1a7a758136ce3d5d8d0e"
"8b86921ffff4f692dd95bdc8e5ff0052"_hex2array,
"exactly block size, no salt"
},
{
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e3f"_hex2u8,
"000102030405060708090a0b0c0d0e0f"
"101112131415161718191a1b1c1d1e1f"
"202122232425262728292a2b2c2d2e2f"
"303132333435363738393a3b3c3d3e3f"_hex2u8,
"65676d800617972fbd87e4b9514e1c67"
"402b7a331096d3bfac22f1abb95374ab"
"c942f16e9ab0ead33b87c91968a6e509"
"e119ff07787b3ef483e1dcdccf6e3022"_hex2array,
"exactly block size, 64 byte salt"
},
};
//-----------------------------------------------------------------------------
int
main ()
{
util::TAP::logger tap;
for (const auto &t: TESTS2b) {
blake2 h (t.salt);
auto digest = h (t.data);
tap.expect_eq (digest, t.digest, "%s", t.message);
}
{
blake2 h;
const std::vector<uint8_t> million (1'000'000, 'a');
tap.expect_eq (
h (million),
"98fb3efb7206fd19ebf69b6f312cf7b6"
"4e3b94dbe1a17107913975a793f177e1"
"d077609d7fba363cbba00d05f7aa4e4f"
"a8715d6428104c0a75643b0ff3fd3eaf"_hex2array,
"million 'a'"
);
}
return tap.status ();
}

View File

@ -85,7 +85,7 @@ main (int, char**) {
std::vector<uint8_t> data (l); std::vector<uint8_t> data (l);
std::iota (std::begin (data), std::end (data), 0); std::iota (std::begin (data), std::end (data), 0);
util::view root {data}; util::view root {data};
auto [a,b] = root.split (root.begin () + l / 2); const auto &[a,b] = root.split (root.begin () + l / 2);
tap.expect_eq (h (a,b), h(root), "split data hash equality, %! bytes", l); tap.expect_eq (h (a,b), h(root), "split data hash equality, %! bytes", l);
}; };

3
test/hash/md6.cpp Normal file
View File

@ -0,0 +1,3 @@
#include "hash/md6.hpp"
int main () {}