Skip to content

Commit

Permalink
Make it easier to diagnose mock failures by printing message sends pr…
Browse files Browse the repository at this point in the history
…operly and storing the send history in the mock
  • Loading branch information
macta committed Apr 30, 2024
1 parent 4ca1de3 commit 7738c55
Show file tree
Hide file tree
Showing 3 changed files with 79 additions and 6 deletions.
58 changes: 58 additions & 0 deletions src/SUnit-MockObjects-Tests/MockMessageSendTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
"
A MockMessageSendTest is a test class for testing the behavior of MockMessageSend
"
Class {
#name : 'MockMessageSendTest',
#superclass : 'TestCase',
#instVars : [
'mockMessage',
'testStream'
],
#category : 'SUnit-MockObjects-Tests-Core',
#package : 'SUnit-MockObjects-Tests',
#tag : 'Core'
}

{ #category : 'running' }
MockMessageSendTest >> setUp [

super setUp.
testStream := WriteStream on: ''

]

{ #category : 'running' }
MockMessageSendTest >> testBinaryMessagePrintOn [
mockMessage := MockMessageSend on: #binaryMsg: with: #(true) do: [ ].

mockMessage printOn: testStream.

self assert: (testStream contents includesSubstring: '#binaryMsg: true')
]

{ #category : 'running' }
MockMessageSendTest >> testKeywordMessageArrayPrintOn [
mockMessage := MockMessageSend on: #keyWord:msg: with: #('hello' #(1 2 3)) do: [ ].

mockMessage printOn: testStream.

self assert: (testStream contents includesSubstring: '#keyWord:msg: ( ''hello'', #(1 2 3) )')
]

{ #category : 'running' }
MockMessageSendTest >> testKeywordMessagePrintOn [
mockMessage := MockMessageSend on: #keyWord:msg: with: #('hello' 'world') do: [ ].

mockMessage printOn: testStream.

self assert: (testStream contents includesSubstring: '#keyWord:msg: ( ''hello'', ''world'' )')
]

{ #category : 'running' }
MockMessageSendTest >> testUnaryMessagePrintOn [
mockMessage := MockMessageSend on: #unaryMsg with: #() do: [ ].

mockMessage printOn: testStream.

self assert: (testStream contents includesSubstring: '#unaryMsg')
]
15 changes: 15 additions & 0 deletions src/SUnit-MockObjects/MockMessageSend.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,21 @@ MockMessageSend >> on: aSymbol with: anArray do: aBlock [
behavior := aBlock
]

{ #category : 'printing' }
MockMessageSend >> printOn: aStream [

aStream nextPutAll: 'Expected Message: '.
selector printOn: aStream.

arguments isEmptyOrNil ifFalse: [
arguments size > 1 ifTrue: [ aStream nextPutAll: ' (' ].
aStream space.
arguments
do: [ :arg | arg printOn: aStream ]
separatedBy: [ aStream nextPutAll: ', ' ].
arguments size > 1 ifTrue: [ aStream nextPutAll: ' )' ]]
]

{ #category : 'accessing' }
MockMessageSend >> selector [

Expand Down
12 changes: 6 additions & 6 deletions src/SUnit-MockObjects/MockObject.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -86,21 +86,21 @@ MockObject >> doesNotUnderstand: aMessage [
"When a message is not understood, check if this is one that have benn taught and if this is the case remove it from the list of messages. This supports the possibility to have sequence of similar messages resulting in different messages. In particular I handle also Joker objects as part of the message argument. See MockObject any"

messages isEmpty
ifTrue: [ failed := true ]
ifTrue: [ failed add: aMessage ]
ifFalse: [ | expected |
expected := messages removeFirst.
(expected matches: aMessage)
ifTrue: [ ^ expected valueWithPossibleArgs: aMessage arguments ]
ifFalse: [ messages addFirst: expected.
failed := true ] ]
ifFalse: [ failed add: aMessage. messages addFirst: expected.
] ]
]

{ #category : 'initialization' }
MockObject >> initialize [

super initialize.
messages := OrderedCollection new.
failed := false
failed := OrderedCollection new.
]

{ #category : 'teaching - returning self' }
Expand Down Expand Up @@ -240,14 +240,14 @@ MockObject >> on: aSelector withArguments: anArray respond: anObject [
MockObject >> on: aSymbol withArguments: anArray verify: aBlock [

messages add: (MockMessageSend on: aSymbol with: anArray do: aBlock).
failed := false

]

{ #category : 'verifying' }
MockObject >> verifyIn: aTestCase [
"Verify that the test did not fail and that all the messages got consumed."

aTestCase deny: failed description: 'Incorrect message sequence'.
aTestCase deny: failed notEmpty description: 'Incorrect message sequence'.
aTestCase
assert: messages isEmpty
description: 'Mock still has messages pending'
Expand Down

0 comments on commit 7738c55

Please sign in to comment.