Add support for Open Document Format 1.1

Contains a kernel for the ODF 1.1 encryption implemented in OpenOffice.
The algorithm uses a SHA-1 checksum, a PBKDF2-HMAC-SHA1 key derivation
with 1024 iterations and Blowfish-CFB encryption.

Valid hashes can be extracted with the libreoffice2john.py script,
available from the John the Ripper Jumbo repository at
https://github.com/magnumripper/JohnTheRipper/blob/bleeding-jumbo/run/libreoffice2john.py

You have to remove the filename suffix at the end of the hash before
passing it to hashcat. Also see 'hashcat -m18600 --example-hashes'.

You can leave the filename prefix if you use the --username option to
process those hashes.

 - Add hash-mode 18600 (Open Document Format (ODF) 1.1 (SHA-1, Blowfish))
 - Tests: add hash-mode 18600 (Open Document Format (ODF) 1.1 (SHA-1, Blowfish))
pull/1822/head
R. Yushaev 5 years ago
parent d6c04c2daf
commit b5a7e967c1

@ -1403,6 +1403,25 @@ typedef struct oldoffice34
} oldoffice34_t;
typedef struct odf11_tmp
{
u32 ipad[5];
u32 opad[5];
u32 dgst[5];
u32 out[5];
} odf11_tmp_t;
typedef struct odf11
{
u32 iterations;
u32 iv[2];
u32 checksum[5];
u32 encrypted_data[256];
} odf11_t;
typedef struct odf12_tmp
{
u32 ipad[5];

@ -0,0 +1,801 @@
/**
* Author......: See docs/credits.txt
* License.....: MIT
*/
#define NEW_SIMD_CODE
#include "inc_vendor.cl"
#include "inc_hash_constants.h"
#include "inc_hash_functions.cl"
#include "inc_types.cl"
#include "inc_common.cl"
#include "inc_simd.cl"
#include "inc_hash_sha1.cl"
#define COMPARE_S "inc_comp_single.cl"
#define COMPARE_M "inc_comp_multi.cl"
// http://www.schneier.com/code/constants.txt
__constant u32a c_sbox0[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
};
__constant u32a c_sbox1[256] =
{
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
};
__constant u32a c_sbox2[256] =
{
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
};
__constant u32a c_sbox3[256] =
{
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
};
__constant u32a c_pbox[18] =
{
0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
0x9216d5d9, 0x8979fb1b
};
#define BF_ROUND(L,R,N) \
{ \
uchar4 c = as_uchar4 ((L)); \
\
u32 tmp; \
\
tmp = S0[c.s3]; \
tmp += S1[c.s2]; \
tmp ^= S2[c.s1]; \
tmp += S3[c.s0]; \
\
(R) ^= tmp ^ P[(N)]; \
}
#define BF_ENCRYPT(L,R) \
{ \
L ^= P[0]; \
\
BF_ROUND (L, R, 1); \
BF_ROUND (R, L, 2); \
BF_ROUND (L, R, 3); \
BF_ROUND (R, L, 4); \
BF_ROUND (L, R, 5); \
BF_ROUND (R, L, 6); \
BF_ROUND (L, R, 7); \
BF_ROUND (R, L, 8); \
BF_ROUND (L, R, 9); \
BF_ROUND (R, L, 10); \
BF_ROUND (L, R, 11); \
BF_ROUND (R, L, 12); \
BF_ROUND (L, R, 13); \
BF_ROUND (R, L, 14); \
BF_ROUND (L, R, 15); \
BF_ROUND (R, L, 16); \
\
u32 tmp; \
\
tmp = R; \
R = L; \
L = tmp; \
\
L ^= P[17]; \
}
DECLSPEC void hmac_sha1_run_V (u32x *w0, u32x *w1, u32x *w2, u32x *w3, u32x *ipad, u32x *opad, u32x *digest)
{
digest[0] = ipad[0];
digest[1] = ipad[1];
digest[2] = ipad[2];
digest[3] = ipad[3];
digest[4] = ipad[4];
sha1_transform_vector (w0, w1, w2, w3, digest);
w0[0] = digest[0];
w0[1] = digest[1];
w0[2] = digest[2];
w0[3] = digest[3];
w1[0] = digest[4];
w1[1] = 0x80000000;
w1[2] = 0;
w1[3] = 0;
w2[0] = 0;
w2[1] = 0;
w2[2] = 0;
w2[3] = 0;
w3[0] = 0;
w3[1] = 0;
w3[2] = 0;
w3[3] = (64 + 20) * 8;
digest[0] = opad[0];
digest[1] = opad[1];
digest[2] = opad[2];
digest[3] = opad[3];
digest[4] = opad[4];
sha1_transform_vector (w0, w1, w2, w3, digest);
}
__kernel void m18600_init (KERN_ATTR_TMPS_ESALT (odf11_tmp_t, odf11_t))
{
/**
* base
*/
const u64 gid = get_global_id (0);
if (gid >= gid_max) return;
sha1_ctx_t sha1_ctx;
sha1_init (&sha1_ctx);
sha1_update_global_swap (&sha1_ctx, pws[gid].i, pws[gid].pw_len);
sha1_final (&sha1_ctx);
// hmac key = hashed passphrase
u32 k0[4];
u32 k1[4];
u32 k2[4];
u32 k3[4];
k0[0] = sha1_ctx.h[0];
k0[1] = sha1_ctx.h[1];
k0[2] = sha1_ctx.h[2];
k0[3] = sha1_ctx.h[3];
k1[0] = sha1_ctx.h[4];
k1[1] = 0;
k1[2] = 0;
k1[3] = 0;
k2[0] = 0;
k2[1] = 0;
k2[2] = 0;
k2[3] = 0;
k3[0] = 0;
k3[1] = 0;
k3[2] = 0;
k3[3] = 0;
// hmac message = salt
u32 m0[4];
u32 m1[4];
u32 m2[4];
u32 m3[4];
m0[0] = salt_bufs[digests_offset].salt_buf[0];
m0[1] = salt_bufs[digests_offset].salt_buf[1];
m0[2] = salt_bufs[digests_offset].salt_buf[2];
m0[3] = salt_bufs[digests_offset].salt_buf[3];
m1[0] = 0;
m1[1] = 0;
m1[2] = 0;
m1[3] = 0;
m2[0] = 0;
m2[1] = 0;
m2[2] = 0;
m2[3] = 0;
m3[0] = 0;
m3[1] = 0;
m3[2] = 0;
m3[3] = 0;
sha1_hmac_ctx_t sha1_hmac_ctx;
sha1_hmac_init_64 (&sha1_hmac_ctx, k0, k1, k2, k3);
tmps[gid].ipad[0] = sha1_hmac_ctx.ipad.h[0];
tmps[gid].ipad[1] = sha1_hmac_ctx.ipad.h[1];
tmps[gid].ipad[2] = sha1_hmac_ctx.ipad.h[2];
tmps[gid].ipad[3] = sha1_hmac_ctx.ipad.h[3];
tmps[gid].ipad[4] = sha1_hmac_ctx.ipad.h[4];
tmps[gid].opad[0] = sha1_hmac_ctx.opad.h[0];
tmps[gid].opad[1] = sha1_hmac_ctx.opad.h[1];
tmps[gid].opad[2] = sha1_hmac_ctx.opad.h[2];
tmps[gid].opad[3] = sha1_hmac_ctx.opad.h[3];
tmps[gid].opad[4] = sha1_hmac_ctx.opad.h[4];
// first pbkdf iteration
m1[0] = 1;
sha1_hmac_ctx_t sha1_hmac_ctx_loop = sha1_hmac_ctx;
sha1_hmac_update_64 (&sha1_hmac_ctx_loop, m0, m1, m2, m3, 20);
sha1_hmac_final (&sha1_hmac_ctx_loop);
tmps[gid].dgst[0] = sha1_hmac_ctx_loop.opad.h[0];
tmps[gid].dgst[1] = sha1_hmac_ctx_loop.opad.h[1];
tmps[gid].dgst[2] = sha1_hmac_ctx_loop.opad.h[2];
tmps[gid].dgst[3] = sha1_hmac_ctx_loop.opad.h[3];
tmps[gid].dgst[4] = sha1_hmac_ctx_loop.opad.h[4];
tmps[gid].out[0] = tmps[gid].dgst[0];
tmps[gid].out[1] = tmps[gid].dgst[1];
tmps[gid].out[2] = tmps[gid].dgst[2];
tmps[gid].out[3] = tmps[gid].dgst[3];
tmps[gid].out[4] = tmps[gid].dgst[4];
}
__kernel void m18600_loop (KERN_ATTR_TMPS_ESALT (odf11_tmp_t, odf11_t))
{
const u64 gid = get_global_id (0);
if ((gid * VECT_SIZE) >= gid_max) return;
u32x ipad[5];
u32x opad[5];
ipad[0] = packv (tmps, ipad, gid, 0);
ipad[1] = packv (tmps, ipad, gid, 1);
ipad[2] = packv (tmps, ipad, gid, 2);
ipad[3] = packv (tmps, ipad, gid, 3);
ipad[4] = packv (tmps, ipad, gid, 4);
opad[0] = packv (tmps, opad, gid, 0);
opad[1] = packv (tmps, opad, gid, 1);
opad[2] = packv (tmps, opad, gid, 2);
opad[3] = packv (tmps, opad, gid, 3);
opad[4] = packv (tmps, opad, gid, 4);
u32x dgst[5];
u32x out[5];
dgst[0] = packv (tmps, dgst, gid, 0);
dgst[1] = packv (tmps, dgst, gid, 1);
dgst[2] = packv (tmps, dgst, gid, 2);
dgst[3] = packv (tmps, dgst, gid, 3);
dgst[4] = packv (tmps, dgst, gid, 4);
out[0] = packv (tmps, out, gid, 0);
out[1] = packv (tmps, out, gid, 1);
out[2] = packv (tmps, out, gid, 2);
out[3] = packv (tmps, out, gid, 3);
out[4] = packv (tmps, out, gid, 4);
for (u32 j = 0; j < loop_cnt; j++)
{
u32x w0[4];
u32x w1[4];
u32x w2[4];
u32x w3[4];
w0[0] = dgst[0];
w0[1] = dgst[1];
w0[2] = dgst[2];
w0[3] = dgst[3];
w1[0] = dgst[4];
w1[1] = 0x80000000;
w1[2] = 0;
w1[3] = 0;
w2[0] = 0;
w2[1] = 0;
w2[2] = 0;
w2[3] = 0;
w3[0] = 0;
w3[1] = 0;
w3[2] = 0;
w3[3] = (64 + 20) * 8;
hmac_sha1_run_V (w0, w1, w2, w3, ipad, opad, dgst);
out[0] ^= dgst[0];
out[1] ^= dgst[1];
out[2] ^= dgst[2];
out[3] ^= dgst[3];
out[4] ^= dgst[4];
unpackv (tmps, dgst, gid, 0, dgst[0]);
unpackv (tmps, dgst, gid, 1, dgst[1]);
unpackv (tmps, dgst, gid, 2, dgst[2]);
unpackv (tmps, dgst, gid, 3, dgst[3]);
unpackv (tmps, dgst, gid, 4, dgst[4]);
unpackv (tmps, out, gid, 0, out[0]);
unpackv (tmps, out, gid, 1, out[1]);
unpackv (tmps, out, gid, 2, out[2]);
unpackv (tmps, out, gid, 3, out[3]);
unpackv (tmps, out, gid, 4, out[4]);
}
}
__kernel void __attribute__((reqd_work_group_size(8, 1, 1))) m18600_comp (KERN_ATTR_TMPS_ESALT (odf11_tmp_t, odf11_t))
{
const u64 gid = get_global_id (0);
const u64 lid = get_local_id (0);
const u64 lsz = get_local_size (0);
if (gid >= gid_max) return;
/**
* base
*/
u32 ukey[4];
ukey[0] = tmps[gid].out[0];
ukey[1] = tmps[gid].out[1];
ukey[2] = tmps[gid].out[2];
ukey[3] = tmps[gid].out[3];
/**
* blowfish setkey
*/
u32 P[18];
for (u32 i = 0; i < 18; i++)
{
P[i] = c_pbox[i] ^ ukey[i % 4];
}
__local u32 S0_all[8][256];
__local u32 S1_all[8][256];
__local u32 S2_all[8][256];
__local u32 S3_all[8][256];
__local u32 *S0 = S0_all[lid];
__local u32 *S1 = S1_all[lid];
__local u32 *S2 = S2_all[lid];
__local u32 *S3 = S3_all[lid];
for (u32 i = 0; i < 256; i++)
{
S0[i] = c_sbox0[i];
S1[i] = c_sbox1[i];
S2[i] = c_sbox2[i];
S3[i] = c_sbox3[i];
}
u32 L0 = 0;
u32 R0 = 0;
for (u32 i = 0; i < 18; i += 2)
{
BF_ENCRYPT (L0, R0);
P[i + 0] = L0;
P[i + 1] = R0;
}
for (u32 i = 0; i < 256; i += 4)
{
BF_ENCRYPT (L0, R0);
S0[i + 0] = L0;
S0[i + 1] = R0;
BF_ENCRYPT (L0, R0);
S0[i + 2] = L0;
S0[i + 3] = R0;
}
for (u32 i = 0; i < 256; i += 4)
{
BF_ENCRYPT (L0, R0);
S1[i + 0] = L0;
S1[i + 1] = R0;
BF_ENCRYPT (L0, R0);
S1[i + 2] = L0;
S1[i + 3] = R0;
}
for (u32 i = 0; i < 256; i += 4)
{
BF_ENCRYPT (L0, R0);
S2[i + 0] = L0;
S2[i + 1] = R0;
BF_ENCRYPT (L0, R0);
S2[i + 2] = L0;
S2[i + 3] = R0;
}
for (u32 i = 0; i < 256; i += 4)
{
BF_ENCRYPT (L0, R0);
S3[i + 0] = L0;
S3[i + 1] = R0;
BF_ENCRYPT (L0, R0);
S3[i + 2] = L0;
S3[i + 3] = R0;
}
__global const odf11_t *es = &esalt_bufs[digests_offset];
u32 ct[2];
u32 pt0[4];
u32 pt1[4];
u32 pt2[4];
u32 pt3[4];
u32 buf[2];
buf[0] = es->iv[0];
buf[1] = es->iv[1];
sha1_ctx_t sha1_ctx;
sha1_init (&sha1_ctx);
// decrypt blowfish-cfb and calculate plaintext checksum at the same time
for (int i = 0; i < 16; i++)
{
const int i16 = i * 16;
ct[0] = es->encrypted_data[i16 + 0];
ct[1] = es->encrypted_data[i16 + 1];
BF_ENCRYPT (buf[0], buf[1]);
pt0[0] = ct[0] ^ buf[0];
pt0[1] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 2];
ct[1] = es->encrypted_data[i16 + 3];
BF_ENCRYPT (buf[0], buf[1]);
pt0[2] = ct[0] ^ buf[0];
pt0[3] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 4];
ct[1] = es->encrypted_data[i16 + 5];
BF_ENCRYPT (buf[0], buf[1]);
pt1[0] = ct[0] ^ buf[0];
pt1[1] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 6];
ct[1] = es->encrypted_data[i16 + 7];
BF_ENCRYPT (buf[0], buf[1]);
pt1[2] = ct[0] ^ buf[0];
pt1[3] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 8];
ct[1] = es->encrypted_data[i16 + 9];
BF_ENCRYPT (buf[0], buf[1]);
pt2[0] = ct[0] ^ buf[0];
pt2[1] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 10];
ct[1] = es->encrypted_data[i16 + 11];
BF_ENCRYPT (buf[0], buf[1]);
pt2[2] = ct[0] ^ buf[0];
pt2[3] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 12];
ct[1] = es->encrypted_data[i16 + 13];
BF_ENCRYPT (buf[0], buf[1]);
pt3[0] = ct[0] ^ buf[0];
pt3[1] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
ct[0] = es->encrypted_data[i16 + 14];
ct[1] = es->encrypted_data[i16 + 15];
BF_ENCRYPT (buf[0], buf[1]);
pt3[2] = ct[0] ^ buf[0];
pt3[3] = ct[1] ^ buf[1];
buf[0] = ct[0];
buf[1] = ct[1];
sha1_update_64 (&sha1_ctx, pt0, pt1, pt2, pt3, 64);
}
sha1_final (&sha1_ctx);
const u32 r0 = sha1_ctx.h[0];
const u32 r1 = sha1_ctx.h[1];
const u32 r2 = sha1_ctx.h[2];
const u32 r3 = sha1_ctx.h[3];
#define il_pos 0
#include COMPARE_M
}

@ -6,6 +6,7 @@
- Added hash-mode 18400 (Open Document Format (ODF) 1.2 (SHA-256, AES))
- Added hash-mode 18500 sha1(md5(md5($pass)))
- Added hash-mode 18600 (Open Document Format (ODF) 1.1 (SHA-1, Blowfish))
##
## Bugs

@ -245,6 +245,7 @@ NVIDIA GPUs require "NVIDIA Driver" (367.x or later)
- PDF 1.7 Level 3 (Acrobat 9)
- PDF 1.7 Level 8 (Acrobat 10 - 11)
- Apple Secure Notes
- Open Document Format (ODF) 1.1 (SHA-1, Blowfish)
- Open Document Format (ODF) 1.2 (SHA-256, AES)
- Password Safe v2
- Password Safe v3

@ -176,7 +176,7 @@ _hashcat ()
{
local VERSION=5.1.0
local HASH_MODES="0 10 11 12 20 21 22 23 30 40 50 60 100 101 110 111 112 120 121 122 124 130 131 132 133 140 141 150 160 200 300 400 500 501 600 900 1000 1100 1400 1410 1411 1420 1421 1430 1440 1441 1450 1460 1500 1600 1700 1710 1711 1720 1722 1730 1731 1740 1750 1760 1800 2100 2400 2410 2500 2501 2600 2611 2612 2711 2811 3000 3100 3200 3710 3711 3800 3910 4010 4110 4300 4400 4500 4520 4521 4522 4700 4800 4900 5100 5200 5300 5400 5500 5600 5700 5800 6000 6100 6211 6212 6213 6221 6222 6223 6231 6232 6233 6241 6242 6243 6300 6400 6500 6600 6700 6800 6900 7000 7100 7200 7300 7400 7500 7700 7800 7900 8000 8100 8200 8300 8400 8500 8600 8700 8800 8900 9000 9100 9200 9300 9400 9500 9600 9700 9710 9720 9800 9810 9820 9900 10000 10100 10200 10300 10400 10410 10420 10500 10600 10700 10800 10900 11000 11100 11200 11300 11400 11500 11600 11700 11800 11850 11860 11900 12000 12001 12100 12200 12300 12400 12500 12600 12700 12800 12900 13000 13100 13200 13300 13400 13500 13600 13800 13900 14000 14100 14700 14800 14900 15000 15100 15200 15300 15400 15500 15600 15700 15900 16000 16100 16200 16300 16400 16500 16600 16700 16800 16801 16900 17300 17400 17500 17600 17700 17800 17900 18000 18100 18200 18300 18400 18500"
local HASH_MODES="0 10 11 12 20 21 22 23 30 40 50 60 100 101 110 111 112 120 121 122 124 130 131 132 133 140 141 150 160 200 300 400 500 501 600 900 1000 1100 1400 1410 1411 1420 1421 1430 1440 1441 1450 1460 1500 1600 1700 1710 1711 1720 1722 1730 1731 1740 1750 1760 1800 2100 2400 2410 2500 2501 2600 2611 2612 2711 2811 3000 3100 3200 3710 3711 3800 3910 4010 4110 4300 4400 4500 4520 4521 4522 4700 4800 4900 5100 5200 5300 5400 5500 5600 5700 5800 6000 6100 6211 6212 6213 6221 6222 6223 6231 6232 6233 6241 6242 6243 6300 6400 6500 6600 6700 6800 6900 7000 7100 7200 7300 7400 7500 7700 7800 7900 8000 8100 8200 8300 8400 8500 8600 8700 8800 8900 9000 9100 9200 9300 9400 9500 9600 9700 9710 9720 9800 9810 9820 9900 10000 10100 10200 10300 10400 10410 10420 10500 10600 10700 10800 10900 11000 11100 11200 11300 11400 11500 11600 11700 11800 11850 11860 11900 12000 12001 12100 12200 12300 12400 12500 12600 12700 12800 12900 13000 13100 13200 13300 13400 13500 13600 13800 13900 14000 14100 14700 14800 14900 15000 15100 15200 15300 15400 15500 15600 15700 15900 16000 16100 16200 16300 16400 16500 16600 16700 16800 16801 16900 17300 17400 17500 17600 17700 17800 17900 18000 18100 18200 18300 18400 18500 18600"
local ATTACK_MODES="0 1 3 6 7"
local HCCAPX_MESSAGE_PAIRS="0 1 2 3 4 5"
local OUTFILE_FORMATS="1 2 3 4 5 6 7 8 9 10 11 12 13 14 15"

@ -423,6 +423,25 @@ typedef struct oldoffice34
} oldoffice34_t;
typedef struct odf11_tmp
{
u32 ipad[5];
u32 opad[5];
u32 dgst[5];
u32 out[5];
} odf11_tmp_t;
typedef struct odf11
{
u32 iterations;
u32 iv[2];
u32 checksum[5];
u32 encrypted_data[256];
} odf11_t;
typedef struct odf12_tmp
{
u32 ipad[5];
@ -1169,6 +1188,7 @@ typedef enum hash_type
HASH_TYPE_ANSIBLE_VAULT = 70,
HASH_TYPE_KRB5ASREP = 71,
HASH_TYPE_ODF12 = 72,
HASH_TYPE_ODF11 = 73,
} hash_type_t;
@ -1398,6 +1418,7 @@ typedef enum kern_type
KERN_TYPE_APFS = 18300,
KERN_TYPE_ODF12 = 18400,
KERN_TYPE_SHA1_DOUBLE_MD5 = 18500,
KERN_TYPE_ODF11 = 18600,
KERN_TYPE_PLAINTEXT = 99999,
} kern_type_t;
@ -1442,6 +1463,7 @@ typedef enum rounds_count
ROUNDS_OFFICE2010 = 100000,
ROUNDS_OFFICE2013 = 100000,
ROUNDS_LIBREOFFICE = 100000,
ROUNDS_OPENOFFICE = 1024,
ROUNDS_DJANGOPBKDF2 = 20000,
ROUNDS_SAPH_SHA1 = 1024,
ROUNDS_PDF14 = (50 + 20),

@ -301,6 +301,7 @@ static const char *ST_HASH_18200 = "$krb5asrep$23$user@domain.com:3e156ada591263
static const char *ST_HASH_18300 = "$fvde$2$16$58778104701476542047675521040224$20000$39602e86b7cea4a34f4ff69ff6ed706d68954ee474de1d2a9f6a6f2d24d172001e484c1d4eaa237d";
static const char *ST_HASH_18400 = "$odf$*1*1*100000*32*751854d8b90731ce0579f96bea6f0d4ac2fb2f546b31f1b6af9a5f66952a0bf4*16*2185a966155baa9e2fb597298febecbc*16*c18eaae34bcbbe9119be017fe5f8b52d*0*051e0f1ce0e866f2b771029e03a6c7119aad132af54c4e45824f16f61f357a40407ab82744fe6370c7b2346075fcd4c2e58ab244411b3ab1d532a46e2321599ef13c3d3472fc2f14d480d8c33215e473da67f90540279d3ef1f62dde314fa222796046e496c951235ddf88aa754620b7810d22ebc8835c90dce9276946f52b8ea7d95d2f86e4cc725366a8b3edacc2ce88518e535991a5f84d5ea8795dc02bfb731b5f202ecaf7d4b245d928c4248709fcdf3fba2acf1a08be0c1eee7dbeda07e8c3a6983565635e99952b8ad79d31c965f245ae90b5cc3dba6387898c66fa35cad9ac9595c41b62e68efcdd73185b38e220cf004269b77ec6974474b03b7569afc3b503a2bf8b2d035756f3f4cb880d9ba815e5c944508a0bde214076c35bf0e0814a96d21ccaa744c9056948ed935209f5c7933841d2ede3d28dd84da89d477d4a0041ce6d8ddab891d929340db6daa921d69b46fd5aee306d0bcef88c38acbb495d0466df7e2f744e3d10201081215c02db5dd479a4cda15a3338969c7baec9d3d2c378a8dd30449319b149dc3b4e7f00996a59fcb5f243d0df2cbaf749241033f7865aefa960adfeb8ebf205b270f90b1f82c34f80d5a8a0db7aec89972a32f5daa2a73c5895d1fced01b3ab8e576bd2630eff01cad97781f4966d4b528e1b15f011f28ae907a352073c96b203adc7742d2b79b2e2f440b17e7856ae119e08d15d8bdf951f6d4a3f9b516da2d9a8f9dd93488f8e0119f3da19138ab787f0d7098a652cccd914aa0ff81d375bd6a5a165acc936f591639059287975cfc3ca4342e5f9501b3249a76d14e56d6d56b319e036bc0449ac7b5afa24ffbea11babed8183edf8d4fdca1c3f0d23bfd4a02797627d556634f1a9304e03737604bd86f6b5a26aa687d6df73383e0f7dfe62a131e8dbb8c3f4f13d24857dd29d76984eac6c45df7428fc79323ffa1f4e7962d705df74320141ed1f16d1ad483b872168df60315ffadbfa1b7f4afaed8a0017421bf5e05348cb5c707a5e852d6fee6077ec1c33bc707bcd97b7701ee05a03d6fa78b0d31c8c97ea16e0edf434961bd5cc7cbb7eb2553730f0405c9bd21cee09b3f7c1bc57779fdfc15f3935985737a1b522004c4436b631a39a66e8577a03f5020e6aa41952c0662c8c57f66caa483b47af38b8cb5d457245fd3241749e17433e6f929233e8862d7c584111b1991b2d6e94278e7e6e1908cee5a83d94c78b75a84a695d25aeb9fdde72174fe6dd75e8d406671f44892a385a4a1e249f61ebc993e985607423a0a5742e668d52c1ebf5cecae7c2b7908f4627b92ec49354a9ccff8cb5763ad074a00e65a485a41bf4c25ce7e6fae49358a58547b1c0ca79713e297310c0a367c3de196f1dd685ca4be643bdf1e4f6b034211d020557e37a3b6614d061010b4a3416b6b279728c245d3322";
static const char *ST_HASH_18500 = "888a2ffcb3854fba0321110c5d0d434ad1aa2880";
static const char *ST_HASH_18600 = "$odf$*0*0*1024*16*bff753835f4ea15644b8a2f8e4b5be3d147b9576*8*ee371da34333b69d*16*a902eff54a4d782a26a899a31f97bef4*0*dae7e41fbc3a500d3ce152edd8876c4f38fb17d673ee2ac44ef1e0e283622cd2ae298a82d8d98f2ea737247881fc353e73a2f535c6e13e0cdc60821c1a61c53a4b0c46ff3a3b355d7b793fad50de15999fc7c1194321d1c54316c3806956c4a3ade7daabb912a2a36398eba883af088b3cb69b43365d9ba9fce3fb0c1524f73947a7e9fc1bf3adb5f85a367035feacb5d97c578b037144c2793f34aa09dcd04bdaa455aee0d4c52fe377248611dd56f2bd4eb294673525db905f5d905a28dec0909348e6bf94bcebf03ddd61a48797cd5728ce6dbb71037b268f526e806401abcf495f6edd0b5d87118671ec690d4627f86a43e51c7f6d42a75a56eec51204d47e115e813ed4425c97b16b195e02ce776c185194b9de43ae89f356e29face016cb393d6fb93af8ea305d921d5592dd184051ac790b9b90266f52b8d53ce1cb1d762942d6d5bbd0e3821be21af9fa6874ba0c60e64f41d3e5b6caca1c53b575afdc5d8f6a3edbf874dbe009c6cb296466fe9637aed4aed8a43a95ea7d26b4090ad33d4ee7a83844b0893e8bc0f04944205fb9576cb5720f019028cd75ca9ac47b3e5fa231354d74135564df43b659cfaea7e195c4a896e0e0e0c85dc9ce3a9ce9ba552bc2a6dbac4901c19558818e1957ed72d78662bb5ba53475ca584371f1825ae0c92322a4404e63c2baad92665aac29b5c6f96e1e6338d48fb0aef4d0b686063974f58b839484f8dcf0a02537cba67a7d2c4de13125d74820cb07ec72782035af1ea6c4db61c77016d1c021b63c8b07adb4e8510f5c41bbc501f60f3dd16462399b52eb146787e38e700147c7aa23ac4d5d22d9d1c93e67a01c92a197d4765cbf8d56a862a1205abb450a182913a69b8d5334a59924f86fb3ccd0dcfe7426053e26ba26b57c05f38d85863fff1f81135b0366e8cd8680663ae8aaf7d005317b849d5e08be882708fa0d8d02d47e89150124b507c34845c922b95e62aa0b3fef218773d7aeb572c67b35ad8787f31ecc6e1846b673b8ba6172223176eabf0020b6aa3aa71405b40b2fc2127bf9741a103f1d8eca21bf27328cdf15153f2f223eff7b831a72ed8ecacf4ea8df4ea44f3a3921e5a88fb2cfa355ece0f05cbc88fdd1ecd368d6e3b2dfabd999e5b708f1bccaeebb296c9d7b76659967742fe966aa6871cbbffe710b0cd838c6e02e6eb608cb5c81d066b60b5b3604396331d97d4a2c4c2317406e48c9f5387a2c72511d1e6899bd450e9ca88d535755bcfddb53a6df118cd9cdc7d8b4b814f7bc17684d8e5975defaa25d06f410ed0724c16b8f69ec3869bc1f05c71483666968d1c04509875dadd72c6182733d564eb1a7d555dc34f6b817c5418626214d0b2c3901c5a46f5b20fddfdf9f71a7dfd75b9928778a3f65e1832dff22be973c2b259744d500a3027c2a2e08972eaaad4c5c4ec871";
static const char *ST_HASH_99999 = "hashcat";
static const char *OPTI_STR_OPTIMIZED_KERNEL = "Optimized-Kernel";
@ -565,6 +566,7 @@ static const char *HT_18200 = "Kerberos 5 AS-REP etype 23";
static const char *HT_18300 = "Apple File System (APFS)";
static const char *HT_18400 = "Open Document Format (ODF) 1.2 (SHA-256, AES)";
static const char *HT_18500 = "sha1(md5(md5($pass)))";
static const char *HT_18600 = "Open Document Format (ODF) 1.1 (SHA-1, Blowfish)";
static const char *HT_99999 = "Plaintext";
static const char *HT_00011 = "Joomla < 2.5.18";
@ -10992,6 +10994,157 @@ int oldoffice34cm2_parse_hash (u8 *input_buf, u32 input_len, hash_t *hash_buf, M
return (PARSER_OK);
}
int odf11_parse_hash (u8 *input_buf, u32 input_len, hash_t *hash_buf, MAYBE_UNUSED hashconfig_t *hashconfig)
{
u32 *digest = (u32 *) hash_buf->digest;
salt_t *salt_s = hash_buf->salt;
odf11_t *odf11 = (odf11_t *) hash_buf->esalt;
token_t token;
token.token_cnt = 12;
token.signatures_cnt = 1;
token.signatures_buf[0] = SIGNATURE_ODF;
token.len_min[0] = 5;
token.len_max[0] = 5;
token.sep[0] = '*';
token.attr[0] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_SIGNATURE;
token.len_min[1] = 1;
token.len_max[1] = 1;
token.sep[1] = '*';
token.attr[1] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[2] = 1;
token.len_max[2] = 1;
token.sep[2] = '*';
token.attr[2] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[3] = 4;
token.len_max[3] = 6;
token.sep[3] = '*';
token.attr[3] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[4] = 2;
token.len_max[4] = 2;
token.sep[4] = '*';
token.attr[4] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[5] = 40;
token.len_max[5] = 40;
token.sep[5] = '*';
token.attr[5] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_HEX;
token.len_min[6] = 1;
token.len_max[6] = 1;
token.sep[6] = '*';
token.attr[6] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[7] = 16;
token.len_max[7] = 16;
token.sep[7] = '*';
token.attr[7] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_HEX;
token.len_min[8] = 2;
token.len_max[8] = 2;
token.sep[8] = '*';
token.attr[8] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len_min[9] = 32;
token.len_max[9] = 32;
token.sep[9] = '*';
token.attr[9] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_HEX;
token.len_min[10] = 1;
token.len_max[10] = 1;
token.sep[10] = '*';
token.attr[10] = TOKEN_ATTR_VERIFY_LENGTH
| TOKEN_ATTR_VERIFY_DIGIT;
token.len[11] = 2048;
token.attr[11] = TOKEN_ATTR_FIXED_LENGTH
| TOKEN_ATTR_VERIFY_HEX;
const int rc_tokenizer = input_tokenizer (input_buf, input_len, &token);
if (rc_tokenizer != PARSER_OK) return (rc_tokenizer);
const u8 *checksum = token.buf[5];
const u8 *iv = token.buf[7];
const u8 *salt = token.buf[9];
const u8 *encrypted_data = token.buf[11];
const u32 cipher_type = strtol ((const char *) token.buf[1], NULL, 10);
const u32 checksum_type = strtol ((const char *) token.buf[2], NULL, 10);
const u32 iterations = strtol ((const char *) token.buf[3], NULL, 10);
const u32 key_size = strtol ((const char *) token.buf[4], NULL, 10);
const u32 iv_len = strtol ((const char *) token.buf[6], NULL, 10);
const u32 salt_len = strtol ((const char *) token.buf[8], NULL, 10);
const u32 unused = strtol ((const char *) token.buf[10], NULL, 10);
if (cipher_type != 0) return (PARSER_SALT_VALUE);
if (checksum_type != 0) return (PARSER_SALT_VALUE);
if (key_size != 16) return (PARSER_SALT_VALUE);
if (iv_len != 8) return (PARSER_SALT_VALUE);
if (salt_len != 16) return (PARSER_SALT_VALUE);
if (unused != 0) return (PARSER_SALT_VALUE);
// esalt
odf11->iterations = iterations;
odf11->checksum[0] = hex_to_u32 (&checksum[0]);
odf11->checksum[1] = hex_to_u32 (&checksum[8]);
odf11->checksum[2] = hex_to_u32 (&checksum[16]);
odf11->checksum[3] = hex_to_u32 (&checksum[24]);
odf11->checksum[4] = hex_to_u32 (&checksum[32]);
odf11->iv[0] = byte_swap_32 (hex_to_u32 (&iv[0]));
odf11->iv[1] = byte_swap_32 (hex_to_u32 (&iv[8]));
for (int i = 0; i < 256; i++)
{
odf11->encrypted_data[i] = byte_swap_32 (hex_to_u32 (&encrypted_data[8 * i]));
}
// salt
salt_s->salt_len = salt_len;
salt_s->salt_iter = iterations - 1;
salt_s->salt_buf[0] = byte_swap_32 (hex_to_u32 (&salt[0]));
salt_s->salt_buf[1] = byte_swap_32 (hex_to_u32 (&salt[8]));
salt_s->salt_buf[2] = byte_swap_32 (hex_to_u32 (&salt[16]));
salt_s->salt_buf[3] = byte_swap_32 (hex_to_u32 (&salt[24]));
/**
* digest
*/
digest[0] = byte_swap_32 (odf11->checksum[0]);
digest[1] = byte_swap_32 (odf11->checksum[1]);
digest[2] = byte_swap_32 (odf11->checksum[2]);
digest[3] = byte_swap_32 (odf11->checksum[3]);
digest[4] = byte_swap_32 (odf11->checksum[4]);
return (PARSER_OK);
}
int odf12_parse_hash (u8 *input_buf, u32 input_len, hash_t *hash_buf, MAYBE_UNUSED hashconfig_t *hashconfig)
{
u32 *digest = (u32 *) hash_buf->digest;
@ -19218,6 +19371,7 @@ const char *strhashtype (const u32 hash_mode)
case 18300: return HT_18300;
case 18400: return HT_18400;
case 18500: return HT_18500;
case 18600: return HT_18600;
case 99999: return HT_99999;
}
@ -23115,6 +23269,44 @@ int ascii_digest (hashcat_ctx_t *hashcat_ctx, char *out_buf, const size_t out_le
byte_swap_32 (odf12->encrypted_data[i + 7]));
}
}
else if (hash_mode == 18600)
{
odf11_t *odf11s = (odf11_t *) esalts_buf;
odf11_t *odf11 = &odf11s[digest_cur];
size_t pos = 0;
snprintf (out_buf, out_len, "%s*0*0*%d*16*%08x%08x%08x%08x%08x*8*%08x%08x*16*%08x%08x%08x%08x*0*",
SIGNATURE_ODF,
odf11->iterations,
byte_swap_32 (odf11->checksum[0]),
byte_swap_32 (odf11->checksum[1]),
byte_swap_32 (odf11->checksum[2]),
byte_swap_32 (odf11->checksum[3]),
byte_swap_32 (odf11->checksum[4]),
odf11->iv[0],
odf11->iv[1],
salt.salt_buf[0],
salt.salt_buf[1],
salt.salt_buf[2],
salt.salt_buf[3]);
pos += strlen (out_buf);
for (int i = 0; i < 256; i += 8, pos += 64)
{
snprintf (&out_buf[pos], out_len - pos, "%08x%08x%08x%08x%08x%08x%08x%08x",
odf11->encrypted_data[i + 0],
odf11->encrypted_data[i + 1],
odf11->encrypted_data[i + 2],
odf11->encrypted_data[i + 3],
odf11->encrypted_data[i + 4],
odf11->encrypted_data[i + 5],
odf11->encrypted_data[i + 6],
odf11->encrypted_data[i + 7]);
}
}
else if (hash_mode == 99999)
{
char *ptr = (char *) digest_buf;
@ -28624,6 +28816,23 @@ int hashconfig_init (hashcat_ctx_t *hashcat_ctx)
hashconfig->st_pass = ST_PASS_HASHCAT_PLAIN;
break;
case 18600: hashconfig->hash_type = HASH_TYPE_ODF11;
hashconfig->salt_type = SALT_TYPE_EMBEDDED;
hashconfig->attack_exec = ATTACK_EXEC_OUTSIDE_KERNEL;
hashconfig->opts_type = OPTS_TYPE_PT_GENERATE_LE;
hashconfig->kern_type = KERN_TYPE_ODF11;
hashconfig->dgst_size = DGST_SIZE_4_5;
hashconfig->parse_func = odf11_parse_hash;
hashconfig->opti_type = OPTI_TYPE_ZERO_BYTE
| OPTI_TYPE_SLOW_HASH_SIMD_LOOP;
hashconfig->dgst_pos0 = 0;
hashconfig->dgst_pos1 = 1;
hashconfig->dgst_pos2 = 2;
hashconfig->dgst_pos3 = 3;
hashconfig->st_hash = ST_HASH_18600;
hashconfig->st_pass = ST_PASS_HASHCAT_PLAIN;
break;
case 99999: hashconfig->hash_type = HASH_TYPE_PLAINTEXT;
hashconfig->salt_type = SALT_TYPE_NONE;
hashconfig->attack_exec = ATTACK_EXEC_INSIDE_KERNEL;
@ -28865,6 +29074,7 @@ int hashconfig_init (hashcat_ctx_t *hashcat_ctx)
case 18200: hashconfig->esalt_size = sizeof (krb5asrep_t); break;
case 18300: hashconfig->esalt_size = sizeof (apple_secure_notes_t); break;
case 18400: hashconfig->esalt_size = sizeof (odf12_t); break;
case 18600: hashconfig->esalt_size = sizeof (odf11_t); break;
}
// hook_salt_size
@ -28983,6 +29193,7 @@ int hashconfig_init (hashcat_ctx_t *hashcat_ctx)
case 16900: hashconfig->tmp_size = sizeof (pbkdf2_sha256_tmp_t); break;
case 18300: hashconfig->tmp_size = sizeof (apple_secure_notes_tmp_t); break;
case 18400: hashconfig->tmp_size = sizeof (odf12_tmp_t); break;
case 18600: hashconfig->tmp_size = sizeof (odf11_tmp_t); break;
};
// hook_size
@ -29042,6 +29253,7 @@ u32 hashconfig_forced_kernel_threads (hashcat_ctx_t *hashcat_ctx)
if (hashconfig->hash_mode == 13100) kernel_threads = 64; // RC4
if (hashconfig->hash_mode == 15700) kernel_threads = 1; // SCRYPT
if (hashconfig->hash_mode == 18200) kernel_threads = 64; // RC4
if (hashconfig->hash_mode == 18600) kernel_threads = 8; // Blowfish
return kernel_threads;
}
@ -29436,6 +29648,7 @@ int hashconfig_get_pw_max (hashcat_ctx_t *hashcat_ctx, const bool optimized_kern
case 16801: pw_max = 64; break; // WPA-PMKID-PMK: fixed length
case 16900: pw_max = PW_MAX; break;
case 18400: pw_max = PW_MAX; break;
case 18600: pw_max = 51; break; // Bogus SHA-1 in StarOffice code
}
return pw_max;
@ -29755,6 +29968,8 @@ void hashconfig_benchmark_defaults (hashcat_ctx_t *hashcat_ctx, salt_t *salt, vo
break;
case 18400: salt->salt_len = 16;
break;
case 18600: salt->salt_len = 16;
break;
}
// special esalt handling
@ -30054,6 +30269,8 @@ void hashconfig_benchmark_defaults (hashcat_ctx_t *hashcat_ctx, salt_t *salt, vo
break;
case 18400: salt->salt_iter = ROUNDS_LIBREOFFICE - 1;
break;
case 18600: salt->salt_iter = ROUNDS_OPENOFFICE - 1;
break;
}
}

@ -394,6 +394,7 @@ static const char *const USAGE_BIG[] =
" 10600 | PDF 1.7 Level 3 (Acrobat 9) | Documents",
" 10700 | PDF 1.7 Level 8 (Acrobat 10 - 11) | Documents",
" 16200 | Apple Secure Notes | Documents",
" 18600 | Open Document Format (ODF) 1.1 (SHA-1, Blowfish) | Documents",
" 18400 | Open Document Format (ODF) 1.2 (SHA-256, AES) | Documents",
" 9000 | Password Safe v2 | Password Managers",
" 5200 | Password Safe v3 | Password Managers",

@ -21,6 +21,7 @@ cpan install Authen::Passphrase::LANManager \
Crypt::Digest::Whirlpool \
Crypt::ECB \
Crypt::Eksblowfish::Bcrypt \
Crypt::GCrypt \
Crypt::Mode::ECB \
Crypt::MySQL \
Crypt::OpenSSH::ChachaPoly \

@ -29,6 +29,7 @@ use Crypt::Digest::RIPEMD160 qw (ripemd160_hex);
use Crypt::Digest::Whirlpool qw (whirlpool_hex);
use Crypt::ECB qw (encrypt);
use Crypt::Eksblowfish::Bcrypt qw (bcrypt en_base64);
use Crypt::GCrypt;
use Crypt::Mode::CBC;
use Crypt::Mode::ECB;
use Crypt::MySQL qw (password41);
@ -94,7 +95,8 @@ my $MODES =
13400, 13500, 13600, 13800, 13900, 14000, 14100, 14400, 14700, 14800, 14900,
15000, 15100, 15200, 15300, 15400, 15500, 15600, 15700, 15900, 16000, 16100,
16200, 16300, 16400, 16500, 16600, 16700, 16800, 16900, 17300, 17400, 17500,
17600, 17700, 17800, 17900, 18000, 18100, 18200, 18300, 18400, 18500, 99999
17600, 17700, 17800, 17900, 18000, 18100, 18200, 18300, 18400, 18500, 18600,
99999
];
## STEP 2a: If your hash mode does not need a salt, add it to this array.
@ -3226,7 +3228,78 @@ sub verify
next unless (exists ($db->{$hash_in}) and (! defined ($db->{$hash_in})));
}
## STEP 2c: Add your custom salt branch here
elsif ($mode == 18600)
{
($hash_in, $word) = split ":", $line;
next unless defined $hash_in;
next unless defined $word;
# tokenize
my @data = split ('\*', $hash_in);
next unless scalar @data == 12;
my $signature = shift @data;
my $cipher_type = shift @data;
my $cs_type = shift @data;
$iter = shift @data;
my $cs_len = shift @data;
my $cs = shift @data;
my $iv_len = shift @data;
my $iv = shift @data;
my $salt_len = shift @data;
$salt = shift @data;
my $unused = shift @data;
my $ciphertext = shift @data;
# validate
next unless ($signature eq '$odf$');
next unless ($cipher_type eq '0');
next unless ($cs_type eq '0');
next unless ($cs_len eq '16');
next unless ($iv_len eq '8');
next unless ($salt_len eq '16');
next unless ($unused eq '0');
next unless defined $ciphertext;
# decrypt
my $b_iv = pack ("H*", $iv);
my $b_salt = pack ("H*", $salt);
my $b_ciphertext = pack ("H*", $ciphertext);
my $kdf = Crypt::PBKDF2->new
(
hash_class => 'HMACSHA1',
iterations => $iter,
output_len => 16
);
my $pass_hash = sha1 ($word);
my $derived_key = $kdf->PBKDF2 ($b_salt, $pass_hash);
my $cfb = Crypt::GCrypt->new(
type => 'cipher',
algorithm => 'blowfish',
mode => 'cfb'
);
$cfb->start ('decrypting');
$cfb->setkey ($derived_key);
$cfb->setiv ($b_iv);
my $b_plaintext = $cfb->decrypt ($b_ciphertext);
$cfb->finish ();
my $plaintext = unpack ("H*", $b_plaintext);
$param = $iv;
$param2 = $plaintext;
next unless (exists ($db->{$hash_in}) and (! defined ($db->{$hash_in})));
}
## STEP 2c: Add your custom hash parser branch here
else
{
print "ERROR: hash mode is not supported\n";
@ -3722,6 +3795,14 @@ sub verify
return unless (substr ($line, 0, $len) eq $hash_out);
}
elsif ($mode == 18600)
{
$hash_out = gen_hash ($mode, $word, $salt, $iter, $param, $param2);
$len = length $hash_out;
return unless (substr ($line, 0, $len) eq $hash_out);
}
## STEP 2c: Add your custom gen_hash call here
else
{
@ -4330,6 +4411,10 @@ sub passthrough
{
$tmp_hash = gen_hash ($mode, $word_buf, substr ($salt_buf, 0, 32));
}
elsif ($mode == 18600)
{
$tmp_hash = gen_hash ($mode, $word_buf, substr ($salt_buf, 0, 32));
}
## STEP 2c: Add your custom salt branch here
else
{
@ -5516,6 +5601,20 @@ sub single
}
}
}
elsif ($mode == 18600)
{
for (my $i = 1; $i < 32; $i++)
{
if ($len != 0)
{
rnd ($mode, $len, 32);
}
else
{
rnd ($mode, $i, 32);
}
}
}
## STEP 2c: Add your custom salt branch here
}
}
@ -10736,6 +10835,63 @@ END_CODE
$tmp_hash = sprintf ("%s", $hash_buf);
}
elsif ($mode == 18600)
{
# defaults for single mode
my $iterations = 1024;
my $iv = "aa" x 8;
my $plaintext = "bb" x 1024;
# parameters for verify mode
if (defined $iter)
{
$iterations = $iter;
}
if (defined $additional_param)
{
$iv = $additional_param;
}
if (defined $additional_param2)
{
$plaintext = $additional_param2;
}
# binary buffers
my $b_iv = pack ("H*", $iv);
my $b_salt = pack ("H*", $salt_buf);
my $b_plaintext = pack ("H*", $plaintext);
my $kdf = Crypt::PBKDF2->new
(
hash_class => 'HMACSHA1',
iterations => $iterations,
output_len => 16
);
my $checksum = sha1_hex ($b_plaintext);
my $pass_hash = sha1 ($word_buf);
my $derived_key = $kdf->PBKDF2 ($b_salt, $pass_hash);
my $cfb = Crypt::GCrypt->new(
type => 'cipher',
algorithm => 'blowfish',
mode => 'cfb',
);
$cfb->start ('encrypting');
$cfb->setkey ($derived_key);
$cfb->setiv ($b_iv);
my $b_ciphertext = $cfb->encrypt ($b_plaintext);
$cfb->finish ();
my $ciphertext = unpack ("H*", $b_ciphertext);
$tmp_hash = '$odf$'."*0*0*$iterations*16*$checksum*8*$iv*16*$salt_buf*0*$ciphertext";
}
elsif ($mode == 99999)
{
$tmp_hash = sprintf ("%s", $word_buf);

@ -30,7 +30,7 @@ HASH_TYPES="0 10 11 12 20 21 22 23 30 40 50 60\
13751 13752 13753 13771 13772 13773 13800 13900 14000 14100 14400 14600 14700\
14800 14900 15000 15100 15200 15300 15400 15500 15600 15700 15900 16000 16100\
16200 16300 16400 16500 16600 16700 16800 16900 17300 17400 17500 17600 17700\
17800 17900 18000 18100 18200 18300 18400 18500 99999"
17800 17900 18000 18100 18200 18300 18400 18500 18600 99999"
VECTOR_WIDTHS="1 2 4 8 16"
@ -48,7 +48,7 @@ SLOW_ALGOS=" 400 500 501 1600 1800 2100 2500 3200 5200 5800 6211\
12900 13000 13200 13400 13600 13711 13712 13713 13721 13722 13723 13731 13732\
13733 13751 13752 13753 13771 13772 13773 14600 14611 14612 14613 14621 14622\
14623 14631 14632 14633 14641 14642 14643 14700 14800 15100 15200 15300 15600\
15700 15900 16000 16200 16300 16800 16900 18400"
15700 15900 16000 16200 16300 16800 16900 18400 18600"
# List of VeraCrypt modes which have test containers
VC_MODES="13711 13712 13713 13721 13722 13723 13731 13732 13733 13751 13752\

Loading…
Cancel
Save