Dolphin MockObjects

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

Dolphin MockObjects

Oli Bye-4
Not strictly a Beta6 topic, but you did ask us to make sure our
libraries work in D6.

So here is my little MockObjects library and tests (which are green for
me ;-)


| package |
package := Package name: 'Mock'.
package paxVersion: 1;
        basicComment: 'http://mockmobjects.com

See the TestCase for examples.

This package relies on Dolphin''s Method>>= and Method>>hash.
The Squeak version (for example) uses PluggableSet and PlugableDictionary'.


package classNames
        add: #IconFinderShell;
        add: #IconModel;
        add: #MockObject;
        add: #MockTestCase;
        yourself.

package binaryGlobalNames: (Set new
        yourself).

package globalAliases: (Set new
        yourself).

package setPrerequisites: (IdentitySet new
        add: 'C:\data\U284195\Dolphin6\Object Arts\Dolphin\Base\Dolphin';
        add: 'C:\data\U284195\Dolphin6\Object Arts\Dolphin\MVP\Views\Common Controls\Dolphin Common Controls';
        add: 'C:\data\U284195\Dolphin6\Object Arts\Dolphin\MVP\Presenters\List\Dolphin List Presenter';
        add: 'C:\data\U284195\Dolphin6\Object Arts\Dolphin\MVP\Base\Dolphin MVP Base';
        add: 'C:\data\U284195\Dolphin6\Camp Smalltalk\SUnit\SUnit';
        yourself).

package!

"Class Definitions"!

Object subclass: #MockObject
        instanceVariableNames: 'expectations actuals'
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
Model subclass: #IconModel
        instanceVariableNames: 'offset'
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
Presenter subclass: #IconFinderShell
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!
TestCase subclass: #MockTestCase
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        classInstanceVariableNames: ''!

"Global Aliases"!


"Loose Methods"!

"End of package definition"!

"Source Globals"!

"Classes"!

MockObject guid: (GUID fromString: '{2CF1B532-BEE1-407C-9AD2-FBF89901AB90}')!
MockObject comment: ''!
!MockObject categoriesForClass!Kernel-Objects! !
!MockObject methodsFor!

doesNotUnderstand: failedMessage
        actuals add: failedMessage.
        ^expectations at: failedMessage.!

expect: selector
        expectations at: selector put: self.!

expect: selector return: reply
        expectations at: selector put: reply!

initialize
        expectations := Dictionary new.
        actuals := Set new.!

verify
        ^(expectations keys equals: actuals) ifFalse: [Error signal: 'Does not verify'].! !
!MockObject categoriesFor: #doesNotUnderstand:!public! !
!MockObject categoriesFor: #expect:!public! !
!MockObject categoriesFor: #expect:return:!public! !
!MockObject categoriesFor: #initialize!private! !
!MockObject categoriesFor: #verify!private! !

!MockObject class methodsFor!

new
        "Answer a new initialize instance of the receiver."

        ^super new initialize! !
!MockObject class categoriesFor: #new!public! !

IconModel guid: (GUID fromString: '{439EEEC0-AE6B-4430-A51A-4F3F96BA0BDF}')!
IconModel comment: ''!
!IconModel categoriesForClass!MVP-Models! !
!IconModel methodsFor!

icon
        ^Icon fromSystemId: offset!

initialize
        offset := 1.!

offset: anOffset
        offset := anOffset.!

printOn: target
        super printOn: target.
        offset printOn: target.! !
!IconModel categoriesFor: #icon!public! !
!IconModel categoriesFor: #initialize!private! !
!IconModel categoriesFor: #offset:!private! !
!IconModel categoriesFor: #printOn:!public! !

IconFinderShell guid: (GUID fromString: '{1A8D084B-626A-45D9-88E7-C6A5A8283967}')!
IconFinderShell comment: ''!
!IconFinderShell categoriesForClass!MVP-Presenters! !
!IconFinderShell class methodsFor!

defaultModel
        |reply|
        reply := ListModel new.
        30000 to: 32520 do: [:i | reply add: (IconModel new offset: i)].
        ^reply.!

resource_Default_view
        "Answer the literal data from which the 'Default view' resource can be reconstituted.
        DO NOT EDIT OR RECATEGORIZE THIS METHOD.

        If you wish to modify this resource evaluate:
        ViewComposer openOn: (ResourceIdentifier class: self selector: #resource_Default_view)
        "

        ^#(#'!!STL' 3 788558 10 ##(STBViewProxy)  8 ##(ListView)  98 30 0 0 98 2 8 1140920397 1025 416 590662 2 ##(ListModel)  202 208 98 0 0 1114638 ##(STBSingletonProxy)  8 ##(SearchPolicy)  8 #identity 524550 ##(ColorRef)  8 4278190080 0 7 0 0 0 416 0 8 4294903777 8 ##(BasicListAbstract)  8 ##(IconicListAbstract)  570 8 ##(IconImageManager)  8 #current 0 0 0 328198 ##(Point)  65 65 0 0 202 208 98 2 920646 5 ##(ListViewColumn)  8 'Offset' 201 8 #left 688 8 ##(SortedCollection)  0 0 416 787814 3 ##(BlockClosure)  0 459302 ##(Context)  1 1 0 0 1180966 ##(CompiledExpression)  0 9 8 ##(UndefinedObject)  8 'doIt' 98 2 8 '[:i | i]' 98 1 202 8 ##(PoolDictionary)  544 8 #[252 1 0 1 1 4 0 17 229 32 106 105] 17 257 0 1 0 0 834 8 'Image' 201 880 688 896 0 0 416 914 0 946 1 1 0 0 978 0 9 1008 8 'doIt' 98 2 8 '[:i | i]' 98 1 202 1104 544 8 #[252 1 0 1 1 4 0 17 229 32 106 105] 17 257 0 1 0 0 8 #report 544 770 65 65 131169 0 0 983302 ##(MessageSequence)  202 208 98 2 721670 ##(MessageSend)  8 #createAt:extent: 98 2 770 11 11 770 1047 1013 416 1410 8 #text: 98 1 8 'Offset' 416 983302 ##(WINDOWPLACEMENT)  8 #[44 0 0 0 0 0 0 0 0 0 0 0 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 255 5 0 0 0 5 0 0 0 16 2 0 0 255 1 0 0] 98 0 770 193 193 0 27 )! !
!IconFinderShell class categoriesFor: #defaultModel!public! !
!IconFinderShell class categoriesFor: #resource_Default_view!public!resources-views! !

MockTestCase guid: (GUID fromString: '{1EFA0B16-373B-4774-B90B-4A4D74E4DA4F}')!
MockTestCase comment: ''!
!MockTestCase categoriesForClass!Unclassified! !
!MockTestCase methodsFor!

testExpectAndReturnFails
        | unit |
        unit := MockObject new.
        unit expect: (Message selector: #callThis) return: true.

        self should: [unit verify] raise: Error.
!

testExpectAndReturnVerifies
        | unit |
        unit := MockObject new.
        unit expect: (Message selector: #callThis) return: true.

        self assert: unit callThis = true.

        unit verify.!

testExpectAndReturnWithArgsFails
        | unit |
        unit := MockObject new.
        unit expect: (Message selector: #callThis: arguments: #(42)) return: true.
       
        self should: [unit callThis: 43] raise: Error.
!

testExpectAndReturnWithArgsVerifies
        | unit |
        unit := MockObject new.
        unit expect: (Message selector: #callThis: arguments: #(42)) return: true.
       
        unit callThis: 42.

        unit verify.
! !
!MockTestCase categoriesFor: #testExpectAndReturnFails!public! !
!MockTestCase categoriesFor: #testExpectAndReturnVerifies!public! !
!MockTestCase categoriesFor: #testExpectAndReturnWithArgsFails!public! !
!MockTestCase categoriesFor: #testExpectAndReturnWithArgsVerifies!public! !

"Binary Globals"!