home *** CD-ROM | disk | FTP | other *** search
/ Xentax forum attachments archive / xentax.7z / 5506 / src.7z / SEGA_BlowFish.pas < prev    next >
Encoding:
Pascal/Delphi Source File  |  2012-02-12  |  25.2 KB  |  543 lines

  1. {
  2. ***************************************************
  3. * A binary compatible Blowfish implementation     *
  4. * written by Dave Barton (davebarton@bigfoot.com) *
  5. ***************************************************
  6. * 64bit block encryption                          *
  7. * Variable size key - up to 448bit                *
  8. *
  9. * http://svn.inspircd.org/index.cgi/trunk/winbot/Blowfish.pas?revision=4992&view=markup
  10. ***************************************************
  11. }
  12. unit SEGA_BlowFish;
  13.  
  14. interface
  15.  
  16. uses
  17.   Windows, SysUtils;
  18.  
  19. type
  20.   TBlowfishData= record
  21.     InitBlock: array[0..7] of byte;    { initial IV }
  22.     LastBlock: array[0..7] of byte;    { current IV }
  23.  
  24.     PBoxM: array[0..17] of DWORD;
  25.     SBoxM: array[0..3,0..255] of DWORD;
  26.   end;
  27.  
  28.  
  29. procedure BlowfishInit(var Data: TBlowfishData; Key: pointer; Len: integer; IV: pointer);
  30.   { initializes the TBlowfishData structure with the key information and IV if applicable }
  31. procedure BlowfishDecryptECB(const Data: TBlowfishData; InData, OutData: pointer);
  32.   { decrypts the data in a 64bit block using the ECB mode }  
  33. procedure BlowfishEncryptECB(const Data: TBlowfishData; InData, OutData: pointer);
  34.   { encrypts the data in a 64bit block using the ECB mode }
  35.  
  36. Var
  37.     SEGAfish : TBlowfishData;
  38.  
  39.     PBox: array[0..17] of DWORD = (
  40.                             $243f6a88, $85a308d3, $13198a2e, $03707344,
  41.                             $a4093822, $299f31d0, $082efa98, $ec4e6c89,
  42.                             $452821e6, $38d01377, $be5466cf, $34e90c6c,
  43.                             $c0ac29b7, $c97c50dd, $3f84d5b5, $b5470917,
  44.                             $9216d5d9, $8979fb1b);
  45.     SBox: array[0..3,0..255] of DWORD = ((
  46.                             $d1310ba6, $98dfb5ac, $2ffd72db, $d01adfb7,
  47.                             $b8e1afed, $6a267e96, $ba7c9045, $f12c7f99,
  48.                             $24a19947, $b3916cf7, $0801f2e2, $858efc16,
  49.                             $636920d8, $71574e69, $a458fea3, $f4933d7e,
  50.  
  51.                             $0d95748f, $728eb658, $718bcd58, $82154aee,
  52.                             $7b54a41d, $c25a59b5, $9c30d539, $2af26013,
  53.                             $c5d1b023, $286085f0, $ca417918, $b8db38ef,
  54.                             $8e79dcb0, $603a180e, $6c9e0e8b, $b01e8a3e,
  55.  
  56.                             $d71577c1, $bd314b27, $78af2fda, $55605c60,
  57.                             $e65525f3, $aa55ab94, $57489862, $63e81440,
  58.                             $55ca396a, $2aab10b6, $b4cc5c34, $1141e8ce,
  59.                             $a15486af, $7c72e993, $b3ee1411, $636fbc2a,
  60.  
  61.                             $2ba9c55d, $741831f6, $ce5c3e16, $9b87931e,
  62.                             $afd6ba33, $6c24cf5c, $7a325381, $28958677,
  63.                             $3b8f4898, $6b4bb9af, $c4bfe81b, $66282193,
  64.                             $61d809cc, $fb21a991, $487cac60, $5dec8032,
  65.  
  66.                             $ef845d5d, $e98575b1, $dc262302, $eb651b88,
  67.                             $23893e81, $d396acc5, $0f6d6ff3, $83f44239,
  68.                             $2e0b4482, $a4842004, $69c8f04a, $9e1f9b5e,
  69.                             $21c66842, $f6e96c9a, $670c9c61, $abd388f0,
  70.  
  71.                             $6a51a0d2, $d8542f68, $960fa728, $ab5133a3,
  72.                             $6eef0b6c, $137a3be4, $ba3bf050, $7efb2a98,
  73.                             $a1f1651d, $39af0176, $66ca593e, $82430e88,
  74.                             $8cee8619, $456f9fb4, $7d84a5c3, $3b8b5ebe,
  75.  
  76.                             $e06f75d8, $85c12073, $401a449f, $56c16aa6,
  77.                             $4ed3aa62, $363f7706, $1bfedf72, $429b023d,
  78.                             $37d0d724, $d00a1248, $db0fead3, $49f1c09b,
  79.                             $075372c9, $80991b7b, $25d479d8, $f6e8def7,
  80.  
  81.                             $e3fe501a, $b6794c3b, $976ce0bd, $04c006ba,
  82.                             $c1a94fb6, $409f60c4, $5e5c9ec2, $196a2463,
  83.                             $68fb6faf, $3e6c53b5, $1339b2eb, $3b52ec6f,
  84.                             $6dfc511f, $9b30952c, $cc814544, $af5ebd09,
  85.  
  86.                             $bee3d004, $de334afd, $660f2807, $192e4bb3,
  87.                             $c0cba857, $45c8740f, $d20b5f39, $b9d3fbdb,
  88.                             $5579c0bd, $1a60320a, $d6a100c6, $402c7279,
  89.                             $679f25fe, $fb1fa3cc, $8ea5e9f8, $db3222f8,
  90.  
  91.                             $3c7516df, $fd616b15, $2f501ec8, $ad0552ab,
  92.                             $323db5fa, $fd238760, $53317b48, $3e00df82,
  93.                             $9e5c57bb, $ca6f8ca0, $1a87562e, $df1769db,
  94.                             $d542a8f6, $287effc3, $ac6732c6, $8c4f5573,
  95.  
  96.                             $695b27b0, $bbca58c8, $e1ffa35d, $b8f011a0,
  97.                             $10fa3d98, $fd2183b8, $4afcb56c, $2dd1d35b,
  98.                             $9a53e479, $b6f84565, $d28e49bc, $4bfb9790,
  99.                             $e1ddf2da, $a4cb7e33, $62fb1341, $cee4c6e8,
  100.  
  101.                             $ef20cada, $36774c01, $d07e9efe, $2bf11fb4,
  102.                             $95dbda4d, $ae909198, $eaad8e71, $6b93d5a0,
  103.                             $d08ed1d0, $afc725e0, $8e3c5b2f, $8e7594b7,
  104.                             $8ff6e2fb, $f2122b64, $8888b812, $900df01c,
  105.  
  106.                             $4fad5ea0, $688fc31c, $d1cff191, $b3a8c1ad,
  107.                             $2f2f2218, $be0e1777, $ea752dfe, $8b021fa1,
  108.                             $e5a0cc0f, $b56f74e8, $18acf3d6, $ce89e299,
  109.                             $b4a84fe0, $fd13e0b7, $7cc43b81, $d2ada8d9,
  110.  
  111.                             $165fa266, $80957705, $93cc7314, $211a1477,
  112.                             $e6ad2065, $77b5fa86, $c75442f5, $fb9d35cf,
  113.                             $ebcdaf0c, $7b3e89a0, $d6411bd3, $ae1e7e49,
  114.                             $00250e2d, $2071b35e, $226800bb, $57b8e0af,
  115.  
  116.                             $2464369b, $f009b91e, $5563911d, $59dfa6aa,
  117.                             $78c14389, $d95a537f, $207d5ba2, $02e5b9c5,
  118.                             $83260376, $6295cfa9, $11c81968, $4e734a41,
  119.                             $b3472dca, $7b14a94a, $1b510052, $9a532915,
  120.  
  121.                             $d60f573f, $bc9bc6e4, $2b60a476, $81e67400,
  122.                             $08ba6fb5, $571be91f, $f296ec6b, $2a0dd915,
  123.                             $b6636521, $e7b9f9b6, $ff34052e, $c5855664,
  124.                             $53b02d5d, $a99f8fa1, $08ba4799, $6e85076a),(
  125.  
  126.                             $4b7a70e9, $b5b32944, $db75092e, $c4192623,
  127.                             $ad6ea6b0, $49a7df7d, $9cee60b8, $8fedb266,
  128.                             $ecaa8c71, $699a17ff, $5664526c, $c2b19ee1,
  129.                             $193602a5, $75094c29, $a0591340, $e4183a3e,
  130.  
  131.                             $3f54989a, $5b429d65, $6b8fe4d6, $99f73fd6,
  132.                             $a1d29c07, $efe830f5, $4d2d38e6, $f0255dc1,
  133.                             $4cdd2086, $8470eb26, $6382e9c6, $021ecc5e,
  134.                             $09686b3f, $3ebaefc9, $3c971814, $6b6a70a1,
  135.  
  136.                             $687f3584, $52a0e286, $b79c5305, $aa500737,
  137.                             $3e07841c, $7fdeae5c, $8e7d44ec, $5716f2b8,
  138.                             $b03ada37, $f0500c0d, $f01c1f04, $0200b3ff,
  139.                             $ae0cf51a, $3cb574b2, $25837a58, $dc0921bd,
  140.  
  141.                             $d19113f9, $7ca92ff6, $94324773, $22f54701,
  142.                             $3ae5e581, $37c2dadc, $c8b57634, $9af3dda7,
  143.                             $a9446146, $0fd0030e, $ecc8c73e, $a4751e41,
  144.                             $e238cd99, $3bea0e2f, $3280bba1, $183eb331,
  145.  
  146.                             $4e548b38, $4f6db908, $6f420d03, $f60a04bf,
  147.                             $2cb81290, $24977c79, $5679b072, $bcaf89af,
  148.                             $de9a771f, $d9930810, $b38bae12, $dccf3f2e,
  149.                             $5512721f, $2e6b7124, $501adde6, $9f84cd87,
  150.  
  151.                             $7a584718, $7408da17, $bc9f9abc, $e94b7d8c,
  152.                             $ec7aec3a, $db851dfa, $63094366, $c464c3d2,
  153.                             $ef1c1847, $3215d908, $dd433b37, $24c2ba16,
  154.                             $12a14d43, $2a65c451, $50940002, $133ae4dd,
  155.  
  156.                             $71dff89e, $10314e55, $81ac77d6, $5f11199b,
  157.                             $043556f1, $d7a3c76b, $3c11183b, $5924a509,
  158.                             $f28fe6ed, $97f1fbfa, $9ebabf2c, $1e153c6e,
  159.                             $86e34570, $eae96fb1, $860e5e0a, $5a3e2ab3,
  160.  
  161.                             $771fe71c, $4e3d06fa, $2965dcb9, $99e71d0f,
  162.                             $803e89d6, $5266c825, $2e4cc978, $9c10b36a,
  163.                             $c6150eba, $94e2ea78, $a5fc3c53, $1e0a2df4,
  164.                             $f2f74ea7, $361d2b3d, $1939260f, $19c27960,
  165.  
  166.                             $5223a708, $f71312b6, $ebadfe6e, $eac31f66,
  167.                             $e3bc4595, $a67bc883, $b17f37d1, $018cff28,
  168.                             $c332ddef, $be6c5aa5, $65582185, $68ab9802,
  169.                             $eecea50f, $db2f953b, $2aef7dad, $5b6e2f84,
  170.  
  171.                             $1521b628, $29076170, $ecdd4775, $619f1510,
  172.                             $13cca830, $eb61bd96, $0334fe1e, $aa0363cf,
  173.                             $b5735c90, $4c70a239, $d59e9e0b, $cbaade14,
  174.                             $eecc86bc, $60622ca7, $9cab5cab, $b2f3846e,
  175.  
  176.                             $648b1eaf, $19bdf0ca, $a02369b9, $655abb50,
  177.                             $40685a32, $3c2ab4b3, $319ee9d5, $c021b8f7,
  178.                             $9b540b19, $875fa099, $95f7997e, $623d7da8,
  179.                             $f837889a, $97e32d77, $11ed935f, $16681281,
  180.  
  181.                             $0e358829, $c7e61fd6, $96dedfa1, $7858ba99,
  182.                             $57f584a5, $1b227263, $9b83c3ff, $1ac24696,
  183.                             $cdb30aeb, $532e3054, $8fd948e4, $6dbc3128,
  184.                             $58ebf2ef, $34c6ffea, $fe28ed61, $ee7c3c73,
  185.  
  186.                             $5d4a14d9, $e864b7e3, $42105d14, $203e13e0,
  187.                             $45eee2b6, $a3aaabea, $db6c4f15, $facb4fd0,
  188.                             $c742f442, $ef6abbb5, $654f3b1d, $41cd2105,
  189.                             $d81e799e, $86854dc7, $e44b476a, $3d816250,
  190.  
  191.                             $cf62a1f2, $5b8d2646, $fc8883a0, $c1c7b6a3,
  192.                             $7f1524c3, $69cb7492, $47848a0b, $5692b285,
  193.                             $095bbf00, $ad19489d, $1462b174, $23820e00,
  194.                             $58428d2a, $0c55f5ea, $1dadf43e, $233f7061,
  195.  
  196.                             $3372f092, $8d937e41, $d65fecf1, $6c223bdb,
  197.                             $7cde3759, $cbee7460, $4085f2a7, $ce77326e,
  198.                             $a6078084, $19f8509e, $e8efd855, $61d99735,
  199.                             $a969a7aa, $c50c06c2, $5a04abfc, $800bcadc,
  200.  
  201.                             $9e447a2e, $c3453484, $fdd56705, $0e1e9ec9,
  202.                             $db73dbd3, $105588cd, $675fda79, $e3674340,
  203.                             $c5c43465, $713e38d8, $3d28f89e, $f16dff20,
  204.                             $153e21e7, $8fb03d4a, $e6e39f2b, $db83adf7),(
  205.  
  206.                             $e93d5a68, $948140f7, $f64c261c, $94692934,
  207.                             $411520f7, $7602d4f7, $bcf46b2e, $d4a20068,
  208.                             $d4082471, $3320f46a, $43b7d4b7, $500061af,
  209.                             $1e39f62e, $97244546, $14214f74, $bf8b8840,
  210.  
  211.                             $4d95fc1d, $96b591af, $70f4ddd3, $66a02f45,
  212.                             $bfbc09ec, $03bd9785, $7fac6dd0, $31cb8504,
  213.                             $96eb27b3, $55fd3941, $da2547e6, $abca0a9a,
  214.                             $28507825, $530429f4, $0a2c86da, $e9b66dfb,
  215.  
  216.                             $68dc1462, $d7486900, $680ec0a4, $27a18dee,
  217.                             $4f3ffea2, $e887ad8c, $b58ce006, $7af4d6b6,
  218.                             $aace1e7c, $d3375fec, $ce78a399, $406b2a42,
  219.                             $20fe9e35, $d9f385b9, $ee39d7ab, $3b124e8b,
  220.  
  221.                             $1dc9faf7, $4b6d1856, $26a36631, $eae397b2,
  222.                             $3a6efa74, $dd5b4332, $6841e7f7, $ca7820fb,
  223.                             $fb0af54e, $d8feb397, $454056ac, $ba489527,
  224.                             $55533a3a, $20838d87, $fe6ba9b7, $d096954b,
  225.  
  226.                             $55a867bc, $a1159a58, $cca92963, $99e1db33,
  227.                             $a62a4a56, $3f3125f9, $5ef47e1c, $9029317c,
  228.                             $fdf8e802, $04272f70, $80bb155c, $05282ce3,
  229.                             $95c11548, $e4c66d22, $48c1133f, $c70f86dc,
  230.  
  231.                             $07f9c9ee, $41041f0f, $404779a4, $5d886e17,
  232.                             $325f51eb, $d59bc0d1, $f2bcc18f, $41113564,
  233.                             $257b7834, $602a9c60, $dff8e8a3, $1f636c1b,
  234.                             $0e12b4c2, $02e1329e, $af664fd1, $cad18115,
  235.  
  236.                             $6b2395e0, $333e92e1, $3b240b62, $eebeb922,
  237.                             $85b2a20e, $e6ba0d99, $de720c8c, $2da2f728,
  238.                             $d0127845, $95b794fd, $647d0862, $e7ccf5f0,
  239.                             $5449a36f, $877d48fa, $c39dfd27, $f33e8d1e,
  240.  
  241.                             $0a476341, $992eff74, $3a6f6eab, $f4f8fd37,
  242.                             $a812dc60, $a1ebddf8, $991be14c, $db6e6b0d,
  243.                             $c67b5510, $6d672c37, $2765d43b, $dcd0e804,
  244.                             $f1290dc7, $cc00ffa3, $b5390f92, $690fed0b,
  245.  
  246.                             $667b9ffb, $cedb7d9c, $a091cf0b, $d9155ea3,
  247.                             $bb132f88, $515bad24, $7b9479bf, $763bd6eb,
  248.                             $37392eb3, $cc115979, $8026e297, $f42e312d,
  249.                             $6842ada7, $c66a2b3b, $12754ccc, $782ef11c,
  250.  
  251.                             $6a124237, $b79251e7, $06a1bbe6, $4bfb6350,
  252.                             $1a6b1018, $11caedfa, $3d25bdd8, $e2e1c3c9,
  253.                             $44421659, $0a121386, $d90cec6e, $d5abea2a,
  254.                             $64af674e, $da86a85f, $bebfe988, $64e4c3fe,
  255.  
  256.                             $9dbc8057, $f0f7c086, $60787bf8, $6003604d,
  257.                             $d1fd8346, $f6381fb0, $7745ae04, $d736fccc,
  258.                             $83426b33, $f01eab71, $b0804187, $3c005e5f,
  259.                             $77a057be, $bde8ae24, $55464299, $bf582e61,
  260.  
  261.                             $4e58f48f, $f2ddfda2, $f474ef38, $8789bdc2,
  262.                             $5366f9c3, $c8b38e74, $b475f255, $46fcd9b9,
  263.                             $7aeb2661, $8b1ddf84, $846a0e79, $915f95e2,
  264.                             $466e598e, $20b45770, $8cd55591, $c902de4c,
  265.  
  266.                             $b90bace1, $bb8205d0, $11a86248, $7574a99e,
  267.                             $b77f19b6, $e0a9dc09, $662d09a1, $c4324633,
  268.                             $e85a1f02, $09f0be8c, $4a99a025, $1d6efe10,
  269.                             $1ab93d1d, $0ba5a4df, $a186f20f, $2868f169,
  270.  
  271.                             $dcb7da83, $573906fe, $a1e2ce9b, $4fcd7f52,
  272.                             $50115e01, $a70683fa, $a002b5c4, $0de6d027,
  273.                             $9af88c27, $773f8641, $c3604c06, $61a806b5,
  274.                             $f0177a28, $c0f586e0, $006058aa, $30dc7d62,
  275.  
  276.                             $11e69ed7, $2338ea63, $53c2dd94, $c2c21634,
  277.                             $bbcbee56, $90bcb6de, $ebfc7da1, $ce591d76,
  278.                             $6f05e409, $4b7c0188, $39720a3d, $7c927c24,
  279.                             $86e3725f, $724d9db9, $1ac15bb4, $d39eb8fc,
  280.  
  281.                             $ed545578, $08fca5b5, $d83d7cd3, $4dad0fc4,
  282.                             $1e50ef5e, $b161e6f8, $a28514d9, $6c51133c,
  283.                             $6fd5c7e7, $56e14ec4, $362abfce, $ddc6c837,
  284.                             $d79a3234, $92638212, $670efa8e, $406000e0),(
  285.  
  286.                             $3a39ce37, $d3faf5cf, $abc27737, $5ac52d1b,
  287.                             $5cb0679e, $4fa33742, $d3822740, $99bc9bbe,
  288.                             $d5118e9d, $bf0f7315, $d62d1c7e, $c700c47b,
  289.                             $b78c1b6b, $21a19045, $b26eb1be, $6a366eb4,
  290.  
  291.                             $5748ab2f, $bc946e79, $c6a376d2, $6549c2c8,
  292.                             $530ff8ee, $468dde7d, $d5730a1d, $4cd04dc6,
  293.                             $2939bbdb, $a9ba4650, $ac9526e8, $be5ee304,
  294.                             $a1fad5f0, $6a2d519a, $63ef8ce2, $9a86ee22,
  295.  
  296.                             $c089c2b8, $43242ef6, $a51e03aa, $9cf2d0a4,
  297.                             $83c061ba, $9be96a4d, $8fe51550, $ba645bd6,
  298.                             $2826a2f9, $a73a3ae1, $4ba99586, $ef5562e9,
  299.                             $c72fefd3, $f752f7da, $3f046f69, $77fa0a59,
  300.  
  301.                             $80e4a915, $87b08601, $9b09e6ad, $3b3ee593,
  302.                             $e990fd5a, $9e34d797, $2cf0b7d9, $022b8b51,
  303.                             $96d5ac3a, $017da67d, $d1cf3ed6, $7c7d2d28,
  304.                             $1f9f25cf, $adf2b89b, $5ad6b472, $5a88f54c,
  305.  
  306.                             $e029ac71, $e019a5e6, $47b0acfd, $ed93fa9b,
  307.                             $e8d3c48d, $283b57cc, $f8d56629, $79132e28,
  308.                             $785f0191, $ed756055, $f7960e44, $e3d35e8c,
  309.                             $15056dd4, $88f46dba, $03a16125, $0564f0bd,
  310.  
  311.                             $c3eb9e15, $3c9057a2, $97271aec, $a93a072a,
  312.                             $1b3f6d9b, $1e6321f5, $f59c66fb, $26dcf319,
  313.                             $7533d928, $b155fdf5, $03563482, $8aba3cbb,
  314.                             $28517711, $c20ad9f8, $abcc5167, $ccad925f,
  315.  
  316.                             $4de81751, $3830dc8e, $379d5862, $9320f991,
  317.                             $ea7a90c2, $fb3e7bce, $5121ce64, $774fbe32,
  318.                             $a8b6e37e, $c3293d46, $48de5369, $6413e680,
  319.                             $a2ae0810, $dd6db224, $69852dfd, $09072166,
  320.  
  321.                             $b39a460a, $6445c0dd, $586cdecf, $1c20c8ae,
  322.                             $5bbef7dd, $1b588d40, $ccd2017f, $6bb4e3bb,
  323.                             $dda26a7e, $3a59ff45, $3e350a44, $bcb4cdd5,
  324.                             $72eacea8, $fa6484bb, $8d6612ae, $bf3c6f47,
  325.  
  326.                             $d29be463, $542f5d9e, $aec2771b, $f64e6370,
  327.                             $740e0d8d, $e75b1357, $f8721671, $af537d5d,
  328.                             $4040cb08, $4eb4e2cc, $34d2466a, $0115af84,
  329.                             $e1b00428, $95983a1d, $06b89fb4, $ce6ea048,
  330.  
  331.                             $6f3f3b82, $3520ab82, $011a1d4b, $277227f8,
  332.                             $611560b1, $e7933fdc, $bb3a792b, $344525bd,
  333.                             $a08839e1, $51ce794b, $2f32c9b7, $a01fbac9,
  334.                             $e01cc87e, $bcc7d1f6, $cf0111c3, $a1e8aac7,
  335.  
  336.                             $1a908749, $d44fbd9a, $d0dadecb, $d50ada38,
  337.                             $0339c32a, $c6913667, $8df9317c, $e0b12b4f,
  338.                             $f79e59b7, $43f5bb3a, $f2d519ff, $27d9459c,
  339.                             $bf97222c, $15e6fc2a, $0f91fc71, $9b941525,
  340.  
  341.                             $fae59361, $ceb69ceb, $c2a86459, $12baa8d1,
  342.                             $b6c1075e, $e3056a0c, $10d25065, $cb03a442,
  343.                             $e0ec6e0e, $1698db3b, $4c98a0be, $3278e964,
  344.                             $9f1f9532, $e0d392df, $d3a0342b, $8971f21e,
  345.  
  346.                             $1b0a7441, $4ba3348c, $c5be7120, $c37632d8,
  347.                             $df359f8d, $9b992f2e, $e60b6f47, $0fe3f11d,
  348.                             $e54cda54, $1edad891, $ce6279cf, $cd3e7e6f,
  349.                             $1618b166, $fd2c1d05, $848fd2c5, $f6fb2299,
  350.  
  351.                             $f523f357, $a6327623, $93a83531, $56cccd02,
  352.                             $acf08162, $5a75ebb5, $6e163697, $88d273cc,
  353.                             $de966292, $81b949d0, $4c50901b, $71c65614,
  354.                             $e6c6c7bd, $327a140a, $45e1d006, $c3f27b9a,
  355.  
  356.                             $c9aa53fd, $62a80f00, $bb25bfe2, $35bdd2f6,
  357.                             $71126905, $b2040222, $b6cbcf7c, $cd769c2b,
  358.                             $53113ec0, $1640e3d3, $38abbd60, $2547adf0,
  359.                             $ba38209c, $f746ce76, $77afa1c5, $20756060,
  360.  
  361.                             $85cbfe4e, $8ae88dd8, $7aaaf9b0, $4cf9aa7e,
  362.                             $1948c25c, $02fb8a8c, $01c36ae4, $d6ebe1f9,
  363.                             $90d4f869, $a65cdea0, $3f09252d, $c208e69f,
  364.                             $b74e6132, $ce77e25b, $578fdfe3, $3ac372e6));
  365.  
  366.   NblKey : array[0..4] of Byte;
  367. {******************************************************************************}
  368. implementation
  369.  
  370. //{$I Blowfish.inc}
  371. {$R-}  
  372. {
  373. uses
  374.   Messages, Variants, Classes, Graphics, Controls, Forms, Dialogs, Unit1;
  375. }
  376.      function Swap32(value : dword) : dword ; assembler ;
  377.      asm
  378.        bswap eax
  379.      end ;
  380.      
  381. procedure BlowfishEncryptECB; // SEGA
  382. var
  383.   xL, xR: DWord;
  384. begin
  385.   Move(InData^,xL,4);
  386.   Move(pointer(integer(InData)+4)^,xR,4);
  387.   //xL:= (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  388.   //xR:= (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  389.  
  390.   xL:= xL xor Data.PBoxM[0];
  391.   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];
  392.   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];
  393.   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];
  394.   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];
  395.   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];
  396.   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];
  397.   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];
  398.   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];
  399.   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];
  400.   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];
  401.   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];
  402.   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];
  403.   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];
  404.   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];
  405.   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];
  406.   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];
  407.   xR:= xR xor Data.PBoxM[17];
  408.  
  409.   //xL:= (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  410.   //xR:= (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  411.  
  412.   Move(xR,OutData^,4);
  413.   Move(xL,pointer(integer(OutData)+4)^,4);
  414. end;
  415.  
  416. procedure BlowfishDecryptECB; //  SEGA
  417. var
  418.   xL, xR: DWord;
  419. begin
  420.   Move(InData^,xL,4);
  421.   Move(pointer(integer(InData)+4)^,xR,4);
  422.  
  423.   //xL:= (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  424.   //xR:= (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  425.  
  426.   xL:= xL xor Data.PBoxM[17];
  427.   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];
  428.   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];
  429.   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];
  430.   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];
  431.   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];
  432.   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];
  433.   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];
  434.   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];
  435.   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];
  436.   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];
  437.   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];
  438.   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];
  439.   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];
  440.   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];
  441.   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];
  442.   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];
  443.   xR:= xR xor Data.PBoxM[0];
  444.  
  445.   //xL:= (xL shr 24) or ((xL shr 8) and $FF00) or ((xL shl 8) and $FF0000) or (xL shl 24);
  446.   //xR:= (xR shr 24) or ((xR shr 8) and $FF00) or ((xR shl 8) and $FF0000) or (xR shl 24);
  447.  
  448.   Move(xR,OutData^,4);
  449.   Move(xL,pointer(integer(OutData)+4)^,4);
  450. end;
  451.  
  452. procedure BlowfishInit;
  453. var
  454.   i, k: integer;
  455.   A: DWord;
  456.   KeyB: PByteArray;
  457.   Block: array[0..7] of byte;
  458. begin
  459.   if (Len<= 0) or (Len> 56) then
  460.     raise Exception.Create('Blowfish: Key must be between 1 and 56 bytes long');
  461.   KeyB:= Key;
  462.   Move(SBox,Data.SBoxM,Sizeof(SBox));
  463.   Move(PBox,Data.PBoxM,Sizeof(PBox));
  464.   with Data do
  465.   begin
  466.     if IV= nil then
  467.     begin
  468.       FillChar(InitBlock,8,0);
  469.       FillChar(LastBlock,8,0);
  470.     end
  471.     else
  472.     begin
  473.       Move(IV^,InitBlock,8);
  474.       Move(IV^,LastBlock,8);
  475.     end;
  476.  
  477.     k:= 0;
  478.  
  479.     for i:= 0 to 17 do // Generate the PBox with the SEED / KEY
  480.     begin
  481.     // PSO2 SEGA IMPLEMENTATION     <<<<<<<< Keys are Generated Correctly now >>>>>>>
  482.  
  483.     A:=0; // WAS UNINITIALISED
  484.       A:= A + (KeyB[k] shl 24);
  485.       A:= A + (KeyB[(k+1) mod Len] shl 16);
  486.       A:= A + (KeyB[(k+2) mod Len] shl 8);
  487.       A:= A + (KeyB[(k+3) mod Len]);
  488.  
  489.       // A now Holds the SEED in decimal
  490.  
  491.       // Write the new value into the P-Box
  492.       PBoxM[i]:= Swap32(PBoxM[i]) xor A; // (PSO2 Endian of P-Box needs flipping) #########  endian-ness of my keys are wrong #########################
  493.       PBoxM[i]:= Swap32(PBoxM[i]); // this fixes endian
  494.       k:= (k+4) mod Len;
  495.     end;
  496.  
  497.     FillChar(Block,Sizeof(Block),0);
  498.  
  499.     for i:= 0 to 8 do // Encrypt the PBox
  500.     begin
  501.       BlowfishEncryptECB(Data,@Block,@Block);
  502.       PBoxM[i*2]  := (Block[3] shl 24) + (Block[2] shl 16) + (Block[1] shl 8) + Block[0];
  503.       PBoxM[i*2+1]:= (Block[7] shl 24) + (Block[6] shl 16) + (Block[5] shl 8) + Block[4];
  504.     end;
  505.     for k:= 0 to 3 do  // Encrypt the 4 SBox`s
  506.     begin
  507.       for i:= 0 to 127 do
  508.       begin
  509.         BlowfishEncryptECB(Data,@Block,@Block);
  510.         SBoxM[k,i*2]  := (Block[3] shl 24) + (Block[2] shl 16) + (Block[1] shl 8) + Block[0]; // GET RID OF ENDIAN SWAP ?
  511.         SBoxM[k,i*2+1]:= (Block[7] shl 24) + (Block[6] shl 16) + (Block[5] shl 8) + Block[4]; // GET RID OF ENDIAN SWAP ?
  512.       end;
  513.     end;
  514.  
  515.   (*
  516.     // LOG IT
  517.     Form1.mmo1.Lines.BeginUpdate;
  518.  
  519.     Form1.mmo1.Lines.Add(#13#10 + 'PBOX');
  520.     i := 0;
  521.     for i:= 0 to 8 do // LOG the PBox
  522.     begin
  523.      Form1.mmo1.lines.Add(IntToHex(PBoxM[i*2], 8));
  524.      Form1.mmo1.lines.Add(IntToHex(PBoxM[i*2+1], 8));
  525.     end;
  526.  
  527.     for k:= 0 to 3 do  // Encrypt the 4 SBox`s
  528.     begin
  529.     Form1.mmo1.lines.Add('SBOX');
  530.       for i:= 0 to 127 do  // ############### SHOULD BE CORRECT NOW  NEEDS CHECKING
  531.       begin
  532.         Form1.mmo1.lines.Add(IntToHex(SBoxM[k,i*2], 8));
  533.         Form1.mmo1.lines.Add(IntToHex(SBoxM[k,i*2+1], 8));
  534.       end;
  535.     Form1.mmo1.lines.Add(#13#10);
  536.     end;
  537.  
  538.     Form1.mmo1.Lines.EndUpdate;
  539.   *)
  540.   end;
  541. end;
  542.  
  543. end.