Application.CurrentScope-Eigenschaft (Visio)
Bestimmt die ID des Bereichs, durch den ein Ereignis ausgelöst wird. Schreibgeschützt.
Syntax
Ausdruck. CurrentScope
expression Eine Variable, die ein Application-Objekt darstellt.
Rückgabewert
Long
Hinweise
Gibt visScopeIDInvalid (-1) zurück, wenn ein Bereich nicht geöffnet ist. Die Bereichs-ID kann eine interne Bereichs-ID von Microsoft Visio sein, die einem Visio-Befehl entspricht, oder eine externe Bereichs-ID, die mit der BeginUndoScope-Methode an einen Automatisierungsclient übergeben wird.
Ein Bereich wird von den Empfängern eines Ereignisses als geöffnet angesehen, wenn das EnterScope-Ereignis ausgelöst und das ExitScope-Ereignis noch nicht ausgelöst wurde.
Verwenden Sie die IsInScope-Eigenschaft, um zu bestimmen, ob die Ereignisse auslösende Warteschlange mit einem bestimmten internen Bereich der Anwendung oder mit einem Bereich verbunden ist, der von einem Automatisierungsclient geöffnet und geschlossen wird.
Beispiel
Dieses Beispiel veranschaulicht, wie die CurrentScope-Eigenschaft zum Bestimmen der ID des aktuellen Bereichs verwendet wird.
Private WithEvents vsoApplication As Visio.Application
Private lngScopeID As Long
Public Sub ScopeActions()
Dim vsoShape As Visio.Shape
'Set the module level application variable to
'trap Application level events.
Set vsoApplication = Application
'Begin a scope, set the module level variable.
lngScopeID = Application.BeginUndoScope("Draw Shapes")
'Draw three shapes.
Set vsoShape = ActivePage.DrawRectangle(1, 2, 2, 1)
ActivePage.DrawOval 3, 4, 4, 3
ActivePage.DrawLine 4, 5, 5, 4
'Change a cell (which would trigger a cell changed event).
vsoShape.Cells("Width").Formula = 5
'End and commit this scope.
Application.EndUndoScope lngScopeID, True
End Sub
Private Sub vsoApplication_CellChanged(ByVal Cell As IVCell)
'Check to see if this cell change is the result of something
'happening within the scope.
If vsoApplication.IsInScope(lngScopeID) Then
Debug.Print Cell.Name & " changed in scope "; lngScopeID
End If
End Sub
Private Sub vsoApplication_EnterScope(ByVal app As IVApplication, _
ByVal nScopeID As Long, _
ByVal bstrDescription As String)
If vsoApplication.CurrentScope = lngScopeID Then
Debug.Print "Entering current scope " & nScopeID
Else
Debug.Print "Enter Scope " & bstrDescription & "(" & nScopeID & ")"
End If
End Sub
Private Sub vsoApplication_ExitScope(ByVal app As IVApplication, _
ByVal nScopeID As Long, _
ByVal strDescription As String, _
ByVal bErrOrCancelled As Boolean)
If vsoApplication.CurrentScope = lngScopeID Then
Debug.Print "Exiting current scope " & nScopeID
Else
Debug.Print "ExitScope " & bstrDescription & "(" & nScopeID & ")"
End If
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.