Atlanta Custom Software Development 

 
   Search        Code/Page
 

User Login
Email

Password

 

Forgot the Password?
Services
» Web Development
» Maintenance
» Data Integration/BI
» Information Management
Programming
  Database
Automation
OS/Networking
Graphics
Links
Tools
» Regular Expr Tester
» Free Tools


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
  1. Get a handle to the base cryptographic provider using CryptAcquireContext.
  2. Create the new key pair using CryptGenKey
  3. Copy the keys to variables using CryptExportKey.
  4. 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
  1. Get a handle to the base cryptographic provider using CryptAcquireContext.
  2. Read Private Key into variable from previously stored location (which can be file/registry or memory).
  3. Call ImportPrivateKey to import the key blob into the key container. You need to pass private key variable which we created in previous step.
  4. Get Hash of the file using CryptCreateHash and CryptHashData. This process may take time depending on the size of the file.
  5. Now call CryptSignHash to create signature. You need to pass file hash which we created in the previous step.
  6. Store signature to file.
  7. Now we dont need hash anymore so destroy the hash by calling CryptDestroyHash. Always relese handle whenever you are done.

Verifying Digital Signature
  1. Get a handle to the base cryptographic provider using CryptAcquireContext.
  2. Read Public Key into variable from previously stored location (which can be file/registry or memory).
  3. Call ImportPrivateKey to import the key blob into the key container. You need to pass private key variable which we created in previous step.
  4. Read the signature file.
  5. Get Hash of the file using CryptCreateHash and CryptHashData. This process may take time depending on the size of the file.
  6. Now call CryptVerifySignature to verify the signature.
  7. Store signature to file.
  8. 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

'///////////////////////////////////

'//Create a new pair of keys.
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

'//Create a signature for a selected file
Private Sub Command1_Click()
  Dim oSecurity As New clsDigitalSig
  '
  ' Digitally sign a file.
  '
  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

'//Verify a file.
Private Sub Command2_Click()
  Dim oSecurity As New clsDigitalSig
  Dim bIsOk   As Boolean
  On Error GoTo ErrorHandler

  ' Verify it.

  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

  '//Check if keyfile already there, if it is there then read its content and display it
  '//Displaying Key is just for Demo purpose, its not safe though
  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  '///create new key pair
    Else
      Command1.Enabled = False
      Command2.Enabled = False
    End If
  End If
End Sub

Sub DisplayKeys()
    '//Display Public key
    Text3 = Replace(FileText(App.Path & "\" & MY_KEYNAME & ".pub"), Chr(0), "")

    '//Display Private key
    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
'dss
Public sGetKeyName As String

Public Const MY_KEYNAME = "DigitalSigDemo"

'
' Enumeration for error codes.
'
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
'
' Key constants
'
Public Const RSA1 As Long = &H31415352
Public Const RSA2 As Long = &H32415352
'
' Algorithm id constants
'
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
'
' Acquire constants
'
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"
'
' dwFlags definitions for CryptAcquireContext
'
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
'
' dwFlag definitions for CryptGenKey
'
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
'
' CryptSetProvParam
'
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
'
' exported key blob definitions
'
Public Const SIMPLEBLOB As Long = &H1
Public Const PUBLICKEYBLOB As Long = &H6
Public Const PRIVATEKEYBLOB As Long = &H7
Public Const PLAINTEXTKEYBLOB As Long = &H8
'
' nte errors
'
Public Const NTE_BAD_UID As Long = &H80090001  ' Bad UID
Public Const NTE_BAD_HASH As Long = &H80090002  ' Bad Hash
Public Const NTE_BAD_KEY As Long = &H80090003  ' Bad Key
Public Const NTE_BAD_LEN As Long = &H80090004  ' Bad Length
Public Const NTE_BAD_DATA As Long = &H80090005  ' Bad Data
Public Const NTE_BAD_SIGNATURE As Long = &H80090006  ' Bad Signature
Public Const NTE_BAD_VER As Long = &H80090007  ' Bad Version of provider
Public Const NTE_BAD_ALGID As Long = &H80090008  ' Invalid algorithm specified
Public Const NTE_BAD_FLAGS As Long = &H80090009  ' Invalid flags specified
Public Const NTE_BAD_TYPE As Long = &H8009000A  ' Invalid type specified
Public Const NTE_BAD_KEY_STATE As Long = &H8009000B  ' Key not valid for use in specified state
Public Const NTE_BAD_HASH_STATE As Long = &H8009000C  ' Hash not valid for use in specified state
Public Const NTE_NO_KEY As Long = &H8009000D  ' Key does not exist
Public Const NTE_NO_MEMORY As Long = &H8009000E  ' Insufficient memory available for the operation
Public Const NTE_EXISTS As Long = &H8009000F  ' Object already exists
Public Const NTE_PERM As Long = &H80090010  ' Access denied
Public Const NTE_NOT_FOUND As Long = &H80090011  ' Object was not found
Public Const NTE_DOUBLE_ENCRYPT As Long = &H80090012  ' Data already encrypted
Public Const NTE_BAD_PROVIDER As Long = &H80090013  ' Invalid provider specified
Public Const NTE_BAD_PROV_TYPE As Long = &H80090014  ' Invalid provider type specified
Public Const NTE_BAD_PUBLIC_KEY As Long = &H80090015  ' Provider's public key is invalid
Public Const NTE_BAD_KEYSET As Long = &H80090016  ' Keyset does not exist
Public Const NTE_PROV_TYPE_NOT_DEF As Long = &H80090017  ' Provider type not defined
Public Const NTE_PROV_TYPE_ENTRY_BAD As Long = &H80090018  ' Provider type as registered is invalid
Public Const NTE_KEYSET_NOT_DEF As Long = &H80090019  ' The keyset is not defined
Public Const NTE_KEYSET_ENTRY_BAD As Long = &H8009001A  ' Keyset as registered is invalid
Public Const NTE_PROV_TYPE_NO_MATCH As Long = &H8009001B  ' Provider type does not match registered value
Public Const NTE_SIGNATURE_FILE_BAD As Long = &H8009001C  ' The digital signature file is corrupt
Public Const NTE_PROVIDER_DLL_FAIL As Long = &H8009001D  ' Provider DLL failed to initialize correctly
Public Const NTE_PROV_DLL_NOT_FOUND As Long = &H8009001E  ' Provider DLL could not be found
Public Const NTE_BAD_KEYSET_PARAM As Long = &H8009001F  ' The Keyset parameter is invalid
Public Const NTE_FAIL As Long = &H80090020  ' An internal error occurred
Public Const NTE_SYS_ERR As Long = &H80090021  ' A base error occurred
'
' Generate constants
'
Public Const AT_SIGNATURE As Long = 2
'
' Length of types in bytes (for lset)
'
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
  '
  ' Decode the selected error code and return a message.
  '
  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 = "")
  '
  ' Raise an error.
  '
  Err.Raise vbObjectError + code, sSource & "." & sRoutine, _
      GetErrorMsg(code) & " " & sArgument
End Sub

Function FileText(ByVal filename As String) As String
  Dim handle As Integer

  ' ensure that the file exists
  If Len(Dir$(filename)) = 0 Then
    Err.Raise 53                    ' File not found
  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
'
' Digital signing and encryption functions.
'
Const Source = "clsDigitalSig"
'
' Chunk size to use to hash files.
'
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  ' handle to crypto provider
Private m_hKeyPair  As Long  ' handle to key pair
Private m_eKeyStatus As E_KEY_TYPE  ' flag indicating current key type

Private m_Signature As String '//String representation of signature

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
  '
  ' Creates a new key pair and writes out
  ' a file for each part called "KeyName.pub"
  ' and "KeyName.pri" respectively in the
  ' application path
  '
  Const Routine = "CreateKeyPair"
  '
  ' See if either key already exists.
  '
  If Dir(App.Path & "\" & KeyName & ".pri") <> "" And _
      Dir(App.Path & "\" & KeyName & ".pub") <> "" Then
    Call pRaiseError(Source, Routine, eKeyAlreadyExists)
  End If
  '
  ' See if provider is obtained.
  '
  If Not (IsProviderOpen) Then
    '
    ' Get the provider.
    '
    If Not (AcquireCryptoProvider) Then
      Call pRaiseError(Source, Routine, eProviderUnavailable)
      Exit Sub
    End If
  End If
  '
  ' Create the new key pair.
  ' The use of &H2000000 guarantees a 512 bit key.
  '
  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
    '
    ' New stored key type.
    '
    m_eKeyStatus = eKeyPrivate
  End If
  '
  ' Copy the keys to variables.
  '
  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
  '
  ' Create the key files.
  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
  '
  ' Destroy the key.
  '
  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
  '
  ' Sign a file with the specified private key.
  '
  Const Routine = "SignFile"
  '
  ' See if the provider is obtained.
  '
  If Not (IsProviderOpen) Then
    '
    ' Get the provider.
    '
    If Not (AcquireCryptoProvider) Then
      Call pRaiseError(Source, Routine, eProviderUnavailable)
      Exit Sub
    End If
  End If
  '
  ' Read the private key file.
  '
  If Not (ReadFile(App.Path & "\" & sKeyName & ".pri", PrivateKey.bPrivateKey)) Then
    Call pRaiseError(Source, Routine, eImportingPrivateKey)
    Exit Sub
  End If
  '
  ' Import the key blob into the key container.
  '
  If Not (ImportPrivateKey(PrivateKey)) Then
    Call pRaiseError(Source, Routine, eImportingPrivateKey)
    Exit Sub
  End If
  '
  ' Hash the file.
  '
  If Not (HashFile(sFileName, hHash)) Then
    Call pRaiseError(Source, Routine, eGeneratingHash)
    Exit Sub
  End If
  '
  ' Create the signature.
  '
  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
  '
  ' Destroy the hash.
  '
  lResult = CryptDestroyHash(hHash)
  '
  ' Write the signature file.
  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)
  '//Construct readable signature string from byte array
  m_Signature = ""
  Dim i, v
  For i = LBound(bSig) To UBound(bSig)
    v = Hex(bSig(i))
    v = IIf(Len(v) = 1, "0" & v, v) '//Prefix zeroif only one char
    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
  '
  ' Verify a file with the specified public key.
  '
  Const Routine = "VerifyFile"
  '
  ' See if the provider is obtained.
  '
  If Not (IsProviderOpen) Then
    '
    ' Get the provider.
    '
    If Not (AcquireCryptoProvider) Then
      Call pRaiseError(Source, Routine, eProviderUnavailable)
      Exit Function
    End If
  End If
  '
  ' Read the public key file.
  '
  If Not (ReadFile(App.Path & "\" & sKeyName & ".pub", PublicKey.bPublicKey)) Then
    Call pRaiseError(Source, Routine, eImportingPublicKey)
    Exit Function
  End If
  '
  ' Import the key blob into key container.
  '
  If Not (ImportPublicKey(PublicKey)) Then
    Call pRaiseError(Source, Routine, eImportingPublicKey)
    Exit Function
  End If
  '
  ' Read the signature file.
  '
  lSigLen = 64
  If Not (ReadFile(sFileName & ".sgn", bSig)) Then
    Call pRaiseError(Source, Routine, eReadingSignatureFile)
    Exit Function
  End If
  '
  ' Hash the file.
  '
  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
  '
  ' Destroy the hash.
  '
  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
  '
  ' Hash a file in preparation for signing or verifying.
  '
  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 the file.
  '
  Open sFileName For Binary As lFileHandle
  '
  ' Progressively hash the file in chunks.
  '
  ReDim abFile(1 To C_CHUNK_SIZE)
  '
  ' Handle whole chunks.
  '
  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
  '
  ' Handle any leftover bytes.
  '
  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
  '
  ' Return a handle to the hash object.
  '
  lHash = hHash
  Exit Function

ErrorHandler:
  HashFile = False
End Function

Private Function AcquireCryptoProvider() As Boolean
  Dim lResult As Long
  '
  ' Get a handle to the base cryptographic provider.
  '
  '
  ' There is no good way to know if a key container
  ' exists other than to assume it does and test the
  ' return code.
  '
  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 unsuccessful, we need to create a container.
  '
  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
    '
    ' Clear the provider handle.
    '
    m_hProvider = 0
  Else
    AcquireCryptoProvider = True
  End If
End Function

Private Function IsProviderOpen() As Boolean
  '
  ' See if a valid crypto provider handle is held.
  '
  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
  '
  ' Export the public part of a key
  ' into the PublicKey variable.
  '
  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
  '
  ' Export the private part of a key
  ' into the PrivateKey variable
  '
  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
  '
  ' Import a private key into the key container.
  '
  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
  '
  ' Import a public key into the key container.
  '
  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
  '
  ' Writes a byte array out to a file.
  '
  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
  '
  ' Reads a byte array from a file.
  ' If Data is fixed, it must be of the expected size.
  '
  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


Submitted By : Nayan Patel  (Member Since : 5/26/2004 12:23:06 PM)

Job Description : He is the moderator of this site and currently working as an independent consultant. He works with VB.net/ASP.net, SQL Server and other MS technologies. He is MCSD.net, MCDBA and MCSE. In his free time he likes to watch funny movies and doing oil painting.
View all (893) submissions by this author  (Birth Date : 7/14/1981 )


Home   |  Comment   |  Contact Us   |  Privacy Policy   |  Terms & Conditions   |  BlogsZappySys

© 2008 BinaryWorld LLC. All rights reserved.