about code formatting in pharo

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

about code formatting in pharo

stephane ducasse
Hi guys

I would like to build a set of canonical code formatting convention for Pharo.
I need your help. Now take time before replying :)
I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
Once we agree I would like to define a wiki page.


**Space after : rule
=============
for example I would like to always have a space after a :

classes := Smalltalk allClasses select:[:aClass|
               (aClass class includesSelector: #cleanUp)
                       or:[aClass class includesSelector: #cleanUp:]
       ].

->


classes := Smalltalk allClasses select: [:aClass|
               (aClass class includesSelector: #cleanUp)
                       or: [aClass class includesSelector: #cleanUp:]
       ].


**Block arg rule
=============
Do we want a space before and after block arg

Smalltalk allClasses select: [:aClass :method|

-> Smalltalk allClasses select: [ :aClass :method |


** selector or block indented compared to receiver
=======================================

Finally do we follow kent block ideas?

classes := Smalltalk allClasses select: [:aClass|
               (aClass class includesSelector: #cleanUp)
                       or: [aClass class includesSelector: #cleanUp:]
       ].

->
classes := Smalltalk allClasses
                        select: [:aClass| (aClass class includesSelector: #cleanUp)
                      or: [aClass class includesSelector: #cleanUp:]].

Stef
_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Lukas Renggli
I would use a formatter, like this you can make it really consistent.
The RBConfigurableFormatter is pretty good in that, the only thing I
don't like is the placing of the square brackets. I should look into
fixing that, otherwise it formats exactly the way I would format
myself (and in the way you propose).

Lukas

On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:

> Hi guys
>
> I would like to build a set of canonical code formatting convention for Pharo.
> I need your help. Now take time before replying :)
> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
> Once we agree I would like to define a wiki page.
>
>
> **Space after : rule
> =============
> for example I would like to always have a space after a :
>
> classes := Smalltalk allClasses select:[:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or:[aClass class includesSelector: #cleanUp:]
>       ].
>
> ->
>
>
> classes := Smalltalk allClasses select: [:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or: [aClass class includesSelector: #cleanUp:]
>       ].
>
>
> **Block arg rule
> =============
> Do we want a space before and after block arg
>
> Smalltalk allClasses select: [:aClass :method|
>
> -> Smalltalk allClasses select: [ :aClass :method |
>
>
> ** selector or block indented compared to receiver
> =======================================
>
> Finally do we follow kent block ideas?
>
> classes := Smalltalk allClasses select: [:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or: [aClass class includesSelector: #cleanUp:]
>       ].
>
> ->
> classes := Smalltalk allClasses
>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>                                                        or: [aClass class includesSelector: #cleanUp:]].
>
> Stef
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Lukas Renggli
http://www.lukas-renggli.ch

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
Lukas do you have some code samples.
Something that I particularly hate is the following

        self bla ifTrue: [
                ...

        ] ifFalse: [
                ...
        ]

That is see in the code.

I want
        self bla
                ifTrue: [ ...
                                        ]
                ifFalse: [
                        ... ]



> I would use a formatter, like this you can make it really consistent.
> The RBConfigurableFormatter is pretty good in that, the only thing I
> don't like is the placing of the square brackets. I should look into
> fixing that, otherwise it formats exactly the way I would format
> myself (and in the way you propose).

I would really like to play with the idea of automatic formatting
to see how it goes.

Stef

>
> Lukas
>
> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>> Hi guys
>>
>> I would like to build a set of canonical code formatting convention for Pharo.
>> I need your help. Now take time before replying :)
>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>> Once we agree I would like to define a wiki page.
>>
>>
>> **Space after : rule
>> =============
>> for example I would like to always have a space after a :
>>
>> classes := Smalltalk allClasses select:[:aClass|
>>               (aClass class includesSelector: #cleanUp)
>>                       or:[aClass class includesSelector: #cleanUp:]
>>       ].
>>
>> ->
>>
>>
>> classes := Smalltalk allClasses select: [:aClass|
>>               (aClass class includesSelector: #cleanUp)
>>                       or: [aClass class includesSelector: #cleanUp:]
>>       ].
>>
>>
>> **Block arg rule
>> =============
>> Do we want a space before and after block arg
>>
>> Smalltalk allClasses select: [:aClass :method|
>>
>> -> Smalltalk allClasses select: [ :aClass :method |
>>
>>
>> ** selector or block indented compared to receiver
>> =======================================
>>
>> Finally do we follow kent block ideas?
>>
>> classes := Smalltalk allClasses select: [:aClass|
>>               (aClass class includesSelector: #cleanUp)
>>                       or: [aClass class includesSelector: #cleanUp:]
>>       ].
>>
>> ->
>> classes := Smalltalk allClasses
>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>
>> Stef
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>
>
>
> --
> Lukas Renggli
> http://www.lukas-renggli.ch
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Lukas Renggli
A few examples:

Object>>perform: selector orSendTo: otherTarget
        "If I wish to intercept and handle selector myself, do it; else send
it to otherTarget"

        ^ (self respondsTo: selector)
                ifTrue: [ self perform: selector ]
                ifFalse: [ otherTarget perform: selector ]

Object>>doesNotUnderstand: aMessage
        "Handle the fact that there was an attempt to send the given message
to the receiver but the receiver does not understand this message
(typically sent from the machine when a message is sent to the
receiver and no method is defined for that selector)."

        "Testing: (3 activeProcess)"

        "fixed suggested by Eliot miranda to make sure
       
        [Object new blah + 1]
  on: MessageNotUnderstood
  do: [:e | e resume: 1] does not loop indefinitively"

        | exception resumeValue |
        (exception := MessageNotUnderstood new)
                message: aMessage;
                receiver: self.
        resumeValue := exception signal.
        ^ exception reachedDefaultHandler
                ifTrue: [ aMessage sentTo: self ]
                ifFalse: [ resumeValue ]

Below is an example that shows the placement of block brackets with
multiline blocks. I would like to change that so that the brackets are
placed on the line above (that's in my opinion the only major flaw in
the automatic formatting), unfortunately I haven't found the time to
do this:

Object>>copyFrom: anotherObject
        "Copy to myself all instance variables I have in common with
anotherObject.  This is dangerous because it ignores an object's
control over its own inst vars.  "

        <primitive: 168>
        | mine his |
        mine := self class allInstVarNames.
        his := anotherObject class allInstVarNames.
        1 to: (mine size min: his size) do:
                        [ :ind |
                        (mine at: ind) = (his at: ind)
                                ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
        self class isVariable & anotherObject class isVariable
                ifTrue:
                        [ 1 to: (self basicSize min: anotherObject basicSize) do: [ :ind |
self basicAt: ind put: (anotherObject basicAt: ind) ] ]

Object>>longPrintStringLimitedTo: aLimitValue
        "Answer a String whose characters are a description of the receiver."

        | str |
        str := String
                streamContents:
                        [ :aStream |
                        self
                                longPrintOn: aStream
                                limitedTo: aLimitValue
                                indent: 0 ]. "Objects without inst vars should return something"
        ^ str isEmpty
                ifTrue: [ self printString , String cr ]
                ifFalse: [ str ]




On 28 February 2010 10:58, Stéphane Ducasse <[hidden email]> wrote:

> Lukas do you have some code samples.
> Something that I particularly hate is the following
>
>        self bla ifTrue: [
>                ...
>
>        ] ifFalse: [
>                ...
>        ]
>
> That is see in the code.
>
> I want
>        self bla
>                ifTrue: [ ...
>                                        ]
>                ifFalse: [
>                        ...             ]
>
>
>
>> I would use a formatter, like this you can make it really consistent.
>> The RBConfigurableFormatter is pretty good in that, the only thing I
>> don't like is the placing of the square brackets. I should look into
>> fixing that, otherwise it formats exactly the way I would format
>> myself (and in the way you propose).
>
> I would really like to play with the idea of automatic formatting
> to see how it goes.
>
> Stef
>
>>
>> Lukas
>>
>> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>>> Hi guys
>>>
>>> I would like to build a set of canonical code formatting convention for Pharo.
>>> I need your help. Now take time before replying :)
>>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>>> Once we agree I would like to define a wiki page.
>>>
>>>
>>> **Space after : rule
>>> =============
>>> for example I would like to always have a space after a :
>>>
>>> classes := Smalltalk allClasses select:[:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or:[aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>> ->
>>>
>>>
>>> classes := Smalltalk allClasses select: [:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>>
>>> **Block arg rule
>>> =============
>>> Do we want a space before and after block arg
>>>
>>> Smalltalk allClasses select: [:aClass :method|
>>>
>>> -> Smalltalk allClasses select: [ :aClass :method |
>>>
>>>
>>> ** selector or block indented compared to receiver
>>> =======================================
>>>
>>> Finally do we follow kent block ideas?
>>>
>>> classes := Smalltalk allClasses select: [:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>> ->
>>> classes := Smalltalk allClasses
>>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>>
>>> Stef
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>>
>> --
>> Lukas Renggli
>> http://www.lukas-renggli.ch
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Lukas Renggli
http://www.lukas-renggli.ch

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Igor Stasenko
In reply to this post by Stéphane Ducasse
On 28 February 2010 11:58, Stéphane Ducasse <[hidden email]> wrote:

> Lukas do you have some code samples.
> Something that I particularly hate is the following
>
>        self bla ifTrue: [
>                ...
>
>        ] ifFalse: [
>                ...
>        ]
>
> That is see in the code.
>
> I want
>        self bla
>                ifTrue: [ ...
>                                        ]
>                ifFalse: [
>                        ...             ]
>
>
+1

But, if there is only single block, i usually typing:

self bla ifTrue: [
    code.
    code.
   ]

also i'm usually putting closing ' ] ' at new line, but indented
relatively to receiver, not like:


self bla ifTrue: [
    code.
    code. ]


Also, if statement ends with ']' , i adding a blank like at the end:


self bla ifTrue: [
    code.
   ].

self bla ifTrue: [
    code.
   ].


>
>> I would use a formatter, like this you can make it really consistent.
>> The RBConfigurableFormatter is pretty good in that, the only thing I
>> don't like is the placing of the square brackets. I should look into
>> fixing that, otherwise it formats exactly the way I would format
>> myself (and in the way you propose).
>
> I would really like to play with the idea of automatic formatting
> to see how it goes.
>
> Stef
>
>>
>> Lukas
>>
>> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>>> Hi guys
>>>
>>> I would like to build a set of canonical code formatting convention for Pharo.
>>> I need your help. Now take time before replying :)
>>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>>> Once we agree I would like to define a wiki page.
>>>
>>>
>>> **Space after : rule
>>> =============
>>> for example I would like to always have a space after a :
>>>
>>> classes := Smalltalk allClasses select:[:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or:[aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>> ->
>>>
>>>
>>> classes := Smalltalk allClasses select: [:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>>
>>> **Block arg rule
>>> =============
>>> Do we want a space before and after block arg
>>>
>>> Smalltalk allClasses select: [:aClass :method|
>>>
>>> -> Smalltalk allClasses select: [ :aClass :method |
>>>
>>>
>>> ** selector or block indented compared to receiver
>>> =======================================
>>>
>>> Finally do we follow kent block ideas?
>>>
>>> classes := Smalltalk allClasses select: [:aClass|
>>>               (aClass class includesSelector: #cleanUp)
>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>       ].
>>>
>>> ->
>>> classes := Smalltalk allClasses
>>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>>
>>> Stef
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>>
>> --
>> Lukas Renggli
>> http://www.lukas-renggli.ch
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Best regards,
Igor Stasenko AKA sig.

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Lukas Renggli
Looks good to me
If one day we get a cooler one we could get

>
> self class isVariable & anotherObject class isVariable
> ifTrue:
> [ 1 to: (self basicSize min: anotherObject basicSize) do: [ :ind |
> self basicAt: ind put: (anotherObject basicAt: ind) ] ]
>

self class isVariable & anotherObject class isVariable
                ifTrue: [ 1 to: (self basicSize min: anotherObject basicSize)
                                do: [ :ind | self basicAt: ind put: (anotherObject basicAt: ind) ] ]


self class isVariable & anotherObject class isVariable
                ifTrue: [ 1
                                to: (self basicSize min: anotherObject basicSize)
                                do: [ :ind | self basicAt: ind put: (anotherObject basicAt: ind) ] ]



> Object>>longPrintStringLimitedTo: aLimitValue
> "Answer a String whose characters are a description of the receiver."
>
> | str |
> str := String
> streamContents:
> [ :aStream |
> self
> longPrintOn: aStream
> limitedTo: aLimitValue
> indent: 0 ]. "Objects without inst vars should return something"
> ^ str isEmpty
> ifTrue: [ self printString , String cr ]
> ifFalse: [ str ]
>
>

I would love to have it like that ;-D

Object>>longPrintStringLimitedTo: aLimitValue
        "Answer a String whose characters are a description of the receiver."

        | str |
        str := String
                        streamContents:
                                [ :aStream |
                                        self
                                                longPrintOn: aStream
                                                limitedTo: aLimitValue
                                                indent: 0 ]. "Objects without inst vars should return something"
        ^ str isEmpty
                ifTrue: [ self printString , String cr ]
                ifFalse: [ str ]




_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Igor Stasenko
But, if there is only single block, i usually typing:

self bla ifTrue: [
   code.
   code.
  ]

Yes I see
I would prefer

self bla ifTrue: [
   code.
   code. ]


for me I try

> self bla ifTrue: [ code ].


or
self bla
        ifTrue: [ code.
                   code.]

but I'm not happy because tabbing does not work to align the last line.
So any ideas. I have to reread the kent book.

Stef

> also i'm usually putting closing ' ] ' at new line, but indented
> relatively to receiver, not like:
>
>
> self bla ifTrue: [
>    code.
>    code. ]
>
>
> Also, if statement ends with ']' , i adding a blank like at the end:
>
>
> self bla ifTrue: [
>    code.
>   ].
>
> self bla ifTrue: [
>    code.
>   ].
>
>
>>
>>> I would use a formatter, like this you can make it really consistent.
>>> The RBConfigurableFormatter is pretty good in that, the only thing I
>>> don't like is the placing of the square brackets. I should look into
>>> fixing that, otherwise it formats exactly the way I would format
>>> myself (and in the way you propose).
>>
>> I would really like to play with the idea of automatic formatting
>> to see how it goes.
>>
>> Stef
>>
>>>
>>> Lukas
>>>
>>> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>>>> Hi guys
>>>>
>>>> I would like to build a set of canonical code formatting convention for Pharo.
>>>> I need your help. Now take time before replying :)
>>>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>>>> Once we agree I would like to define a wiki page.
>>>>
>>>>
>>>> **Space after : rule
>>>> =============
>>>> for example I would like to always have a space after a :
>>>>
>>>> classes := Smalltalk allClasses select:[:aClass|
>>>>               (aClass class includesSelector: #cleanUp)
>>>>                       or:[aClass class includesSelector: #cleanUp:]
>>>>       ].
>>>>
>>>> ->
>>>>
>>>>
>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>               (aClass class includesSelector: #cleanUp)
>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>       ].
>>>>
>>>>
>>>> **Block arg rule
>>>> =============
>>>> Do we want a space before and after block arg
>>>>
>>>> Smalltalk allClasses select: [:aClass :method|
>>>>
>>>> -> Smalltalk allClasses select: [ :aClass :method |
>>>>
>>>>
>>>> ** selector or block indented compared to receiver
>>>> =======================================
>>>>
>>>> Finally do we follow kent block ideas?
>>>>
>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>               (aClass class includesSelector: #cleanUp)
>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>       ].
>>>>
>>>> ->
>>>> classes := Smalltalk allClasses
>>>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>>>
>>>> Stef
>>>> _______________________________________________
>>>> Pharo-project mailing list
>>>> [hidden email]
>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>>
>>>
>>>
>>>
>>> --
>>> Lukas Renggli
>>> http://www.lukas-renggli.ch
>>>
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>
>
>
> --
> Best regards,
> Igor Stasenko AKA sig.
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Igor Stasenko
On 28 February 2010 12:44, Stéphane Ducasse <[hidden email]> wrote:

> But, if there is only single block, i usually typing:
>
> self bla ifTrue: [
>   code.
>   code.
>  ]
>
> Yes I see
> I would prefer
>
> self bla ifTrue: [
>   code.
>   code. ]
>
>
> for me I try
>
>> self bla ifTrue: [ code ].
>
yes, one-liner is ok, but only if its short.

The most disguising thing in formatting an exception handling code:

runTest: aSelector

        | actualResult expectedResult |
        [ self
                logTest: aSelector;
                clearLog;
                perform: aSelector ]
                        on: MyTestError do:
                                [ :ex | self log: 'Unhandled Exception'.
                                        ex return: nil ].

as you can see, its a bit hard to quickly determine, where ends one
block and starts another one.
That's why i'm always putting ' ] ' at the next line, and align its
indentation to be the same as in opening brace:

        [ self
                logTest: aSelector;
                clearLog;
                perform: aSelector
        ]
        on: MyTestError do:
                [ :ex | self log: 'Unhandled Exception'.
                        ex return: nil
                ].

do you agree that this one is much more readable?

>
> or
> self bla
>        ifTrue: [ code.
>                   code.]
>
> but I'm not happy because tabbing does not work to align the last line.
> So any ideas. I have to reread the kent book.
>
> Stef
>
>> also i'm usually putting closing ' ] ' at new line, but indented
>> relatively to receiver, not like:
>>
>>
>> self bla ifTrue: [
>>    code.
>>    code. ]
>>
>>
>> Also, if statement ends with ']' , i adding a blank like at the end:
>>
>>
>> self bla ifTrue: [
>>    code.
>>   ].
>>
>> self bla ifTrue: [
>>    code.
>>   ].
>>
>>
>>>
>>>> I would use a formatter, like this you can make it really consistent.
>>>> The RBConfigurableFormatter is pretty good in that, the only thing I
>>>> don't like is the placing of the square brackets. I should look into
>>>> fixing that, otherwise it formats exactly the way I would format
>>>> myself (and in the way you propose).
>>>
>>> I would really like to play with the idea of automatic formatting
>>> to see how it goes.
>>>
>>> Stef
>>>
>>>>
>>>> Lukas
>>>>
>>>> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>>>>> Hi guys
>>>>>
>>>>> I would like to build a set of canonical code formatting convention for Pharo.
>>>>> I need your help. Now take time before replying :)
>>>>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>>>>> Once we agree I would like to define a wiki page.
>>>>>
>>>>>
>>>>> **Space after : rule
>>>>> =============
>>>>> for example I would like to always have a space after a :
>>>>>
>>>>> classes := Smalltalk allClasses select:[:aClass|
>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>                       or:[aClass class includesSelector: #cleanUp:]
>>>>>       ].
>>>>>
>>>>> ->
>>>>>
>>>>>
>>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>>       ].
>>>>>
>>>>>
>>>>> **Block arg rule
>>>>> =============
>>>>> Do we want a space before and after block arg
>>>>>
>>>>> Smalltalk allClasses select: [:aClass :method|
>>>>>
>>>>> -> Smalltalk allClasses select: [ :aClass :method |
>>>>>
>>>>>
>>>>> ** selector or block indented compared to receiver
>>>>> =======================================
>>>>>
>>>>> Finally do we follow kent block ideas?
>>>>>
>>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>>       ].
>>>>>
>>>>> ->
>>>>> classes := Smalltalk allClasses
>>>>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>>>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>>>>
>>>>> Stef
>>>>> _______________________________________________
>>>>> Pharo-project mailing list
>>>>> [hidden email]
>>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>>>
>>>>
>>>>
>>>>
>>>> --
>>>> Lukas Renggli
>>>> http://www.lukas-renggli.ch
>>>>
>>>> _______________________________________________
>>>> Pharo-project mailing list
>>>> [hidden email]
>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>>
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>>
>> --
>> Best regards,
>> Igor Stasenko AKA sig.
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Best regards,
Igor Stasenko AKA sig.

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Adrian Lienhard
I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".

According to these rules I would format the following example:

---------------
1 to: (mine size min: his size) do:
                        [ :ind |
                        (mine at: ind) = (his at: ind)
                                ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
---------------

as:

---------------
1
        to: (mine size min: his size)
        do: [ :index |
                (mine at: index) = (his at: index) ifTrue: [
                        self
                                instVarAt: index
                                put: (anotherObject instVarAt: index) ] ].
---------------

Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.

Cheers,
Adrian




On Feb 28, 2010, at 12:47 , Igor Stasenko wrote:

> On 28 February 2010 12:44, Stéphane Ducasse <[hidden email]> wrote:
>> But, if there is only single block, i usually typing:
>>
>> self bla ifTrue: [
>>   code.
>>   code.
>>  ]
>>
>> Yes I see
>> I would prefer
>>
>> self bla ifTrue: [
>>   code.
>>   code. ]
>>
>>
>> for me I try
>>
>>> self bla ifTrue: [ code ].
>>
> yes, one-liner is ok, but only if its short.
>
> The most disguising thing in formatting an exception handling code:
>
> runTest: aSelector
>
> | actualResult expectedResult |
> [ self
> logTest: aSelector;
> clearLog;
> perform: aSelector ]
> on: MyTestError do:
> [ :ex | self log: 'Unhandled Exception'.
> ex return: nil ].
>
> as you can see, its a bit hard to quickly determine, where ends one
> block and starts another one.
> That's why i'm always putting ' ] ' at the next line, and align its
> indentation to be the same as in opening brace:
>
> [ self
> logTest: aSelector;
> clearLog;
> perform: aSelector
> ]
> on: MyTestError do:
> [ :ex | self log: 'Unhandled Exception'.
> ex return: nil
> ].
>
> do you agree that this one is much more readable?
>
>>
>> or
>> self bla
>>        ifTrue: [ code.
>>                   code.]
>>
>> but I'm not happy because tabbing does not work to align the last line.
>> So any ideas. I have to reread the kent book.
>>
>> Stef
>>
>>> also i'm usually putting closing ' ] ' at new line, but indented
>>> relatively to receiver, not like:
>>>
>>>
>>> self bla ifTrue: [
>>>    code.
>>>    code. ]
>>>
>>>
>>> Also, if statement ends with ']' , i adding a blank like at the end:
>>>
>>>
>>> self bla ifTrue: [
>>>    code.
>>>   ].
>>>
>>> self bla ifTrue: [
>>>    code.
>>>   ].
>>>
>>>
>>>>
>>>>> I would use a formatter, like this you can make it really consistent.
>>>>> The RBConfigurableFormatter is pretty good in that, the only thing I
>>>>> don't like is the placing of the square brackets. I should look into
>>>>> fixing that, otherwise it formats exactly the way I would format
>>>>> myself (and in the way you propose).
>>>>
>>>> I would really like to play with the idea of automatic formatting
>>>> to see how it goes.
>>>>
>>>> Stef
>>>>
>>>>>
>>>>> Lukas
>>>>>
>>>>> On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:
>>>>>> Hi guys
>>>>>>
>>>>>> I would like to build a set of canonical code formatting convention for Pharo.
>>>>>> I need your help. Now take time before replying :)
>>>>>> I would like to structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
>>>>>> Once we agree I would like to define a wiki page.
>>>>>>
>>>>>>
>>>>>> **Space after : rule
>>>>>> =============
>>>>>> for example I would like to always have a space after a :
>>>>>>
>>>>>> classes := Smalltalk allClasses select:[:aClass|
>>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>>                       or:[aClass class includesSelector: #cleanUp:]
>>>>>>       ].
>>>>>>
>>>>>> ->
>>>>>>
>>>>>>
>>>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>>>       ].
>>>>>>
>>>>>>
>>>>>> **Block arg rule
>>>>>> =============
>>>>>> Do we want a space before and after block arg
>>>>>>
>>>>>> Smalltalk allClasses select: [:aClass :method|
>>>>>>
>>>>>> -> Smalltalk allClasses select: [ :aClass :method |
>>>>>>
>>>>>>
>>>>>> ** selector or block indented compared to receiver
>>>>>> =======================================
>>>>>>
>>>>>> Finally do we follow kent block ideas?
>>>>>>
>>>>>> classes := Smalltalk allClasses select: [:aClass|
>>>>>>               (aClass class includesSelector: #cleanUp)
>>>>>>                       or: [aClass class includesSelector: #cleanUp:]
>>>>>>       ].
>>>>>>
>>>>>> ->
>>>>>> classes := Smalltalk allClasses
>>>>>>                        select: [:aClass| (aClass class includesSelector: #cleanUp)
>>>>>>                                                        or: [aClass class includesSelector: #cleanUp:]].
>>>>>>
>>>>>> Stef
>>>>>> _______________________________________________
>>>>>> Pharo-project mailing list
>>>>>> [hidden email]
>>>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>>>>
>>>>>
>>>>>
>>>>>
>>>>> --
>>>>> Lukas Renggli
>>>>> http://www.lukas-renggli.ch
>>>>>
>>>>> _______________________________________________
>>>>> Pharo-project mailing list
>>>>> [hidden email]
>>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>>
>>>>
>>>> _______________________________________________
>>>> Pharo-project mailing list
>>>> [hidden email]
>>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>>
>>>
>>>
>>>
>>> --
>>> Best regards,
>>> Igor Stasenko AKA sig.
>>>
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>
>
>
> --
> Best regards,
> Igor Stasenko AKA sig.
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

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

codingconventions.pdf (117K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Schwab,Wilhelm K
In reply to this post by Lukas Renggli
Stef,

It pains me to have to be a pain about this.  I never use a space after a colon; what other people do is their business, but I much prefer having the space gone.  Other formatting concerns are far less trivial to me than a personal preference.

Lukas is correct about using a formatter, but it has to be a separate or optional step because the current state of formatting is hostile to comments.  If moving code to Pharo has taught me anything, it is that I have been correct to embed dated (month-year) comments in my code.  The RB scatters them to the four corners, which is why I don't use the thing.

I also format code in ways that are analogous to phrasing in music.  I tried to capture it in a custom formatter, and quickly realized that I see design, workflow, organizational politics, etc., and the machine sees syntax.  It will never "understand" what belongs together and what does not.  Anything that forces formatting on me is defective.

If there is a way for me to optionally format my code with a Pharo formatter, I'm happy to do so as I turn it over.  Anything that I am actively using will be littered with comments (until I tire of them[*]) and formatted in a way that helps me see the big picture long after the machine smashes it down to a mere sequence of byte codes.

Bill

[*] every so often, I clean out truly obsolete information, but that is more a question of the amount of change that has occurred, not chronological age.  In moving to Pharo, I ran across couple of related defects from 2003, and fixed them within an hour thanks to comments in the code.  This is one of many such stories that have formed my (somewhat stubborn) thoughts on code formatting.



-----Original Message-----
From: [hidden email] [mailto:[hidden email]] On Behalf Of Lukas Renggli
Sent: Sunday, February 28, 2010 4:52 AM
To: [hidden email]
Subject: Re: [Pharo-project] about code formatting in pharo

I would use a formatter, like this you can make it really consistent.
The RBConfigurableFormatter is pretty good in that, the only thing I don't like is the placing of the square brackets. I should look into fixing that, otherwise it formats exactly the way I would format myself (and in the way you propose).

Lukas

On 28 February 2010 10:36, stephane ducasse <[hidden email]> wrote:

> Hi guys
>
> I would like to build a set of canonical code formatting convention for Pharo.
> I need your help. Now take time before replying :) I would like to
> structure the discussion and proceed step by step. So at max I would like to discuss one or two formatting approach per mail.
> Once we agree I would like to define a wiki page.
>
>
> **Space after : rule
> =============
> for example I would like to always have a space after a :
>
> classes := Smalltalk allClasses select:[:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or:[aClass class includesSelector: #cleanUp:]
>       ].
>
> ->
>
>
> classes := Smalltalk allClasses select: [:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or: [aClass class includesSelector: #cleanUp:]
>       ].
>
>
> **Block arg rule
> =============
> Do we want a space before and after block arg
>
> Smalltalk allClasses select: [:aClass :method|
>
> -> Smalltalk allClasses select: [ :aClass :method |
>
>
> ** selector or block indented compared to receiver
> =======================================
>
> Finally do we follow kent block ideas?
>
> classes := Smalltalk allClasses select: [:aClass|
>               (aClass class includesSelector: #cleanUp)
>                       or: [aClass class includesSelector: #cleanUp:]
>       ].
>
> ->
> classes := Smalltalk allClasses
>                        select: [:aClass| (aClass class
> includesSelector: #cleanUp)
>                                                        or: [aClass class includesSelector: #cleanUp:]].
>
> Stef
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Lukas Renggli
http://www.lukas-renggli.ch

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

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

jgfoster
In reply to this post by Stéphane Ducasse

On Feb 28, 2010, at 1:58 AM, Stéphane Ducasse wrote:

> Lukas do you have some code samples.
> Something that I particularly hate is the following
>
> self bla ifTrue: [
> ...
>
> ] ifFalse: [
> ...
> ]

I'd like to understand what it is about the above you hate.

> That is see in the code.
>
> I want
> self bla
> ifTrue: [ ...
> ]
> ifFalse: [
> ... ]

Does the code in the ifTrue: block begin on the same line? How about the ifFalse: block? If it begins on the same line, then how many indents for the second line?

James
_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Levente Uzonyi-2
On Sun, 28 Feb 2010, James Foster wrote:

>
> On Feb 28, 2010, at 1:58 AM, Stéphane Ducasse wrote:
>
>> Lukas do you have some code samples.
>> Something that I particularly hate is the following
>>
>> self bla ifTrue: [
>> ...
>>
>> ] ifFalse: [
>> ...
>> ]
>
> I'd like to understand what it is about the above you hate.
It's like C code, not like a message send. Do you write code like this?

aCollection do: [ :each |
  ...
] separatedBy: [
  ...
]

>
>> That is see in the code.
>>
>> I want
>> self bla
>> ifTrue: [ ...
>> ]
>> ifFalse: [
>> ... ]
>
> Does the code in the ifTrue: block begin on the same line? How about the ifFalse: block? If it begins on the same line, then how many indents for the second line?
>
IMHO, if the code in the first block is short enought, then it's only a
single line, otherwise not, for example:

self bla
  ifTrue: [ self bar ]
  ifFalse: [
  ... ]

self bla
  ifTrue: [
  ... ]
  ifFalse: [
  ... ]

This book has great guidelines:
http://stephane.ducasse.free.fr/FreeBooks/WithStyle/SmalltalkWithStyle.pdf


Levente



> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Schwab,Wilhelm K
In reply to this post by Adrian Lienhard
Adrian,

Horrible is an understatement :)  Your version is a big improvement.  I frequently put ending brackets on their own line with indentation to aid in matching, but not always.

I do not (much) care what conventions the benevolent dictators select for Pharo, but I **do** care that it not be forced on my code that I retain for my own use.  There should be ways to compile, export and load code and packagets w/o encountering automatic formatting.  As long as that is the case, enjoy!!

Bill



-----Original Message-----
From: [hidden email] [mailto:[hidden email]] On Behalf Of Adrian Lienhard
Sent: Sunday, February 28, 2010 8:11 AM
To: [hidden email]
Subject: Re: [Pharo-project] about code formatting in pharo

I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".

According to these rules I would format the following example:

---------------
1 to: (mine size min: his size) do:
                        [ :ind |
                        (mine at: ind) = (his at: ind)
                                ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
---------------

as:

---------------
1
        to: (mine size min: his size)
        do: [ :index |
                (mine at: index) = (his at: index) ifTrue: [
                        self
                                instVarAt: index
                                put: (anotherObject instVarAt: index) ] ].
---------------

Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.

Cheers,
Adrian


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Adrian Lienhard
Hi Bill,

Don't worry. Nobody wants to force you to use his conventions :)

The question really only concerns the code of PharoCore. I think a consistent way of code formatting really is a good idea, even if not everybody agrees with each rule.

Cheers,
Adrian

On Feb 28, 2010, at 18:43 , Schwab,Wilhelm K wrote:

> Adrian,
>
> Horrible is an understatement :)  Your version is a big improvement.  I frequently put ending brackets on their own line with indentation to aid in matching, but not always.
>
> I do not (much) care what conventions the benevolent dictators select for Pharo, but I **do** care that it not be forced on my code that I retain for my own use.  There should be ways to compile, export and load code and packagets w/o encountering automatic formatting.  As long as that is the case, enjoy!!
>
> Bill
>
>
>
> -----Original Message-----
> From: [hidden email] [mailto:[hidden email]] On Behalf Of Adrian Lienhard
> Sent: Sunday, February 28, 2010 8:11 AM
> To: [hidden email]
> Subject: Re: [Pharo-project] about code formatting in pharo
>
> I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".
>
> According to these rules I would format the following example:
>
> ---------------
> 1 to: (mine size min: his size) do:
> [ :ind |
> (mine at: ind) = (his at: ind)
> ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
> ---------------
>
> as:
>
> ---------------
> 1
> to: (mine size min: his size)
> do: [ :index |
> (mine at: index) = (his at: index) ifTrue: [
> self
> instVarAt: index
> put: (anotherObject instVarAt: index) ] ].
> ---------------
>
> Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.
>
> Cheers,
> Adrian
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Schwab,Wilhelm K
Adrian,

I appreciate the reassurance, and agree that conventions are a good idea.  I further agree with Lukas that a formatter is a good way to get there, but want to make the case for doing that in a way that does not force the hands of end-user (which I appear to have done).

Bill


-----Original Message-----
From: [hidden email] [mailto:[hidden email]] On Behalf Of Adrian Lienhard
Sent: Sunday, February 28, 2010 2:52 PM
To: [hidden email]
Subject: Re: [Pharo-project] about code formatting in pharo

Hi Bill,

Don't worry. Nobody wants to force you to use his conventions :)

The question really only concerns the code of PharoCore. I think a consistent way of code formatting really is a good idea, even if not everybody agrees with each rule.

Cheers,
Adrian

On Feb 28, 2010, at 18:43 , Schwab,Wilhelm K wrote:

> Adrian,
>
> Horrible is an understatement :)  Your version is a big improvement.  I frequently put ending brackets on their own line with indentation to aid in matching, but not always.
>
> I do not (much) care what conventions the benevolent dictators select for Pharo, but I **do** care that it not be forced on my code that I retain for my own use.  There should be ways to compile, export and load code and packagets w/o encountering automatic formatting.  As long as that is the case, enjoy!!
>
> Bill
>
>
>
> -----Original Message-----
> From: [hidden email]
> [mailto:[hidden email]] On Behalf Of
> Adrian Lienhard
> Sent: Sunday, February 28, 2010 8:11 AM
> To: [hidden email]
> Subject: Re: [Pharo-project] about code formatting in pharo
>
> I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".
>
> According to these rules I would format the following example:
>
> ---------------
> 1 to: (mine size min: his size) do:
> [ :ind |
> (mine at: ind) = (his at: ind)
> ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
> ---------------
>
> as:
>
> ---------------
> 1
> to: (mine size min: his size)
> do: [ :index |
> (mine at: index) = (his at: index) ifTrue: [
> self
> instVarAt: index
> put: (anotherObject instVarAt: index) ] ].
> ---------------
>
> Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.
>
> Cheers,
> Adrian
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


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

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Igor Stasenko
>
> runTest: aSelector
>
> | actualResult expectedResult |
> [ self
> logTest: aSelector;
> clearLog;
> perform: aSelector ]
> on: MyTestError do:
> [ :ex | self log: 'Unhandled Exception'.
> ex return: nil ].
>
> as you can see, its a bit hard to quickly determine, where ends one
> block and starts another one.
> That's why i'm always putting ' ] ' at the next line, and align its
> indentation to be the same as in opening brace:
>
> [ self
> logTest: aSelector;
> clearLog;
> perform: aSelector
> ]
> on: MyTestError do:
> [ :ex | self log: 'Unhandled Exception'.
> ex return: nil
> ].
>
> do you agree that this one is much more readable

Not for me :)
May be I read too much Smalltalk code I prefer the rectangle approach of the first one ;)
_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Adrian Lienhard
thanks adrian


On Feb 28, 2010, at 2:11 PM, Adrian Lienhard wrote:

> I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".
>
> According to these rules I would format the following example:
>
> ---------------
> 1 to: (mine size min: his size) do:
> [ :ind |
> (mine at: ind) = (his at: ind)
> ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
> ---------------
>
> as:
>
> ---------------
> 1
> to: (mine size min: his size)
> do: [ :index |
> (mine at: index) = (his at: index) ifTrue: [
> self
> instVarAt: index
> put: (anotherObject instVarAt: index) ] ].
> ---------------
>
> Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.

:)

why not like that?
> 1
> to: (mine size min: his size)
> do: [ :index |
> (mine at: index) = (his at: index)
> ifTrue: [ self
> instVarAt: index
> put: (anotherObject instVarAt: index) ] ].



_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Levente Uzonyi-2
+ 10

>> I'd like to understand what it is about the above you hate.
>
> It's like C code, not like a message send. Do you write code like this?
>
> aCollection do: [ :each |
> ...
> ] separatedBy: [
> ...
> ]
>
>>
>>> That is see in the code.
>>>
>>> I want
>>> self bla
>>> ifTrue: [ ...
>>> ]
>>> ifFalse: [
>>> ... ]
>>
>> Does the code in the ifTrue: block begin on the same line? How about the ifFalse: block? If it begins on the same line, then how many indents for the second line?
>>
>
> IMHO, if the code in the first block is short enought, then it's only a single line, otherwise not, for example:
>
> self bla
> ifTrue: [ self bar ]
> ifFalse: [
> ... ]
>
> self bla
> ifTrue: [
> ... ]
> ifFalse: [
> ... ]
>
> This book has great guidelines:
> http://stephane.ducasse.free.fr/FreeBooks/WithStyle/SmalltalkWithStyle.pdf
>
>
> Levente
>
>
>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by Adrian Lienhard
you know go (the language) includes in the language the formatting so there is no discussion.
Now I really like to see smalltalk code and not C code because.....

It slows me down a lot when I read and I read a lot of code. :)

Stef



On Feb 28, 2010, at 8:51 PM, Adrian Lienhard wrote:

> Hi Bill,
>
> Don't worry. Nobody wants to force you to use his conventions :)
>
> The question really only concerns the code of PharoCore. I think a consistent way of code formatting really is a good idea, even if not everybody agrees with each rule.
>
> Cheers,
> Adrian
>
> On Feb 28, 2010, at 18:43 , Schwab,Wilhelm K wrote:
>
>> Adrian,
>>
>> Horrible is an understatement :)  Your version is a big improvement.  I frequently put ending brackets on their own line with indentation to aid in matching, but not always.
>>
>> I do not (much) care what conventions the benevolent dictators select for Pharo, but I **do** care that it not be forced on my code that I retain for my own use.  There should be ways to compile, export and load code and packagets w/o encountering automatic formatting.  As long as that is the case, enjoy!!
>>
>> Bill
>>
>>
>>
>> -----Original Message-----
>> From: [hidden email] [mailto:[hidden email]] On Behalf Of Adrian Lienhard
>> Sent: Sunday, February 28, 2010 8:11 AM
>> To: [hidden email]
>> Subject: Re: [Pharo-project] about code formatting in pharo
>>
>> I've attached the coding conventions that we use at Cmsbox and netstyle.ch. They closely follow the suggestions of Kent Beck's "Smalltalk Best Practice Patterns".
>>
>> According to these rules I would format the following example:
>>
>> ---------------
>> 1 to: (mine size min: his size) do:
>> [ :ind |
>> (mine at: ind) = (his at: ind)
>> ifTrue: [ self instVarAt: ind put: (anotherObject instVarAt: ind) ] ].
>> ---------------
>>
>> as:
>>
>> ---------------
>> 1
>> to: (mine size min: his size)
>> do: [ :index |
>> (mine at: index) = (his at: index) ifTrue: [
>> self
>> instVarAt: index
>> put: (anotherObject instVarAt: index) ] ].
>> ---------------
>>
>> Putting "[ :ind |" on a new line and using multiple tab indentation looks horrible to me.
>>
>> Cheers,
>> Adrian
>>
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: about code formatting in pharo

Stéphane Ducasse
In reply to this post by jgfoster
Hi James

> Lukas do you have some code samples.
>> Something that I particularly hate is the following
>>
>> self bla ifTrue: [
>> ...
>>
>> ] ifFalse: [
>> ...
>> ]
>
> I'd like to understand what it is about the above you hate.

See levente
In addition I have to apy extreme attention to see that the two branches are sent to the same conditional

>
>> That is see in the code.
>>
>> I want
>> self bla
>> ifTrue: [ ...
>> ]
>> ifFalse: [
>> ... ]
>
> Does the code in the ifTrue: block begin on the same line? How about the ifFalse: block? If it begins on the same line, then how many indents for the second line?
>
> James
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


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