Skip to content

Commit

Permalink
Merge pull request #6056 from tommy9/fakesFixes
Browse files Browse the repository at this point in the history
Fakes fixes
  • Loading branch information
retailcoder authored Nov 24, 2022
2 parents bffd6ff + a30aeed commit 18213d9
Show file tree
Hide file tree
Showing 6 changed files with 93 additions and 3 deletions.
2 changes: 1 addition & 1 deletion Rubberduck.Main/ComClientLibrary/UnitTesting/FakeBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ protected bool TrySetReturnValue(bool any = false)

#region IFake

private static readonly List<ReturnValueInfo> ReturnValues = new List<ReturnValueInfo>();
private readonly List<ReturnValueInfo> ReturnValues = new List<ReturnValueInfo>();
public virtual void Returns(object value, int invocation = FakesProvider.AllInvocations)
{
ReturnValues.Add(new ReturnValueInfo(invocation, string.Empty, string.Empty, value));
Expand Down
6 changes: 4 additions & 2 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/Fakes/Date.cs
Original file line number Diff line number Diff line change
Expand Up @@ -18,14 +18,16 @@ public Date()
public void DateCallback(IntPtr retVal)
{
OnCallBack(true);
if (!TrySetReturnValue()) // specific invocation
if (!TrySetReturnValue())
{
TrySetReturnValue(true); // any invocation
TrySetReturnValue(true);
}
if (PassThrough)
{
FakesProvider.SuspendFake(typeof(Now));
var nativeCall = Marshal.GetDelegateForFunctionPointer<DateDelegate>(NativeFunctionAddress);
nativeCall(retVal);
FakesProvider.ResumeFake(typeof(Now));
return;
}
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
Expand Down
2 changes: 2 additions & 0 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/Fakes/Time.cs
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,10 @@ public void TimeCallback(IntPtr retVal)
}
if (PassThrough)
{
FakesProvider.SuspendFake(typeof(Now));
var nativeCall = Marshal.GetDelegateForFunctionPointer<TimeDelegate>(NativeFunctionAddress);
nativeCall(retVal);
FakesProvider.ResumeFake(typeof(Now));
return;
}
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
Expand Down
24 changes: 24 additions & 0 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/FakesProvider.cs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,30 @@ public void StartTest()
CodeIsUnderTest = true;
}

public static void SuspendFake(Type type)
{
foreach (var fake in ActiveFakes.Values)
{
if (fake.GetType() == type)
{
fake.DisableHook();
return;
}
}
}

public static void ResumeFake(Type type)
{
foreach (var fake in ActiveFakes.Values)
{
if (fake.GetType() == type)
{
fake.EnableHook();
return;
}
}
}

public void StopTest()
{
foreach (var fake in ActiveFakes.Values)
Expand Down
15 changes: 15 additions & 0 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/StubBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,21 @@ protected void OnCallBack(bool trackNoParams = false)
}
}

public void DisableHook()
{
foreach (var hook in _hooks)
{
hook.ThreadACL.SetExclusiveACL(new[] { 0 });
}
}
public void EnableHook()
{
foreach (var hook in _hooks)
{
hook.ThreadACL.SetInclusiveACL(new[] { 0 });
}
}

public virtual void Dispose()
{
foreach (var hook in _hooks)
Expand Down
47 changes: 47 additions & 0 deletions RubberduckTests/IntegrationTests/FakeTests.bas
Original file line number Diff line number Diff line change
Expand Up @@ -729,3 +729,50 @@ TestExit:
TestFail:
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

'@TestMethod
Public Sub TestIssue4476()
On Error GoTo TestFail

'Arrange:
Fakes.Now.PassThrough = True
Fakes.Date.PassThrough = True
Dim retVal As Variant

'Act:
retVal = Now
retVal = Date '<== KA-BOOOM
retVal = Now 'ensure fake reinstated

'Assert:
Fakes.Now.Verify.Exactly 2
Fakes.Date.Verify.Once

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

'@TestMethod
Public Sub TestIssue5944()
On Error GoTo TestFail

Fakes.InputBox.Returns 20
Fakes.MsgBox.Returns 20

Dim inputBoxReturnValue As String
Dim msgBoxReturnValue As Integer

inputBoxReturnValue = InputBox("Dummy")
msgBoxReturnValue = MsgBox("Dummy")

Fakes.MsgBox.Verify.Once
Fakes.InputBox.Verify.Once

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

0 comments on commit 18213d9

Please sign in to comment.