'/******************************************************************************
' * Copyright (C) 2000 by Robert Hubley. *
' * All rights reserved. *
' * *
' * This software is provided ``AS IS'' and any express or implied *
' * warranties, including, but not limited to, the implied warranties of *
' * merchantability and fitness for a particular purpose, are disclaimed. *
' * In no event shall the authors be liable for any direct, indirect, *
' * incidental, special, exemplary, or consequential damages (including, but *
' * not limited to, procurement of substitute goods or services; loss of use, *
' * data, or profits; or business interruption) however caused and on any *
' * theory of liability, whether in contract, strict liability, or tort *
' *  including negligence or otherwise) arising in any way out of the use of *
' * this software, even if advised of the possibility of such damage. *
' * *
' ******************************************************************************
'
' CLASS: MD5
'
'  ESCRIPTION:
' This is a class which encapsulates a set of MD5 Message Digest functions.
' MD5 algorithm produces a 128 bit digital fingerprint (signature) from an
' dataset of arbitrary length. For details see RFC 1321 (summarized below).
' This implementation is derived from the RSA Data Security, Inc. MD5 Message-Digest
' algorithm reference implementation (originally written in C)
'
' AUTHOR:
' Robert M. Hubley 12/1999
'
'
' NOTES:
' Network Working Group R. Rivest
' Request for Comments: 1321 MIT Laboratory for Computer Science
' and RSA Data Security, Inc.
' April 1992
'
'
' The MD5 Message-Digest Algorithm
'
' Summary
'
' This document describes the MD5 message-digest algorithm. The
' algorithm takes as input a message of arbitrary length and produces
' as output a 128-bit "fingerprint" or "message digest" of the input.
' It is conjectured that it is computationally infeasible to produce
' two messages having the same message digest, or to produce any
' message having a given prespecified target message digest. The MD5
' algorithm is intended for digital signature applications, where a
' large file must be "compressed" in a secure manner before being
' encrypted with a private (secret) key under a public-key cryptosystem
' such as RSA.
'
' The MD5 algorithm is designed to be quite fast on 32-bit machines. In
' addition, the MD5 algorithm does not require any large substitution
' tables; the algorithm can be coded quite compactly.
'
' The MD5 algorithm is an extension of the MD4 message-digest algorithm
' 1,2]. MD5 is slightly slower than MD4, but is more "conservative" in
' design. MD5 was designed because it was felt that MD4 was perhaps
' being adopted for use more quickly than justified by the existing
' critical review; because MD4 was designed to be exceptionally fast,
' it is "at the edge" in terms of risking successful cryptanalytic
' attack. MD5 backs off a bit, giving up a little in speed for a much
' greater likelihood of ultimate security. It incorporates some
' suggestions made by various reviewers, and contains additional
' optimizations. The MD5 algorithm is being placed in the public domain
' for review and possible adoption as a standard.
'
' RFC Author:
' Ronald L.Rivest
' Massachusetts Institute of Technology
' Laboratory for Computer Science
' NE43 -324545 Technology Square
' Cambridge, MA 02139-1986
' Phone: (617) 253-5880
' EMail: Rivest@ theory.lcs.mit.edu
'
'
'
' CHANGE HISTORY:
'
' 0.1.0 RMH 1999/12/29 Original version
'
'
'=
'= Class Variables
'=
Private State(4) As Long
Private ByteCounter As Long
Private ByteBuffer(63) As Byte
'=
'= Class Properties
'=
Property Get RegisterA() As String
RegisterA = State(1)
End Property
Property Get RegisterB() As String
RegisterB = State(2)
End Property
Property Get RegisterC() As String
RegisterC = State(3)
End Property
Property Get RegisterD() As String
RegisterD = State(4)
End Property
'=
'= Class Functions
'=
'
' Function to quickly digest a file into a hex string
'
Public Function DigestFileToHexStr(FileName As String) As String
Open FileName For Binary Access Read As #1
MD5Init
Do While Not EOF(1)
Get #1, , ByteBuffer
If Loc(1) < LOF(1) Then
ByteCounter = ByteCounter + 64
MD5Transform ByteBuffer
End If
Loop
ByteCounter = ByteCounter + (LOF(1) Mod 64)
Close #1
MD5Final
 igestFileToHexStr = GetValues
End Function
'
' Function to digest a text string and output the result as a string
' of hexadecimal characters.
'
Public Function DigestStrToHexStr(SourceString As String) As String
MD5Init
MD5Update Len(SourceString), StringToArray(SourceString)
MD5Final
 igestStrToHexStr = GetValues
End Function
'
' A utility function which converts a string into an array of
' bytes.
'
Private Function StringToArray(InString As String) As Byte()
Dim I As Integer
Dim bytBuffer() As Byte
ReDim bytBuffer(Len(InString))
For I = 0 To Len(InString) - 1
bytBuffer(I) = Asc(Mid(InString, I + 1, 1))
Next I
StringToArray = bytBuffer
End Function
'
' Concatenate the four state vaules into one string
'
Public Function GetValues() As String
GetValues = LongToString(State(1)) & LongToString(State(2)) & LongToString(State(3)) & LongToString(State(4))
End Function
'
' Convert a Long to a Hex string
'
Private Function LongToString(Num As Long) As String
Dim a As Byte
Dim b As Byte
Dim c As Byte
Dim d As Byte
a = Num And &HFF&
If a < 16 Then
LongToString = "0" & Hex
Else
LongToString = Hex
End If
b = (Num And &HFF00& \ 256
If b < 16 Then
LongToString = LongToString & "0" & Hex(b)
Else
LongToString = LongToString & Hex(b)
End If
c = (Num And &HFF0000) \ 65536
If c < 16 Then
LongToString = LongToString & "0" & Hex(c)
Else
LongToString = LongToString & Hex(c)
End If
If Num < 0 Then
d = ((Num And &H7F000000) \ 16777216) Or &H80&
Else
d = (Num And &HFF000000) \ 16777216
End If
If d < 16 Then
LongToString = LongToString & "0" & Hex(d)
Else
LongToString = LongToString & Hex(d)
End If
End Function
'
' Initialize the class
' This must be called before a digest calculation is started
'
Public Sub MD5Init()
ByteCounter = 0
State(1) = UnsignedToLong(1732584193#)
State(2) = UnsignedToLong(4023233417#)
State(3) = UnsignedToLong(2562383102#)
State(4) = UnsignedToLong(271733878#)
End Sub
'
' MD5 Final
'
Public Sub MD5Final()
Dim dblBits As Double
Dim padding(72) As Byte
Dim lngBytesBuffered As Long
padding(0) = &H80
dblBits = ByteCounter * 8
' Pad out
lngBytesBuffered = ByteCounter Mod 64
If lngBytesBuffered <= 56 Then
MD5Update 56 - lngBytesBuffered, padding
Else
MD5Update 120 - ByteCounter, padding
End If
padding(0) = UnsignedToLong(dblBits) And &HFF&
padding(1) = UnsignedToLong(dblBits) \ 256 And &HFF&
padding(2) = UnsignedToLong(dblBits) \ 65536 And &HFF&
padding(3) = UnsignedToLong(dblBits) \ 16777216 And &HFF&
padding(4) = 0
padding(5) = 0
padding(6) = 0
padding(7) = 0
MD5Update 8, padding
End Sub
'
' Break up input stream into 64 byte chunks
'
Public Sub MD5Update(InputLen As Long, InputBuffer() As Byte)
Dim II As Integer
Dim I As Integer
Dim J As Integer
Dim K As Integer
Dim lngBufferedBytes As Long
Dim lngBufferRemaining As Long
Dim lngRem As Long
lngBufferedBytes = ByteCounter Mod 64
lngBufferRemaining = 64 - lngBufferedBytes
ByteCounter = ByteCounter + InputLen
' Use up old buffer results first
If InputLen >= lngBufferRemaining Then
For II = 0 To lngBufferRemaining - 1
ByteBuffer(lngBufferedBytes + II) = InputBuffer(II)
Next II
MD5Transform ByteBuffer
lngRem = (InputLen) Mod 64
' The transfer is a multiple of 64 lets do some transformations
For I = lngBufferRemaining To InputLen - II - lngRem Step 64
For J = 0 To 63
ByteBuffer(J) = InputBuffer(I + J)
Next J
MD5Transform ByteBuffer
Next I
lngBufferedBytes = 0
Else
I = 0
End If
' Buffer any remaining input
For K = 0 To InputLen - I - 1
ByteBuffer(lngBufferedBytes + K) = InputBuffer(I + K)
Next K
End Sub
'
' MD5 Transform
'
Private Sub MD5Transform(Buffer() As Byte)
Dim x(16) As Long
Dim a As Long
Dim b As Long
Dim c As Long
Dim d As Long
a = State(1)
b = State(2)
c = State(3)
d = State(4)
 ecode 64, x, Buffer
' Round 1
FF a, b, c, d, x(0), S11, -680876936
FF d, a, b, c, x(1), S12, -389564586
FF c, d, a, b, x(2), S13, 606105819
FF b, c, d, a, x(3), S14, -1044525330
FF a, b, c, d, x(4), S11, -176418897
FF d, a, b, c, x(5), S12, 1200080426
FF c, d, a, b, x(6), S13, -1473231341
FF b, c, d, a, x(7), S14, -45705983
FF a, b, c, d, x(8), S11, 1770035416
FF d, a, b, c, x(9), S12, -1958414417
FF c, d, a, b, x(10), S13, -42063
FF b, c, d, a, x(11), S14, -1990404162
FF a, b, c, d, x(12), S11, 1804603682
FF d, a, b, c, x(13), S12, -40341101
FF c, d, a, b, x(14), S13, -1502002290
FF b, c, d, a, x(15), S14, 1236535329
' Round 2
GG a, b, c, d, x(1), S21, -165796510
GG d, a, b, c, x(6), S22, -1069501632
GG c, d, a, b, x(11), S23, 643717713
GG b, c, d, a, x(0), S24, -373897302
GG a, b, c, d, x(5), S21, -701558691
GG d, a, b, c, x(10), S22, 38016083
GG c, d, a, b, x(15), S23, -660478335
GG b, c, d, a, x(4), S24, -405537848
GG a, b, c, d, x(9), S21, 568446438
GG d, a, b, c, x(14), S22, -1019803690
GG c, d, a, b, x(3), S23, -187363961
GG b, c, d, a, x(8), S24, 1163531501
GG a, b, c, d, x(13), S21, -1444681467
GG d, a, b, c, x(2), S22, -51403784
GG c, d, a, b, x(7), S23, 1735328473
GG b, c, d, a, x(12), S24, -1926607734
' Round 3
HH a, b, c, d, x(5), S31, -378558
HH d, a, b, c, x(8), S32, -2022574463
HH c, d, a, b, x(11), S33, 1839030562
HH b, c, d, a, x(14), S34, -35309556
HH a, b, c, d, x(1), S31, -1530992060
HH d, a, b, c, x(4), S32, 1272893353
HH c, d, a, b, x(7), S33, -155497632
HH b, c, d, a, x(10), S34, -1094730640
HH a, b, c, d, x(13), S31, 681279174
HH d, a, b, c, x(0), S32, -358537222
HH c, d, a, b, x(3), S33, -722521979
HH b, c, d, a, x(6), S34, 76029189
HH a, b, c, d, x(9), S31, -640364487
HH d, a, b, c, x(12), S32, -421815835
HH c, d, a, b, x(15), S33, 530742520
HH b, c, d, a, x(2), S34, -995338651
' Round 4
II a, b, c, d, x(0), S41, -198630844
II d, a, b, c, x(7), S42, 1126891415
II c, d, a, b, x(14), S43, -1416354905
II b, c, d, a, x(5), S44, -57434055
II a, b, c, d, x(12), S41, 1700485571
II d, a, b, c, x(3), S42, -1894986606
II c, d, a, b, x(10), S43, -1051523
II b, c, d, a, x(1), S44, -2054922799
II a, b, c, d, x(8), S41, 1873313359
II d, a, b, c, x(15), S42, -30611744
II c, d, a, b, x(6), S43, -1560198380
II b, c, d, a, x(13), S44, 1309151649
II a, b, c, d, x(4), S41, -145523070
II d, a, b, c, x(11), S42, -1120210379
II c, d, a, b, x(2), S43, 718787259
II b, c, d, a, x(9), S44, -343485551
State(1) = LongOverflowAdd(State(1), a)
State(2) = LongOverflowAdd(State(2), b)
State(3) = LongOverflowAdd(State(3), c)
State(4) = LongOverflowAdd(State(4), d)
Private Sub Decode(Length As Integer, OutputBuffer() As Long, InputBuffer() As Byte)
Dim intDblIndex As Integer
Dim intByteIndex As Integer
Dim dblSum As Double
intDblIndex = 0
For intByteIndex = 0 To Length - 1 Step 4
dblSum = InputBuffer(intByteIndex) + _
InputBuffer(intByteIndex + 1) * 256# + _
InputBuffer(intByteIndex + 2) * 65536# + _
InputBuffer(intByteIndex + 3) * 16777216#
OutputBuffer(intDblIndex) = UnsignedToLong(dblSum)
intDblIndex = intDblIndex + 1
Next intByteIndex
End Sub
'
' FF, GG, HH, and II transformations for rounds 1, 2, 3, and 4.
' Rotation is separate from addition to prevent recomputation.
'
Private Function FF(a As Long, _
b As Long, _
c As Long, _
d As Long, _
x As Long, _
s As Long, _
ac As Long) As Long
a = LongOverflowAdd4(a, (b And c) Or (Not (b) And d), x, ac)
a = LongLeftRotate(a, s)
a = LongOverflowAdd(a, b)
End Function
Private Function GG(a As Long, _
b As Long, _
c As Long, _
d As Long, _
x As Long, _
s As Long, _
ac As Long) As Long
a = LongOverflowAdd4(a, (b And d) Or (c And Not (d)), x, ac)
a = LongLeftRotate(a, s)
a = LongOverflowAdd(a, b)
End Function
Private Function HH(a As Long, _
b As Long, _
c As Long, _
d As Long, _
x As Long, _
s As Long, _
ac As Long) As Long
a = LongOverflowAdd4(a, b Xor c Xor d, x, ac)
a = LongLeftRotate(a, s)
a = LongOverflowAdd(a, b)
End Function
Private Function II(a As Long, _
b As Long, _
c As Long, _
d As Long, _
x As Long, _
s As Long, _
ac As Long) As Long
a = LongOverflowAdd4(a, c Xor (b Or Not (d)), x, ac)
a = LongLeftRotate(a, s)
a = LongOverflowAdd(a, b)
End Function
'
' Rotate a long to the right
'
Function LongLeftRotate(value As Long, bits As Long) As Long
Dim lngSign As Long
Dim lngI As Long
bits = bits Mod 32
If bits = 0 Then LongLeftRotate = value: Exit Function
For lngI = 1 To bits
lngSign = value And &HC0000000
value = (value And &H3FFFFFFF) * 2
value = value Or ((lngSign < 0) And 1) Or (CBool(lngSign And _
&H40000000) And &H80000000)
Next
LongLeftRotate = value
End Function
'
' Function to add two unsigned numbers together as in C.
' Overflows are ignored!
'
Private Function LongOverflowAdd(Val1 As Long, Val2 As Long) As Long
Dim lngHighWord As Long
Dim lngLowWord As Long
Dim lngOverflow As Long
lngLowWord = (Val1 And &HFFFF& + (Val2 And &HFFFF&
lngOverflow = lngLowWord \ 65536
lngHighWord = (((Val1 And &HFFFF0000) \ 65536) + ((Val2 And &HFFFF0000) \ 65536) + lngOverflow) And &HFFFF&
LongOverflowAdd = UnsignedToLong((lngHighWord * 65536#) + (lngLowWord And &HFFFF&)
End Function
'
' Function to add two unsigned numbers together as in C.
' Overflows are ignored!
'
Private Function LongOverflowAdd4(Val1 As Long, Val2 As Long, val3 As Long, val4 As Long) As Long
Dim lngHighWord As Long
Dim lngLowWord As Long
Dim lngOverflow As Long
lngLowWord = (Val1 And &HFFFF& + (Val2 And &HFFFF& + (val3 And &HFFFF& + (val4 And &HFFFF&
lngOverflow = lngLowWord \ 65536
lngHighWord = (((Val1 And &HFFFF0000) \ 65536) + _
 (Val2 And &HFFFF0000) \ 65536) + _
 (val3 And &HFFFF0000) \ 65536) + _
 (val4 And &HFFFF0000) \ 65536) + _
lngOverflow) And &HFFFF&
LongOverflowAdd4 = UnsignedToLong((lngHighWord * 65536#) + (lngLowWord And &HFFFF&)
End Function
'
' Convert an unsigned double into a long
'
Private Function UnsignedToLong(value As Double) As Long
If value < 0 Or value >= OFFSET_4 Then Error 6 ' Overflow
If value <= MAXINT_4 Then
UnsignedToLong = value
Else
UnsignedToLong = value - OFFSET_4
End If
End Function
'
' Convert a long to an unsigned Double
'
Private Function LongToUnsigned(value As Long) As Double
If value < 0 Then
LongToUnsigned = value + OFFSET_4
Else
LongToUnsigned = value
End If
юзать
Dim md5Test As MD5
Private Sub btnRunTest_Click()
lblResults(0).Caption = LCase(md5Test.DigestStrToHexStr("")
lblResults(1).Caption = LCase(md5Test.DigestStrToHexStr("a")
lblResults(2).Caption = LCase(md5Test.DigestStrToHexStr("abc")
lblResults(3).Caption = LCase(md5Test.DigestStrToHexStr("message digest")
lblResults(4).Caption = LCase(md5Test.DigestStrToHexStr("abcdefghijklmnopqrstuvwxyz")
lblResults(5).Caption = LCase(md5Test.DigestStrToHexStr("ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789")
lblResults(6).Caption = LCase(md5Test.DigestStrToHexStr("12345678901234567890123456789012345678901234567890123456789012345678901234567890")
End Sub
Private Sub Form_Load()
' Instantiate our class
Set md5Test = New MD5
End Sub
На скорость не тестил, но думаю пол лимона на пару мин работы...
P.S. Могу исходник на асме кинуть, будет значительно быстрее...
Вот вам все что нужно и на API
Option Explicit
'******************************************************
Public Declare Function CryptAcquireContext Lib "advapi32.dll" Alias "CryptAcquireContextA" (phProv As Long, pszContainer As String, pszProvider As String, ByVal dwProvType As Long, ByVal dwFlags As Long) As Long
Public Declare Function CryptReleaseContext Lib "advapi32.dll" (ByVal hProv As Long, ByVal dwFlags As Long) As Long
Public Declare Function CryptCreateHash Lib "advapi32.dll" (ByVal hProv As Long, ByVal Algid As Long, ByVal hKey As Long, ByVal dwFlags As Long, phHash As Long) As Long
Public Declare Function CryptDestroyHash Lib "advapi32.dll" (ByVal hHash As Long) As Long
Public Declare Function CryptHashData Lib "advapi32.dll" (ByVal hHash As Long, ByVal pbdata As String, ByVal dwDataLen As Long, ByVal dwFlags As Long) As Long
Public Declare Function CryptBinHashData Lib "advapi32.dll" Alias "CryptHashData" (ByVal hHash As Long, pbdata As Any, ByVal dwDataLen As Long, ByVal dwFlags As Long) As Long
Public Declare Function CryptGetHashParam Lib "advapi32.dll" (ByVal hHash As Long, ByVal dwParam As Long, pbdata As Any, pdwDataLen As Long, ByVal dwFlags As Long) As Long
Public Declare Function CryptGenKey Lib "advapi32.dll" (ByVal hProv As Long, ByVal Algid As Long, ByVal dwFlags As Long, phKey As Long) As Long
Public Declare Function CryptDeriveKey Lib "advapi32.dll" (ByVal hProv As Long, ByVal Algid As Long, ByVal hBaseData As Long, ByVal dwFlags As Long, phKey As Long) As Long
Public Declare Function CryptExportKey Lib "advapi32.dll" (ByVal hKey As Long, ByVal hExpKey As Long, ByVal dwBlobType As Long, ByVal dwFlags As Long, pbdata As Any, pdwDataLen As Long) As Long
Public Declare Function CryptImportKey Lib "advapi32.dll" (ByVal hProv As Long, pbdata As Any, ByVal dwDataLen As Long, ByVal hImpKey As Long, ByVal dwFlags As Long, phKey As Long) As Long
Public Declare Function CryptDestroyKey Lib "advapi32.dll" (ByVal hKey As Long) As Long
Public Declare Function CryptEncrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, pbdata As Any, pdwDataLen As Long, ByVal dwBufLen As Long) As Long
Public Declare Function CryptStringEncrypt Lib "advapi32.dll" Alias "CryptEncrypt" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbdata As String, pdwDataLen As Long, ByVal dwBufLen As Long) As Long
Public Declare Function CryptDecrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, pbdata As Any, pdwDataLen As Long) As Long
Public Declare Function CryptStringDecrypt Lib "advapi32.dll" Alias "CryptDecrypt" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbdata As String, pdwDataLen As Long) As Long
Public Declare Function GetLastError Lib "kernel32" () As Long
Public Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (ByVal dwFlags As Long, lpSource As Any, ByVal dwMessageId As Long, ByVal dwLanguageId As Long, ByVal lpBuffer As String, ByVal nSize As Long, Arguments As Long) As Long
Public Declare Function WriteFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, ByVal lpOverlapped As Any) As Long
Public Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, ByVal lpOverlapped As Any) As Long
Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, ByVal lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function SetFilePointer Lib "kernel32" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
Public Declare Function SetFileAttributes Lib "kernel32" Alias "SetFileAttributesA" (ByVal lpFileName As String, ByVal dwFileAttributes As Long) As Long
Public Declare Function GetFileAttributes Lib "kernel32" Alias "GetFileAttributesA" (ByVal lpFileName As String) As Long
Public Declare Function GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
Public Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
Public Declare Function GetTempPath Lib "kernel32" Alias "GetTempPathA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
Public Declare Function DeleteFile Lib "kernel32" Alias "eleteFileA" (ByVal lpFileName As String) As Long
Public Declare Function DrawEdge Lib "user32" (ByVal hdc As Long, qrc As RECT, ByVal edge As Long, ByVal grfFlags As Long) As Long
Public Declare Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Public Declare Sub CopyMem Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
'------------------------------------------------------
Public Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
'------------------------------------------------------
Public Const BDR_SUNKENOUTER = &H2
Public Const BDR_RAISEDINNER = &H4
Public Const BDR_RAISEDOUTER = &H1
Public Const EDGE_RAISED = (BDR_RAISEDOUTER Or BDR_RAISEDINNER)
Public Const EDGE_ETCHED = (BDR_SUNKENOUTER Or BDR_RAISEDINNER)
Public Const BF_BOTTOM = &H8
Public Const BF_LEFT = &H1
Public Const BF_RIGHT = &H4
Public Const BF_TOP = &H2
Public Const BF_RECT = (BF_LEFT Or BF_TOP Or BF_RIGHT Or BF_BOTTOM)
Public Const BF_ADJUST = &H2000
Public Const MOVEFILE_REPLACE_EXISTING = &H1
Public Const MOVEFILE_COPY_ALLOWED = &H2
Public Const FILE_BEGIN = 0
Public Const FILE_SHARE_READ = &H1
Public Const FILE_SHARE_WRITE = &H2
Public Const CREATE_ALWAYS = 2
Public Const OPEN_ALWAYS = 4
Public Const TRUNCATE_EXISTING = 5
Public Const CREATE_NEW = 1
Public Const OPEN_EXISTING = 3
Public Const GENERIC_READ = &H80000000
Public Const GENERIC_WRITE = &H40000000
Public Const INVALID_HANDLE_VALUE = -1
Public Const FILE_ATTRIBUTE_ARCHIVE = &H20
Public Const FILE_ATTRIBUTE_DIRECTORY = &H10
Public Const FILE_ATTRIBUTE_HIDDEN = &H2
Public Const FILE_ATTRIBUTE_NORMAL = &H80
Public Const FILE_ATTRIBUTE_READONLY = &H1
Public Const FILE_ATTRIBUTE_SYSTEM = &H4
Public Const FILE_ATTRIBUTE_TEMPORARY = &H100
Public Const FILE_POINTER_FAIL = &HFFFFFFFF
Public Const ERROR_ILLEGAL_PROPERTY& = 1001&
Public Const ERROR_NO_HASH_CREATE& = 1002&
Public Const ERROR_NO_KEY_CONTAINER& = 1003&
Public Const ERROR_NO_HASH_CREATED& = 1004&
Public Const ERROR_NO_DIGEST& = 1005&
Public Const ERROR_NO_HASH_DATA& = 1006&
Public Const ERROR_FILE_NOT_FOUND& = 1007&
Public Const ERROR_NO_HASH_DESTROY& = 1008&
Public Const ERROR_NO_HASH_PASSW& = 1010&
Public Const ERROR_NO_KEY_DERIVED& = 1011&
Public Const ERROR_NO_DECRYPT& = 1012&
Public Const ERROR_NO_ENCRYPT& = 1009
Public Const ERROR_TMPPTH_NOT_FOUND& = 1013&
Public Const ERROR_ALGO_NOT_SUPP& = 1014&
Public Const ERROR_NO_TMP_FILE& = 1015&
Public Const ERROR_NO_FILE_OPEN& = 1016&
Public Const ERROR_NO_READ& = 1017&
Public Const ERROR_NO_WRITE& = 1018&
Public Const ERROR_NO_TMP_OPEN& = 1019&
Public Const ERROR_NOTHING_DIGESTED& = 1020&
Public Const ERROR_IS_DIR& = 1021&
Public Const NO_DATASET& = 0&
Public Const ERROR_FILE_SIZE& = 1022&
Public Const FORMAT_MESSAGE_FROM_SYSTEM& = &H1000
Public Const FORMAT_MESSAGE_ALLOCATE_BUFFER& = &H100
Public Const LANG_NEUTRAL& = &H0
Public Const SUBLANG_DEFAULT& = &H1 ' user default
Public Const ERROR_MSG_FAIL& = &H0
Public Const MS_DEF_PROV = "Microsoft Base Cryptographic Provider v1.0"
Public Const MS_ENHANCED_PROV = "Microsoft Enhanced Cryptographic Provider v1.0"
Public Const PROV_RSA_FULL = 1
Public Const CRYPT_NEWKEYSET = &H8
Public Const HP_ALGID = 1
Public Const HP_HASHVAL = 2
Public Const HP_HASHSIZE = 4
Public Const HP_FILE_RW_BLOCKSIZE_1k = 1000&
Public Const HP_FILE_RW_BLOCKSIZE_2k = 2000&
Public Const HP_FILE_RW_BLOCKSIZE_4k = 4000&
Public Const HP_FILE_RW_BLOCKSIZE_8k = 8000&
Public Const HP_FILE_RW_BLOCKSIZE_16k = 16000&
Public Const HP_FILE_RW_BLOCKSIZE_30k = 30000&
Public Const HP_FILE_RW_BLOCKSIZE_40k = &H9C40
Public Const HP_FILE_RW_BLOCKSIZE_50k = &HC350
Public Const HP_FILE_RW_BLOCKSIZE_60k& = &HEA60
Public Const HP_FILE_RW_BLOCKSIZE_80k& = &H13880
Public Const HP_FILE_RW_BLOCKSIZE_100k& = &H186A0
Public Const SIMPLEBLOB = 1
Public Const PUBLICKEYBLOB = 6
Public Const PRIVATEKEYBLOB = 7
Public Const PLAINTEXTKEYBLOB = 8
Public Const ALG_CLASS_SIGNATURE = 8192
Public Const ALG_CLASS_DATA_ENCRYPT = 24576
Public Const ALG_CLASS_HASH = 32768
Public Const ALG_TYPE_ANY = 0
Public Const ALG_TYPE_BLOCK = 1536
Public Const ALG_TYPE_STREAM = 2048
Public Const ALG_SID_DES = 1
Public Const ALG_SID_3DES = 3
Public Const ALG_SID_3DES_112 = 9
Public Const ALG_SID_RC2 = 2
Public Const ALG_SID_RC4 = 1
Public Const ALG_SID_MD2 = 1
Public Const ALG_SID_MD4 = 2
Public Const ALG_SID_MD5 = 3
Public Const ALG_SID_SHA = 4
Public Const CALG_MD2 = (ALG_CLASS_HASH Or ALG_TYPE_ANY Or ALG_SID_MD2)
Public Const CALG_MD4 = (ALG_CLASS_HASH Or ALG_TYPE_ANY Or ALG_SID_MD4)
Public Const CALG_MD5 = ((ALG_CLASS_HASH Or ALG_TYPE_ANY) Or ALG_SID_MD5)
Public Const CALG_SHA = (ALG_CLASS_HASH Or ALG_TYPE_ANY Or ALG_SID_SHA)
Public Const CALG_DES = (ALG_CLASS_DATA_ENCRYPT Or ALG_TYPE_BLOCK Or ALG_SID_DES)
Public Const CALG_3DES = (ALG_CLASS_DATA_ENCRYPT Or ALG_TYPE_BLOCK Or ALG_SID_3DES)
Public Const CALG_3DES_112 = (ALG_CLASS_DATA_ENCRYPT Or ALG_TYPE_BLOCK Or ALG_SID_3DES_112)
Public Const CALG_RC2 = ((ALG_CLASS_DATA_ENCRYPT Or ALG_TYPE_BLOCK) Or ALG_SID_RC2)
Public Const CALG_RC4 = ((ALG_CLASS_DATA_ENCRYPT Or ALG_TYPE_STREAM) Or ALG_SID_RC4)
Public Const TEMP_FILE = "ECA"
Public Const TEMP_SIZE = 255&
Public Const DEF_WIDTH = 930&
Public Const DEF_HEIGHT = 1080&
Public Const DEF_MAX_FILE_SIZE& = &H2710
'******************************************************
'------------------------------------------------------
Public Enum EC_HASH_ALG_ID
MD2
MD4
MD5
SHA
End Enum
Public Enum EC_HASH_DATAFORMAT
EC_HF_HEXADECIMAL
EC_HF_NUMERIC
EC_HF_ASCII
End Enum
Private Enum EC_HASH_STATUS
EC_HASH_NONE
EC_HASH_BUSY
EC_HASH_READY
End Enum
Private Enum EC_CRYPT_STATUS
EC_CRYPT_NONE
EC_CRYPT_BUSY
EC_CRYPT_READY
End Enum
Private Enum EC_PROVIDER
[No Providers]
[Microsoft Base Cryptographic Provider v.1]
[Microsoft Enhanced Cryptographic Provider]
End Enum
Public Enum EC_CRYPT_ALGO_ID
RC2
RC4
 ES
[Triple DES]
[Triple DES 112]
End Enum
Public Enum EC_CRYPT_SPEED
[1KB]
[2KB]
[4KB]
[8KB]
[16KB]
[30KB]
[40KB]
[50KB]
[60KB]
[80KB]
[100KB]
End Enum
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' Cryptology Service Provider properties
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Private m_CSP_Provider As Long
Private m_Provider_Name As EC_PROVIDER
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' Hash Properties
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Private m_Hash_Object As Long
Private m_Hash_Data(20) As Byte 'This value will usually be 16 or 20, depending on the hash algorithm.
Private m_Hash_DataLen As Long
Public m_Hash_Algo_Id As EC_HASH_ALG_ID
Public m_Hash_Algorithm As Long
Private m_Hash_Status As EC_HASH_STATUS
Private m_Hash_DataReady As Boolean
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' Encryption/Decryption Properties
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public m_EncDec_Password As String
Private m_EncDec_InBuffer As String
Public m_EncDec_Algo_Id As EC_CRYPT_ALGO_ID
Private m_EncDec_Status As EC_CRYPT_STATUS
Public m_EncDec_Algorithm As Long
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' Sub Procedures
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' CreateHash Sub procedure
' Initializes Hash Object
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Sub CreateHash()
Dim lError As Long
On Error GoTo ErrCreateHash
' lReturn: Holds the value returned by InitProvider()
 im lReturn As Long
' If we have an already created hash object
' then "KILL IT"
If m_Hash_Status = EC_HASH_READY Then
Call DestroyHash
End If
' Let's try!
' Get a handle to the provider
lReturn = InitProvider()
' No success getting a handle to the provider?
' Then raise an error
If lReturn = 0 Then
lError = ERROR_NO_KEY_CONTAINER
'err.raise vbObjectError ' Fire error handler
End If
'Attempt to acquire a handle to a Hash object
If Not CBool(CryptCreateHash(m_CSP_Provider, m_Hash_Algorithm, _
0, 0, m_Hash_Object)) Then
lError = ERROR_NO_HASH_CREATE
'err.raise vbObjectError ' Fire error handler
End If
' Hash Status = READY [to work!]
m_Hash_Status = EC_HASH_READY
Exit Sub
ErrCreateHash:
' Just raise the error back to the user
' so it can be trap by him/her
 im sMsg As String
Select Case lError
Case ERROR_NO_KEY_CONTAINER: sMsg = "Error getting a handle to key containers"
Case ERROR_NO_HASH_CREATE: sMsg = "Unable to initialize Hash object"
Case Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End Select
'err.raise Number:=(vbObjectError + lError), Source:="EzCryptoApi", Description:=sMsg
End Sub
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' HashDigestData Sub procedure
' Creates a 'Digest' of the data
' Input:
' 1] sData: The data to be 'digested'
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Sub HashDigestData(ByVal sData As String)
Dim lError As Long
On Error GoTo ErrDigest
If m_Hash_Status = EC_HASH_BUSY Then Exit Sub
m_Hash_DataReady = False ' Data not ready yet
m_Hash_DataLen = NO_DATASET
' If we don't have a created Hash object
' then raise an error
If m_Hash_Status <> EC_HASH_READY Then
lError = ERROR_NO_HASH_CREATED
GoTo ErrNoCreated
''err.raise vbObjectError + 1004, , "Hash Object has not been created yet."
End If
' We are busy
m_Hash_Status = EC_HASH_BUSY
 im lDataLen As Long ' Holds the length of the data
lDataLen = Len(sData)
' Digest data
If Not CBool(CryptHashData(m_Hash_Object, sData, lDataLen, 0)) Then
lError = ERROR_NO_DIGEST
'err.raise vbObjectError ' Fire error handler
''err.raise vbObjectError + 1005, , "Unable to digest the data."
End If
' Call SetHashData procedure to set
' the variable that holds the result
' of this digestion [see SetHashData]
Call SetHashData
If m_Hash_DataLen = NO_DATASET Then
lError = ERROR_NO_HASH_DATA
'err.raise vbObjectError ' Fire error handler
End If
m_Hash_DataReady = True ' Yep! Data ready
m_Hash_Status = EC_HASH_READY ' And we are ready to work again
' Raise event HashDataComplete
Exit Sub
ErrNoCreated:
'err.raise vbObjectError + lError, "EzCryptoApi", "Hash Object has not been created yet"
ErrDigest:
 im sMsg As String
m_Hash_Status = EC_HASH_READY
Select Case lError
Case ERROR_NO_DIGEST: sMsg = "Error 'digesting' data"
Case ERROR_NO_HASH_DATA: sMsg = "Error setting/getting digested data"
Case Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End Select
'err.raise vbObjectError + Error, "EzCryptoApi", sMsg
End Sub
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' GetDigestedData Function procedure
' Returns the digested data from
' Input:
' 1] sFilePath: The path and filename of the file to hash
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Function GetDigestedData(ByVal echfFormat As EC_HASH_DATAFORMAT) As String
Dim lError As Long
On Error GoTo errHandler
If echfFormat < EC_HF_HEXADECIMAL Or echfFormat > EC_HF_ASCII Then
lError = ERROR_ILLEGAL_PROPERTY
'err.raise vbObjectError ' Fire error handler
''err.raise vbObjectError + 1001, , "Illegal property value"
End If
'GetDigestedData = m_Hash_Prov.GetHashData(hFormat)
 im sData As String, sHex As String
 im icounter As Integer
If m_Hash_Status = EC_HASH_NONE Then
lError = ERROR_NO_HASH_CREATE
'err.raise vbObjectError ' Fire error handler
''err.raise vbObjectError + 1004, , _
"The Hash object has not been created yet."
End If
If m_Hash_DataLen = NO_DATASET Or m_Hash_DataReady = False Then
lError = ERROR_NOTHING_DIGESTED
'err.raise vbObjectError ' Fire error handler
End If
' Format the data as specified
Select Case echfFormat
Case EC_HF_HEXADECIMAL
For icounter = 0 To m_Hash_DataLen - 1
sHex = Hex(m_Hash_Data(icounter))
If Len(sHex) > 1 Then
sData = sData & sHex & vbTab
Else
sData = sData & "0" & sHex & vbTab
End If
sHex = ""
Next
Case EC_HF_NUMERIC
For icounter = 0 To m_Hash_DataLen - 1
sData = sData & CStr(m_Hash_Data(icounter))
Next
Case EC_HF_ASCII
For icounter = 0 To m_Hash_DataLen - 1
sData = sData & Chr(m_Hash_Data(icounter))
Next
End Select
GetDigestedData = sData
Exit Function
errHandler:
 im sMsg As String
Select Case lError
Case ERROR_NO_HASH_CREATE: sMsg = "Hash object has not been created yet"
Case ERROR_NOTHING_DIGESTED: sMsg = "Nothing has been digested yet"
Case Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End Select
'err.raise vbObjectError + lError, "EzCryptoApi", sMsg
End Function
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' DestroyHash Sub procedure
' Destroys the Hash Object [if any]
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Sub DestroyHash()
Dim lError As Long
On Error GoTo ErrDestroyHash
' We do some action only if we got
' the object, otherwise just pass
If m_Hash_Status = EC_HASH_READY Then
If Not CBool(CryptDestroyHash(m_Hash_Object)) Then
lError = ERROR_NO_HASH_CREATE
'err.raise vbObjectError ' Fire error handler
''err.raise vbObjectError + 1008, , "Unable to destroy Hash Object."
End If
' Re-set property values
m_Hash_DataLen = 0
m_Hash_DataReady = False
m_Hash_Status = EC_HASH_NONE
End If
Exit Sub
ErrDestroyHash:
If lError = ERROR_NO_HASH_CREATE Then
'err.raise vbObjectError + lError, "EzCryptoApi", "Unable to destroy Hash object"
Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End If
End Sub
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' SetHashData Sub procedure
' Initializes m_Hash_Data byte array with the hash value
' of the data digested
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Private Sub SetHashData()
Dim lLength As Long
lLength = 20& ' This will hold the actual length of the digested data
If Not CBool(CryptGetHashParam(m_Hash_Object, HP_HASHVAL, m_Hash_Data(0), _
lLength, 0)) Then
m_Hash_DataLen = 0
Exit Sub
End If
' Set the module variable to the actual length of the hash value
m_Hash_DataLen = lLength
End Sub
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' InitKey Sub procedure
' Initializes encryption/decryption keys
'
' Output:
' A handle to the encryption/decryption key if successful
' zero otherwise
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Private Function InitKey() As Long
Dim lHash As Long
Dim lKey As Long
' Not very optimistic
InitKey = 0
lKey = 0
' No success getting a handle to the provider?
' Then raise an error
If Not CBool(InitProvider()) Then
GoTo Done
''err.raise vbObjectError + 1003, , "Error getting a handle to key containers"
End If
If Not CBool(CryptCreateHash(m_CSP_Provider, m_Hash_Algorithm, 0, 0, lHash)) Then
GoTo Done
' 'err.raise vbObject + 1002, , "Unable to initalize hash object for encryption"
End If
'Hash in the password data.
If Not CBool(CryptHashData(lHash, m_EncDec_Password, Len(m_EncDec_Password), 0)) Then
GoTo Done
' 'err.raise vbObjectError + 1010, , "Unable to 'hash' the password"
End If
'Let's derive a session key from the hash object.
If Not CBool(CryptDeriveKey(m_CSP_Provider, m_EncDec_Algorithm, lHash, 0, lKey)) Then
GoTo Done
' 'err.raise vbObjectError + 1011, , "Unable to derive a session key from Hash object"
End If
CryptDestroyHash (lHash)
lHash = 0
' Success? lKey will have a handle to the session key
Done:
InitKey = lKey
End Function
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' InitProvider Sub procedure
' Initializes Cryptographic Service Provider
'
' Output:
' A handle to key container, zero otherwise
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Private Function InitProvider() As Long
Dim sProvider As String ' Name of provider
Dim sContainer As String ' vbnullchar
InitProvider = 1 'Very optimistic
If m_CSP_Provider = 0 Then
sProvider = MS_ENHANCED_PROV & vbNullChar
m_Provider_Name = [Microsoft Enhanced Cryptographic Provider]
sContainer = vbNullChar
'Attempt to acquire a handle to the chosen key container.
If Not CBool(CryptAcquireContext(m_CSP_Provider, ByVal sContainer, ByVal sProvider, PROV_RSA_FULL, 0)) Then
' Attempt to create a new key container
If Not CBool(CryptAcquireContext(m_CSP_Provider, ByVal sContainer, ByVal sProvider, PROV_RSA_FULL, CRYPT_NEWKEYSET)) Then
' Attempt to get a handle to the enhanced key container
sProvider = MS_DEF_PROV & vbNullChar
m_Provider_Name = [Microsoft Base Cryptographic Provider v.1]
If Not CBool(CryptAcquireContext(m_CSP_Provider, ByVal sContainer, ByVal sProvider, PROV_RSA_FULL, 0)) Then
' Attempt to create a new key container
If Not CBool(CryptAcquireContext(m_CSP_Provider, ByVal sContainer, ByVal sProvider, PROV_RSA_FULL, CRYPT_NEWKEYSET)) Then
' If Ambient.UserMode = False Then
' MsgBox "Unable to get a handle to key containers..." & vbCrLf & "Check your registry for the following names:" & _
' vbCrLf & "Microsoft Base Cryptographic Provider v1.0" & vbCrLf & _
' "Microsoft Enhanced Cryptographic Provider v1.0" & vbCrLf & "Without them, EzCryptoApi won't work.", vbCritical, "Fatal Error [EzCryptoApi]"
' m_Provider_Name = [No Providers]
' 'If it is not possible to get a handle to the
' '[default] OP containers, return 0 [sight! :{ ]
' InitProvider = 0
' End If
End If
End If
End If
End If
End If
End Function
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' EncryptData Sub procedure
' Encrypts a small amounts of data
' Input:
' 1] sData: Data to encrypt
' Output:
' The Encrypted data as a string
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Function EncryptData(ByVal sData As String) As String
' If working get out of here
If m_EncDec_Status = EC_CRYPT_BUSY Then Exit Function
Dim lKey As Long ' Handle to the key
Dim sBuffer As String ' Encrypted buffer
Dim lLength As Long ' Length of buffer to encrypt
Dim lBufLen As Long ' Length of buffer pass to the function
Dim lError As Long ' Error values
'On Error GoTo ErrEncrypt
m_EncDec_Status = EC_CRYPT_BUSY
'Get handle to a session key
lKey = InitKey
If lKey = 0 Then
lError = ERROR_NO_KEY_DERIVED
'err.raise vbObjectError ' Fire error handler
End If
'Prepare a string buffer for the CryptEncrypt function
lLength = Len(sData) ' Get the length
lBufLen = lLength * 2 ' Initialize lBufLen with what will be the buffer size
sBuffer = String(lBufLen, vbNullChar) ' Allocate buffer size
LSet sBuffer = sData ' Copy the data to the left of the variable without resizing sBuffer
'Encrypt data!
If Not CBool(CryptStringEncrypt(lKey, 0, 1, 0, sBuffer, lLength, lBufLen)) Then
lError = ERROR_NO_ENCRYPT
' Fire error handler
End If
' Return encrypted data
EncryptData = Left$(sBuffer, lLength)
'Free up CSP resources
'Destroy session key.
If (lKey) Then CryptDestroyKey lKey
' Ready to work again
m_EncDec_Status = EC_CRYPT_READY
Exit Function
ErrEncrypt:
m_EncDec_Status = EC_CRYPT_NONE
 im sMsg As String
If (lKey) Then CryptDestroyKey lKey
Select Case lError
Case ERROR_NO_KEY_DERIVED: sMsg = "Error deriving a key for encryption"
Case ERROR_NO_ENCRYPT: sMsg = "Error encrypting data"
Case Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End Select
'err.raise vbObjectError + lError, "EzCryptoApi", sMsg
End Function
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
' DecryptData Sub procedure
' Decrypts a small amounts of data
' Input:
' 1] sData: Data to decrypt
' Output:
' The Decrypted data as a string
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Public Function DecryptData(ByVal sData As String) As String
If m_EncDec_Status = EC_CRYPT_BUSY Then Exit Function
Dim lError As Long ' To raise errors
Dim lKey As Long ' Key to use encryption algorithm
Dim lResult As Long ' Is the provider ready?
Dim lBufLen As Long ' Length of data
On Error GoTo ErrDecrypt
m_EncDec_Status = EC_CRYPT_BUSY
'Get a handle to session key
lKey = InitKey()
If lKey = 0 Then
lError = ERROR_NO_KEY_DERIVED
'err.raise vbObjectError ' Fire error handler
End If
'Prepare sBuffer for CryptStringDecrypt
lBufLen = Len(sData)
'Decrypt data
If Not CBool(CryptStringDecrypt(lKey, 0, 1, 0, sData, lBufLen)) Then
lError = ERROR_NO_DECRYPT
'err.raise vbObjectError ' Fire error handler
End If
'Return decrypted string
 ecryptData = Mid$(sData, 1, lBufLen)
'Release CSP Resources
If lKey Then CryptDestroyKey lKey
m_EncDec_Status = EC_CRYPT_READY
Exit Function
ErrDecrypt:
m_EncDec_Status = EC_CRYPT_NONE
 im sMsg As String
Select Case lError
Case ERROR_NO_KEY_DERIVED: sMsg = "Error to derive a key for decryption"
Case ERROR_NO_DECRYPT: sMsg = "Error decrypting data"
Case Else: 'err.raise err.Number, "EzCryptoApi", err.Description
End Select
'err.raise vbObjectError + lError, "Ezcryptoapi", sMsg
End Function
Public Sub Initialize()
Dim lResult As Long
lResult = InitProvider
If lResult = 1 Then CryptReleaseContext m_CSP_Provider, 0
m_CSP_Provider = 0
End Sub
Public Sub InitDefaultProperties()
' Default properties
m_Hash_Algo_Id = SHA
m_Hash_Algorithm = CALG_SHA
m_EncDec_Algo_Id = [Triple DES]
m_EncDec_Algorithm = CALG_3DES
m_EncDec_Password = ""
End Sub
Public Sub Terminate()
If m_Hash_Status = EC_HASH_READY Then CryptDestroyHash m_Hash_Object
If m_CSP_Provider Then CryptReleaseContext m_CSP_Provider, 0
End Sub
А вообще-то, слушай, кинь и асм и цэ, откомпилю в длл, может скорость сравню....
Я когда-то мучил алгоритм md5, написал брут по словарю, на ассемблере ессно, долго оптимизировал алгоритм и пришёл решению, которое давало довольно неплохие результаты, в частности на моём процессоре Duron950/256 словарь с числом слов 3126988 перебирается примерно за 3 секунды. Возможно кто-то сможет ещё лучше оптимизировать мою реализацию, но больше 10% в скорости выжать уже вряд ли удасться.
Исходники и сам брут здесь: http://hunger.ru/releases/3