SQLSelect -->iSQLQuery_ToString - Problem with Join on 2 or more Tables
Issue detected when attempting to create SQLString if 2 or more tables are necessary to JOIN. the resulting SQL contains error and cannot be used.
Can you please supply a code snippet, what the resulting SQL is, and what you expected?
Even better would be if you were able to provide a failing test case that I could add to the unit tests. The test would, by definition, include the generation code as well as the expectation.
The tests already include this:
Function JoinTest()
'Check Join
Set MySelect = Create_SQLSelect
With MySelect
.addTable "users", "u"
.InnerJoin "countries", "c", "u.country=c.country"
.Fields = Array("u.uname", "c.capital")
End With
Set Interfaced = MySelect
JoinTest = AssertObjectStringEquals(Interfaced, "SELECT u.uname, c.capital FROM users u INNER JOIN countries c ON u.country=c.country")
MySelect.AddField "t.zone"
MySelect.InnerJoin "timezones", "t", "c.capital=t.city"
Call AssertObjectStringEquals(Interfaced, "SELECT u.uname, c.capital, t.zone FROM users u INNER JOIN countries c ON u.country=c.country INNER JOIN timezones t ON c.capital=t.city")
End Function
the second of which includes two inner joins.
Rereading your comment, are you calling addTable() multiple times? You only need to do that once. I wonder if there is an issue if instead of using a join, a where clause is used as in:
SELECT u.uname, c.capital FROM users u, countries c WHERE u.country=c.country
There is no test for this type of query, although this syntax is usually not recommend since joins are more efficient. There should be a test for it though since it IS a valid SQL statement.
It looks like addTable cannot be successfully called multiple times. Also, addJoin “” table, alias does not work because it fails to add a comma between tables.
I think I’ll work on modifying addTable to be called multiple times, however, this is not a join, and might not be what you are referring to.
#33 may be related to this, and it has been fixed. Please let me know how to reproduce this issue or if that fix resolved your issue.
Sorry for the late reply.
To give you a proper example, suppose u have 4 Tables like the example below:

The query I am trying to build is to get data from "tblDataRecords", but JOIN with the other three to get the respective ClassName.
Query i need to Create:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblClassOne INNER JOIN (tblClassThree INNER JOIN (tblClassTwo INNER JOIN tblDataRecords ON tblClassTwo.ClassID = tblDataRecords.ClassTwo) ON tblClassThree.ClassID = tblDataRecords.ClassThree) ON tblClassOne.ClassID = tblDataRecords.ClassOne
WHERE tblDataRecords.RecordDate=#1/12/2022#;
Code Snipet:
Dim MySelect As SQLSelect
Set MySelect = Create_SQLSelect
With MySelect
.Fields = Array("tblDataRecords.RecordID", _
"tblDataRecords.RecordName", _
"tblClassOne.ClassOneName", _
"tblDataRecords.RecordDate")
.Table = "tblDataRecords"
'using InnerJoin or AddJoin works great
.InnerJoin "tblClassOne", "", "tblClassOne.ClassID = tblDataRecords.ClassOne"
'.AddJoin "INNER", "tblClassOne", "", "tblClassOne.ClassID = tblDataRecords.ClassOne"
.AddWhere "tblDataRecords.RecordDate", "#1/12/2022#"
End With
Debug.Print MySelect.iSQLQuery_ToString
Resulting Querys:
'using InnerJoin
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblDataRecords.RecordDate
FROM tblDataRecords INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne
WHERE tblDataRecords.RecordDate=#1/12/2022#
'using AddJoin
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblDataRecords.RecordDate
FROM tblDataRecords INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne
WHERE tblDataRecords.RecordDate=#1/12/2022#
The problem only occurs if i attempt to JOIN 3 or more Tables, check code Snipet:
Dim MySelect As SQLSelect
Set MySelect = Create_SQLSelect
With MySelect
.Fields = Array("tblDataRecords.RecordID", _
"tblDataRecords.RecordName", _
"tblClassOne.ClassOneName", _
"tblClassTwo.ClassTwoName", _
"tblClassThree.ClassThreeName", _
"tblDataRecords.RecordDate")
.Table = "tblDataRecords"
.InnerJoin "tblClassOne", "", "tblClassOne.ClassID = tblDataRecords.ClassOne"
.AddJoin "INNER", "tblClassTwo", "", "tblClassTwo.ClassID = tblDataRecords.ClassTwo"
.AddJoin "INNER", "tblClassThree", "", "tblClassThree.ClassID = tblDataRecords.ClassThree"
.AddWhere "tblDataRecords.RecordDate", "#1/12/2022#"
End With
Debug.Print MySelect.iSQLQuery_ToString
Resulting Query:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblDataRecords INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo INNER JOIN tblClassThree ON tblClassThree.ClassID = tblDataRecords.ClassThree
WHERE tblDataRecords.RecordDate=#1/12/2022#
When i attempt to run this query it returns Error
What is the error that you are seeing? Does #1/12/2022# need to be quoted?
.AddWhere "tblDataRecords.RecordDate", str("#1/12/2022#")
When I run your first code snippet, I get:
SELECT tblDataRecords.RecordID,
tblDataRecords.RecordName,
tblClassOne.ClassOneName,
tblClassTwo.ClassTwoName,
tblClassThree.ClassThreeName,
tblDataRecords.RecordDate
FROM tblDataRecords
INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne
INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo
INNER JOIN tblClassThree ON tblClassTwo.ClassID = tblDataRecords.ClassTwo
WHERE tblDataRecords.RecordDate=#1/12/2022#
However, both code snippets look to be the same.
Can you update your library code from the repository if you have not recently done so?
Three years ago I changed AddJoin to allow multiple joins. It used to be:
Public Sub AddJoin(sType, sTable, Optional sAlias = Null, Optional sCondition = Null)
Dim MyJoin As New SQLJoin
With MyJoin
.Type = sType
.Table = sTable
.Alias = sAlias
.Condition = sCondition
End With
'Add MyJoin to the Join Array
End Sub
and it is now:
' Sub: AddJoin
' Add a join condition to the SQL query
Public Sub AddJoin(sType As String, sTable As String, Optional sAlias As String = "", Optional sCondition As String = "")
'Should Check that sType is either "INNER", "LEFT OUTER", or "RIGHT OUTER"
Dim JoinLen As Integer
JoinLen = UBound(aJoin)
ReDim Preserve aJoin(0 To JoinLen + 1)
aJoin(JoinLen + 1) = Array(sType, sTable, sAlias, sCondition)
End Sub
Does your version of the code have the older version of the function?
Just edited my previous post. Think i Had a issue with "Copy and Paste" cause both code snippets were not supposed to be the same...
I don't have a older version. I downloaded a couple of days before creating this issue.
here is the function i asked for:

To answer your question:
Does #1/12/2022# need to be quoted? No it doesnt (The DB i tested on is Access)
What is the error that you are seeing? The Query returned by
Debug.Print MySelect.iSQLQuery_ToStringDoesnt Run on Access it returns a error
Query that i expected and that runs great on Access:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblClassOne INNER JOIN (tblClassThree INNER JOIN (tblClassTwo INNER JOIN tblDataRecords ON tblClassTwo.ClassID = tblDataRecords.ClassTwo) ON tblClassThree.ClassID = tblDataRecords.ClassThree) ON tblClassOne.ClassID = tblDataRecords.ClassOne
WHERE tblDataRecords.RecordDate=#1/12/2022#;
Query that is returned by iSQLQuery_ToString:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblDataRecords INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo INNER JOIN tblClassThree ON tblClassThree.ClassID = tblDataRecords.ClassThree
WHERE tblDataRecords.RecordDate=#1/12/2022#
The JOINS are not correct. Compare the 2 Querys.
Is this line correct?
.AddJoin "INNER", "tblClassThree", "", "tblClassTwo.ClassID = tblDataRecords.ClassTwo"
should it be
.AddJoin "INNER", "tblClassThree", "", "tblClassThree.ClassID = tblDataRecords.ClassThree"
OK .. i edited the posts once more .. and corrected it again.
Thats what the code snippet that i used and what i get from Debug.Print MySelect.iSQLQuery_ToString is the following query.
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblDataRecords INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo INNER JOIN tblClassThree ON tblClassThree.ClassID = tblDataRecords.ClassThree
WHERE tblDataRecords.RecordDate=#1/12/2022#
when i try to run this on Access i get the following error:

On the other hand, the query i gived u as example:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblClassOne INNER JOIN (tblClassThree INNER JOIN (tblClassTwo INNER JOIN tblDataRecords ON tblClassTwo.ClassID = tblDataRecords.ClassTwo) ON tblClassThree.ClassID = tblDataRecords.ClassThree) ON tblClassOne.ClassID = tblDataRecords.ClassOne
WHERE tblDataRecords.RecordDate=#1/12/2022#;

If necessary i can provide u with the Access Data Base itself and a Excel Macro Workbook with the code for u to test yourself.
I don’t see where a problem would be. The parenthesis are optional, so that shouldn’t cause a problem. Can you try using table aliases instead of leaving them as empty strings? I’d have to look at the code, but maybe it’s adding an extra space between the table name and “ON”. Google says that error usually is from non-ascii table names or having spaces in field names, but that’s not the issue here.
is the final semicolon a must have?
Ahh! In MS Access, parenthesis are not optional.
I think the fix will be: if number of joins is greater than two, for all joins except the last one add an open-paren after the join type, and a closing-paren before the ON.
I don’t see where a problem would be. The parenthesis are optional, so that shouldn’t cause a problem. Can you try using table aliases instead of leaving them as empty strings? I’d have to look at the code, but maybe it’s adding an extra space between the table name and “ON”. Google says that error usually is from non-ascii table names or having spaces in field names, but that’s not the issue here.
is the final semicolon a must have?
The final semicolon is only required in the MS Access query editor if i am not mistaken using ADO doesn't require the semicolon
Ahh! In MS Access, parenthesis are not optional.
I think the fix will be: if number of joins is greater than two, for all joins except the last one add an open-paren after the join type, and a closing-paren before the ON.
when u get a fix for this, let me know, so i can make a test and give you feedback about it.
Ahh! In MS Access, parenthesis are not optional.
I think the fix will be: if number of joins is greater than two, for all joins except the last one add an open-paren after the join type, and a closing-paren before the ON.
Not sure if what u say will work..
I give you a sugestion to work with and i'm pretty sure that it will require minimal code changes. Also i tested it and this i can assure you it works!
Current Output of SQLSelect.iSQLQuery_ToString:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM tblDataRecords
INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne
INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo
INNER JOIN tblClassThree ON tblClassThree.ClassID = tblDataRecords.ClassThree
WHERE tblDataRecords.RecordDate=#1/12/2022#
Correct Query that works on MS Access:
SELECT tblDataRecords.RecordID, tblDataRecords.RecordName, tblClassOne.ClassOneName, tblClassTwo.ClassTwoName, tblClassThree.ClassThreeName, tblDataRecords.RecordDate
FROM ( ( tblDataRecords
INNER JOIN tblClassOne ON tblClassOne.ClassID = tblDataRecords.ClassOne )
INNER JOIN tblClassTwo ON tblClassTwo.ClassID = tblDataRecords.ClassTwo )
INNER JOIN tblClassThree ON tblClassThree.ClassID = tblDataRecords.ClassThree
WHERE tblDataRecords.RecordDate=#1/12/2022#


Thanks! If you’ve made a change to the code in the library and want to submit a pull request, go ahead.
Think this should do the trick. I havent tested it.. Im on mobile phone atm
File: SQLSelect.cls Modified function JoinString() Code snippet untested
Private Function JoinString()
Dim R As Long
Dim I As Long
Dim Lines() As String
Dim Line As String
Dim LineArray As Variant
ReDim Lines(0 To UBound(aJoin))
For R = 0 To UBound(aJoin)
LineArray = aJoin(R)
Line = ""
If LineArray(0) <> "" Then
Line = LineArray(0) & " JOIN "
ElseIf R > 0 Then
Lines(R - 1) = Lines(R - 1) & ","
End If
Line = Line & LineArray(1)
If LineArray(2) <> "" Then
Line = Line & " " & LineArray(2)
End If
If LineArray(3) <> "" Then
Line = Line & " ON " & LineArray(3)
End If
'Add inicial open parenthesis as needed join
If R = 0 And UBound(aJoin) > 1 Then
For I = 2 To UBound(aJoin)
Line = " ( " & Line
Next I
Lines(R) = Line
'Add close parenthesis for join
ElseIf R > 0 And R < UBound(aJoin) And UBound(aJoin) > 1 Then
Lines(R) = Line & " ) "
Else
'Normal output
Lines(R) = Line
End If
Next R
JoinString = Join(Lines, " ")
End Function
Thanks! If you’ve made a change to the code in the library and want to submit a pull request, go ahead.
As you suggested, created a pull request with a modified Function JoinString()
I made a couple of tests and all of them worked on MS Access.