First commit
This commit is contained in:
commit
c8307fdf87
|
@ -0,0 +1,4 @@
|
|||
*.o
|
||||
*.ppu
|
||||
*~
|
||||
|
|
@ -0,0 +1,826 @@
|
|||
unit BCrypt;
|
||||
{$mode objfpc}{$H+}
|
||||
{$codepage utf8}
|
||||
|
||||
interface
|
||||
|
||||
uses
|
||||
SysUtils,
|
||||
Classes;
|
||||
|
||||
const
|
||||
// bcrypt uses 128-bit (16-byte) salt
|
||||
BCRYPT_SALT_LEN = 16;
|
||||
BLOWFISH_NUM_ROUNDS = 16;
|
||||
BCRYPT_DEFAULT_COST = 12;
|
||||
|
||||
PBoxOrg: array[0..17] of DWord = (
|
||||
$243f6a88, $85a308d3, $13198a2e, $03707344, $a4093822, $299f31d0, $082efa98,
|
||||
$ec4e6c89, $452821e6, $38d01377, $be5466cf, $34e90c6c, $c0ac29b7, $c97c50dd,
|
||||
$3f84d5b5, $b5470917, $9216d5d9, $8979fb1b
|
||||
);
|
||||
|
||||
SBoxOrg: array[0..1023] of DWord = (
|
||||
$d1310ba6, $98dfb5ac, $2ffd72db, $d01adfb7, $b8e1afed, $6a267e96, $ba7c9045,
|
||||
$f12c7f99, $24a19947, $b3916cf7, $0801f2e2, $858efc16, $636920d8, $71574e69,
|
||||
$a458fea3, $f4933d7e, $0d95748f, $728eb658, $718bcd58, $82154aee, $7b54a41d,
|
||||
$c25a59b5, $9c30d539, $2af26013, $c5d1b023, $286085f0, $ca417918, $b8db38ef,
|
||||
$8e79dcb0, $603a180e, $6c9e0e8b, $b01e8a3e, $d71577c1, $bd314b27, $78af2fda,
|
||||
$55605c60, $e65525f3, $aa55ab94, $57489862, $63e81440, $55ca396a, $2aab10b6,
|
||||
$b4cc5c34, $1141e8ce, $a15486af, $7c72e993, $b3ee1411, $636fbc2a, $2ba9c55d,
|
||||
$741831f6, $ce5c3e16, $9b87931e, $afd6ba33, $6c24cf5c, $7a325381, $28958677,
|
||||
$3b8f4898, $6b4bb9af, $c4bfe81b, $66282193, $61d809cc, $fb21a991, $487cac60,
|
||||
$5dec8032, $ef845d5d, $e98575b1, $dc262302, $eb651b88, $23893e81, $d396acc5,
|
||||
$0f6d6ff3, $83f44239, $2e0b4482, $a4842004, $69c8f04a, $9e1f9b5e, $21c66842,
|
||||
$f6e96c9a, $670c9c61, $abd388f0, $6a51a0d2, $d8542f68, $960fa728, $ab5133a3,
|
||||
$6eef0b6c, $137a3be4, $ba3bf050, $7efb2a98, $a1f1651d, $39af0176, $66ca593e,
|
||||
$82430e88, $8cee8619, $456f9fb4, $7d84a5c3, $3b8b5ebe, $e06f75d8, $85c12073,
|
||||
$401a449f, $56c16aa6, $4ed3aa62, $363f7706, $1bfedf72, $429b023d, $37d0d724,
|
||||
$d00a1248, $db0fead3, $49f1c09b, $075372c9, $80991b7b, $25d479d8, $f6e8def7,
|
||||
$e3fe501a, $b6794c3b, $976ce0bd, $04c006ba, $c1a94fb6, $409f60c4, $5e5c9ec2,
|
||||
$196a2463, $68fb6faf, $3e6c53b5, $1339b2eb, $3b52ec6f, $6dfc511f, $9b30952c,
|
||||
$cc814544, $af5ebd09, $bee3d004, $de334afd, $660f2807, $192e4bb3, $c0cba857,
|
||||
$45c8740f, $d20b5f39, $b9d3fbdb, $5579c0bd, $1a60320a, $d6a100c6, $402c7279,
|
||||
$679f25fe, $fb1fa3cc, $8ea5e9f8, $db3222f8, $3c7516df, $fd616b15, $2f501ec8,
|
||||
$ad0552ab, $323db5fa, $fd238760, $53317b48, $3e00df82, $9e5c57bb, $ca6f8ca0,
|
||||
$1a87562e, $df1769db, $d542a8f6, $287effc3, $ac6732c6, $8c4f5573, $695b27b0,
|
||||
$bbca58c8, $e1ffa35d, $b8f011a0, $10fa3d98, $fd2183b8, $4afcb56c, $2dd1d35b,
|
||||
$9a53e479, $b6f84565, $d28e49bc, $4bfb9790, $e1ddf2da, $a4cb7e33, $62fb1341,
|
||||
$cee4c6e8, $ef20cada, $36774c01, $d07e9efe, $2bf11fb4, $95dbda4d, $ae909198,
|
||||
$eaad8e71, $6b93d5a0, $d08ed1d0, $afc725e0, $8e3c5b2f, $8e7594b7, $8ff6e2fb,
|
||||
$f2122b64, $8888b812, $900df01c, $4fad5ea0, $688fc31c, $d1cff191, $b3a8c1ad,
|
||||
$2f2f2218, $be0e1777, $ea752dfe, $8b021fa1, $e5a0cc0f, $b56f74e8, $18acf3d6,
|
||||
$ce89e299, $b4a84fe0, $fd13e0b7, $7cc43b81, $d2ada8d9, $165fa266, $80957705,
|
||||
$93cc7314, $211a1477, $e6ad2065, $77b5fa86, $c75442f5, $fb9d35cf, $ebcdaf0c,
|
||||
$7b3e89a0, $d6411bd3, $ae1e7e49, $00250e2d, $2071b35e, $226800bb, $57b8e0af,
|
||||
$2464369b, $f009b91e, $5563911d, $59dfa6aa, $78c14389, $d95a537f, $207d5ba2,
|
||||
$02e5b9c5, $83260376, $6295cfa9, $11c81968, $4e734a41, $b3472dca, $7b14a94a,
|
||||
$1b510052, $9a532915, $d60f573f, $bc9bc6e4, $2b60a476, $81e67400, $08ba6fb5,
|
||||
$571be91f, $f296ec6b, $2a0dd915, $b6636521, $e7b9f9b6, $ff34052e, $c5855664,
|
||||
$53b02d5d, $a99f8fa1, $08ba4799, $6e85076a, $4b7a70e9, $b5b32944, $db75092e,
|
||||
$c4192623, $ad6ea6b0, $49a7df7d, $9cee60b8, $8fedb266, $ecaa8c71, $699a17ff,
|
||||
$5664526c, $c2b19ee1, $193602a5, $75094c29, $a0591340, $e4183a3e, $3f54989a,
|
||||
$5b429d65, $6b8fe4d6, $99f73fd6, $a1d29c07, $efe830f5, $4d2d38e6, $f0255dc1,
|
||||
$4cdd2086, $8470eb26, $6382e9c6, $021ecc5e, $09686b3f, $3ebaefc9, $3c971814,
|
||||
$6b6a70a1, $687f3584, $52a0e286, $b79c5305, $aa500737, $3e07841c, $7fdeae5c,
|
||||
$8e7d44ec, $5716f2b8, $b03ada37, $f0500c0d, $f01c1f04, $0200b3ff, $ae0cf51a,
|
||||
$3cb574b2, $25837a58, $dc0921bd, $d19113f9, $7ca92ff6, $94324773, $22f54701,
|
||||
$3ae5e581, $37c2dadc, $c8b57634, $9af3dda7, $a9446146, $0fd0030e, $ecc8c73e,
|
||||
$a4751e41, $e238cd99, $3bea0e2f, $3280bba1, $183eb331, $4e548b38, $4f6db908,
|
||||
$6f420d03, $f60a04bf, $2cb81290, $24977c79, $5679b072, $bcaf89af, $de9a771f,
|
||||
$d9930810, $b38bae12, $dccf3f2e, $5512721f, $2e6b7124, $501adde6, $9f84cd87,
|
||||
$7a584718, $7408da17, $bc9f9abc, $e94b7d8c, $ec7aec3a, $db851dfa, $63094366,
|
||||
$c464c3d2, $ef1c1847, $3215d908, $dd433b37, $24c2ba16, $12a14d43, $2a65c451,
|
||||
$50940002, $133ae4dd, $71dff89e, $10314e55, $81ac77d6, $5f11199b, $043556f1,
|
||||
$d7a3c76b, $3c11183b, $5924a509, $f28fe6ed, $97f1fbfa, $9ebabf2c, $1e153c6e,
|
||||
$86e34570, $eae96fb1, $860e5e0a, $5a3e2ab3, $771fe71c, $4e3d06fa, $2965dcb9,
|
||||
$99e71d0f, $803e89d6, $5266c825, $2e4cc978, $9c10b36a, $c6150eba, $94e2ea78,
|
||||
$a5fc3c53, $1e0a2df4, $f2f74ea7, $361d2b3d, $1939260f, $19c27960, $5223a708,
|
||||
$f71312b6, $ebadfe6e, $eac31f66, $e3bc4595, $a67bc883, $b17f37d1, $018cff28,
|
||||
$c332ddef, $be6c5aa5, $65582185, $68ab9802, $eecea50f, $db2f953b, $2aef7dad,
|
||||
$5b6e2f84, $1521b628, $29076170, $ecdd4775, $619f1510, $13cca830, $eb61bd96,
|
||||
$0334fe1e, $aa0363cf, $b5735c90, $4c70a239, $d59e9e0b, $cbaade14, $eecc86bc,
|
||||
$60622ca7, $9cab5cab, $b2f3846e, $648b1eaf, $19bdf0ca, $a02369b9, $655abb50,
|
||||
$40685a32, $3c2ab4b3, $319ee9d5, $c021b8f7, $9b540b19, $875fa099, $95f7997e,
|
||||
$623d7da8, $f837889a, $97e32d77, $11ed935f, $16681281, $0e358829, $c7e61fd6,
|
||||
$96dedfa1, $7858ba99, $57f584a5, $1b227263, $9b83c3ff, $1ac24696, $cdb30aeb,
|
||||
$532e3054, $8fd948e4, $6dbc3128, $58ebf2ef, $34c6ffea, $fe28ed61, $ee7c3c73,
|
||||
$5d4a14d9, $e864b7e3, $42105d14, $203e13e0, $45eee2b6, $a3aaabea, $db6c4f15,
|
||||
$facb4fd0, $c742f442, $ef6abbb5, $654f3b1d, $41cd2105, $d81e799e, $86854dc7,
|
||||
$e44b476a, $3d816250, $cf62a1f2, $5b8d2646, $fc8883a0, $c1c7b6a3, $7f1524c3,
|
||||
$69cb7492, $47848a0b, $5692b285, $095bbf00, $ad19489d, $1462b174, $23820e00,
|
||||
$58428d2a, $0c55f5ea, $1dadf43e, $233f7061, $3372f092, $8d937e41, $d65fecf1,
|
||||
$6c223bdb, $7cde3759, $cbee7460, $4085f2a7, $ce77326e, $a6078084, $19f8509e,
|
||||
$e8efd855, $61d99735, $a969a7aa, $c50c06c2, $5a04abfc, $800bcadc, $9e447a2e,
|
||||
$c3453484, $fdd56705, $0e1e9ec9, $db73dbd3, $105588cd, $675fda79, $e3674340,
|
||||
$c5c43465, $713e38d8, $3d28f89e, $f16dff20, $153e21e7, $8fb03d4a, $e6e39f2b,
|
||||
$db83adf7, $e93d5a68, $948140f7, $f64c261c, $94692934, $411520f7, $7602d4f7,
|
||||
$bcf46b2e, $d4a20068, $d4082471, $3320f46a, $43b7d4b7, $500061af, $1e39f62e,
|
||||
$97244546, $14214f74, $bf8b8840, $4d95fc1d, $96b591af, $70f4ddd3, $66a02f45,
|
||||
$bfbc09ec, $03bd9785, $7fac6dd0, $31cb8504, $96eb27b3, $55fd3941, $da2547e6,
|
||||
$abca0a9a, $28507825, $530429f4, $0a2c86da, $e9b66dfb, $68dc1462, $d7486900,
|
||||
$680ec0a4, $27a18dee, $4f3ffea2, $e887ad8c, $b58ce006, $7af4d6b6, $aace1e7c,
|
||||
$d3375fec, $ce78a399, $406b2a42, $20fe9e35, $d9f385b9, $ee39d7ab, $3b124e8b,
|
||||
$1dc9faf7, $4b6d1856, $26a36631, $eae397b2, $3a6efa74, $dd5b4332, $6841e7f7,
|
||||
$ca7820fb, $fb0af54e, $d8feb397, $454056ac, $ba489527, $55533a3a, $20838d87,
|
||||
$fe6ba9b7, $d096954b, $55a867bc, $a1159a58, $cca92963, $99e1db33, $a62a4a56,
|
||||
$3f3125f9, $5ef47e1c, $9029317c, $fdf8e802, $04272f70, $80bb155c, $05282ce3,
|
||||
$95c11548, $e4c66d22, $48c1133f, $c70f86dc, $07f9c9ee, $41041f0f, $404779a4,
|
||||
$5d886e17, $325f51eb, $d59bc0d1, $f2bcc18f, $41113564, $257b7834, $602a9c60,
|
||||
$dff8e8a3, $1f636c1b, $0e12b4c2, $02e1329e, $af664fd1, $cad18115, $6b2395e0,
|
||||
$333e92e1, $3b240b62, $eebeb922, $85b2a20e, $e6ba0d99, $de720c8c, $2da2f728,
|
||||
$d0127845, $95b794fd, $647d0862, $e7ccf5f0, $5449a36f, $877d48fa, $c39dfd27,
|
||||
$f33e8d1e, $0a476341, $992eff74, $3a6f6eab, $f4f8fd37, $a812dc60, $a1ebddf8,
|
||||
$991be14c, $db6e6b0d, $c67b5510, $6d672c37, $2765d43b, $dcd0e804, $f1290dc7,
|
||||
$cc00ffa3, $b5390f92, $690fed0b, $667b9ffb, $cedb7d9c, $a091cf0b, $d9155ea3,
|
||||
$bb132f88, $515bad24, $7b9479bf, $763bd6eb, $37392eb3, $cc115979, $8026e297,
|
||||
$f42e312d, $6842ada7, $c66a2b3b, $12754ccc, $782ef11c, $6a124237, $b79251e7,
|
||||
$06a1bbe6, $4bfb6350, $1a6b1018, $11caedfa, $3d25bdd8, $e2e1c3c9, $44421659,
|
||||
$0a121386, $d90cec6e, $d5abea2a, $64af674e, $da86a85f, $bebfe988, $64e4c3fe,
|
||||
$9dbc8057, $f0f7c086, $60787bf8, $6003604d, $d1fd8346, $f6381fb0, $7745ae04,
|
||||
$d736fccc, $83426b33, $f01eab71, $b0804187, $3c005e5f, $77a057be, $bde8ae24,
|
||||
$55464299, $bf582e61, $4e58f48f, $f2ddfda2, $f474ef38, $8789bdc2, $5366f9c3,
|
||||
$c8b38e74, $b475f255, $46fcd9b9, $7aeb2661, $8b1ddf84, $846a0e79, $915f95e2,
|
||||
$466e598e, $20b45770, $8cd55591, $c902de4c, $b90bace1, $bb8205d0, $11a86248,
|
||||
$7574a99e, $b77f19b6, $e0a9dc09, $662d09a1, $c4324633, $e85a1f02, $09f0be8c,
|
||||
$4a99a025, $1d6efe10, $1ab93d1d, $0ba5a4df, $a186f20f, $2868f169, $dcb7da83,
|
||||
$573906fe, $a1e2ce9b, $4fcd7f52, $50115e01, $a70683fa, $a002b5c4, $0de6d027,
|
||||
$9af88c27, $773f8641, $c3604c06, $61a806b5, $f0177a28, $c0f586e0, $006058aa,
|
||||
$30dc7d62, $11e69ed7, $2338ea63, $53c2dd94, $c2c21634, $bbcbee56, $90bcb6de,
|
||||
$ebfc7da1, $ce591d76, $6f05e409, $4b7c0188, $39720a3d, $7c927c24, $86e3725f,
|
||||
$724d9db9, $1ac15bb4, $d39eb8fc, $ed545578, $08fca5b5, $d83d7cd3, $4dad0fc4,
|
||||
$1e50ef5e, $b161e6f8, $a28514d9, $6c51133c, $6fd5c7e7, $56e14ec4, $362abfce,
|
||||
$ddc6c837, $d79a3234, $92638212, $670efa8e, $406000e0, $3a39ce37, $d3faf5cf,
|
||||
$abc27737, $5ac52d1b, $5cb0679e, $4fa33742, $d3822740, $99bc9bbe, $d5118e9d,
|
||||
$bf0f7315, $d62d1c7e, $c700c47b, $b78c1b6b, $21a19045, $b26eb1be, $6a366eb4,
|
||||
$5748ab2f, $bc946e79, $c6a376d2, $6549c2c8, $530ff8ee, $468dde7d, $d5730a1d,
|
||||
$4cd04dc6, $2939bbdb, $a9ba4650, $ac9526e8, $be5ee304, $a1fad5f0, $6a2d519a,
|
||||
$63ef8ce2, $9a86ee22, $c089c2b8, $43242ef6, $a51e03aa, $9cf2d0a4, $83c061ba,
|
||||
$9be96a4d, $8fe51550, $ba645bd6, $2826a2f9, $a73a3ae1, $4ba99586, $ef5562e9,
|
||||
$c72fefd3, $f752f7da, $3f046f69, $77fa0a59, $80e4a915, $87b08601, $9b09e6ad,
|
||||
$3b3ee593, $e990fd5a, $9e34d797, $2cf0b7d9, $022b8b51, $96d5ac3a, $017da67d,
|
||||
$d1cf3ed6, $7c7d2d28, $1f9f25cf, $adf2b89b, $5ad6b472, $5a88f54c, $e029ac71,
|
||||
$e019a5e6, $47b0acfd, $ed93fa9b, $e8d3c48d, $283b57cc, $f8d56629, $79132e28,
|
||||
$785f0191, $ed756055, $f7960e44, $e3d35e8c, $15056dd4, $88f46dba, $03a16125,
|
||||
$0564f0bd, $c3eb9e15, $3c9057a2, $97271aec, $a93a072a, $1b3f6d9b, $1e6321f5,
|
||||
$f59c66fb, $26dcf319, $7533d928, $b155fdf5, $03563482, $8aba3cbb, $28517711,
|
||||
$c20ad9f8, $abcc5167, $ccad925f, $4de81751, $3830dc8e, $379d5862, $9320f991,
|
||||
$ea7a90c2, $fb3e7bce, $5121ce64, $774fbe32, $a8b6e37e, $c3293d46, $48de5369,
|
||||
$6413e680, $a2ae0810, $dd6db224, $69852dfd, $09072166, $b39a460a, $6445c0dd,
|
||||
$586cdecf, $1c20c8ae, $5bbef7dd, $1b588d40, $ccd2017f, $6bb4e3bb, $dda26a7e,
|
||||
$3a59ff45, $3e350a44, $bcb4cdd5, $72eacea8, $fa6484bb, $8d6612ae, $bf3c6f47,
|
||||
$d29be463, $542f5d9e, $aec2771b, $f64e6370, $740e0d8d, $e75b1357, $f8721671,
|
||||
$af537d5d, $4040cb08, $4eb4e2cc, $34d2466a, $0115af84, $e1b00428, $95983a1d,
|
||||
$06b89fb4, $ce6ea048, $6f3f3b82, $3520ab82, $011a1d4b, $277227f8, $611560b1,
|
||||
$e7933fdc, $bb3a792b, $344525bd, $a08839e1, $51ce794b, $2f32c9b7, $a01fbac9,
|
||||
$e01cc87e, $bcc7d1f6, $cf0111c3, $a1e8aac7, $1a908749, $d44fbd9a, $d0dadecb,
|
||||
$d50ada38, $0339c32a, $c6913667, $8df9317c, $e0b12b4f, $f79e59b7, $43f5bb3a,
|
||||
$f2d519ff, $27d9459c, $bf97222c, $15e6fc2a, $0f91fc71, $9b941525, $fae59361,
|
||||
$ceb69ceb, $c2a86459, $12baa8d1, $b6c1075e, $e3056a0c, $10d25065, $cb03a442,
|
||||
$e0ec6e0e, $1698db3b, $4c98a0be, $3278e964, $9f1f9532, $e0d392df, $d3a0342b,
|
||||
$8971f21e, $1b0a7441, $4ba3348c, $c5be7120, $c37632d8, $df359f8d, $9b992f2e,
|
||||
$e60b6f47, $0fe3f11d, $e54cda54, $1edad891, $ce6279cf, $cd3e7e6f, $1618b166,
|
||||
$fd2c1d05, $848fd2c5, $f6fb2299, $f523f357, $a6327623, $93a83531, $56cccd02,
|
||||
$acf08162, $5a75ebb5, $6e163697, $88d273cc, $de966292, $81b949d0, $4c50901b,
|
||||
$71c65614, $e6c6c7bd, $327a140a, $45e1d006, $c3f27b9a, $c9aa53fd, $62a80f00,
|
||||
$bb25bfe2, $35bdd2f6, $71126905, $b2040222, $b6cbcf7c, $cd769c2b, $53113ec0,
|
||||
$1640e3d3, $38abbd60, $2547adf0, $ba38209c, $f746ce76, $77afa1c5, $20756060,
|
||||
$85cbfe4e, $8ae88dd8, $7aaaf9b0, $4cf9aa7e, $1948c25c, $02fb8a8c, $01c36ae4,
|
||||
$d6ebe1f9, $90d4f869, $a65cdea0, $3f09252d, $c208e69f, $b74e6132, $ce77e25b,
|
||||
$578fdfe3, $3ac372e6
|
||||
);
|
||||
|
||||
MagicText: array[0..5] of DWord = (
|
||||
$4f727068, $65616e42, $65686f6c, $64657253, $63727944, $6f756274
|
||||
);
|
||||
|
||||
BsdBase64EncodeTable: array[0..63] of char =
|
||||
{ 0:} './' +
|
||||
{ 2:} 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' +
|
||||
{28:} 'abcdefghijklmnopqrstuvwxyz' +
|
||||
{54:} '0123456789';
|
||||
|
||||
BsdBase64DecodeTable: array[#0..#127] of integer = (
|
||||
// ________________
|
||||
{ 0:} -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
|
||||
// ________________
|
||||
{ 16:} -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1,
|
||||
// ______________./
|
||||
{ 32:} -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, 0, 1,
|
||||
// 0123456789______
|
||||
{ 48:} 54, 55, 56, 57, 58, 59, 60, 61, 62, 63, -1, -1, -1, -1, -1, -1,
|
||||
// _ABCDEFGHIJKLMNO
|
||||
{ 64:} -1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16,
|
||||
// PQRSTUVWXYZ_____
|
||||
{ 80:} 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, -1, -1, -1, -1, -1,
|
||||
// _abcdefghijklmno
|
||||
{ 96:} -1, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42,
|
||||
// pqrstuvwxyz_____
|
||||
{113:} 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53, -1, -1, -1, -1, -1
|
||||
);
|
||||
|
||||
type
|
||||
THashTypes = (bcDefault, bcPHP, bcBSD, bcUnknown);
|
||||
RTPasswordInformation = Object
|
||||
Algo : THashTypes;
|
||||
Cost : Word;
|
||||
AlgoName,
|
||||
BCryptSalt,
|
||||
BCryptHash : AnsiString;
|
||||
end;
|
||||
|
||||
EHash = class(EArgumentException);
|
||||
|
||||
TBCryptHash = class(TObject)
|
||||
private
|
||||
FSBox: array[0..1023] of DWord;
|
||||
FPBox: array[0..17] of DWord;
|
||||
function BsdBase64Encode(const RawByteData: TBytes; CharacterLength: Sizeint): AnsiString;
|
||||
function BsdBase64Decode(const EncodedString : AnsiString): TBytes;
|
||||
function Crypt(const Password, Salt : AnsiString; Cost : Byte; HashType : THashTypes) : AnsiString;
|
||||
function CryptRaw(const HashKey, Salt: TBytes; Cost : Byte): TBytes;
|
||||
procedure EKSKey(const Salt, HashKey: TBytes);
|
||||
procedure Encipher(var lr: array of DWord; const offset: SizeInt);
|
||||
function FormatPasswordHash(const Salt, Hash: TBytes; Cost : Byte; HashType : THashTypes): AnsiString;
|
||||
function getRandomBlockFileName : AnsiString;
|
||||
procedure InitializeKey();
|
||||
function isBSDAlphabet(CurrentCharacter : Char) : Boolean;
|
||||
function MakeSalt : TBytes;
|
||||
function MTRandomBytes(NumberOfBytes : SizeUInt) : AnsiString;
|
||||
procedure NKey(const HashKey: TBytes);
|
||||
function osHasRandomBlock : Boolean;
|
||||
function osHasURandomBlock : Boolean;
|
||||
function ResolveHashType(const HashType : AnsiString) : THashTypes;
|
||||
function StreamToWord(const RawByteData: TBytes; var offset: SizeInt): DWord;
|
||||
function UnixRandomBytes(NumberOfBytes : SizeUInt) : AnsiString;
|
||||
public
|
||||
constructor Create; overload;
|
||||
destructor Destroy; override;
|
||||
function CreateHash(const Password : AnsiString) : AnsiString; overload;
|
||||
function CreateHash(const Password : AnsiString; HashType : THashTypes) : AnsiString; overload;
|
||||
function CreateHash(const Password : AnsiString; HashType : THashTypes; Cost : Byte) : AnsiString; overload;
|
||||
function VerifyHash(const Password, Hash : AnsiString) : Boolean;
|
||||
function NeedsRehash(const BCryptHash : AnsiString) : Boolean; overload;
|
||||
function NeedsRehash(const BCryptHash : AnsiString; Cost : Byte) : Boolean; overload;
|
||||
function HashGetInfo(const Hash : AnsiString) : RTPasswordInformation;
|
||||
end;
|
||||
|
||||
implementation
|
||||
|
||||
uses
|
||||
Math,
|
||||
RegExpr;
|
||||
|
||||
constructor TBCryptHash.Create;
|
||||
begin
|
||||
inherited Create;
|
||||
end;
|
||||
|
||||
destructor TBCryptHash.Destroy;
|
||||
begin
|
||||
inherited Destroy;
|
||||
end;
|
||||
|
||||
function TBCryptHash.BsdBase64Decode(const EncodedString : AnsiString): TBytes;
|
||||
|
||||
function Char64(Character: AnsiChar): Sizeint;
|
||||
begin
|
||||
if Ord(Character) > Length(BsdBase64DecodeTable) then
|
||||
begin
|
||||
Result := -1;
|
||||
end
|
||||
else begin
|
||||
Result := BsdBase64DecodeTable[Character];
|
||||
end;
|
||||
end; { Char64 }
|
||||
|
||||
procedure Append(Value: Byte);
|
||||
var
|
||||
i: SizeUint;
|
||||
begin
|
||||
i := Length(Result);
|
||||
SetLength(Result, i + 1);
|
||||
Result[i] := Value;
|
||||
end; { Append }
|
||||
|
||||
var
|
||||
i,
|
||||
EncodedStringLength,
|
||||
c1, c2, c3, c4: Sizeint;
|
||||
|
||||
begin
|
||||
SetLength(Result, 0);
|
||||
i := 1;
|
||||
EncodedStringLength := Length(EncodedString);
|
||||
while (i < EncodedStringLength) and (Length(Result) < BCRYPT_SALT_LEN) do
|
||||
begin
|
||||
c1 := Char64(EncodedString[i]);
|
||||
Inc(i);
|
||||
c2 := Char64(EncodedString[i]);
|
||||
Inc(i);
|
||||
if (c1 = -1) or (c2 = -1) then
|
||||
begin
|
||||
Exit;
|
||||
end;
|
||||
|
||||
{
|
||||
Now we have at least one byte in c1|c2
|
||||
c1 = ..111111
|
||||
c2 = ..112222
|
||||
}
|
||||
Append((c1 shl 2) or ((c2 and $30) shr 4));
|
||||
//If there's a 3rd character, then we can use c2|c3 to form the second byte
|
||||
if (i > EncodedStringLength) or (Length(Result) >= BCRYPT_SALT_LEN) then
|
||||
begin
|
||||
Break;
|
||||
end;
|
||||
|
||||
c3 := Char64(EncodedString[i]);
|
||||
Inc(i);
|
||||
if (c3 = -1) then
|
||||
begin
|
||||
Exit;
|
||||
end;
|
||||
|
||||
{
|
||||
Now we have the next byte in c2|c3
|
||||
c2 = ..112222
|
||||
c3 = ..222233
|
||||
}
|
||||
Append(((c2 and $0f) shl 4) or ((c3 and $3c) shr 2));
|
||||
//If there's a 4th caracter, then we can use c3|c4 to form the third byte
|
||||
if (i > EncodedStringLength) or (Length(Result) >= BCRYPT_SALT_LEN) then
|
||||
begin
|
||||
Break;
|
||||
end;
|
||||
|
||||
c4 := Char64(EncodedString[i]);
|
||||
Inc(i);
|
||||
if c4 = -1 then
|
||||
begin
|
||||
Exit;
|
||||
end;
|
||||
|
||||
{
|
||||
Now we have the next byte in c3|c4
|
||||
c3 = ..222233
|
||||
c4 = ..333333
|
||||
}
|
||||
Append(((c3 and $03) shl 6) or c4);
|
||||
end; { While }
|
||||
end; { TBCryptHash.BsdBase64Decode }
|
||||
|
||||
function TBCryptHash.BsdBase64Encode(const RawByteData: TBytes; CharacterLength: Sizeint): AnsiString;
|
||||
var
|
||||
i,
|
||||
b1, b2: SizeInt;
|
||||
begin
|
||||
Result := '';
|
||||
if (CharacterLength <= 0) or (CharacterLength > Length(RawByteData)) then
|
||||
begin
|
||||
Exit;
|
||||
end;
|
||||
|
||||
i := 0;
|
||||
while i < CharacterLength do
|
||||
begin
|
||||
b1 := RawByteData[i] and $ff;
|
||||
Inc(i);
|
||||
|
||||
Result := Result + BsdBase64EncodeTable[(b1 shr 2) and $3f];
|
||||
b1 := (b1 and $03) shl 4;
|
||||
if i >= CharacterLength then
|
||||
begin
|
||||
Result := Result + BsdBase64EncodeTable[b1 and $3f];
|
||||
Exit;
|
||||
end;
|
||||
|
||||
b2 := RawByteData[i] and $ff;
|
||||
Inc(i);
|
||||
b1 := b1 or ((b2 shr 4) and $0f);
|
||||
|
||||
Result := Result + BsdBase64EncodeTable[b1 and $3f];
|
||||
b1 := (b2 and $0f) shl 2;
|
||||
if i >= CharacterLength then
|
||||
begin
|
||||
Result := Result + BsdBase64EncodeTable[b1 and $3f];
|
||||
Exit;
|
||||
end;
|
||||
|
||||
b2 := RawByteData[i] and $ff;
|
||||
Inc(i);
|
||||
b1 := b1 or ((b2 shr 6) and $03);
|
||||
Result := Result + BsdBase64EncodeTable[b1 and $3f];
|
||||
Result := Result + BsdBase64EncodeTable[b2 and $3f];
|
||||
end;
|
||||
end; { TBCryptHash.BsdBase64Encode }
|
||||
|
||||
function TBCryptHash.CryptRaw(const HashKey, Salt: TBytes; Cost : Byte): TBytes;
|
||||
var
|
||||
CryptData: array[0..5] of DWord;
|
||||
CryptLength: integer;
|
||||
BCryptRounds: DWord;
|
||||
i, j: SizeInt;
|
||||
begin
|
||||
Move(MagicText[0], CryptData[0], Sizeof(MagicText));
|
||||
CryptLength := Length(CryptData);
|
||||
BCryptRounds := 1 shl Cost;
|
||||
InitializeKey();
|
||||
EKSKey(Salt, HashKey);
|
||||
|
||||
for i := 1 to BCryptRounds do
|
||||
begin
|
||||
NKey(HashKey);
|
||||
NKey(Salt);
|
||||
end;
|
||||
|
||||
for i := 1 to 64 do
|
||||
begin
|
||||
for j := 0 to (CryptLength shr 1) - 1 do
|
||||
begin
|
||||
Encipher(CryptData, j shl 1);
|
||||
end;
|
||||
end;
|
||||
|
||||
SetLength(Result, CryptLength * 4);
|
||||
j := 0;
|
||||
for i := 0 to CryptLength - 1 do
|
||||
begin
|
||||
Result[j] := (CryptData[i] shr 24) and $FF;
|
||||
Inc(j);
|
||||
Result[j] := (CryptData[i] shr 16) and $FF;
|
||||
Inc(j);
|
||||
Result[j] := (CryptData[i] shr 8) and $FF;
|
||||
Inc(j);
|
||||
Result[j] := CryptData[i] and $FF;
|
||||
Inc(j);
|
||||
end;
|
||||
end; { TBCryptHash.CryptRaw }
|
||||
|
||||
procedure TBCryptHash.EKSKey(const Salt, HashKey: TBytes);
|
||||
var
|
||||
lr: array[0..1] of DWord;
|
||||
i, passwordOffset, saltOffset, PLen, SLen: SizeInt;
|
||||
begin
|
||||
passwordOffset := 0;
|
||||
saltOffset := 0;
|
||||
PLen := Length(FPBox);
|
||||
SLen := Length(FSBox);
|
||||
lr[0] := 0;
|
||||
lr[1] := 0;
|
||||
|
||||
for i := 0 to PLen - 1 do
|
||||
begin
|
||||
FPBox[i] := FPBox[i] xor StreamToWord(HashKey, passwordOffset);
|
||||
end;
|
||||
for i := 0 to (PLen div 2) - 1 do
|
||||
begin
|
||||
lr[0] := lr[0] xor StreamToWord(Salt, saltOffset);
|
||||
lr[1] := lr[1] xor StreamToWord(Salt, saltOffset);
|
||||
Encipher(lr, 0);
|
||||
FPBox[2 * i] := lr[0];
|
||||
FPBox[2 * i + 1] := lr[1];
|
||||
end;
|
||||
for i := 0 to (SLen div 2) - 1 do
|
||||
begin
|
||||
lr[0] := lr[0] xor StreamToWord(Salt, saltOffset);
|
||||
lr[1] := lr[1] xor StreamToWord(Salt, saltOffset);
|
||||
Encipher(lr, 0);
|
||||
FSBox[2 * i] := lr[0];
|
||||
FSBox[2 * i + 1] := lr[1];
|
||||
end;
|
||||
end; { TBCryptHash.EKSKey }
|
||||
|
||||
{$OVERFLOWCHECKS OFF}
|
||||
procedure TBCryptHash.Encipher(var lr: array of DWord; const offset: SizeInt);
|
||||
var
|
||||
i, n, block, r: DWord;
|
||||
begin
|
||||
block := lr[offset];
|
||||
r := lr[offset + 1];
|
||||
block := block xor FPBox[0];
|
||||
i := 1;
|
||||
while i <= BLOWFISH_NUM_ROUNDS - 1 do
|
||||
begin
|
||||
n := FSBox[(block shr 24) and $FF];
|
||||
n := n + FSBox[$100 or ((block shr 16) and $FF)];
|
||||
n := n xor FSBox[$200 or ((block shr 8) and $FF)];
|
||||
n := n + FSBox[$300 or (block and $FF)];
|
||||
r := r xor (n xor FPBox[i]);
|
||||
Inc(i);
|
||||
|
||||
n := FSBox[(r shr 24) and $FF];
|
||||
n := n + FSBox[$100 or ((r shr 16) and $FF)];
|
||||
n := n xor FSBox[$200 or ((r shr 8) and $FF)];
|
||||
n := n + FSBox[$300 or (r and $FF)];
|
||||
block := block xor (n xor FPBox[i]);
|
||||
Inc(i);
|
||||
end;
|
||||
lr[offset] := r xor FPBox[BLOWFISH_NUM_ROUNDS + 1];
|
||||
lr[offset + 1] := block;
|
||||
end;
|
||||
{$OVERFLOWCHECKS ON}
|
||||
|
||||
function TBCryptHash.FormatPasswordHash(const Salt, Hash: TBytes; Cost : Byte; HashType : THashTypes): AnsiString;
|
||||
var
|
||||
saltString: ansistring;
|
||||
hashString: ansistring;
|
||||
HashPrefix : AnsiString;
|
||||
begin
|
||||
case HashType of
|
||||
bcBSD : begin
|
||||
HashPrefix := '2a';
|
||||
end;
|
||||
bcPHP,bcDefault : begin
|
||||
HashPrefix := '2y';
|
||||
end;
|
||||
end;
|
||||
saltString := BsdBase64Encode(Salt, Length(Salt));
|
||||
hashString := BsdBase64Encode(Hash, Length(MagicText) * 4 - 1);
|
||||
Result := Format('$%s$%d$%s%s', [HashPrefix, Cost, saltString, hashString]);
|
||||
end;
|
||||
|
||||
function TBCryptHash.getRandomBlockFileName : AnsiString;
|
||||
var
|
||||
OSRandomBlockFileName : PAnsiString;
|
||||
begin
|
||||
OSRandomBlockFileName := NewStr(Space(12));
|
||||
SetLength(OSRandomBlockFileName^, 12);
|
||||
if osHasURandomBlock then
|
||||
begin
|
||||
AssignStr(OSRandomBlockFileName, '/dev/urandom');
|
||||
end
|
||||
else if osHasRandomBlock then
|
||||
begin
|
||||
AssignStr(OSRandomBlockFileName,'/dev/random');
|
||||
end;
|
||||
Result := OSRandomBlockFileName^;
|
||||
DisposeStr(OSRandomBlockFileName);
|
||||
end; { TBCryptHash.getRandomBlockFileName }
|
||||
|
||||
procedure TBCryptHash.InitializeKey();
|
||||
begin
|
||||
Move(SBoxOrg, FSBox, Sizeof(FSBox));
|
||||
Move(PBoxOrg, FPBox, Sizeof(FPBox));
|
||||
end; { TBCryptHash.InitializeKey }
|
||||
|
||||
function TBCryptHash.isBSDAlphabet(CurrentCharacter : Char) : Boolean;
|
||||
begin
|
||||
Result := CurrentCharacter in ['.','/','a'..'z', 'A'..'Z', '0'..'9'];
|
||||
end; { TBCryptHash.isBSDAlphabet }
|
||||
|
||||
function TBCryptHash.MTRandomBytes(NumberOfBytes : SizeUInt) : AnsiString;
|
||||
var
|
||||
RandomByteString : AnsiString;
|
||||
Count : SizeUint;
|
||||
WorkingByte : sizeUInt;
|
||||
begin
|
||||
Count := 1;
|
||||
WorkingByte := 0;
|
||||
SetLength(RandomByteString, (NumberOfBytes * 2) +1);
|
||||
|
||||
Randomize;
|
||||
while Count <= (NumberOfBytes * 2) do
|
||||
begin
|
||||
{ ???: Replace this with internal Windows CryptGenRandom function
|
||||
when I get ahold of a Windows machine. }
|
||||
WorkingByte := WorkingByte or RandomRange(1000000, Maxint) xor RandomRange(10000, Maxint);
|
||||
RandomByteString[Count] := Chr(WorkingByte mod 256);
|
||||
Inc(Count);
|
||||
end;
|
||||
SetLength(RandomByteString, NumberOfBytes);
|
||||
Result := RandomByteString;
|
||||
end; { TBCryptHash.MTRandomBytes }
|
||||
|
||||
procedure TBCryptHash.NKey(const HashKey: TBytes);
|
||||
var
|
||||
lr: array[0..1] of DWord;
|
||||
i, passwordOffset, PLen, SLen: SizeInt;
|
||||
begin
|
||||
passwordOffset := 0;
|
||||
PLen := Length(FPBox);
|
||||
SLen := Length(FSBox);
|
||||
lr[0] := 0;
|
||||
lr[1] := 0;
|
||||
|
||||
for i := 0 to PLen - 1 do
|
||||
begin
|
||||
FPBox[i] := FPBox[i] xor StreamToWord(HashKey, passwordOffset);
|
||||
end;
|
||||
for i := 0 to (PLen div 2) - 1 do
|
||||
begin
|
||||
Encipher(lr, 0);
|
||||
FPBox[2 * i] := lr[0];
|
||||
FPBox[2 * i + 1] := lr[1];
|
||||
end;
|
||||
for i := 0 to (SLen div 2) - 1 do
|
||||
begin
|
||||
Encipher(lr, 0);
|
||||
FSBox[2 * i] := lr[0];
|
||||
FSBox[2 * i + 1] := lr[1];
|
||||
end;
|
||||
end; { TBCryptHash.NKey }
|
||||
|
||||
function TBCryptHash.osHasRandomBlock : Boolean;
|
||||
begin
|
||||
osHasRandomBlock := FileExists('/dev/random');
|
||||
end; { TBCryptHash.osHasRandomBlock }
|
||||
|
||||
function TBCryptHash.osHasURandomBlock : Boolean;
|
||||
begin
|
||||
osHasURandomBlock := FileExists('/dev/urandom');
|
||||
end; { TBCryptHash.osHasURandomBlock }
|
||||
|
||||
function TBCryptHash.MakeSalt : TBytes;
|
||||
var
|
||||
ByteArray: TBytes;
|
||||
RandomTempString : AnsiString;
|
||||
i : SizeInt;
|
||||
begin
|
||||
SetLength(RandomTempString, 17);
|
||||
SetLength(ByteArray, 16);
|
||||
{$IFDEF UNIX}
|
||||
RandomTempString := UnixRandomBytes(BCRYPT_SALT_LEN);
|
||||
{$ELSE}
|
||||
Randomize;
|
||||
RandomTempString := MTRandomBytes(BCRYPT_SALT_LEN);
|
||||
{$ENDIF}
|
||||
i := 0;
|
||||
while i <= Length(RandomTempString) do
|
||||
begin
|
||||
ByteArray[i] := Ord(RandomTempString[i+1]);
|
||||
Inc(i);
|
||||
end;
|
||||
SetLength(ByteArray, 16);
|
||||
Result := ByteArray;
|
||||
end;
|
||||
|
||||
function TBCryptHash.StreamToWord(const RawByteData: TBytes; var offset: SizeInt): DWord;
|
||||
var
|
||||
i: SizeInt;
|
||||
begin
|
||||
Result := 0;
|
||||
for i := 1 to 4 do
|
||||
begin
|
||||
Result := (Result shl 8) or (RawByteData[offset] and $FF);
|
||||
offset := (offset + 1) mod Length(RawByteData);
|
||||
end;
|
||||
end; { TBCryptHash.StreamToWord }
|
||||
|
||||
function TBCryptHash.UnixRandomBytes(NumberOfBytes : SizeUInt) : AnsiString;
|
||||
var
|
||||
OSRandomBlockFileName : AnsiString;
|
||||
RandomFileStream : TFileStream;
|
||||
RandomFileBuffer : AnsiString;
|
||||
FileBytesRead : SizeUInt;
|
||||
begin
|
||||
SetLength(OSRandomBlockFileName, 13);
|
||||
OSRandomBlockFileName := getRandomBlockFileName;
|
||||
SetLength(RandomFileBuffer, (NumberOfBytes * 2));
|
||||
try
|
||||
RandomFileStream := TFileStream.Create(OSRandomBlockFileName, fmOpenRead);
|
||||
RandomFileStream.Position := 0;
|
||||
FileBytesRead := 1;
|
||||
|
||||
while FileBytesRead <= (NumberOfBytes * 2) do
|
||||
begin
|
||||
RandomFileStream.Read(RandomFileBuffer[FileBytesRead], 1);
|
||||
Inc(FileBytesRead);
|
||||
end;
|
||||
except
|
||||
on E:Exception do
|
||||
writeln('File : ', OSRandomBlockFileName, ' could not be read or written because: ', E.Message);
|
||||
end;
|
||||
|
||||
SetLength(RandomFileBuffer, NumberOfBytes);
|
||||
RandomFileStream.Free;
|
||||
Result := RandomFileBuffer;
|
||||
end; { TBCryptHash.unixRandomBytes }
|
||||
|
||||
function TBCryptHash.CreateHash(const Password : AnsiString) : AnsiString; overload;
|
||||
begin
|
||||
Result := CreateHash(Password, bcPHP, BCRYPT_DEFAULT_COST);
|
||||
end;
|
||||
function TBCryptHash.CreateHash(const Password : AnsiString; HashType : THashTypes) : AnsiString; overload;
|
||||
begin
|
||||
Result := CreateHash(Password, HashType, BCRYPT_DEFAULT_COST);
|
||||
end; { TBCryptHash.CreateHash }
|
||||
|
||||
function TBCryptHash.CreateHash(const Password : AnsiString; HashType : THashTypes; Cost : Byte) : AnsiString; overload;
|
||||
var
|
||||
PasswordKey,
|
||||
SaltBytes,
|
||||
Hash : TBytes;
|
||||
begin
|
||||
if (Cost < 10) or (Cost > 30) then
|
||||
begin
|
||||
raise Exception.Create('Invalid value for cost. It must be between 10 and 30.');
|
||||
end;
|
||||
SetLength(PasswordKey, Length(Password) + 1);
|
||||
Move(Password[1], PasswordKey[0], Length(Password));
|
||||
PasswordKey[High(PasswordKey)] := 0;
|
||||
SaltBytes := MakeSalt;
|
||||
Hash := CryptRaw(PasswordKey, SaltBytes, Cost);
|
||||
Result := FormatPasswordHash(SaltBytes, Hash, Cost, HashType);
|
||||
end; { TBCryptHash.CreateHash }
|
||||
|
||||
function TBCryptHash.Crypt(const Password, Salt : AnsiString; Cost : Byte; HashType : THashTypes) : AnsiString;
|
||||
var
|
||||
PasswordKey,
|
||||
SaltBytes,
|
||||
Hash : TBytes;
|
||||
begin
|
||||
SetLength(PasswordKey, Length(Password) +1);
|
||||
Move(Password[1], PasswordKey[0], Length(Password));
|
||||
PasswordKey[High(PasswordKey)] := 0;
|
||||
saltBytes := BsdBase64Decode(Salt);
|
||||
|
||||
Hash := CryptRaw(PasswordKey, SaltBytes, Cost);
|
||||
Result := FormatPasswordHash(SaltBytes, Hash, Cost, HashType);
|
||||
end;
|
||||
|
||||
function TBCryptHash.ResolveHashType(const HashType : AnsiString) : THashTypes;
|
||||
begin
|
||||
case HashType of
|
||||
'$2y$': begin
|
||||
Result := (bcPHP);
|
||||
end;
|
||||
'$2a$': begin
|
||||
Result := (bcBSD);
|
||||
end;
|
||||
else
|
||||
begin
|
||||
Result := (bcPHP);
|
||||
end;
|
||||
end;
|
||||
end;
|
||||
|
||||
function TBCryptHash.VerifyHash(const Password, Hash : AnsiString) : Boolean;
|
||||
var
|
||||
RegexObj: TRegExpr;
|
||||
WorkingBcryptHash : AnsiString;
|
||||
HashCounter, ResultStatus, Cost : Byte;
|
||||
HashType : THashTypes;
|
||||
Begin
|
||||
ResultStatus := 0;
|
||||
RegexObj := TRegExpr.Create;
|
||||
RegexObj.Expression := '^(\$2\w{1}\$)(\d{2})\$([\./0-9A-Za-z]{22})';
|
||||
if RegexObj.Exec(Hash) then
|
||||
begin
|
||||
HashType := ResolveHashType(RegexObj.Match[1]);
|
||||
Cost := StrToInt(RegexObj.Match[2]);
|
||||
WorkingBcryptHash := Crypt(Password, RegexObj.Match[3], Cost, HashType);
|
||||
if (Length(WorkingBcryptHash) < 60) or (Length(WorkingBcryptHash) > 60) then
|
||||
begin
|
||||
Result := False;
|
||||
Exit;
|
||||
end;
|
||||
if Length(Hash) <> Length(WorkingBcryptHash) then
|
||||
begin
|
||||
Result := False;
|
||||
Exit;
|
||||
end;
|
||||
for HashCounter := 1 to Length(Hash) do
|
||||
begin
|
||||
{ From ext/standard/password.c php_password_verify line 244
|
||||
We're using this method instead of = in order to provide
|
||||
resistance towards timing attacks. This is a constant time
|
||||
equality check that will always check every byte of both
|
||||
values. }
|
||||
ResultStatus := ResultStatus or (ord(WorkingBcryptHash[HashCounter]) xor ord(Hash[HashCounter]));
|
||||
end;
|
||||
Result := (ResultStatus = 0);
|
||||
end
|
||||
else begin
|
||||
Result := False;
|
||||
end;
|
||||
RegexObj.Free;
|
||||
end;
|
||||
|
||||
function TBCryptHash.NeedsRehash(const BCryptHash : AnsiString) : Boolean; overload;
|
||||
begin
|
||||
Result := NeedsRehash(BCryptHash, BCRYPT_DEFAULT_COST);
|
||||
end;
|
||||
|
||||
function TBCryptHash.NeedsRehash(const BCryptHash : AnsiString; Cost : Byte) : Boolean; overload;
|
||||
var
|
||||
OldCost: Byte;
|
||||
begin
|
||||
OldCost := StrToInt(Copy(BCryptHash, 5, 2));
|
||||
if OldCost <> Cost then
|
||||
begin
|
||||
Result := True;
|
||||
end else
|
||||
begin
|
||||
Result := False;
|
||||
end;
|
||||
end;
|
||||
|
||||
function TBCryptHash.HashGetInfo(const Hash : AnsiString) : RTPasswordInformation;
|
||||
var
|
||||
PasswordInfo : RTPasswordInformation;
|
||||
BCryptCost : Byte;
|
||||
BCryptHash,
|
||||
BCryptSalt : AnsiString;
|
||||
HashType : THashTypes;
|
||||
begin
|
||||
if (Length(Hash) < 60) or (Length(Hash) > 60) then
|
||||
begin
|
||||
raise EHash.Create(Format(#10#13'Invalid hash %s'#10#13, [Hash]));
|
||||
Exit;
|
||||
end;
|
||||
HashType := ResolveHashType(Copy(Hash, 1, 4));
|
||||
BCryptCost := StrToInt(Copy(Hash, 5, 2));
|
||||
BCryptSalt := Copy(Hash, 8, 22);
|
||||
BCryptHash := Copy(Hash, 30, 60);
|
||||
|
||||
PasswordInfo.Algo := HashType;
|
||||
PasswordInfo.Cost := BCryptCost;
|
||||
PasswordInfo.AlgoName := 'bcrypt';
|
||||
PasswordInfo.BCryptSalt := BCryptSalt;
|
||||
PasswordInfo.BCryptHash := BCryptHash;
|
||||
|
||||
Result := PasswordInfo;
|
||||
end;
|
||||
|
||||
end.
|
|
@ -0,0 +1,21 @@
|
|||
The MIT License (MIT)
|
||||
|
||||
Copyright (c) 2016 renegadebbs
|
||||
|
||||
Permission is hereby granted, free of charge, to any person obtaining a copy
|
||||
of this software and associated documentation files (the "Software"), to deal
|
||||
in the Software without restriction, including without limitation the rights
|
||||
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
|
||||
copies of the Software, and to permit persons to whom the Software is
|
||||
furnished to do so, subject to the following conditions:
|
||||
|
||||
The above copyright notice and this permission notice shall be included in all
|
||||
copies or substantial portions of the Software.
|
||||
|
||||
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
|
||||
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
|
||||
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
|
||||
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
|
||||
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
|
||||
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
|
||||
SOFTWARE.
|
|
@ -0,0 +1,117 @@
|
|||
# Free Pascal BCrypt
|
||||
|
||||
Free Pascal [BCrypt](https://en.wikipedia.org/wiki/Bcrypt "BCrypt") implementation.
|
||||
|
||||
This started because I wanted something that would be compatible with PHP's $2y$ BCrypt hashing. Ultimately there is no difference between the $2a$ algorithm and the $2y$ algorithm. Just the a, and y. But I didn't want to have a wrapper function that replaced the a with the y.
|
||||
|
||||
If you try to verify a $2a$ password with PHP it will verify, but if you run the needs rehash function it will always say it needs a rehash. So I moved this to Free Pascal compatible class format.
|
||||
|
||||
Tested with :
|
||||
* Free Pascal
|
||||
* 2.6.4 (Linux, Gentoo)
|
||||
* 3.0.0 (Linux, Gentoo)
|
||||
* PHP
|
||||
* 5.6.20-pl0-gentoo
|
||||
* 7.0.6_rc1-pl0-gentoo.
|
||||
|
||||
### Usage
|
||||
```pascal
|
||||
BCrypt.CreateHash(Password);
|
||||
BCrypt.CreateHash(Password, HashType);
|
||||
BCrypt.CreateHash(Password, HashType, Cost);
|
||||
```
|
||||
Where
|
||||
* Password is the password to be hashed
|
||||
* HashType is one of bcPHP, bcBSD, or bcDefault, bcPHP is the default $2y$
|
||||
* and Cost is a number between 10 and 30, default is 12.
|
||||
```pascal
|
||||
var
|
||||
BCrypt : TBCryptHash;
|
||||
Hash : AnsiString;
|
||||
begin
|
||||
BCrypt := TBCryptHash.Create;
|
||||
Hash := BCrypt.CreateHash('password'); // PHP $2y$ hash with a cost of 12
|
||||
// or
|
||||
Hash := BCrypt.CreateHash('password', bcBSD); // BSD $2a$ hash with a cost of 12
|
||||
// or
|
||||
Hash := BCrypt.CreateHash('password', bcPHP, 14); // PHP hash, with a cost of 14
|
||||
Writeln(Hash);
|
||||
BCrypt.Free;
|
||||
end;
|
||||
```
|
||||
|
||||
To verify
|
||||
```pascal
|
||||
var
|
||||
BCrypt : TBCryptHash;
|
||||
Hash : AnsiString;
|
||||
Verify : Boolean;
|
||||
begin
|
||||
Hash := '$2y$12$GuC.Gk2YDsp8Yvga.IuSNOWM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq';
|
||||
BCrypt := TBCryptHash.Create;
|
||||
Verify := BCrypt.VerifyHash('password', Hash);
|
||||
BCrypt.Free;
|
||||
end;
|
||||
```
|
||||
|
||||
HashGetInfo - raises EHash exception if the hash is bad, ([too short](https://youtu.be/xT0Qb5ns7_A "too short"), too long);
|
||||
```pascal
|
||||
var
|
||||
BCrypt : TBCryptHash;
|
||||
Hash : AnsiString;
|
||||
PasswordInfo : RTPasswordInformation;
|
||||
begin
|
||||
BCrypt := TBCryptHash.Create;
|
||||
Hash := '$2y$12$GuC.Gk2YDsp8Yvga.IuSNOWM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq';
|
||||
PasswordInfo := BCrypt.HashGetInfo(Hash);
|
||||
with PasswordInfo do
|
||||
begin
|
||||
WriteLn('Algo : ', Algo); // bcPHP
|
||||
WriteLn('AlgoName : ', AlgoName); // bcrypt
|
||||
WriteLn('Cost : ', Cost); // 12
|
||||
WriteLn('Salt : ', BCryptSalt); // GuC.Gk2YDsp8Yvga.IuSNO
|
||||
WriteLn('Hash : ', BCryptHash); // WM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq
|
||||
end;
|
||||
|
||||
Hash := '$2a$12$GuC.Gk2YDsp8Yvga.IuSNOWM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq';
|
||||
PasswordInfo := BCrypt.HashGetInfo(Hash);
|
||||
with PasswordInfo do
|
||||
begin
|
||||
WriteLn('Algo : ', Algo); // bcBSD
|
||||
WriteLn('AlgoName : ', AlgoName); // bcrypt
|
||||
WriteLn('Cost : ', Cost); // 12
|
||||
WriteLn('Salt : ', BCryptSalt); // GuC.Gk2YDsp8Yvga.IuSNO
|
||||
WriteLn('Hash : ', BCryptHash); // WM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq
|
||||
end;
|
||||
BCrypt.Free;
|
||||
end;
|
||||
```
|
||||
NeedsRehash
|
||||
```pascal
|
||||
var
|
||||
BCrypt : TBCryptHash;
|
||||
Hash : AnsiString;
|
||||
Rehash : Boolean;
|
||||
begin
|
||||
BCrypt := TBCryptHash.Create;
|
||||
Hash := '$2a$12$GuC.Gk2YDsp8Yvga.IuSNOWM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq';
|
||||
Rehash := BCrypt.NeedsRehash(Hash); // false
|
||||
Rehash := BCrypt.NeedsRehash(Hash, 14); // true
|
||||
Hash := '$2y$14$GuC.Gk2YDsp8Yvga.IuSNOWM0fxEIsAEaWC1hqEI14Wa.7Ps3iYFq';
|
||||
Rehash := BCrypt.NeedsRehash(Hash); // true
|
||||
Rehash := BCrypt.NeedsRehash(Hash, 14); // false
|
||||
BCrypt.Free;
|
||||
end;
|
||||
```
|
||||
### Evolution
|
||||
This has had quite the evolution.
|
||||
|
||||
[FreeBSD crypt.c](https://svnweb.freebsd.org/base/stable/10/lib/libcrypt/crypt.c?revision=273043&view=markup "FreeBSD crypt.c")
|
||||
|
||||
[BCrypt for Delphi](https://github.com/JoseJimeniz/bcrypt-for-delphi "BCrypt for Delphi")
|
||||
|
||||
[BCrypt for Delphi, Lazarus, FPC](https://github.com/PonyPC/BCrypt-for-delphi-lazarus-fpc "BCrypt for Delphi, Lazarus, FPC")
|
||||
|
||||
[PHP password.c](https://github.com/php/php-src/blob/master/ext/standard/password.c "PHP password.c") For the verify logic.
|
||||
|
||||
To here.
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>BCRYPT_DEFAULT_COST</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>BCRYPT_DEFAULT_COST</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 15</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> BCRYPT_DEFAULT_COST <span class="sym">=</span> <span class="num">12</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>BCRYPT_SALT_LEN</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>BCRYPT_SALT_LEN</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 13</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> BCRYPT_SALT_LEN <span class="sym">=</span> <span class="num">16</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>BLOWFISH_NUM_ROUNDS</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>BLOWFISH_NUM_ROUNDS</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 14</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> BLOWFISH_NUM_ROUNDS <span class="sym">=</span> <span class="num">16</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
File diff suppressed because one or more lines are too long
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>BsdBase64EncodeTable</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>BsdBase64EncodeTable</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 177</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> BsdBase64EncodeTable<span class="sym">: </span><span class="kw">array</span> <span class="sym">[</span><span class="num">0</span><span class="sym">.</span><span class="sym">.</span><span class="num">63</span><span class="sym">]</span> <span class="kw">of</span> Char <span class="sym">=</span> <span class="str">'./'</span> <span class="sym">+</span> <span class="str">'ABCDEFGHIJKLMNOPQRSTUVWXYZ'</span> <span class="sym">+</span> <span class="str">'abcdefghijklmnopqrstuvwxyz'</span> <span class="sym">+</span> <span class="str">'0123456789'</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/ehash.html" onClick="opener.location.href = '../bcrypt/ehash.html'; return false;">EHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/ehash.html" onClick="opener.location.href = '../bcrypt/ehash.html'; return false;">EHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/ehash.html" onClick="opener.location.href = '../bcrypt/ehash.html'; return false;">EHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,45 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>EHash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>EHash</h1>
|
||||
<p>[<a href="../bcrypt/ehash-1.html" onClick="window.open('../bcrypt/ehash-1.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Properties</a> (<a href="../bcrypt/ehash-2.html" onClick="window.open('../bcrypt/ehash-2.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/ehash-3.html" onClick="window.open('../bcrypt/ehash-3.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Methods</a> (<a href="../bcrypt/ehash-4.html" onClick="window.open('../bcrypt/ehash-4.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/ehash-5.html" onClick="window.open('../bcrypt/ehash-5.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Events</a> (<a href="../bcrypt/ehash-6.html" onClick="window.open('../bcrypt/ehash-6.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] </p>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 212</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">type</span> EHash <span class="sym">=</span> <span class="kw">class</span><span class="sym">(</span>EArgumentException<span class="sym">)</span> <span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>Inheritance</h2>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td align="center" valign="top"><p><tt><span class="code"><a href="../bcrypt/ehash.html">EHash</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center">|</td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center"><p><tt><span class="code">EArgumentException</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center">?</td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center"><p><tt><span class="code">TObject</span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,44 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Reference for unit 'BCrypt': Constants</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][Constants][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Reference for unit 'BCrypt': Constants</h1>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/bcrypt_default_cost.html">BCRYPT_DEFAULT_COST</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/bcrypt_salt_len.html">BCRYPT_SALT_LEN</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/blowfish_num_rounds.html">BLOWFISH_NUM_ROUNDS</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/bsdbase64decodetable.html">BsdBase64DecodeTable</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/bsdbase64encodetable.html">BsdBase64EncodeTable</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/magictext.html">MagicText</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/pboxorg.html">PBoxOrg</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/sboxorg.html">SBoxOrg</a></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,23 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Reference for unit 'BCrypt': Types</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][Types][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Reference for unit 'BCrypt': Types</h1>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/thashtypes.html">THashTypes</a></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,29 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Reference for unit 'BCrypt': Classes</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][Classes][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Reference for unit 'BCrypt': Classes</h1>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/ehash.html">EHash</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="../bcrypt/tbcrypthash.html">TBCryptHash</a></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,95 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Index of all identifiers in unit 'BCrypt'</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][Index]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Index of all identifiers in unit 'BCrypt'</h1>
|
||||
<table width="50%" border="1" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="#SECTIONB">B</a> </td>
|
||||
<td valign="top"><a href="#SECTIONE">E</a> </td>
|
||||
<td valign="top"><a href="#SECTIONM">M</a> </td>
|
||||
<td valign="top"><a href="#SECTIONP">P</a> </td>
|
||||
<td valign="top"><a href="#SECTIONR">R</a> </td>
|
||||
<td valign="top"><a href="#SECTIONS">S</a> </td>
|
||||
<td valign="top"><a href="#SECTIONT">T</a> </td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>B<a name="SECTIONB"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/thashtypes.html">bcBSD</a></td>
|
||||
<td valign="top"><a href="../bcrypt/bcrypt_default_cost.html">BCRYPT_DEFAULT_COST</a></td>
|
||||
<td valign="top"><a href="../bcrypt/blowfish_num_rounds.html">BLOWFISH_NUM_ROUNDS</a></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/thashtypes.html">bcDefault</a></td>
|
||||
<td valign="top"><a href="../bcrypt/bcrypt_salt_len.html">BCRYPT_SALT_LEN</a></td>
|
||||
<td valign="top"><a href="../bcrypt/bsdbase64decodetable.html">BsdBase64DecodeTable</a></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/thashtypes.html">bcPHP</a></td>
|
||||
<td valign="top"><a href="../bcrypt/thashtypes.html">bcUnknown</a></td>
|
||||
<td valign="top"><a href="../bcrypt/bsdbase64encodetable.html">BsdBase64EncodeTable</a></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>E<a name="SECTIONE"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/ehash.html">EHash</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>M<a name="SECTIONM"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/magictext.html">MagicText</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>P<a name="SECTIONP"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/pboxorg.html">PBoxOrg</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>R<a name="SECTIONR"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>S<a name="SECTIONS"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/sboxorg.html">SBoxOrg</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>T<a name="SECTIONT"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="../bcrypt/tbcrypthash.html">TBCryptHash</a></td>
|
||||
<td valign="top"><a href="../bcrypt/thashtypes.html">THashTypes</a></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,33 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Reference for unit 'BCrypt'</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[Overview][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Reference for unit 'BCrypt'</h1>
|
||||
<p></p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">uses</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> System<span class="sym">,</span> </span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> SysUtils<span class="sym">,</span> </span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> Classes<span class="sym">;</span> </span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>MagicText</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>MagicText</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 173</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> MagicText<span class="sym">: </span><span class="kw">array</span> <span class="sym">[</span><span class="num">0</span><span class="sym">.</span><span class="sym">.</span><span class="num">5</span><span class="sym">]</span> <span class="kw">of</span> DWord <span class="sym">=</span> <span class="sym">(</span><span class="num">$4f727068</span><span class="sym">,</span> <span class="num">$65616e42</span><span class="sym">,</span> <span class="num">$65686f6c</span><span class="sym">,</span> <span class="num">$64657253</span><span class="sym">,</span> <span class="num">$63727944</span><span class="sym">,</span> <span class="num">$6f756274</span><span class="sym">)</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>PBoxOrg</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>PBoxOrg</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 17</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">const</span> PBoxOrg<span class="sym">: </span><span class="kw">array</span> <span class="sym">[</span><span class="num">0</span><span class="sym">.</span><span class="sym">.</span><span class="num">17</span><span class="sym">]</span> <span class="kw">of</span> DWord <span class="sym">=</span> <span class="sym">(</span><span class="num">$243f6a88</span><span class="sym">,</span> <span class="num">$85a308d3</span><span class="sym">,</span> <span class="num">$13198a2e</span><span class="sym">,</span> <span class="num">$03707344</span><span class="sym">,</span> <span class="num">$a4093822</span><span class="sym">,</span> <span class="num">$299f31d0</span><span class="sym">,</span> <span class="num">$082efa98</span><span class="sym">,</span> <span class="num">$ec4e6c89</span><span class="sym">,</span> <span class="num">$452821e6</span><span class="sym">,</span> <span class="num">$38d01377</span><span class="sym">,</span> <span class="num">$be5466cf</span><span class="sym">,</span> <span class="num">$34e90c6c</span><span class="sym">,</span> <span class="num">$c0ac29b7</span><span class="sym">,</span> <span class="num">$c97c50dd</span><span class="sym">,</span> <span class="num">$3f84d5b5</span><span class="sym">,</span> <span class="num">$b5470917</span><span class="sym">,</span> <span class="num">$9216d5d9</span><span class="sym">,</span> <span class="num">$8979fb1b</span><span class="sym">)</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/rtpasswordinformation.html" onClick="opener.location.href = '../bcrypt/rtpasswordinformation.html'; return false;">RTPasswordInformation</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/rtpasswordinformation.html" onClick="opener.location.href = '../bcrypt/rtpasswordinformation.html'; return false;">RTPasswordInformation</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/rtpasswordinformation.html" onClick="opener.location.href = '../bcrypt/rtpasswordinformation.html'; return false;">RTPasswordInformation</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation.Algo</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation.Algo</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 205</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">.</span>Algo<span class="sym"> : </span><a href="../bcrypt/thashtypes.html">THashTypes</a><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation.AlgoName</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation.AlgoName</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 209</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">.</span>AlgoName<span class="sym"> : </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation.BCryptHash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation.BCryptHash</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 209</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">.</span>BCryptHash<span class="sym"> : </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation.BCryptSalt</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation.BCryptSalt</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 209</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">.</span>BCryptSalt<span class="sym"> : </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation.Cost</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation.Cost</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 206</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">.</span>Cost<span class="sym"> : </span>Word<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,51 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>RTPasswordInformation</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>RTPasswordInformation</h1>
|
||||
<p>[<a href="../bcrypt/rtpasswordinformation-1.html" onClick="window.open('../bcrypt/rtpasswordinformation-1.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Properties</a> (<a href="../bcrypt/rtpasswordinformation-2.html" onClick="window.open('../bcrypt/rtpasswordinformation-2.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/rtpasswordinformation-3.html" onClick="window.open('../bcrypt/rtpasswordinformation-3.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Methods</a> (<a href="../bcrypt/rtpasswordinformation-4.html" onClick="window.open('../bcrypt/rtpasswordinformation-4.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/rtpasswordinformation-5.html" onClick="window.open('../bcrypt/rtpasswordinformation-5.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Events</a> (<a href="../bcrypt/rtpasswordinformation-6.html" onClick="window.open('../bcrypt/rtpasswordinformation-6.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] </p>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 204</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">type</span> RTPasswordInformation <span class="sym">=</span> <span class="kw">object</span> <span class="kw">end</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.algo.html">Algo</a><span class="sym">: </span><a href="../bcrypt/thashtypes.html">THashTypes</a><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.cost.html">Cost</a><span class="sym">: </span>Word<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.algoname.html">AlgoName</a><span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.bcryptsalt.html">BCryptSalt</a><span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <a href="../bcrypt/rtpasswordinformation.bcrypthash.html">BCryptHash</a><span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>Inheritance</h2>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td align="center" valign="top"><p><tt><span class="code"><a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
File diff suppressed because one or more lines are too long
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,47 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.create.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.create.html'; return false;">Create</a></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.destroy.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.destroy.html'; return false;">Destroy</a></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.createhash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.createhash.html'; return false;">CreateHash</a></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.verifyhash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.verifyhash.html'; return false;">VerifyHash</a></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.needsrehash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.needsrehash.html'; return false;">NeedsRehash</a></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td></td>
|
||||
<td><p><a href="../bcrypt/tbcrypthash.hashgetinfo.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.hashgetinfo.html'; return false;">HashGetInfo</a></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,43 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.create.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.create.html'; return false;">Create</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.createhash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.createhash.html'; return false;">CreateHash</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.destroy.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.destroy.html'; return false;">Destroy</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.hashgetinfo.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.hashgetinfo.html'; return false;">HashGetInfo</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.needsrehash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.needsrehash.html'; return false;">NeedsRehash</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p> </p></td>
|
||||
<td><p></p></td>
|
||||
<td nowrap="nowrap"><p><a href="../bcrypt/tbcrypthash.verifyhash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.verifyhash.html'; return false;">VerifyHash</a> (<a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a>)</p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,17 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td colspan="3"><p><tt><span class="code"><b><a href="../bcrypt/tbcrypthash.html" onClick="opener.location.href = '../bcrypt/tbcrypthash.html'; return false;">TBCryptHash</a></b></span></tt></p></td>
|
||||
<td></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,13 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title></title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.Create</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.Create</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 237</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">constructor</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>Create<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,53 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.CreateHash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.CreateHash</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 239</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>CreateHash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Password<span class="sym">: </span>AnsiString</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>AnsiString<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span><br><br><span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>CreateHash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Password<span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> HashType<span class="sym">: </span><a href="../bcrypt/thashtypes.html">THashTypes</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>AnsiString<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span><br><br><span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>CreateHash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Password<span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> HashType<span class="sym">: </span><a href="../bcrypt/thashtypes.html">THashTypes</a><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> Cost<span class="sym">: </span>Byte</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>AnsiString<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,26 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.Destroy</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.Destroy</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 238</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">destructor</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>Destroy<span class="sym">;</span><span class="kw"> override</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,32 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.HashGetInfo</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.HashGetInfo</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 245</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>HashGetInfo<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Hash<span class="sym">: </span>AnsiString</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span><a href="../bcrypt/rtpasswordinformation.html">RTPasswordInformation</a><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,63 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash</h1>
|
||||
<p>[<a href="../bcrypt/tbcrypthash-1.html" onClick="window.open('../bcrypt/tbcrypthash-1.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Properties</a> (<a href="../bcrypt/tbcrypthash-2.html" onClick="window.open('../bcrypt/tbcrypthash-2.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/tbcrypthash-3.html" onClick="window.open('../bcrypt/tbcrypthash-3.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Methods</a> (<a href="../bcrypt/tbcrypthash-4.html" onClick="window.open('../bcrypt/tbcrypthash-4.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] [<a href="../bcrypt/tbcrypthash-5.html" onClick="window.open('../bcrypt/tbcrypthash-5.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">Events</a> (<a href="../bcrypt/tbcrypthash-6.html" onClick="window.open('../bcrypt/tbcrypthash-6.html', 'list', 'dependent=yes,resizable=yes,scrollbars=yes,height=400,width=300'); return false;">by Name</a>)] </p>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 214</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">type</span> TBCryptHash <span class="sym">=</span> <span class="kw">class</span><span class="sym">(</span>TObject<span class="sym">)</span> <span class="kw">end</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">public</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">constructor </span><a href="../bcrypt/tbcrypthash.create.html">Create</a><span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">destructor </span><a href="../bcrypt/tbcrypthash.destroy.html">Destroy</a><span class="sym">;</span><span class="kw"> override</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">function </span><a href="../bcrypt/tbcrypthash.createhash.html">CreateHash</a><span class="sym">();</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">function </span><a href="../bcrypt/tbcrypthash.verifyhash.html">VerifyHash</a><span class="sym">();</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">function </span><a href="../bcrypt/tbcrypthash.needsrehash.html">NeedsRehash</a><span class="sym">();</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> <span class="kw">function </span><a href="../bcrypt/tbcrypthash.hashgetinfo.html">HashGetInfo</a><span class="sym">();</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>Inheritance</h2>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td align="center" valign="top"><p><tt><span class="code"><a href="../bcrypt/tbcrypthash.html">TBCryptHash</a></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center">|</td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td align="center"><p><tt><span class="code">TObject</span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,41 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.NeedsRehash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.NeedsRehash</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 243</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>NeedsRehash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>BCryptHash<span class="sym">: </span>AnsiString</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>Boolean<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span><br><br><span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>NeedsRehash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>BCryptHash<span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> Cost<span class="sym">: </span>Byte</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>Boolean<span class="sym">;</span><span class="kw"> overload</span><span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,35 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>TBCryptHash.VerifyHash</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>TBCryptHash.VerifyHash</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 242</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">public</span> <span class="kw">function</span> <a href="../bcrypt/tbcrypthash.html">TBCryptHash</a><span class="sym">.</span>VerifyHash<span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Password<span class="sym">: </span>AnsiString<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"> <span class="kw">const </span>Hash<span class="sym">: </span>AnsiString</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">):</span>Boolean<span class="sym">;</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,41 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>THashTypes</title>
|
||||
<link rel="stylesheet" href="../fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="../bcrypt/index.html">Overview</a>][<a href="../bcrypt/index-2.html">Constants</a>][<a href="../bcrypt/index-3.html">Types</a>][<a href="../bcrypt/index-4.html">Classes</a>][<a href="../bcrypt/index-8.html">Index</a>]</b></td>
|
||||
<td align="right"><span class="bartitle">Reference for unit 'BCrypt' (<a href="../index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>THashTypes</h1>
|
||||
<p></p>
|
||||
<h2>Declaration</h2>
|
||||
<p>Source position: BCrypt.pas line 203</p>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="kw">type </span>THashTypes<span class="sym"> = </span><span class="sym">(</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> bcDefault<span class="sym">,</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> bcPHP<span class="sym">,</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> bcBSD<span class="sym">,</span></span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"> bcUnknown</span></tt></p></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td><p><tt><span class="code"><span class="sym">);</span></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,166 @@
|
|||
/*
|
||||
$Id: fpdoc.css,v 1.1 2003/03/17 23:03:20 michael Exp $
|
||||
|
||||
Default style sheet for FPDoc reference documentation
|
||||
by Sebastian Guenther, sg@freepascal.org
|
||||
|
||||
Feel free to use this file as a template for your own style sheets.
|
||||
*/
|
||||
|
||||
body {
|
||||
background: white
|
||||
}
|
||||
|
||||
body, p, th, td, caption, h1, h2, h3, ul, ol, dl {
|
||||
color: black;
|
||||
font-family: sans-serif
|
||||
}
|
||||
|
||||
tt, span.kw, pre {
|
||||
font-family: Courier, monospace
|
||||
}
|
||||
|
||||
body, p, th, td, caption, ul, ol, dl, tt, span.kw, pre {
|
||||
font-size: 14px
|
||||
}
|
||||
|
||||
A:link {
|
||||
color: blue
|
||||
}
|
||||
|
||||
A:visited {
|
||||
color: darkblue
|
||||
}
|
||||
|
||||
A:active {
|
||||
color: red
|
||||
}
|
||||
|
||||
A {
|
||||
text-decoration: none
|
||||
}
|
||||
|
||||
A:hover {
|
||||
text-decoration: underline
|
||||
}
|
||||
|
||||
h1, h2, td.h2 {
|
||||
color: #005A9C
|
||||
}
|
||||
|
||||
/* Especially for Netscape on Linux: */
|
||||
h3, td.h3 {
|
||||
font-size: 12pt
|
||||
}
|
||||
|
||||
/* source fragments */
|
||||
span.code {
|
||||
white-space: nowrap
|
||||
}
|
||||
|
||||
/* symbols in source fragments */
|
||||
span.sym {
|
||||
color: darkred
|
||||
}
|
||||
|
||||
/* keywords in source fragments */
|
||||
span.kw {
|
||||
font-weight: bold
|
||||
}
|
||||
|
||||
/* comments in source fragments */
|
||||
span.cmt {
|
||||
color: darkcyan;
|
||||
font-style: italic
|
||||
}
|
||||
|
||||
/* directives in source fragments */
|
||||
span.dir {
|
||||
color: darkyellow;
|
||||
font-style: italic
|
||||
}
|
||||
|
||||
/* numbers in source fragments */
|
||||
span.num {
|
||||
color: darkmagenta
|
||||
}
|
||||
|
||||
/* characters (#...) in source fragments */
|
||||
span.chr {
|
||||
color: darkcyan
|
||||
}
|
||||
|
||||
/* strings in source fragments */
|
||||
span.str {
|
||||
color: blue
|
||||
}
|
||||
|
||||
/* assembler passages in source fragments */
|
||||
span.asm {
|
||||
color: green
|
||||
}
|
||||
|
||||
|
||||
td.pre {
|
||||
white-space: pre
|
||||
}
|
||||
|
||||
p.cmt {
|
||||
color: gray
|
||||
}
|
||||
|
||||
span.warning {
|
||||
color: red;
|
||||
font-weight: bold
|
||||
}
|
||||
|
||||
/* !!!: How should we define this...? */
|
||||
span.file {
|
||||
color: darkgreen
|
||||
}
|
||||
|
||||
table.remark {
|
||||
background-color: #ffffc0;
|
||||
}
|
||||
|
||||
table.bar {
|
||||
background-color: #a0c0ff;
|
||||
}
|
||||
|
||||
span.bartitle {
|
||||
font-weight: bold;
|
||||
font-style: italic;
|
||||
color: darkblue
|
||||
}
|
||||
|
||||
span.footer {
|
||||
font-style: italic;
|
||||
color: darkblue
|
||||
}
|
||||
|
||||
/* definition list */
|
||||
dl {
|
||||
border: 3px double #ccc;
|
||||
padding: 0.5em;
|
||||
}
|
||||
|
||||
/* definition list: term */
|
||||
dt {
|
||||
float: left;
|
||||
clear: left;
|
||||
width: auto; /* normally browsers default width of largest item */
|
||||
padding-right: 20px;
|
||||
font-weight: bold;
|
||||
color: darkgreen;
|
||||
}
|
||||
|
||||
/* definition list: description */
|
||||
dd {
|
||||
margin: 0 0 0 110px;
|
||||
padding: 0 0 0.5em 0;
|
||||
}
|
||||
|
||||
/* for browsers in standards compliance mode */
|
||||
td p {
|
||||
margin: 0;
|
||||
}
|
|
@ -0,0 +1,100 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Index of all identifiers in package 'TBCryptHash'</title>
|
||||
<link rel="stylesheet" href="fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[Index][<a href="index-9.html">Class hierarchy</a>]</b></td>
|
||||
<td align="right"><span class="bartitle"> (<a href="index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Index of all identifiers in package 'TBCryptHash'</h1>
|
||||
<table width="50%" border="1" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="#SECTIONB">B</a> </td>
|
||||
<td valign="top"><a href="#SECTIONE">E</a> </td>
|
||||
<td valign="top"><a href="#SECTIONM">M</a> </td>
|
||||
<td valign="top"><a href="#SECTIONP">P</a> </td>
|
||||
<td valign="top"><a href="#SECTIONR">R</a> </td>
|
||||
<td valign="top"><a href="#SECTIONS">S</a> </td>
|
||||
<td valign="top"><a href="#SECTIONT">T</a> </td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>B<a name="SECTIONB"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/thashtypes.html">bcBSD</a></td>
|
||||
<td valign="top"><a href="bcrypt/bcrypt_default_cost.html">BCRYPT_DEFAULT_COST</a></td>
|
||||
<td valign="top"><a href="bcrypt/bsdbase64decodetable.html">BsdBase64DecodeTable</a></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/thashtypes.html">bcDefault</a></td>
|
||||
<td valign="top"><a href="bcrypt/bcrypt_salt_len.html">BCRYPT_SALT_LEN</a></td>
|
||||
<td valign="top"><a href="bcrypt/bsdbase64encodetable.html">BsdBase64EncodeTable</a></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/thashtypes.html">bcPHP</a></td>
|
||||
<td valign="top"><a href="bcrypt/thashtypes.html">bcUnknown</a></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/index.html">BCrypt</a></td>
|
||||
<td valign="top"><a href="bcrypt/blowfish_num_rounds.html">BLOWFISH_NUM_ROUNDS</a></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>E<a name="SECTIONE"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/ehash.html">EHash</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>M<a name="SECTIONM"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/magictext.html">MagicText</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>P<a name="SECTIONP"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/pboxorg.html">PBoxOrg</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>R<a name="SECTIONR"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/rtpasswordinformation.html">RTPasswordInformation</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>S<a name="SECTIONS"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/sboxorg.html">SBoxOrg</a></td>
|
||||
<td valign="top"></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h2>T<a name="SECTIONT"></a></h2>
|
||||
<table Width="80%" cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><a href="bcrypt/tbcrypthash.html">TBCryptHash</a></td>
|
||||
<td valign="top"><a href="bcrypt/thashtypes.html">THashTypes</a></td>
|
||||
<td valign="top"></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,29 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Class hierarchy</title>
|
||||
<script>function expandorcollapse (o) {
|
||||
o.className = (o.className=="toggletreeclose") ? "toggletreeopen" : "toggletreeclose";
|
||||
o.parentNode.className = (o.className=="toggletreeclose") ? "classtree" : "classtreeclosed";
|
||||
return false;
|
||||
}</script>
|
||||
<link rel="stylesheet" href="fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="index-8.html">Index</a>][Class hierarchy]</b></td>
|
||||
<td align="right"><span class="bartitle"> (<a href="index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Class hierarchy</h1>
|
||||
<ul class="classtreelist">
|
||||
<li class="classtree"><span class="toggletreeclose" onclick="expandorcollapse(this)"> </span>TObject<ul class="classtreelist">
|
||||
<li class="classtree"><span class="toggletreeclose" onclick="expandorcollapse(this)"> </span>EArgumentException<ul class="classtreelist">
|
||||
<li class="classtree"><span class="toggletreeclose" onclick="expandorcollapse(this)"> </span><a href="bcrypt/ehash.html">EHash</a> (<a href="bcrypt/index.html">BCrypt</a>)</li></ul></li>
|
||||
<li class="classtree"><span class="toggletreeclose" onclick="expandorcollapse(this)"> </span><a href="bcrypt/tbcrypthash.html">TBCryptHash</a> (<a href="bcrypt/index.html">BCrypt</a>)</li></ul></li>
|
||||
</ul>
|
||||
</body>
|
||||
</html>
|
|
@ -0,0 +1,25 @@
|
|||
<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
|
||||
<html>
|
||||
<head>
|
||||
<meta content="text/html; charset=utf-8" http-equiv="Content-Type">
|
||||
<title>Reference for package 'TBCryptHash'</title>
|
||||
<link rel="stylesheet" href="fpdoc.css" type="text/css">
|
||||
|
||||
</head>
|
||||
<body>
|
||||
<table class="bar" width="100%" border="0" cellpadding="4" cellspacing="0">
|
||||
<tr>
|
||||
<td><b>[<a href="index-8.html">Index</a>][<a href="index-9.html">Class hierarchy</a>]</b></td>
|
||||
<td align="right"><span class="bartitle"> (<a href="index.html">#TBCryptHash</a>)</span></td>
|
||||
</tr>
|
||||
</table>
|
||||
<h1>Reference for package 'TBCryptHash'</h1>
|
||||
<p></p>
|
||||
<h2>Units</h2>
|
||||
<table cellpadding="0" cellspacing="0">
|
||||
<tr>
|
||||
<td valign="top"><p><tt><span class="code"><a href="bcrypt/index.html">BCrypt</a></span></tt></p></td>
|
||||
</tr>
|
||||
</table>
|
||||
</body>
|
||||
</html>
|
Binary file not shown.
After Width: | Height: | Size: 274 B |
Binary file not shown.
After Width: | Height: | Size: 289 B |
|
@ -0,0 +1,7 @@
|
|||
<?xml version="1.0" encoding="utf-8"?>
|
||||
<TObject unit="System">
|
||||
<EArgumentException>
|
||||
<EHash unit="BCrypt"/>
|
||||
</EArgumentException>
|
||||
<TBCryptHash unit="BCrypt"/>
|
||||
</TObject>
|
|
@ -0,0 +1,344 @@
|
|||
Program BCryptHashTest;
|
||||
{$mode objfpc}{$H+}
|
||||
{$ASSERTIONS ON}
|
||||
{$UNITPATH ../}
|
||||
|
||||
uses BCrypt, Classes, SysUtils, Crt;
|
||||
const
|
||||
HashToMatch1 = '$2y$14$6m54yWmpJRWWVkUz9p7feOlfQvafHGwsWt9pYupeLr8DU5wKMv.wW';
|
||||
HashToMatch2 = '$2y$16$d6eiNIIJPsVWtF.RCr.GUuCRs2hHFDB.0wPR.uK4kTi7KJvIO7k8e';
|
||||
BSDHashToMatch = '$2a$14$6m54yWmpJRWWVkUz9p7feOlfQvafHGwsWt9pYupeLr8DU5wKMv.wW';
|
||||
ShortHash = '$2y$14$6m54yWmpJRWWVkUz9p7feOlfQvafHGwsWt9pYupeLr8DU5wK';
|
||||
LongHash = '$2y$14$6m54yWmpJRWWVkUz9p7feOlfQvafHGwsWt9pYupeLr8DU5wKMv.wWwKMvwKMv';
|
||||
StaticPassword = 'password';
|
||||
|
||||
var
|
||||
TBCrypt : TBCryptHash;
|
||||
PasswordInfo : RTPasswordInformation;
|
||||
i, j,
|
||||
Assertions,
|
||||
FailedAssertions,
|
||||
PassedAssertions : Word;
|
||||
Passed : Boolean;
|
||||
|
||||
PasswordHashes : array [1..14] of AnsiString = (
|
||||
'$2y$10$LCb3aOt8lAXSzNrEpQKDQO1zc2wCCQltrDwSEbb9JaUo4OKbphC3i',
|
||||
'$2y$11$H7TRTJZqQTzN5RCiwMOne.yjVxyKCd4GyLrBQzV91gK0T4XQeKTNa',
|
||||
'$2y$12$EL5tAZCoKb/kz4Q6WWCiw.DY1Ow/PcyE0w0Uo/SNjtnq7mePss/Yq',
|
||||
'$2y$13$ou4ZkaFPLILNkSLNINSw9uEARJOQQr8u02KbVuosBs3ULxpbEpjwS',
|
||||
'$2y$14$jvv79wTecdgfOjhefJL8B.ziJNvfqf.hR9IkUdEzgOVyqzgUDMnW.',
|
||||
'$2y$15$EdDG3DH94Yw5HWD8pHFpwuF6Bs/24cnf0c.H2UrhPeld4sl5.LPT.',
|
||||
'$2y$16$NjsYCIxFgM0KUfJ2N0tW1umTh4hUV696cEwVo8TM/grYdfbc4dwwu',
|
||||
// BSD
|
||||
'$2a$10$gd4l18fYW85l4he4zRD.seTuSA81Ku.Myqhdqp0LapOoGyHIe3okG',
|
||||
'$2a$11$sbCP6X5yYvjYe8EJt2H4wOGxiTT/JIXz.fCaVdLAXp58mEiXeQlrO',
|
||||
'$2a$12$hnT.LCI2PlLFDDI8lAi6G.Lmb5Q45pUIKk7Rabos9LNl8gqW4Z9gi',
|
||||
'$2a$13$UB99eDai2k5YrwAAbqxPreIStZiSszuRT0AZCP4hvavPSxUoC7DxW',
|
||||
'$2a$14$SDveEpfBff4N4FkpvQyxyu07EFhADHjk3lJkW3mV0/1x98xK28LKK',
|
||||
'$2a$15$7z9ZVYe16/s6NAXjWO2eyeCPR0tyUhI4PCj0LlJZ3XUR2NMrmO18y',
|
||||
'$2a$16$ZhJeznvMiClYg20vpSjPDOC79J5KKlaLmQAXuObWHl90G2D21NvKO');
|
||||
|
||||
PHPPasswordHashes : array [1..7] of AnsiString = (
|
||||
'$2y$10$jRrQ51AeaJsJwNUw.QCDsOixDj.E0Vf2AG4tZdDmWqCSypmpFTr/q',
|
||||
'$2y$11$VEWaKBoOqoer/kjv3p/6SOa0SVTLRqH5huBsH7/6UlOvHI8f4zvvO',
|
||||
'$2y$12$hB6POF2QYZrkIx5a/CzB.OxvmJV9gy.93SPmOvwVySwukE1fJFgZm',
|
||||
'$2y$13$UWJNfSSzwYKeYyddhVYbNuyjYJx6ZZMGSLJnYcxiaFmYmPcTnJgxK',
|
||||
'$2y$14$FY/x2WRjTSB54IcSiRkz3u0mtyyNzeX/JQmxFxIyWrrc24JK3EuVK',
|
||||
'$2y$15$LE0.AEojI.2T6RadZVhc7eVsAkGsv0A2t0cKgWQBuAes86m.G036q',
|
||||
'$2y$16$yYy5GcoIgdd02DmUM3tfded5R5mv4K5QNG8QZDylGadokBdSL2WU6');
|
||||
|
||||
PasswordHashFailures : array [1..7] of AnsiString = (
|
||||
'$2y$10$LCb3aOt8lAXSzNrEpQKDQO1zc2wCCQltrDwSEbb9JaUo4OKbph',
|
||||
'$2y$11$H7TRTJZqQTzN5RCiwMOne.yjVxyKCd4GyLrBQzV91gK0T4XQeKTNadr',
|
||||
'$2y$12$EL5tAZCoKb/kz4Q6WWCiw.DY1Ow/PcyE0w0Uo/SNjtnq7mePss/YQ',
|
||||
'$2y$13$ou4ZkaFPLILNkSLNINSw9uEARJOQQr8u02KbVuosBs3ULxpbEpjwt',
|
||||
'$2y$14$jvv79wTecdgfOjhefJL8B.ziJNvfqf.hR9IkUdEzgOVyqzgUDMn.W',
|
||||
'$2y$15$EdDG3DH94Yw5HWD8pHFpwuF6Bs/24cnf0c.H2UrhPeld4sl5.LP.',
|
||||
'$2y$16$NjsYCIxFgM0KUfJ2N0tW1umTh4hV696cEwVo8TM/gYdfbc4duwwd/');
|
||||
|
||||
begin
|
||||
|
||||
TBCrypt := TBCryptHash.Create;
|
||||
|
||||
Assertions := 0;
|
||||
FailedAssertions := 0;
|
||||
PassedAssertions := 0;
|
||||
|
||||
WriteLn(#10#13'Testing Pascal Hashes ...'#10#13);
|
||||
for i := 1 to 14 do
|
||||
begin
|
||||
Write('Testing : ', PasswordHashes[i]);
|
||||
try
|
||||
Assert(TBCrypt.VerifyHash(StaticPassword, PasswordHashes[i]) = True, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
WriteLn(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
Continue;
|
||||
end;
|
||||
end;
|
||||
WriteLn(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
if i = 7 then
|
||||
begin
|
||||
Writeln(#10#13'Testing BSD Hashes ...'#10#13);
|
||||
end;
|
||||
end;
|
||||
WriteLn(#10#13'Testing PHP Hashes ...'#10#13);
|
||||
for i := 1 to 7 do
|
||||
begin
|
||||
Write('Testing : ', PHPPasswordHashes[i]);
|
||||
try
|
||||
Assert(TBCrypt.VerifyHash(StaticPassword, PHPPasswordHashes[i]) = True, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
WriteLn(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
Continue;
|
||||
end;
|
||||
end;
|
||||
WriteLn(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
WriteLn(#10#13'Testing Failures ...'#10#13);
|
||||
for i := 1 to 7 do
|
||||
begin
|
||||
Write('Testing : ', PasswordHashFailures[i]);
|
||||
try
|
||||
Assert(TBCrypt.VerifyHash(StaticPassword, PasswordHashFailures[i]) = False, 'Should Be False');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
WriteLn(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
Continue;
|
||||
end;
|
||||
end;
|
||||
WriteLn(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
|
||||
end;
|
||||
|
||||
WriteLn(#10#13'Testing Rehash True ...'#10#13);
|
||||
for i := 1 to 7 do
|
||||
begin
|
||||
Write('Testing : ', PasswordHashes[i]);
|
||||
try
|
||||
Assert(TBCrypt.NeedsRehash(PasswordHashes[i], 17) = True, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
WriteLn(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
Continue;
|
||||
end;
|
||||
end;
|
||||
WriteLn(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
|
||||
WriteLn(#10#13'Testing Rehash False ...'#10#13);
|
||||
j := 10;
|
||||
for i := 1 to 7 do
|
||||
begin
|
||||
Write('Testing : ', PasswordHashes[i]);
|
||||
try
|
||||
Assert(TBCrypt.NeedsRehash(PasswordHashes[i], j) = False, 'Should Be False');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
WriteLn(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
Inc(j);
|
||||
Continue;
|
||||
end;
|
||||
end;
|
||||
WriteLn(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
Inc(j);
|
||||
end;
|
||||
|
||||
WriteLn(#10#13'Testing HashGetInfo on hash '#10#13, HashToMatch2, ' ...'#10#13);
|
||||
PasswordInfo := TBCrypt.HashGetInfo(HashToMatch2);
|
||||
Passed := True;
|
||||
With PasswordInfo do
|
||||
begin
|
||||
Writeln('Algo : ', Algo);
|
||||
try
|
||||
Assert(Algo = bcPHP);
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Inc(FailedAssertions);
|
||||
end;
|
||||
end;
|
||||
WriteLn('AlgoName : ', AlgoName);
|
||||
WriteLn('Cost : ', Cost);
|
||||
Write('Salt : ', BCryptSalt);
|
||||
try
|
||||
Assert(Length(BCryptSalt) = 22, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Passed := False;
|
||||
end;
|
||||
end;
|
||||
if Passed = False then
|
||||
begin
|
||||
Writeln(' Length - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' Length - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
Passed := True;
|
||||
Write('Hash : ', BCryptHash);
|
||||
try
|
||||
Assert(Length(BCryptHash) = 31, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Passed := False;
|
||||
end;
|
||||
end;
|
||||
if Passed = False then
|
||||
begin
|
||||
Writeln(' Length - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' Length - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
|
||||
end;
|
||||
|
||||
WriteLn(#10#13'Testing HashGetInfo on bsd hash '#10#13, BSDHashToMatch, ' ...'#10#13);
|
||||
PasswordInfo := TBCrypt.HashGetInfo(BSDHashToMatch);
|
||||
Passed := True;
|
||||
With PasswordInfo do
|
||||
begin
|
||||
Writeln('Algo : ', Algo);
|
||||
try
|
||||
Assert(Algo = bcBSD);
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Inc(FailedAssertions);
|
||||
end;
|
||||
end;
|
||||
WriteLn('AlgoName : ', AlgoName);
|
||||
WriteLn('Cost : ', Cost);
|
||||
Write('Salt : ', BCryptSalt);
|
||||
try
|
||||
Assert(Length(BCryptSalt) = 22, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Passed := False;
|
||||
end;
|
||||
end;
|
||||
if Passed = False then
|
||||
begin
|
||||
Writeln(' Length - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' Length - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
Passed := True;
|
||||
Write('Hash : ', BCryptHash);
|
||||
try
|
||||
Assert(Length(BCryptHash) = 31, 'Should Be True');
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EAssertionFailed do
|
||||
begin
|
||||
Passed := False;
|
||||
end;
|
||||
end;
|
||||
if Passed = False then
|
||||
begin
|
||||
Writeln(' Length - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' Length - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end;
|
||||
|
||||
end;
|
||||
|
||||
Writeln(#10#13'Testing PasswordInfo with bad Hashes.'#10#13);
|
||||
Passed := False;
|
||||
try
|
||||
Write('Short Hash : ', ShortHash);
|
||||
PasswordInfo := TBCrypt.HashGetInfo(ShortHash);
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EHash do
|
||||
begin
|
||||
Passed := True;
|
||||
end;
|
||||
end;
|
||||
if Passed = True then
|
||||
begin
|
||||
Writeln(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end;
|
||||
Passed := False;
|
||||
try
|
||||
Write('Long Hash : ', LongHash);
|
||||
PasswordInfo := TBCrypt.HashGetInfo(LongHash);
|
||||
Inc(Assertions);
|
||||
except
|
||||
on e: EHash do
|
||||
begin
|
||||
Passed := True;
|
||||
end;
|
||||
end;
|
||||
if Passed = True then
|
||||
begin
|
||||
Writeln(' - Pass');
|
||||
Inc(PassedAssertions);
|
||||
end else
|
||||
begin
|
||||
Writeln(' - Fail');
|
||||
Inc(FailedAssertions);
|
||||
end;
|
||||
|
||||
|
||||
Writeln(#10#13'Testing hashing ...'#10#13);
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcBSD));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcDefault));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcPHP));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcBSD, 14));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcDefault, 14));
|
||||
Writeln(TBCrypt.CreateHash(StaticPassword, bcPHP, 14));
|
||||
Writeln(#10#13);
|
||||
|
||||
TBCrypt.Free;
|
||||
Writeln('Assertions : ', Assertions);
|
||||
Writeln('Passed Assertions : ', PassedAssertions);
|
||||
Writeln('Failed Assertions : ', FailedAssertions);
|
||||
Writeln;
|
||||
end.
|
|
@ -0,0 +1,80 @@
|
|||
<?php
|
||||
|
||||
function bcrypt_assert_handler($file, $line, $code, $desc = null)
|
||||
{
|
||||
if ($desc) {
|
||||
print $desc . PHP_EOL;
|
||||
}
|
||||
}
|
||||
|
||||
assert_options(ASSERT_ACTIVE, 1);
|
||||
assert_options(ASSERT_WARNING, 0);
|
||||
assert_options(ASSERT_QUIET_EVAL, 0);
|
||||
assert_options(ASSERT_CALLBACK, 'bcrypt_assert_handler');
|
||||
|
||||
$bsdPascalHash = '$2a$12$9NWTTEbRtjLNd4KdW.VtUekFA6pJ3DF23FqdvwwvMtoMD9zqdaZg2';
|
||||
$bsdPascalHashFail = '$2a$12$9NWTTEbRtjLNd4KdW.VtUekFA6pJ3DF23FqdvwwvMtoMD9zqdaZg1';
|
||||
|
||||
$pascalHashesMT = [
|
||||
'$2y$10$kJgRFQ993paFLArmPE3gn.8yuUB/SRpaEw7lkJJ1oVqhWVIecI5nO',
|
||||
'$2y$11$kJgRFQ993paFLArmPE3gn.n9OJBeYd77RdOYnkdp9orILyaa5jDb6',
|
||||
'$2y$12$onWrpSgN3URAnmBJZkpqieH1QwbkDe5.RXInCYJG9MCtXL0yH6rxe',
|
||||
'$2y$13$AIbAdbn1wJ.Fc1dTNo/Ya..7mbUiSW91PRfn2d8.OYBkV5ddtjbge',
|
||||
'$2y$14$4Q96fpQzCJ6OrfBHW/vYn.DP2JFC/PzdPPKjdEuVs8JPMkYWRPAWy',
|
||||
'$2y$15$O2XqJxnSG0yOGuEgbgAGredSC7GPs72Bhm96cs0uWh79qhMVSroPy',
|
||||
'$2y$16$kRupPRj4D7V0wDJwOqvHPev4ZA8/C4upHvvvXpnCt7nnWi.6tyrKK',
|
||||
];
|
||||
|
||||
$pascalHashesURandom = [
|
||||
'$2y$10$UCFG03qurE5eKhIIQRiMpu4Q1Y8xX2RgtHeB0TECbAsTW8bRrRmua',
|
||||
'$2y$11$rbUzZuxaYAN9I3encPoqGO6tzwUId9Ig2U2FQy.l2jjGCX9VqnP9q',
|
||||
'$2y$12$hDyyWY5qnGyE4he.2gbH3euopm.mOoMbnk78ZR9UgzjwaJp9BeGjK',
|
||||
'$2y$13$Vt527KNEnGTfUSX90HzP8un0WWYN038sOMrr/LdaP1GzWr77/j17.',
|
||||
'$2y$14$EitIDTZ4p2GxK63gDgSLAu63fGqkj0VxWmfaYERkpuXt.SCA1YLh2',
|
||||
'$2y$15$ELRZS1FLgo4.vVkJNqsnPeaKkUeHgIGLP42aHWHHc8ze8gUQviApO',
|
||||
'$2y$16$Y0QNc8vaJJY5mQO0IkN6oeAxEVjtnHYqk0WeWLPm7bRjxA7fWHRBG',
|
||||
];
|
||||
|
||||
print PHP_EOL . 'Testing bsdPascalHash ... ' . str_repeat(PHP_EOL, 2);
|
||||
print 'Testing : ' . $bsdPascalHash;
|
||||
if (true === assert(password_verify('password', $bsdPascalHash), ' - Fail')) {
|
||||
print ' - Pass' . PHP_EOL;
|
||||
}
|
||||
print PHP_EOL . 'Testing bsdPascalHash for failure ... ' . str_repeat(PHP_EOL, 2);
|
||||
print 'Testing : ' . $bsdPascalHashFail;
|
||||
if (true === assert(!password_verify('password', $bsdPascalHashFail), ' - Fail')) {
|
||||
print ' - Pass' . PHP_EOL;
|
||||
}
|
||||
|
||||
print PHP_EOL . 'Testing Pascal hashes MTRand ... ' . str_repeat(PHP_EOL, 2);
|
||||
foreach ($pascalHashesMT as $pascalHash) {
|
||||
print 'Testing : ' . $pascalHash;
|
||||
if (true === assert(password_verify('password', $pascalHash), ' - Fail')) {
|
||||
print ' - Pass' . PHP_EOL;
|
||||
}
|
||||
}
|
||||
|
||||
print PHP_EOL . 'Testing Pascal hashes urandom ... ' . str_repeat(PHP_EOL, 2);
|
||||
foreach ($pascalHashesURandom as $pascalHash) {
|
||||
print 'Testing : ' . $pascalHash;
|
||||
if (true === assert(password_verify('password', $pascalHash), ' - Fail')) {
|
||||
print ' - Pass' . PHP_EOL;
|
||||
}
|
||||
}
|
||||
|
||||
print PHP_EOL . 'Testing password_needs_rehash ... ' . str_repeat(PHP_EOL, 2);
|
||||
foreach ($pascalHashesURandom as $pascalHash) {
|
||||
print 'Testing : ' . $pascalHash;
|
||||
if (true === assert(
|
||||
!password_needs_rehash(
|
||||
$pascalHash,
|
||||
PASSWORD_BCRYPT,
|
||||
['cost' => substr($pascalHash, 4, 2)]
|
||||
),
|
||||
' - Fail'
|
||||
)
|
||||
) {
|
||||
print ' - Pass' . PHP_EOL;
|
||||
}
|
||||
}
|
||||
print PHP_EOL;
|
Loading…
Reference in New Issue