John Fuex has been working in software development professionally for over 20 years in Austin, Texas. Although he still keeps his hands dirty in code as much as possible, he has spent much of the last decade managing a software development organization that included product development, consulting, testing and technical writing.
Specializing in Microsoft development and database platforms, he has created countless web, desktop and client-server applications. John’s current tool of choice is ASP.NET which he has worked with since it was introduced as what is now wistfully known as ASP classic. Despite a preference for C# and advanced skills with MS SQL Server, he remains an unabashed apologist of maligned and misunderstood technologies including MS Access and Visual Basic.
In his current role as VP of Product Management at a “Big 4” consulting firm, he enjoys most the opportunity to mentor other programmers and encourage them to reach the pinnacle of their potential. In many ways he finds it more rewarding to build a programmer than a program.
He has published two study guides for the MCSD Visual Basic certification exams and several articles in trade journals specializing in technology for litigators.
LinkedIn Profile
Stack Overflow Profile
If you’d like to comment privately about anything on this blog, or volunteer to write an article, you can contact John at the following address:
[…] platform: choosing the target language, mainly between VB.NET and C#. Today I found a great post by John Fuex on that subject, not inciting the war between both trenches but instead describing the process he […]
[…] John Fuex describing the process he and his company went through to solve the C# versus .NET dilemma when migrating […]
How do you pronounce your last name?
It is pronounced to rhyme with “Dukes”
John,
Absolutely love your article on linking SQL server tables. I have been using and modify your example code for a few years now as I learn VBA, Mostly for support of several Access applications that I inherited when I was hired at DHS.
It would be great if you could do an article on using class modules in Access/MS Office that is more indepth than all the examples that can be found by Google and the like. Many , at least all that I could find, only cover VERY MINIMAL functionality at best.
What I am now trying to do is use classes for storing SQL record sets into arrays and dictionarys for reporting and form data. I have found that there are almost no examples or tutorials on how to use unbound forms for “Work at Home” users to improve application usability through remote VPN connections,
I would also like the express my gratitude for you taking the time to write your articles and post your code examples!! Everything has been a great resourse and I have learned quite a lot form them.
Thank you VERY much!!!
John Fuhrman
——————————————————
Here are a couple of class modules that I have created using your VBA code as a base. Feel free to use it. (It is mostly YOUR VBA!!)
cDBcon.cls
Option Compare Database
Option Explicit
Private Const fnModName = “cDBCon”
Public ConnectionString As String
Private m_con As ADODB.Connection
Public Property Get Connection() As ADODB.Connection
If m_con Is Nothing Then
Set m_con = New ADODB.Connection
End If
Set Connection = m_con
If m_con.State = adStateOpen Then
If m_con.Errors.Count = 0 Then
‘ Debug.Print “g_dbCon.Connection Open”
Exit Property
Else
‘ Debug.Print “g_dbCon.Connection Closed”
m_con.Close
End If
End If
If m_con.State adStateClosed Then
‘ Need to test further to see what happens with these.
Debug.Print “clsDbCon.Connection() Unknown Connection State: ” & m_con.State
Exit Property
End If
m_con.ConnectionString = ConnectionString
m_con.Open
Set Connection = m_con
End Property
cSQL.cls
Option Compare Database
Option Explicit
Private Const modName = “cSQL”
‘ constants required from ADODB library
‘CommandTypeEnum Values
Const adCmdUnspecified As Long = -1
Const adCmdText As Long = 1
Const adCmdTable As Long = 2
Const adCmdStoredProc As Long = 4
Const adCmdUnknown As Long = 8
Const adCmdFile As Long = 256
Const adCmdTableDirect As Long = 512
‘ObjectStateEnum Values
Const adStateClosed As Long = 0
Const adStateOpen As Long = 1
Const adStateConnecting As Long = 2
Const adStateExecuting As Long = 4
Const adStateFetching As Long = 8
‘DataTypeEnum Values
Const adEmpty As Long = 0
Const adSmallInt As Long = 2
Const adInteger As Long = 3
Const adSingle As Long = 4
Const adDouble As Long = 5
Const adCurrency As Long = 6
Const adDate As Long = 7
Const adBSTR As Long = 9
‘ Const adIDispatch As Long = 9 ‘Currently Not Supported on ADO
Const adError As Long = 10
Const adBoolean As Long = 11
Const adVariant As Long = 12
Const adIUnknown As Long = 13 ‘Currently Not Supported on ADO
Const adDecimal As Long = 14
Const adTinyInt As Long = 16
Const adUnsignedTinyInt As Long = 17
Const adUnsignedSmallInt As Long = 18
Const adUnsignedInt As Long = 19
Const adBigInt As Long = 20
Const adUnsignedBigInt As Long = 21
Const adFileTime As Long = 64
Const adGUID As Long = 72
Const adBinary As Long = 128
Const adChar As Long = 129
Const adWChar As Long = 130
Const adNumeric As Long = 131
Const adUserDefined As Long = 132
Const adDBDate As Long = 133
Const adDBTime As Long = 134
Const adDBTimeStamp As Long = 135
Const adChapter As Long = 136
Const adPropVariant As Long = 138
Const adVarNumeric As Long = 139
Const adVarChar As Long = 200
Const adLongVarChar As Long = 201
Const adVarWChar As Long = 202
Const adLongVarWChar As Long = 203
Const adVarBinary As Long = 204
Const adLongVarBinary As Long = 205
Const AdArray As Long = 8192
‘ParameterDirectionEnum Values
Const adParamUnknown As Long = 0
Const adParamInput As Long = 1
Const adParamOutput As Long = 2
Const adParamInputOutput As Long = 3
Const adParamReturnValue As Long = 4
‘ExecuteOptionEnum
Const adAsyncExecute As Long = 16
Const adAsyncFetch As Long = 32
Const adAsyncFetchNonBlocking As Long = 64
Const adExecuteNoRecords As Long = 128
Const adExecuteStream As Long = 1024
Const adExecuteRecord As Long = vbEmpty
Const adOptionUnspecified As Long = -1
Const HKEY_CLASSES_ROOT = &H80000000
Const HKEY_CURRENT_USER = &H80000001
Const HKEY_LOCAL_MACHINE = &H80000002
Const HKEY_USERS = &H80000003
Const ERROR_SUCCESS = 0&
Const SYNCHRONIZE = &H100000
Const STANDARD_RIGHTS_READ = &H20000
Const STANDARD_RIGHTS_WRITE = &H20000
Const STANDARD_RIGHTS_EXECUTE = &H20000
Const STANDARD_RIGHTS_REQUIRED = &HF0000
Const STANDARD_RIGHTS_ALL = &H1F0000
Const KEY_QUERY_VALUE = &H1
Const KEY_SET_VALUE = &H2
Const KEY_CREATE_SUB_KEY = &H4
Const KEY_ENUMERATE_SUB_KEYS = &H8
Const KEY_NOTIFY = &H10
Const KEY_CREATE_LINK = &H20
Const KEY_READ = ((STANDARD_RIGHTS_READ Or KEY_QUERY_VALUE Or _
KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY) And (Not SYNCHRONIZE))
Const REG_DWORD = 4
Const REG_BINARY = 3
Const REG_SZ = 1
Private mServer As String
Private mDBName As String
Public Property Let SQLserver(ByVal strSQLServer As String)
mServer = strSQLServer
End Property
Public Property Get SQLserver() As String
SQLserver = mServer
End Property
Public Property Let DBName(ByVal strDBName As String)
mDBName = strDBName
End Property
Public Property Get DBName() As String
DBName = mDBName
End Property
Public Property Get ADOConnectionString() As String
ADOConnectionString = BuildADOConnectionString(mServer, mDBName, g_objApplicationData.ApplicationTitle)
End Property
Private Function BuildADOConnectionString(server As Variant, DBName As Variant, Optional App_Title As Variant) As String
If IsNull(App_Title) = True Then App_Title = “Access Application”
Dim strComputer As String
Dim strKeyPath As String
Dim strValue As String
Dim i As Integer
Dim X As Variant
Dim strValueName As String
Dim arrValueNames As Variant
Dim arrValueTypes As Variant
strComputer = “.”
Dim objRegistry As Object
Set objRegistry = GetObject(“winmgmts:\\” & strComputer & “\root\default:StdRegProv”)
‘Dim dicValueNames As New Scripting.Dictionary
Dim dicValueNames As Object
Set dicValueNames = CreateObject(“Scripting.Dictionary”)
strKeyPath = “SOFTWARE\ODBC\ODBCINST.INI\ODBC Drivers”
objRegistry.EnumValues HKEY_LOCAL_MACHINE, strKeyPath, arrValueNames, arrValueTypes
For i = 0 To UBound(arrValueNames)
strValueName = arrValueNames(i)
objRegistry.GetStringValue HKEY_LOCAL_MACHINE, strKeyPath, strValueName, strValue
If InStr(1, arrValueNames(i), “SQL Server Native”) Then
dicValueNames.Add (i), arrValueNames(i)
ElseIf arrValueNames(i) Like “SQL Server” Then
dicValueNames.Add (i), arrValueNames(i)
End If
Next
For Each X In dicValueNames.Keys
If InStr(1, dicValueNames(X), “Native”, vbTextCompare) Then
TempVars.Add “varSQLdriver”, dicValueNames(X)
BuildADOConnectionString = _
“Driver={” & dicValueNames(X) & “};” & _
“Server=” & server & “;” & _
“APP=” & App_Title & “;” & _
“Database=” & DBName & “;” & _
“TRUSTED_CONNECTION=yes;” & _
“MultipleActiveResultSets = True;”
ElseIf Not InStr(1, dicValueNames(X), “Native”, vbTextCompare) Then
TempVars.Add “varSQLdriver”, dicValueNames(X)
BuildADOConnectionString = _
“Driver={” & dicValueNames(X) & “};” & _
“Server=” & server & “;” & _
“APP=” & App_Title & “;” & _
“Database=” & DBName & “;” & _
“TRUSTED_CONNECTION=yes;” & _
“MultipleActiveResultSets = False;”
End If
Next
End Function
Public Function LinkAllTables(server As Variant, database As Variant, _
OverwriteIfExists As Boolean, _
Optional isView As Boolean, _
Optional Schema As Variant, _
Optional TableName As Variant, _
Optional LinkedTableName As Variant)
If IsMissing(isView) = True Then isView = False
If IsMissing(Schema) = True Then Schema = “dbo”
‘ If IsMissing(Schema) = False Then LogToFile “Schema Variable is ” & Schema & “.”
‘ If IsMissing(Schema) = True Then LogToFile “Schema Variable is ” & Schema & “.”
‘ If IsMissing(TableName) = True Then LogToFile “Missing TableName Variable.”
‘ If IsMissing(TableName) = False Then LogToFile “TableName Variable is ” & TableName & “.”
‘ If IsMissing(LinkedTableName) = True Then LogToFile “Missing LinkedTableName Variable.”
‘ If IsMissing(LinkedTableName) = False Then LogToFile “LinkedTableName Variable is ” & LinkedTableName & “.”
On Error GoTo Error_Handler
‘Usage Example: Call linkalltables(“SQL01″,”SQLDB”, true, “HR”)
‘ (link all tables in database “SQLDB” on SQL Server Instance SQO01,
‘ in the ‘dbo’ and ‘HR’ schema’s overwriting any existing linked tables.
‘This will also update the link if the underlying table definition has been modified.
‘Late bind rsTableList as New ADODB.Recordset
Dim dbCon As ADODB.Connection
Dim cmd As ADODB.Command
Dim rsTableList As ADODB.Recordset
Set dbCon = New ADODB.Connection
Set cmd = New ADODB.Command
Set rsTableList = New ADODB.Recordset
dbCon.ConnectionString = BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
dbCon.Open
LogToFile “————————————————————————”
LogToFile “Server: ” & server & ” Database: ” & database
LogToFile “dbCon.ConnectionString: ” & dbCon.ConnectionString
LogToFile “BuildADOConnectionString: ” & BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
LogToFile “————————————————————————”
Dim sqlTableList As String
sqlTableList = “SELECT [TABLE_SCHEMA] + ‘.’ + [TABLE_NAME] as TableName”
sqlTableList = sqlTableList + ” FROM [INFORMATION_SCHEMA].[TABLES]”
sqlTableList = sqlTableList + ” INNER JOIN [sys].[all_objects]”
sqlTableList = sqlTableList + ” ON [INFORMATION_SCHEMA].[TABLES].TABLE_NAME = [sys].[all_objects].[name]”
If isView = True Then
sqlTableList = sqlTableList + ” WHERE [sys].[all_objects].[type] IN (‘V’)”
Else
sqlTableList = sqlTableList + ” WHERE [sys].[all_objects].[type] IN (‘U’)”
End If
sqlTableList = sqlTableList + ” AND [sys].[all_objects].[is_ms_shipped]1″
sqlTableList = sqlTableList + ” AND [sys].[all_objects].[name] ‘sysdiagrams'”
sqlTableList = sqlTableList + ” ORDER BY [TABLE_SCHEMA], [TABLE_NAME]”
rsTableList.Open sqlTableList, dbCon, adOpenStatic, adLockOptimistic
If dbCon.State = adStateClosed Then
dbCon.Open
rsTableList.Open sqlTableList, dbCon, adOpenStatic, adLockOptimistic
End If
Function_Continue:
While Not rsTableList.EOF
Dim arrSchema As Variant
arrSchema = Split(rsTableList(“TableName”), “.”, , vbTextCompare)
If IsMissing(TableName) = False And IsMissing(LinkedTableName) = True Then
If arrSchema(0) = Schema And arrSchema(1) = TableName Then
If LinkTable(arrSchema(1), server, database, rsTableList(“TableName”), OverwriteIfExists) Then
LogToFile “Linking ” & arrSchema(0) & ” table ” & arrSchema(1)
End If
End If
End If
If IsMissing(TableName) = False And IsMissing(LinkedTableName) = False Then
If arrSchema(0) = Schema And arrSchema(1) = TableName Then
If LinkTable(LinkedTableName, server, database, rsTableList(“TableName”), OverwriteIfExists) Then
LogToFile “Linking ” & arrSchema(0) & ” table ” & arrSchema(1)
End If
End If
End If
If IsMissing(TableName) = True And IsMissing(LinkedTableName) = True Then
If arrSchema(0) = Schema Then
If LinkTable(arrSchema(1), server, database, rsTableList(“TableName”), OverwriteIfExists) Then
LogToFile “Linking ” & arrSchema(0) & ” table ” & arrSchema(1)
End If
End If
End If
rsTableList.MoveNext
Wend
Error_Handler:
If Err.Number = -2147467259 Then
dbCon.ConnectionString = BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
dbCon.Open
GoTo Function_Continue
End If
GoTo Function_Quit
Function_End:
On Error GoTo Function_Quit
rsTableList.Close
GoTo Function_Quit
Function_Quit:
LogToFile “————————————————————————”
Set rsTableList = Nothing
End Function
Private Function LinkTable(LinkedTableAlias As Variant, _
server As Variant, _
database As Variant, _
SourceTableName As Variant, _
OverwriteIfExists As Boolean)
On Error GoTo Error_Handler
‘This method will also update the link if the underlying table definition has been modified.
‘The overwrite parameter will cause it to re-map/refresh the link for LinktedTable Alias, but only if it was already a linked table.
‘ it will not overwrite an existing query or local table with the name specified in LinkedTableAlias.
‘Links to a SQL Server table without the need to set up a DSN in the ODBC Console.
Dim dbsCurrent As DAO.database
Dim tdfLinked As TableDef
‘ Open a database to which a linked table can be appended.
Set dbsCurrent = CurrentDb()
‘Check for and deal with the scenario of the table alias already existing
If TableNameInUse(LinkedTableAlias) Then
If (Not OverwriteIfExists) Then
‘ LogToFile “Can’t use name ‘” + LinkedTableAlias + “‘ because it would overwrite existing table.”
Exit Function
End If
‘delete existing table, but only if it is a linked table
If IsLinkedTable(LinkedTableAlias) Then
dbsCurrent.TableDefs.Delete LinkedTableAlias
dbsCurrent.TableDefs.Refresh
Else
‘ LogToFile “Can’t use name ‘” + LinkedTableAlias + “‘ because it would overwrite an existing query or local table.”
Exit Function
End If
End If
‘Create a linked table
Set tdfLinked = dbsCurrent.CreateTableDef(LinkedTableAlias)
tdfLinked.SourceTableName = SourceTableName
tdfLinked.Connect = “ODBC;” & BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
Function_Continue:
dbsCurrent.TableDefs.Append tdfLinked
GoTo Function_End:
Error_Handler:
‘ LogToFile “ErrorNumber: ” & Err.Number & vbCrLf & “ErrorDesc: ” & Err.Description & vbCrLf & “ErrorSource: ” & Err.Source
Select Case (Err.Number)
Case (3151)
Err.Clear
tdfLinked.Connect = “ODBC;” & BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
GoTo Function_Continue
Case (-2147467259)
Err.Clear
tdfLinked.Connect = “ODBC;” & BuildADOConnectionString(server, database, g_objApplicationData.ApplicationTitle)
GoTo Function_Continue
Case (3626) ‘too many indexes on source table for Access
Err.Clear
On Error GoTo 0
If LinkTable(LinkedTableAlias, server, database, “vw” & SourceTableName, OverwriteIfExists) Then
‘ LogToFile “Can’t link directly to table ‘” + SourceTableName + “‘ because it contains too many indexes for Access to handle. Linked to view ‘” & “vw” & SourceTableName & “‘ instead.”
LinkTable = True
Else
‘ LogToFile “Can’t link table ‘” + SourceTableName + “‘ because it contains too many indexes for Access to handle. Create a view named ‘” & “vw” & SourceTableName & “‘ that selects all rows/columns from ‘” & SourceTableName & “‘ and try again to circumvent this.”
LinkTable = False
Exit Function
End If
End Select
Function_End:
tdfLinked.RefreshLink
LinkTable = True
GoTo Function_Quit
Function_Quit:
Set tdfLinked = Nothing
End Function
Private Function TableNameInUse(TableName As Variant) As Boolean
‘check for local tables, linked tables and queries (they all share the same namespace)
TableNameInUse = DCount(“*”, “MSYSObjects”, “(Type = 4 or type=1 or type=5) AND [Name]='” & TableName & “‘”) > 0
End Function
Private Function IsLinkedTable(TableName As Variant) As Boolean
IsLinkedTable = DCount(“*”, “MSYSObjects”, “(Type = 4) AND [Name]='” & TableName & “‘”) > 0
End Function
Public Function DeleteODBCTableNames(Optional stLocalTableName As String)
On Error GoTo Err_DeleteODBCTableNames
Dim dbs As DAO.database
Dim tdf As TableDef
Dim i As Integer
Dim prpLoop As Property
Set dbs = CurrentDb()
If Len(stLocalTableName) = 0 Then
For i = dbs.TableDefs.Count – 1 To 0 Step -1
Set tdf = dbs.TableDefs(i)
If (tdf.Attributes And dbAttachedODBC) Then
‘ Debug.Print “Deleting Linked Table:” & vbTab & tdf.Name
dbs.TableDefs.Delete (tdf.Name)
End If
Next i
Else
‘ Debug.Print “Local Table: ” & vbTab & stLocalTableName
dbs.TableDefs.Delete (stLocalTableName)
End If
dbs.Close
Set dbs = Nothing
Exit_DeleteODBCTableNames:
Exit Function
Err_DeleteODBCTableNames:
MsgBox (“Error # ” & str(Err.Number) & ” was generated by ” & Err.Source & Chr(13) & Err.DESCRIPTION)
Resume Exit_DeleteODBCTableNames
End Function
I then use modCommon.bas to start and initialize the classes as global objects and set application settings and such. Basically an application startup module.
Option Compare Database
Option Explicit
Private Const fnModName = “modCommon”
Public Const INITIAL_DEBUG_LEVEL As Integer = 2
Public Const INITIAL_APPLICATION_TITLE As String = “PRODUCTION REPORT”
Public Const INITIAL_APPLICATION_VERSION As Integer = 0
‘Global Classes used for application settings and DB connections
Global g_dtmStartupTime As Date
‘Global ADODBconnection to SQL Server
Global g_dbCon As cDBCon
Global g_AdoValueConverter As cAdoValueConverter
‘Global Application Settings
Global g_SystemInfo As cSystemInfo
Global g_objApplicationData As cApplicationData
‘Global Application DB settings for mapping tables and views
Global g_objSQL As cSQL
Global g_objSQL_INPUT_COMPLETED As cSQL
Global g_objDbCon As cDBCon
Global g_objDbCon_INPUT_COMPLETED As cDBCon
‘Global Recordsets
Global g_RecordSet As ADODB.Recordset
‘———————————————————‘
Public Function Startup(Optional fnRunningModName As String = “Stratup”)
g_dtmStartupTime = Now()
On Error GoTo ErrorHandler
LogToFile “modCommon.Startup() Started”
‘ Turn off the Ribbon Bar
ShowRibbon False
‘ Open the Main Switchbord menu and Maximize it
DoCmd.OpenForm “Switchboard”, acNormal, “”, “”, , acNormal
DoCmd.Maximize
‘ Set Command Bar Settings
DoCmd.SetDisplayedCategories 0, “acNavigationCategoryTablesAndViews”
DoCmd.SetDisplayedCategories 0, “acNavigationCategoryObjectType”
DoCmd.SetDisplayedCategories 0, “acNavigationCategoryModifiedDate”
DoCmd.SetDisplayedCategories 0, “acNavigationCategoryCreatedDate”
DoCmd.NavigateTo “acNavigationCategoryObjectType”, “acNavigationGroupForms”
DoCmd.LockNavigationPane -1
‘ Make sure all programming referrence libraries are added
AddRefLib
‘ Create global objects.
CreateObjects
‘ Set the initial debug level.
g_objApplicationData.DebugLevel = INITIAL_DEBUG_LEVEL
‘ Set Application Title
g_objApplicationData.ApplicationTitle = INITIAL_APPLICATION_TITLE
g_objSQL.SQLserver = “SQL-C1-01”
g_objSQL.DBName = “PRODUCTION_REPORT”
g_objDbCon.ConnectionString = g_objSQL.ADOConnectionString
g_objSQL_INPUT_COMPLETED.SQLserver = “SQL-C1-01”
g_objSQL_INPUT_COMPLETED.DBName = “INPUT_COMPLETED”
g_objDbCon_INPUT_COMPLETED.ConnectionString = g_objSQL_INPUT_COMPLETED.ADOConnectionString
LogToFile “Application Opened”
‘ Load All Client Settings
g_objApplicationData.LoadAllSettings
PrintAppSettings
Application.SetOption “Show Hidden Objects”, False
Application.SetOption “Show System Objects”, False
Application.SetOption “Show Navigation Pane Search Bar”, False
Call DeleteODBCTableNames
g_objSQL.LinkAllTables _
g_objSQL.SQLserver, _
g_objSQL.DBName, _
True, False, “dbo”
g_objSQL.LinkAllTables _
g_objSQL.SQLserver, _
g_objSQL.DBName, _
True, True, “dbo”
g_objSQL_SI_INPUT_COMPLETED.LinkAllTables _
g_objSQL_INPUT_COMPLETED.SQLserver, _
g_objSQL_INPUT_COMPLETED.DBName, _
True, False, “dbo”, “COMPLETED”
‘ Show the Information PopUp form
‘ InitSplash
LogToFile “modCommon.Startup() Finished”
Exit_Function:
Exit Function
ErrorHandler:
iF g_objApplicationData.DebugLevel > 2 Then
LogToFile fnModName & “.” & fnRunningModName & “()” & ” Error: ” & GetErrorDescription
LogToFile fnModName & “.” & fnRunningModName & “()” & ” Finished”
Resume Exit_Function
End If
End Function
Private Sub CreateObjects()
Set g_SystemInfo = New cSystemInfo
Set g_dbCon = New cDBCon
Set g_objDbCon_INPUT_COMPLETED = New cDBCon
Set g_objDbCon = New cDBCon
Set g_objApplicationData = New cApplicationData
Set g_objSQL = New cSQL
Set g_objSQL_INPUT_COMPLETED = New cSQL
Set g_AdoValueConverter = New cAdoValueConverter
End Sub
Public Sub PrintAppSettings()
‘ Replace LogToFile with Debug.Print to see results in the immediate window (CTRL-G)
LogToFile “———————————————————-”
LogToFile g_objApplicationData.ApplicationTitle
LogToFile g_objApplicationData.ApplicationVersion
LogToFile “———————————————————-”
‘ LogToFile g_objSQL.SQLserver
‘ LogToFile g_objSQL.DBName
‘ LogToFile g_objSQL.ADOConnectionString
‘ LogToFile “———————————————————-”
‘ LogToFile g_objSQL_SI_INPUT_COMPLETED.SQLserver
‘ LogToFile g_objSQL_SI_INPUT_COMPLETED.DBName
‘ LogToFile g_objSQL_SI_INPUT_COMPLETED.ADOConnectionString
‘ LogToFile “———————————————————-”
End Sub