Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How to chosse query fields from list box 1

Status
Not open for further replies.

spider8

Technical User
Aug 12, 2001
13
US
HI,
I have a user that wants his own query wizard of sorts. Does anyone know the easiest way to have users run their own queries based on field names they choose, say, from a list box? In other words, they need to be able to choose which fields they want, not just filter given fields by a set of criteria. I'm trying to play around with sql strings in code, but I'm afraid I'm just not experienced enough at it to really know what I'm doing....I'm hoping that if someone can point me down the path of least resistance in this area, I can take it from there...
Thx
 
Spider,

You can traverse the Listbox and construct your own
SQL statement. You can put the SQL in a QueryDef.
You can probably search here for QueryDef and see some
samples.

Normally, people use Listboxes to construct the -
"Where field IN (...)" clause of a QueryDef, but there
is no reason that it can't be used to construct the -
"Select a,b,c ..." part.

However, given that you dynamically construct the SQL to
retrieve "n" columns from a table, what do you have on
the other hand to receive it?

Wayne
 
My Apologies--it turned out to be several days before I could even return to this issue (for a variety of reasons)WayneRyan, you out me on the right track, and I finally knucked down and learned how to write the SQL in code myself. Here is what I came up with so far, and happily, it works:
Dim dbNm As Database
Dim qryDef As QueryDef
Set dbNm = CurrentDb()
Dim strSQL As String
Dim strfld As String
Dim n As Integer

For n = 0 To 28
If Not (IsNull(lstQry.ItemData(n))) Then
strfld = strfld & lstQry.ItemData(n) & ","
End If
Next n
strSQL = "SELECT " & [strfld] & " FROM tblcoreemployeedata"
strSQL = Replace(strSQL, ", from", " from")
Set qryDef = dbNm.QueryDefs("qrylstfields")
qryDef.SQL = strSQL
DoCmd.OpenQuery "qrylstfields", acViewNormal

I have a lot more to add to this before the Query wizard is complete, of course, but for now I am so releived to have the code working so far. Thanks.
 
Here's another way to do it and the code can be resused in other databases you may create in the future. The tag property and name of the controls is the key to making it work. To test it, create a new module, copy and paste the code below in the new module, create a form with 2 text boxes to represent your date range and 1 multi-select listbox that contains a list of your equipment. Then open the report like this:

Docmd.OpenReport "rptViewEquipment",acViewPreview,,BuildWhereClause(Me)


Note that the code doesn't care whether you have 0 pairs of textboxes (date ranges) or many. Nor does it care whether you have 0 multi-select listboxes or many. It will handle it all. Again, the key to making it work is setting the tag property correctly and naming the controls correctly.

For example, suppose you have 2 text boxes (named ServiceDate_BeginR and ServiceDate_EndR) and 1 multi-select list box (list of equipment).

Now suppose the user enters a 6/1/2005 for the begin date range and 6/1/2006 for the end date range. And also suppose the user selects EqupID 1 and EquipID 5 from the list box.
The following function will return your where clause as:

(Betweeen #6/1/2005# and #6/1/2006#) and (EquipID In(1,5))

The key to how this works is using a naming convention and using the Tag Property. The function below assumes that the text boxes that represent a pair of date ranges has a naming convention where the Base Names are the same but the suffix is either _BeginR (ServiceDate_BeginR) or _EndR (ServiceDate_EndR). The tag property of the textbox that represents the 1st date in the range (ServiceDate_BeginR) has the following format:
Where=YourTableName.YourDateFieldName,Date;

The only things you need to note in the multi-select listbox is the Tag property and the bound column. The format of the tag property should look like this:

Where=YourTableName.YourEquipmentIDFieldName,Number;

Where EquipID represents the bound column of the list box.

Code:
Option Compare Database
Option Explicit

    Dim mstrAnd As String
    Dim mstrFilter As String
    
Function BuildWhereClause(frm As Form) As String

'********************************
'*  Declaration Specifications  *
'********************************

    On Error GoTo ErrHandler

'****************
'*  Initialize  *
'****************

    mstrFilter = vbNullString
    mstrAnd = vbNullString
    
    BuildWhereClause_DateRange frm
    BuildWhereClause_ListBox frm
    
    If (InStr(1, mstrFilter, "!!!Error!!!") > 0) Then
        MsgBox "error"
        BuildWhereClause = "!!!ERROR!!!"
        Exit Function
    End If
    
    BuildWhereClause = mstrFilter
    
'********************
'*  Exit Procedure  *
'********************
        
ExitProcedure:

    Exit Function

'****************************
'*  Error Recovery Section  *
'****************************
        
ErrHandler:

    Err.Raise Err.Number,"BuildWhereClause" & ";" & Err.Source,Err.Description        
 
End Function


Function BuildWhereClause_DateRange(frm As Form)

'********************************
'*  Declaration Specifications  *
'********************************

    Dim ctl As Control
    Dim ctlEndR As Control
    
    Dim strField As String
    Dim strType As String
    
    Dim i As Integer
    Dim j As Integer
    Dim k As Integer
    
    On Error GoTo ErrHandler

'*********************************************************
'*  Loop thru all controls on form to find list box(es)  *
'*********************************************************

    For Each ctl In frm.Controls
                
        If (ctl.ControlType = acTextBox) And (Right$(ctl.Name, 7) = "_BeginR") Then
                
        '*************************************************************************************************
        '*  Should this list box be processed?                                                           *
        '*  If so, then tag property contains the name of the table and field and the type of the field  *
        '*      (Structure of tag property:  Where=TableName.FieldName,DataType,    )                    *
        '*      NOTE that the code assumes the tag property is structured properly                       *
        '*************************************************************************************************
            
            If ((ctl.Enabled) And (Not ctl.Locked) And (InStr(ctl.Tag, "Where=") > 0)) Then
                
                If (IsNull(ctl)) Then GoTo 7000
                On Error Resume Next
                Set ctlEndR = frm(Left$(ctl.Name, Len(ctl.Name) - 7) & "_EndR")
                If (Err.Number = 2465) Then
                    Err.Clear
                    GoTo 7000
                End If
                If (IsNull(ctlEndR)) Then GoTo 7000
    
                On Error GoTo ErrHandler
                
                j = InStr(ctl.Tag, "Where=")
                k = InStr(j, ctl.Tag, ",")
                strField = Mid(ctl.Tag, j + 6, k - (j + 6))
                
                j = InStr(k + 1, ctl.Tag, ";")
                strType = Mid(ctl.Tag, k + 1, j - k - 1)
                
                mstrFilter = mstrFilter & mstrAnd & " (" & strField & " Between #" & ctl.Value & "# AND #" & ctlEndR.Value & "#) "
                mstrAnd = " AND "
                
            End If
        End If
7000:
    Next
    
'********************
'*  Exit Procedure  *
'********************
        
ExitProcedure:

    Exit Function

'****************************
'*  Error Recovery Section  *
'****************************
        
ErrHandler:
        
Err.Raise Err.Number,"BuildWhereClause_DateRange" & ";" & Err.Source,Err.Description 

End Function


Function BuildWhereClause_ListBox(frm)

'********************************
'*  Declaration Specifications  *
'********************************

    Dim ctl As Control
    
    Dim varItem As Variant
    
    Dim strField As String
    Dim strType As String
    
    Dim i As Integer
    Dim j As Integer
    Dim k As Integer
    
    On Error GoTo ErrHandler

'*********************************************************
'*  Loop thru all controls on form to find list box(es)  *
'*********************************************************

    For Each ctl In frm.Controls
                
        If (ctl.ControlType = acListBox) Then
                
        '*************************************************************************************************
        '*  Should this list box be processed?                                                           *
        '*  If so, then tag property contains the name of the table and field and the type of the field  *
        '*      (Structure of tag property:  Where=TableName.FieldName,DataType;    )                    *
        '*      NOTE that the code assumes the tag property is structured properly                       *
        '*************************************************************************************************
            
            If ((ctl.Enabled) And (Not ctl.Locked) And (ctl.ItemsSelected.Count > 0) And (InStr(ctl.Tag, "Where=") > 0)) Then
                
                j = InStr(ctl.Tag, "Where=")
                k = InStr(j, ctl.Tag, ",")
                strField = Mid(ctl.Tag, j + 6, k - (j + 6))
                
                j = InStr(k + 1, ctl.Tag, ";")
                strType = Mid(ctl.Tag, k + 1, j - k - 1)
                
                mstrFilter = mstrFilter & mstrAnd & " (" & strField & " In ("
                
        '******************************************
        '*  Loop thru items selected in list box  *
        '******************************************
        
                For Each varItem In ctl.ItemsSelected
                    
                    If (strType = "String") Then
                        mstrFilter = mstrFilter & "'" & ctl.Column(ctl.BoundColumn - 1, varItem) & "', "
                    ElseIf (strType = "Number") Then
                        mstrFilter = mstrFilter & ctl.Column(ctl.BoundColumn - 1, varItem) & ", "
                    End If
                    
                Next varItem
    
                mstrFilter = Mid(mstrFilter, 1, Len(mstrFilter) - 2) & ")) "
                mstrAnd = " AND "
                
            End If
        End If
    
    Next
    
'********************
'*  Exit Procedure  *
'********************
        
ExitProcedure:

    Exit Function

'****************************
'*  Error Recovery Section  *
'****************************
        
ErrHandler:
        
Err.Raise Err.Number,"BuildWhereClause_ListBox" & ";" & Err.Source,Err.Description 

End Function
 
Thanks-this code is pretty cool too--This could come in handy when I'm contruccting the "where" variables in my code.I'm grateful for the input!
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top