Adding Using Code
You can use Application.SendKeys to add Watches
The VBE must be in focus when the code is run. You can either do this manually or use the VBIDE object to set the focus.
Call AddWatch sub with the specified arguments.
You can add these to a sub you call when you start a new session, as demonstrated in my "HelloNewSession()"
Enum enumWatchType
WatchExpression
BreakWhenTrue
BreakWhenChange
End Enum
Enum enumProceduresType
AllProcedures
Caller
End Enum
Enum enumModuleType
AllModules
CurrentModule
ThisWorkbook
End Enum
Public testVar As Boolean
Sub HelloNewSession()
AddWatch "testVar = True", AllProcedures, CurrentModule, BreakWhenTrue
testVar = True
End Sub
Sub AddWatch( _
expression As String, _
Optional proceduresType As enumProceduresType = enumProceduresType.Caller, _
Optional moduleType As enumModuleType = enumModuleType.CurrentModule, _
Optional watchType As enumWatchType = enumWatchType.WatchExpression)
Dim i As Long
Application.SendKeys "%DA"
Application.SendKeys getEscapedSendkeysText(expression)
If proceduresType = enumProceduresType.AllProcedures Then
Application.SendKeys "%p"
For i = 1 To 1000 'You could use VBIDE to count the valid types to actually scroll up the right number of times!
Application.SendKeys "{UP}"
Next
End If
If moduleType = enumModuleType.AllModules Then
Application.SendKeys "%m"
For i = 1 To 1000 'You could use VBIDE to count the valid types to actually scroll up the right number of times!
Application.SendKeys "{UP}"
Next
ElseIf moduleType = enumModuleType.ThisWorkbook Then
Application.SendKeys "%m"
For i = 1 To 1000 'You could use VBIDE to count the valid types to actually scroll up the right number of times!
Application.SendKeys "{DOWN}"
Next
End If
Select Case watchType
Case enumWatchType.WatchExpression
Application.SendKeys "%w"
Case enumWatchType.BreakWhenTrue
Application.SendKeys "%t"
Case enumWatchType.BreakWhenChange
Application.SendKeys "%c"
End Select
Application.SendKeys "~"
End Sub
Function getEscapedSendkeysText(ByVal text As String) As String
Dim char As String, i As Long
Const chars As String = "~%+^()[]"
For i = 1 To Len(chars)
char = Mid$(chars, i, 1)
text = Replace(text, char, "{" & char & "}")
Next
getEscapedSendkeysText = text
End Function
© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext