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 301 forks source link

Rubberduck is not able to run two testmodules with identically named methods in Microsoft Access (MSO 2013) and VBA 7.1 #570

Closed HenrikBach1 closed 9 years ago

HenrikBach1 commented 9 years ago

Steps to reproduce the error:

  1. Create two different test modules (TestModule1 & -2) with a test method in each.
  2. Run all tests in Rubberduck.

An error emerges: Microsoft Access cannot find the procedure .ModuleInitialize.

rubberduck203 commented 9 years ago

Thanks for reporting this! We'll look into it.

retailcoder commented 9 years ago

@ckuhn203 does Acces' Application.Run syntax support module-qualified calls? I can't remember off the top of my head, but if the syntax doesn't allow it then this might only work in Excel..

If the ModuleInitialize methods are not used, they can be safely removed. If they serve a purpose, then a work-around could be to leverage the '@ModuleInitialize and '@ModuleCleanup markers, and make sure the methods have distinct names in each test module.

TestModule1

'@ModuleInitialize
Public Sub InitializeTestModule1()
    '...
End Sub

'@ModuleCleanup
Public Sub CleanupTestModule1()
    '...
End Sub

TestModule2

'@ModuleInitialize
Public Sub InitializeTestModule2()
    '...
End Sub

'@ModuleCleanup
Public Sub CleanupTestModule2()
    '...
End Sub
rubberduck203 commented 9 years ago

It does not support module specific calls.

    protected virtual string GenerateMethodCall(QualifiedMemberName qualifiedMemberName)
    {
        //Access only supports Project.Procedure syntax. Error occurs if there are naming conflicts.
        // http://msdn.microsoft.com/en-us/library/office/ff193559(v=office.15).aspx
        // https://github.com/retailcoder/Rubberduck/issues/109

        var projectName = qualifiedMemberName.QualifiedModuleName.Project.Name;
        return string.Concat(projectName, ".", qualifiedMemberName.MemberName);
    }

https://github.com/retailcoder/Rubberduck/blob/master/RetailCoder.VBE/VBEHost/AccessApp.cs#L16

So, yes. Each method will need a unique name.

rubberduck203 commented 9 years ago

Something I would like to do, as a separate feature, is create a template/snippet system where code can be created by the user and easily insert into a code module. Once that occurs, we can easily switch the Unit Test Module template to use this system. At that point, it would be easy to have the HostApp retrieve the correct template for its environment. This might even include the ability to just shut off Unit Testing for that particular host.

@HenrikBach1 if you can confirm that the workaround works, I'll create a separate issue for that and reference this one. Either way, I think we'll leave this issue open for the time being.

retailcoder commented 9 years ago

I didn't mention it, but the TestInitialize and TestCleanup methods would also need a unique name.

retailcoder commented 9 years ago

Relevant read: #109

HenrikBach1 commented 9 years ago

No, it doesn't work as expected.

To me it seems, that neither TestInitialize or TestCleanup is called from the framework. Probably neither the other methods, too.

To be more specific: It ran the test methods successfully in the first module. But, otherwise returned false for the rest, due to some pre-condition/Baseline setup in TestInitialized and removal in TestCleanup.

However, running all tests for a single test module with unique names is repeatable.

rubberduck203 commented 9 years ago

Repro:

Use the test explorer to insert 2 identical new test modules. TestModule1 and TestModule2.

Option Compare Database
Option Explicit

Option Private Module

'@TestModule
Private Assert As New Rubberduck.AssertClass

'@ModuleInitialize
Public Sub ModuleInitialize()
    'this method runs once per module.
End Sub

'@ModuleCleanup
Public Sub ModuleCleanup()
    'this method runs once per module.
End Sub

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

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

'@TestMethod
Public Sub TestMethod1() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

Exception

This gives me an unhandled exception with the following stack trace: (I'm concerned that it's unhandled and not showing up as a simple test failure.)

\ Exception Text ** System.Runtime.InteropServices.COMException (0x800A09D5): Microsoft Access cannot find the procedure 'Database5.ModuleInitialize.' at Microsoft.Office.Interop.Access._Application.Run(String Procedure, Object& Arg1, Object& Arg2, Object& Arg3, Object& Arg4, Object& Arg5, Object& Arg6, Object& Arg7, Object& Arg8, Object& Arg9, Object& Arg10, Object& Arg11, Object& Arg12, Object& Arg13, Object& Arg14, Object& Arg15, Object& Arg16, Object& Arg17, Object& Arg18, Object& Arg19, Object& Arg20, Object& Arg21, Object& Arg22, Object& Arg23, Object& Arg24, Object& Arg25, Object& Arg26, Object& Arg27, Object& Arg28, Object& Arg29, Object& Arg30) at Rubberduck.VBEHost.AccessApp.Run(QualifiedMemberName qualifiedMemberName) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\VBEHost\AccessApp.cs:line 13 at Rubberduck.UnitTesting.ProjectTestExtensions.RunMethodsWithAttribute[TAttribute](VBComponent component) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UnitTesting\ProjectTestExtensions.cs:line 28 at Rubberduck.UI.UnitTesting.TestExplorerDockablePresenter._testEngine_ModuleInitialize(Object sender, TestModuleEventArgs e) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UI\UnitTesting\TestExplorerDockablePresenter.cs:line 52 at Rubberduck.UnitTesting.TestEngine.RunModuleInitialize(QualifiedModuleName qualifiedModuleName) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UnitTesting\TestEngine.cs:line 54 at Rubberduck.UnitTesting.TestEngine.AssignResults(IEnumerable1 testMethods) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UnitTesting\TestEngine.cs:line 105 at Rubberduck.UnitTesting.TestEngine.Run(IEnumerable1 tests) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UnitTesting\TestEngine.cs:line 94 at Rubberduck.UI.UnitTesting.TestExplorerDockablePresenter.RunTests(IEnumerable`1 tests) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UI\UnitTesting\TestExplorerDockablePresenter.cs:line 96 at Rubberduck.UI.UnitTesting.TestExplorerDockablePresenter.OnExplorerRunAllTestsButtonClick(Object sender, EventArgs e) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UI\UnitTesting\TestExplorerDockablePresenter.cs:line 111 at Rubberduck.UI.UnitTesting.TestExplorerWindow.OnButtonClick(EventHandler clickEvent) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UI\UnitTesting\TestExplorerWindow.cs:line 73 at Rubberduck.UI.UnitTesting.TestExplorerWindow.RunAllTestsMenuItemClicked(Object sender, EventArgs e) in c:\Users\Mathieu\Source\Repos\Rubberduck\RetailCoder.VBE\UI\UnitTesting\TestExplorerWindow.cs:line 122 at System.Windows.Forms.ToolStripItem.RaiseEvent(Object key, EventArgs e) at System.Windows.Forms.ToolStripMenuItem.OnClick(EventArgs e) at System.Windows.Forms.ToolStripItem.HandleClick(EventArgs e) at System.Windows.Forms.ToolStripItem.HandleMouseUp(MouseEventArgs e) at System.Windows.Forms.ToolStripItem.FireEventInteractive(EventArgs e, ToolStripItemEventType met) at System.Windows.Forms.ToolStripItem.FireEvent(EventArgs e, ToolStripItemEventType met) at System.Windows.Forms.ToolStrip.OnMouseUp(MouseEventArgs mea) at System.Windows.Forms.ToolStripDropDown.OnMouseUp(MouseEventArgs mea) at System.Windows.Forms.Control.WmMouseUp(Message& m, MouseButtons button, Int32 clicks) at System.Windows.Forms.Control.WndProc(Message& m) at System.Windows.Forms.ScrollableControl.WndProc(Message& m) at System.Windows.Forms.ToolStrip.WndProc(Message& m) at System.Windows.Forms.ToolStripDropDown.WndProc(Message& m) at System.Windows.Forms.Control.ControlNativeWindow.OnMessage(Message& m) at System.Windows.Forms.Control.ControlNativeWindow.WndProc(Message& m) at System.Windows.Forms.NativeWindow.Callback(IntPtr hWnd, Int32 msg, IntPtr wparam, IntPtr lparam)

Fix:

Make sure all annotated methods have a unique name. In this case, I put a 2 after each procedure in TestModule2.

Option Compare Database
Option Explicit

Option Private Module

'@TestModule
Private Assert As New Rubberduck.AssertClass

'@ModuleInitialize
Public Sub ModuleInitialize2()
    'this method runs once per module.
End Sub

'@ModuleCleanup
Public Sub ModuleCleanup2()
    'this method runs once per module.
End Sub

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

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

'@TestMethod
Public Sub TestMethod2() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

Everything works as expected again.

Verify Module and Test Intialize/Cleanup runs.

TestModule1

Option Compare Database
Option Explicit

Option Private Module

'@TestModule
Private Assert As New Rubberduck.AssertClass

'@ModuleInitialize
Public Sub ModuleInitialize()
    'this method runs once per module.
    Debug.Print "Module Initalize"
End Sub

'@ModuleCleanup
Public Sub ModuleCleanup()
    'this method runs once per module.
    Debug.Print "Module Cleanup"
End Sub

'@TestInitialize
Public Sub TestInitialize()
    'this method runs before every test in the module.
    Debug.Print "Test Intialize"
End Sub

'@TestCleanup
Public Sub TestCleanup()
    'this method runs afer every test in the module.
    Debug.Print "Test Cleanup"
End Sub

'@TestMethod
Public Sub TestMethod1() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True
    Debug.Print "TestMethod1 Successful"

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

'@TestMethod
Public Sub TestMethod2() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True
    Debug.Print "TestMethod2 Successful"

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

TestModule2

Option Compare Database
Option Explicit

Option Private Module

'@TestModule
Private Assert As New Rubberduck.AssertClass

'@ModuleInitialize
Public Sub ModuleInitialize2()
    'this method runs once per module.
    Debug.Print "Module Initalize"
End Sub

'@ModuleCleanup
Public Sub ModuleCleanup2()
    'this method runs once per module.
    Debug.Print "Module Cleanup"
End Sub

'@TestInitialize
Public Sub TestInitialize2()
    'this method runs before every test in the module.
    Debug.Print "Test Intialize"
End Sub

'@TestCleanup
Public Sub TestCleanup2()
    'this method runs afer every test in the module.
    Debug.Print "Test Cleanup"
End Sub

'@TestMethod
Public Sub TestMethod3() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True
    Debug.Print "TestMethod3 Successful"

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

'@TestMethod
Public Sub TestMethod4() 'TODO: Rename test
    On Error GoTo TestFail

    'Arrange:

    'Act:

    'Assert:
    Assert.IsTrue True
    Debug.Print "TestMethod4 Successful"

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

Results:

Module Initalize Test Intialize TestMethod1 Successful Test Cleanup Module Cleanup Module Initalize Test Intialize TestMethod2 Successful Test Cleanup Module Cleanup Module Initalize Test Intialize Test Intialize Test Cleanup Module Cleanup Module Initalize Test Intialize Test Cleanup Test Cleanup Module Cleanup Module Initalize Test Intialize TestMethod3 Successful Test Cleanup Module Cleanup Module Initalize Test Intialize TestMethod4 Successful Test Cleanup Module Cleanup

rubberduck203 commented 9 years ago

I found some interesting things that I will open issues for so we can verify whether or not they're still issues in the next release.

  1. Module Intialize/Cleanup is running on every iteration instead of once per TestModule.
  2. Indenting the entire module one tab breaks the test discovery. I'm assuming we have a parse error in that situation.
retailcoder commented 9 years ago

@ckuhn203 module initialize/cleanup is supposed to run once per module, not sure what happened here, but I could have sworn it was the case. This is definitely getting fixed by next release. Test discovery breaks specifically because we are not using the parser for that, but still the frail VBIDE code from 1.0 which was essentially ported from the VBA version of the unit testing framework - rewriting test discovery to work off the parse results will definitely fix this.

And we should fix as much as possible of the unit testing issues before we release 1.4, because of the architecture changes - let's leverage the separate dll and limit updates on the testing project, i.e. let's cram every fix we can into the next release!

rubberduck203 commented 9 years ago

I'm assuming this was fixed in the great 2.0 re-write. =)

retailcoder commented 9 years ago

@ckuhn203 well, Access will never let us have same-name methods in different modules; I'll make a separate issue for parameterizing the test module template, which is really just a big hard-coded string literal.

This will give us more flexibility when generating the methods, to be smarter about naming them - regardless of the host app.

retailcoder commented 9 years ago

Oh, and yeah, I'll be catching that exception ;-)

rubberduck203 commented 9 years ago

Lol. Fair enough @retailcoder.