problme with script for printing

stephengrenfell

Registered User.
Local time
Today, 17:05
Joined
Jul 1, 2009
Messages
19
Hello,

I have a VBA script that selects records from the table tblInv where the value of tblInv.InvSendEmail=True and then sends the value of InvNum to the rptInv for each selected record.

I am a bit bogged down with the SQL syntax. I get an Error 3131 "syntax error in FROM clause.."

Any help apprciated.

Thanks.

Here is the code:

Private Sub cmdPrintInvoices_Click()
' Error handler
On Error GoTo cmdPrintInvoices_error
Dim rst As DAO.Recordset

Const PrintInvoiceQuery As String = "SELECT [InvNum]" & "FROM tblInv" & "WHERE tblInv.InvSendEmail=True"

' Get a recordset using the query
Set rst = CurrentDb.OpenRecordset(PrintInvoiceQuery, dbOpenSnapshot)

' Move through the recordset looking at each record
With rst
Do While Not .EOF

' Open report.
DoCmd.OpenReport "rptInv", acViewNormal, , "InvNum = ![InvNum]"

.MoveNext
Loop
End With

rst.Close
Set rst = Nothing

exit_cmdPrintInvoices_error:
Exit Sub

cmdPrintInvoices_error:
MsgBox "Error " & Err & "." & Chr(13) & Chr(10) & Chr(10) & Err.Description & ".", vbExclamation
Resume exit_cmdPrintInvoices_error
End Sub
 
Thanks for your prompt reply.

debug.print PrintInvoiceQuery doesn't show anything.. whereever I put it..

Error 3131 says there is a syntax error in the FROM clause in the line

Const PrintInvoiceQuery As String = "SELECT [InvNum]" & "FROM tblInv" & "WHERE tblInv.InvSendEmail=True"

If the value of PrintInvoiceQuery is NULL then would debug.print PrintInvoiceQuery do anything ?.

Am I doing something stupid ?..


Thanks
 
Code:
Dim PrintInvoiceQuery As String
PrintInvoiceQuery  = "SELECT [InvNum]" & "FROM tblInv" & "WHERE tblInv.InvSendEmail=True"
debug.print PrintInvoiceQuery
 
You need a space between [InvNum]" & "FROM.
Putting a space between the quote and FROM should work.
 
inserting a space before FROM and after tblInv produces this string (using Debug.Print PrintInvoiceQuery)

SELECT [InvNum] FROM tblInv WHERE tblInv.InvSendEmail=True

However it now seems there is no value for ![InvNum] passed to the rptInv report since it prompts for a value.

If I remove the exclamation mark just in front of [InvNum]. Like this:

DoCmd.OpenReport "rptInv", acViewNormal, , "InvNum = [InvNum]"

then the report selects all records in the tblInv table and not only the ones with InvSendEmail=True

Thanks again for your prompt responses.
 
I don't think the problem is with the DoCmd.OpenReport

Because if I use the following

DoCmd.OpenReport "rptInv", acViewNormal, , "InvNum = ![InvNum]"

Then it prompts for the value of !InvNum and if I enter a valid value the record is printed correctly - which implies the DoCmd.OpenReport is working but is not being passed values for InvNum.

If I remove the exclamation mark just in front of [InvNum] then it prints all the records in the tblInv table. What does the presence of the exclamation mark do ?.

Which suggests that either the WHERE is doing nothing and all records are being selected, or there is something wrong with the way the InvNum values are being passed from rst Recordset.

Any suggestions ?.
 
Correct. Your WHERE does nothing.

Study very carefully the examples in the link provided for HOW you construct the WHERE in the DoCmd.OpenReport
 
Ah.. so the filtering must be applied in the DoCmd.OpenReport and not in the CurrentDb.OpenRecordset querry.

Changing the DoCmd.OpenReport does indeed only select the records with tblInv.InvSendEmail=True. However it seems to go around the loop and "infinite" number of times and not drop out after 1 loop.

Here's the revised code for reference:

Code:
Private Sub cmdPrintInvoices_Click()

    ' Error handler
    On Error GoTo cmdPrintInvoices_error

    Dim rst As DAO.Recordset
    
    Const PrintInvoiceQuery As String = "SELECT [InvNum]" & " FROM tblInv "
    Debug.Print PrintInvoiceQuery
  
    ' Get a recordset using the query
    
    Set rst = CurrentDb.OpenRecordset(PrintInvoiceQuery, dbOpenSnapshot)
    
    
    ' Move through the recordset looking at each record
    With rst
        Do While Not .EOF
               
           ' Open report.
           'Debug.Print [InvNum]
        DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvSendEmail=True", , "InvNum = ![InvNum]"
            
            .MoveNext
        Loop
    End With
    
    rst.Close
    Set rst = Nothing
    
exit_cmdPrintInvoices_error:
    Exit Sub
    
cmdPrintInvoices_error:
    MsgBox "Error " & Err & "." & Chr(13) & Chr(10) & Chr(10) & Err.Description & ".", vbExclamation
    Resume exit_cmdPrintInvoices_error
End Sub
 
Your DOCmd.OpenReport WHERE is still unchanged (and incorrect). Come back when you have changed it.
 
Below is a revised version.

The tblInv.InvSendEmail=True part of the WHERE in the DoCmd.OpenReport seems to work as it only selects records that have InvSendEmail=True.

However all the records that have InvSendEmail=True are printed many many times. What I need is that they are printed once.

It would seem that the AND tblInv.InvNum=[InvNum] part of the WHERE in the DoCmd.OpenReport does not do anything.

As the Do While Not .EOF Loop executes is the value of [InvNum] changing each time ?. Or is the tblInv.InvNum=[InvNum] not correct ?.

Thanks again for your help and patience.

Code:
Private Sub cmdPrintInvoices_Click()
    ' Error handler
    On Error GoTo cmdPrintInvoices_error
    Dim rst As DAO.Recordset
    
    Const PrintInvoiceQuery As String = "SELECT [InvNum]" & " FROM tblInv "
    Debug.Print PrintInvoiceQuery
  
    ' Get a recordset using the query
    
    Set rst = CurrentDb.OpenRecordset(PrintInvoiceQuery, dbOpenSnapshot)
    
    
    ' Move through the recordset looking at each record
    With rst
        Do While Not .EOF
            
           ' Open report.
           DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvSendEmail=True AND tblInv.InvNum=[InvNum]"
            
            .MoveNext
        Loop
    End With
    
    rst.Close
    Set rst = Nothing
    
exit_cmdPrintInvoices_error:
    Exit Sub
    
cmdPrintInvoices_error:
    MsgBox "Error " & Err & "." & Chr(13) & Chr(10) & Chr(10) & Err.Description & ".", vbExclamation
    Resume exit_cmdPrintInvoices_error
End Sub
 
It seems that each time the DoCmd.OpenReport is executed all the records that match the tblInv.InvSendEmail=True cirteria are printed once. This is repeated for each pass of the Do While Not .EOF .... Loop

I need it to print only one record that matches both the tblInv.InvSendEmail=True AND tblInv.InvNum=[InvNum]cirteria each for each pass of the Do While Not .EOF .... Loop.

I could just remove the Do While Not .EOF .... Loop if I only wanted one copy of each selected record.

But I need to add an additional criteria that controls the number of copies depending on the value of tblCust.LivState. Modifying the DOCmd.OpenReport WHERE to tblInv.InvSendEmail=True AND tblCust.LivState='CHE' AND tblInv.InvNum=[InvNum] ; does indeed only select the records that match tblInv.InvSendEmail=True AND tblCust.LivState='CHE' but of course they are printed once for each iteration of the Do While Not .EOF .... Loop. If I can solve this problem and only print the selected record that matches tblInv.InvSendEmail=True AND tblCust.LivState='CHE' AND tblInv.InvNum=[InvNum] once I could add additional DoCmd.OpenReport stateemnts for each copy (it needs to print 5 copies if tblCust.LivState='CHE' or 2 copies if tblCust.LivState!='CHE')

Hope this makes sense.

Thanks again for your help.
 
Solved (Re: problme with script for printing)

I soved my problem. Apart from the syntax of the WHERE part of the DoCmd.OpenReport there was another fundamental problem. I should have been selecting the correct records in VBA before the DoCmd.OpenReport otherwise each non valid record throws up a "No record matches the selected criteria".

Thanks agian for your help.

Here is a copy of the working code:

Code:
Private Sub cmdPrintInvoices_Click()

    ' Error handler
    On Error GoTo cmdPrintInvoices_error

    Dim rst As DAO.Recordset
    Dim InvoiceNum As String
    Dim CustNum As String

    Const PrintInvoiceQuery As String = "SELECT [InvNum], [InvSendEmail], [InvCustNum] " & " FROM tblInv "
    ' Get a recordset using the query
    Set rst = CurrentDb.OpenRecordset(PrintInvoiceQuery, dbOpenSnapshot)
    ' Move through the recordset looking at each record
    With rst
        Do While Not .EOF
           ' select InvNum from OpenRecordSet
           InvoiceNum = rst.Fields("InvNum")
           ' check if InvSendEmail is true for this record
           If rst.Fields("InvSendEmail") = True Then
                ' Open report.
                DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvNum=" + InvoiceNum
                DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvNum=" + InvoiceNum
                ' select InvCustNum from OpenRecordSet
                CustNum = rst.Fields("InvCustNum")
                ' check if LivState = CHE for this customer
                If DLookup("LivState", "tblCust", "CustNum = " + CustNum) = "CHE" Then
                                DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvNum=" + InvoiceNum
                                DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvNum=" + InvoiceNum
                                DoCmd.OpenReport "rptInv", acViewNormal, , "tblInv.InvNum=" + InvoiceNum
                End If
                
           End If
            .MoveNext
        Loop
    End With
    
    rst.Close
    Set rst = Nothing
    
exit_cmdPrintInvoices_error:
    Exit Sub
    
cmdPrintInvoices_error:
    MsgBox "Error " & Err & "." & Chr(13) & Chr(10) & Chr(10) & Err.Description & ".", vbExclamation
    Resume exit_cmdPrintInvoices_error
End Sub
 

Users who are viewing this thread

Back
Top Bottom