Document.SaveAs2 method (Word)

Saves the specified document with a new name or format. Some of the arguments for this method correspond to the options in the Save As dialog box (File tab).

Syntax

expression. SaveAs2( _FileName_ , _FileFormat_ , _LockComments_ , _Password_ , _AddToRecentFiles_ , _WritePassword_ , _ReadOnlyRecommended_ , _EmbedTrueTypeFonts_ , _SaveNativePictureFormat_ , _SaveFormsData_ , _SaveAsAOCELetter_ , _Encoding_ , _InsertLineBreaks_ , _AllowSubstitutions_ , _LineEnding_ , _AddBiDiMarks_ , _CompatibilityMode_ )

expression An expression that returns a Document object.

Parameters

Name Required/Optional Data type Description
FileName Optional Variant The name for the document. The default is the current folder and file name. If the document has never been saved, the default name is used (for example, Doc1.doc). If a document with the specified file name already exists, the document is overwritten without prompting the user.
FileFormat Optional Variant The format in which the document is saved. Can be any WdSaveFormat constant. To save a document in another format, specify the appropriate value for the SaveFormat property of the FileConverter object.
LockComments Optional Variant True to lock the document for comments. The default is False.
Password Optional Variant A password string for opening the document. (See Remarks below.)
AddToRecentFiles Optional Variant True to add the document to the list of recently used files on the File menu. The default is True.
WritePassword Optional Variant A password string for saving changes to the document. (See Remarks below.)
ReadOnlyRecommended Optional Variant True to have Microsoft Word suggest read-only status whenever the document is opened. The default is False.
EmbedTrueTypeFonts Optional Variant True to save TrueType fonts with the document. If omitted, the EmbedTrueTypeFonts argument assumes the value of the EmbedTrueTypeFonts property.
SaveNativePictureFormat Optional Variant If graphics were imported from another platform (for example, Macintosh), True to save only the Microsoft Windows version of the imported graphics.
SaveFormsData Optional Variant True to save the data entered by a user in a form as a record.
SaveAsAOCELetter Optional Variant If the document has an attached mailer, True to save the document as an AOCE letter (the mailer is saved).
Encoding Optional Variant The code page, or character set, to use for documents saved as encoded text files. The default is the system code page. You cannot use all MsoEncoding constants with this parameter.
InsertLineBreaks Optional Variant If the document is saved as a text file, True to insert line breaks at the end of each line of text.
AllowSubstitutions Optional Variant If the document is saved as a text file, True allows Word to replace some symbols with text that looks similar. For example, displaying the copyright symbol as (c). The default is False.
LineEnding Optional Variant The way Word marks the line and paragraph breaks in documents saved as text files. Can be one of the following WdLineEndingType constants: wdCRLF (default) or wdCROnly.
AddBiDiMarks Optional Variant True adds control characters to the output file to preserve bi-directional layout of the text in the original document.
CompatibilityMode Optional Variant The compatibility mode that Word uses when opening the document. WdCompatibilityMode constant.
Important
By default, if no value is specified for this parameter, Word enters a value of 0, which specifies that the current compatibility mode of the document should be retained.

Return value

Nothing

Example

The following code example saves the active document as Test.rtf in rich-text format (RTF).

Sub SaveAsRTF() 
    ActiveDocument.SaveAs2 FileName:="Text.rtf", _ 
        FileFormat:=wdFormatRTF 
End Sub

The following code example saves the active document in text-file format with the extension ".txt".

Sub SaveAsTextFile() 
    Dim strDocName As String 
    Dim intPos As Integer 
 
    ' Find position of extension in file name 
    strDocName = ActiveDocument.Name 
    intPos = InStrRev(strDocName, ".") 
 
    If intPos = 0 Then 
 
        ' If the document has not yet been saved 
        ' Ask the user to provide a file name 
        strDocName = InputBox("Please enter the name " & _ 
            "of your document.") 
    Else 
 
        ' Strip off extension and add ".txt" extension 
        strDocName = Left(strDocName, intPos - 1) 
        strDocName = strDocName & ".txt" 
    End If 
 
    ' Save file with new extension 
    ActiveDocument.SaveAs2 FileName:=strDocName, _ 
        FileFormat:=wdFormatText 
End Sub

The following code example loops through all the installed converters, and if it finds the WordPerfect 6.0 converter, it saves the active document using the converter.

Sub SaveWithConverter() 
 
    Dim cnvWrdPrf As FileConverter 
 
    ' Look for WordPerfect file converter 
    ' And save document using the converter 
    ' For the FileFormat converter value 
    For Each cnvWrdPrf In Application.FileConverters 
        If cnvWrdPrf.ClassName = "WrdPrfctWin" Then 
            ActiveDocument.SaveAs2 FileName:="MyWP.doc", _ 
                FileFormat:=cnvWrdPrf.SaveFormat 
        End If 
    Next cnvWrdPrf 
 
End Sub

The following code example shows a procedure that saves a document with a password.

Sub SaveWithPassword(docCurrent As Document, strPWD As String) 
    With docCurrent 
        .SaveAs2 WritePassword:=strPWD 
    End With 
End Sub

See also

Document Object

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.