On 30.05.2012 14:05, Mariano Martinez Peck wrote:
Hi guys. I found a problem while working with FuelPreview where we store objects of the graph in a Set. While doing a collect, there was an error because an implementation of #= was assuming that the argument was of a certain shape. Of course, that should answer false instead. So I wrote this test to see all existing wrong implementations:

testAllClassesImplementSafeEqualsMethod
"This tests that all classes in the system that implements #= do it in a way that they don't throw error when passing as an argument something different from expected. The correct behavior is that #= answers false."
    | wrongClasses |
    wrongClasses := IdentityDictionary  new.
     ((SystemNavigation default allImplementorsOf: #=)
            collect: [:each | each methodClass])
            do: [:each |
                | instance |
"Some classes like CompiledMethod override basicNew to throw an error.
                In any case, the comparison will be false, so no problem"
                [instance := each basicNew] on: Error do: [].
                [instance = Object new]
                    on: Error
                    do: [: err | wrongClasses at: each put: err ]].
    self assert: wrongClasses isEmpty


The result is: {Magnitude. WideCharacterSet. KMKeymap. MCMockDefinition. ScaledDecimal. MCSnapshot}

So, my I think we should change #= in those classes by adding:

    self == aKeymap
        ifTrue: [ ^ true ].
    self class = aKeymap class
        ifFalse: [ ^ false ].

at the beginning of the #=

what do you think?  if agree, I open an issue.


--
Mariano
http://marianopeck.wordpress.com

I'd test against self species rather than self class, since it gives greater flexibility for user-defined instances to potentially = classes in the system.

In other word, #class has a very strict meaning which would hinder extensibility, #species less so.

Otherwise I agree.

Cheers,
Henry

Reply via email to