Encryption in VBA using the Microsoft NG Cryptography (CNG) API

Gustav BrockMVP
CERTIFIED EXPERT
Published:
Updated:
Edited by: David Draper
This article series will show you how to utilise the Next Generation Cryptography (CNG) API from Microsoft for modern hashing and encrypting/decrypting in VBA.
In this part: Encryption.

Introduction

Purpose of these articles

The Microsoft CNG APIs constitute a collection of more than a dozen APIs that handle all the aspects and supporting functions to calculate hash values and perform encryption and decryption meeting modern high demands and standards.

This series details one method to implement these features in applications supported by VBA (Visual Basic for Applications), for example Microsoft Access and Microsoft Excel.

The theory for and the clever mathematics behind hashing and encryption will not be touched; this is covered massively in books and articles published over a long period of time by dedicated experts. A search with Bing or Google will return a long list of resources to study.


Sections

The series has been split in five parts. This allows you to skip parts you are either familiar with or wish to implement later if at all.

  1. Utilise Microsoft's Next Generation Cryptography (CNG) API in VBA
  2. Hashing in VBA using the Microsoft NG Cryptography (CNG) API
  3. Encryption in VBA using the Microsoft NG Cryptography (CNG) API
  4. Using binary storage to serve the Microsoft NG Cryptography (CNG) API
  5. Storing passwords in VBA using the Microsoft NG Cryptography (CNG) API

The three first deal, as stated, with hashing and encrypting/decrypting based on the CNG API, while the forth explains how to combine these techniques with the little known feature of Access, storing binary data, as this in many cases will represent the optimal storage method for hashed or encrypted data. The last demonstrates how to save and verify passwords totally safe using these tools.


Part 3. Encryption

Basic usage

Encryption, in this context, is the process of creating a scrambled but reversible code that identifies the input. To encrypt the input, a key is used.

Note that, when encrypting, the generated code is unique, as different code can and will be generated from identical input/key pairs, thus the generated code will appear random.

However, the generated code is not random. By providing the key used for the encryption, the code can be reversed to recreate the original input.

The typical usage of encryption is for storing or transporting sensitive data in a format unreadable for anyone not having the key to decrypt the data. When storing or transporting the data, the encrypted data is used. To read the data, the key used to encrypt the data must be known. Having this, the encrypted data can be decrypted to rebuild the original plain data.


Encryption methods

The mathematical method used to encrypt and decrypted a string is called an algorithm. These have evolved over time, and the oldest are now deprecated, though still in use.

The single algorithm offered here is AES (Advanced Encryption Standard) as it is fast and also considered the best. Also, it is very widely used.

The byte length generated by this algorithm has a minimum of 48 approaching twice the length of the input for large inputs. Some examples are:


Input Length Byte Length
4 48
36 128
100 256
228 512
1024 2096
4096 8240


Thus, pay attention to the possible length of text to encrypt.


Working with encryption

Note, that the lengths listed above for the AES encryption algorithm are the lengths of the generated byte arrays. As these bytes can take many other values than those for normal ASCII characters - even control characters and other non-printable characters - the byte array must for many practical purposes be converted to something printable.

The simple method would be to convert to the hexadecimal representation of the bytes, for example (for a snippet of four bytes of the data, where character <tab> is the third):


aX<tab>! -> 6158092D

but that consumes twice as many characters, thus an input string of only 100 characters encrypted using AES would have a length of 256 x 2 = 512 characters - not very efficient.

A better method is to use Base64 encoding. If offers the same - a printable and portable string of ASCII characters - but takes only 50% (or less) additional space compared to the byte lengths listed above:


Input Length Base64 Length
4 88
36 172
68 256
100 344
228 684
1024 2796
4096 10988


Again, pay attention to the possible length of text to encrypt.

For example, the maximum length of a Short Text field in Access is 255, thus it can't hold the encrypted and Base64 encoded value of a text value of 68 characters; to use this field type, the plain text must be kept at only 67 characters or shorter.

To conclude: With an overhead of about 300%, the encrypted values can be treated as normal plain text.


Encrypting text

A set of functions is used to encrypt the input and return the encrypted data:


Encrypt
    EncryptData
        HashData
            CngHash
        RandomData
            CngRandom
        CngEncrypt
    ByteBase64

The top function, Encrypt, the one that creates a Base64 encoded encrypted text value from a passed text using a specific key, contains less than a handful of code lines:


' Encrypt a string using AES and a key.
' Return the encrypted text as a Base64 encoded string.
'
' Example:
'   Text = "Careful with that axe, Eugene!"
'   Key = "Have a Cigar"
'   EncryptedText = Encrypt(Text, Key)
'   EncryptedText -> 6uLffExuQmAi/oI3AzCLZTRZfv1XL6kl01z4hJ5y1MWXHgFACj3XhvboF/rNU89znrX1d5btmCbRK9dAjjjlKxTDJMImQr3YGiscMDvn/YtjKmc8nFuR65IU9vEn4a0Rca72k55cZXjKzOGMpbZ/6A==
'
' Note: Length of the encrypted string can be predetermined by the function EncryptedTextLength:
'   ' Use Text from example above.
'   Length = EncryptedTextLength(Len(Text))
'   Length -> 152
'
' Original code by Erik A, 2019.
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function Encrypt( _
    ByVal Text As String, _
    ByVal Key As String) _
    As String

    Dim EncryptedData()     As Byte
    Dim EncryptedText       As String

    If Text = "" Or Key = "" Then
        ' Nothing to do.
    Else
        If EncryptData((Text), (Key), EncryptedData) = True Then
            ' Success.
            ' Convert the byte array to a Base64 encoded string.
            EncryptedText = ByteBase64(EncryptedData)
        Else
            ' Missing Text or Key.
        End If
    End If

    Encrypt = EncryptedText

End Function

The usage is extremely simple:


Dim Text    As String
Dim Key     As String
Dim Value   As String

Text = "Get your filthy hands off my desert."
Key = "Absolutely Curtains"
Value = Encrypt(Text, Key)

Debug.Print "Plain text:", Text
Debug.Print "Encrypted:", Value

' Output:
' Plain text:   Get your filthy hands off my desert.
' Encrypted:    VrsKJl+J7giIvRGActl9BYl0sZLn3sliMF62vMjRsVev32ALx08EnrXmt57lWR+DvsDsPT3l0jwJvmBTSyeaeQBfw9TsqVIdanDQ2Cnx5QhyWndqSAJKz8DEatWHBH9277O2YI3cVmku/Pzb0R2o8srbc7dt9cBuxPQ4zQ+vLx8=

The few lines of code in the function is possible, because it pulls data from the second level function, EncryptData, also taking a second argument for the key.

The third argument, however, is where the encrypted data will be returned, while the function itself only returns a value, True/False, to tell, if the process was successful or not:


' Encrypt a byte array using AES encryption and a KeyData passed as another byte array.
' Return by reference the encrypted data as a byte array.
' Return True if success.
'
' To be called from function Encrypt.
'
' NOTE:
'   Even when passed the same arguments (TextData and KeyData), the returned and
'   encrypted data will be unique for every call.
'
' Original code by Erik A, 2019.
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function EncryptData( _
    ByRef TextData() As Byte, _
    ByRef KeyData() As Byte, _
    ByRef EncryptedData() As Byte) _
    As Boolean

    Const SizeLength        As Long = 4
    Const IVectorLength     As Long = 16
    Const SecretLength      As Long = 16

    Dim KeyHash()           As Byte
    Dim InputHash()         As Byte
    Dim Data()              As Byte
    Dim DataLength          As Long
    Dim IVector()           As Byte
    Dim InputHashLength     As Long
    Dim Result              As Boolean

    ' Get SHA1 hash of the data and of the KeyData.
    InputHash = HashData(TextData, bcSha1)
    InputHashLength = UBound(InputHash) + 1
    KeyHash = HashData(KeyData, bcSha1)
    ReDim Preserve KeyHash(0 To SecretLength)

    If StrPtr(InputHash) = 0 Or StrPtr(KeyHash) = 0 Then
        ' Either no data or no KeyData. Nothing to do.
    Else
        DataLength = UBound(TextData) - LBound(TextData) + 1

        ' Data size is: Long (4 bytes) + DataLength + SHA1 (20 bytes)
        ReDim Data(0 To SizeLength + DataLength + InputHashLength - 1)
        ' Append length (in bytes) to start of array.
        RtlMoveMemory Data(0), DataLength, SizeLength
        ' Append data.
        RtlMoveMemory Data(SizeLength), TextData(LBound(TextData)), DataLength
        ' Append hash of the data.
        RtlMoveMemory Data(SizeLength + DataLength), InputHash(0), InputHashLength

        ' Generate IVector.
        IVector = RandomData(IVectorLength)
        ' Encrypt data.
        EncryptedData = CngEncrypt( _
            VarPtr(Data(0)), SizeLength + DataLength + InputHashLength, _
            VarPtr(IVector(0)), IVectorLength, _
            VarPtr(KeyHash(0)), SecretLength)
        ' Deallocate copy made to encrypt.
        Erase Data
        ' Extend encrypted data to append IVector.
        ReDim Preserve EncryptedData(LBound(EncryptedData) To UBound(EncryptedData) + IVectorLength)
        ' Append IVector.
        RtlMoveMemory EncryptedData(UBound(EncryptedData) - LBound(EncryptedData) + 1 - IVectorLength), IVector(0), IVectorLength
        Result = True
    End If

    EncryptData = Result

End Function

The important feature of the function is, that both input and output are byte arrays. However, you may have noticed, that function Encrypt above doesn't pass two byte arrays, but plain text for Text and Key:


EncryptData((Text), (Key), EncryptedData)

That's because you can assign a text variable directly to a byte array; no conversion is needed.

The output is, in function Encrypt, held in the byte array EncryptedData, which then is passed to the function ByteBase64, which converts the byte array to Base64 encoded text. Though quite convoluted, that function is trivial and won't be discussed here.

Function EncryptData also contains relatively few code lines. Essentially, it only prepares the input data and wraps the function, that does "the real work", CngEncrypt, which makes no less than nine calls to the CNG API to create the encrypted data.

The details of these calls will not be discussed here. However, each step is commented in-line, and links to the documentation at Microsoft are included, should you wish to study this further.

The usage of this function is also very straight:


Dim Text            As String
Dim Key             As String
Dim EncryptedData() As Byte
Dim Success         As Boolean

Text = "Get your filthy hands off my desert."
Key = "Absolutely Curtains"
Success = EncryptData((Text), (Key), EncryptedData)
If Success Then
    ' Convert byte array to unicode.
    Debug.Print StrConv(EncryptedData, vbUnicode)
End If

' Partial output if success.
' Ém9dL‡ðeE¤æÂÒ^¾ý¿g-C2jÊO²t‰Éró 5ÈB<.ËD@UÙ½ <snip>

Part 4 of this series will demonstrate some applications for this function.


Decrypting text

A set of functions is used to decrypt the input and return the decrypted data:


Decrypt
    Base64Bytes
    DecryptData
        HashData
            CngHash
        CngDecrypt
        CngHash

The top function, Decrypt, the one that reads a Base64 encoded encrypted text value from a passed text and decrypts it using a specific key, contains less than a handful of code lines:


' Decrypt a Base64 encoded string encrypted using AES and a key.
' Return the decrypted and decoded text as a plain string.
'
' Example:
'   EncryptedText = "6uLffExuQmAi/oI3AzCLZTRZfv1XL6kl01z4hJ5y1MWXHgFACj3XhvboF/rNU89znrX1d5btmCbRK9dAjjjlKxTDJMImQr3YGiscMDvn/YtjKmc8nFuR65IU9vEn4a0Rca72k55cZXjKzOGMpbZ/6A=="
'   Key = "Have a Cigar"
'   Text = Decrypt(EncryptedText, Key)
'   Text -> Careful with that axe, Eugene!
'
' Original code by Erik A, 2019.
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function Decrypt( _
    ByVal EncryptedText As String, _
    ByVal Key As String) _
    As String

    Dim EncryptedData()     As Byte
    Dim TextData()          As Byte
    
    If EncryptedText = "" Or Key = "" Then
        ' Nothing to do.
    Else
        ' Convert the Base64 encoded string to a byte array.
        EncryptedData = Base64Bytes(EncryptedText)
        If DecryptData(EncryptedData, (Key), TextData) = True Then
            ' Success.
        Else
            ' Invalid EncryptedData or wrong key.
        End If
    End If
    
    Decrypt = TextData

End Function

The usage is extremely simple:


Dim Text    As String
Dim Key     As String
Dim Value   As String

Text = _
    "VrsKJl+J7giIvRGActl9BYl0sZLn3sliMF62vMjRsVev32ALx08EnrXmt57lWR" & _ 
    "+DvsDsPT3l0jwJvmBTSyeaeQBfw9TsqVIdanDQ2Cnx5QhyWndqSAJKz8DEatWH" & _
    "BH9277O2YI3cVmku/Pzb0R2o8srbc7dt9cBuxPQ4zQ+vLx8="
Key = "Absolutely Curtains"
Value = Decrypt(Text, Key)

Debug.Print "Encrypted:", Text
Debug.Print "Plain text:", Value

' Output:
' Encrypted:    VrsKJl+J7giIvRGActl9BYl0sZLn3sliMF62vMjRsVev32ALx08EnrXmt57lWR+DvsDsPT3l0jwJvmBTSyeaeQBfw9TsqVIdanDQ2Cnx5QhyWndqSAJKz8DEatWHBH9277O2YI3cVmku/Pzb0R2o8srbc7dt9cBuxPQ4zQ+vLx8=
' Plain text:   Get your filthy hands off my desert.


Supplemental functions

As you may have noticed, two enums are used for specifying the encryption algorithm and the random algorithm:


' Allowed BCrypt random algorithms.
Public Enum BcRandomAlgorithm
    [_First] = 1
    bcRng = 1
    bcFips186DsaRng = 2
    [_Last] = 2
End Enum

' Utilised BCrypt encryption algorithms.
Public Enum BcEncryptionAlgorithm
    [_First] = 1
    bcAes = 1
    [_Last] = 1
End Enum

This is to validate input and make it easy to always supply the rightly spelled and uppercased random and encryption algorithm names to function CngEncrypt.

Functions BcryptRandomAlgorithm and BcryptEncryptionAlgorithm serve this purpose:


' Return the literal random algorithm name determined by
' the passed value of enum BcRandomAlgorithm.
'
' To be called from functions CngRandom and IsBcryptRandomAlgorithm.
'
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function BcryptRandomAlgorithm( _
    ByVal BcryptRandomAlgorithmId As BcRandomAlgorithm) _
    As String
    
    Dim RandomAlgorithmName     As String
    
    ' Note: RandomAlgorithmName must be in UPPERCASE.
    Select Case BcryptRandomAlgorithmId
        Case BcRandomAlgorithm.bcRng
            RandomAlgorithmName = "RNG"
        Case BcRandomAlgorithm.bcFips186DsaRng
            RandomAlgorithmName = "FIPS186DSARNG"
    End Select
    
    BcryptRandomAlgorithm = RandomAlgorithmName

End Function
' Return the literal encryption algorithm name determined by
' the passed value of enum BcEncryptionAlgorithm.
'
' To be called from functions CngEncrypt and CngDecrypt.
'
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function BcryptEncryptionAlgorithm( _
    ByVal BcryptEncryptionAlgorithmId As BcEncryptionAlgorithm) _
    As String
    
    Dim EncryptionAlgorithmName As String
    
    ' Note: EncryptionAlgorithmName must be in UPPERCASE.
    Select Case BcryptEncryptionAlgorithmId
        Case BcEncryptionAlgorithm.bcAes
            EncryptionAlgorithmName = "AES"
    End Select
    
    BcryptEncryptionAlgorithm = EncryptionAlgorithmName

End Function

Likewise, functions, IsBcryptRandomAlgorithm and IsBcryptRandomAlgorithmId, are included to verify/validate either a literal algorithm name or an enum value for the random algorithm name:


' Return True if the passed text value represents a value of
' enum BcRandomAlgorithm.
' Note: To validate, RandomAlgorithm must be in UPPERCASE.
'
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function IsBcryptRandomAlgorithm( _
    ByVal RandomAlgorithm As String) _
    As Boolean
    
    Dim Index           As BcRandomAlgorithm
    Dim Result          As Boolean
    
    For Index = BcRandomAlgorithm.[_First] To BcRandomAlgorithm.[_Last]
        If BcryptRandomAlgorithm(Index) = RandomAlgorithm Then
            Result = True
            Exit For
        End If
    Next
    
    IsBcryptRandomAlgorithm = Result
    
End Function
' Return True if the passed value of enum BcRandomAlgorithm
' is valid.
'
' To be called from function CngRandom.
'
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function IsBcryptRandomAlgorithmId( _
    ByVal RandomAlgorithmId As BcRandomAlgorithm) _
    As Boolean
    
    Dim Result          As Boolean
    
    If BcRandomAlgorithm.[_First] <= RandomAlgorithmId And RandomAlgorithmId <= BcRandomAlgorithm.[_Last] Then
        Result = True
    End If
    
    IsBcryptRandomAlgorithmId = Result
    
End Function

Similar functions for the encryption algorithm are left out, as only one algorithm (AES) is in use, and therefor is used by default.

Finally, to determine the length of an encrypted value - either as a byte array or a Base64 encoded string - without actually encrypting something, two simple functions, EncryptedByteLength and EncryptedTextLength, will return those values:


' Return the byte length of a string of the length DecryptedTextLength
' encrypted with function EncryptData.
'
' To be called from function FitByteField.
'
' Example:
'   Text = "Careful with that axe, Eugene!"
'   DecryptedTextLength = Len(Text)     ' = 30
'   Length = EncryptedByteLength(DecryptedTextLength)
'   Length -> 112
'
' Example data:
'
' Length plain  Length encrypted
'   0             0
'   1            48
'   4            64
'  12            80
'  20            96
'  28           112
'  36           128
'  44           144
'  52           160
'  60           176
'  68           192
'  76           208
'  84           224
'  92           240
' 100           256
' 108           272
' 116           288
' 124           304
' 132           320
' 140           336
' 148           352
' 156           368
' 164           384
' 172           400
' 180           416
' 188           432
' 196           448
' 204           464
' 212           480
' 220           496
' 227           496
' 227 characters is the largest string to encrypt, if the
' encrypted byte array must fit a Binary field of Access.
' 228           512
'
' 2022-02-18. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function EncryptedByteLength( _
    ByVal DecryptedTextLength As Long) _
    As Long
    
    Dim Length  As Long

    If DecryptedTextLength > 0 Then
        Length = 48 + ((DecryptedTextLength + 4) \ 8) * 16
    End If
    
    EncryptedByteLength = Length

End Function
' Return the length of a string encrypted and encoded with function Encrypt.
'
' To be called from function FitTextField.
'
' Example:
'   Text = "Careful with that axe, Eugene!"
'   DecryptedTextLength = Len(Text)     ' = 30
'   Length = EncryptedTextLength(DecryptedTextLength)
'   Length -> 152
'
' Example data:
'
' Length plain  Length encrypted
'   0             0
'   1            64
'   4            88
'  12           108
'  20           128
'  28           152
'  36           172
'  44           192
'  52           216
'  60           236
'  67           236
' 67 characters is the largest string to encrypt, if the
' encrypted string must fit a Short Text field of Access.
'  68           256
'  76           280
'  84           300
'  92           320
' 100           344
' 108           364
' 116           384
' 124           408
' 132           428
' 140           448
' 148           472
' 156           492
' 164           512
' 172           536
' 180           556
' 188           576
' 196           600
' 204           620
' 212           640
' 220           664
' 228           684
' 236           704
' 244           728
' 252           748
' The maximum length of an Access text field is 255 characters.
' 255           748
' 260           768
'
' 2021-10-24. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function EncryptedTextLength( _
    ByVal DecryptedTextLength As Long) _
    As Long
    
    Dim Length      As Long
    
    If DecryptedTextLength > 0 Then
        Length = 64 - Int(-(DecryptedTextLength - 3) / 8) * 20 - Int(-(DecryptedTextLength - 3) / 24) * 4
    End If
    
    EncryptedTextLength = Length

End Function

These functions can come in handy for code that creates or alters table design where fields for encrypted values will be included.


Conclusion

A full set of functions for encryption meeting modern standards has been presented. The functions cover all common needs for encryption in typical applications written in VBA.


Code and download

The full code and demo are attached for Microsoft Access and Excel 365.

Microsoft Office 365: CngCrypt.zip

At any time, full and updated code is available on GitHub VBA.Cryptography
I hope you found this article useful. You are encouraged to ask questions, report any bugs or make any other comments about it below.

Note: If you need further "Support" about this topic, please consider using the Ask a Question feature of Experts Exchange. I monitor questions asked and would be pleased to provide any additional support required in questions asked in this manner, along with other EE experts.

Please do not forget to press the "Thumbs Up" button if you think this article was helpful and valuable for EE members.

  
0
5,725 Views
Gustav BrockMVP
CERTIFIED EXPERT

Comments (0)

Have a question about something in this article? You can receive help directly from the article author. Sign up for a free trial to get started.