Consulting

Page 2 of 2 FirstFirst 1 2
Results 21 to 34 of 34

Thread: Solved: Excel VBA invokes Word

  1. #21
    MS Excel MVP VBAX Tutor
    Joined
    Mar 2005
    Posts
    246
    Location
    A good VBA reference would be Excel Power Programming by John Walkenbach.

    Using the mail merge interaction of Word and Excel is one way to do what you want, making multiple copies of a document, one per row if data in Excel. See
    http://word.mvps.org/FAQS/MailMerge/...AMailMerge.htm
    http://www.mvps.org/dmcritchie/excel/mailmerg.htm (and links at the end of the page)
    http://office.microsoft.com/en-us/ex...037601033.aspx
    http://j-walk.com/ss/excel/tips/tip92.htm

    You could use the bit of code I provided before to allow reuse of the bookmarks, or you could just close the Word document and reopen it to get a fresh copy. Or make a template, and create a new file based on the template for each row of the Excel worksheet.
    - Jon
    -------
    Jon Peltier, Microsoft Excel MVP
    Peltier Technical Services
    Tutorials and Custom Solutions
    http://PeltierTech.com
    _______

  2. #22
    VBAX Master
    Joined
    Jul 2006
    Location
    Belgium
    Posts
    1,286
    Location
    Quote Originally Posted by jwise
    The "destroyed bookmark" could be a problem since I will essentially be printing one document for each row in my spreadsheet. I am assuming this means that I must recreate the bookmark after I insert the cell (or text) in the document. There are around ten bookmarks, so what I hearing is insert text 1 at bookmark 1, put bookmark back, go to remaining 9 in sequence, then print the page.

    The other thought was just to "end nosave" Word. It just seemed that restarting Word for each row is a lot of overhead. This may not be a consideration in this realm. In the mainframe realm, I processed millions of records and this could be a big problem. Today there will be around 40 rows in this spreadsheet, and if it takes two minutes, that's no big deal. I am just accustomed to thinking in the old way... this old dog is returning to his ______.
    When you save your template to a different name (xxx-temp.doc) and close the doc, the original doc will remain intact because you have saved it to another name (so there is no need to restore the bookmarktext --- the way I used them ---). Print this and use kill command to delete file and begin with the new row. So for every row that needs to be done, open, fill in, save, print, close, kill.

    When you don't quit the Word object unitl the last row ??? What is the overhead. I think printing will take more time then processing those rows.

    Charlize

  3. #23

    Thanks again

    Thanks again to all who have posted in response to my questions.

    I have had an interruption in this project, and it will be a couple of days before I get back to this.

    I have always been a collector of reference texts, and I now have "Excel VBA for Dummies" and "Excel 2003 Power Programming with VBA (J. Walkenbach), "Professional Excel Development" (Bullen, Bovey, and Green), and "Excel Programming 2nd Edition" (Jinjer Simon). I like and have used all these texts. I do not plan on reading all of any one book; I bought them for reference purposes. I may decide to read all of the "Dummies" book because that is certainly my level. I have two more books on order by authors Linda Johnson and Juan Pablo Gonzalez (et al) which address Excel and Office integration more directly. I also have another Excel VBA text on order by Richard Shepherd which supposedly addresses the Excel object model in depth.

    In my "interrupt project" I am able to utilize much of the code I have written for this project. I was struggling with the technique to determine the "highlighted" row until I found the answer quite by accident in the Simon text. Is there a good reference text for finding this kind of information? For example, I need to know the last row that has any data in it.

    TIA

  4. #24
    MS Excel MVP VBAX Tutor
    Joined
    Mar 2005
    Posts
    246
    Location
    There isn't necessarily much sense in collecting more and more books on the same topic. For in-depth object model reference I find it better to use online help, lots of trial and error, and Google. The Excel 200X VBA Developer's Handbooks are pretty good for this as well, except for the 2003 version, which was cobbled togather by a different author who didn't really get it.

    I haven't seen the book by Linda and Juan Pablo; I have a different book by Simon which I'm not much impressed with.

    To find specific answers, try the book's index, then try Google.

    Google {excel last row}:
    Results 1 - 10 of about 1,220,000 for excel last row. (0.23 seconds)
    - Jon
    -------
    Jon Peltier, Microsoft Excel MVP
    Peltier Technical Services
    Tutorials and Custom Solutions
    http://PeltierTech.com
    _______

  5. #25
    VBAX Master Norie's Avatar
    Joined
    Jan 2005
    Location
    Stirling, Scotland
    Posts
    1,831
    Location
    One example of getting the last row.
    [vba]
    LastRow = ThisWorkbook.Worksheets("Sheet1").Range("A" & Rows.Count).End(xlUp).Row
    [/vba]
    Note this is only one example and there are various other methods which you'lll probably find if you try a search like Jon suggests.

  6. #26
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,443
    Location
    Quote Originally Posted by jwise
    Thanks again to all who posted. You are educating me.

    By "OOP requirements", I meant those somewhat strange statements like
    "Set XX as Object"
    etc. The strange is relative to someone who comes from a strictly procedural background (and mainframe at that). Sorry, but it just doesn't look like code. "N = N + 1" looks like code to an old asm programmer. There is nothing political in this at all. Perhaps I should be asking for a good OOP text reference. All of this was designed to give my advisors a clue as to my lack of OOP understanding.
    I don't think you need to worry to much about OOP in this context, but more about the language syntax.

    [vba]

    Set xx = New Object
    [/vba]

    is just in loading a variable, but in this case an object variable as against a numeric or string variable. It really is not that much different to

    [vba]

    N = 17
    [/vba]

    which originally we would have written as

    [vba]

    Let N = 17
    [/vba]

    the Let has just fallen intro dis-use.

    Quote Originally Posted by jwise
    The "destroyed bookmark" could be a problem since I will essentially be printing one document for each row in my spreadsheet. I am assuming this means that I must recreate the bookmark after I insert the cell (or text) in the document. There are around ten bookmarks, so what I hearing is insert text 1 at bookmark 1, put bookmark back, go to remaining 9 in sequence, then print the page.
    You could use a template, and just re-open that.

    Quote Originally Posted by jwise
    The other thought was just to "end nosave" Word. It just seemed that restarting Word for each row is a lot of overhead. This may not be a consideration in this realm. In the mainframe realm, I processed millions of records and this could be a big problem. Today there will be around 40 rows in this spreadsheet, and if it takes two minutes, that's no big deal. I am just accustomed to thinking in the old way... this old dog is returning to his ______.
    You should always try to keep the code effeicient, even on small jobs. Practising such techniques always makes it easier to apply when really necessary.

  7. #27
    Thanks again to all who have posted. You have been most helpful. I will do additional testing and get back with you. I have completed the other task. Now I have to enter 41 x 8 x 14 numbers into my "DATA" worksheet. Then I'll take on Word...

  8. #28

    Word/Excel formatting

    I'm back from my other task. Since I understand the objects a little better, I am getting to Word. The document was basically designed with blanks in it initially. These blanks were filled-in by the user once the calculations were made.

    The purpose of this project was to eliminate transcribing these numbers from Excel to the paper form, i.e. Excel would invoke Word and insert the numbers in the document and print it.

    The problem I'm encountering is that the inserted numbers do not have their Excel formatting, e.g. "12345" instead of "$12,345". How can I get this formatting into the fields?

    Second question: How do I leave a "hole" in the Word document for the data? When I insert this data, the print lines are extended and wrapped, thus the single page form spills into the next page. Perhaps this is an inappropriate question.

    TIA

  9. #29

    Invoking Word from XL

    Thanks to several responders, I was able to get the XL to Word print working... sort of. For some strange reason, it only works when I run it in the debugger. If I invoke it using "Alt-F8", the macro appears to work, but the Word page never prints. If I single-step it through the debugger,
    it works as advertised. This is XL2000 under XP Pro SP2 with 256mb memory.

    I am attaching the workbook, with the macro source and test data. Since there is a one attachment limit, I will post again with the Word document template. Please remember to update the code to point to the template.

    The basic problem is that I get no output from Word if I just run the macro. If I run the macro in the debugger using F8 "single step", it works as designed. To use this macro, you must SELECT a row (the one to print) BEFORE you invoke "prtOneRecap".

    FYI... All data is FICTIONAL.

    Perhaps some of you can spot my blunder in the code, so you can take a look here:

    [vba]
    Sub prtOneRecap()
    '
    ' prtOneRecap Prints one recap sheet. Code is basically the
    ' same as prtRecap, except that it prints only the
    ' selected row.

    Dim rcMsg As Integer
    Dim i As Integer

    Dim wrdApp As Word.Application
    Dim rngDoc As Word.Range
    Dim wrdDoc As Word.Document

    Dim sPropName As String
    Dim sMoYr As String
    Dim sInitials As String
    Dim sTotalOpIncome As String
    Dim sTotalGrossIncome As String
    Dim sGrossPotRent As String
    Dim sConcessions As String
    Dim sNetIncome As String
    Dim sActPercent As String
    Dim sPrePaid As String
    Dim sFutureRent As String
    Dim sAdjIncomeMonth As String
    Dim sAdjPercent As String
    Dim sDelinq As String
    Dim sPastDue As String

    On Error GoTo errHandler

    rcMsg = MsgBox("prtOneRecap Version1.0")

    Set CurrentRange = Selection

    i = CurrentRange.Row

    Set wrdApp = New Word.Application

    wrdApp.Visible = True

    Set wrdDoc = wrdApp.Documents.Open(FileName:="c:\chuck\New Monthly Recap.dot")

    Set rngDoc = wrdApp.ActiveDocument.Range(Start:=0, End:=400)
    '
    ' Repair the printable data.
    ' this means Word was printing "12345"
    ' when we wannted $12,345. There was
    ' also a problem with dates and percentages
    '

    sPropName = StrFix(Cells(i, 1), 44)
    sMoYr = StrFix(Format(Cells(i, 2), "mmm yy"), 12)
    sTotalOpIncome = StrFix(Format(Cells(i, 9), "$###,##0"), 20)
    sTotalGrossIncome = StrFix(Format(Cells(i, 10), "$###,##0"), 20)
    sGrossPotRent = StrFix(Format(Cells(i, 3), "$###,##0"), 20)
    sConcessions = StrFix(Format(Cells(i, 5), "$####,###0"), 20)
    sNetIncome = StrFix(Format(Cells(i, 11), "$###,##0"), 20)
    sActPercent = StrFix(Format(Cells(i, 13), "##.0#%"), 12)
    'sTotalOpIncome2 = sTotalOpIncome
    sPrePaid = StrFix(Format(Cells(i, 4), "$###,##0"), 12)
    sFutureRent = StrFix(Format(Cells(i, 7), "$###,##0"), 12)
    sAdjIncomeMonth = StrFix(Format(Cells(i, 12), "$###,##0"), 20)
    sAdjPercent = StrFix(Format(Cells(i, 14), "##.0#%"), 12)
    sDelinq = StrFix(Format(Cells(i, 6), "$###,##0"), 20)
    sPastDue = StrFix(Format(Cells(i, 8), "$###,##0"), 20)

    With wrdApp.ActiveDocument
    .Bookmarks("PropName").Range.Text = sPropName 'header line
    .Bookmarks("MoYr").Range.Text = sMoYr

    .Bookmarks("TotalOpIncome").Range.Text = sTotalOpIncome 'line 1
    .Bookmarks("TotalGrossIncome").Range.Text = sTotalGrossIncome

    .Bookmarks("GrossPotRent").Range.Text = sGrossPotRent 'line 2
    .Bookmarks("Concessions").Range.Text = sConcessions
    .Bookmarks("NetIncome").Range.Text = sNetIncome

    .Bookmarks("ActPercent").Range.Text = sActPercent 'line 3

    .Bookmarks("TotalOpIncome2").Range.Text = sTotalOpIncome 'line 5
    .Bookmarks("PrePaid").Range.Text = sPrePaid

    .Bookmarks("FutureRent").Range.Text = sFutureRent 'line 6
    .Bookmarks("AdjIncomeMonth").Range.Text = sAdjIncomeMonth
    .Bookmarks("AdjPercent").Range.Text = sAdjPercent

    .Bookmarks("Delinq").Range.Text = sDelinq 'line 7
    .Bookmarks("PastDue").Range.Text = sPastDue

    End With

    wrdApp.Application.PrintOut FileName:="", Range:=wdPrintAllDocument, Item:= _
    wdPrintDocumentContent, Copies:=1, Pages:="", PageType:=wdPrintAllPages, _
    Collate:=True, Background:=True, PrintToFile:=False, PrintZoomColumn:=0, _
    PrintZoomRow:=0, PrintZoomPaperWidth:=0, PrintZoomPaperHeight:=0

    Set rngDoc = Nothing 'Clean up Range

    Set wrdDoc = Nothing

    wrdApp.Quit savechanges:=False

    Set wrdApp = Nothing

    GoTo endIt

    errHandler:
    rcMsg = MsgBox("prtOneRecap- The error handler was entered!")

    Set rngDoc = Nothing

    Set wrdDoc = Nothing

    wrdApp.Quit savechanges:=False

    Set wrdApp = Nothing

    rcMsg = MsgBox("The error handler issued Quit!")

    endIt:
    End Sub [/vba]
    I am interested in general comments on this code as well since I am very new to this genre.

  10. #30

    Word template attachment for above

    To test the previously included macro, please use this template.

    I had to alter the document for file size considerations. I hope this still works. I had problems trying to zip the files, so I couldn't do that to beat the rules. Sorry... I also had to rename it. You will need to change the name back to ".dot" instead of ".doc"

    TIA

  11. #31
    VBAX Master
    Joined
    Jul 2006
    Location
    Belgium
    Posts
    1,286
    Location
    Put this after your printcommand [VBA]Application.Wait (Now + TimeValue("0:00:10"))[/VBA]Because your printer needs time to process the request. If you close the document immediately, the printspooler can't fetch the request.

    Suggestion to put coding in a normal module. Right click with mouse on project window (left side of screen) and choose insert module.

    2nd suggestion. Use doubleclick on a line to print the line.

    Charlize

  12. #32

    Print works! How do I save Word document?

    Thanks to Charlize. The Wait fixed that problem.

    After I used the routine, the boss asked if I could save the Word document so that it could be emailed later. The net of this is that the "print" statement now needs to be a "save".

    [vba] ChangeFileOpenDirectory (docPath)

    ActiveDocument.SaveAs FileName:=docName, FileFormat:= _
    wdFormatDocument, LockComments:=False, Password:="", AddToRecentFiles:= _
    True, WritePassword:="", ReadOnlyRecommended:=False, EmbedTrueTypeFonts:= _
    False, SaveNativePictureFormat:=False, SaveFormsData:=False, _
    SaveAsAOCELetter:=False


    'wrdApp.ChangeFileOpenDirectory (docPath)

    'wrdApp.ActiveDocument.SaveAs FileName:=docName, FileFormat:= _
    'wdFormatDocument, LockComments:=False, Password:="", AddToRecentFiles:= _
    'True, WritePassword:="", ReadOnlyRecommended:=False, EmbedTrueTypeFonts:= _
    'False, SaveNativePictureFormat:=False, SaveFormsData:=False, _
    'SaveAsAOCELetter:=False
    [/vba]

    The "ChangeFileOpenDirectory" and "docName" variable were traced with the debugger and have the appropriate variables. I turned on Word visibility and I can switch to Word BEFORE the save attempt and see that everything is properly set up.

    The commented-out code was a previous attempt to solve this problem.

    Here is the original code (and it works thanks to Charlize and others!) that I wanted to replace:

    [vba]
    wrdApp.Application.PrintOut FileName:="", Range:=wdPrintAllDocument, Item:= _
    wdPrintDocumentContent, Copies:=1, Pages:="", PageType:=wdPrintAllPages, _
    Collate:=True, Background:=True, PrintToFile:=False, PrintZoomColumn:=0, _
    PrintZoomRow:=0, PrintZoomPaperWidth:=0, PrintZoomPaperHeight:=0
    [/vba]

    The error comes immediately in the debugger, so I'm sure that the "object" is checking my request and finding some error.

    Any ideas?

  13. #33
    MS Excel MVP VBAX Tutor
    Joined
    Mar 2005
    Posts
    246
    Location
    Why do you need "wrdApp.Application.PrintOut"? Isn't wrdApp the Word Application?

    From the bottom of the Object Browser:
    Sub SaveAs([FileName], [FileFormat], [LockComments], [Password], [AddToRecentFiles], [WritePassword], [ReadOnlyRecommended], [EmbedTrueTypeFonts], [SaveNativePictureFormat], [SaveFormsData], [SaveAsAOCELetter], [Encoding], [InsertLineBreaks], [AllowSubstitutions], [LineEnding], [AddBiDiMarks])

    It's pretty much optional, so replace
    [vba]ChangeFileOpenDirectory (docPath)

    ActiveDocument.SaveAs FileName:=docName, FileFormat:= _
    wdFormatDocument, LockComments:=False, Password:="", AddToRecentFiles:= _
    True, WritePassword:="", ReadOnlyRecommended:=False, EmbedTrueTypeFonts:= _
    False, SaveNativePictureFormat:=False, SaveFormsData:=False, _
    SaveAsAOCELetter:=False [/vba]

    with this

    [vba]wrdApp.ActiveDocument.SaveAs FullName[/vba]

    where FullName is the path and file name where the document is to be saved.
    - Jon
    -------
    Jon Peltier, Microsoft Excel MVP
    Peltier Technical Services
    Tutorials and Custom Solutions
    http://PeltierTech.com
    _______

  14. #34

    Thanks Jon!

    Thanks again, Jon. It worked the first time! I discovered another minor problem, but it was easily fixed. The file name I created did not have an extension, so Word was saving the file as ".dot" since the template was so named. I appended the ".doc" to my file name, and this problem was corrected.

    Since I tried several different things like "Application...", I was pretty sure that the problem was my understanding of objects. I've been looking at the VBE help files, but I'm obviously missing something. When I use VBE, I see that it SOMETIMES provides parameter choices for various objects. Other times it does not, especially when I am trying to correct a problem.

    How would you reccomend that I approach this? I basically guess until I get the correct object. I also noticed that your solution as opposed to my attempts has few parameters. I think I am including defaults whereas you are just taking them. How am I supposed to learn this? I've seen nothing in the doc (meaning help files) to indicate defaults. Your solution is certainly less CLUTTERED than my attempts!

    Thanks again.

Posting Permissions

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