On Wed, Dec 23, 2009 at 1:08 AM, Nicolas Cellier <
[email protected]> wrote:

> 2009/12/23 Stéphane Ducasse <[email protected]>:
> >
> >
> >
> > Hi
> >
> > (SortedCollection new addAll: #(9 2 3 ); yourself)
> > hasEqualElements: (OrderedCollection withAll: #(9 2 3)) -> false
> >
> > hasEqualElements: otherCollection
> > "Answer whether the receiver's size is the same as otherCollection's
> > size, and each of the receiver's elements equal the corresponding
> > element of otherCollection.
> > This should probably replace the current definition of #= ."
> >
> > | size |
> > (otherCollection isKindOf: SequenceableCollection) ifFalse: [^ false].
> > (size := self size) = otherCollection size ifFalse: [^ false].
> > 1 to: size do:
> > [:index |
> > (self at: index) = (otherCollection at: index) ifFalse: [^ false]].
> > ^ true
> >
> > For me the name of this method is misleading and I would really like to
> > renaming it
> > hasStructurallyEqualElements: and have new one doing hasEqualElements:
> >
> > What do you think?
> > I would like a beautiful world....
> >
> > Stef (freezing with a flu in my bed.... cool christmax).
> >
> >
>
> Didn't VW had a #isSameSquenceAs:
>
> Nicolas
>
>
<methods>
<class-id>Core.SequenceableCollection</class-id>
<category>comparing</category>

<body package="Collections-Abstract"
selector="isSameSequenceAs:">isSameSequenceAs: otherCollection
        "Answer whether the receiver's size is the same as otherCollection's
size, and each
         of the receiver's elements equal the corresponding element of
otherCollection."

        | size |
        (size := self size) = otherCollection size ifFalse: [^false].
        1 to: size do: [:index |
                (self at: index) = (otherCollection at: index) ifFalse:
[^false]].
        ^true</body>
</methods>


i.e. trust the caller is providing a sequence and if otherCollection doesn't
implement at: there will be a run-time error, hence any otherCollection
isKindOf: SequenceableCollection is just wasted cycles.
_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to