Skip to main content Link Search Menu Expand Document (external link) Copy Copied

tJoin

New

Run a left, right outer or inner join on the provided data tables.


Syntax

expression.tJoin(nType, leftTable, rightTable, Columns, matchKeys, [predicate= vbNullString], [headers=True])

Parameters

Part Description
nType Required. Identifier specifying a JoinType enumeration variable representing the join nature.
leftTable Required. Identifier specifying a CSVArrayList Type object. Represents the first table in the join operation.
rightTable Required. Identifier specifying a CSVArrayList Type object. Represents the second table in the join operation.
Columns Required. Identifier specifying a String Type variable. Specifies the structure of the rows returned.
matchKeys Required. Identifier specifying a String Type variable. Represents the primary and preference keys to be matched.
predicate Required. Identifier specifying a String Type variable. Represents the condition that must be met when selecting rows.
headers Required. Identifier specifying a Boolean Type variable. Indicates if the tables have headers.

Returns value

Type: CSVArrayList


See also
Filter method.

Behavior

Use a string such as “{1-2,5,ID};{1-6}” as a predicate of the columns to indicate the join of columns 1 to 2, 5 and ‘ID’ of leftTable with the columns 1 to 6 of rightTable. Use a string such as “{*};{1-3}” to indicate the union of ALL columns of leftTable with columns 1 to 3 of rightTable. The predicate must use the dot syntax [t1.#][t1.fieldName] to indicate the fields of the table, where t1 refers to the leftTable. The matchKeys predicate must be given as “#/$;#/$”.

☕Example

Sub Join(ByRef lTable As CSVArrayList, ByRef rTable As CSVArrayList)
    Dim CSVint As CSVinterface
    
    Set CSVint = New CSVinterface
    With CSVint
        ' Performs a Left join returning the "1st" and "Country" fields of the left table and the 
		  ' "Total_Revenue" field of the right table, joined in the "Order_ID" field of both tables, 
		  ' of those records that satisfy the given condition.
        .tJoin JoinType.JT_LeftJoin _
                lTable, rTable, _
                "{1,Country};{Total_Revenue}", _
                "Order_ID;Order_ID", _
                "t2.Total_Revenue>3000000 & t1.Region='Central America and the Caribbean'"
    End With
    Set CSVint = Nothing
End Sub

Back to Methods overview