Access VBA

This category holds articles regarding Access VBA, but also general things I come accross Access and its usage in companies.

The following method exports all available queries in an Access database into individual text files, which are called like the corresponding query.

Source Code

DAO does not provide the support ADODB gives you, therefore this method will only work with queries created and stored in a current MS Access database.

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
' @Author - Alexander Bolte
' @ChangeDate - 2016-03-15
' @Description - exports all queries available in current database query definitions.
' @Param trgDir - a String representing a target directory to export
' all queries in current query definition.
' @Returns true, if all queries have been successfully exported into provided target directory.
Function exportQueries(ByVal trgDir As String) As Boolean
    Dim sql As String
    Dim name As String
    Dim q As Object
    Dim trgFile As String
 
    ' Reference a query.
    For Each q In CurrentDb.QueryDefs
        ' Get the SQL from a referenced query as text.
        sql = q.sql
        ' Get a queries name.
        name = q.name
        ' Replace special characters in file name.
        trgFile = trgDir & "\" & VBATools.replaceSpecialCharacters(name) & ".sql"
        ' Delete the target file, if already existing.
        Call VBATools.deleteFileOnHD(trgFile)
        ' Write the query text into a separate text file.
        Call VBATools.writeLineToTextFile(trgFile, sql, False)
    Next
End Function

Resources

The method writeLineToTextFile is not a standard VBA method, but can be found at following URL.

The target encoding should not be UTF-16LE but ASCII, if you intend to use a versioning tool like GIT to keep track of changes in MS Access queries.

Write a String into a text file

Replacing special characters can be a pain, if you do not rely on regular expressions.

Replace special escape characters in String

Delete a file on a users hard disc (VBScript, which can easily be adjusted to VBA).

VBScript to delete file

Recently I had to link tables from one access file in another access file.

I did not intend to document such a trivial task on my webpage, but since the function I copied from the internet ran into an endless loop after I only provided an invalid file path I decided to implement something myself.

Enjoy.

' @Author
'   Alexander Bolte
'
' @ChangeDate
'   2014-07-29
'
' @Description
'   Linking given table from given source Access database in CurrentDb under provided target name.
'   If a linked table already exists under given name, the link will be broken and replaced with the new one.
'
' @Param strDatabaseSource
'   String providing the full path of the source access database.
' @Param strTableSource
'   String providing the source table name in the source access database.
' @Param strTableDestination
'   String providing the target table name in CurrentDB.
' @Return
'   True, if linkage succeeded, else false.
Public Function LinkTable( _
        ByVal strDatabaseSource As String, _
        ByVal strTableSource As String, ByVal strTableDestination As String _
    ) As Boolean
    Dim dbSource As DAO.Database
    Dim dbTarget As DAO.Database
    Dim dbDestination As DAO.Database
    Dim tdf As DAO.TableDef
   
On Error GoTo LinkTable_Err

    Call unlinkTable(strTableDestination)
    Set dbSource = DBEngine.Workspaces(0).OpenDatabase(strDatabaseSource)
    Set dbDestination = CurrentDb
    Set tdf = dbDestination.CreateTableDef(strTableDestination)
    tdf.Connect = ";DATABASE=" & strDatabaseSource
    tdf.SourceTableName = strTableSource
    dbDestination.TableDefs.Append tdf
    LinkTable = True
LinkTable_Err:
    If Err.Number <> 0 Then
MsgBox Err.Description, vbCritical, cDialogTitle
Err.Clear
LinkTable = False
    End If
   
    If Not (dbSource Is Nothing) Then
        dbSource.Close
        Set dbSource = Nothing
    End If
    Set dbDestination = Nothing
    Set tdf = Nothing
End Function 

If you have to change the sort order of data returned in a RecordSet to behave case sensitive in VBA you can use a trick, which is provided by Microsoft.

Source Code

The below function returns a hexadecimal representation of a handed String, which can then be used in an ORDER BY clause of a sequel statement.

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
' @Author - Microsoft
' @ChangeDate - 2007
' @Description - Returns the hexadecimal expression for a handed String,
' which can then be used in sequel statements to sort case sensitive.
' @Remarks - Original Source can be gotten from the following URL.
' https://support.office.com/en-us/article/Sort-records-in-case-sensitive-order-8fea1de4-6189-40e7-9359-00cd7d7845c0
Function StrToHex(S As Variant) As Variant
    Dim Temp As String
    Dim I As Integer
    
    If VarType(S) <> 8 Then
        StrToHex = S
    Else
        Temp = ""
        For I = 1 To Len(S)
            Temp = Temp & Format(Hex(Asc(Mid(S, I, 1))), "00")
        Next I
        StrToHex = Temp
    End If
End Function

Example

1
2
3
select * 
from aTable 
order by StrToHex(aTextField)

References

Original Source is available at following URL.
https://support.office.com/en-us/article/Sort-records-in-case-sensitive-order-8fea1de4-6189-40e7-9359-00cd7d7845c0

 

Subcategories