The SmartDocsAutomationDocument Class
When the SmartDocs add-in is loaded, any document of the type *.docx can be used with the SmartDocs technology. In order to make this association, a Word.Document object is passed to the API using the GetDocument method in order to obtain an instance of the SmartDocsAutomationDocument class, a SmartDocs Document, so to speak.
A SmartDocs Document is the entry point for programmatically working with the SmartDocs technology. It provides the necessary methods to obtain information and objects for working with conditional content, snippets and variables, as well as for managing snapshots and publishing the document.
Obtaining a SmartDocs Document Object
Since every macro that works with SmartDocs will need to obtain a SmartDocs Document object, wrapping up these steps in a separate procedure is recommended. And, while the expectation is that everything will always work, having error handling in place is useful in case something does go wrong. For example, the add-in might be disabled or have been unloaded.
The code below demonstrates how this can be done. Rather than relying on internal errors Microsoft® Word might raise, that may or may not be helpful, customized errors are raised when the expected result is not produced.
Of particular importance is whether the SmartDocs add-in is loaded and available. If it is not, an attempt to assign it to a variable fails silently, without returning an error. The error then occurs when initializing the AutomationService, but the reason is not apparent. The sample code performs an explicit check for the presence of the SmartDocs add-in and raises a specific error if it is not available.
You may also want to determine whether a document contains any SmartDocs content. The test procedure demonstrates how that is done using the method HasSmartDocsContent.
Option Explicit Private Const cModuleName As String = "basSmartDocs_Document_Sample" Public Const cSmartDocAddinProgramID As String = "ThirtySix.SmartDocs.AddIn" Public Const cMsgTitle_SmartDocVBADemo As String = "SmartDoc VBA Demo Code" Private Sub Test_GetSmartDocs_Document() Dim sProcName As String, sSourceName As String Dim SD_Doc As Object Dim SD_AutomationResult As Object Dim sContains_SD_Info As String On Error GoTo ErrorHandler sProcName = "Test_GetSmartDocs_Document" sSourceName = cModuleName & "." & sProcName Set SD_Doc = Get_SmartDoc_Document(ActiveDocument) If SD_Doc Is Nothing Then Err.Raise vbObjectError + 1001, sSourceName, _ "SmartDocs Document could not be initialized." End If Set SD_AutomationResult = SD_Doc.HasSmartDocsContent If Not SD_AutomationResult.Success Then Err.Raise vbObjectError + 1002, sSourceName, _ "Could not determine whether the document contains SmartDocs content." End If If SD_AutomationResult.Object Then sContains_SD_Info = "contains" Else sContains_SD_Info = "does not contain" End If MsgBox "Now we're ready to work with the SmartDocs document. This document " _ & sContains_SD_Info & " SmartDocs content.", vbInformation + vbOKOnly, _ cMsgTitle_SmartDocVBADemo Exit Sub ErrorHandler: MsgBox Err.Number & vbCr & Err.Description & vbCr & _ Err.Source, vbCritical + vbOKOnly, cMsgTitle_SmartDocVBADemo End Sub 'Errors are passed back to the calling procedure Function Get_SmartDoc_Document(Doc As Word.Document) As Object Dim SD_addin As Office.COMAddIn Dim AutomationService As Object Dim AutomationResult As Object Dim AutomationDocument As Object ' /////////////////////////////////////////////////// ' // Make sure the SmartDocs COM add-in is loaded. // ' /////////////////////////////////////////////////// Set SD_addin = Get_SmartDoc_Addin() If SD_addin Is Nothing Then Err.Raise vbObjectError + 1000, "Test", _ "The SmartDocs Add-in is not loaded." End If ' ////////////////////////////////////////// ' // Get the SmartDocs automation object. // ' ////////////////////////////////////////// Set AutomationService = SD_addin.Object.Automation If Not AutomationService.Initialized Then AutomationService.Initialize If Not AutomationResult.Success Then Err.Raise vbObjectError + AutomationResult.ErrorCode, _ "basSmartDocs_Sample.Get_SmartDoc_Document.AutomationService", _ AutomationResult.Message End If End If ' /////////////////////////////////// ' // Get the document to automate. // ' /////////////////////////////////// Set AutomationResult = AutomationService.GetDocument(Doc) If Not AutomationResult.Success Then Err.Raise vbObjectError + AutomationResult.ErrorCode, _ "basSmartDocs_Sample.Get_SmartDoc_Document.GetDocument", _ AutomationResult.Message End If Set AutomationDocument = AutomationResult.Object Set Get_SmartDoc_Document = AutomationDocument End Function 'Gets an object for the SmartDoc add-in if it's loaded and returns it. 'If the add-in is not loaded then the object is set to Nothing and returned. Function Get_SmartDoc_Addin() As Office.COMAddIn Dim adins As Office.COMAddIns, adin As COMAddIn Dim adinLoaded As Boolean adinLoaded = False Set adins = Application.COMAddIns For Each adin In adins If adin.Connect = True And adin.ProgID = cSmartDocAddinProgramID Then adinLoaded = True Exit For End If Next If Not adinLoaded Then Set adin = Nothing Set Get_SmartDoc_Addin = adin End Function
Comments