Skip to content

Commit

Permalink
Avoid picking up 'ReturnsWhen' results when should use 'Returns' result
Browse files Browse the repository at this point in the history
  • Loading branch information
tommy9 committed Jun 26, 2018
1 parent 5b99df7 commit 368c724
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 2 deletions.
5 changes: 3 additions & 2 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/FakeBase.cs
Expand Up @@ -59,8 +59,9 @@ protected bool TrySetReturnValue(string parameter, object value, bool any = fals
protected bool TrySetReturnValue(bool any = false)
{
var returnInfo =
ReturnValues.Where(r => r.Invocation == (any ? FakesProvider.AllInvocations : (int) InvocationCount))
.ToList();
ReturnValues.Where(r => r.Invocation == (any ? FakesProvider.AllInvocations : (int) InvocationCount) &&
r.Argument != null &&
r.Argument == string.Empty).ToList();

if (returnInfo.Count <= 0)
{
Expand Down
40 changes: 40 additions & 0 deletions RubberduckTests/IntegrationTests/FakeTests.bas
Expand Up @@ -335,3 +335,43 @@ TestExit:
TestFail:
Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
End Sub

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

Dim userInput As String

Fakes.InputBox.ReturnsWhen "Prompt", "Second", "User entry 2"
Fakes.MsgBox.Returns vbOK

Dim msgBoxRetVal As Integer
msgBoxRetVal = MsgBox("This is faked", Title:="My Title")

Assert.IsTrue msgBoxRetVal = vbOK
Fakes.MsgBox.Verify.Once

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

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

Dim userInput As String
Fakes.InputBox.ReturnsWhen "prompt", "Dummy1", "dummy1 user input"
Fakes.InputBox.ReturnsWhen "prompt", "Expected", "expected user input"
Fakes.InputBox.ReturnsWhen "prompt", "Dummy2", "dummy2 user input"

userInput = InputBox(prompt:="Expected")

Assert.AreEqual "expected user input", userInput

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

0 comments on commit 368c724

Please sign in to comment.