Propriedade InvisibleApp. IsInScope (Visio)InvisibleApp.IsInScope property (Visio)
Determina se uma chamada de um manipulador de eventos está entre um evento EnterScope e um evento ExitScope de um escopo.Determines whether a call to an event handler is between an EnterScope event and an ExitScope event for a scope. Somente leitura.Read-only.
SintaxeSyntax
expressão. IsInScope (nCmdID)expression.IsInScope (nCmdID)
expressão Uma variável que representa um objeto InvisibleApp .expression A variable that represents an InvisibleApp object.
ParâmetrosParameters
NomeName | Obrigatório/OpcionalRequired/Optional | Tipo de dadosData type | DescriçãoDescription |
---|---|---|---|
nCmdIDnCmdID | ObrigatórioRequired | LongLong | A ID do escopo.The scope ID. |
Valor de retornoReturn value
BoolianoBoolean
ComentáriosRemarks
As constantes que representam IDs de escopos têm o prefixo visCmd e são declaradas pela biblioteca de tipos do Visio.Constants representing scope IDs are prefixed with visCmd and are declared by the Visio type library. Você também pode usar uma ID retornada pelo método BeginUndoScope.You can also use an ID returned by the BeginUndoScope method.
Você poderia usar essa propriedade em um manipulador de eventos CellChanged para determinar se uma alteração de célula resultou de uma operação específica.You could use this property in a CellChanged event handler to determine whether a cell change was the result of a particular operation.
ExemploExample
Este exemplo mostra como usar a propriedade IsInScope para determinar se uma chamada para um procedimento que manipula o evento cellchanged está em um escopo específico; ou seja, se a chamada ocorre entre os eventos EnterScope e ExitScope para esse escopo.This example shows how to use the IsInScope property to determine whether a call to a procedure that handles the CellChanged event is in a particular scope; that is, whether the call occurs between the EnterScope and ExitScope events for that scope.
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
Suporte e comentáriosSupport and feedback
Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação?Have questions or feedback about Office VBA or this documentation? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.