Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion src/ClassModules/SQLSelect.cls
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ End Sub
' Sub: addTable
' Add a table to the query statement
Public Sub addTable(sName As String, Optional sAlias As String = "")
aJoin(0) = Array("", sName, sAlias, "")
aJoin = ArrayPush(aJoin, Array("", sName, sAlias, ""))
End Sub

' Sub: AddHaving
Expand Down Expand Up @@ -226,6 +226,8 @@ Private Function JoinString()
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
Expand Down
10 changes: 10 additions & 0 deletions src/Modules/SQLHelperFunctions.bas
Original file line number Diff line number Diff line change
Expand Up @@ -74,3 +74,13 @@ Public Sub QuickSort(vArray As Variant, inLow As Long, inHi As Long)
QuickSort vArray, tmpLow, inHi
End If
End Sub

Public Function ArrayPush(vArray As Variant, newValue As Variant)
ArrLen = UBound(vArray)
If IsEmpty(vArray(0)) Then
ArrLen = -1
End If
ReDim Preserve vArray(0 To ArrLen + 1)
vArray(ArrLen + 1) = newValue
ArrayPush = vArray
End Function
12 changes: 12 additions & 0 deletions testing/ClassModules/SQLlibSelectTests.cls
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,18 @@ Function DistinctTest()
DistinctTest = AssertObjectStringEquals(Interfaced, "SELECT DISTINCT c.country FROM customers c ORDER BY c.country ASC")
End Function

Function MultipleTableTest()
'Distinct
Set MySelect = Create_SQLSelect
With MySelect
.AddTable "countries", "c"
.AddTable "users", "u"
.Fields = Array("u.uname", "c.capital")
End With
Set Interfaced = MySelect
MultipleTableTest = AssertObjectStringEquals(Interfaced, "SELECT u.uname, c.capital FROM countries c, users u")
End Function

' Sub: iTestCase_RunTest
' Run a specific test.
Public Sub iTestCase_RunTest(Test As String, Optional clsObj = Nothing)
Expand Down