Nothing like a good old fashioned configuration file to make you feel like you’re programming in 1995. But you know what? Sometimes you just need to do it. And it still amazes me how many off-the-shelf applications still rely on INI files to store their settings (I’m looking at you, LotusNotes!).
Personally, I like INI files. I find them easy to work with and easy to deploy. And, of course, it doesn’t hurt that you can read and write to them using VBA.
If you Google reading or writing to INI files using VBA, you’ll get a bunch of different results, all pointing you in the same basic direction. Specifically, you need to use two different Windows APIs in order to do this “GetPrivateProfileString”, and “WritePrivateProfileString”. One reads from an INI file, the other writes to it. I’m going to assume you can figure out which is which.
Invariably, the examples you uncover on Google show that these routines are always separate. One routine fo reading, one for writing.
I hate that.
I like my code as concise as possible while still being as modular as possible. What do I mean by that? I mean that I want a routine (or function in this case) that I can call from another point in the code and choose whether I’m reading or writing to the configuration file. And I want the routine portable enough so I can drop it into any application I want and not have to worry about customizing it too terribly much.
And so, I give you the code below, commented for your pleasure:
'*******************************************************************************
' Declaration for Reading and Wrting to an INI file.
'*******************************************************************************
'++++++++++++++++++++++++++++++++++++++++++++++++++++
' API Functions for Reading and Writing to INI File
'++++++++++++++++++++++++++++++++++++++++++++++++++++
' Declare for reading INI files.
Private Declare Function GetPrivateProfileString Lib "kernel32" _
Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, _
ByVal lpKeyName As Any, _
ByVal lpDefault As String, _
ByVal lpReturnedString As String, _
ByVal nSize As Long, _
ByVal lpFileName As String)As Long
' Declare for writing INI files.
Private Declare Function WritePrivateProfileString Lib "kernel32" _
Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, _
ByVal lpKeyName As Any, _
ByVal lpString As Any, _
ByVal lpFileName As String)As Long
'++++++++++++++++++++++++++++++++++++++++++++++++++++
' Enumeration for sManageSectionEntry funtion
'++++++++++++++++++++++++++++++++++++++++++++++++++++
Enum iniAction
iniRead = 1
iniWrite = 2
End Enum
'*******************************************************************************
' End INI file declaratin Section.
'*******************************************************************************
Function sManageSectionEntry(inAction As iniAction, _
sSection As String, _
sKey As String, _
sIniFile As String, _
Optional sValue As String)As String
'*******************************************************************************
' Description: This reads an INI file section/key combination and
' returns the read value as a string.
'
' Author: Scott Lyerly
' Contact: scott.c.lyerly@gmail.com
'
' Notes: Requires "Private Declare Function GetPrivateProfileString" and
' "WritePrivateProfileString" to be added in the declarations
' at the top of the module.
'
' Name: Date: Init: Modification:
' sManageSectionEntry 26-Nov-2013 SCL Original development
'
' Arguments: inAction The action to take in teh funciton, reading or writing to
' to the INI file. Uses the enumeration iniAction in the
' declarations section.
' sSection The seciton of the INI file to search
' sKey The key of the INI from which to retrieve a value
' sIniFile The name and directory location of the INI file
' sValue The value to be written to the INI file (if writing - optional)
'
' Returns: string The return string is one of three things:
' 1) The value being sought from the INI file.
' 2) The value being written to the INI file (should match
' the sValue parameter).
' 3) The word "Error". This can be changed to whatever makes
' the most sense to the programmer using it.
'*******************************************************************************
On Error GoTo Err_ManageSectionEntry
' Variable declarations.
Dim sRetBuf As String
Dim iLenBuf As Integer
Dim sFileName As String
Dim sReturnValue As String
Dim lRetVal As Long
' Based on the inAction parameter, take action.
If inAction = iniRead Then ' If reading from the INI file.
' Set the return buffer to by 256 spaces. This should be enough to
' hold the value being returned from the INI file, but if not,
' increase the value.
sRetBuf = Space(256)
' Get the size of the return buffer.
iLenBuf = Len(sRetBuf)
' Read the INI Section/Key value into the return variable.
sReturnValue = GetPrivateProfileString(sSection, _
sKey, _
"", _
sRetBuf, _
iLenBuf, _
sIniFile)
' Trim the excess garbage that comes through with the variable.
sReturnValue = Trim(Left(sRetBuf, sReturnValue))
' If we get a value returned, pass it back as the argument.
' Else pass "False".
If Len(sReturnValue) > 0 Then
sManageSectionEntry = sReturnValue
Else
sManageSectionEntry = "Error"
End If
ElseIf inAction = iniWrite Then ' If writing to the INI file.
' Check to see if a value was passed in the sValue parameter.
If Len(sValue) = 0 Then
sManageSectionEntry = "Error"
Else
' Write to the INI file and capture the value returned
' in the API function.
lRetVal = WritePrivateProfileString(sSection, _
sKey, _
sValue, _
sIniFile)
' Check to see if we had an error wrting to the INI file.
If lRetVal = 0 Then sManageSectionEntry = "Error"
End If
End If
Exit_Clean:
Exit Function
Err_ManageSectionEntry:
MsgBox Err.Number & ": " & Err.Description
Resume Exit_Clean
End Function
Some thoughts on what’s going on here:
I’ve taken the two APIs that you would call to read and write to a configuration file and put them into a single function. I’m choosing which action to take based on the inbound inAction parameter.
That parameter, inAction, you may have noticed is an enumeration set up at the top of this module. I like the enumeration in this case because it lets me be very specific in my choice of action to take with regard to the INI file. Yes, I could have saved four lines of code by using a boolean instead. I could have set the function to “read” if TRUE and “write” if FALSE. Except I hate that option. I like enumerations for explicitly spelling out what my options are for value for a specific parameter. That way there’s no confusion.
So what does the implementation of this function look like? Glad you asked! I’ve included a sample routine below that you easily use to test this function out.
Sub SampleINIFunctionImplementaion()
Const sINI_FILE As String = "C:\Users\scott\Desktop\fruits & veggies.ini"
Dim sReturn As String
' Read the ini file
sReturn = sManageSectionEntry(iniRead, "Produce", "Fruit", sINI_FILE)
MsgBox sReturn
sReturn = sManageSectionEntry(iniRead, "Produce", "Vegetable", sINI_FILE)
MsgBox sReturn
' Write to the ini file
sReturn = sManageSectionEntry(iniWrite, "Produce", "Fruit", sINI_FILE, "banana")
sReturn = sManageSectionEntry(iniWrite, "Produce", "Vegetable", sINI_FILE, "squash")
End Sub
That’s about it. Feel free to copy and paste and use for your own Excel applications.
(Fine print: use at your own risk, blah blah blah…)