Skip to content

Commit

Permalink
Add Date fake and integration tests
Browse files Browse the repository at this point in the history
  • Loading branch information
tommy9 committed Jun 23, 2018
1 parent 1e18d71 commit 6ba990d
Show file tree
Hide file tree
Showing 5 changed files with 76 additions and 0 deletions.
Expand Up @@ -75,5 +75,9 @@ public interface IFakesProvider
[DispId(16)]
[Description("Configures VBA.DateTime.Time calls.")]
IFake Time { get; }

[DispId(17)]
[Description("Configures VBA.DateTime.Date calls.")]
IFake Date { get; }
}
}
38 changes: 38 additions & 0 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/Fakes/Date.cs
@@ -0,0 +1,38 @@
using System;
using System.Runtime.InteropServices;

namespace Rubberduck.UnitTesting.Fakes
{
internal class Date : FakeBase
{
private static readonly IntPtr ProcessAddress = EasyHook.LocalHook.GetProcAddress(TargetLibrary, "rtcGetDateVar");

public Date()
{
InjectDelegate(new DateDelegate(DateCallback), ProcessAddress);
}

[DllImport(TargetLibrary, SetLastError = true)]
private static extern void rtcGetDateVar(out object retVal);

[UnmanagedFunctionPointer(CallingConvention.StdCall, SetLastError = true)]
private delegate void DateDelegate(IntPtr retVal);

public void DateCallback(IntPtr retVal)
{
OnCallBack(true);
if (!TrySetReturnValue()) // specific invocation
{
TrySetReturnValue(true); // any invocation
}
if (PassThrough)
{
object result;
rtcGetDateVar(out result);
Marshal.GetNativeVariantForObject(result, retVal);
return;
}
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
}
}
}
Expand Up @@ -75,6 +75,7 @@ public void StopTest()
public IFake CurDir => RetrieveOrCreateFunction<IFake>(typeof(CurDir));
public IFake Now => RetrieveOrCreateFunction<IFake>(typeof(Now));
public IFake Time => RetrieveOrCreateFunction<IFake>(typeof(Time));
public IFake Date => RetrieveOrCreateFunction<IFake>(typeof(Date));


#endregion
Expand Down
1 change: 1 addition & 0 deletions Rubberduck.Main/Rubberduck.Main.csproj
Expand Up @@ -243,6 +243,7 @@
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IFakesProvider.cs" />
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IStub.cs" />
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IVerify.cs" />
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Date.cs" />
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Time.cs" />
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Now.cs" />
<Compile Include="ComClientLibrary\UnitTesting\PermissiveAssertClass.cs" />
Expand Down
32 changes: 32 additions & 0 deletions RubberduckTests/IntegrationTests/FakeTests.bas
Expand Up @@ -303,3 +303,35 @@ TestExit:
TestFail:
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

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

With Fakes.Date
.Returns #1/1/1993#
Assert.IsTrue Date = #1/1/1993#
.Verify.Once
End With
TestExit:
Exit Sub
TestFail:
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub


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

With Fakes.Date
.Returns #9:00:00 AM#
.Passthrough = True
Assert.IsTrue Date <> #1/1/1993#
.Verify.Once
End With
TestExit:
Exit Sub
TestFail:
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

0 comments on commit 6ba990d

Please sign in to comment.