Skip to content

Commit 5b99df7

Browse files
authored
Merge pull request #4131 from tommy9/AddMoreFakes
Add fakes for Now, Time and Date functions
2 parents fa78fb4 + f0b7098 commit 5b99df7

File tree

8 files changed

+231
-2
lines changed

8 files changed

+231
-2
lines changed

Rubberduck.Main/ComClientLibrary/Abstract/UnitTesting/IFakesProvider.cs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -67,5 +67,17 @@ public interface IFakesProvider
6767
[DispId(14)]
6868
[Description("Configures VBA.FileSystem.CurDir calls.")]
6969
IFake CurDir { get; }
70+
71+
[DispId(15)]
72+
[Description("Configures VBA.DateTime.Now calls.")]
73+
IFake Now { get; }
74+
75+
[DispId(16)]
76+
[Description("Configures VBA.DateTime.Time calls.")]
77+
IFake Time { get; }
78+
79+
[DispId(17)]
80+
[Description("Configures VBA.DateTime.Date calls.")]
81+
IFake Date { get; }
7082
}
7183
}

Rubberduck.Main/ComClientLibrary/UnitTesting/FakeBase.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ protected override void TrackUsage(string parameter, object value, string typeNa
4141
SuppressesCall = false;
4242
}
4343

44-
private bool TrySetReturnValue(string parameter, object value, bool any = false)
44+
protected bool TrySetReturnValue(string parameter, object value, bool any = false)
4545
{
4646
var returnInfo =
4747
ReturnValues.Where(r => r.Invocation == (any ? FakesProvider.AllInvocations : (int) InvocationCount) &&
@@ -56,7 +56,7 @@ private bool TrySetReturnValue(string parameter, object value, bool any = false)
5656
return true;
5757
}
5858

59-
private bool TrySetReturnValue(bool any = false)
59+
protected bool TrySetReturnValue(bool any = false)
6060
{
6161
var returnInfo =
6262
ReturnValues.Where(r => r.Invocation == (any ? FakesProvider.AllInvocations : (int) InvocationCount))
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
using System;
2+
using System.Runtime.InteropServices;
3+
4+
namespace Rubberduck.UnitTesting.Fakes
5+
{
6+
internal class Date : FakeBase
7+
{
8+
private static readonly IntPtr ProcessAddress = EasyHook.LocalHook.GetProcAddress(TargetLibrary, "rtcGetDateVar");
9+
10+
public Date()
11+
{
12+
InjectDelegate(new DateDelegate(DateCallback), ProcessAddress);
13+
}
14+
15+
[DllImport(TargetLibrary, SetLastError = true)]
16+
private static extern void rtcGetDateVar(out object retVal);
17+
18+
[UnmanagedFunctionPointer(CallingConvention.StdCall, SetLastError = true)]
19+
private delegate void DateDelegate(IntPtr retVal);
20+
21+
public void DateCallback(IntPtr retVal)
22+
{
23+
OnCallBack(true);
24+
if (!TrySetReturnValue()) // specific invocation
25+
{
26+
TrySetReturnValue(true); // any invocation
27+
}
28+
if (PassThrough)
29+
{
30+
object result;
31+
rtcGetDateVar(out result);
32+
Marshal.GetNativeVariantForObject(result, retVal);
33+
return;
34+
}
35+
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
36+
}
37+
}
38+
}
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
using System;
2+
using System.Runtime.InteropServices;
3+
4+
namespace Rubberduck.UnitTesting.Fakes
5+
{
6+
internal class Now : FakeBase
7+
{
8+
private static readonly IntPtr ProcessAddress = EasyHook.LocalHook.GetProcAddress(TargetLibrary, "rtcGetPresentDate");
9+
10+
public Now()
11+
{
12+
InjectDelegate(new NowDelegate(NowCallback), ProcessAddress);
13+
}
14+
15+
[DllImport(TargetLibrary, SetLastError = true)]
16+
private static extern void rtcGetPresentDate(out object retVal);
17+
18+
[UnmanagedFunctionPointer(CallingConvention.StdCall, SetLastError = true)]
19+
private delegate void NowDelegate(IntPtr retVal);
20+
21+
public void NowCallback(IntPtr retVal)
22+
{
23+
OnCallBack(true);
24+
if (!TrySetReturnValue()) // specific invocation
25+
{
26+
TrySetReturnValue(true); // any invocation
27+
}
28+
if (PassThrough)
29+
{
30+
object result;
31+
rtcGetPresentDate(out result);
32+
Marshal.GetNativeVariantForObject(result, retVal);
33+
return;
34+
}
35+
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
36+
}
37+
}
38+
}
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
using System;
2+
using System.Runtime.InteropServices;
3+
4+
namespace Rubberduck.UnitTesting.Fakes
5+
{
6+
internal class Time : FakeBase
7+
{
8+
private static readonly IntPtr ProcessAddress = EasyHook.LocalHook.GetProcAddress(TargetLibrary, "rtcGetTimeVar");
9+
10+
public Time()
11+
{
12+
InjectDelegate(new TimeDelegate(TimeCallback), ProcessAddress);
13+
}
14+
15+
[DllImport(TargetLibrary, SetLastError = true)]
16+
private static extern void rtcGetTimeVar(out object retVal);
17+
18+
[UnmanagedFunctionPointer(CallingConvention.StdCall, SetLastError = true)]
19+
private delegate void TimeDelegate(IntPtr retVal);
20+
21+
public void TimeCallback(IntPtr retVal)
22+
{
23+
OnCallBack(true);
24+
if (!TrySetReturnValue()) // specific invocation
25+
{
26+
TrySetReturnValue(true); // any invocation
27+
}
28+
if (PassThrough)
29+
{
30+
object result;
31+
rtcGetTimeVar(out result);
32+
Marshal.GetNativeVariantForObject(result, retVal);
33+
return;
34+
}
35+
Marshal.GetNativeVariantForObject(ReturnValue ?? 0, retVal);
36+
}
37+
}
38+
}

Rubberduck.Main/ComClientLibrary/UnitTesting/FakesProvider.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,9 @@ private T RetrieveOrCreateFunction<T>(Type type) where T : class
7373
public IStub ChDir => RetrieveOrCreateFunction<IStub>(typeof(ChDir));
7474
public IStub ChDrive => RetrieveOrCreateFunction<IStub>(typeof(ChDrive));
7575
public IFake CurDir => RetrieveOrCreateFunction<IFake>(typeof(CurDir));
76+
public IFake Now => RetrieveOrCreateFunction<IFake>(typeof(Now));
77+
public IFake Time => RetrieveOrCreateFunction<IFake>(typeof(Time));
78+
public IFake Date => RetrieveOrCreateFunction<IFake>(typeof(Date));
7679

7780

7881
#endregion

Rubberduck.Main/Rubberduck.Main.csproj

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -243,6 +243,9 @@
243243
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IFakesProvider.cs" />
244244
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IStub.cs" />
245245
<Compile Include="ComClientLibrary\Abstract\UnitTesting\IVerify.cs" />
246+
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Date.cs" />
247+
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Time.cs" />
248+
<Compile Include="ComClientLibrary\UnitTesting\Fakes\Now.cs" />
246249
<Compile Include="ComClientLibrary\UnitTesting\PermissiveAssertClass.cs" />
247250
<Compile Include="ComClientLibrary\UnitTesting\FakeBase.cs" />
248251
<Compile Include="ComClientLibrary\UnitTesting\Fakes\CurDir.cs" />

RubberduckTests/IntegrationTests/FakeTests.bas

Lines changed: 97 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -238,3 +238,100 @@ TestExit:
238238
TestFail:
239239
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
240240
End Sub
241+
242+
'@TestMethod
243+
Public Sub NowFakeWorks()
244+
On Error GoTo TestFail
245+
246+
With Fakes.Now
247+
.Returns #1/1/2018 9:00:00 AM#
248+
Assert.IsTrue Now = #1/1/2018 9:00:00 AM#
249+
.Verify.Once
250+
End With
251+
252+
TestExit:
253+
Exit Sub
254+
TestFail:
255+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
256+
End Sub
257+
258+
'@TestMethod
259+
Public Sub NowFakePassThroughWorks()
260+
On Error GoTo TestFail
261+
262+
With Fakes.Now
263+
.Returns #1/1/2018 9:00:00 AM#
264+
.Passthrough = True
265+
Assert.IsTrue Now <> #1/1/2018 9:00:00 AM#
266+
.Verify.Once
267+
End With
268+
269+
TestExit:
270+
Exit Sub
271+
TestFail:
272+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
273+
End Sub
274+
275+
'@TestMethod
276+
Public Sub TimeFakeWorks()
277+
On Error GoTo TestFail
278+
279+
With Fakes.Time
280+
.Returns #9:00:00 AM#
281+
Assert.IsTrue Time = #9:00:00 AM#
282+
.Verify.Once
283+
End With
284+
TestExit:
285+
Exit Sub
286+
TestFail:
287+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
288+
End Sub
289+
290+
'@TestMethod
291+
Public Sub TimeFakePassThroughWorks()
292+
On Error GoTo TestFail
293+
294+
With Fakes.Time
295+
.Returns #9:00:00 AM#
296+
.Passthrough = True
297+
Assert.IsTrue Time <> #9:00:00 AM#
298+
.Verify.Once
299+
End With
300+
301+
TestExit:
302+
Exit Sub
303+
TestFail:
304+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
305+
End Sub
306+
307+
'@TestMethod
308+
Public Sub DateFakeWorks()
309+
On Error GoTo TestFail
310+
311+
With Fakes.Date
312+
.Returns #1/1/1993#
313+
Assert.IsTrue Date = #1/1/1993#
314+
.Verify.Once
315+
End With
316+
TestExit:
317+
Exit Sub
318+
TestFail:
319+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
320+
End Sub
321+
322+
323+
'@TestMethod
324+
Public Sub DateFakePassThroughWorks()
325+
On Error GoTo TestFail
326+
327+
With Fakes.Date
328+
.Returns #1/1/1993#
329+
.Passthrough = True
330+
Assert.IsTrue Date <> #1/1/1993#
331+
.Verify.Once
332+
End With
333+
TestExit:
334+
Exit Sub
335+
TestFail:
336+
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
337+
End Sub

0 commit comments

Comments
 (0)