Tee hee, cool beans guys :)

Niko

On Tue, Nov 10, 2009 at 6:32 PM, Stéphane Ducasse
<stephane.duca...@inria.fr> wrote:
> It is a pearl!
> may be a joke for geek but I love it.
>
> STef
>> ((Project class parseTreeFor: #mostRecent:onServer:) allChildren
>>       reject: [ :each | each isVariable ])
>>       asBag sortedCounts
>>       first: 20
>>
>> 5x RBLiteralValueNode(-1)
>> 3x RBMessageNode(Array with: goodName
>>       with: max)
>> 3x RBMessageNode(max = -1)
>> 3x RBAssignmentNode(goodName := rawList at: ind)
>> 3x RBSequenceNode(^ Array with: goodName
>>       with: max)
>> 3x RBReturnNode(^ nothingFound)
>> 3x RBMessageNode(max = -1 ifFalse:
>>               [ ^ Array with: goodName
>>                       with: max ])
>> 3x RBBlockNode([ ^ Array with: goodName
>>       with: max ])
>> 3x RBMessageNode(rawList at: ind)
>> 3x RBReturnNode(^ Array with: goodName
>>       with: max)
>> 2x RBBlockNode([ num := (Project parseProjectFileName: aName) second.
>> num > max ifTrue:
>>               [ max := num.
>>               goodName := rawList at: ind ] ])
>> 2x RBMessageNode((Project parseProjectFileName: aName) second)
>> 2x RBAssignmentNode(num := (Project parseProjectFileName: aName) second)
>> 2x RBAssignmentNode(max := num)
>> 2x RBBlockNode([ max := num.
>> goodName := rawList at: ind ])
>> 2x RBMessageNode((Project parseProjectFileName: aName))
>> 2x RBSequenceNode(max := num.
>> goodName := rawList at: ind)
>> 2x RBMessageNode(num > max ifTrue:
>>               [ max := num.
>>               goodName := rawList at: ind ])
>> 2x RBMessageNode(num > max)
>> 2x RBLiteralValueNode(' ')
>> ...
>>
>>
>> 2009/11/10 Stéphane Ducasse <stephane.duca...@inria.fr>:
>>> if you want to have fun try to identify the number of times certain parts 
>>> are duplicated inside the same method.
>>>
>>> Stef
>>>
>>> mostRecent: projName onServer: aServerDirectory
>>>        "Find the exact fileName of the most recent version of project with 
>>> the stem name of projName.  Names are of the form 'projName|mm.pr' where mm 
>>> is a mime-encoded integer version number.
>>>        File names may or may not be HTTP escaped, %20 on the server."
>>>        | stem list max goodName triple num stem1 stem2 rawList nothingFound 
>>> unEscName |
>>>        self flag: #bob.        "do we want to handle unversioned projects 
>>> as well?"
>>>        nothingFound := {  nil. -1  }.
>>>        aServerDirectory ifNil: [ ^ nothingFound ].
>>>        "23 sept 2000 - some old projects have periods in name so be more 
>>> careful"
>>>        unEscName := projName unescapePercents.
>>>        triple := Project parseProjectFileName: unEscName.
>>>        stem := triple first.
>>>        rawList := aServerDirectory fileNames.
>>>        rawList isString ifTrue:
>>>                [ self inform: 'server is unavailable'.
>>>                ^ nothingFound ].
>>>        list := rawList collect: [ :nnn | nnn unescapePercents ].
>>>        max := -1.
>>>        goodName := nil.
>>>        list withIndexDo:
>>>                [ :aName :ind |
>>>                (aName beginsWith: stem) ifTrue:
>>>                        [ num := (Project parseProjectFileName: aName) 
>>> second.
>>>                        num > max ifTrue:
>>>                                [ max := num.
>>>                                goodName := rawList at: ind ] ] ].
>>>        max = -1 ifFalse:
>>>                [ ^ Array
>>>                        with: goodName
>>>                        with: max ].
>>>
>>>        "try with underbar for spaces on server"
>>>        (stem includes: $ ) ifTrue:
>>>                [ stem1 := stem
>>>                        copyReplaceAll: ' '
>>>                        with: '_'.
>>>                list withIndexDo:
>>>                        [ :aName :ind |
>>>                        (aName beginsWith: stem1) ifTrue:
>>>                                [ num := (Project parseProjectFileName: 
>>> aName) second.
>>>                                num > max ifTrue:
>>>                                        [ max := num.
>>>                                        goodName := rawList at: ind ] ] ] ].
>>>        max = -1 ifFalse:
>>>                [ ^ Array
>>>                        with: goodName
>>>                        with: max ].
>>>
>>>        "try without the marker | "
>>>        stem1 := stem allButLast , '.pr'.
>>>        stem2 := stem1
>>>                copyReplaceAll: ' '
>>>                with: '_'.      "and with spaces replaced"
>>>        list withIndexDo:
>>>                [ :aName :ind |
>>>                (aName beginsWith: stem1) | (aName beginsWith: stem2) ifTrue:
>>>                        [ (triple := aName findTokens: '.') size >= 2 ifTrue:
>>>                                [ max := 0.
>>>                                goodName := rawList at: ind ] ] ].      "no 
>>> other versions"
>>>        max = -1 ifFalse:
>>>                [ ^ Array
>>>                        with: goodName
>>>                        with: max ].
>>>        ^ nothingFound  "no matches"
>>> _______________________________________________
>>> Pharo-project mailing list
>>> Pharo-project@lists.gforge.inria.fr
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>>
>> --
>> Lukas Renggli
>> http://www.lukas-renggli.ch
>>
>> _______________________________________________
>> Pharo-project mailing list
>> Pharo-project@lists.gforge.inria.fr
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>

_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to