[ENH] Syntax extension for continuations

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

[ENH] Syntax extension for continuations

Igor Stasenko
Hello,

Out of curiosity, i tried to look how it would be hard to change
parser to support extended continuation syntax.
And it was quite simple, i had to change only single method!

A new syntax using double semicolon ';;' to indicate a continuation.

So, code like:

self foo ;; bar ;; zork

is equivalent to:

self foo bar zork

But when its going to binary, or keyword messages, it allows to write
more clean code,
because it not requires using parenthesis.

For instance:

(1/10) asFloat

with new syntax can be written as:

1/10 ;; asFloat

More complex example:

((self foo: bar) + 10 ) baz

can be written as

self foo: bar ;; + 10 ;; baz


Note, that it is same number of characters to type.. but is much more
clean, and less time expensive to code,
because when you coding, you usually type first message:

self foo: bar `

and then you realising that next message is binary and hence you need
to go back to beginning of line and put open paren there:

`( self foo: bar

then again, go to the end of message, and continue typing:

( self foo: bar ` ) + 10

` - is cursor position.

so, it is much more keystrokes & navigation than just typing two semicolons :)

P.S. don't burn me for my herecy, please :)

--
Best regards,
Igor Stasenko AKA sig.

parser-continuations.1.cs (1K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: [ENH] Syntax extension for continuations

Igor Stasenko
Here is more examples (found by searching .sources file with 3 or more '(((' ).

ContextPart>>handleSignal:

(((self tempAt: 1) handles: exception) and: [self tempAt: 3]) ifFalse: [
        ^ self nextHandlerContext handleSignal: exception].


self tempAt: 1 ;; handles: exception ;; and: [self tempAt: 3] ;; ifFalse: [
                ^ self nextHandlerContext handleSignal: exception].


Bezier3Segment.

before:

bezier2SegmentCount: pixelError
        "Compute the number of quadratic bezier segments needed to approximate
        this cubic with no more than a specified error"
        | a |
        a := (start x negated @ start y negated) + (3 * via1) - (3 * via2) +
(end).
        ^ (((a r / (20.0 * pixelError)) raisedTo: 0.333333) ceiling) max: 1.

after:

bezier2SegmentCount: pixelError
        "Compute the number of quadratic bezier segments needed to approximate
        this cubic with no more than a specified error"
        | a |
        a := start x negated @ start y negated ;; + (3 * via1) - (3 * via2) +
end.
        ^ a r / (20.0 * pixelError) raisedTo: 0.333333 ;; ceiling max: 1.


ZipArchive

before:

lastIndexOfPKSignature: aSignature in: data
        "Answer the last index in data where aSignature (4 bytes long)
occurs, or 0 if not found"
        | a b c d |
        a := aSignature first.
        b := aSignature second.
        c := aSignature third.
        d := aSignature fourth.
        (data size - 3) to: 1 by: -1 do: [ :i |
                (((data at: i) = a)
                        and: [ ((data at: i + 1) = b)
                                and: [ ((data at: i + 2) = c)
                                        and: [ ((data at: i + 3) = d) ]]])
                                                ifTrue: [ ^i ]
        ].
        ^0

after:

lastIndexOfPKSignature: aSignature in: data
        "Answer the last index in data where aSignature (4 bytes long)
occurs, or 0 if not found"
        | a b c d |
        a := aSignature first.
        b := aSignature second.
        c := aSignature third.
        d := aSignature fourth.
        data size - 3 to: 1 by: -1 do: [ :i |
                data at: i ;; = a
                        and: [ data at: i + 1 ;; = b
                                and: [ data at: i + 2 ;; = c
                                        and: [ data at: i + 3 ;; = d ]]]
                                                ifTrue: [ ^i ]
        ].
        ^0


Character

before:

asUppercase
        "If the receiver is lowercase, answer its matching uppercase Character."
        "A tentative implementation.  Eventually this should consult the
Unicode table."

        | v |
        v := self charCode.
        (((8r141 <= v and: [v <= 8r172]) or: [16rE0 <= v and: [v <= 16rF6]])
or: [16rF8 <= v and: [v <= 16rFE]])
                ifTrue: [^ Character value: value - 8r40]
                ifFalse: [^ self]

after:

asUppercase
        "If the receiver is lowercase, answer its matching uppercase Character."
        "A tentative implementation.  Eventually this should consult the
Unicode table."

        | v |
        v := self charCode.
        8r141 <= v and: [v <= 8r172] ;; or: [16rE0 <= v and: [v <= 16rF6]] ;;
or: [16rF8 <= v and: [v <= 16rFE]] ;;
                ifTrue: [^ Character value: value - 8r40]
                ifFalse: [^ self]



--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: [ENH] Syntax extension for continuations

Levente Uzonyi-2
In reply to this post by Igor Stasenko
On Mon, 1 Nov 2010, Igor Stasenko wrote:

> Hello,
>
> Out of curiosity, i tried to look how it would be hard to change
> parser to support extended continuation syntax.
> And it was quite simple, i had to change only single method!
>
> A new syntax using double semicolon ';;' to indicate a continuation.
>
> So, code like:
>
> self foo ;; bar ;; zork
>
> is equivalent to:
>
> self foo bar zork
>
> But when its going to binary, or keyword messages, it allows to write
> more clean code,
> because it not requires using parenthesis.
>
> For instance:
>
> (1/10) asFloat
>
> with new syntax can be written as:
>
> 1/10 ;; asFloat
>
> More complex example:
>
> ((self foo: bar) + 10 ) baz
>
> can be written as
>
> self foo: bar ;; + 10 ;; baz
>
>
> Note, that it is same number of characters to type.. but is much more
> clean, and less time expensive to code,
> because when you coding, you usually type first message:
>
> self foo: bar `
>
> and then you realising that next message is binary and hence you need
> to go back to beginning of line and put open paren there:
>
> `( self foo: bar
>
> then again, go to the end of message, and continue typing:
>
> ( self foo: bar ` ) + 10
>
> ` - is cursor position.
>
> so, it is much more keystrokes & navigation than just typing two semicolons :)
>
> P.S. don't burn me for my herecy, please :)

This idea comes up every few years. This post sums up well the last
attempt: http://blog.3plus4.org/2007/08/30/message-chains/ .

I don't think it's worth changing the syntax for this. IMHO 1-2 pairs of
parentheses usually improve readability. More parenthesis is rarely
needed. Also mixing ;; with ; makes the code harder to understand. Try
this: self foo ; bar ;; baz ; foo ;; bar ; baz.

Note that the term 'continuation' means a totally different thing:
http://en.wikipedia.org/wiki/Continuation .


Levente

>
> --
> Best regards,
> Igor Stasenko AKA sig.
>

Reply | Threaded
Open this post in threaded view
|

Re: [squeak-dev] Re: [ENH] Syntax extension for continuations

Igor Stasenko
On 1 November 2010 05:04, Levente Uzonyi <[hidden email]> wrote:

> On Mon, 1 Nov 2010, Igor Stasenko wrote:
>
>> Hello,
>>
>> Out of curiosity, i tried to look how it would be hard to change
>> parser to support extended continuation syntax.
>> And it was quite simple, i had to change only single method!
>>
>> A new syntax using double semicolon ';;' to indicate a continuation.
>>
>> So, code like:
>>
>> self foo ;; bar ;; zork
>>
>> is equivalent to:
>>
>> self foo bar zork
>>
>> But when its going to binary, or keyword messages, it allows to write
>> more clean code,
>> because it not requires using parenthesis.
>>
>> For instance:
>>
>> (1/10) asFloat
>>
>> with new syntax can be written as:
>>
>> 1/10 ;; asFloat
>>
>> More complex example:
>>
>> ((self foo: bar) + 10 ) baz
>>
>> can be written as
>>
>> self foo: bar ;; + 10 ;; baz
>>
>>
>> Note, that it is same number of characters to type.. but is much more
>> clean, and less time expensive to code,
>> because when you coding, you usually type first message:
>>
>> self foo: bar `
>>
>> and then you realising that next message is binary and hence you need
>> to go back to beginning of line and put open paren there:
>>
>> `( self foo: bar
>>
>> then again, go to the end of message, and continue typing:
>>
>> ( self foo: bar ` ) + 10
>>
>> ` - is cursor position.
>>
>> so, it is much more keystrokes & navigation than just typing two
>> semicolons :)
>>
>> P.S. don't burn me for my herecy, please :)
>
> This idea comes up every few years. This post sums up well the last attempt:
> http://blog.3plus4.org/2007/08/30/message-chains/ .
>
Yes. I know.

> I don't think it's worth changing the syntax for this. IMHO 1-2 pairs of
> parentheses usually improve readability. More parenthesis is rarely needed.
> Also mixing ;; with ; makes the code harder to understand. Try this: self
> foo ; bar ;; baz ; foo ;; bar ; baz.
>
this is incorrect syntax.


> Note that the term 'continuation' means a totally different thing:
> http://en.wikipedia.org/wiki/Continuation .
>

It was called so in tiny smalltalk (if i remember), when i first
learned a syntax. You name it.


>
> Levente
>
>>
>> --
>> Best regards,
>> Igor Stasenko AKA sig.
>>
>
>



--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: [ENH] Syntax extension for continuations

Levente Uzonyi-2
In reply to this post by Igor Stasenko
On Mon, 1 Nov 2010, Igor Stasenko wrote:

> Here is more examples (found by searching .sources file with 3 or more '(((' ).
>
> ContextPart>>handleSignal:
>
> (((self tempAt: 1) handles: exception) and: [self tempAt: 3]) ifFalse: [
> ^ self nextHandlerContext handleSignal: exception].
>
>
> self tempAt: 1 ;; handles: exception ;; and: [self tempAt: 3] ;; ifFalse: [
> ^ self nextHandlerContext handleSignal: exception].


What about this?

((self tempAt: 3) and: [ (self tempAt: 1) handles: exception ]) ifFalse: [
  ^ self nextHandlerContext handleSignal: exception].

>
>
> Bezier3Segment.
>
> before:
>
> bezier2SegmentCount: pixelError
> "Compute the number of quadratic bezier segments needed to approximate
> this cubic with no more than a specified error"
> | a |
> a := (start x negated @ start y negated) + (3 * via1) - (3 * via2) +
> (end).
> ^ (((a r / (20.0 * pixelError)) raisedTo: 0.333333) ceiling) max: 1.
>
> after:
>
> bezier2SegmentCount: pixelError
> "Compute the number of quadratic bezier segments needed to approximate
> this cubic with no more than a specified error"
> | a |
> a := start x negated @ start y negated ;; + (3 * via1) - (3 * via2) +
> end.
> ^ a r / (20.0 * pixelError) raisedTo: 0.333333 ;; ceiling max: 1.

There are 2 superfluous parenthesis in the original code (which you
omitted in your code). Here's the same without them:

  ^(a r / (20.0 * pixelError) raisedTo: 0.333333) ceiling max: 1.

If I want to be "tricky", I can even remove another parenthesis:

  ^(0.05 * a r / pixelError raisedTo: 0.333333) ceiling max: 1.

>
>
> ZipArchive
>
> before:
>
> lastIndexOfPKSignature: aSignature in: data
> "Answer the last index in data where aSignature (4 bytes long)
> occurs, or 0 if not found"
> | a b c d |
> a := aSignature first.
> b := aSignature second.
> c := aSignature third.
> d := aSignature fourth.
> (data size - 3) to: 1 by: -1 do: [ :i |
> (((data at: i) = a)
> and: [ ((data at: i + 1) = b)
> and: [ ((data at: i + 2) = c)
> and: [ ((data at: i + 3) = d) ]]])
> ifTrue: [ ^i ]
> ].
> ^0
>
> after:
>
> lastIndexOfPKSignature: aSignature in: data
> "Answer the last index in data where aSignature (4 bytes long)
> occurs, or 0 if not found"
> | a b c d |
> a := aSignature first.
> b := aSignature second.
> c := aSignature third.
> d := aSignature fourth.
> data size - 3 to: 1 by: -1 do: [ :i |
> data at: i ;; = a
> and: [ data at: i + 1 ;; = b
> and: [ data at: i + 2 ;; = c
> and: [ data at: i + 3 ;; = d ]]]
> ifTrue: [ ^i ]
> ].
> ^0

Same as above, superfluous parenthesis. This is what you get after
removing 5 of them and a bit of reformatting:

  data size - 3 to: 1 by: -1 do: [ :i |
  (data at: i) = a and: [
  (data at: i + 1) = b and: [
  (data at: i + 2) = c and: [
  (data at: i + 3) = d ] ] ])
  ifTrue: [ ^i ]
  ].



>
>
> Character
>
> before:
>
> asUppercase
> "If the receiver is lowercase, answer its matching uppercase Character."
> "A tentative implementation.  Eventually this should consult the
> Unicode table."
>
> | v |
> v := self charCode.
> (((8r141 <= v and: [v <= 8r172]) or: [16rE0 <= v and: [v <= 16rF6]])
> or: [16rF8 <= v and: [v <= 16rFE]])
> ifTrue: [^ Character value: value - 8r40]
> ifFalse: [^ self]
>
> after:
>
> asUppercase
> "If the receiver is lowercase, answer its matching uppercase Character."
> "A tentative implementation.  Eventually this should consult the
> Unicode table."
>
> | v |
> v := self charCode.
> 8r141 <= v and: [v <= 8r172] ;; or: [16rE0 <= v and: [v <= 16rF6]] ;;
> or: [16rF8 <= v and: [v <= 16rFE]] ;;
> ifTrue: [^ Character value: value - 8r40]
> ifFalse: [^ self]

There's #between:and: or you can use better formatting to improve
readability here:

  ((v between: 8r141 and: 8r172) or: [
  v between: 16rE0 and: 16rF6 ] or: [
  v between: 16rF8 and: 16rFE ])
  ifTrue: [ ^Character value: value - 8r40].

or

  ((8r141 <= v and: [ v <= 8r172 ]) or: [
                 (16rE0 <= v and: [ v <= 16rF6 ]) or: [
                 16rF8 <= v and: [ v <= 16rFE ] ] ])
  ifTrue: [ ^Character value: value - 8r40].


Levente

>
>
>
> --
> Best regards,
> Igor Stasenko AKA sig.
>
>

Reply | Threaded
Open this post in threaded view
|

Re: [squeak-dev] Re: [ENH] Syntax extension for continuations

Levente Uzonyi-2
In reply to this post by Igor Stasenko
On Mon, 1 Nov 2010, Igor Stasenko wrote:

> On 1 November 2010 05:04, Levente Uzonyi <[hidden email]> wrote:

snip

>> foo ; bar ;; baz ; foo ;; bar ; baz.
>>
> this is incorrect syntax.

This is correct: ((self foo; bar) baz; foo) bar; baz.
Message chaining should be equivalent with this, shouldn't it?


Levente

>
>
>> Note that the term 'continuation' means a totally different thing:
>> http://en.wikipedia.org/wiki/Continuation .
>>
>
> It was called so in tiny smalltalk (if i remember), when i first
> learned a syntax. You name it.
>
>
>>
>> Levente
>>
>>>
>>> --
>>> Best regards,
>>> Igor Stasenko AKA sig.
>>>
>>
>>
>
>
>
> --
> Best regards,
> Igor Stasenko AKA sig.
>
>

Reply | Threaded
Open this post in threaded view
|

Re: [ENH] Syntax extension for continuations

Igor Stasenko
On 1 November 2010 05:33, Levente Uzonyi <[hidden email]> wrote:

> On Mon, 1 Nov 2010, Igor Stasenko wrote:
>
>> On 1 November 2010 05:04, Levente Uzonyi <[hidden email]> wrote:
>
> snip
>
>>> foo ; bar ;; baz ; foo ;; bar ; baz.
>>>
>> this is incorrect syntax.
>
> This is correct: ((self foo; bar) baz; foo) bar; baz.
> Message chaining should be equivalent with this, shouldn't it?
>

yes, but continuation err.. chaining ';;' takes precedence before cascade ';'

which means that you can write only as:

self foo zork ;; bar ;; bum ; baz ; lz

but not

self foo zork ; bar ;; bum ; baz ;; lz

otherwise you will also need to use parens to disambiguate nested cascades.

>
> Levente
>



--
Best regards,
Igor Stasenko AKA sig.