Kamis, 26 Mei 2011

RE: [MS_AccessPros] User selection of multiple parameters to print reports

 

Walter-

VarType is a built-in VBA function. Delete any code you created.

John Viescas, author
Microsoft Office Access 2010 Inside Out
Microsoft Office Access 2007 Inside Out
Building Microsoft Access Applications
Microsoft Office Access 2003 Inside Out
SQL Queries for Mere Mortals
http://www.viescas.com/
(Paris, France)

-----Original Message-----
From: MS_Access_Professionals@yahoogroups.com
[mailto:MS_Access_Professionals@yahoogroups.com] On Behalf Of nkpberk
Sent: Thursday, May 26, 2011 7:20 PM
To: MS_Access_Professionals@yahoogroups.com
Subject: Re: [MS_AccessPros] User selection of multiple parameters to print
reports

John:
Upon using your "IsNothing" function I found "VarType" function reference, I put
together my own "VarType" and it works fine with strings, empty strings and Null
but utterly fails on numeric data. Help!
Walter

--- In MS_Access_Professionals@yahoogroups.com, "John Viescas" <john@...> wrote:
>
> Walter-
>
> Forgot to include my custom IsNothing function that you'll need if you choose
to
> use my code as a template. I've pasted it below.
>
> John Viescas, author
> Microsoft Office Access 2010 Inside Out
> Microsoft Office Access 2007 Inside Out
> Building Microsoft Access Applications
> Microsoft Office Access 2003 Inside Out
> SQL Queries for Mere Mortals
> http://www.viescas.com/
> (Paris, France)
>
> ----------------------------------------------
> Public Function IsNothing(ByVal varValueToTest) As Integer
> '----------------------------------------------------------
> ' Does a "nothing" test based on data type.
> ' Null = nothing
> ' Empty = nothing
> ' Number = 0 is nothing
> ' String = "" is nothing
> ' Date/Time is never nothing
> ' Inputs: A value to test for logical "nothing"
> ' Outputs: True = value passed is a logical "nothing", False = it ain't
> ' Created By: JLV 01/31/95
> ' Last Revised: JLV 01/31/95
> '----------------------------------------------------------
> Dim intSuccess As Integer
>
> On Error GoTo IsNothing_Err
> IsNothing = True
>
> Select Case varType(varValueToTest)
> Case 0 ' Empty
> GoTo IsNothing_Exit
> Case 1 ' Null
> GoTo IsNothing_Exit
> Case 2, 3, 4, 5, 6 ' Integer, Long, Single, Double, Currency
> If varValueToTest <> 0 Then IsNothing = False
> Case 7 ' Date / Time
> IsNothing = False
> Case 8 ' String
> If (Len(varValueToTest) <> 0 And varValueToTest <> " ") Then
> IsNothing = False
> End Select
>
>
> IsNothing_Exit:
> On Error GoTo 0
> Exit Function
>
> IsNothing_Err:
> IsNothing = True
> Resume IsNothing_Exit
>
> End Function
>
>
> -----Original Message-----
> From: MS_Access_Professionals@yahoogroups.com
> [mailto:MS_Access_Professionals@yahoogroups.com] On Behalf Of nkpberk
> Sent: Monday, May 23, 2011 11:38 PM
> To: MS_Access_Professionals@yahoogroups.com
> Subject: Re: [MS_AccessPros] User selection of multiple parameters to print
> reports
>
> John:
> Copied that to a txt file.
> Mine may be a bit simpler forcing only known values from the combo boxes and
> "null's", the date issue will probably be the only enterable (word?) value.
> I'm sure I will code myself into a corner with this but I'll cross that when I
> get there.
> Thanx
> Walter
>
> --- In MS_Access_Professionals@yahoogroups.com, "John Viescas" <john@> wrote:
> >
> > Walter-
> >
> > Although you could format your query parameters to ignore Null values, that
> > won't work well if you have more than 3 parameters. The best bet is to
> > dynamically create a filter that you use to open the report based on what
the
> > user selected. Below is an example from one of the sample applications in
my
> > books. The form contains several text filters that the code examines to
> > assemble a filter to open the requested form, but the same technique could
be
> > used for a report.
> >
> > ------------------------------------
> > Private Sub cmdSearch_Click()
> > Dim varWhere As Variant
> > ' Initialize to Null
> > varWhere = Null
> > ' If specified a company name value
> > If Not IsNothing(Me.txtCompany) Then
> > ' .. build the predicate
> > varWhere = "[CompanyName] LIKE '" & Me.txtCompany & "*'"
> > End If
> > ' Do City next
> > If Not IsNothing(Me.txtCity) Then
> > ' .. build the predicate
> > ' Note: taking advantage of Null propogation
> > ' so we don't have to test for any previous predicate
> > varWhere = (varWhere + " AND ") & "[City] LIKE '" & Me.txtCity &
"*'"
> > End If
> > ' Do State next
> > If Not IsNothing(Me.txtState) Then
> > ' .. build the predicate
> > varWhere = (varWhere + " AND ") & "[StateOrProvince] LIKE '" &
> > Me.txtState & "*'"
> > End If
> > ' Do County next
> > If Not IsNothing(Me.txtCounty) Then
> > ' .. build the predicate
> > varWhere = (varWhere + " AND ") & "[County] LIKE '" & Me.txtCounty &
> > "*'"
> > End If
> > ' Finally, do Referred By
> > If Not IsNothing(Me.cmbReferredBy) Then
> > ' .. build the predicate
> > varWhere = (varWhere + " AND ") & "[ReferredBy] = " &
Me.cmbReferredBy
> > End If
> >
> > ' Check to see that we built a filter
> > If IsNothing(varWhere) Then
> > MsgBox "You must enter at least one search criteria.",
vbInformation,
> > gstrAppTitle
> > Exit Sub
> > End If
> >
> > ' See if any rows with a quick DLookup
> > If IsNothing(DLookup("CompanyID", "tblCompanies", varWhere)) Then
> > MsgBox "No Companies meet your criteria.", vbInformation,
gstrAppTitle
> > Exit Sub
> > End If
> >
> > ' Open Companies filtered
> > ' Note: if form already open, this just applies the filter
> > DoCmd.OpenForm "frmCompanies", WhereCondition:=varWhere
> > ' Done
> > DoCmd.Close acForm, Me.Name
> > End Sub
> > ------------------------
> >
> > Because the user can enter text for any of the search criteria, the code
> > assembles LIKE predicates and uses the * wildcard to do a generic search.
The
> > last item is a combo box that returns the integer key for the ReferredBy
> field,
> > so I use a simple = comparison.
> >
> > Here's another that uses a combination of text, date/time, Yes/No, and combo
> box
> > integer values:
> >
> > -----------------------------------
> > Private Sub cmdSearch_Click()
> > Dim varWhere As Variant, varDateSearch As Variant
> > Dim rst As DAO.Recordset
> > ' Initialize to Null
> > varWhere = Null
> > varDateSearch = Null
> > ' First, validate the dates
> > ' If there's something in Contact Date From
> > If Not IsNothing(Me.txtContactFrom) Then
> > ' First, make sure it's a valid date
> > If Not IsDate(Me.txtContactFrom) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Contact From is not a valid date.",
> vbCritical,
> > gstrAppTitle
> > Exit Sub
> > End If
> > ' Now see if they specified a "to" date
> > If Not IsNothing(Me.txtContactTo) Then
> > ' First, make sure it's a valid date
> > If Not IsDate(Me.txtContactTo) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Contact To is not a valid date.",
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > ' Got two dates, now make sure "to" is >= "from"
> > If Me.txtContactTo < Me.txtContactFrom Then
> > MsgBox "Contact To date must be greater than or equal to
> Contact
> > From date.", _
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > End If
> > Else
> > ' No "from" but did they specify a "to"?
> > If Not IsNothing(Me.txtContactTo) Then
> > ' Make sure it's a valid date
> > If Not IsDate(Me.txtContactTo) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Contact To is not a valid date.",
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > End If
> > End If
> > ' If there's something in Follow-up Date From
> > If Not IsNothing(Me.txtFollowUpFrom) Then
> > ' First, make sure it's a valid date
> > If Not IsDate(Me.txtFollowUpFrom) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Follow-up From is not a valid date.",
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > ' Now see if they specified a "to" date
> > If Not IsNothing(Me.txtFollowUpTo) Then
> > ' First, make sure it's a valid date
> > If Not IsDate(Me.txtFollowUpTo) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Follow-up To is not a valid date.",
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > ' Got two dates, now make sure "to" is >= "from"
> > If Me.txtFollowUpTo < Me.txtFollowUpFrom Then
> > MsgBox "Follow-up To date must be greater than or equal to
> > Follow-up From date.", _
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > End If
> > Else
> > ' No "from" but did they specify a "to"?
> > If Not IsNothing(Me.txtFollowUpTo) Then
> > ' Make sure it's a valid date
> > If Not IsDate(Me.txtFollowUpTo) Then
> > ' Nope, warn them and bail
> > MsgBox "The value in Follow-up To is not a valid date.",
> > vbCritical, gstrAppTitle
> > Exit Sub
> > End If
> > End If
> > End If
> >
> > ' OK, start building the filter
> > ' If specified a contact type value
> > If Not IsNothing(Me.cmbContactType) Then
> > ' .. build the predicate
> > varWhere = "(ContactType.Value = '" & Me.cmbContactType & "')"
> > End If
> >
> > ' Do Last Name next
> > If Not IsNothing(Me.txtLastName) Then
> > ' .. build the predicate
> > ' Note: taking advantage of Null propogation
> > ' so we don't have to test for any previous predicate
> > varWhere = (varWhere + " AND ") & "([LastName] LIKE '" &
> Me.txtLastName
> > & "*')"
> > End If
> >
> > ' Do First Name next
> > If Not IsNothing(Me.txtFirstName) Then
> > ' .. build the predicate
> > varWhere = (varWhere + " AND ") & "([FirstName] LIKE '" &
> > Me.txtFirstName & "*')"
> > End If
> >
> > ' Do Company next
> > If Not IsNothing(Me.cmbCompanyID) Then
> > ' .. build the predicate
> > ' Must use a subquery here because the value is in a linking
table...
> > varWhere = (varWhere + " AND ") & _
> > "([ContactID] IN (SELECT ContactID FROM tblCompanyContacts " & _
> > "WHERE tblCompanyContacts.CompanyID = " & Me.cmbCompanyID & "))"
> > End If
> >
> > ' Do City next
> > If Not IsNothing(Me.txtCity) Then
> > ' .. build the predicate
> > ' Test for both Work and Home city
> > varWhere = (varWhere + " AND ") & "(([WorkCity] LIKE '" & Me.txtCity
&
> > "*')" & _
> > " OR ([HomeCity] LIKE '" & Me.txtCity & "*'))"
> > End If
> >
> > ' Do State next
> > If Not IsNothing(Me.txtState) Then
> > ' .. build the predicate
> > ' Test for both Work and Home state
> > varWhere = (varWhere + " AND ") & "(([WorkStateOrProvince] LIKE '" &
> > Me.txtState & "*')" & _
> > " OR ([HomeStateOrProvince] LIKE '" & Me.txtState & "*'))"
> > End If
> >
> > ' Do Contact date(s) next -- this is a toughie
> > ' because we want to end up with one filter on the subquery table
> > ' for both Contact Date range and FollowUp Date range
> > ' Check Contact From first
> > If Not IsNothing(Me.txtContactFrom) Then
> > ' .. build the predicate
> > varDateSearch = "tblContactEvents.ContactDateTime >= #" &
> > Me.txtContactFrom & "#"
> > End If
> > ' Now do Contact To
> > If Not IsNothing(Me.txtContactTo) Then
> > ' .. add to the predicate, but add one because ContactDateTime
> includes
> > ' a date AND a time
> > varDateSearch = (varDateSearch + " AND ") & _
> > "tblContactEvents.ContactDateTime < #" & CDate(Me.txtContactTo)
+
> 1
> > & "#"
> > End If
> > ' Now do Follow-up From
> > If Not IsNothing(Me.txtFollowUpFrom) Then
> > ' .. add to the predicate
> > varDateSearch = (varDateSearch + " AND ") & _
> > "tblContactEvents.ContactFollowUpDate >= #" & Me.txtFollowUpFrom
&
> > "#"
> > End If
> > ' Finally, do Follow-up To
> > If Not IsNothing(Me.txtFollowUpTo) Then
> > ' .. add to the predicate
> > varDateSearch = (varDateSearch + " AND ") & _
> > "tblContactEvents.ContactFollowUpDate <= #" & Me.txtFollowUpTo &
> "#"
> > End If
> > ' Did we build any date filter?
> > If Not IsNothing(varDateSearch) Then
> > ' OK, add to the overall filter
> > ' Must use a subquery here because the value is in a linking
table...
> > varWhere = (varWhere + " AND ") & _
> > "([ContactID] IN (SELECT ContactID FROM tblContactEvents " & _
> > "WHERE " & varDateSearch & "))"
> > End If
> >
> > ' Do Product
> > If Not IsNothing(Me.cmbProductID) Then
> > ' .. build the predicate
> > ' Must use a subquery here because the value is in a linking
table...
> > varWhere = (varWhere + " AND ") & _
> > "([ContactID] IN (SELECT ContactID FROM tblContactProducts " & _
> > "WHERE tblContactProducts.ProductID = " & Me.cmbProductID & "))"
> > End If
> >
> > ' Finally, do the Inactive check box
> > If (Me.chkInactive = False) Then
> > ' Build a filter to exclude inactive contacts
> > varWhere = (varWhere + " AND ") & _
> > "(Inactive = False)"
> > End If
> >
> > ' Check to see that we built a filter
> > If IsNothing(varWhere) Then
> > MsgBox "You must enter at least one search criteria.",
vbInformation,
> > gstrAppTitle
> > Exit Sub
> > End If
> >
> > ' Open a recordset to see if any rows returned with this filter
> > Set rst = CurrentDb.OpenRecordset("SELECT tblContacts.* FROM tblContacts
> > WHERE " & varWhere)
> > ' See if found none
> > If rst.RecordCount = 0 Then
> > MsgBox "No Contacts meet your criteria.", vbInformation,
gstrAppTitle
> > ' Clean up recordset
> > rst.Close
> > Set rst = Nothing
> > Exit Sub
> > End If
> >
> > ' Hide me to fix later focus problems
> > Me.Visible = False
> > ' Move to last to find out how many
> > rst.MoveLast
> > ' If 5 or less or frmContacts already open,
> > If (rst.RecordCount < 6) Or IsFormLoaded("frmContacts") Then
> > ' Open Contacts filtered
> > ' Note: if form already open, this just applies the filter
> > DoCmd.OpenForm "frmContacts", WhereCondition:=varWhere
> > ' Make sure focus is on contacts
> > Forms!frmContacts.SetFocus
> > Else
> > ' Ask if they want to see a summary list first
> > If vbYes = MsgBox("Your search found " & rst.RecordCount & "
contacts.
> > " & _
> > "Do you want to see a summary list first?", _
> > vbQuestion + vbYesNo, gstrAppTitle) Then
> > ' Show the summary
> > DoCmd.OpenForm "frmContactSummary", WhereCondition:=varWhere
> > ' Make sure focus is on contact summary
> > Forms!frmContactSummary.SetFocus
> > Else
> > ' Show the full contacts info filtered
> > DoCmd.OpenForm "frmContacts", WhereCondition:=varWhere
> > ' Make sure focus is on contacts
> > Forms!frmContacts.SetFocus
> > End If
> > End If
> >
> > ' Done
> > DoCmd.Close acForm, Me.Name
> > ' Clean up recordset
> > rst.Close
> > Set rst = Nothing
> >
> > End Sub
> > ------------------------------------------
> >
> > In a couple of the examples above, the code builds a filter using a subquery
> > because the table containing the filter value isn't in the Record Source of
> what
> > I'm filtering.
> >
> > Note that Date/Time literal values must be surrounded with # and Text
literal
> > values must be surrounded by either single or double quotes.
> >
> > Hope that helps...
> >
> > John Viescas, author
> > Microsoft Office Access 2010 Inside Out
> > Microsoft Office Access 2007 Inside Out
> > Building Microsoft Access Applications
> > Microsoft Office Access 2003 Inside Out
> > SQL Queries for Mere Mortals
> > http://www.viescas.com/
> > (Paris, France)
> >
> >
> >
> > -----Original Message-----
> > From: MS_Access_Professionals@yahoogroups.com
> > [mailto:MS_Access_Professionals@yahoogroups.com] On Behalf Of nkpberk
> > Sent: Sunday, May 22, 2011 8:12 PM
> > To: MS_Access_Professionals@yahoogroups.com
> > Subject: [MS_AccessPros] User selection of multiple parameters to print
> reports
> >
> > Hello Group;
> > I have progressed to the point where I want to generate reports (same basic
> > report) to multiple parameters selected by the user. I have made a form with
> > combo boxes to select the parameter for each field, how do I create a filter
> > base on the choices in the combo boxes and ignore the boxes with no choice
> made.
> > The report uses the same table for all reports just the selection criteria
> > changes by 1 or more parameters.
> > I have a command button to open the report and I don't know how to format
the
> > filter.
> > Walter Griffin
> >
> >
> >
> > ------------------------------------
> >
> > Yahoo! Groups Links
> >
>
>
>
>
> ------------------------------------
>
> Yahoo! Groups Links
>

------------------------------------

Yahoo! Groups Links

__._,_.___
Recent Activity:
MARKETPLACE

Stay on top of your group activity without leaving the page you're on - Get the Yahoo! Toolbar now.


Get great advice about dogs and cats. Visit the Dog & Cat Answers Center.

.

__,_._,___

Tidak ada komentar:

Posting Komentar