A Cryptographic Filter Box Class in Visual Basic

Steve Kirk
Microsoft Developer Network Technology Group

September 17, 1996

Click to open or copy the files in the VBCrypto sample application for this technical article.

Abstract

The Microsoft® Cryptography API (CryptoAPI for short) is a set of functions for maintaining security of data as it is transmitted over non-secure paths. This article demonstrates a cryptography class in Visual Basic® that encapsulates these functions in a Cryptography object. The Cryptography Filter Box object, CryptoFilterBox, brings a Component Object Model (COM) interface to applications that use encryption and digital signature techniques.

The Microsoft CryptoAPI is the foundation of the Microsoft Internet Security Framework and provides system-level certificate management and cryptography functions to applications developers under Windows NT® version 4.0 and Windows® 95 with Internet Explorer 3.0.

Interfacing with the Cryptographic Services Provider

The actual implementation of cryptographic services is done by the cryptographic services provider (CSP). Although a CSP is supplied with Windows NT 4.0 and Internet Explorer 3.0, many cryptographic companies are shipping or developing CSPs as software only or software/hardware combinations with a range of security levels, costs, and export restrictions. The architectural justification for an abstract interface that hides implementation details from the applications developer is strong for cryptographic services because:

Figure 1. CryptoAPI architecture

High-Level Processes

Because the details of cryptographic functions are left to the CSP, the application developer only needs to be concerned with two high-level processes: encryption and validation (signature/certification).

Encryption

Encryption actually changes the content of the message. The main advantage of encryption is that an encrypted message cannot be read without decryption so the message is only readable by those privileged with the matching CSP and password or key. The main disadvantage of encryption is the high computing cost of encrypting the whole message and the resulting time delay.

Validation

It is often more important to be able to validate a message for authenticity and integrity than to encrypt it. Signature validation and certificate validation authenticate the message source and verify that the message is not altered between the time that it is signed and the time that it is validated.

Signature Validation

The message and an optional password are inputs to the signature process, which generates a signature. The message, signature, and password are examined during validation, which will fail if any of the components have changed.

Certificate Validation

Certificate validation is similar to signature validation in that the process is used to authenticate the source of the message and to make sure that the message has not been altered. Certificate validation also identifies the source of the message via a certificate that includes the source's name and phone number. Certificate validation is offered as a protection against virus-carrying and malicious software being downloaded over the Internet, by providing identification of the source of the software.

The CryptoFilterBox Object

The CryptoFilterBox object has methods and properties that provide the high-level cryptographic processes.

Table 1. CryptoFilterBox Methods

Method Description
Encrypt Encrypt the contents of InBuffer into OutBuffer
Decrypt Decrypt the contents of InBuffer into OutBuffer
Sign Create an electronic signature based on PrivateKey and the contents of InBuffer and place in Signature
Validate Validate Signature based on InBuffer and PublicKey and place result in Valid

Table 2. CryptoFilterBox Properties

Property Description
InBuffer Text input buffer (used for Sign, Validate, Decrypt, and Encrypt)
OutBuffer Text output buffer (used for Decrypt and Encrypt)
Password Text password buffer (used for Sign, Validate, Decrypt, and Encrypt)
Signature Text signature buffer (used for Sign and Validate)
Status Integer
Invalid = 0
Valid = 1
Busy = 2

The CryptoFilterBox Class Module

Declarations Section of the Class Module

The following Declare Function statements create an interface between our Visual Basic class module and the cryptography functions in ADVAPI32.DLL. Use of the PRIVATE option hides these functions from everything outside the class module.

Private 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

Private 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

Private 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

Private Declare Function CryptDestroyHash Lib "advapi32.dll" (ByVal hHash _
   As Long) As Long

Private Declare Function CryptDestroyKey Lib "advapi32.dll" (ByVal hKey _
   As Long) As Long

Private Declare Function CryptEncrypt Lib "advapi32.dll" (ByVal hKey As _
   Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As _
   Long, pbData As Byte, pdwDataLen As Long, ByVal dwBufLen As Long) As Long

Private Declare Function CryptExportKey Lib "advapi32.dll" (ByVal hKey As _
   Long, ByVal hExpKey As Long, ByVal dwBlobType As Long, ByVal dwFlags As _
   Long, pbData As Byte, pdwDataLen As Long) As Long

Private Declare Function CryptGenKey Lib "advapi32.dll" ( _
   ByVal hProv As Long, ByVal Algid As Long, ByVal dwFlags As Long, phKey _
   As Long) As Long

Private Declare Function CryptGetProvParam Lib "advapi32.dll" ( _
   ByVal hProv As Long, ByVal dwParam As Long, pbData As Any, _
   pdwDataLen As Long, ByVal dwFlags As Long) As Long

Private Declare Function CryptGetUserKey Lib "advapi32.dll" ( _
   ByVal hProv As Long, ByVal dwKeySpec As Long, phUserKey As Long) As Long

Private Declare Function CryptHashData Lib "advapi32.dll" (ByVal hHash As _
   Long, pbData As Byte, ByVal dwDataLen As Long, ByVal dwFlags As Long) As Long

Private Declare Function CryptReleaseContext Lib "advapi32.dll" (ByVal hProv _
   As Long, ByVal dwFlags As Long) As Long

Private Declare Function CryptSignHashA Lib "advapi32.dll" (ByVal hHash _
   As Long, ByVal dwKeySpec As Long, ByVal sDescription As String, ByVal _
   dwFlags As Long, pbSignature As Byte, pdwSigLen As Long) As Long

Private Declare Function CryptVerifySignatureA Lib "advapi32.dll" (ByVal _
   hHash As Long, pbSignature As Byte, ByVal dwSigLen As Long, ByVal _
   hPubKey As Long, ByVal sDescription As String, ByVal dwFlags As Long) As Long

'API error function
Private Declare Function GetLastError Lib "kernel32" () As Long

'API memory functions
Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, _
   ByVal dwBytes As Long) As Long

Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long

Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long

Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As _
   Long

Private Declare Sub CpyMemValAdrFromRefAdr Lib "kernel32" Alias _
   "RtlMoveMemory" (ByVal hpvDest As Any, hpvSource As Any, ByVal _
   cbCopy As Long)

Private Declare Sub CpyMemRefAdrFromValAdr Lib "kernel32" Alias _
   "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Any, ByVal _
   cbCopy As Long)

Property Procedures

The property procedures handle assignment and retrieval of the object's properties.

Each property that is exposed has a Public Property Get procedure corresponding to the property name.

Public Property Get FileName() As String
'Return object's FileName property.
FileName = sFileName
End Property

Each property that is writeable has a Public Property Let or Public Property Set corresponding to the property name. Object type properties have a Public Property Set. Non-object type properties have a Public Property Let.

Public Property Let FileName(vNewValue As String)
'Handle assignment of object's FileName property.
sFileName = vNewValue
End Property

Object Methods

Public procedures in the class module are exposed as methods on objects instantiated from the CryptoFilterBox Class. Encrypt, Decrypt, Sign, and Verify are the methods that are exposed.

Encrypt Method

The Encrypt method is provided by Public Sub Encrypt() that encrypts InBuffer and places the result in OutBuffer.

Public Sub Encrypt()
'Encrypt InBuffer into OutBuffer.
Dim lHExchgKey As Long
Dim lHkeyBlobLen As Long
Dim lHCryptprov As Long
Dim lHHash As Long
Dim lHkey As Long
Dim lResult As Long
Dim sContainer As String
Dim sProvider As String
ReDim aKeyBlob(0) As Byte
ReDim aPassword(0) As Byte
ReDim aCryptBuffer(0) As Byte
Dim lCryptLength As Long
Dim lCryptBufLen As Long
Dim lCryptPoint As Long
Dim lPasswordPoint As Long
Dim lPasswordCount As Long

On Error GoTo ErrEncrypt

'Switch Status property.
lStatus = CFB_BUSY

'Get handle to the default provider.
sContainer = Chr$(0)
sProvider = Chr$(0)
sProvider = MS_DEF_PROV & Chr$(0)
If bApiNot(CryptAcquireContext(lHCryptprov, ByVal sContainer, ByVal _
  sProvider, PROV_RSA_FULL, 0)) Then
    MsgBox ("Error " & CStr(GetLastError) & " during CryptAcquireContext!")
    GoTo Done
End If

If sPassword = "" Then
    'Encrypt the file with a random session key.
    
    'Create a random session key.
    If bApiNot(CryptGenKey(lHCryptprov, ENCRYPT_ALGORITHM, CRYPT_EXPORTABLE, _
      lHkey)) Then
        MsgBox ("Error during CryptGenKey! " & CStr(GetLastError))
        GoTo Done
    End If
    
    'Get handle to key exchange public key.
    If bApiNot(CryptGetUserKey(lHCryptprov, AT_KEYEXCHANGE, lHExchgKey)) Then
        MsgBox ("Error during CryptGetUserKey! " & CStr(GetLastError))
        GoTo Done
    End If
    'Determine size of the key blob and allocate memory.
    'if(!CryptExportKey(hKey, hXchgKey, SIMPLEBLOB, 0, NULL, &dwKeyBlobLen)) {
    '    printf("Error %x computing blob length!\n", GetLastError());
    '    goto done;
        
    'Determine size of the key blob and allocate memory.
    If bApiNot(CryptExportKey(lHkey, lHExchgKey, SIMPLEBLOB, 0, 0, _
      lHkeyBlobLen)) Then
        MsgBox ("Error " & CStr(GetLastError) & " computing blob length!")
        GoTo Done
    End If
    
    ReDim aKeyBlob(lHkeyBlobLen)
    
    'Export session key into a simple key blob.
    If bApiNot(CryptExportKey(lHkey, lHExchgKey, SIMPLEBLOB, 0, aKeyBlob(0), _
       lHkeyBlobLen)) Then
        MsgBox ("Error " & CStr(GetLastError) & " during CryptExportKey!")
        GoTo Done
    End If
    
    'Release key exchange key handle.
    CryptDestroyKey (lHExchgKey)
    lHExchgKey = 0
    
    'Write size of key blob to destination file.
    'Write key blob to destination file.

Else
    'Encrypt the file with a session key derived from a password.

    'Create a hash object.
    If bApiNot(CryptCreateHash(lHCryptprov, CALG_MD5, 0, 0, lHHash)) Then
        MsgBox ("Error " & CStr(GetLastError) & " during CryptCreateHash!")
        GoTo Done
    End If
    
    lPasswordCount = Len(sPassword)
    If lPasswordCount > 0 Then
        ReDim aPassword(lPasswordCount - 1)
    End If
    lPasswordPoint = 1
    While lPasswordPoint <= lPasswordCount
        aPassword(lPasswordPoint - 1) = Asc(Mid$(sPassword, lPasswordPoint, 1))
        lPasswordPoint = lPasswordPoint + 1
    Wend
    
    'Hash in the password data.
    If bApiNot(CryptHashData(lHHash, aPassword(0), lPasswordCount, 0)) Then
        MsgBox ("Error " & CStr(GetLastError) & " during CryptHashData!")
        GoTo Done
    End If
    
    'Derive a session key from the hash object.
    If bApiNot(CryptDeriveKey(lHCryptprov, ENCRYPT_ALGORITHM, lHHash, 0,_
               lHkey)) Then
        MsgBox ("Error " & CStr(GetLastError) & " during CryptDeriveKey!")
        GoTo Done
    End If

   'Destroy the hash object.
   CryptDestroyHash (lHHash)
   lHHash = 0

End If

'ReDim aCryptBuffer(0) As Byte
'Dim lCryptLength As Long
'Dim lCryptBufLen As Long
'Dim lCryptPoint As Long

lCryptLength = Len(sInBuffer)
lCryptBufLen = lCryptLength * 2
ReDim aCryptBuffer(lCryptBufLen)
lCryptPoint = 1
While lCryptPoint <= lCryptLength
    aCryptBuffer(lCryptPoint - 1) = Asc(Mid$(sInBuffer, lCryptPoint, 1))
    lCryptPoint = lCryptPoint + 1
Wend

'Encrypt data
If bApiNot(CryptEncrypt(lHkey, 0, 1, 0, aCryptBuffer(0), lCryptLength, _
   lCryptBufLen)) Then
    MsgBox ("bytes required:" & CStr(lCryptLength))
    MsgBox ("Error " & CStr(GetLastError) & " during CryptEncrypt!")
    'GoTo Done
End If

sOutBuffer = ""
lCryptPoint = 0
While lCryptPoint <= lCryptBufLen
    If aCryptBuffer(lCryptPoint) = 0 Then
        lCryptPoint = lCryptBufLen
    Else
        sOutBuffer = sOutBuffer & Chr$(aCryptBuffer(lCryptPoint))
    End If
    lCryptPoint = lCryptPoint + 1
Wend
    
Done:

'Destroy session key.
    If (lHkey) Then lResult = CryptDestroyKey(lHkey)

'Release key exchange key handle.
    If lHExchgKey Then CryptDestroyKey (lHExchgKey)

'Destroy hash object.
    If lHHash Then CryptDestroyHash (lHHash)

'Release provider handle.
    If lHCryptprov Then lResult = CryptReleaseContext(lHCryptprov, 0)

'switch Status property
lStatus = CFB_READY

Exit Sub
ErrEncrypt:
    MsgBox ("ErrEncrypt " & Error$)
    GoTo Done
End Sub

Decrypt Method

The decrypt method does this, that, the other, and the other-other.

Public Sub Decrypt()
'Decrypt InBuffer into OutBuffer
Dim lHExchgKey As Long
Dim lHkeyBlobLen As Long
Dim lHCryptprov As Long
Dim lHHash As Long
Dim lHkey As Long
Dim lResult As Long
Dim sContainer As String
Dim sProvider As String
ReDim aKeyBlob(0) As Byte
ReDim aPassword(0) As Byte
ReDim aCryptBuffer(0) As Byte
Dim lCryptLength As Long
Dim lCryptBufLen As Long
Dim lCryptPoint As Long
Dim lPasswordPoint As Long
Dim lPasswordCount As Long
On Error GoTo ErrDecrypt
'switch Status property
lStatus = CFB_BUSY
        
'Get handle to the default provider.
sContainer = Chr$(0)
sProvider = Chr$(0)
sProvider = MS_DEF_PROV & Chr$(0)
If bApiNot(CryptAcquireContext(lHCryptprov, ByVal sContainer, ByVal _
   sProvider, PROV_RSA_FULL, 0)) Then
    MsgBox ("Error " & CStr(GetLastError) & " during CryptAcquireContext!")
    GoTo Done
End If

If sPassword = "" Then
'Decrypt the file with the saved session key.
'Read key blob length from source file and allocate memory.

    'Import key blob into CSP.
    'if(!CryptImportKey(hProv, pbKeyBlob, dwKeyBlobLen, 0, 0, &hKey)) {
    '    printf("Error %x during CryptImportKey!\n", GetLastError());
    '    goto done;
    '}

Else
    'Decrypt the file with a session key derived from a password.

    'Create a hash object.
    'if(!CryptCreateHash(hProv, CALG_MD5, 0, 0, &hHash)) {
    '    printf("Error %x during CryptCreateHash!\n", GetLastError());
    '    goto done;
    '}

    'Hash in the password data.
    'if(!CryptHashData(hHash, szPassword, strlen(szPassword), 0)) {
    '    printf("Error %x during CryptHashData!\n", GetLastError());
    '    goto done;
    '}

    'Derive a session key from the hash object.
    'if(!CryptDeriveKey(hProv, ENCRYPT_ALGORITHM, hHash, 0, &hKey)) {
    '    printf("Error %x during CryptDeriveKey!\n", GetLastError());
    '    goto done;
    '}

    'Destroy the hash object.
    'CryptDestroyHash(hHash);
    'hHash = 0;

End If
'    // Determine number of bytes to decrypt at a time. This must be a 
'    // multiple of ENCRYPT_BLOCK_SIZE.
'    dwBlockLen = 1000 - 1000 % ENCRYPT_BLOCK_SIZE;
'    dwBufferLen = dwBlockLen;''''
'
'    // Allocate memory.
'    if((pbBuffer = malloc(dwBufferLen)) == NULL) {
'    printf("Out of memory!\n");
'    goto done;
'    }
'
'    // Decrypt source file and write to destination file.
'    do {
'    // Read up to 'dwBlockLen' bytes from source file.
'    dwCount = fread(pbBuffer, 1, dwBlockLen, hSource);
'    if(ferror(hSource)) {
'        printf("Error reading Ciphertext!\n");
'            goto done;
'        }
'    eof = feof(hSource);
'
'        // Decrypt data
'        if(!CryptDecrypt(hKey, 0, eof, 0, pbBuffer, &dwCount)) {
'            printf("Error %x during CryptDecrypt!\n", GetLastError());
'            goto done;
'        }
'
'        // Write data to destination file.
'    fwrite(pbBuffer, 1, dwCount, hDestination);
'    if(ferror(hDestination)) {
'        printf("Error writing Plaintext!\n");
'            goto done;
'        }
'    } while(!feof(hSource));
'

Done:

'Destroy session key.
    If (lHkey) Then lResult = CryptDestroyKey(lHkey)

'Release key exchange key handle.
    If lHExchgKey Then CryptDestroyKey (lHExchgKey)

'Destroy hash object.
    If lHHash Then CryptDestroyHash (lHHash)

'Release provider handle.
    If lHCryptprov Then lResult = CryptReleaseContext(lHCryptprov, 0)

'switch Status property
lStatus = CFB_READY

Exit Sub

ErrDecrypt:
MsgBox ("ErrDecrypt " & Error$)
GoTo Done
End Sub

Sign Method

The Sign method is provided by Public Sub Sign(), which creates a signature for the combination of the contents of InBuffer and Password and places it in Signature.

Public Sub Sign()
'Create a signature for Inbuffer and place in Signature.
Dim sContainer As String
Dim sDescription As String
Dim sProvider As String
Dim lDataLen As Long
Dim lDataPoint As Long
Dim lHCryptprov As Long
Dim lHHash As Long
Dim lResult As Long
Dim lSignatureLen As Long
ReDim aByteData(0) As Byte

On Error GoTo ErrSign
    
'Switch Status property.
lStatus = CFB_BUSY

'Initialize Signature property.
sSignature = ""

'Get handle to the default provider.
sContainer = Chr$(0)
sProvider = MS_DEF_PROV & Chr$(0)
If bApiNot(CryptAcquireContext(lHCryptprov, ByVal sContainer, ByVal _
   sProvider, PROV_RSA_FULL, 0)) Then
    MsgBox ("Error " & CStr(GetLastError) & " during CryptAcquireContext!")
    GoTo ReleaseHandles:
End If

'Create a hash object.
If bApiNot(CryptCreateHash(lHCryptprov, CALG_MD5, 0, 0, lHHash)) Then
    MsgBox ("Error " & CStr(GetLastError) & " during CryptCreateHash!")
    GoTo ReleaseHandles:
End If

'Add data to hash object.
lDataLen = Len(sInBuffer)
If lDataLen > 0 Then
    ReDim aByteData(lDataLen - 1)
End If
lDataPoint = 1
While lDataPoint <= lDataLen
    aByteData(lDataPoint - 1) = Asc(Mid$(sInBuffer, lDataPoint, 1))
    lDataPoint = lDataPoint + 1
Wend

If bApiNot(CryptHashData(lHHash, aByteData(0), lDataLen, 0)) Then
    MsgBox ("Error " & CStr(GetLastError) & " during CryptHashData!")
    GoTo ReleaseHandles:
End If

'Sign hash object.
'Determine size of signature.
sDescription = Chr$(0)
lResult = CryptSignHashA(lHHash, AT_SIGNATURE, sDescription, 0, 0, _
   lSignatureLen)

If lSignatureLen <> 0 Then
    ReDim aByteData(lSignatureLen - 1)
Else
    ReDim aByteData(0)
End If

'Sign hash object (with signature key).
If bApiNot(CryptSignHashA(lHHash, AT_SIGNATURE, sDescription, 0, _
   aByteData(0), lSignatureLen)) Then
    MsgBox ("Error " & CStr(GetLastError()) & " during CryptSignHash")
    GoTo ReleaseHandles:
End If

lDataPoint = 0
While lDataPoint <= lSignatureLen - 1
    sSignature = sSignature & Chr$(aByteData(lDataPoint))
    lDataPoint = lDataPoint + 1
Wend

ReleaseHandles:
'Destroy hash object.
If lHHash Then lResult = CryptDestroyHash(lHHash)
'Release provider handle.
If lHCryptprov Then lResult = CryptReleaseContext(lHCryptprov, 0)

'switch Status property
lStatus = CFB_READY

Exit Sub
ErrSign:
MsgBox ("ErrSign " & Error$)
GoTo ReleaseHandles
End Sub

ValidateMethod

The Validate method is provided by Public Sub Validate(), which validates the combination of InBuffer, Password, and Signature, and updates Status with the result.

Public Sub Validate()
'Validate InBuffer with Signature and assign Status with result.
Dim bValid As Boolean
Dim sContainer As String
Dim sDescription As String
Dim sProvider As String
Dim lDataLen As Long
Dim lDataPoint As Long
Dim lHCryptprov As Long
Dim lHHash As Long
Dim lResult As Long
Dim lSignatureLen As Long
Dim lHCryptKey As Long
ReDim aByteData(0) As Byte

On Error GoTo ErrValidate

'switch Status property
lStatus = CFB_BUSY

'Initialize internal valid flag.
bValid = True

'Get handle to the default provider.
sContainer = Chr$(0)
sProvider = MS_DEF_PROV & Chr$(0)
If bApiNot(CryptAcquireContext(lHCryptprov, ByVal sContainer, ByVal _
   sProvider, PROV_RSA_FULL, 0)) Then
    bValid = False
    MsgBox ("Error " & CStr(GetLastError) & " during CryptAcquireContext!")
    GoTo ReleaseHandles:
End If

'Create a hash object.
If bApiNot(CryptCreateHash(lHCryptprov, CALG_MD5, 0, 0, lHHash)) Then
    bValid = False
    MsgBox ("Error " & CStr(GetLastError) & " during CryptCreateHash!")
    GoTo ReleaseHandles:
End If

'Add data to hash object.
lDataLen = Len(sInBuffer)
If lDataLen > 0 Then
    ReDim aByteData(lDataLen - 1)
End If
lDataPoint = 1
While lDataPoint <= lDataLen
    aByteData(lDataPoint - 1) = Asc(Mid$(sInBuffer, lDataPoint, 1))
    lDataPoint = lDataPoint + 1
Wend

If bApiNot(CryptHashData(lHHash, aByteData(0), lDataLen, 0)) Then
    bValid = False
    MsgBox ("Error " & CStr(GetLastError) & " during CryptHashData!")
    GoTo ReleaseHandles:
End If

'Determine size of signature.
'sDescription = Chr$(0)
'lResult = CryptSignHashA(lHHash, AT_SIGNATURE, sDescription, 0, 0, _
   lSignatureLen)

'Get handle to signature key.
If bApiNot(CryptGetUserKey(lHCryptprov, AT_SIGNATURE, lHCryptKey)) Then
    bValid = False
    MsgBox ("Error " & CStr(GetLastError) & " during CryptGetUserKey!")
    GoTo ReleaseHandles:
End If

lSignatureLen = Len(sSignature)
If lSignatureLen > 0 Then
    ReDim aByteData(lSignatureLen - 1)
Else
    ReDim aButeData(0)
End If
lDataPoint = 1
While lDataPoint <= lSignatureLen
    aByteData(lDataPoint - 1) = Asc(Mid$(sSignature, lDataPoint, 1))
    lDataPoint = lDataPoint + 1
Wend


'Verify signature.
If bApiNot(CryptVerifySignatureA(lHHash, aByteData(0), lSignatureLen, _
   lHCryptKey, sDescription, 0)) Then

    If GetLastError = NTE_BAD_SIGNATURE Then
        bValid = False
        GoTo ReleaseHandles:
    Else
        bValid = False
        MsgBox ("Error " & CStr(GetLastError) & " during CryptVerifySignature!")
        GoTo ReleaseHandles:
    End If

End If


ReleaseHandles:
'Release signature key.
If lHCryptKey Then lResult = CryptDestroyKey(lHCryptKey)
'Destroy hash object.
If lHHash Then lResult = CryptDestroyHash(lHHash)
'Release provider handle.
If lHCryptprov Then lResult = CryptReleaseContext(lHCryptprov, 0)

Select Case bValid
    Case True
        lStatus = CFB_VALID
    Case Else
        lStatus = CFB_READY
End Select

Exit Sub

ErrValidate:
MsgBox ("ErrValidate " & Error$)
bValid = False
GoTo ReleaseHandles

End Sub

The VBCrypto Sample Application

The VBCrypto sample application is built around the CryptoFilterBox class. It has text boxes for each object property, a list box of methods, and a Go button. Clicking the Go button assigns the object properties from the text boxes and executes the method selected in the method list. The text boxes are then updated from the object properties. The status property is read only so that its text box is not enabled.

Create the Sample Application

  1. Create a new project.

  2. Add the file CRYPTO.CLS.

  3. Remove the default form1 from the project.

  4. Add the file CRYPTO.FRM.

  5. Set the project startup option to frm1.

  6. Press F5 to run.

The CryptoFilterBox object is instantiated when the form is loaded.

Private Sub Form_Load()
'Instantiate CryptoFilterBox object and populate the method list.
Dim lResult As Long
On Error GoTo ErrForm_Load

Set objCryptoFilterBox = New clsCryptoFilterBox

'Populate the method list.
lstMethod.AddItem "Decrypt"
lstMethod.AddItem "Encrypt"
lstMethod.AddItem "Sign"
lstMethod.AddItem "Validate"

Exit Sub
ErrForm_Load:
MsgBox ("ErrForm_Load " & Error$)
Exit Sub
End Sub

The Go Button assigns CryptoFilterBox properties from the text boxes, runs the selected method, and updates the text boxes.

Private Sub cmbGo_Click()
'Assign CryptoFilterBox properties, call the selected method, 
' and update text boxes.
 On Error GoTo ErrcmbGo_Click
 Select Case lstMethod.Text
   Case "Decrypt"
      objCryptoFilterBox.InBuffer = txtInput.Text
      objCryptoFilterBox.Password = txtPassword.Text
      objCryptoFilterBox.Decrypt
      txtOutput.Text = objCryptoFilterBox.OutBuffer
   Case "Encrypt"
      objCryptoFilterBox.InBuffer = txtInput.Text
      objCryptoFilterBox.Password = txtPassword.Text
      objCryptoFilterBox.Encrypt
      txtOutput.Text = objCryptoFilterBox.OutBuffer
   Case "Sign"
      objCryptoFilterBox.InBuffer = txtInput.Text
      objCryptoFilterBox.Sign
      txtSignature.Text = objCryptoFilterBox.Signature
   Case "Validate"
      objCryptoFilterBox.InBuffer = txtInput.Text
      objCryptoFilterBox.Signature = txtSignature.Text
      objCryptoFilterBox.Validate
      Select Case objCryptoFilterBox.Status
         Case CFB_VALID
            MsgBox ("Signature is valid")
         Case Else
            MsgBox ("Invalid signature")
      End Select
   Case ""
      MsgBox ("Method not selected")
   Case Else
      MsgBox ("Unknown method selected.")
End Select
Exit Sub

ErrcmbGo_Click:
    MsgBox ("ErrcmbGo_Click " & Error$)
    Resume
End Sub

Cryptography Demonstrations

Encrypt a Text String

  1. Enter This is a secret in input box.

  2. Select Encrypt from the methods list and click Go.

  3. The encrypted message fills the output box.

Decrypt a Text String

  1. Copy the encrypted message from the output box to the input box.

  2. Select Decrypt from the methods list and click Go.

  3. This is a secret is displayed in the output box.

Sign a Text String and Validate the Signature

  1. Enter The price is ten dollars in the input box.

  2. Enter a password in the input box.

  3. Select Sign from the methods list and click the Go button.

Validate the Input, Password, and Signature

  1. Change the input box, the password, or the signature.

  2. Select Validate from the methods list and click the Go button.

  3. Status becomes Invalid.

Conclusion

The CryptoFilterBox server provides data encryption and signing functionality to applications written in any language that can use a COM server with just a few lines of code. Although this article has covered only a small part of the Microsoft Internet Security Framework, and has omitted many issues that must be addressed before employing a security system, it has demonstrated the fundamental techniques required for secure communication and commerce on public networks.

Additional References

Application Programmer's Guide and Reference, CryptoAPI Version 2.0 Beta (Sept. 10, 1996 Preliminary).

Robert Coleridge, "The Cryptography API, or "How to Keep a Secret." (MSDN Library, Technical Articles)

Microsoft Internet Security Framework at http://www.microsoft.com/intdev/security/.