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 Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Create a Query that Returns one Record

Status
Not open for further replies.

Centurin

IS-IT--Management
Oct 19, 2008
7
0
0
US
Hi guys,

I'm trying to make a Mail Merge document in Word using a form on my database. I've looked at faq181-271 and faq181-28. What I want to do is simply have a command button that uses data from the current record in my form to create a word document using mail merge.

The Faq recommends to make a query for the mail merge. My question is how do I setup the query to return only the current record? For example, when the user presses the command button, only the currently viewed record is mail merged. I know this is a fairly simple question, so I apologize. Any help is appreciated. Thanks.
 
You can set the query to reference the form. For example, you can type into the criteria line something on the lines of:

= Forms!frmPeople!PersonID

As an aside, this: is the best way to mailmerge, as far as I am concerned. With very little effort, it gets around nearly all the problems involved in linking a document directly to Access.
 
In that faq, it stated usage as

Private Sub cmdPrintInvoice_Click()
RunMailmerge "SELECT * FROM qryInvoicesFormatted " & _
"WHERE CustID = " & txtCustID.Value & _
" AND SaleDate = #" & _
Format(txtSaleDate.Value, "mm/dd/yyyy") & _
"#", "exInvoice", "invoice.doc"
End Sub

I more or less want to merge all the fields from the form. I see the code above is referencing a query which I can easily do. But would I have to include every field as part of the SELECT or is there a way to simply have it output everything from the query?
 
Do you know what is the meaning of the star in SELECT * FROM ?

Hope This Helps, PH.
FAQ219-2884
FAQ181-2886
 
Select *
Means select all fields from the query

WHERE CustID = " & txtCustID.Value
Means only select records that match the current record CustID. This would generally be the key field.

AND SaleDate = #" & _
Format(txtSaleDate.Value, "mm/dd/yyyy") & _
Illustrates the inclusion of another parameter.
 
Remou - I would think the "best way" to do mail merge is within Access itself.
Just create a new report. Click on the Detail Bar. On the property sheet make Force New Page show After Section. Using textboxes, format your letter, eg. the control source would look like: ="Dear " & [Fname] & " :" etc.

Straight forward and no coding. Grant you, no one uses this little trick.
 
fneily, that is certainly the best way :) However, the advantage of Word is that users get to mess around, which is something users usually like to do.
 
I have a couple questions about setting this up. In the fact is says I need: 1) a working text export specification, 2) a sample text file containing data using those specific fields, and of course, 3) a Word mailmerge document.

I found a guide to creating a text export spec, but I'm not sure if the query I make for it needs to return one record, or all the records.

Second, I'm assuming I have to specify the name of the sample text file and the mail merge doc. I see in the usage code where it specifies the Doc, but not the sample text file.

Any help in setting this up is appreciated. Thanks
 
Also, this part of the code,

'these are the listing of the export specifications.
Public Const exExampleSpec1 As String = "exSpec1"
Public Const exExampleSpec2 As String = "exSpec2"

is giving me an error stating constants, fixed-length strings, arrays, user-defined types, and declare statements are not allowed as Public statements in object models.
 
The export spec can be created using one record. The text file is named in the code using date and time, so you do not need to supply a name.

Here is a simplified version of PSeale's code. It is also less general, so cannot be as widely applied in its current state.

Code:
Option Compare Database
Option Explicit

Public Sub RunMailmerge(SQL As String, Optional MergeTemplate As String = "")
'MergeTemplate is the full path and name of a Word template file (.dot)

On Error GoTo Sub_Error
    Dim objWordDoc As Object 'Word.Document
    Dim strMailmergeDataFilename As String
    Dim strMergeDocumentFilename As String
    Dim strSaveDirectory As String
    Dim fs
    
    'The name of the folder where the files will be created. This folder
    'will be created if it does not exist.
    strSaveDirectory = CurrentProject.Path & "\WordFiles\"
    
    'The name of the file to hold the data (.txt) and the nanme of the
    'merge document (.doc)
    strMailmergeDataFilename = strSaveDirectory & Format(Now, "yymmdd_hhnnss") & ".txt"
    strMergeDocumentFilename = strSaveDirectory & Format(Now, "yymmdd_hhnnss") & ".doc"
    
    Set fs = CreateObject("Scripting.FileSystemObject")
    
    If Not fs.FolderExists(strSaveDirectory) Then
        fs.CreateFolder (strSaveDirectory)
    End If
    
    'Export the query to a CSV, see code below
    If ExportSQLToCSV(SQL, strMailmergeDataFilename) <> True Then
        GoTo Sub_Exit
    End If
    
    If MergeTemplate <> "" Then
        'If a template has been supplied, get a Word document
        'using that template ...
        Set objWordDoc = GetObject(MergeTemplate, "Word.Document")
    Else
        'Otherwise, just get a Word document
        Set objWordDoc = GetObject("", "Word.Document")
    End If
    
    'Make it visible.
    objWordDoc.Application.Visible = True
    
    'Open the data source, ie the .txt file
    'Format:=0 '0 = wdOpenFormatAuto
    objWordDoc.Mailmerge.OpenDataSource _
        Name:=strMailmergeDataFilename, ConfirmConversions:=False, _
        ReadOnly:=False, LinkToSource:=True, AddToRecentFiles:=False, _
        PasswordDocument:="", PasswordTemplate:="", WritePasswordDocument:="", _
        WritePasswordTemplate:="", Revert:=False, Format:=0, _
        Connection:="", SQLStatement:="", SQLStatement1:=""

    'PSeale's code is nicely general and can be used anywhere, the code below cannot.
    'It assumes that you are building a letter and that the letter contains certain fields
    'It is not needed, if you supply a template (.dot) and from this comment to "****END"
    'it can be deleted or editied to show the fields in your query.
    If MergeTemplate = "" Then
        With objWordDoc.Application
            .Selection.TypeText Text:=vbCrLf & vbCrLf & vbCrLf & vbCrLf & vbCrLf & vbCrLf
            .Selection.TypeText Text:=Format(Date, "Long Date")
            .Selection.TypeText Text:=vbCrLf & vbCrLf
            .ActiveDocument.Mailmerge.EditMainDocument
            .ActiveDocument.Mailmerge.Fields.Add Range:=.Selection.Range, Name:="Contact"
            .Selection.TypeParagraph
            .ActiveDocument.Mailmerge.Fields.Add Range:=.Selection.Range, Name:="Company"
            .Selection.TypeParagraph
            .ActiveDocument.Mailmerge.Fields.Add Range:=.Selection.Range, Name:="Address"
            .Selection.TypeParagraph
            .Selection.TypeParagraph
            .Selection.TypeText Text:="Dear "
            .ActiveDocument.Mailmerge.Fields.Add Range:=.Selection.Range, Name:="Dear"
        End With
    End If
    '****END
    
    'Uncomment the next two lines if you want the mailmerge to run automatically
    'objWordDoc.MailMerge.Destination = 0 '0 = wdSendToNewDocument
    'objWordDoc.MailMerge.Execute
    
Sub_Exit:
On Error Resume Next
    'Word pops up a messagebox to confirm saving the document,
    'even if specifically set it to "wdDoNotSaveChanges".
    'Therefore first save the document, then close it.
    'objWordDoc.Save
    'objWordDoc.Close SaveChanges:=-1 '-1 = wdSaveChanges
    
    Set objWordDoc = Nothing
    'attempt to delete file, silently fail on errors.
    'FileSystem.Kill strMailmergeDataFilename
    
    Exit Sub
    
Sub_Error:
    MsgBox Err.Description
    Resume Sub_Exit
End Sub


Function ExportSQLToCSV(SQL As String, FullPathAndFilename As String) As Boolean
On Error GoTo Sub_Error
    'steps:
    '-create a new querydef with the SQL parameter as its SQL.
    'save & attach this querydef.
    'run the TransferText on this temp querydef,
    'delete the querydef
    
    Dim strQDFName As String
    Dim strErrMessage As String
    Dim db As DAO.Database
    Dim qdf As DAO.QueryDef
    
    ExportSQLToCSV = False
    
    strQDFName = "~temp_mailmerge_" & Format(Now, "yymmdd_hhnnss")

    Set db = CurrentDb
    Set qdf = db.CreateQueryDef(strQDFName, SQL)
    Set qdf = Nothing
    Set db = Nothing
    
    If DCount("*", strQDFName) <= 0 Then
        'in this case, if the query is empty/contains no entries, we
        'should pop up a custom error message.  Basically we shouldn't attempt to
        'run the mailmerge if there's no data anyway, right?
        'So we have to turn off the standard error handling, delete the query (otherwise
        'the query is not deleted), and raise the error.
        '
        'the calling function "RunMailmerge" will catch and handle the error, and then
        'gracefully exit.
        On Error GoTo 0
        CurrentDb.QueryDefs.Delete strQDFName
        strErrMessage = "The report has no data, and thus cannot properly merge."
        Err.Raise vbObjectError + 1024 + 2, "Query Export to CSV", strErrMessage
    End If
    
    AttemptToDeleteFile FullPathAndFilename
    DoCmd.TransferText acExportDelim, , strQDFName, FullPathAndFilename, True
    
    If Dir(FullPathAndFilename) <> "" Then ExportSQLToCSV = True
    
Sub_Exit:
On Error Resume Next
    CurrentDb.QueryDefs.Delete strQDFName
    
    Exit Function
    
Sub_Error:
    MsgBox Err.Description
    Resume Sub_Exit
End Function


'AttemptToDeleteFile -
'attempts to delete the mailmerge.txt file located in the database directory.
'Basically provides error-handling capabilities to the single "Kill" method call.

Private Sub AttemptToDeleteFile(strFilename As String)
On Error GoTo Sub_Error
    
    Kill strFilename
    
Sub_Exit:
    Exit Sub
    
Sub_Error:
    If Err.Number = 53 Then 'err 53 = file not found, that means the file is already deleted!
        'no error, continue
        Resume Sub_Exit
    ElseIf MsgBox("Cannot delete file.  Close all Word mailmerge documents and click Retry.", vbRetryCancel + vbExclamation, "File In Use") = vbRetry Then
        Resume
    Else
        On Error GoTo 0
        Err.Raise vbObjectError + 1024 + 1, "file in use", "File In Use@" & _
                    "Cannot complete the mailmerge process because the file '" & strFilename & "' " & _
                    "is in use.  Close all Word mailmerge documents and try again."
    End If
End Sub
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top