rubberduck-vba / Rubberduck

Every programmer needs a rubberduck. COM add-in for the VBA & VB6 IDE (VBE).
https://rubberduckvba.com
GNU General Public License v3.0
1.92k stars 302 forks source link

Test hanging and Excel Crashing when faking InputBox and MsgBox #4729

Closed ronykrell closed 5 years ago

ronykrell commented 5 years ago

Rubberduck version information The info below can be copy-paste-completed from the first lines of Rubberduck's Log or the About box:

Rubberduck version 2.3.0.4227 loading:
Operating System: Microsoft Windows NT 10.0.17763.0 x64
Host Product: Microsoft Office x64
Host Version: 16.0.11029.20108
Host Executable: EXCEL.EXE;

Description

I'm using RubberDuck to test an Excel Workbook, and Excel crashes when running the RubberDuck test.

A sheet in the workbook contains a Worksheet_Change event that prompts the user for a password when changing a particular cell. If the user enters the correct password, a MsgBox saying "Correct Password" is displayed. If the user enters the incorrect password, a MsgBox saying "Incorrect password" is displayed, and the change to the cell is undone.

I wrote a test in RubberDuck to test the code. The test has to change the value at cell A1, successfully handle the password prompt (InputBox), handle the MsgBox properly, and then verify the value of cell A1 is as expected.

When I run the RubberDuck test, Excel hangs. When I stop the test either via the Pause or Stop buttons in the VBA Editor, Excel crashes.

Note that the actual use application is much more complex - I simplified the code as much as possible to get to the simplest use case that makes it possible to reproduce the issue.

To Reproduce Create a new Workbook Add a WorkSheet_Change Event with the following code

Option Explicit

Private Sub Worksheet_Change(ByVal Target As Range)
    Dim changed As Range
    Set changed = Intersect(Target, Range("A1"))
    Dim pword As String
    If Not changed Is Nothing Then
        pword = InputBox("Input password")
        If pword <> "password123" Then
            MsgBox "Wrong password", , "Error"
            Application.EnableEvents = False
            Application.Undo
            Application.EnableEvents = True
        Else
            MsgBox "Correct Password'", , "Correct"
        End If
    End If
End Sub

Add a Rubberduck test module with the following code

Option Explicit

Option Private Module

'@TestModule
'@Folder("Tests")

Private Assert As Object
Private Fakes As Object

'@ModuleInitialize
Public Sub ModuleInitialize()
    'this method runs once per module.
    Set Assert = CreateObject("Rubberduck.AssertClass")
    Set Fakes = CreateObject("Rubberduck.FakesProvider")
    Fakes.InputBox.Returns "password123"
    Fakes.MsgBox.Returns 42
    AdjustCell
End Sub

'@ModuleCleanup
Public Sub ModuleCleanup()
    'this method runs once per module.
    Set Assert = Nothing
    Set Fakes = Nothing
End Sub

'@TestInitialize
Public Sub TestInitialize()
    'this method runs before every test in the module.
End Sub

'@TestCleanup
Public Sub TestCleanup()
    'this method runs after every test in the module.
End Sub

Private Sub AdjustCell()
    With Sheet1
        .Range("A1").Value = 2
    End With
End Sub

'@TestMethod
Public Sub TestAdjustedCell()
    On Error GoTo TestFail
    Assert.isTrue Sheet1.Range("A1").Value = 2
TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

Expected behavior Test to Pass

Logfile

2019-01-20 10:18:25.9390;INFO-2.3.0.4227;Rubberduck.Common.LogLevelHelper;
    Rubberduck version 2.3.0.4227 loading:
    Operating System: Microsoft Windows NT 10.0.17763.0 x64
    Host Product: Microsoft Office x64
    Host Version: 16.0.11029.20108
    Host Executable: EXCEL.EXE;
2019-01-20 10:18:26.2649;INFO-2.3.0.4227;Rubberduck.UI.Command.VersionCheckCommand;Executing version check.;
2019-01-20 10:18:37.1932;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (1) is invoking StateChanged (Started);
2019-01-20 10:18:37.9621;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (2) is invoking StateChanged (LoadingReference);
2019-01-20 10:18:39.9941;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (3) is invoking StateChanged (Parsing);
2019-01-20 10:18:40.9071;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (4) is invoking StateChanged (Parsed);
2019-01-20 10:18:41.2745;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (5) is invoking StateChanged (ResolvingDeclarations);
2019-01-20 10:18:41.8327;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (6) is invoking StateChanged (ResolvedDeclarations);
2019-01-20 10:18:42.8899;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (7) is invoking StateChanged (ResolvingReferences);
2019-01-20 10:18:43.4362;WARN-2.3.0.4227;Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses.TypeAnnotationPass;Failed to resolve type VBE;
2019-01-20 10:18:43.8295;WARN-2.3.0.4227;Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses.TypeAnnotationPass;Failed to resolve type VBE;
2019-01-20 10:18:43.9064;WARN-2.3.0.4227;Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses.TypeAnnotationPass;Failed to resolve type VBProject;
2019-01-20 10:18:43.9495;WARN-2.3.0.4227;Rubberduck.Parsing.VBA.ReferenceManagement.CompilationPasses.TypeAnnotationPass;Failed to resolve type VBProject;
2019-01-20 10:18:44.1787;WARN-2.3.0.4227;Rubberduck.Parsing.Symbols.IdentifierReferenceResolver;Type Context: Failed to resolve Object. Binding as much as we can.;
2019-01-20 10:18:44.1950;WARN-2.3.0.4227;Rubberduck.Parsing.Symbols.IdentifierReferenceResolver;Type Context: Failed to resolve Object. Binding as much as we can.;
2019-01-20 10:18:44.6102;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (8) is invoking StateChanged (Ready);
2019-01-20 10:18:44.7753;WARN-2.3.0.4227;Rubberduck.Inspections.Rubberduck.Inspections.Inspector;System.NullReferenceException: Object reference not set to an instance of an object.
   at Rubberduck.Inspections.CodePathAnalysis.Walker.GenerateTree(IParseTree tree, Declaration declaration) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\CodePathAnalysis\Walker.cs:line 72
   at Rubberduck.Inspections.Concrete.AssignmentNotUsedInspection.DoGetInspectionResults() in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Concrete\AssignmentNotUsedInspection.cs:line 33
   at Rubberduck.Inspections.Abstract.InspectionBase.GetInspectionResults(CancellationToken token) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Abstract\InspectionBase.cs:line 166
   at Rubberduck.Inspections.Rubberduck.Inspections.Inspector.RunInspection(IInspection inspection, ConcurrentBag`1 allIssues, CancellationToken token) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Inspector.cs:line 188;System.NullReferenceException: Object reference not set to an instance of an object.
   at Rubberduck.Inspections.CodePathAnalysis.Walker.GenerateTree(IParseTree tree, Declaration declaration) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\CodePathAnalysis\Walker.cs:line 72
   at Rubberduck.Inspections.Concrete.AssignmentNotUsedInspection.DoGetInspectionResults() in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Concrete\AssignmentNotUsedInspection.cs:line 33
   at Rubberduck.Inspections.Abstract.InspectionBase.GetInspectionResults(CancellationToken token) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Abstract\InspectionBase.cs:line 166
   at Rubberduck.Inspections.Rubberduck.Inspections.Inspector.RunInspection(IInspection inspection, ConcurrentBag`1 allIssues, CancellationToken token) in C:\projects\rubberduck\Rubberduck.CodeAnalysis\Inspections\Inspector.cs:line 188
2019-01-20 10:18:46.3588;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (9) is invoking StateChanged (Busy);
2019-01-20 10:18:46.4633;ERROR-2.3.0.4227;Rubberduck.UnitTesting.TestEngine;Unexpected expection while running unit tests; unit tests will be aborted;System.Runtime.InteropServices.SEHException (0x80004005): External component has thrown an exception.
   at Rubberduck.VBEditor.ComManagement.TypeLibsSupport.IDispatch.Invoke(Int32 dispIdMember, Guid& riid, UInt32 lcid, UInt32 dwFlags, DISPPARAMS& pDispParams, Object& pVarResult, EXCEPINFO& pExcepInfo, UInt32& pArgErr)
   at Rubberduck.VBEditor.ComManagement.TypeLibsSupport.IDispatchHelper.Invoke(IDispatch obj, Int32 memberId, InvokeKind invokeKind, Object[] args) in C:\projects\rubberduck\Rubberduck.VBEEditor\ComManagement\TypeLibs\TypeLibsSupport.cs:line 397
   at Rubberduck.VBEditor.ComManagement.TypeLibs.TypeInfoWrapper.StdModExecute(String name, Object[] args) in C:\projects\rubberduck\Rubberduck.VBEEditor\ComManagement\TypeLibs\TypeInfos.cs:line 678
   at Rubberduck.VBEditor.ComManagement.TypeLibsAPI.VBETypeLibsAPI.ExecuteCode(ITypeLibWrapper projectTypeLib, String standardModuleName, String procName, Object[] args) in C:\projects\rubberduck\Rubberduck.VBEEditor\ComManagement\TypeLibs\TypeLibsAPI.cs:line 251
   at Rubberduck.UnitTesting.VBEInteraction.RunDeclarations(ITypeLibWrapper typeLib, IEnumerable`1 declarations) in C:\projects\rubberduck\Rubberduck.UnitTesting\UnitTesting\VBEInteraction.cs:line 31
   at Rubberduck.UnitTesting.TestEngine.RunWhileSuspended(IEnumerable`1 tests) in C:\projects\rubberduck\Rubberduck.UnitTesting\UnitTesting\TestEngine.cs:line 199
2019-01-20 10:18:46.4707;INFO-2.3.0.4227;Rubberduck.Parsing.VBA.RubberduckParserState;RubberduckParserState (10) is invoking StateChanged (Ready);

Additional context Add any other context about the problem here.

retailcoder commented 5 years ago

Thanks for reporting; for the record the SO question was fine too =)

The Fakes API objects are meant to be very short-lived, i.e. the duration of a single test. Here they're alive from before the first test runs, until after the last test finished.

These are hooks into the VBA runtime, intercepting internal function calls: them being alive for longer than they're needed is definitely not helping.

Another thing is the very nature of the test itself: unit testing isolates functionality from its dependencies, but here everything relies on Excel raising an event when a worksheet is modified: not only that's global state not controlled by the test, it involves a worksheet that isn't controlled by the test either; it's not a unit.

Instead of implementing the functionality directly in an event handler, writing a testable function in another module (and invoking it from the handler) would be a preferred approach: that way a test wouldn't need to involve any worksheet, or any worksheet events; whether application events are enabled wouldn't make any difference either.

The test execution throwing an exception is interesting though. Stupid question: does the code compile? (debug ~> compile VBAProject)

ronykrell commented 5 years ago

Hi, thanks for the super quick response. Yes, the code compiles.

The Fakes API objects are meant to be very short-lived, i.e. the duration of a single test. Here they're alive from before the first test runs, until after the last test finished.

These are hooks into the VBA runtime, intercepting internal function calls: them being alive for longer than they're needed is definitely not helping.

I tried destroying the fakes object right after the AdjustCell call (Set Fakes = Nothing) so that any side effects are as short-lived as possible, but that didn't change the hang/crash behavior.

Going through this process (adjusting a field and going through the password prompt InputBox and MsgBox) is really a pre-req before running any of the tests in the real application's case - the code that runs before any of the tests is changing a cell (this is the code that I posted), running a few algorithms that ingest multiple cell values from the UI (not posted), and then the separate Rubberduck tests test whether different UI outputs are correct. Yes, admittedly this is not following good unit testing principles.

comintern commented 5 years ago

I spent some time trying to replicate this locally with the provided code (and with a couple other scenarios inspired by the log file) and haven't been able to cause a crash in Excel 2013 x64. When Excel crashes, it should be generating a application crash event via Windows Error Reporting. Can you track down a sample WER log and post the contents here? You should find it in the Event Viewer under Windows Logs -> Application. There can be a lot of traffic through there, so you may want to filter by "Error".

Note: Setting Fakes = Nothing will not deterministically "destroy" it. It will decrease the reference count by one and make it unreachable by VBA from that scope, but the lifetime of the underlying object is controlled by the COM server (in this case Rubberduck). The same thing would happen if the object leaves active scope.

Also keep in mind that Fakes is simply the provider - the behavior is provided by Fakes.InputBox and Fakes.MsgBox. These need to remain in scope for the duration of the test that faked method is hooked - when they fall out of scope, they will unhook. The intended use is with a single test method like this:

    With Fakes.MsgBox
        .Returns vbOK
        MsgBox "This is faked"
        .Verify.Once
        .Verify.Parameter "Prompt", "This is faked"
    End With

If you use them in the initialize code, Rubberduck will call it a single time during the test run, but the 2 faked calls become eligible for garbage collection as soon as ModuleInitialize exits. GC is non-deterministic, so it's impossible to predict what the state of the hook will be after ModuleInitialize exits.

The entire situation is compound by the triggering of event handlers during the test run (and our test framework is neither intended nor designed to be used that way). Keep in mind that these are being executed by Excel, not the VBA code. If the event handler triggers a call to the faked methods, or Excel attempts to generate a VBA message box, all bets are now off because neither your code or Rubberduck's code has control over how that call is made.

ronykrell commented 5 years ago

Thanks so much for spending time on this! Learning a lot about VBA and Rubberduck The crash event log is attached.

If you use them in the initialize code, Rubberduck will call it a single time during the test run, but the 2 faked calls become eligible for garbage collection as soon as ModuleInitialize exits. GC is non-deterministic, so it's impossible to predict what the state of the hook will be after ModuleInitialize exits.

OK, good to know. The event here is triggered within module initialize, not in the test - so if the calls get garbage collected after ModuleInitialize it seems that it'd be ok.

If the event handler triggers a call to the faked methods, or Excel attempts to generate a VBA message box, all bets are now off because neither your code or Rubberduck's code has control over how that call is made.

Oh interesting, if I understand correctly, a MsgBox would have different behavior if it's created by VBA that's run by Excel (i.e. VBA in the Sheet's event handler) versus VBA run by VBA (i.e. a Sub / Function). I wonder why the expected behavior would be different. Is it a timing issue - i.e. events are asynchronous and Rubberduck has no way of knowing when the event has completed and it can move on from ModuleInitialize?

Creating a sub, moving all the code in the event handler to that sub, and then calling the sub from the event handler wouldn't help, would it?

Excel Crash Event Log

bclothier commented 5 years ago

Depends on to where it gets moved.

Remember the objective is to test your behaviors in an unit, so you want to eliminate all the event handling and dancing with the documents. For a good example of this, see this blog.

For your unit test to be independent, you will want to be able to invoke the sub directly without using events. Thus, moving your sub to a private sub on Excel worksheet won't do anything for you. Moving it to a public standard module might simplify setup but now you're polluting the global namespace with a new public function that might not be applicable/appropriate. A more clean method is to create classes and delegate the responsibility to it. You then use the worksheets' events to invoke the appropriate methods on the class instance. You could go further and use interfaces but for starter, a class instance should be a big step up.

bclothier commented 5 years ago

I'm going to close this as by-design since as discussed, this is not appropriate way to set up tests involving hosts' events. If there are other issues or legitimate cases you think you can argue for why hosts should be involved (which most likely makes it is no longer unit test but rather integration test), feel free to open an issue making the case.