Consulting

Results 1 to 15 of 15

Thread: VBA for mail merge

  1. #1

    Question VBA for mail merge

    Can anyone advice me how I use VBA to save a mailmerged document.

    My manual process is to :

    1.Open my source file with that contains the merge field data.
    2.Open my mail merge main document.
    3.Select the merge to new document icon.
    4.save the new doc to a new location and name.

    The location and name are both in the document as a inserted merge field.

    can this be automated to pick up these fields and save the file?

    The location and name are not ever the same.

    Thanks

  2. #2
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84
    Quote Originally Posted by baillieston
    ____________________________
    Can anyone advice me how I use VBA to save a mailmerged document.

    can this be automated to pick up these fields and save the file?

    Hi, Baillieston!

    I just want to let you know that I am working on your idea right now. I read your question for the first time today (july 15), and I feel pretty confident that I can write the macro you need. However, it may take me a day or two.

    So if you can wait for a few days, I will be back with an answer.

    Or, perhaps someone else will come and answer before me!! Either way, if you just hang in there you are sure to get the answer you need.

    I'll be back by monday at the latest with a macro for you to try.

    Cheers!
    Kelly

  3. #3
    Hi Kelly,

    I look forward to trying out your code.
    Thanks for your help.

    Baillieston.

  4. #4
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84

    Mail Merge Macro - version 1

    The mail merge macro is attached below as Demo_MailM_Macro_v1.doc.zip

    phwew!

    Well, I have finished my FIRST version of the macro. (I have ideas on how to alter it to make a SECOND or even third version(s), but this first version should be good for testing.)

    Now I am faced with the challenge of explaining it!!!

    Actually, it should be fairly user-friendly, but due to the issues at stake in a mail merge, I need to clarify certain points.

    Important Notes:

    • this macro (version 1) is designed to produce merged "Form Letters" (Therefore, if envelopes or something else were desired, alterations to the macro would be necessary)

    • the resulting new document will be saved in regular Word doc format (therefore, if it were necessary to save the resulting merged output as some other file - such as txt or rtf - then changes would be needed)

    • this macro assumes that the FIELDS that specify the path/location and the name (file name) for the final SAVE are named:
      • Location_To_Save
      • and
      • Name_To_Save
      (The macro could easily be changed so that it would look for other fields)

    Now for some directions.

    First, I recommend downloading the zipped file Demo_MailM_Macro_v1.doc.zip

    _______________________________________________
    For those who don't download anthing ever... I will post the entire macro code at the end of this message. If you use the code from this forum thread without downloading the file, then you could paste the code into a module as part of the "Normal" template or into a module of any file, BUT BUT BUT .... when you run the macro, you NEED TO HAVE your MAIN mail merge document as the ACTIVE DOCUMENT. The macro itself will warn you about this with a MsgBox)
    _______________________________________________


    The method of downloading the file has the following important advantage:

    • The document in the download ***IS*** the main merge document in addition to being just a 'vehicle' for downloading the macro
    In other words, by downloading the document, you will get almost everything you need to simply run the macro straight away.

    This is what the document will look like:


    As you can see, some fields are already inserted for you!

    (If the image above is broken then check the attachments below)

    One more important step: Your data source file
    I have also attached a sample data source to this forum thread. If you don't wish to download the data source file I have provided, then you MUST create your own. Obviously, the macro won't work without a source file. So, if you decide to create your own, then please look at the photograph below to see what you need to include:



    (If the image is broken, then please get the GIF from the attachments below)

    YOU MAY SAVE THE DATA SOURCE FILE ANYWHERE ON YOUR COMPUTER. THE MACRO WILL PROMPT YOU FOR ITS LOCATION.

    Once you have the macro, the main merge file (included in Demo_MailM_Macro_v1.doc.zip), and a data source file (see below: MyDataSourceFile.doc.zip) then run the macro.

    At first glance, the macro may not seem much more efficient than the usual process of clicking around on the built-in MS Word "Mail Merge Helper" box. However, the ultimate goal of this macro (at least for baillieston) is to avoid having to even specify the location of the data source file.

    SO... To Baillieston (or to others who are interested) ... let me know if this VERSION ONE macro works. Assuming that the process in general is working and running smoothly, then all we have to do is REMOVE the part of the macro that prompts for the location of the data source. Then, we would include some internal code within the macro that basically sets the location of the data source as a constant.

    That way, the user would only see one initial message confirming that the active doc is the main doc, and then the macro would run and finish without any further need for clicks or other interaction.

    ADDITIONALLY... extra code could be added onto the END of the macro to automatically close one or more documents, or print them, or whatever else we desire.

    Okay!!! I invite anyone and everyone to try this macro out and post back to me. Please feel free to post anything: questions, critiques, suggestions, ideas....

    Thanks, all!
    -Kelly


    The mail merge macro is attached below as Demo_MailM_Macro_v1.doc.zip

  5. #5
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84
    The data source file is attached below

  6. #6
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84
    The first screen shot is attached below

  7. #7
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84
    The second screenshot is attached below

  8. #8
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84

    Mail Merge Macro VERSION ONE - VBA CODE

    [vba]Sub Mail_Merge_Macro_July_2004()

    Dim CorrectDocTrue As Byte
    'Initial confirmation to make sure user wants to begin with current doc
    Dim MyDocWithFields As String
    'Remember the name of the original MAIN merge doc
    Dim YesNoCancelled As Byte
    'Result of a msgbox informing the user of the process and giving a chance to cancel
    Dim anOpenFileDialog As Dialog
    'an object used to display the "open file" built-in dialog
    Dim TryAgain As Byte
    'Result of a msgbox that appears if the user did not choose a file to open
    Dim Name_of_Source As String
    'the name of the file that the user chose in the "open file" dialog
    Dim FileToSave As String
    'the complete file name and path retrieved from the correct MERGE FIELDS in the data source file
    Dim PathOfFileToSave As String
    'the path only of FileToSave. the path and file names are retrieved from MERGE FIELDS
    Dim NameToSave
    'the file name only (not the path) retrieved from the correct MERGE FIELD

    '************************************************************************** *
    '******BEGIN WITH SOME MESSAGES TO THE USER - BELOW ************************

    Beep

    CorrectDocTrue = MsgBox("Is -- " & ActiveDocument.Name & " -- the desired" & vbCr & vbCr _
    & """Mail Merge Main Document?""", vbYesNoCancel + vbQuestion, ActiveDocument.Name & " - Mail Merge")

    If CorrectDocTrue = vbCancel Then
    Exit Sub
    End If

    If CorrectDocTrue = vbNo Then
    MsgBox "You must have your desired ""Mail Merge Main Document""" & vbCr _
    & "open and active before running this macro." & vbCr & vbCr _
    & "Open and/or make your main merge document the active" & vbCr _
    & "window and then run the macro again.", vbInformation, "Mail Merge Macro - Please Try Again"
    Exit Sub
    End If

    MyDocWithFields = ActiveDocument.Name

    If ActiveDocument.MailMerge.Fields.Count = 0 Then
    MsgBox "There are no Mail Merge Fields in the current document." & vbCr & vbCr _
    & "Before trying again, please do one of the following:" & vbCr & vbCr & _
    vbTab & "-Add Mail Merge Fields to " & MyDocWithFields & vbCr & vbCr & _
    vbTab & vbTab & "OR" & vbCr & vbCr & vbTab & "-Choose another doc and run the macro from there " _
    & vbCr & vbCr & "REMEMBER:" & vbCr & _
    "You must have your desired ""Mail Merge Main Document""" & vbCr _
    & "open and active before running this macro.", vbExclamation, "Mail Merge Macro Failed"
    End
    End If

    YesNoCancelled = MsgBox("Let's begin!" & vbCr & vbCr & "Once you click ""OK,"" you will see an Open File" & vbCr & vbCr _
    & "dialog box. Please find and select your DATA SOURCE file.", vbOKCancel, "Mail Merge Macro - Begin")

    If YesNoCancelled = vbCancel Then
    MsgBox "You did not click OK." & vbCr & vbCr & "The macro has been ended.", vbExclamation, "Mail Merge Macro ENDED"
    Exit Sub
    End If


    '********USE BUILT-IN DIALOG SO USER CAN LOCATE DATA SOURCE FILE**********

    GetDataSource:

    Set anOpenFileDialog = Dialogs(wdDialogFileOpen)

    anOpenFileDialog.Display

    If anOpenFileDialog.Name = "" Then

    TryAgain = MsgBox("No file was specified." & vbCr & vbCr _
    & "Would you like to try again?" & vbCr & vbCr _
    & "(choose cancel to quit)", vbOKCancel + vbExclamation, "Mail Merge Macro - No File Chosen")

    If TryAgain = vbCancel Then
    Exit Sub
    Else
    GoTo GetDataSource
    End If

    End If

    Name_of_Source = CurDir & "\" & anOpenFileDialog.Name

    ActiveDocument.MailMerge.MainDocumentType = wdFormLetters

    ActiveDocument.MailMerge.OpenDataSource Name:= _
    Name_of_Source


    '*****RETRIEVE SAVE-TO LOCATION AND NAME FROM THE MERGE FIELDS***********

    On Error Resume Next
    FileToSave = Trim(Documents(MyDocWithFields).MailMerge.DataSource.DataFields("Location_T o_Save").Value)
    If Err.Number <> 0 Then ErrorHandle Err.Number, "Location_To_Save", Name_of_Source
    On Error GoTo 0

    If Right(FileToSave, 1) <> "\" And Right(FileToSave, 1) <> "/" Then
    FileToSave = FileToSave & "\"
    End If

    PathOfFileToSave = FileToSave

    On Error Resume Next
    NameToSave = Trim(Documents(MyDocWithFields).MailMerge.DataSource.DataFields("Name_To_Sa ve").Value)
    If Err.Number <> 0 Then ErrorHandle Err.Number, "Name_To_Save", Name_of_Source
    On Error GoTo 0

    FileToSave = FileToSave & NameToSave & ".doc"


    '*******PERFORM THE MERGE AND SAVE NEW DOC**************

    Application.DisplayAlerts = wdAlertsNone

    With ActiveDocument.MailMerge
    .Destination = wdSendToNewDocument
    With .DataSource
    .FirstRecord = wdDefaultFirstRecord
    .LastRecord = wdDefaultLastRecord
    End With
    .Execute Pause:=True
    End With

    Application.DisplayAlerts = wdAlertsAll

    On Error Resume Next

    ActiveDocument.SaveAs FileName:=FileToSave, FileFormat:=wdFormatDocument

    If Err.Number = 5153 Then
    MsgBox "CANNOT SAVE """ & ActiveDocument.Name & """ AS" & vbCr _
    & vbCr & """" & NameToSave & """ BECAUSE THERE IS ALREADY" & vbCr & vbCr _
    & "ANOTHER ACTIVE DOCUMENT NAMED """ & NameToSave & ".""" & _
    vbCr & vbCr & "Please manually save """ & ActiveDocument.Name & ".""", vbExclamation, "Mail Merge Macro - Save Failed"
    Err.Clear
    End
    End If

    If Err.Number = 5156 Or Err.Number = 5152 Then
    MsgBox "There was an error with the directory location for saving the file." & vbCr & vbCr & _
    "The data source file specifies to save to: " & vbCr & vbCr & _
    vbTab & PathOfFileToSave & vbCr & vbCr & _
    "The specified directory and/or drive could not be found on this computer." & vbCr & vbCr & _
    "Please save """ & ActiveDocument.Name & """ manually.", vbExclamation, "Mail Merge Macro - Save Failed"
    Err.Clear
    End
    End If

    On Error GoTo 0

    MsgBox "Success!" & vbCr & vbCr & """" & MyDocWithFields & """ and """ & anOpenFileDialog.Name & """" & vbCr & _
    "were merged to a new document. The new document was saved as:" & vbCr & vbCr & _
    vbTab & FileToSave, vbInformation, "Mail Merge Macro - Complete"

    End Sub

    Sub ErrorHandle(myData As Integer, myField_inQuestion As String, SourceFile As String)

    MsgBox "The data source file (" & SourceFile & ")" & vbCr & _
    "does not contain a field named: " & myField_inQuestion & vbCr & vbCr & _
    "This macro requires that the data source file contain" & vbCr & _
    "the following fields:" & vbCr & vbCr & _
    vbTab & "Location_To_Save (containing a directory path)" & vbCr & _
    vbTab & "Name_To_Save (containing a file name)" & vbCr & vbCr & _
    "Please select or create an appropriate data source file and try again.", vbExclamation, "Mail Merge Macro Failed"
    End

    End Sub
    [/vba]

  9. #9
    Hi Kelly,

    This looks great and looks like you have put a lot of work into it, the instructions are fab.

    But......... I can't run the macro as it comes up with an error saying something like below.

    "The macros in this project are disabled. Please enable"

    I can't work out how to enable them.

    I have clicked the option to allow macros but it still errors.

    Is this something that you need to change or do I need to change something?

    Thanks in advance.
    Baillieston.

  10. #10
    Site Admin
    Urban Myth
    VBAX Guru
    Joined
    May 2004
    Location
    Oregon, United States
    Posts
    4,940
    Location
    Tools -> Macros -> Security. Ensure anything below High. If using 2003, trusted macros will work, just ensure that it's specified as trusted. Save, try again. HTH

  11. #11
    Site Admin
    The Princess
    VBAX Guru Anne Troy's Avatar
    Joined
    May 2004
    Location
    Arlington Heights, IL
    Posts
    2,530
    Location
    Kell: Are you for hire?
    That's a SERIOUS question.
    I may have a project lead for you.
    ~Anne Troy

  12. #12
    VBAX Regular Kelly's Avatar
    Joined
    Jun 2004
    Location
    Los Angeles, California
    Posts
    84
    Ballieston,

    Thank you for your kind words.

    I am crossing my fingers for you.

    HOPEFULLY, the problem is that (for some stupid reason) it does no good to "Macro -> Security" and change the settings once you have already opened the document.

    I hope that if you change the security settings and then close down word and start all over again... then hopefully it will all work.

    But I wonder,... Hey Firefyter!! Hey Dreamboat!! Were you guys able to get it to work???

  13. #13
    Site Admin
    Urban Myth
    VBAX Guru
    Joined
    May 2004
    Location
    Oregon, United States
    Posts
    4,940
    Location
    Yup, worked great for me. Running Win XP w/ Office XP.

  14. #14
    Moderator VBAX Wizard lucas's Avatar
    Joined
    Jun 2004
    Location
    Tulsa, Oklahoma
    Posts
    7,323
    Location
    Worked great for me also. Win XP Office 2000
    Steve
    "Nearly all men can stand adversity, but if you want to test a man's character, give him power."
    -Abraham Lincoln

  15. #15

    Smile Works great

    Hi Kelly,

    This works great now after your suggestion, the macro does exactly as I wished. Sorry it has taken so long to reply, but i have been moved to a new job and not had the chance to try it out. Would it be okay to add to this post when I am next back in the same job where I wanted to use this? Then I can ask for help with your suggestion below.

    "then all we have to do is REMOVE the part of the macro that prompts for the location of the data source. Then, we would include some internal code within the macro that basically sets the location of the data source as a constant.

    That way, the user would only see one initial message confirming that the active doc is the main doc, and then the macro would run and finish without any further need for clicks or other interaction. "

    "ADDITIONALLY... extra code could be added onto the END of the macro to automatically close one or more documents, or print them, or whatever else we desire."

    In the meantime thanks for everything, I have learned a lot by reading your code and explanations.

    Good luck
    Baillieston



Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •