Page.Document-Eigenschaft (Visio)

Ruft das Document-Objekt ab, das einem -Objekt zugeordnet ist. Schreibgeschützt.

Syntax

Ausdruck. Dokument

Ausdruck Eine Variable, die ein Page-Objekt darstellt.

Rückgabewert

Dokument

HinwBemerkungeneise

Wenn Ihre Visual Studio-Projektmappe den Verweis Microsoft.Office.Interop.Visio enthält, wird diese Eigenschaft den folgenden Typen zugeordnet:

  • Microsoft.Office.Interop.Visio.IVPage.Document

Beispiel

Das folgende Makro von VBA (Microsoft Visual Basic für Applikationen) veranschaulicht, wie die Document-Eigenschaft verschiedener Objekte zum Abrufen von Daten über diese Objekte verwendet wird, und führt folgende Aktionen aus:

  • Es fügt ein Document-Objekt zur Documents-Auflistung hinzu und legt zahlreiche der Eigenschaften des Document-Objekts fest.

  • Es ruft das aktive Fenster und das aktive Zeichenblatt ab, zeichnet ein Rechteck auf das Zeichenblatt und legt ein Master-Shape im Document-Objekt ab, um es so zahlreichen Objekten zum Bearbeiten bereitzustellen.

  • Es verwendet die Document-Eigenschaft zum Abrufen des Document-Objekts, das jedem dieser anderen Objekte zugeordnet ist.

 
Public Sub Document_Example() 
  
    Dim vsoDocument As Visio.Document  
    Dim vsoTempDocument As Visio.Document  
    Dim vsoPage As Visio.Page  
    Dim vsoShape As Visio.Shape  
    Dim vsoWindow As Visio.Window  
    Dim vsoMaster As Visio.Master  
 
    'Add a document to the Documents collection. 
    Set vsoDocument = Documents.Add("")  
 
    'Set the title of the document. 
     vsoDocument.Title = "My Document"  
 
    'Get the active window and active page. 
    Set vsoWindow = ActiveWindow  
    Set vsoPage = ActivePage  
 
    'Draw a rectangle on the page. 
    Set vsoShape = vsoPage.DrawRectangle(2, 2, 5, 5)  
 
    'Add a master. 
    Set vsoMaster = vsoDocument.Masters.Add  
 
    'Get the Document object associated with various other objects.'Get the Document object associated with the Window object. 
    Set vsoTempDocument = vsoWindow.Document  
 
    'Get the Title property of the Document object to verify that this is the same document we added earlier.  
    Debug.Print vsoTempDocument.Title  
 
    'Get the Document object associated with the Page object. 
    Set vsoTempDocument = vsoPage.Document  
    Debug.Print vsoTempDocument.Title  
 
    'Get the Document object associated with the Shape object. 
    Set vsoTempDocument = vsoShape.Document  
    Debug.Print vsoTempDocument.Title  
 
    'Get the Document object associated with the Master object. 
    Set vsoTempDocument = vsoMaster.Document  
    Debug.Print vsoTempDocument.Title  
 
End Sub

Support und Feedback

Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.