thanks for the explanation.
I will add this in the method comment and probably class comment
http://code.google.com/p/pharo/issues/detail?id=1685

Stef

On Dec 25, 2009, at 1:11 AM, Eliot Miranda wrote:

> 
> 
> On Thu, Dec 24, 2009 at 2:52 PM, Levente Uzonyi <[email protected]> wrote:
> On Thu, 24 Dec 2009, Eliot Miranda wrote:
> >
> > This 'hack' is as old as Smalltalk-80 V2 and is AFAICT in all Smalltalk-80
> > derived Smalltalks:
> >
> > !Object methodsFor: 'accessing'!
> > at: index
> >    "Answer the value of an indexable field in the receiver. Fail if the
> >    argument index is not an Integer or is out of bounds. Essential. See
> >    documentation in Object metaclass."
> >
> >    <primitive: 60>
> >    index isInteger
> >        ifTrue: [self errorSubscriptBounds: index].
> >    (index isKindOf: Number)
> >        ifTrue: [^self at: index truncated]
> >        ifFalse: [self errorNonIntegerIndex]!
> >
> > It is also free in the sense that the failure code is only invoked when the
> > primitive fails and so adds nothing to the cost of successful accesses,
> > which are the high dynamic frequency operation.  It will also show up under
> > profiling if one is concerned about efficiency, and so isn't a hidden cost.
> >
> > It is also in keeping with Smalltalk's mixed mode/arbitrary precision
> > implicit coercion number system that one *can* use fractions or floats as
> > indices.
> >
> > Stripping out coercions like this will make the system more brittle.  So
> > please do *not* remove this "hack".  I think it's a feature and a useful
> > one.
> 
> Can you give me an example that demonstrates the usefulness of this
> feature?
> 
> | a r |
> a := Array new: 10 withAll: 0.
> r := Random new.
> 100 timesRepeat: [| v | v := r next * 10 + 1. a at: v put: (a at: v) + 1].
> a
> 
> i.e. I didn't have to provide an explicit rounding step.  That's useful.  But 
> in general anywhere where an index is derived by some calculation not having 
> to provide the rounding step could be useful/helpful/more concise.  e.g. (n 
> roundTo: 0.1) * 10 vs ((n roundTo: 0.1) * 10) asInteger.
> 
> Some thought went into the original choice.  It is not a hack but there by 
> intent.  The integers are simply a subset of the reals and forcing the 
> programmer to use them is favouring the machine above the programmer.
> 
> But I think you should justify getting rid of it rather than my having to 
> justify keeping it.  Getting rid of it risks breaking code.  If it is there 
> but does not harm then why get rid of it?
> 
> best
> Eliot
> 
> 
> Levente
> 
> _______________________________________________
> Pharo-project mailing list
> [email protected]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> 
> _______________________________________________
> Pharo-project mailing list
> [email protected]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to