⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 blowunit.pas

📁 本系统在一些大中型企业(跨多达24个区域)一直都在很好的服务过
💻 PAS
📖 第 1 页 / 共 2 页
字号:
unit Blowunit;
{*****************************************************************************
 UNIT: BlowUnit
 Description:  "Blowfish, a new secret-key block cipher.  It is a
                Feistel network, iterating a simple encryption function 16 times.
                The block size is 64 bits, and the key can be any length up to
                448 bits.  Although there is a complex initialization phase
                required before any encryption can take place, the actual
                encryption of data is very efficient on large microprocessors."
                ...." it is only suitable for applications where the key does
                not change often, like a communications link or an automatic file
                encryptor.  It is significantly faster than DES when implemented
                on 32-bit microprocessors with large data caches, such as the
                Pentium and the PowerPC."

                From BlowFish.Doc, Bruce Schneier Counterpane Systems,
                730 Fair Oaks Ave, Oak Park, IL  60302, schneier@winternet.com

"Blowfish is unpatented, and will remain so in all countries.  The
 algorithm is hereby placed in the public domain, and can be
 freely used by anyone.", Bruce Schneier Counterpane Systems(Algorithm Author)
 (See LEGAL)
 This Object Pascal is largely a port of the reference C Code.
 -----------------------------------------------------------------------------
 Code Author:  Greg Carter, gregc@cryptocard.com
 Organization: CRYPTOCard Corporation, info@cryptocard.com, http://www.cryptocard.com
               R&D Division, Carleton Place, ON, CANADA, K7C 3T2
               1-613-253-3152 Voice, 1-613-253-4685 Fax.
 Date of V.1:  Jan. 3 1996.
 -----------------------------------------------------------------------------}
 {Useage:  Below is typical usage(for File)of the BlowFish Object, Follow these steps:
           1) Declare and Create Variable of type TBlowFish.
           2) Set InputSource Type, either SourceFile, SourceByteArray, or
              SourceString(Pascal style string).
           3) Set Cipher Mode, optionally IVector.
           4) Point to Input Source and set Input Length(If needed)
           5) Point to Output Structure(array, file).
           6) Set Key;
           7) Call BF_EncipherData Method.
           8) Reference the Output. Thats it.
 **** Note **** Steps 2..6 can occure in any order.
 Here is a procedure in Delphi used to encrypt a file:
procedure Tcryptfrm.OpenCiphButtonClick(Sender: TObject);
var
 BlowFish: TBlowFish; (*Step 1*)
begin
BlowFish := TBlowFish.Create;(*Step 1b*)
 try
  If OpenDialog1.Execute then
  begin
   BlowFish.InputType := SourceFile; (*Step 2*)
   BlowFish.CipherMode := ECBMode;   (*Step 3*)
   BlowFish.InputFilePath := OpenDialog1.FileName; (*Step 4*)
   BlowFish.OutputFilePath := ChangeFileExt(OpenDialog1.FileName, '.ccc'); (*Step 5*)
   BlowFish.Key := 'abcdefghijklmnopqrstuvwxyz'; (*Step 6*)
   BlowFish.BF_EncipherData(False);  (*Step 7*)
  end;
 finally
  BlowFish.free;
 end;
end;
-----------------------------------------------------------------------------}
{LEGAL:        The algorithm was placed into the public domain, hence requires
               no license or runtime fees.  However this code is copyright by
               CRYPTOCard.  CRYPTOCard grants anyone who may wish to use, modify
               or redistribute this code privileges to do so, provided the user
               agrees to the following three(3) rules:

               1)Any Applications, (ie exes which make use of this
               Object...), for-profit or non-profit,
               must acknowledge the author of this Object(ie.
               BlowFish Implementation provided by Greg Carter, CRYPTOCard
               Corporation) somewhere in the accompanying Application
               documentation(ie AboutBox, HelpFile, readme...).  NO runtime
               or licensing fees are required!

               2)Any Developer Component(ie Delphi Component, Visual Basic VBX,
               DLL) derived from this software must acknowledge that it is
               derived from "BlowFish Object Pascal Implementation Originated by
               Greg Carter, CRYPTOCard Corporation 1996". Also all efforts should
               be made to point out any changes from the original.
               !!!!!Further, any Developer Components based on this code
               *MAY NOT* be sold for profit.  This Object was placed into the
               public domain, and therefore any derived components should
               also.!!!!!

               3)CRYPTOCard Corporation makes no representations concerning this
               software or the suitability of this software for any particular
               purpose. It is provided "as is" without express or implied
               warranty of any kind. CRYPTOCard accepts no liability from any
               loss or damage as a result of using this software.

CRYPTOCard Corporation is in no way affiliated with Bruce Schneier
(Algorithm Author) or Counterpane Systems.
-----------------------------------------------------------------------------
SECURITY:      BLOWFISH is a relatively new encryption algorithm.  I do not
               think that it has been proven to be either unsecure or secure.

MODE:          ECB(Electronic CodeBook Mode) is used to encipher data.
-----------------------------------------------------------------------------
Why Use this instead of a freely available C DLL?

The goal was to provide a number of Encryption/Hash implementations in Object
Pascal, so that the Pascal Developer has considerably more freedom.  These
Implementations are geared toward the PC(Intel) Microsoft Windows developer,
who will be using Borland's New 32bit developement environment(Delphi32).  The
code generated by this new compiler is considerablely faster then 16bit versions.
And should provide the Developer with faster implementations then those using
C DLLs. Also DLLs are a secruity risk, it is very easy to 'imitate' a DLL.  An
Attacker could replace the C DLL, unknown to your exe.  Now if you call the DLL,
you will mostlikely be passing in the Keys in plaintext.  Now the Attacker has
all the secret keys. Using these routines a Pascal developer can keep all the
Key passing within one exe.
-----------------------------------------------------------------------------
NOTES:       This code is based on the supplied reference C code.
------------------------------------------------------------------------------
Revised:  00/00/00 BY: ******* Reason: ******
------------------------------------------------------------------------------
}
interface
{Declare the compiler defines}
{$I CRYPTDEF.INC}
{------Changeable compiler switches-----------------------------------}
{$A+   Word align variables }
{$F+   Force Far calls }
{$K+   Use smart callbacks
{$N+   Allow coprocessor instructions }
{$P+   Open parameters enabled }
{$S+   Stack checking }
{$T-   @ operator is NOT typed }
{$IFDEF DELPHI}
{$U-   Non Pentium safe FDIV }
{$Z-   No automatic word-sized enumerations}
{$ENDIF}
{---------------------------------------------------------------------}
uses SysUtils, Cryptcon{$IFDEF DELPHI}, Classes{$ENDIF}
     {$IFDEF BP7},objects{$ENDIF};
{,WinTypes, WinProcs,Messages, Graphics,}

type

 twoAword = record
  Xl: aword; {this assumes bytes are read in in MSB, so we have to flip}
  Xr: aword;
 end;

 PtwoAword = ^twoAword;

 Const
  bf_N = 16;
 type

 Pbf_P = ^Tbf_PArray;
 Tbf_PArray = array[0..(bf_N + 1)] of UWORD_32bits;

 Pbf_S = ^Tbf_SArray;
 Tbf_SArray = array[0..3, 0..255] of UWORD_32bits;

{$IFDEF DELPHI}
TBlowFish = class(TCrypto)
 Private
 { Private declarations }
{$ENDIF}
{$IFDEF BP7}
 PTBlowFish = ^TBlowFish; {For BP7 Objects}
 TBlowFish = object(TCrypto)
 Public             {Since BP7 doesn't support Properties, we make these Public}
{$ENDIF}
 Private
  Fpbf_P: Pbf_P;    {Pointer to bf_P array}
  Fpbf_S: Pbf_S;    {Pointer to bf_S array}
  FpXl: Paword;     {Lower 32 bits of Active Encipher Data}
  FpXr: Paword;     {Upper 32 bits of Active Encipher Data}
  Function bf_F(x: Paword): aword;
  Procedure InitArray;
  Procedure ROUND(a, b: Paword; n: BYTE);
  Procedure BF_Initialize;           {Computation of the SubKeys}
  Procedure BF_Encipher;             {Enciphers 64bit block}
  Procedure BF_Decipher;             {Deciphers 64bit block}
{$IFDEF DELPHI}
  Procedure EncipherBLOCK;override; {Enciphers Block, calls BF_Encipher}
  Procedure DecipherBLOCK;override; {Deciphers Block, calls BF_Decipher}
  Procedure SetKeys;override;       {Used to set SubKeys}
{$ENDIF}
{$IFDEF BP7}
  Procedure EncipherBLOCK; virtual;{Enciphers Block, calls BF_Encipher}
  Procedure DecipherBLOCK; virtual;{Deciphers Block, calls BF_Decipher}
  Procedure SetKeys;       virtual;{Used to set SubKeys}
{$ENDIF}
{$IFDEF DELPHI}
 protected
    { Protected declarations }
{$ENDIF}
 public
    { Public declarations }
{$IFDEF DELPHI}
  constructor Create(Owner: TComponent);override;
  destructor  Destroy;override;
{$ENDIF}
{$IFDEF BP7}
  constructor Init;
  destructor  Done;virtual;
{$ENDIF}
end;{TBlowFish}

{$IFDEF DELPHI}
 procedure Register;{register the component to the Delphi toolbar}
{$ENDIF}
 Const
 {bf_N = 16;}
 KEYBYTES = 8;
 MAXKEYBYTES = 56;
 BF_MAXKEYLENGTH = 65;
 BF_MINKEYLENGTH = 8;

 bf_P: array[0..(bf_N + 1)] of UWORD_32bits = (
  $243f6a88, $85a308d3, $13198a2e, $03707344,
  $a4093822, $299f31d0, $082efa98, $ec4e6c89,
  $452821e6, $38d01377, $be5466cf, $34e90c6c,
  $c0ac29b7, $c97c50dd, $3f84d5b5, $b5470917,
  $9216d5d9, $8979fb1b);
{Initial Random SubKey boxes, set to Pi}
 bf_S: array[0..3, 0..255] of UWORD_32bits =
(
( $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),
  {second 256}
 ($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),
  {Thrid 256}
 ($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,

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -