binary selectors ambiguity and space

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
45 messages Options
123
Reply | Threaded
Open this post in threaded view
|

binary selectors ambiguity and space

Nicolas Cellier-3
Sorry cannot find the thread which started this discussion,
but it seems i cannot have some binary selector with minus sign last.

For example, i can compile
    Compiler evaluate: 'nil -+ nil'
Or
    Compiler evaluate: 'nil -/+ nil'

But i cannot compile
    Compiler evaluate: 'nil +- nil'
nor
    Compiler evaluate: 'nil +/- nil'

I understand that eventually some expressions might be ambiguous like
 1+-2 that can be interpreted as (1) + (-2) or (1) +- (2)
But such ambiguity could raise an error or warning,
and in most case, spaces will help disambiguating:
 1+-   2 would be (1) +- (2)
 1+   -2 would be (1) + (-2)

Funny, in current 3.9 spaces are ignored:
i have '1 +-   2' interpreted as (1) + (-2)

I cannot even write 1 +-+ 2, though no ambiguity lie there...

I guess all this is very squeak specific

Nicolas


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Dan Ingalls
Well, the *idea* was that you should not need spaces, and St-76, borrowing from APL, had a different character for the semantically different high-minus sign for negative literals, so this was not a problem.  High-minus bit the dust with the ascii changes of St80 thus necessitating a space before negative literals that follow binary messages.

>Sorry cannot find the thread which started this discussion,
>but it seems i cannot have some binary selector with minus sign last.
>
>For example, i can compile
>    Compiler evaluate: 'nil -+ nil'
>Or
>    Compiler evaluate: 'nil -/+ nil'
>
>But i cannot compile
>    Compiler evaluate: 'nil +- nil'
>nor
>    Compiler evaluate: 'nil +/- nil'
>
>I understand that eventually some expressions might be ambiguous like
> 1+-2 that can be interpreted as (1) + (-2) or (1) +- (2)
>But such ambiguity could raise an error or warning,
>and in most case, spaces will help disambiguating:
> 1+-   2 would be (1) +- (2)
> 1+   -2 would be (1) + (-2)

Agreed.

>Funny, in current 3.9 spaces are ignored:
>i have '1 +-   2' interpreted as (1) + (-2)
>
>I cannot even write 1 +-+ 2, though no ambiguity lie there...

Agreed.

>I guess all this is very squeak specific

I don't know, but it ought to be fixed.

        - Dan

Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
Let us look inside Parser:

$- except as first binary character is forbidden in Scanner>>xBinary
Thus '1 +- 2' will scan successive tokens (1) (#+) (#-) (2).
This will be parsed with Parser>>messagePart:repeat:
Then Parser>>primaryException will gather (#-) (2) into (LiteralNode value:
-2)

Without a space  '1+-2' will scan same 4 tokens (1) (#+) (#-) (2), and result
will be the same.

However, inside literal quotes, space are significant in current
implementation:
#(1 - 2) will answer (Array with: 1 with: #- with: 2),
#(1-2) will be scanned and parsed into (Array with: 1 with: -2).

Concatenating - and 2 as a single token occur in Scanner>>scanLitVec if and
only if char following - is a digit...

I know how to change this:
- move token concatenation from #scanLitVec to #scanToken
- remove #- handling in #primaryExpression
- remove limitation in #xBinary

But then, this will change semantics of #(1--2) that will be parsed #(1 #'--'
2) instead of #(1 #- -2).
We can also make a special handling in xBinary and not groke last - when
immediately followed with a digit, and raise a Warning exception with
defaultAction doNothing, but wich could be caught in Parser to warn user of
possible ambiguity if interactive...

Thus we would keep most compatibility with current implementation.

What do squeakers think of this change ?

Nicolas


Le Samedi 13 Mai 2006 02:36, Dan Ingalls a écrit :

> Well, the *idea* was that you should not need spaces, and St-76, borrowing
> from APL, had a different character for the semantically different
> high-minus sign for negative literals, so this was not a problem.
> High-minus bit the dust with the ascii changes of St80 thus necessitating a
> space before negative literals that follow binary messages.
>
> >Sorry cannot find the thread which started this discussion,
> >but it seems i cannot have some binary selector with minus sign last.
> >
> >For example, i can compile
> >    Compiler evaluate: 'nil -+ nil'
> >Or
> >    Compiler evaluate: 'nil -/+ nil'
> >
> >But i cannot compile
> >    Compiler evaluate: 'nil +- nil'
> >nor
> >    Compiler evaluate: 'nil +/- nil'
> >
> >I understand that eventually some expressions might be ambiguous like
> > 1+-2 that can be interpreted as (1) + (-2) or (1) +- (2)
> >But such ambiguity could raise an error or warning,
> >and in most case, spaces will help disambiguating:
> > 1+-   2 would be (1) +- (2)
> > 1+   -2 would be (1) + (-2)
>
> Agreed.
>
> >Funny, in current 3.9 spaces are ignored:
> >i have '1 +-   2' interpreted as (1) + (-2)
> >
> >I cannot even write 1 +-+ 2, though no ambiguity lie there...
>
> Agreed.
>
> >I guess all this is very squeak specific
>
> I don't know, but it ought to be fixed.
>
> - Dan


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Wolfgang Helbig-2
In reply to this post by Nicolas Cellier-3
Hi Nicolas,

you found out:
>$- except as first binary character is forbidden in Scanner>>xBinary
>Thus '1 +- 2' will scan successive tokens (1) (#+) (#-) (2).

This complies with the syntax diagrams in the Purple Book (this page is left
blank in my edition of the Blue Book):

The minus character must not be the second character of a binary selector. Why?
What's so bad about a binary selector like #/- or #\- ? (These selectors would
mean Integer division rounded towards minus infinity, as opposed to the accepted
binary selectors #/+ and #\+, which is, suprise, Integer division rounded
towards plus infinity.)

Greetings,
Wolfgang

--
Weniger, aber besser.


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
Hi Wolgang

Le Samedi 13 Mai 2006 18:35, Wolfgang Helbig a écrit :

> Hi Nicolas,
>
> you found out:
> >$- except as first binary character is forbidden in Scanner>>xBinary
> >Thus '1 +- 2' will scan successive tokens (1) (#+) (#-) (2).
>
> This complies with the syntax diagrams in the Purple Book (this page is
> left blank in my edition of the Blue Book):
>
> The minus character must not be the second character of a binary selector.
> Why?

The reason is simply because of negative number literal constants like -2,
So as to avoid ambiguity of expressions like x--2.
Dan said space should not be significant...
In fact, if you look Squeak literal arrays, or VW implementation, you can see
that in fact it is: #(1-2) and #(1-  2)

> What's so bad about a binary selector like #/- or #\- ? (These
> selectors would mean Integer division rounded towards minus infinity, as
> opposed to the accepted binary selectors #/+ and #\+, which is, suprise,
> Integer division rounded towards plus infinity.)
>
> Greetings,
> Wolfgang
>
> --
> Weniger, aber besser.

I agree, if we remove the limitation (simple) and disambiguate with a
precedence rule as i proposed (minus sign immediately preceding a digit will
always form a negated number literal), then we can have plenty of others
selectors, like <-  +/-  etc... i do not know for what purpose yet but sure
some will find.
Of course, we deviate from the blue bible, but from Alejandro point of view,
this is just normal evolution of a living system...
What nobody knows yet is if the Darwinian selection will select this change as
a viable one.

Nicolas




Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
Le Samedi 13 Mai 2006 19:43, nicolas cellier a écrit :
> Dan said space should not be significant...
> In fact, if you look Squeak literal arrays, or VW implementation, you can
> see that in fact it is: #(1-2) and #(1-  2)

To be correct, space put around binary selectors should not be significant.
That is (1   -   -2)  should lead same result as (1--2).

This is not exactly the same as space placed between minus sign and following
digit like in my example. Space are significant as a separator of course, and
(-  2) should maybe not be interpreted as a literal constant (nor a valid
expression). In VW, this syntax is rejected, you can check the bible again.

Nicolas


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
In reply to this post by Nicolas Cellier-3
Finally only Scanner>>xBinary need a one line change to allow $- in binary
selector and preserve the way negated literals are formed without
ambiguity... Really simple.

You can find it at http://bugs.impara.de/view.php?id=3616

Nicolas


Le Samedi 13 Mai 2006 10:05, nicolas cellier a écrit :

> Let us look inside Parser:
>
> $- except as first binary character is forbidden in Scanner>>xBinary
> Thus '1 +- 2' will scan successive tokens (1) (#+) (#-) (2).
> This will be parsed with Parser>>messagePart:repeat:
> Then Parser>>primaryException will gather (#-) (2) into (LiteralNode value:
> -2)
>
> Without a space  '1+-2' will scan same 4 tokens (1) (#+) (#-) (2), and
> result will be the same.
>
> However, inside literal quotes, space are significant in current
> implementation:
> #(1 - 2) will answer (Array with: 1 with: #- with: 2),
> #(1-2) will be scanned and parsed into (Array with: 1 with: -2).
>
> Concatenating - and 2 as a single token occur in Scanner>>scanLitVec if and
> only if char following - is a digit...
>
> I know how to change this:
> - move token concatenation from #scanLitVec to #scanToken
> - remove #- handling in #primaryExpression
> - remove limitation in #xBinary
>
> But then, this will change semantics of #(1--2) that will be parsed #(1
> #'--' 2) instead of #(1 #- -2).
> We can also make a special handling in xBinary and not groke last - when
> immediately followed with a digit, and raise a Warning exception with
> defaultAction doNothing, but wich could be caught in Parser to warn user of
> possible ambiguity if interactive...
>
> Thus we would keep most compatibility with current implementation.
>
> What do squeakers think of this change ?
>
> Nicolas



Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Wolfgang Helbig-2
In reply to this post by Nicolas Cellier-3
Hi Dan,
you explained:
>Well, the *idea* was that you should not need spaces, and St-76, borrowing from
>APL, had a different character for the semantically different high-minus sign

What's so bad about needing spaces? After all, the space key is one of the
easiest to hit :-). And spaces are already required as separators between
keywords and argument names, aren't they?. It seems quite natural to require
spaces as separators between a binary selector and a "special character" like
minus.

Then you could get rid of the special treatment of the minus character. That is,
the minus character would be allowed as a second character of a binary selector.

This change would simplify the grammar and slightly enlarge the expressivenes of
the language -- at the cost of needing a separator between the one character
binary selector #- followed by a minus as part of a number literal.

Here is the change of the grammar expressed in EBNF:

special_character ::=
        + | - | / | \ | * | ~ | < | > | = | @ | % | | | & | ? | ! | ,

binary_selector ::= special_character [special_character]

See also at
        http://people.squeakfoundation.org/article/58.html
for the EBNF meta characters and some other modifications I've proposed for the
grammar.

Greetings,
Wolfgang
--
Weniger, aber besser.


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Wolfgang Helbig-2
In reply to this post by Nicolas Cellier-3
I wrote some minutes ago:
easiest to hit :-).And spaces are already required as separators between
keywords and argument names, aren't they?.

Well they aren't! I should have written:
        "between argument names and keywords"
Greetings,
Wolfgang

--
Weniger, aber besser.


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Ralph Johnson
Spaces SHOULD be important.  I think indentation should be important,
too.  People find them easy to understand.  It is computers that get
confused by them.  Make things easier for people, not computers.

(I'm not suggesting that Smalltalk pay attention to indentation, or
advocating any major change to Smalltalk.  But I do think that all
arguments of the form "spaces should not matter" are completely
bogus.)

-Ralph Johnson

Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
Le Samedi 13 Mai 2006 23:34, Ralph Johnson a écrit :
> Spaces SHOULD be important.  I think indentation should be important,
> too. People find them easy to understand.  It is computers that get
> confused by them.  Make things easier for people, not computers.
>

Hi Ralph,

You are right, but that's exactly our point: make things easier for people.

Our problem is not the case when we have separators or indentations.
Our problem is try to avoid ambiguity when there are no separator.

One way would be to force user to introduce these separators, as proposed by
Wolfgang, but i dislike it because user could not write anymore x-1. Even if
space bar is large, we are so lazy... And it's annoying for backward
compatibility.

This is why I proposed another solution, add a precedence rule that says x+-1
is always interpreted as (x) + (-1), and not (x) +- (1).
But that solution is not perfect since (y:=1. x+-y) would not be interpreted
the same as (x+-1), something breaking formal beauty, and maybe some users
common sense...
This is why i propose to warn the user with a dialog box in case such
construct is used in interactive environment.

This is also why Wolfgang suggestion to force the separator, if not my
favourite, is not something crazy. That help keeping language clean and
uniform, something also related to making people life easier...


> (I'm not suggesting that Smalltalk pay attention to indentation, or
> advocating any major change to Smalltalk.  But I do think that all
> arguments of the form "spaces should not matter" are completely
> bogus.)
>
> -Ralph Johnson

You must take into account that we must satisfy both people that like to input
separators and people that don't...

Nicolas


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Wolfgang Helbig-2
In reply to this post by Nicolas Cellier-3
>One way would be to force user to introduce these separators, as proposed by
>Wolfgang, but i dislike it because user could not write anymore x-1.
This is not what I intended. The notation as proposed by me requires a separator
only when needed to resolve ambiguities. The separator separates  a binary
selector from an adjacent "special_character". The separator could be a space.
But also any other character that must not occur in a binary selector. Like a
letter or a digit, or, to be more explicit, any character that is not a "special
character". Just like a nonalphanumeric character is required to seperate
adjacent identifiers. With binary selectors, a space is required only when
        the binary selector consists of one character
                AND
        the next character would be a "special character"
       
So "x+-3" would be parsed as "x" "+-" "3". And only if you want it to be
parsed as "x" "+" "-3", you need to hit the large key to write "x+ -3".

What I mean seems best expressed by the wordings from the C Reference Manual:
        http://www.ba-stuttgart.de/~helbig/os/v6/doc/c.ps
"In general blanks, tabs, newlines, and comments as described below are ignored
except as they serve to separate tokens. At least one of these characters is
required to separate otherwise adjacent identifiers, constants, and certain
operator-pairs" (Documents for Use with the Unix Time Sharing System, Sixth
Edition, C Reference Manual, page 1, as distributed with Unix Version 6)

You find a "separator" already in the Algol 60 report.
        http://www.masswerk.at/algol60/report.htm
where it is neatly defined as a nonterminal. So, geographically, "separator"
made it from Norway, via Switzerland (Pascal, Modula, Oberon) to the US East
Cost (New Jersey), but then disappeared on its way to the US West Cost. The Blue
Book doesn't mention it, instead it seems to be used silently by Smalltalk to
separate adjacent identifiers in "message patterns". Kind of sloppy.

Greetings
Wolfgang

--
Weniger, aber besser.


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

stéphane ducasse-2
In reply to this post by Nicolas Cellier-3
Nicolas

do you have a bunch of tests describing the problems and the changes?
This is really important that we document such a behavior.

Stef
On 13 mai 06, at 22:42, nicolas cellier wrote:

> Finally only Scanner>>xBinary need a one line change to allow $- in  
> binary
> selector and preserve the way negated literals are formed without
> ambiguity... Really simple.
>
> You can find it at http://bugs.impara.de/view.php?id=3616
>
> Nicolas
>
>
> Le Samedi 13 Mai 2006 10:05, nicolas cellier a écrit :
>> Let us look inside Parser:
>>
>> $- except as first binary character is forbidden in Scanner>>xBinary
>> Thus '1 +- 2' will scan successive tokens (1) (#+) (#-) (2).
>> This will be parsed with Parser>>messagePart:repeat:
>> Then Parser>>primaryException will gather (#-) (2) into  
>> (LiteralNode value:
>> -2)
>>
>> Without a space  '1+-2' will scan same 4 tokens (1) (#+) (#-) (2),  
>> and
>> result will be the same.
>>
>> However, inside literal quotes, space are significant in current
>> implementation:
>> #(1 - 2) will answer (Array with: 1 with: #- with: 2),
>> #(1-2) will be scanned and parsed into (Array with: 1 with: -2).
>>
>> Concatenating - and 2 as a single token occur in  
>> Scanner>>scanLitVec if and
>> only if char following - is a digit...
>>
>> I know how to change this:
>> - move token concatenation from #scanLitVec to #scanToken
>> - remove #- handling in #primaryExpression
>> - remove limitation in #xBinary
>>
>> But then, this will change semantics of #(1--2) that will be  
>> parsed #(1
>> #'--' 2) instead of #(1 #- -2).
>> We can also make a special handling in xBinary and not groke last  
>> - when
>> immediately followed with a digit, and raise a Warning exception with
>> defaultAction doNothing, but wich could be caught in Parser to  
>> warn user of
>> possible ambiguity if interactive...
>>
>> Thus we would keep most compatibility with current implementation.
>>
>> What do squeakers think of this change ?
>>
>> Nicolas
>
>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
In reply to this post by Wolfgang Helbig-2
Le Dimanche 14 Mai 2006 07:58, Wolfgang Helbig a écrit :

> >One way would be to force user to introduce these separators, as proposed
> > by Wolfgang, but i dislike it because user could not write anymore x-1.
>
> This is not what I intended. The notation as proposed by me requires a
> separator only when needed to resolve ambiguities. The separator separates
> a binary selector from an adjacent "special_character". The separator could
> be a space. But also any other character that must not occur in a binary
> selector. Like a letter or a digit, or, to be more explicit, any character
> that is not a "special character". Just like a nonalphanumeric character is
> required to seperate adjacent identifiers. With binary selectors, a space
> is required only when the binary selector consists of one character
>   AND
>  the next character would be a "special character"
>
> So "x+-3" would be parsed as "x" "+-" "3". And only if you want it to be
> parsed as "x" "+" "-3", you need to hit the large key to write "x+ -3".
>
> Greetings
> Wolfgang
>
> --
> Weniger, aber besser.

Sorry, my interpretation was too radical.

I think your proposition is cleaner than mine, because x+-y will be
interpreted the same way as x+-2, but it does introduce a potential
compatibility problem, not with +-, my example was badly chosen, but maybe
with x*-2 or x/-2...

In such case, i have a natural tendancy to favour compatibility solution, but
maybe we should prefer the clean solution to be selected, with some tools to
help making the transition.

It is simple to detect the case in Scanner>>xBinary and have an Exception
raised in that case. The exception defaultAction would be to proceed simply.
But this Exception can also be caught and pop up a warning. I will try today
to parse a 3.9 image, a kind of statistical test just to check if this
ambiguity is hypothetic or is really hurting squeakers.

Nicolas


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Alexandre Bergel-2
In reply to this post by Nicolas Cellier-3
> What do squeakers think of this change ?

go for it, but write tests :-)

Cheers,
Alexandre


>
> Nicolas
>
>
> Le Samedi 13 Mai 2006 02:36, Dan Ingalls a écrit :
>> Well, the *idea* was that you should not need spaces, and St-76,  
>> borrowing
>> from APL, had a different character for the semantically different
>> high-minus sign for negative literals, so this was not a problem.
>> High-minus bit the dust with the ascii changes of St80 thus  
>> necessitating a
>> space before negative literals that follow binary messages.
>>
>>> Sorry cannot find the thread which started this discussion,
>>> but it seems i cannot have some binary selector with minus sign  
>>> last.
>>>
>>> For example, i can compile
>>>    Compiler evaluate: 'nil -+ nil'
>>> Or
>>>    Compiler evaluate: 'nil -/+ nil'
>>>
>>> But i cannot compile
>>>    Compiler evaluate: 'nil +- nil'
>>> nor
>>>    Compiler evaluate: 'nil +/- nil'
>>>
>>> I understand that eventually some expressions might be ambiguous  
>>> like
>>> 1+-2 that can be interpreted as (1) + (-2) or (1) +- (2)
>>> But such ambiguity could raise an error or warning,
>>> and in most case, spaces will help disambiguating:
>>> 1+-   2 would be (1) +- (2)
>>> 1+   -2 would be (1) + (-2)
>>
>> Agreed.
>>
>>> Funny, in current 3.9 spaces are ignored:
>>> i have '1 +-   2' interpreted as (1) + (-2)
>>>
>>> I cannot even write 1 +-+ 2, though no ambiguity lie there...
>>
>> Agreed.
>>
>>> I guess all this is very squeak specific
>>
>> I don't know, but it ought to be fixed.
>>
>> - Dan
>
>

--
_,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:
Alexandre Bergel  http://www.cs.tcd.ie/Alexandre.Bergel
^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;.




Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
In reply to this post by Nicolas Cellier-3
Le Dimanche 14 Mai 2006 10:22, nicolas cellier a écrit :
> It is simple to detect the case in Scanner>>xBinary and have an Exception
> raised in that case. The exception defaultAction would be to proceed
> simply. But this Exception can also be caught and pop up a warning. I will
> try today to parse a 3.9 image, a kind of statistical test just to check if
> this ambiguity is hypothetic or is really hurting squeakers.
>
> Nicolas

OK, i just checked, the compatibility problems are not hypothetical.

Notification subclass: #AmbiguousBinarySelectorNotification
 instanceVariableNames: ''
 classVariableNames: ''
 poolDictionaries: ''
 category: 'Exceptions-Kernel'.

Scanner>>xBinary
    tokenType := #binary.
    token := self step asSymbol.
    [| type |
    type := typeTable at: hereChar asciiValue ifAbsent: [#xLetter].
    type == #xBinary and: [hereChar ~= $- or: [aheadChar isDigit
            ifTrue: [AmbiguousBinarySelectorNotification signal. false]
            ifFalse: [true]]]] whileTrue: [
        token := (token, (String with: self step)) asSymbol].

| report |
report := (String new: 128) writeStream.
Smalltalk keysAndValuesDo: [:name :cls |
    (cls isKindOf: Behavior)
        ifTrue: [(Array with: cls with: cls class) do: [:class |
            class selectorsDo: [:selector |
                [class compilerClass new
                        parse: (class sourceCodeAt: selector)
                        in: class notifying: nil]
                    on: AmbiguousBinarySelectorNotification
                    do: [:exc |
                        report
                            print: class; nextPutAll: #'>>';
                            print: selector; cr]]]]].
report contents inspect

That gave me this list in 3.9a7029,
most problems coming from (1@-1) constructs:

PaintBoxMorph>>#init4
PaintBoxMorph>>#fixUpColorPicker
StandardSystemView>>#closeBoxFrame
StandardSystemView>>#growBoxFrame
PostscriptDummyWarp>>#subCanvas:
PNGReadWriterTest>>#drawTransparentStuffOn:
PNGReadWriterTest>>#drawStuffOn:
ViewerLine>>#addGetterFeedback
Point>>#fourNeighbors
Point>>#eightNeighbors
ScriptEditorMorph>>#createThreadShowing
ScriptEditorMorph>>#extent:
MethodFinder>>#testRandom
MethodFinder>>#testFromTuple:
Form>>#findShapeAroundSeedBlock:
Form>>#pageImage:at:corner:
Form class>>#xorHack:
Form class>>#toothpaste:
Morph>>#changeColorTarget:selector:originalColor:hand:
TTSampleStringMorph>>#computeTransform
FractionTest>>#testFractionPrinting
LipsMorph>>#openness:
PianoKeyboardMorph>>#buildKeyboard
FlashPlayerWindow>>#adjustBookControls
FloatMathPluginTests>>#md5HashStream:
TTSampleFontMorph>>#drawCharactersOn:
GraphicSymbolInstance class>>#example
AlignmentMorph>>#addUpDownArrowsFor:
PreDebugWindow>>#adjustBookControls
SyntaxMorph>>#selectorMenuAsk:
SyntaxMorph>>#drawOn:
SyntaxMorph class>>#standardInset
PointTest>>#testBearingToPoint
PointTest>>#testTheta
Cursor class>>#initBottomRight
Cursor class>>#initResizeLeft
Cursor class>>#initNormalWithMask
Cursor class>>#initResizeTopLeft
Cursor class>>#initCorner
Cursor class>>#initCrossHair
Cursor class>>#initSquare
Cursor class>>#initResizeTop
Cursor class>>#initResizeTopRight
Cursor class>>#initBottomLeft
PolygonMorph>>#nudgeForLabel:
FlapTab>>#fitContents
StandardSystemController>>#cursorOnBorder


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Ralph Johnson
The solution for parsing 1@-1 is easy, define @- to be a binary
selector just like @, except that it makes the y coordinate be
negative.

For everything else, write a converter to add the extra space.

Given Smalltalk's strict left to right evaluation order for messages,
I do not think that people would be surprised to learn that 1*-1 meant
that the *- message would be sent to 1 with 1 as an argument.  In
fact, as a twenty-year Smalltalk veteran, I still think that the way
Smalltalk treats - is wierd.

-Ralph Johnson

Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Wolfgang Helbig-2
In reply to this post by Nicolas Cellier-3
Hi Nicolas,

we were discussing:

>> So "x+-3" would be parsed as "x" "+-" "3". And only if you want it to be
>> parsed as "x" "+" "-3", you need to hit the large key to write "x+ -3".

>In such case, i have a natural tendancy to favour compatibility solution, but
>maybe we should prefer the clean solution to be selected, with some tools to
>help making the transition.
>
>It is simple to detect the case in Scanner>>xBinary and have an Exception
>raised in that case. The exception defaultAction would be to proceed simply.
>But this Exception can also be caught and pop up a warning. I will try today
>to parse a 3.9 image, a kind of statistical test just to check if this
>ambiguity is hypothetic or is really hurting squeakers.

The  Scanner>>xBinary method should not at all accept expressions like "x+-3".
Instead it should kindly ask the programmer to resolve the ambiguity by
inserting white space. Without taking a default action. Expressions are
ambiguous, if a minus character can be parsed both as the second character of a
binary selector and as the first character of a number literal.

If the folks start grumbling at this pedantry tell them Monk was here :-)

Greetings
Wolfgang
--
Weniger, aber besser.


Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Stephan Rudlof
On 15.05.2006 07:41, Wolfgang Helbig wrote:
>...

> The  Scanner>>xBinary method should not at all accept expressions like "x+-3".
> Instead it should kindly ask the programmer to resolve the ambiguity by
> inserting white space. Without taking a default action. Expressions are
> ambiguous, if a minus character can be parsed both as the second character of a
> binary selector and as the first character of a number literal.

++.

Regards,
Stephan

>...
--
Stephan Rudlof ([hidden email])
   "Genius doesn't work on an assembly line basis.
    You can't simply say, 'Today I will be brilliant.'"
    -- Kirk, "The Ultimate Computer", stardate 4731.3

Reply | Threaded
Open this post in threaded view
|

Re: binary selectors ambiguity and space

Nicolas Cellier-3
In reply to this post by Wolfgang Helbig-2
Le Lundi 15 Mai 2006 07:41, Wolfgang Helbig a écrit :

> The  Scanner>>xBinary method should not at all accept expressions like
> "x+-3". Instead it should kindly ask the programmer to resolve the
> ambiguity by inserting white space. Without taking a default action.
> Expressions are ambiguous, if a minus character can be parsed both as the
> second character of a binary selector and as the first character of a
> number literal.
>
> If the folks start grumbling at this pedantry tell them Monk was here :-)
>
> Greetings
> Wolfgang
> --
> Weniger, aber besser.

I totally agree,
user shall be kindly invited to, for code he has responsibility on.
That is, when he accepts a method in a browser debugger or any other
interactive text pane.

But this turn out very annoying when you get warned 20 times or more that you
should resolve ambiguity over wich you do not have control yet, for example
when you try to load a package from SqueakMap or Monticello.

This is why i propose the notification to raise a popup dialog only if
Parser>>interactive answer true.

This is exactly the same when temporary variables names clash with inst var
names: you cannot accept the method interactively, but you can when you load
it from any repository.

See senders of #interactive.

Nicolas


123