Consulting

Results 1 to 13 of 13

Thread: WORD VBA - Open and save file to new location

  1. #1

    WORD VBA - Open and save file to new location

    How can I open a file from a WORD UserForm in the ActiveDocument and save that new file to a different location then the active document containing the UserForm

  2. #2
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,335
    Location
    "Open" a file implies a file (specifically that one) already exists.
    Save that "new" file implies your are working with a file that you just created.

    What is it specifically that you are trying to do?
    Greg

    Visit my website: http://gregmaxey.com

  3. #3
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    You save a file using SaveAs. So, use SaveAs. You can save a file in ANY location you want using SaveAs (as long as that location actually exists of course).

    Say you open a file c:\yadda\ThisDoc.doc. The fact it is a userform that creates a new file is completely irrelevant....assuming as greg asks you did in fact create a new file.[vba]
    Sub NowSaveme()
    ActiveDocument.SaveAs "c:\SomeCompletely\OtherFolder\andANOTHER_Name.doc"
    End Sub
    [/vba]RE: the code above, the new document is of now of course the ActiveDocument.


    It does not have to be if you user document objects.

    But to reoterate what Greg asked. "What is it specifically that you are trying to do?"

    Be specific. Be clear.

  4. #4
    VBAX Regular
    Joined
    Aug 2006
    Posts
    79
    Location
    Try this one:

    [VBA]Sub SaveMe()
    Set dlgSaveAs = Dialogs(wdDialogFileSaveAs)
    With dlgSaveAs
    .Name = "E:\TEST" & "\" & "New Name.doc"
    .Format = wdFormatDocument
    .Show
    End With
    End Sub[/VBA]

  5. #5
    From my user form, I want to open a text file, change the name and save it as a new name without making it the active file

  6. #6
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    Why?

    And, if you open it Word (as opposed to using VBA to access it), then this is not possible. If you open it in Word, it IS the active document.

    Why open the file just to rename essentially a copy? There are other ways to do this. Look up using FileSystemObject.

    I am missing something.

  7. #7
    I am trying to
    (1) Read available text files in the current directory
    (2) Choose one file (e.g., mTextFile.txt) and open it
    (3) Save the mTextFile.txt to a text box (editing file in text box).
    (4) Save the changes to either the same text file or to a new textfile

  8. #8
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    This is not what you asked. What does:

    (1) Read available text files in the current directory
    (2) Choose one file (e.g., mTextFile.txt) and open it
    (3) Save the mTextFile.txt to a text box (editing file in text box).
    (4) Save the changes to either the same text file or to a new textfile

    have do with Active Document? If nothing, please state a bit more precisely what you actually do want to do. For example #4 is rather vague...that "or" make quite a bit of difference.

    Plus you do not state if the textbox exists already, or are you making a new textbox. I really do not know what you mean by "editing file in text box". You do not edit any files in text boxes, you can change a string in a textbox.

  9. #9
    Quote Originally Posted by fumei
    This is not what you asked. What does:

    (1) Read available text files in the current directory
    (2) Choose one file (e.g., mTextFile.txt) and open it
    (3) Save the mTextFile.txt to a text box (editing file in text box).
    (4) Save the changes to either the same text file or to a new textfile

    have do with Active Document? If nothing, please state a bit more precisely what you actually do want to do. For example #4 is rather vague...that "or" make quite a bit of difference.

    Plus you do not state if the textbox exists already, or are you making a new textbox. I really do not know what you mean by "editing file in text box". You do not edit any files in text boxes, you can change a string in a textbox.
    Sorry for the confusion, I did not put as much detail in as I sould have. Let me be more clear.
    - I have a user form that pops up automatically when the word document (userform.doc) is opened.
    - The user can click a button on the form called "readRIS" which opens the wdDialogFileOpen dialog. It shows the current directory where the userform.doc is located.
    - The user can click on a file to select it. The file to open is a text file but has a .ris extension (e.g., myreferences.ris)
    - NOTE: I use ".Display" instead of ".Show" to avoid executing the open command. I just want to get the file name so I can read the file in.

    Code:
    ---------------------------
    With Application.Dialogs(wdDialogFileOpen)
    .Display
    sFilename = .Name
    End With
    ---------------------------
    - I copy the contents of the textfile as a string to a textbox (called fText) on the form (already existing).
    - I send the string containing the contents of "myreferences.ris" in the textbox to a parser which cleans up the data.
    - The user can edit the text in the textbox (ftext).

    Code
    ---------------------------
    Public Sub ReadRIS_Click()
    Dim sPath As String
    With ActiveDocument
    ' Get filename
    With Application.Dialogs(wdDialogFileOpen)
    .Display
    sFilename = .Name
    End With
    ' Read .ris file
    fText = ReadTextFile(sFilename)
    ' parse .ris file
    fileStr = ParseRIS(fText)
    ' display .ris file and file name
    fText = fileStr ' write parsed file to textbox
    RISFileName = "source: " & sFilename ' show filename in textbox
    End With
    End Sub
    ---------------------------
    - I now want the user to click save button (already existing) that saves the edited info in the textbox (ftext) to a different text file called myreferences.txt.
    - Now there are two text files existing with the same name but different extensions. The first is the original myreferences.ris file and the second is the cleaned and edited version with a myreferences.txt extension.

    It is working up to the point of saving the Textbox (ftext) to a new file called myreferences.txt. This is the part I am having trouble with.
    Last edited by jspattavina; 09-07-2010 at 10:07 AM.

  10. #10
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    You seem to think ftext is the textbox.

    It is not.

    As it seems to me, ftext is a string variable, yes? BTW: it does not seem to be declared here. Is this a global variable? Or are you not using Option Explicit?
    [vba]fText = fileStr ' write parsed file to textbox[/vba]That sure seems like one string variable equals another string variable. It sure does NOT look it does any writing of "parsed file to textbox".

    In any case, it does not really matter. IF you have a string (no matter how you got it), yes, you can write it as a text file.

    Using, as I have stated...File.SaveAs.

    In other words, create a NEW document (temporarily) and copy in your string variable - whatever it is, and however you got it - and do a SaveAs.[vba]
    Sub SaveAsText()
    Dim tempDoc As Document

    Set tempDoc = Documents.Add
    tempDoc.Range.Text = ftext
    tempDoc.SaveAs FileName:="c:\blahblah.txt", _
    fileformat:=wdFormatText
    tempDoc.Close
    Set tempDoc = Nothing
    End Sub
    [/vba]
    The string - ftext - is put into a new document, and that document is saved as a textfile, and then closed.

    Done.

    If sFilename (also undeclared) is blahblah.ris, and you want to save your text file as blahblah.txt, then strip off the last three characters for your SaveAs filename - assuming it DOES include the full path! Strip off "ris" and replace it with .txt.

    I suggest you did without using Replace - unless you can guarantee the filename will never have "ris" as text within it.
    [vba]
    tempDoc.SaveAs FileName:=Left(sFilename, Len(sFilename) - 3) & "txt", _
    fileformat:=wdFormatText

  11. #11
    Thank you very much. This is exactly what i need. !!!!
    --------------------------------------------------
    By the way fText is a text box. So when I set
    fText = fileStr I am setting the Text or Value for Textbox named fText to the string named fileStr.

    Again - Thanks Gerry

  12. #12
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    "By the way fText is a text box. So when I set

    fText = fileStr I am setting the Text or Value for Textbox named fText to the
    string named fileStr.

    Oh really? Your code sure does NOT look like that.

    There is no Set instruction. There is no declaration of ftext being an object. If it was an object (a textbox) then I suggest you follow standard namaing convention - especially as you do not seem to be declaring things.

    objTextbox would indicate to me it is an object.

    ftext looks like a string variable.

    IF ftext is a textbox (and I remain unconvinced it is) then:[vba]
    tempDoc.Range.Text = ftext
    [/vba] may fail.

    Please answer:

    1. are you in fact using Option Explicit

    2. what KIND of textbox is this?????

  13. #13

    Problem Opening and Reading Text File

    I am using the following code to Open a dialog box and let the user select a text file. Then get the file name and open a text file, read the contents to a string (mStr) and then write the string to a textbox (fText). It works for some text files but not others. For example the file "ARE_Journals.ris" opens fine and I can read the data. The file "ARE_MPEG Compression.ris" does not open and read?. Both files can be opened in a text editor and appear to be the similar (structure and line endings etc.).

    Can anyone tell me what is wrong?

    CODE:
    ----------------------------------------------------------
    With ActiveDocument
    mStr = ""
    'Get filename
    With Application.Dialogs(wdDialogFileOpen)
    .Display
    sFileName = .Name
    End With
    'Prepend path to Filename
    sFile = ThisDocument.path & "\" & sFileName
    'OpenFile
    Dim iFile As Integer
    On Local Error Resume Next
    'Use FreeFile to supply a file number that is not already in use
    iFile = FreeFile
    Open sFile For Input As #iFile
    'Read the whole content of the file to the string called mStr
    mStr = Input$(LOF(iFile), iFile)
    Close #iFile
    'Write the Str to a TextBox called fText
    fText.Text = mStr
    End With

Posting Permissions

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