Advertisement
Guest User

Blowfish for Delphi

a guest
May 3rd, 2012
2,230
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Delphi 35.22 KB | None | 0 0
  1. unit Blowfish;
  2.  
  3. {
  4. ***************************************************
  5. * A binary compatible Blowfish implementation     *
  6. * written by Dave Barton (davebarton@bigfoot.com) *
  7. ***************************************************
  8. * 64bit block encryption                          *
  9. * Variable size key - up to 448bit                *
  10. ***************************************************
  11. }
  12.  
  13. interface
  14.  
  15. uses
  16.   Sysutils, Windows;
  17.  
  18. type
  19.   TBlowfishData= record
  20.      InitBlock: array[0..7] of Byte;    { initial IV }
  21.      LastBlock: array[0..7] of Byte;    { current IV }
  22.      SBoxM: array[0..3, 0..255] of DWORD;
  23.      PBoxM: array[0..17] of DWORD;
  24.   end;
  25.  
  26. function BlowfishSelfTest: Boolean;
  27.   { performs a self test on this implementation }
  28. procedure BlowfishInit(out Data: TBlowfishData; Key: Pointer; Len: Integer; IV: Pointer);
  29.   { initializes the TBlowfishData structure with the key information and IV if applicable }
  30. procedure BlowfishBurn(var State: TBlowfishData);
  31.   { erases all information about the key }
  32.  
  33. procedure BlowfishEncryptECB(const Data: TBlowfishData; InData, OutData: Pointer);
  34.   { encrypts the data in a 64bit block using the ECB mode }
  35. procedure BlowfishEncryptCBC(var Data: TBlowfishData; InData, OutData: Pointer);
  36.   { encrypts the data in a 64bit block using the CBC chaining mode }
  37. procedure BlowfishEncryptOFB(var Data: TBlowfishData; InData, OutData: Pointer);
  38.   { encrypts the data in a 64bit block using the OFB chaining mode }
  39. procedure BlowfishEncryptCFB(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  40.   { encrypts Len bytes of data using the CFB chaining mode }
  41. procedure BlowfishEncryptOFBC(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  42.   { encrypts Len bytes of data using the OFB counter chaining mode }
  43.  
  44. procedure BlowfishDecryptECB(const Data: TBlowfishData; InData, OutData: Pointer);
  45.   { decrypts the data in a 64bit block using the ECB mode }
  46. procedure BlowfishDecryptCBC(var Data: TBlowfishData; InData, OutData: Pointer);
  47.   { decrypts the data in a 64bit block using the CBC chaining mode }
  48. procedure BlowfishDecryptOFB(var Data: TBlowfishData; InData, OutData: Pointer);
  49.   { decrypts the data in a 64bit block using the OFB chaining mode }
  50. procedure BlowfishDecryptCFB(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  51.   { decrypts Len bytes of data using the CFB chaining mode }
  52. procedure BlowfishDecryptOFBC(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  53.   { decrypts Len bytes of data using the OFB counter chaining mode }
  54.  
  55. procedure BlowfishReset(var Data: TBlowfishData);
  56.   { resets the chaining mode information }
  57.  
  58. procedure BlowfishInitState(var State: TBlowfishData);
  59.     { Copy the S and P boxes into the state }
  60.  
  61.  
  62. implementation
  63.  
  64. {$IFDEF UnitTests}
  65. uses
  66.     TestFramework;
  67.  
  68. type
  69.     TBlowfishTests = class(TTestCase)
  70.     published
  71.         procedure SelfTest;
  72.     end;
  73.  
  74. {$ENDIF}
  75.  
  76. const
  77.     //SBLOCKS ARE THE HEX DIGITS OF PI.
  78.     //The amount of hex digits can be increased if you want to experiment with more rounds and longer key lengths
  79.     PBox: array[0..17] of DWORD = (
  80.                 $243f6a88, $85a308d3, $13198a2e, $03707344, $a4093822, $299f31d0,
  81.                 $082efa98, $ec4e6c89, $452821e6, $38d01377, $be5466cf, $34e90c6c,
  82.                 $c0ac29b7, $c97c50dd, $3f84d5b5, $b5470917, $9216d5d9, $8979fb1b);
  83.  
  84.     SBox: array[0..3, 0..255] of DWORD = (
  85.             //SBox[0]
  86.             (
  87.                           $d1310ba6, $98dfb5ac, $2ffd72db, $d01adfb7, $b8e1afed, $6a267e96,
  88.                           $ba7c9045, $f12c7f99, $24a19947, $b3916cf7, $0801f2e2, $858efc16,
  89.                           $636920d8, $71574e69, $a458fea3, $f4933d7e, $0d95748f, $728eb658,
  90.                           $718bcd58, $82154aee, $7b54a41d, $c25a59b5, $9c30d539, $2af26013,
  91.                           $c5d1b023, $286085f0, $ca417918, $b8db38ef, $8e79dcb0, $603a180e,
  92.                           $6c9e0e8b, $b01e8a3e, $d71577c1, $bd314b27, $78af2fda, $55605c60,
  93.                           $e65525f3, $aa55ab94, $57489862, $63e81440, $55ca396a, $2aab10b6,
  94.                           $b4cc5c34, $1141e8ce, $a15486af, $7c72e993, $b3ee1411, $636fbc2a,
  95.                           $2ba9c55d, $741831f6, $ce5c3e16, $9b87931e, $afd6ba33, $6c24cf5c,
  96.                           $7a325381, $28958677, $3b8f4898, $6b4bb9af, $c4bfe81b, $66282193,
  97.                           $61d809cc, $fb21a991, $487cac60, $5dec8032, $ef845d5d, $e98575b1,
  98.                           $dc262302, $eb651b88, $23893e81, $d396acc5, $0f6d6ff3, $83f44239,
  99.                           $2e0b4482, $a4842004, $69c8f04a, $9e1f9b5e, $21c66842, $f6e96c9a,
  100.                           $670c9c61, $abd388f0, $6a51a0d2, $d8542f68, $960fa728, $ab5133a3,
  101.                           $6eef0b6c, $137a3be4, $ba3bf050, $7efb2a98, $a1f1651d, $39af0176,
  102.                           $66ca593e, $82430e88, $8cee8619, $456f9fb4, $7d84a5c3, $3b8b5ebe,
  103.                           $e06f75d8, $85c12073, $401a449f, $56c16aa6, $4ed3aa62, $363f7706,
  104.                           $1bfedf72, $429b023d, $37d0d724, $d00a1248, $db0fead3, $49f1c09b,
  105.                           $075372c9, $80991b7b, $25d479d8, $f6e8def7, $e3fe501a, $b6794c3b,
  106.                           $976ce0bd, $04c006ba, $c1a94fb6, $409f60c4, $5e5c9ec2, $196a2463,
  107.                           $68fb6faf, $3e6c53b5, $1339b2eb, $3b52ec6f, $6dfc511f, $9b30952c,
  108.                           $cc814544, $af5ebd09, $bee3d004, $de334afd, $660f2807, $192e4bb3,
  109.                           $c0cba857, $45c8740f, $d20b5f39, $b9d3fbdb, $5579c0bd, $1a60320a,
  110.                           $d6a100c6, $402c7279, $679f25fe, $fb1fa3cc, $8ea5e9f8, $db3222f8,
  111.                           $3c7516df, $fd616b15, $2f501ec8, $ad0552ab, $323db5fa, $fd238760,
  112.                           $53317b48, $3e00df82, $9e5c57bb, $ca6f8ca0, $1a87562e, $df1769db,
  113.                           $d542a8f6, $287effc3, $ac6732c6, $8c4f5573, $695b27b0, $bbca58c8,
  114.                           $e1ffa35d, $b8f011a0, $10fa3d98, $fd2183b8, $4afcb56c, $2dd1d35b,
  115.                           $9a53e479, $b6f84565, $d28e49bc, $4bfb9790, $e1ddf2da, $a4cb7e33,
  116.                           $62fb1341, $cee4c6e8, $ef20cada, $36774c01, $d07e9efe, $2bf11fb4,
  117.                           $95dbda4d, $ae909198, $eaad8e71, $6b93d5a0, $d08ed1d0, $afc725e0,
  118.                           $8e3c5b2f, $8e7594b7, $8ff6e2fb, $f2122b64, $8888b812, $900df01c,
  119.                           $4fad5ea0, $688fc31c, $d1cff191, $b3a8c1ad, $2f2f2218, $be0e1777,
  120.                           $ea752dfe, $8b021fa1, $e5a0cc0f, $b56f74e8, $18acf3d6, $ce89e299,
  121.                           $b4a84fe0, $fd13e0b7, $7cc43b81, $d2ada8d9, $165fa266, $80957705,
  122.                           $93cc7314, $211a1477, $e6ad2065, $77b5fa86, $c75442f5, $fb9d35cf,
  123.                           $ebcdaf0c, $7b3e89a0, $d6411bd3, $ae1e7e49, $00250e2d, $2071b35e,
  124.                           $226800bb, $57b8e0af, $2464369b, $f009b91e, $5563911d, $59dfa6aa,
  125.                           $78c14389, $d95a537f, $207d5ba2, $02e5b9c5, $83260376, $6295cfa9,
  126.                           $11c81968, $4e734a41, $b3472dca, $7b14a94a, $1b510052, $9a532915,
  127.                           $d60f573f, $bc9bc6e4, $2b60a476, $81e67400, $08ba6fb5, $571be91f,
  128.                           $f296ec6b, $2a0dd915, $b6636521, $e7b9f9b6, $ff34052e, $c5855664,
  129.                           $53b02d5d, $a99f8fa1, $08ba4799, $6e85076a
  130.             ),
  131.             //SBox[1]
  132.             (
  133.                          $4b7a70e9, $b5b32944, $db75092e, $c4192623, $ad6ea6b0, $49a7df7d,
  134.                           $9cee60b8, $8fedb266, $ecaa8c71, $699a17ff, $5664526c, $c2b19ee1,
  135.                           $193602a5, $75094c29, $a0591340, $e4183a3e, $3f54989a, $5b429d65,
  136.                           $6b8fe4d6, $99f73fd6, $a1d29c07, $efe830f5, $4d2d38e6, $f0255dc1,
  137.                           $4cdd2086, $8470eb26, $6382e9c6, $021ecc5e, $09686b3f, $3ebaefc9,
  138.                           $3c971814, $6b6a70a1, $687f3584, $52a0e286, $b79c5305, $aa500737,
  139.                           $3e07841c, $7fdeae5c, $8e7d44ec, $5716f2b8, $b03ada37, $f0500c0d,
  140.                           $f01c1f04, $0200b3ff, $ae0cf51a, $3cb574b2, $25837a58, $dc0921bd,
  141.                           $d19113f9, $7ca92ff6, $94324773, $22f54701, $3ae5e581, $37c2dadc,
  142.                           $c8b57634, $9af3dda7, $a9446146, $0fd0030e, $ecc8c73e, $a4751e41,
  143.                           $e238cd99, $3bea0e2f, $3280bba1, $183eb331, $4e548b38, $4f6db908,
  144.                           $6f420d03, $f60a04bf, $2cb81290, $24977c79, $5679b072, $bcaf89af,
  145.                           $de9a771f, $d9930810, $b38bae12, $dccf3f2e, $5512721f, $2e6b7124,
  146.                           $501adde6, $9f84cd87, $7a584718, $7408da17, $bc9f9abc, $e94b7d8c,
  147.                           $ec7aec3a, $db851dfa, $63094366, $c464c3d2, $ef1c1847, $3215d908,
  148.                           $dd433b37, $24c2ba16, $12a14d43, $2a65c451, $50940002, $133ae4dd,
  149.                           $71dff89e, $10314e55, $81ac77d6, $5f11199b, $043556f1, $d7a3c76b,
  150.                           $3c11183b, $5924a509, $f28fe6ed, $97f1fbfa, $9ebabf2c, $1e153c6e,
  151.                           $86e34570, $eae96fb1, $860e5e0a, $5a3e2ab3, $771fe71c, $4e3d06fa,
  152.                           $2965dcb9, $99e71d0f, $803e89d6, $5266c825, $2e4cc978, $9c10b36a,
  153.                           $c6150eba, $94e2ea78, $a5fc3c53, $1e0a2df4, $f2f74ea7, $361d2b3d,
  154.                           $1939260f, $19c27960, $5223a708, $f71312b6, $ebadfe6e, $eac31f66,
  155.                           $e3bc4595, $a67bc883, $b17f37d1, $018cff28, $c332ddef, $be6c5aa5,
  156.                           $65582185, $68ab9802, $eecea50f, $db2f953b, $2aef7dad, $5b6e2f84,
  157.                           $1521b628, $29076170, $ecdd4775, $619f1510, $13cca830, $eb61bd96,
  158.                           $0334fe1e, $aa0363cf, $b5735c90, $4c70a239, $d59e9e0b, $cbaade14,
  159.                           $eecc86bc, $60622ca7, $9cab5cab, $b2f3846e, $648b1eaf, $19bdf0ca,
  160.                           $a02369b9, $655abb50, $40685a32, $3c2ab4b3, $319ee9d5, $c021b8f7,
  161.                           $9b540b19, $875fa099, $95f7997e, $623d7da8, $f837889a, $97e32d77,
  162.                           $11ed935f, $16681281, $0e358829, $c7e61fd6, $96dedfa1, $7858ba99,
  163.                           $57f584a5, $1b227263, $9b83c3ff, $1ac24696, $cdb30aeb, $532e3054,
  164.                           $8fd948e4, $6dbc3128, $58ebf2ef, $34c6ffea, $fe28ed61, $ee7c3c73,
  165.                           $5d4a14d9, $e864b7e3, $42105d14, $203e13e0, $45eee2b6, $a3aaabea,
  166.                           $db6c4f15, $facb4fd0, $c742f442, $ef6abbb5, $654f3b1d, $41cd2105,
  167.                           $d81e799e, $86854dc7, $e44b476a, $3d816250, $cf62a1f2, $5b8d2646,
  168.                           $fc8883a0, $c1c7b6a3, $7f1524c3, $69cb7492, $47848a0b, $5692b285,
  169.                           $095bbf00, $ad19489d, $1462b174, $23820e00, $58428d2a, $0c55f5ea,
  170.                           $1dadf43e, $233f7061, $3372f092, $8d937e41, $d65fecf1, $6c223bdb,
  171.                           $7cde3759, $cbee7460, $4085f2a7, $ce77326e, $a6078084, $19f8509e,
  172.                           $e8efd855, $61d99735, $a969a7aa, $c50c06c2, $5a04abfc, $800bcadc,
  173.                           $9e447a2e, $c3453484, $fdd56705, $0e1e9ec9, $db73dbd3, $105588cd,
  174.                           $675fda79, $e3674340, $c5c43465, $713e38d8, $3d28f89e, $f16dff20,
  175.                           $153e21e7, $8fb03d4a, $e6e39f2b, $db83adf7
  176.                 ),
  177.                 //SBox[2]
  178.                 (
  179.                      $e93d5a68, $948140f7, $f64c261c, $94692934, $411520f7, $7602d4f7,
  180.                           $bcf46b2e, $d4a20068, $d4082471, $3320f46a, $43b7d4b7, $500061af,
  181.                           $1e39f62e, $97244546, $14214f74, $bf8b8840, $4d95fc1d, $96b591af,
  182.                           $70f4ddd3, $66a02f45, $bfbc09ec, $03bd9785, $7fac6dd0, $31cb8504,
  183.                           $96eb27b3, $55fd3941, $da2547e6, $abca0a9a, $28507825, $530429f4,
  184.                           $0a2c86da, $e9b66dfb, $68dc1462, $d7486900, $680ec0a4, $27a18dee,
  185.                           $4f3ffea2, $e887ad8c, $b58ce006, $7af4d6b6, $aace1e7c, $d3375fec,
  186.                           $ce78a399, $406b2a42, $20fe9e35, $d9f385b9, $ee39d7ab, $3b124e8b,
  187.                           $1dc9faf7, $4b6d1856, $26a36631, $eae397b2, $3a6efa74, $dd5b4332,
  188.                           $6841e7f7, $ca7820fb, $fb0af54e, $d8feb397, $454056ac, $ba489527,
  189.                           $55533a3a, $20838d87, $fe6ba9b7, $d096954b, $55a867bc, $a1159a58,
  190.                           $cca92963, $99e1db33, $a62a4a56, $3f3125f9, $5ef47e1c, $9029317c,
  191.                           $fdf8e802, $04272f70, $80bb155c, $05282ce3, $95c11548, $e4c66d22,
  192.                           $48c1133f, $c70f86dc, $07f9c9ee, $41041f0f, $404779a4, $5d886e17,
  193.                           $325f51eb, $d59bc0d1, $f2bcc18f, $41113564, $257b7834, $602a9c60,
  194.                           $dff8e8a3, $1f636c1b, $0e12b4c2, $02e1329e, $af664fd1, $cad18115,
  195.                           $6b2395e0, $333e92e1, $3b240b62, $eebeb922, $85b2a20e, $e6ba0d99,
  196.                           $de720c8c, $2da2f728, $d0127845, $95b794fd, $647d0862, $e7ccf5f0,
  197.                           $5449a36f, $877d48fa, $c39dfd27, $f33e8d1e, $0a476341, $992eff74,
  198.                           $3a6f6eab, $f4f8fd37, $a812dc60, $a1ebddf8, $991be14c, $db6e6b0d,
  199.                           $c67b5510, $6d672c37, $2765d43b, $dcd0e804, $f1290dc7, $cc00ffa3,
  200.                           $b5390f92, $690fed0b, $667b9ffb, $cedb7d9c, $a091cf0b, $d9155ea3,
  201.                           $bb132f88, $515bad24, $7b9479bf, $763bd6eb, $37392eb3, $cc115979,
  202.                           $8026e297, $f42e312d, $6842ada7, $c66a2b3b, $12754ccc, $782ef11c,
  203.                           $6a124237, $b79251e7, $06a1bbe6, $4bfb6350, $1a6b1018, $11caedfa,
  204.                           $3d25bdd8, $e2e1c3c9, $44421659, $0a121386, $d90cec6e, $d5abea2a,
  205.                           $64af674e, $da86a85f, $bebfe988, $64e4c3fe, $9dbc8057, $f0f7c086,
  206.                           $60787bf8, $6003604d, $d1fd8346, $f6381fb0, $7745ae04, $d736fccc,
  207.                           $83426b33, $f01eab71, $b0804187, $3c005e5f, $77a057be, $bde8ae24,
  208.                           $55464299, $bf582e61, $4e58f48f, $f2ddfda2, $f474ef38, $8789bdc2,
  209.                           $5366f9c3, $c8b38e74, $b475f255, $46fcd9b9, $7aeb2661, $8b1ddf84,
  210.                           $846a0e79, $915f95e2, $466e598e, $20b45770, $8cd55591, $c902de4c,
  211.                           $b90bace1, $bb8205d0, $11a86248, $7574a99e, $b77f19b6, $e0a9dc09,
  212.                           $662d09a1, $c4324633, $e85a1f02, $09f0be8c, $4a99a025, $1d6efe10,
  213.                           $1ab93d1d, $0ba5a4df, $a186f20f, $2868f169, $dcb7da83, $573906fe,
  214.                           $a1e2ce9b, $4fcd7f52, $50115e01, $a70683fa, $a002b5c4, $0de6d027,
  215.                           $9af88c27, $773f8641, $c3604c06, $61a806b5, $f0177a28, $c0f586e0,
  216.                           $006058aa, $30dc7d62, $11e69ed7, $2338ea63, $53c2dd94, $c2c21634,
  217.                           $bbcbee56, $90bcb6de, $ebfc7da1, $ce591d76, $6f05e409, $4b7c0188,
  218.                           $39720a3d, $7c927c24, $86e3725f, $724d9db9, $1ac15bb4, $d39eb8fc,
  219.                           $ed545578, $08fca5b5, $d83d7cd3, $4dad0fc4, $1e50ef5e, $b161e6f8,
  220.                           $a28514d9, $6c51133c, $6fd5c7e7, $56e14ec4, $362abfce, $ddc6c837,
  221.                           $d79a3234, $92638212, $670efa8e, $406000e0
  222.                 ),
  223.                 //SBox[3]
  224.                 (
  225.                           $3a39ce37, $d3faf5cf, $abc27737, $5ac52d1b, $5cb0679e, $4fa33742,
  226.                           $d3822740, $99bc9bbe, $d5118e9d, $bf0f7315, $d62d1c7e, $c700c47b,
  227.                           $b78c1b6b, $21a19045, $b26eb1be, $6a366eb4, $5748ab2f, $bc946e79,
  228.                           $c6a376d2, $6549c2c8, $530ff8ee, $468dde7d, $d5730a1d, $4cd04dc6,
  229.                           $2939bbdb, $a9ba4650, $ac9526e8, $be5ee304, $a1fad5f0, $6a2d519a,
  230.                     $63ef8ce2, $9a86ee22, $c089c2b8, $43242ef6, $a51e03aa, $9cf2d0a4,
  231.                     $83c061ba, $9be96a4d, $8fe51550, $ba645bd6, $2826a2f9, $a73a3ae1,
  232.                           $4ba99586, $ef5562e9, $c72fefd3, $f752f7da, $3f046f69, $77fa0a59,
  233.                           $80e4a915, $87b08601, $9b09e6ad, $3b3ee593, $e990fd5a, $9e34d797,
  234.                     $2cf0b7d9, $022b8b51, $96d5ac3a, $017da67d, $d1cf3ed6, $7c7d2d28,
  235.                     $1f9f25cf, $adf2b89b, $5ad6b472, $5a88f54c, $e029ac71, $e019a5e6,
  236.                     $47b0acfd, $ed93fa9b, $e8d3c48d, $283b57cc, $f8d56629, $79132e28,
  237.                     $785f0191, $ed756055, $f7960e44, $e3d35e8c, $15056dd4, $88f46dba,
  238.                     $03a16125, $0564f0bd, $c3eb9e15, $3c9057a2, $97271aec, $a93a072a,
  239.                     $1b3f6d9b, $1e6321f5, $f59c66fb, $26dcf319, $7533d928, $b155fdf5,
  240.                     $03563482, $8aba3cbb, $28517711, $c20ad9f8, $abcc5167, $ccad925f,
  241.                     $4de81751, $3830dc8e, $379d5862, $9320f991, $ea7a90c2, $fb3e7bce,
  242.                     $5121ce64, $774fbe32, $a8b6e37e, $c3293d46, $48de5369, $6413e680,
  243.                     $a2ae0810, $dd6db224, $69852dfd, $09072166, $b39a460a, $6445c0dd,
  244.                     $586cdecf, $1c20c8ae, $5bbef7dd, $1b588d40, $ccd2017f, $6bb4e3bb,
  245.                     $dda26a7e, $3a59ff45, $3e350a44, $bcb4cdd5, $72eacea8, $fa6484bb,
  246.                     $8d6612ae, $bf3c6f47, $d29be463, $542f5d9e, $aec2771b, $f64e6370,
  247.                     $740e0d8d, $e75b1357, $f8721671, $af537d5d, $4040cb08, $4eb4e2cc,
  248.                     $34d2466a, $0115af84, $e1b00428, $95983a1d, $06b89fb4, $ce6ea048,
  249.                     $6f3f3b82, $3520ab82, $011a1d4b, $277227f8, $611560b1, $e7933fdc,
  250.                     $bb3a792b, $344525bd, $a08839e1, $51ce794b, $2f32c9b7, $a01fbac9,
  251.                     $e01cc87e, $bcc7d1f6, $cf0111c3, $a1e8aac7, $1a908749, $d44fbd9a,
  252.                     $d0dadecb, $d50ada38, $0339c32a, $c6913667, $8df9317c, $e0b12b4f,
  253.                     $f79e59b7, $43f5bb3a, $f2d519ff, $27d9459c, $bf97222c, $15e6fc2a,
  254.                     $0f91fc71, $9b941525, $fae59361, $ceb69ceb, $c2a86459, $12baa8d1,
  255.                     $b6c1075e, $e3056a0c, $10d25065, $cb03a442, $e0ec6e0e, $1698db3b,
  256.                     $4c98a0be, $3278e964, $9f1f9532, $e0d392df, $d3a0342b, $8971f21e,
  257.                     $1b0a7441, $4ba3348c, $c5be7120, $c37632d8, $df359f8d, $9b992f2e,
  258.                     $e60b6f47, $0fe3f11d, $e54cda54, $1edad891, $ce6279cf, $cd3e7e6f,
  259.                     $1618b166, $fd2c1d05, $848fd2c5, $f6fb2299, $f523f357, $a6327623,
  260.                     $93a83531, $56cccd02, $acf08162, $5a75ebb5, $6e163697, $88d273cc,
  261.                     $de966292, $81b949d0, $4c50901b, $71c65614, $e6c6c7bd, $327a140a,
  262.                     $45e1d006, $c3f27b9a, $c9aa53fd, $62a80f00, $bb25bfe2, $35bdd2f6,
  263.                     $71126905, $b2040222, $b6cbcf7c, $cd769c2b, $53113ec0, $1640e3d3,
  264.                     $38abbd60, $2547adf0, $ba38209c, $f746ce76, $77afa1c5, $20756060,
  265.                     $85cbfe4e, $8ae88dd8, $7aaaf9b0, $4cf9aa7e, $1948c25c, $02fb8a8c,
  266.                           $01c36ae4, $d6ebe1f9, $90d4f869, $a65cdea0, $3f09252d, $c208e69f,
  267.                           $b74e6132, $ce77e25b, $578fdfe3, $3ac372e6
  268.                 )
  269.             );
  270.  
  271. {$R-}
  272.  
  273. //O = I1 xor I2
  274. procedure XorBlock(I1, I2, O1: PByteArray; Len: Integer);
  275. var
  276.     i: Integer;
  277. begin
  278.     for i := 0 to Len-1 do
  279.         O1[i] := I1[i] xor I2[i];
  280. end;
  281.  
  282. //P = P + 1
  283. procedure IncBlock(P: PByteArray; Len: Integer);
  284. begin
  285.     Inc(P[Len-1]);
  286.     if (P[Len-1]= 0) and (Len> 1) then
  287.         IncBlock(P,Len-1);
  288. end;
  289.  
  290. function BlowfishSelfTest;
  291.  
  292.     procedure t(Key, InBlock, ExpectedOutput: Pointer; KeyLength: Integer=8);
  293.     var
  294.         Block: array[0..7] of Byte;
  295.         Data: TBlowfishData;
  296.     begin
  297.         BlowfishInit(Data, Key, KeyLength, nil);
  298.         try
  299.             BlowfishEncryptECB(Data, InBlock, @Block);
  300.  
  301.             //Check the actual encrypted block matches the expected block
  302.             if not CompareMem(@Block, ExpectedOutput, Sizeof(Block)) then
  303.                 raise Exception.Create('Blowfish self-test failed.');
  304.  
  305.             //Now go backwards, decrypt the ciper to make sure we get the plaintext back
  306.             BlowfishDecryptECB(Data, @Block, @Block);
  307.  
  308.             //Check that decrypting results in original values
  309.             if not CompareMem(@Block, InBlock, Sizeof(Block)) then
  310.                 raise Exception.Create('Blowfish self-test failed.');
  311.         finally
  312.             BlowfishBurn(Data);
  313.         end;
  314.     end;
  315.  
  316.     function ByteSwap(const X: Int64): Int64;
  317.     begin
  318.         Result :=
  319.                 ((X and $00000000000000FF) shl 56) or
  320.                 ((X and $000000000000FF00) shl 40) or
  321.                 ((X and $0000000000FF0000) shl 24) or
  322.                 ((X and $00000000FF000000) shl  8) or
  323.                 ((X and $000000FF00000000) shr  8) or
  324.                 ((X and $0000FF0000000000) shr 24) or
  325.                 ((X and $00FF000000000000) shr 40) or
  326.                 ((X and $FF00000000000000) shr 56);
  327.     end;
  328.  
  329.     procedure t2(nKey, nIn, nOut: Int64);
  330.     var
  331.         key: array[0..7] of Byte;
  332.         inBlock: array[0..7] of Byte;
  333.         outBlock: array[0..7] of Byte;
  334.     begin
  335.         //The published test vectors are in big endian, we work in little endian
  336.         //Swap the endian of each
  337.         nKey := ByteSwap(nKey);
  338.         nIn := ByteSwap(nIn);
  339.         nOut := ByteSwap(nOut);
  340.  
  341.         Move(nKey, key[0], 8);
  342.         Move(nIn, inBlock[0], 8);
  343.         Move(nOut, outBlock[0], 8);
  344.  
  345.         t(@key[0], @inBlock[0], @outBlock[0]);
  346.     end;
  347.  
  348.     procedure t3(nOut: Int64; KeyLength: Integer);
  349.     var
  350.         nIn: Int64; //FEDCBA9876543210
  351.     const
  352.         baseKey: array[0..23] of Byte = ($F0, $E1, $D2, $C3, $B4, $A5, $96, $87, $78, $69, $5A, $4B, $3C, $2D, $1E, $0F, $00, $11, $22, $33, $44, $55, $66, $77);
  353.     begin
  354.         //Swap endian order of InBlock and expected outBlock
  355.         nIn := ByteSwap($FEDCBA9876543210);
  356.         nOut := ByteSwap(nOut);
  357.  
  358.         {
  359.             Hard part is swapping the endian order of the variable length key
  360.             The key if the Byte string F0E1D2C3B4A5968778695A4B3C2D1E0F0011223344556677
  361.             varying from 1 Byte to 24 bytes by taking more and more bytes from the key
  362.         }
  363.         t(@baseKey[0], @nIn, @nOut, KeyLength);
  364.     end;
  365. begin
  366.     {
  367.         Official test vectors from http://www.schneier.com/code/vectors.txt
  368.  
  369.         Test vectors by Eric Young.  These tests all assume Blowfish with 16
  370.         rounds.
  371.  
  372.         All data is shown as a hex string with 012345 loading as
  373.         data[0]=0x01;
  374.         data[1]=0x23;
  375.         data[2]=0x45;
  376.         ecb test data (taken from the DES validation tests)
  377.  
  378.         key bytes               clear bytes             cipher bytes
  379.     }
  380.     t2($0000000000000000, $0000000000000000, $4EF997456198DD78);
  381.     t2($FFFFFFFFFFFFFFFF, $FFFFFFFFFFFFFFFF, $51866FD5B85ECB8A);
  382.     t2($3000000000000000, $1000000000000001, $7D856F9A613063F2);
  383.     t2($1111111111111111, $1111111111111111, $2466DD878B963C9D);
  384.     t2($0123456789ABCDEF, $1111111111111111, $61F9C3802281B096);
  385.     t2($1111111111111111, $0123456789ABCDEF, $7D0CC630AFDA1EC7);
  386.     t2($0000000000000000, $0000000000000000, $4EF997456198DD78);
  387.     t2($FEDCBA9876543210, $0123456789ABCDEF, $0ACEAB0FC6A0A28D);
  388.     t2($7CA110454A1A6E57, $01A1D6D039776742, $59C68245EB05282B);
  389.     t2($0131D9619DC1376E, $5CD54CA83DEF57DA, $B1B8CC0B250F09A0);
  390.     t2($07A1133E4A0B2686, $0248D43806F67172, $1730E5778BEA1DA4);
  391.     t2($3849674C2602319E, $51454B582DDF440A, $A25E7856CF2651EB);
  392.     t2($04B915BA43FEB5B6, $42FD443059577FA2, $353882B109CE8F1A);
  393.     t2($0113B970FD34F2CE, $059B5E0851CF143A, $48F4D0884C379918);
  394.     t2($0170F175468FB5E6, $0756D8E0774761D2, $432193B78951FC98);
  395.     t2($43297FAD38E373FE, $762514B829BF486A, $13F04154D69D1AE5);
  396.     t2($07A7137045DA2A16, $3BDD119049372802, $2EEDDA93FFD39C79);
  397.     t2($04689104C2FD3B2F, $26955F6835AF609A, $D887E0393C2DA6E3);
  398.     t2($37D06BB516CB7546, $164D5E404F275232, $5F99D04F5B163969);
  399.     t2($1F08260D1AC2465E, $6B056E18759F5CCA, $4A057A3B24D3977B);
  400.     t2($584023641ABA6176, $004BD6EF09176062, $452031C1E4FADA8E);
  401.     t2($025816164629B007, $480D39006EE762F2, $7555AE39F59B87BD);
  402.     t2($49793EBC79B3258F, $437540C8698F3CFA, $53C55F9CB49FC019);
  403.     t2($4FB05E1515AB73A7, $072D43A077075292, $7A8E7BFA937E89A3);
  404.     t2($49E95D6D4CA229BF, $02FE55778117F12A, $CF9C5D7A4986ADB5);
  405.     t2($018310DC409B26D6, $1D9D5C5018F728C2, $D1ABB290658BC778);
  406.     t2($1C587F1C13924FEF, $305532286D6F295A, $55CB3774D13EF201);
  407.     t2($0101010101010101, $0123456789ABCDEF, $FA34EC4847B268B2);
  408.     t2($1F1F1F1F0E0E0E0E, $0123456789ABCDEF, $A790795108EA3CAE);
  409.     t2($E0FEE0FEF1FEF1FE, $0123456789ABCDEF, $C39E072D9FAC631D);
  410.     t2($0000000000000000, $FFFFFFFFFFFFFFFF, $014933E0CDAFF6E4);
  411.     t2($FFFFFFFFFFFFFFFF, $0000000000000000, $F21E9A77B71C49BC);
  412.     t2($0123456789ABCDEF, $0000000000000000, $245946885754369A);
  413.     t2($FEDCBA9876543210, $FFFFFFFFFFFFFFFF, $6B5C5A9C5D9E0A5A);
  414.  
  415.     //Encrypting [FEDCBA9876543210] with variable key length
  416.     //(expectedCiperOutput, numberOfBytesToUseFromSourceKey)
  417.     t3($F9AD597C49DB005E, 1);
  418.     t3($E91D21C1D961A6D6, 2);
  419.     t3($E9C2B70A1BC65CF3, 3);
  420.     t3($BE1E639408640F05, 4);
  421.     t3($B39E44481BDB1E6E, 5);
  422.     t3($9457AA83B1928C0D, 6);
  423.     t3($8BB77032F960629D, 7);
  424.     t3($E87A244E2CC85E82, 8);
  425.     t3($15750E7A4F4EC577, 9);
  426.     t3($122BA70B3AB64AE0, 10);
  427.     t3($3A833C9AFFC537F6, 11);
  428.     t3($9409DA87A90F6BF2, 12);
  429.     t3($884F80625060B8B4, 13);
  430.     t3($1F85031C19E11968, 14);
  431.     t3($79D9373A714CA34F, 15);
  432.     t3($93142887EE3BE15C, 16);
  433.     t3($03429E838CE2D14B, 17);
  434.     t3($A4299E27469FF67B, 18);
  435.     t3($AFD5AED1C1BC96A8, 19);
  436.     t3($10851C0E3858DA9F, 20);
  437.     t3($E6F51ED79B9DB21F, 21);
  438.     t3($64A6E14AFD36B46F, 22);
  439.     t3($80C7D7D45A5479AD, 23);
  440.     t3($05044B62FA52D080, 24);
  441.     //Blowfish supports key lengths up to 448 bits (56 bytes).
  442.     //But we only have test vectors up to 192 bits (24 bytes)
  443.  
  444.     {
  445.         TODO: Test chaining modes
  446.  
  447.         chaining mode test data
  448.         key[16]   = 0123456789ABCDEFF0E1D2C3B4A59687
  449.         iv[8]     = FEDCBA9876543210
  450.         data[29]  = "7654321 Now is the time for " (includes trailing '\0')
  451.         data[29]  = 37363534333231204E6F77206973207468652074696D6520666F722000
  452.  
  453.         cbc cipher text
  454.             cipher[32]= 6B77B4D63006DEE605B156E27403979358DEB9E7154616D959F1652BD5FF92CC
  455.         cfb64 cipher text cipher[29]=
  456.             E73214A2822139CAF26ECF6D2EB9E76E3DA3DE04D1517200519D57A6C3
  457.         ofb64 cipher text cipher[29]=
  458.             E73214A2822139CA62B343CC5B65587310DD908D0C241B2263C2CF80DA
  459.     }
  460.  
  461.     Result := True;
  462. end;
  463.  
  464. procedure BlowfishInit(out Data: TBlowfishData; Key: Pointer; Len: Integer; IV: Pointer);
  465. var
  466.   i, k: Integer;
  467.   A: DWord;
  468.   KeyB: PByteArray;
  469.   Block: array[0..7] of Byte;
  470. begin
  471.     if (Len <= 0) or (Len > 56) then
  472.         raise Exception.Create('Blowfish: Key must be between 1 and 56 bytes long');
  473.  
  474.     {
  475.         Copy the digits of the number pi first into the subkeys,
  476.         then into the S-boxes.
  477.     }
  478.     BlowfishInitState(Data);
  479.  
  480.     with Data do
  481.     begin
  482.         {
  483.             XOR all the subkeys in the P-array with the encryption key
  484.             The first 32 bits of the key are XORed with P1, the next 32 bits with P2, and so on.
  485.             The key is viewed as being cyclic; when the process reaches the end of the key,
  486.             it starts reusing bits from the beginning to XOR with subkeys.
  487.         }
  488.         KeyB := Key;
  489.         k := 0;
  490.         for i := 0 to 17 do
  491.         begin
  492.             A :=      KeyB[(k+3) mod Len];
  493.             A := A + (KeyB[(k+2) mod Len] shl 8);
  494.             A := A + (KeyB[(k+1) mod Len] shl 16);
  495.             A := A + (KeyB[k]             shl 24);
  496.             PBoxM[i] := PBoxM[i] xor A;
  497.             k := (k+4) mod Len;
  498.         end;
  499.  
  500.         //Blowfsh-encrypt the first 64 bits of its salt argument using the current state of the key schedule.
  501.         if IV = nil then
  502.         begin
  503.             FillChar(InitBlock, 8, 0);
  504.             FillChar(LastBlock, 8, 0);
  505.         end
  506.         else
  507.         begin
  508.             Move(IV^, InitBlock, 8);
  509.             Move(IV^, LastBlock, 8);
  510.         end;
  511.  
  512.         FillChar(Block, Sizeof(Block), 0);
  513.         for i := 0 to 8 do
  514.         begin
  515.             BlowfishEncryptECB(Data, @Block, @Block);
  516.  
  517.             PBoxM[i*2] :=   Block[3] + (Block[2] shl 8) + (Block[1] shl 16) + (Block[0] shl 24);
  518.             PBoxM[i*2+1] := Block[7] + (Block[6] shl 8) + (Block[5] shl 16) + (Block[4] shl 24);
  519.         end;
  520.  
  521.  
  522.         for k := 0 to 3 do
  523.         begin
  524.             for i := 0 to 127 do
  525.             begin
  526.                 BlowfishEncryptECB(Data, @Block, @Block);
  527.                 SBoxM[k, i*2] :=   Block[3] + (Block[2] shl 8) + (Block[1] shl 16) + (Block[0] shl 24);
  528.                 SBoxM[k, i*2+1] := Block[7] + (Block[6] shl 8) + (Block[5] shl 16) + (Block[4] shl 24);
  529.             end;
  530.         end;
  531.     end;
  532. end;
  533.  
  534. procedure BlowfishInitState(var State: TBlowfishData);
  535. begin
  536.     Move(SBox, State.SBoxM, Sizeof(SBox));
  537.     Move(PBox, State.PBoxM, Sizeof(PBox));
  538. end;
  539.  
  540. procedure BlowfishBurn(var State: TBlowfishData);
  541. begin
  542.   FillChar(State, Sizeof(State), 0);
  543. end;
  544.  
  545. {$OVERFLOWCHECKS OFF}
  546. procedure BlowfishEncryptECB(const Data: TBlowfishData; InData, OutData: Pointer);
  547. var
  548.   xL, xR: DWord;
  549. begin
  550.   Move(InData^, xL, 4);
  551.   Move(Pointer(Integer(InData)+4)^, xR, 4);
  552.   xL := (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  553.   xR := (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  554.   xL := xL xor Data.PBoxM[0];
  555.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[1];
  556.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[2];
  557.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[3];
  558.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[4];
  559.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[5];
  560.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[6];
  561.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[7];
  562.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[8];
  563.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[9];
  564.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[10];
  565.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[11];
  566.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[12];
  567.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[13];
  568.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[14];
  569.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[15];
  570.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[16];
  571.   xR := xR xor Data.PBoxM[17];
  572.   xL := (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  573.   xR := (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  574.   Move(xR, OutData^, 4);
  575.   Move(xL, Pointer(Integer(OutData)+4)^, 4);
  576. end;
  577.  
  578. procedure BlowfishDecryptECB(const Data: TBlowfishData; InData, OutData: Pointer);
  579. var
  580.   xL, xR: DWord;
  581. begin
  582.   Move(InData^, xL, 4);
  583.   Move(Pointer(Integer(InData)+4)^, xR, 4);
  584.   xL := (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  585.   xR := (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  586.   xL := xL xor Data.PBoxM[17];
  587.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[16];
  588.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[15];
  589.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[14];
  590.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[13];
  591.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[12];
  592.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[11];
  593.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[10];
  594.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[9];
  595.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[8];
  596.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[7];
  597.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[6];
  598.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[5];
  599.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[4];
  600.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[3];
  601.   xR := xR xor (((Data.SBoxM[0, (xL shr 24) and $FF] + Data.SBoxM[1, (xL shr 16) and $FF]) xor Data.SBoxM[2, (xL shr 8) and $FF]) + Data.SBoxM[3, xL and $FF]) xor Data.PBoxM[2];
  602.   xL := xL xor (((Data.SBoxM[0, (xR shr 24) and $FF] + Data.SBoxM[1, (xR shr 16) and $FF]) xor Data.SBoxM[2, (xR shr 8) and $FF]) + Data.SBoxM[3, xR and $FF]) xor Data.PBoxM[1];
  603.   xR := xR xor Data.PBoxM[0];
  604.   xL := (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  605.   xR := (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  606.   Move(xR, OutData^, 4);
  607.   Move(xL, Pointer(Integer(OutData)+4)^, 4);
  608. end;
  609. {$OVERFLOWCHECKS ON}
  610.  
  611. procedure BlowfishEncryptCBC(var Data: TBlowfishData; InData, OutData: Pointer);
  612. begin
  613.   XorBlock(InData, @Data.LastBlock, OutData, 8);
  614.   BlowfishEncryptECB(Data, OutData, OutData);
  615.   Move(OutData^, Data.LastBlock, 8);
  616. end;
  617.  
  618. procedure BlowfishDecryptCBC(var Data: TBlowfishData; InData, OutData: Pointer);
  619. var
  620.   TempBlock: array[0..7] of Byte;
  621. begin
  622.   Move(InData^, TempBlock, 8);
  623.   BlowfishDecryptECB(Data, InData, OutData);
  624.   XorBlock(OutData, @Data.LastBlock, OutData, 8);
  625.   Move(TempBlock, Data.LastBlock, 8);
  626. end;
  627.  
  628. procedure BlowfishEncryptCFB(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  629. var
  630.   i: Integer;
  631.   TempBlock: array[0..7] of Byte;
  632. begin
  633.   for i := 0 to Len-1 do
  634.   begin
  635.     BlowfishEncryptECB(Data, @Data.LastBlock, @TempBlock);
  636.     PByteArray(OutData)[i] := PByteArray(InData)[i] xor TempBlock[0];
  637.     Move(Data.LastBlock[1], Data.LastBlock[0], 7);
  638.     Data.LastBlock[7] := PByteArray(OutData)[i];
  639.   end;
  640. end;
  641.  
  642. procedure BlowfishDecryptCFB(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  643. var
  644.   i: Integer;
  645.   TempBlock: array[0..7] of Byte;
  646.   b: Byte;
  647. begin
  648.   for i := 0 to Len-1 do
  649.   begin
  650.     b := PByteArray(InData)[i];
  651.     BlowfishEncryptECB(Data, @Data.LastBlock, @TempBlock);
  652.     PByteArray(OutData)[i] := PByteArray(InData)[i] xor TempBlock[0];
  653.     Move(Data.LastBlock[1], Data.LastBlock[0], 7);
  654.     Data.LastBlock[7] := b;
  655.   end;
  656. end;
  657.  
  658. procedure BlowfishEncryptOFB(var Data: TBlowfishData; InData, OutData: Pointer);
  659. begin
  660.   BlowfishEncryptECB(Data, @Data.LastBlock, @Data.LastBlock);
  661.   XorBlock(@Data.LastBlock, InData, OutData, 8);
  662. end;
  663.  
  664. procedure BlowfishDecryptOFB(var Data: TBlowfishData; InData, OutData: Pointer);
  665. begin
  666.   BlowfishEncryptECB(Data, @Data.LastBlock, @Data.LastBlock);
  667.   XorBlock(@Data.LastBlock, InData, OutData, 8);
  668. end;
  669.  
  670. procedure BlowfishEncryptOFBC(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  671. var
  672.   i: Integer;
  673.   TempBlock: array[0..7] of Byte;
  674. begin
  675.   for i := 0 to Len-1 do
  676.   begin
  677.     BlowfishEncryptECB(Data, @Data.LastBlock, @TempBlock);
  678.     PByteArray(OutData)[i] := PByteArray(InData)[i] xor TempBlock[0];
  679.     IncBlock(@Data.LastBlock, 8);
  680.   end;
  681. end;
  682.  
  683. procedure BlowfishDecryptOFBC(var Data: TBlowfishData; InData, OutData: Pointer; Len: Integer);
  684. var
  685.   i: Integer;
  686.   TempBlock: array[0..7] of Byte;
  687. begin
  688.   for i := 0 to Len-1 do
  689.   begin
  690.     BlowfishEncryptECB(Data, @Data.LastBlock, @TempBlock);
  691.      PByteArray(OutData)[i] := PByteArray(InData)[i] xor TempBlock[0];
  692.     IncBlock(@Data.LastBlock, 8);
  693.   end;
  694. end;
  695.  
  696. procedure BlowfishReset(var Data: TBlowfishData);
  697. begin
  698.   Move(Data.InitBlock, Data.LastBlock, 8);
  699. end;
  700.  
  701. { TBlowfishTests }
  702.  
  703. {$IFDEF UnitTests}
  704. procedure TBlowfishTests.SelfTest;
  705. begin
  706.     CheckTrue(BlowfishSelfTest);
  707. end;
  708. {$ENDIF}
  709.  
  710. initialization
  711. {$IFDEF UnitTests}
  712.     RegisterTest('Library', TBlowfishTests.Suite);
  713. {$ENDIF}
  714.  
  715. end.
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement