Skip to content

Commit 0462e65

Browse files
authored
Merge pull request #3888 from bclothier/FixUnitTesting
Fix Heisenbug in unit test.
2 parents 4e9c732 + 44f7887 commit 0462e65

File tree

6 files changed

+66
-20
lines changed

6 files changed

+66
-20
lines changed

Rubberduck.Core/App.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,6 @@
1313
using Rubberduck.Parsing.Inspections.Resources;
1414
using Rubberduck.Parsing.UIContext;
1515
using Rubberduck.UI.Command;
16-
using Rubberduck.VBEditor.ComManagement;
1716
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1817
using Rubberduck.VBEditor.Utility;
1918
using Rubberduck.VersionCheck;

Rubberduck.Core/UnitTesting/ProjectTestExtensions.cs

Lines changed: 23 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
1-
using System.Runtime.InteropServices;
1+
using System;
2+
using System.Runtime.InteropServices;
23
using System.Reflection;
3-
using System.IO;
4+
using Microsoft.Win32;
45
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
56

67
namespace Rubberduck.UnitTesting
@@ -10,12 +11,27 @@ public static class ProjectTestExtensions
1011
{
1112
public static void EnsureReferenceToAddInLibrary(this IVBProject project)
1213
{
13-
// FIXME should rely on the assembly containing the UnitTest components.
14-
// Those are not necessarily the same.
15-
var assembly = Assembly.GetEntryAssembly();
14+
var libFolder = IntPtr.Size == 8 ? "win64" : "win32";
15+
// TODO: This assumes the current assembly is same major/minor as the TLB!!!
16+
var libVersion = Assembly.GetExecutingAssembly().GetName().Version;
17+
const string libGuid = RubberduckGuid.RubberduckTypeLibGuid;
18+
var pathKey = Registry.ClassesRoot.OpenSubKey($@"TypeLib\{{{libGuid}}}\{libVersion.Major}.{libVersion.Minor}\0\{libFolder}");
19+
20+
var referencePath = pathKey?.GetValue(string.Empty, string.Empty) as string;
21+
string name = null;
1622

17-
var name = assembly.GetName().Name.Replace('.', '_');
18-
var referencePath = Path.ChangeExtension(assembly.Location, ".tlb");
23+
if (!string.IsNullOrWhiteSpace(referencePath))
24+
{
25+
var tlbKey =
26+
Registry.ClassesRoot.OpenSubKey($@"TypeLib\{{{libGuid}}}\{libVersion.Major}.{libVersion.Minor}");
27+
28+
name = tlbKey?.GetValue(string.Empty, string.Empty) as string;
29+
}
30+
31+
if (string.IsNullOrWhiteSpace(referencePath) || string.IsNullOrWhiteSpace(name))
32+
{
33+
throw new InvalidOperationException("Cannot locate the tlb in the registry or the entry may be corrupted. Therefore early binding is not possible");
34+
}
1935

2036
using (var references = project.References)
2137
{

Rubberduck.Core/UnitTesting/TestEngine.cs

Lines changed: 34 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
using NLog;
77
using Rubberduck.Parsing.Annotations;
88
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.UIContext;
910
using Rubberduck.Parsing.VBA;
1011
using Rubberduck.UI;
1112
using Rubberduck.UI.UnitTesting;
@@ -21,17 +22,41 @@ public class TestEngine : ITestEngine
2122
private readonly RubberduckParserState _state;
2223
private readonly IFakesFactory _fakesFactory;
2324
private readonly IVBETypeLibsAPI _typeLibApi;
25+
private readonly IUiDispatcher _uiDispatcher;
2426

2527
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
2628

27-
public TestEngine(TestExplorerModel model, IVBE vbe, RubberduckParserState state, IFakesFactory fakesFactory, IVBETypeLibsAPI typeLibApi)
29+
private bool _testRequested;
30+
private IEnumerable<TestMethod> _tests;
31+
32+
public TestEngine(TestExplorerModel model, IVBE vbe, RubberduckParserState state, IFakesFactory fakesFactory, IVBETypeLibsAPI typeLibApi, IUiDispatcher uiDispatcher)
2833
{
2934
Debug.WriteLine("TestEngine created.");
3035
Model = model;
3136
_vbe = vbe;
3237
_state = state;
3338
_fakesFactory = fakesFactory;
3439
_typeLibApi = typeLibApi;
40+
_uiDispatcher = uiDispatcher;
41+
42+
_state.StateChanged += StateChangedHandler;
43+
}
44+
45+
private void StateChangedHandler(object sender, ParserStateEventArgs e)
46+
{
47+
if (_testRequested && (e.State == ParserState.Ready))
48+
{
49+
_testRequested = false;
50+
_uiDispatcher.InvokeAsync(() =>
51+
{
52+
RunInternal(_tests);
53+
});
54+
}
55+
56+
if (_testRequested && !e.IsError)
57+
{
58+
_testRequested = false;
59+
}
3560
}
3661

3762
public TestExplorerModel Model { get; }
@@ -51,11 +76,18 @@ public void Refresh()
5176

5277
public void Run()
5378
{
79+
_testRequested = true;
80+
_tests = Model.LastRun;
81+
// We will run the tests once parsing has completed
5482
Refresh();
55-
Run(Model.LastRun);
5683
}
5784

5885
public void Run(IEnumerable<TestMethod> tests)
86+
{
87+
_uiDispatcher.InvokeAsync(() => RunInternal(tests));
88+
}
89+
90+
private void RunInternal(IEnumerable<TestMethod> tests)
5991
{
6092
var testMethods = tests as IList<TestMethod> ?? tests.ToList();
6193
if (!testMethods.Any())

Rubberduck.Core/UnitTesting/TestMethod.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@
88
using Rubberduck.UI;
99
using Rubberduck.UI.Controls;
1010
using Rubberduck.VBEditor;
11-
using Rubberduck.VBEditor.Application;
1211
using Rubberduck.VBEditor.ComManagement.TypeLibsAPI;
1312
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1413

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,11 @@ public ParserStateEventArgs(ParserState state, CancellationToken token)
5151

5252
public ParserState State { get; }
5353
public CancellationToken Token { get; }
54+
55+
public bool IsError => (State == ParserState.ResolverError ||
56+
State == ParserState.Error ||
57+
State == ParserState.UnexpectedError);
58+
5459
}
5560

5661
public class RubberduckStatusMessageEventArgs : EventArgs
@@ -535,10 +540,7 @@ public ParserState GetModuleState(QualifiedModuleName module)
535540

536541
private readonly object _statusLockObject = new object();
537542
private ParserState _status;
538-
public ParserState Status
539-
{
540-
get => _status;
541-
}
543+
public ParserState Status => _status;
542544

543545
private void SetStatusWithCancellation(ParserState value, CancellationToken token)
544546
{
@@ -659,7 +661,7 @@ private IReadOnlyList<UnboundMemberDeclaration> AllUnresolvedMemberDeclarationsF
659661
}
660662

661663
private readonly ConcurrentBag<SerializableProject> _builtInDeclarationTrees = new ConcurrentBag<SerializableProject>();
662-
public IProducerConsumerCollection<SerializableProject> BuiltInDeclarationTrees { get { return _builtInDeclarationTrees; } }
664+
public IProducerConsumerCollection<SerializableProject> BuiltInDeclarationTrees => _builtInDeclarationTrees;
663665

664666
/// <summary>
665667
/// Gets a copy of the collected declarations, excluding the built-in ones.

RubberduckTests/Refactoring/MoveCloserToUsageTests.cs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -887,13 +887,11 @@ Dim foo As Object
887887
foo.OtherProperty = 1626
888888
End Sub";
889889

890-
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(input, out var component);
890+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(input, out var component, referenceStdLibs: true);
891+
891892
using (var state = MockParser.CreateAndParse(vbe.Object))
892893
{
893894
var messageBox = new Mock<IMessageBox>();
894-
messageBox.Setup(m => m.Show(It.IsAny<string>(), It.IsAny<string>(),
895-
It.IsAny<MessageBoxButtons>(), It.IsAny<MessageBoxIcon>()))
896-
.Returns(DialogResult.OK);
897895
var refactoring = new MoveCloserToUsageRefactoring(vbe.Object, state, messageBox.Object);
898896
refactoring.Refactor(state.AllUserDeclarations.First(d => d.DeclarationType == DeclarationType.Variable));
899897
var rewriter = state.GetRewriter(component);

0 commit comments

Comments
 (0)