Propiedad Application.IsInScope (Visio)
Determina si una llamada a un controlador de eventos está entre un evento EnterScope y un evento ExitScope para un ámbito. Solo lectura.
Sintaxis
expresión. IsInScope (nCmdID)
expresión Variable que representa un objeto Application.
Parámetros
Nombre | Obligatorio/opcional | Tipo de datos | Descripción |
---|---|---|---|
nCmdID | Necesario | Long | Identificador de ámbito. |
Valor devuelto
Booleano
Comentarios
Las constantes que representan identificadores de ámbito van precedidas de visCmd y se declaran en la biblioteca de tipos de Visio. También puede utilizar un identificador devuelto por el método BeginUndoScope.
Esta propiedad podría usarla en un controlador de eventos CellChanged para determinar si un cambio de celda fue consecuencia de una operación determinada.
Ejemplo:
En este ejemplo se muestra cómo usar la propiedad IsInScope para determinar si una llamada a un procedimiento que controla el evento CellChanged está en un ámbito determinado; es decir, si la llamada se produce entre los eventos EnterScope y ExitScope para ese ámbito.
Private WithEvents vsoApplication As Visio.Application
Private lngScopeID As Long
Public Sub IsInScope_Example()
Dim vsoShape As Visio.Shape
'Set the module-level application variable to
'trap application-level events.
Set vsoApplication = Application
'Begin a scope.
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 (to trigger the CellChanged 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 my 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 bstrDescription As String, _
ByVal bErrOrCancelled As Boolean)
If vsoApplication.CurrentScope = lngScopeID Then
Debug.Print "Exiting my scope " & nScopeID
Else
Debug.Print "ExitScope " & bstrDescription & "(" & nScopeID & ")"
End If
End Sub
Soporte técnico y comentarios
¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.