From 7738c5521efdde5020f26769d0d6afe021c3cba5 Mon Sep 17 00:00:00 2001 From: Tim Mackinnon Date: Tue, 30 Apr 2024 01:28:02 +0100 Subject: [PATCH] Make it easier to diagnose mock failures by printing message sends properly and storing the send history in the mock --- .../MockMessageSendTest.class.st | 58 +++++++++++++++++++ .../MockMessageSend.class.st | 15 +++++ src/SUnit-MockObjects/MockObject.class.st | 12 ++-- 3 files changed, 79 insertions(+), 6 deletions(-) create mode 100644 src/SUnit-MockObjects-Tests/MockMessageSendTest.class.st diff --git a/src/SUnit-MockObjects-Tests/MockMessageSendTest.class.st b/src/SUnit-MockObjects-Tests/MockMessageSendTest.class.st new file mode 100644 index 00000000000..5249b88f2d5 --- /dev/null +++ b/src/SUnit-MockObjects-Tests/MockMessageSendTest.class.st @@ -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') +] diff --git a/src/SUnit-MockObjects/MockMessageSend.class.st b/src/SUnit-MockObjects/MockMessageSend.class.st index 02c9bf6bffc..a00868e0266 100644 --- a/src/SUnit-MockObjects/MockMessageSend.class.st +++ b/src/SUnit-MockObjects/MockMessageSend.class.st @@ -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 [ diff --git a/src/SUnit-MockObjects/MockObject.class.st b/src/SUnit-MockObjects/MockObject.class.st index f6418557c5e..b3c4e801845 100644 --- a/src/SUnit-MockObjects/MockObject.class.st +++ b/src/SUnit-MockObjects/MockObject.class.st @@ -86,13 +86,13 @@ 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' } @@ -100,7 +100,7 @@ MockObject >> initialize [ super initialize. messages := OrderedCollection new. - failed := false + failed := OrderedCollection new. ] { #category : 'teaching - returning self' } @@ -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'