Share via


Propiedad InvisibleApp.CurrentScope (Visio)

Determina el identificador del ámbito que hace que se desencadene un evento. Solo lectura.

Sintaxis

expresión. CurrentScope

Expresión Variable que representa un objeto InvisibleApp .

Valor devuelto

Long

Comentarios

Devuelve la constante visScopeIDInvalid (-1) si no está abierto el ámbito. El identificador de ámbito puede ser un identificador de ámbito de Microsoft Visio interno que se corresponde con un comando de Visio o un identificador de ámbito externo pasado a un cliente de automatización mediante el método BeginUndoScope.

Los destinatarios de un evento consideran que un ámbito está abierto si se ha desencadenado el evento EnterScope pero no el evento ExitScope.

Para determinar si el desencadenamiento de cola de eventos está relacionado con un determinado ámbito interno a la aplicación o con uno abierto y cerrado mediante un cliente de automatización, utilice la propiedad IsInScope.

Ejemplo:

Este ejemplo muestra cómo utilizar la propiedad CurrentScope para determinar el identificador del ámbito actual.

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

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.