In this article we will talk about digital signature and how to use it to detect any intended/unintended data tampering. Data can be tmpered in many ways it can be intentionally tmpered or it can be currupted during communication or may be some other reason. Anyways today I will show you the use of powerful Crypto APIs which can be used to detect this type of tampering.
What is Digital Signature
A digital signature is an electronic signature that can be used to authenticate the identity of the sender of a message, or of the signer of a document. It can also be used to ensure that the original content of the message or document that has been conveyed is unchanged.
Before you create a digital signature you need a private key and to verify a digital signature you need public key. Private key should remain secrete all time and public key should be distributed to users.
Creating Public/Private Key Pair
- Get a handle to the base cryptographic provider using CryptAcquireContext.
- Create the new key pair using CryptGenKey
- Copy the keys to variables using CryptExportKey.
- Write Public/Private key variables to files or store somewhere else so later on you can use it to create a signature or verify existing signature.
Creating Digital Signature
- Get a handle to the base cryptographic provider using CryptAcquireContext.
- Read Private Key into variable from previously stored location (which can be file/registry or memory).
- Call ImportPrivateKey to import the key blob into the key container. You need to pass private key variable which we created in previous step.
- Get Hash of the file using CryptCreateHash and CryptHashData. This process may take time depending on the size of the file.
- Now call CryptSignHash to create signature. You need to pass file hash which we created in the previous step.
- Store signature to file.
- Now we dont need hash anymore so destroy the hash by calling CryptDestroyHash. Always relese handle whenever you are done.
Verifying Digital Signature
- Get a handle to the base cryptographic provider using CryptAcquireContext.
- Read Public Key into variable from previously stored location (which can be file/registry or memory).
- Call ImportPrivateKey to import the key blob into the key container. You need to pass private key variable which we created in previous step.
- Read the signature file.
- Get Hash of the file using CryptCreateHash and CryptHashData. This process may take time depending on the size of the file.
- Now call CryptVerifySignature to verify the signature.
- Store signature to file.
- Now we dont need hash anymore so destroy the hash by calling CryptDestroyHash. Always relese handle whenever you are done.
Step-By-Step Example
- Create a standard exe project - Add one module and one class - Rename class name to clsDigitalSig - Add 3 command button controls and 4 textbox controls - Add the following code in form1
Form1.frm |
Click here to copy the following block | Option Explicit
Private Sub Command3_Click() Dim oSecurity As New clsDigitalSig On Error Resume Next Kill App.Path & "\" & MY_KEYNAME & ".pub" Kill App.Path & "\" & MY_KEYNAME & ".pri" On Error GoTo ErrorHandler Call oSecurity.CreateKeyPair(MY_KEYNAME)
Set oSecurity = Nothing Call DisplayKeys Exit Sub ErrorHandler: MsgBox Err.Source & vbNewLine & vbNewLine & Err.Description End Sub
Private Sub Command1_Click() Dim oSecurity As New clsDigitalSig On Error GoTo ErrorHandler
Call oSecurity.SignFile(MY_KEYNAME, Text1.Text) MsgBox "File signed!", vbInformation, "Signing complete" Text2 = oSecurity.Signature Set oSecurity = Nothing Exit Sub
ErrorHandler: MsgBox Err.Source & vbNewLine & vbNewLine & Err.Description End Sub
Private Sub Command2_Click() Dim oSecurity As New clsDigitalSig Dim bIsOk As Boolean On Error GoTo ErrorHandler
If Text1 <> "" Then bIsOk = oSecurity.VerifyFile(MY_KEYNAME, Text1) Else Exit Sub End If
If bIsOk Then MsgBox "File verification successful!", vbInformation, "File Verification" Else MsgBox "Error validating file! Tampering possible!", vbExclamation, "File Verification" End If Set oSecurity = Nothing Exit Sub
ErrorHandler: MsgBox "Error validating file! Tampering possible!", vbExclamation, "Verification" End Sub
Private Sub Form_Load() Dim bKeyFileFound As Boolean, ret
Command1.Caption = "Sign" Command2.Caption = "Verify Signature" Command3.Caption = "Create Public/Private Key Pair"
Text1.Text = App.Path & "\SignMe.txt"
Text2.BackColor = &HC0C0C0: Text2.ForeColor = vbRed Text3.BackColor = &HC0C0C0: Text3.ForeColor = vbBlue Text4.BackColor = &HC0C0C0: Text4.ForeColor = vbBlue
If Dir(App.Path & "\" & MY_KEYNAME & ".pri") <> "" Then If Dir(App.Path & "\" & MY_KEYNAME & ".pub") <> "" Then bKeyFileFound = True Else bKeyFileFound = False End If Else bKeyFileFound = False End If
If bKeyFileFound = True Then DisplayKeys Else ret = MsgBox("No key pair found. Do you want to create a default public/private key pair?", vbYesNo + vbQuestion) If ret = vbYes Then Call Command3_Click Else Command1.Enabled = False Command2.Enabled = False End If End If End Sub
Sub DisplayKeys() Text3 = Replace(FileText(App.Path & "\" & MY_KEYNAME & ".pub"), Chr(0), "")
Text4 = Replace(FileText(App.Path & "\" & MY_KEYNAME & ".pri"), Chr(0), "") End Sub |
- Add the following code in Module1
Module1.bas |
Click here to copy the following block | Option Explicit
Public sGetKeyName As String
Public Const MY_KEYNAME = "DigitalSigDemo"
Public Enum eERROR_CODE eProviderUnavailable = 101 eGeneratingKeyPair = 102 eExportingPublicKey = 103 eExportingPrivateKey = 104 eGeneratingHash = 105 eGeneratingSignature = 106 eWritingSignatureFile = 107 eImportingPublicKey = 108 eImportingPrivateKey = 109 eReadingSignatureFile = 110 eKeyAlreadyExists = 111 End Enum
Public Const RSA1 As Long = &H31415352 Public Const RSA2 As Long = &H32415352
Public Const ALG_CLASS_HASH As Long = (4 * 2 ^ 13) Public Const ALG_SID_MD5 As Long = 3 Public Const CALG_MD5 As Long = ALG_CLASS_HASH + ALG_SID_MD5
Public Const PROV_RSA_FULL As Long = 1 Public Const MS_DEF_PROV = "Microsoft Base Cryptographic Provider v1.0" Public Const MS_ENHANCED_PROV = "Microsoft Enhanced Cryptographic Provider v1.0"
Public Const CRYPT_VERIFYCONTEXT As Long = &HF0000000 Public Const CRYPT_NEWKEYSET As Long = &H8 Public Const CRYPT_DELETEKEYSET As Long = &H10 Public Const CRYPT_MACHINE_KEYSET As Long = &H20
Public Const CRYPT_EXPORTABLE As Long = &H1 Public Const CRYPT_USER_PROTECTED As Long = &H2 Public Const CRYPT_CREATE_SALT As Long = &H4 Public Const CRYPT_UPDATE_KEY As Long = &H8 Public Const CRYPT_NO_SALT As Long = &H10 Public Const CRYPT_PREGEN As Long = &H40 Public Const CRYPT_RECIPIENT As Long = &H10 Public Const CRYPT_INITIATOR As Long = &H40 Public Const CRYPT_ONLINE As Long = &H80 Public Const CRYPT_SF As Long = &H100 Public Const CRYPT_CREATE_IV As Long = &H200 Public Const CRYPT_KEK As Long = &H400 Public Const CRYPT_DATA_KEY As Long = &H800
Public Const PP_CLIENT_HWND As Long = 1 Public Const PP_CONTEXT_INFO As Long = 11 Public Const PP_KEYEXCHANGE_KEYSIZE As Long = 12 Public Const PP_SIGNATURE_KEYSIZE As Long = 13 Public Const PP_KEYEXCHANGE_ALG As Long = 14 Public Const PP_SIGNATURE_ALG As Long = 15 Public Const PP_DELETEKEY As Long = 24
Public Const SIMPLEBLOB As Long = &H1 Public Const PUBLICKEYBLOB As Long = &H6 Public Const PRIVATEKEYBLOB As Long = &H7 Public Const PLAINTEXTKEYBLOB As Long = &H8
Public Const NTE_BAD_UID As Long = &H80090001 Public Const NTE_BAD_HASH As Long = &H80090002 Public Const NTE_BAD_KEY As Long = &H80090003 Public Const NTE_BAD_LEN As Long = &H80090004 Public Const NTE_BAD_DATA As Long = &H80090005 Public Const NTE_BAD_SIGNATURE As Long = &H80090006 Public Const NTE_BAD_VER As Long = &H80090007 Public Const NTE_BAD_ALGID As Long = &H80090008 Public Const NTE_BAD_FLAGS As Long = &H80090009 Public Const NTE_BAD_TYPE As Long = &H8009000A Public Const NTE_BAD_KEY_STATE As Long = &H8009000B Public Const NTE_BAD_HASH_STATE As Long = &H8009000C Public Const NTE_NO_KEY As Long = &H8009000D Public Const NTE_NO_MEMORY As Long = &H8009000E Public Const NTE_EXISTS As Long = &H8009000F Public Const NTE_PERM As Long = &H80090010 Public Const NTE_NOT_FOUND As Long = &H80090011 Public Const NTE_DOUBLE_ENCRYPT As Long = &H80090012 Public Const NTE_BAD_PROVIDER As Long = &H80090013 Public Const NTE_BAD_PROV_TYPE As Long = &H80090014 Public Const NTE_BAD_PUBLIC_KEY As Long = &H80090015 Public Const NTE_BAD_KEYSET As Long = &H80090016 Public Const NTE_PROV_TYPE_NOT_DEF As Long = &H80090017 Public Const NTE_PROV_TYPE_ENTRY_BAD As Long = &H80090018 Public Const NTE_KEYSET_NOT_DEF As Long = &H80090019 Public Const NTE_KEYSET_ENTRY_BAD As Long = &H8009001A Public Const NTE_PROV_TYPE_NO_MATCH As Long = &H8009001B Public Const NTE_SIGNATURE_FILE_BAD As Long = &H8009001C Public Const NTE_PROVIDER_DLL_FAIL As Long = &H8009001D Public Const NTE_PROV_DLL_NOT_FOUND As Long = &H8009001E Public Const NTE_BAD_KEYSET_PARAM As Long = &H8009001F Public Const NTE_FAIL As Long = &H80090020 Public Const NTE_SYS_ERR As Long = &H80090021
Public Const AT_SIGNATURE As Long = 2
Public Const T_PUBLICKEYBLOBLEN = 84 Public Const T_PRIVATEKEYBLOBLEN = 308
Public Type T_EXP_PUBLICKEYBLOB bPublicKey(1 To T_PUBLICKEYBLOBLEN) As Byte End Type
Public Type T_EXP_PRIVATEKEYBLOB bPrivateKey(1 To T_PRIVATEKEYBLOBLEN) As Byte End Type
Public Type T_PUBLICKEYBLOB bType As Byte bVersion As Byte reserved As Integer aiKeyAlg As Long magic As Long bitlen As Long pubexp As Long modulus(1 To 64) As Byte End Type
Public Type T_PRIVATEKEYBLOB bType As Byte bVersion As Byte reserved As Integer aiKeyAlg As Long magic As Long bitlen As Long pubexp As Long modulus(1 To 64) As Byte prime1(1 To 32) As Byte prime2(1 To 32) As Byte exponent1(1 To 32) As Byte exponent2(1 To 32) As Byte coefficient(1 To 32) As Byte privateExponent(1 To 64) As Byte End Type
Public Declare Function CryptAcquireContext Lib "advapi32.dll" _ Alias "CryptAcquireContextA" (ByRef hCryptProv As Long, _ ByVal pszContainer As String, ByVal 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 CryptGenKey Lib "advapi32.dll" _ (ByVal hProv As Long, ByVal Algid As Long, ByVal dwFlags As Long, _ ByRef 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, ByRef pbData As Any, _ ByRef pdwDataLen 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, ByRef phHash As Long) As Long
Public Declare Function CryptHashData Lib "advapi32.dll" _ (ByVal hHash As Long, ByRef pbData As Any, ByVal dwDataLen As Long, _ ByVal dwFlags As Long) As Long
Public Declare Function CryptSignHash Lib "advapi32.dll" _ Alias "CryptSignHashA" (ByVal hHash As Long, ByVal dwKeySpec As Long, _ ByVal sDescription As String, ByVal dwFlags As Long, _ ByRef pbSignature As Any, ByRef pdwSigLen As Long) As Long
Public Declare Function CryptVerifySignature Lib "advapi32.dll" _ Alias "CryptVerifySignatureA" (ByVal hHash As Long, _ ByRef pbSignature As Any, ByVal dwSigLen As Long, _ ByVal hPubKey As Long, ByVal sDescription As String, _ ByVal dwFlags As Long) As Long
Public Declare Function CryptDestroyHash Lib "advapi32.dll" _ (ByVal hHash As Long) As Long
Public Declare Function CryptImportKey Lib "advapi32.dll" _ (ByVal hProv As Long, ByRef pbData As Any, ByVal dwDataLen As Long, _ ByVal hPubKey As Long, ByVal dwFlags As Long, _ ByRef phKey As Long) As Long
Public Declare Function CryptDestroyKey Lib "advapi32.dll" _ (ByVal hKey As Long) As Long
Private Function GetErrorMsg(code As eERROR_CODE) As String Select Case code Case eProviderUnavailable GetErrorMsg = "Error accessing security module" Case eGeneratingKeyPair GetErrorMsg = "Error generating key pair" Case eExportingPublicKey GetErrorMsg = "Error exporting public key" Case eExportingPrivateKey GetErrorMsg = "Error exporting private key" Case eGeneratingHash GetErrorMsg = "Error generating hash" Case eGeneratingSignature GetErrorMsg = "Error signing file" Case eWritingSignatureFile GetErrorMsg = "Error writing signature file" Case eImportingPublicKey GetErrorMsg = "Error importing public key" Case eImportingPrivateKey GetErrorMsg = "Error importing private key" Case eReadingSignatureFile GetErrorMsg = "Error reading signature file" Case eKeyAlreadyExists GetErrorMsg = "Error creating key, key already exists" End Select End Function
Public Sub pRaiseError(sSource As String, sRoutine As String, _ code As eERROR_CODE, Optional ByVal sArgument As String = "") Err.Raise vbObjectError + code, sSource & "." & sRoutine, _ GetErrorMsg(code) & " " & sArgument End Sub
Function FileText(ByVal filename As String) As String Dim handle As Integer
If Len(Dir$(filename)) = 0 Then Err.Raise 53 End If
Dim f As Integer Dim s As String handle = FreeFile Open filename For Binary Access Read As handle s = Space(LOF(handle)) Get #handle, , s Close handle FileText = s End Function |
- Add the following code in clsDigitalSig
clsDigitalSig.cls |
Click here to copy the following block | Option Explicit
Const Source = "clsDigitalSig"
Private Const C_CHUNK_SIZE As Long = 512
Public Enum E_KEY_TYPE eKeyNone = 0 eKeyPublic = 1 eKeyPrivate = 2 End Enum
Private m_hProvider As Long Private m_hKeyPair As Long Private m_eKeyStatus As E_KEY_TYPE
Private m_Signature As String
Public Property Get Signature() As String Signature = m_Signature End Property
Public Sub CreateKeyPair(KeyName As String) Dim lResult As Long Dim PublicKey As T_EXP_PUBLICKEYBLOB Dim PrivateKey As T_EXP_PRIVATEKEYBLOB Const Routine = "CreateKeyPair" If Dir(App.Path & "\" & KeyName & ".pri") <> "" And _ Dir(App.Path & "\" & KeyName & ".pub") <> "" Then Call pRaiseError(Source, Routine, eKeyAlreadyExists) End If If Not (IsProviderOpen) Then If Not (AcquireCryptoProvider) Then Call pRaiseError(Source, Routine, eProviderUnavailable) Exit Sub End If End If lResult = CryptGenKey(m_hProvider, _ AT_SIGNATURE, &H2000000 Or CRYPT_EXPORTABLE, m_hKeyPair)
If lResult = 0 Then m_eKeyStatus = eKeyNone Call pRaiseError(Source, Routine, eGeneratingKeyPair) Exit Sub Else m_eKeyStatus = eKeyPrivate End If If Not (ExportPublicKey(PublicKey)) Then Call pRaiseError(Source, Routine, eExportingPublicKey) Exit Sub End If If Not (ExportPrivateKey(PrivateKey)) Then Call pRaiseError(Source, Routine, eExportingPrivateKey) Exit Sub End If If Not (WriteFile(App.Path & "\" & KeyName & ".pub", PublicKey.bPublicKey)) Then Call pRaiseError(Source, Routine, eExportingPublicKey) End If If Not (WriteFile(App.Path & "\" & KeyName & ".pri", PrivateKey.bPrivateKey)) Then Call pRaiseError(Source, Routine, eExportingPrivateKey) End If CryptDestroyKey m_hKeyPair
m_eKeyStatus = eKeyNone End Sub
Public Sub SignFile(sKeyName As String, sFileName As String) Dim lResult As Long Dim hHash As Long Dim lSigLen As Long Dim bSig(1 To 64) As Byte Dim PrivateKey As T_EXP_PRIVATEKEYBLOB Const Routine = "SignFile" If Not (IsProviderOpen) Then If Not (AcquireCryptoProvider) Then Call pRaiseError(Source, Routine, eProviderUnavailable) Exit Sub End If End If If Not (ReadFile(App.Path & "\" & sKeyName & ".pri", PrivateKey.bPrivateKey)) Then Call pRaiseError(Source, Routine, eImportingPrivateKey) Exit Sub End If If Not (ImportPrivateKey(PrivateKey)) Then Call pRaiseError(Source, Routine, eImportingPrivateKey) Exit Sub End If If Not (HashFile(sFileName, hHash)) Then Call pRaiseError(Source, Routine, eGeneratingHash) Exit Sub End If lSigLen = 64 lResult = CryptSignHash(hHash, AT_SIGNATURE, vbNullString, 0, bSig(1), lSigLen) If lResult = 0 Then Call pRaiseError(Source, Routine, eGeneratingSignature) Exit Sub End If lResult = CryptDestroyHash(hHash) If Not (WriteFile(sFileName & ".sgn", bSig)) Then Call pRaiseError(Source, Routine, eWritingSignatureFile) Exit Sub End If Call RefreshSigString(bSig) End Sub
Private Sub RefreshSigString(bSig() As Byte) m_Signature = "" Dim i, v For i = LBound(bSig) To UBound(bSig) v = Hex(bSig(i)) v = IIf(Len(v) = 1, "0" & v, v) m_Signature = m_Signature & " " & v Next End Sub
Public Function VerifyFile(sKeyName As String, sFileName As String) As Boolean Dim lResult As Long Dim lSigLen As Long Dim hHash As Long Dim bSig(1 To 64) As Byte Dim PublicKey As T_EXP_PUBLICKEYBLOB Const Routine = "VerifyFile" If Not (IsProviderOpen) Then If Not (AcquireCryptoProvider) Then Call pRaiseError(Source, Routine, eProviderUnavailable) Exit Function End If End If If Not (ReadFile(App.Path & "\" & sKeyName & ".pub", PublicKey.bPublicKey)) Then Call pRaiseError(Source, Routine, eImportingPublicKey) Exit Function End If If Not (ImportPublicKey(PublicKey)) Then Call pRaiseError(Source, Routine, eImportingPublicKey) Exit Function End If lSigLen = 64 If Not (ReadFile(sFileName & ".sgn", bSig)) Then Call pRaiseError(Source, Routine, eReadingSignatureFile) Exit Function End If If Not (HashFile(sFileName, hHash)) Then Call pRaiseError(Source, Routine, eGeneratingHash) Exit Function End If
lResult = CryptVerifySignature(hHash, bSig(1), lSigLen, m_hKeyPair, vbNullString, 0) If lResult = 0 Then VerifyFile = False Else VerifyFile = True End If lResult = CryptDestroyHash(hHash) Call RefreshSigString(bSig) End Function
Private Function HashFile(sFileName As String, lHash As Long) As Boolean Dim hHash As Long Dim lResult As Long Dim lFileHandle As Long Dim lBytesRemaining As Long Dim abFile() As Byte lResult = CryptCreateHash(m_hProvider, CALG_MD5, 0, 0, hHash)
If lResult = 0 Then HashFile = False Exit Function End If
lFileHandle = FreeFile
On Error GoTo ErrorHandler Open sFileName For Binary As lFileHandle ReDim abFile(1 To C_CHUNK_SIZE) While (LOF(lFileHandle) - Seek(lFileHandle) >= C_CHUNK_SIZE) Get lFileHandle, , abFile lResult = CryptHashData(hHash, abFile(1), C_CHUNK_SIZE, 0) If lResult = 0 Then HashFile = False Exit Function End If Wend lBytesRemaining = (LOF(lFileHandle) - Seek(lFileHandle) + 1)
If lBytesRemaining > 0 Then ReDim abFile(1 To lBytesRemaining) Get lFileHandle, , abFile lResult = CryptHashData(hHash, abFile(1), lBytesRemaining, 0) If lResult = 0 Then HashFile = False Exit Function End If End If
Close lFileHandle
HashFile = True lHash = hHash Exit Function
ErrorHandler: HashFile = False End Function
Private Function AcquireCryptoProvider() As Boolean Dim lResult As Long lResult = CryptAcquireContext(m_hProvider, vbNullString, _ vbNullString, PROV_RSA_FULL, 0) If lResult = 0 Then lResult = CryptAcquireContext(m_hProvider, App.EXEName, _ vbNullString, PROV_RSA_FULL, 0)
End If
If lResult = 0 Then If Err.LastDllError = NTE_EXISTS Or Err.LastDllError = NTE_BAD_KEYSET Then lResult = CryptAcquireContext(m_hProvider, App.EXEName, _ vbNullString, PROV_RSA_FULL, CRYPT_NEWKEYSET) End If End If
If lResult = 0 Then AcquireCryptoProvider = False m_hProvider = 0 Else AcquireCryptoProvider = True End If End Function
Private Function IsProviderOpen() As Boolean IsProviderOpen = (m_hProvider <> 0) End Function
Private Function ExportPublicKey(ByRef PublicKey As T_EXP_PUBLICKEYBLOB) As Boolean Dim lLenKey As Long Dim lResult As Long If m_eKeyStatus = eKeyNone Or m_hKeyPair = 0 Then ExportPublicKey = False Exit Function End If
lLenKey = LenB(PublicKey) lResult = CryptExportKey(m_hKeyPair, 0, PUBLICKEYBLOB, 0, PublicKey, lLenKey)
If lResult = 0 Then ExportPublicKey = False Else ExportPublicKey = True End If End Function
Private Function ExportPrivateKey(ByRef PrivateKey As T_EXP_PRIVATEKEYBLOB) As Boolean Dim lLenKey As Long Dim lResult As Long If m_eKeyStatus <> eKeyPrivate Or m_hKeyPair = 0 Then ExportPrivateKey = False Exit Function End If
lLenKey = LenB(PrivateKey) lResult = CryptExportKey(m_hKeyPair, 0, PRIVATEKEYBLOB, 0, PrivateKey, lLenKey)
If lResult = 0 Then ExportPrivateKey = False Else ExportPrivateKey = True End If End Function
Private Function ImportPrivateKey(ByRef PrivateKey As T_EXP_PRIVATEKEYBLOB) As Boolean Dim lLenKey As Long Dim lResult As Long lLenKey = LenB(PrivateKey) lResult = CryptImportKey(m_hProvider, PrivateKey, lLenKey, 0, 0, m_hKeyPair)
If lResult = 0 Then ImportPrivateKey = False Else ImportPrivateKey = True End If End Function
Private Function ImportPublicKey(ByRef PublicKey As T_EXP_PUBLICKEYBLOB) As Boolean Dim lLenKey As Long Dim lResult As Long lLenKey = LenB(PublicKey) lResult = CryptImportKey(m_hProvider, PublicKey, lLenKey, 0, 0, m_hKeyPair) ImportPublicKey = (lResult <> 0) End Function
Private Function WriteFile(sFileName As String, Data() As Byte) As Boolean Dim lFileHandle As Long On Error GoTo ErrorHandler
lFileHandle = FreeFile
Open sFileName For Binary As lFileHandle Put lFileHandle, , Data Close lFileHandle
WriteFile = True Exit Function
ErrorHandler: WriteFile = False End Function
Private Function ReadFile(sFileName As String, Data() As Byte) As Boolean Dim lFileHandle As Long On Error GoTo ErrorHandler
lFileHandle = FreeFile
Open sFileName For Binary As lFileHandle
ReDim bData(1 To LOF(lFileHandle))
Get lFileHandle, , Data Close lFileHandle
ReadFile = True Exit Function
ErrorHandler: ReadFile = False End Function |
|