2009/10/20  <[email protected]>:
> I don't see where are we willing to arrive at.
>
> '' asNumber gives zero in several other Smalltalks (Dolphin and VW,
> for example) and used to work as Mariano mentions in earlier versions
> of Pharo (which makes me surmise is the way Squeak worked as well).
>
> So attempting addressing Nicolas point: the context where '' can be
> expected is when reading text from some other source (mainly text from
> a file) into you Pharo application.
>
> A library API has to have a reasonable balance between an excruciating
> "conceptual right" set of calls and the "principle of minimum
> surprise" for the corner cases in general.
>
> From this discussion, are we saying that for now on in order to have
> strings converted into numbers if we want to have the behaviour ''
> returning zero we shall change from '' asNumber to '' asNumberOrZero
> and this method will call a more general method like this?
>
> Number>>asNumberOrZero
> ^self asNumberOr: 0
>
> And
>
> Number>>asNumberOr: aNumber
> ^Number readFrom: self ifFail: [^aNumber]
>
> Just my .0199999....
>
>

If this is an identified inter-dialect feature, then some applications
will rely on it, and then yes we SHOULD maintain the feature.

But we can in no way keep all the silly other cases.
However, did you try these in other dialects
' ' asNumber.
'a' asNumber.
'b2' asNumber.
etc...

I guess VW & Dolphin should fail in all these cases...
Squeak did not and would answer 0 in most cases, and that's what I
don't want to see anymore...

Another question is should we authorize non blank trailing characters
? I think no.
'2r' asNumber.
'2 + 3' asNumber.
etc..

If the feature is OK, I would say:

asNumber
  | strm num |
  self isEmpty: [^0].
  strm := self readStream.
  strm skipSeparators.
  num := Number readFrom: strm. "<- if it fails, this message will
signal an Error..."
  strm skipSeparators atEnd ifFalse: [self error: 'I do not represent
a valid number'].
  ^num


Nicolas

>
>
> Em 20/10/2009 05:26, Stéphane Ducasse <[email protected]> escreveu:
>>  I like asNumberOrZero we could  have asNumberOr: aNumber so that we
>> are not bound  to Zero and I would include it.   Now what the others
>> think?  Stef
>>  On Oct 20, 2009, at 4:31 AM, Nicolas Cellier wrote:
>>
>> > 2009/10/20 Mariano Martinez Peck :
>> >>
>> >> On Mon, Oct 19, 2009 at 10:33 PM, Nicolas Cellier wrote:
>> >>> Yes, I understand the paradigm, nil is nothing is zero, empty is
>> >>> nothing is zero...   But frankly, do you think  '' forms a valid
>> >>> Number ? In  every context ?  So yes, this  is expected, and can
>> >>> break compatibility, but sometimes this is necessary.
>> >>> If you want to keep this  behaviour, you have to use an explicit
>> >>> rule like: asNumberOrZero ^Number readFrom: self ifFail: [^0]
>> >>>
>> >> Thanks Nicolas. Now, the question  is, do you think we can create
>> >> this method in  String as part of Pharo core? or  I should add it
>> >> to my application?
>> >> cheers
>> >> mariano
>> >>
>> > Depends if  the pattern  was used by  many packages or  not...  It
>> > would be stupid to create 10x  the same extension to work around a
>> > pharo  change.   Would  it   be  a  temporary  helper  subject  to
>> > deprecation, or a definitive feature  ?  I can't tell, and i don't
>> > decide, i only suggest.
>> > Nicolas
>> >
>> >>> Hope this helps...
>> >>> Nicolas
>> >>> 2009/10/20 Mariano Martinez Peck :
>> >>>> Hi folks: In older images, like  10418, '' asNumber gave me a 0
>> >>>> (zero).  But now, I get a 'Reading a number failed'.
>> >>>> Is this expected?
>> >>>> Perhaps it is due to the fix to this bug:
>> >>>>
>> >>>> http://code.google.com/p/pharo/issues/detail?can=1&q=1258&colspec=ID%20Type%20Status%20Summary%20Milestone&id=1258
>> >>>> any toughs?
>> >>>> best
>> >>>> Mariano
>
> _______________________________________________
> 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