[squeak-dev] The Trunk: Compiler-nice.201.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Wed Mar 30 23:42:47 UTC 2011


"An interesting snippet"
Compiler recompileAll.
(MessageNode classPool at:#MacroSelectors) collect: [:e | e ->
(SystemNavigation default allCallsOn: e) size]
->
{#ifTrue:->7601 .
 #ifFalse:->3252 .
 #ifTrue:ifFalse:->4152 .
 #ifFalse:ifTrue:->249 .
 #and:->2222 .
 #or:->1355 .
 #whileFalse:->490 .
 #whileTrue:->723 .
 #whileFalse->99 .
 #whileTrue->93 .
 #to:do:->1178 .
 #to:by:do:->140 .
 #caseOf:->7 .
 #caseOf:otherwise:->33 .
 #ifNil:->2773 .
 #ifNotNil:->2065 .
 #ifNil:ifNotNil:->568 .
 #ifNotNil:ifNil:->157 .
 #repeat->23}


2011/3/31  <commits at source.squeak.org>:
> Nicolas Cellier uploaded a new version of Compiler to project The Trunk:
> http://source.squeak.org/trunk/Compiler-nice.201.mcz
>
> ==================== Summary ====================
>
> Name: Compiler-nice.201
> Author: nice
> Time: 31 March 2011, 12:45:32.697 am
> UUID: d694a5f8-4d75-2f4d-a06d-4c5de7fe1656
> Ancestors: Compiler-nice.200
>
> Put optimized selectors in CompiledMethod literals so that senders can be browsed normally.
> Take care to not overflow the scarse literal ressource.
>
> It is necessary to evaluate (Compiler recompileAll) before succesfully browsing senders of #ifNil:
>
> Thanks to Marcus at http://code.google.com/p/pharo/issues/detail?id=2559 for the idea.
>
> =============== Diff against Compiler-nice.200 ===============
>
> Item was changed:
>  ParseNode subclass: #Encoder
> +       instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals optimizedSelectors'
> -       instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'Compiler-Kernel'!
>
>  !Encoder commentStamp: '<historical>' prior: 0!
>  I encode names and literals into tree nodes with byte codes for the compiler. Byte codes for literals are not assigned until the tree-sizing pass of the compiler, because only then is it known which literals are actually needed. I also keep track of sourceCode ranges during parsing and code generation so I can provide an inverse map for the debugger.!
>
> Item was changed:
>  ----- Method: Encoder>>allLiterals (in category 'results') -----
>  allLiterals
> +       addedSelectorAndMethodClassLiterals ifFalse:
> -       ((literalStream isKindOf: WriteStream)
> -        and: [ (addedSelectorAndMethodClassLiterals ifNil: [ false ]) not]) ifTrue:
>                [addedSelectorAndMethodClassLiterals := true.
> +               "Put the optimized selectors in literals so as to browse senders more easily"
> +               optimizedSelectors := optimizedSelectors reject: [:e| literalStream originalContents hasLiteral: e].
> +               optimizedSelectors isEmpty ifFalse: [
> +                       "Use one entry per literal if enough room, else make anArray"
> +                       literalStream position + optimizedSelectors size + 2 > 255
> +                               ifTrue: [self litIndex: optimizedSelectors asArray]
> +                               ifFalse: [optimizedSelectors do: [:e | self litIndex: e]]].
> +               "Add a slot for selector or MethodProperties"
> +               self litIndex: nil.
> +               self litIndex: self associationForClass].
> +       ^literalStream contents!
> -                self litIndex: nil.
> -                self litIndex: self associationForClass].
> -       ^literalStream contents
> -
> -       "The funky ifNil: [false], even though the init method initializes addedSAMCL,
> -        is simply so that Monticello can load and compile this update without
> -        killing the encoder that is compiling that update itself..."!
>
> Item was changed:
>  ----- Method: Encoder>>initScopeAndLiteralTables (in category 'initialize-release') -----
>  initScopeAndLiteralTables
>
>        scopeTable := StdVariables copy.
>        litSet := StdLiterals copy.
>        "comments can be left hanging on nodes from previous compilations.
>         probably better than this hack fix is to create the nodes afresh on each compilation."
>        scopeTable do:
>                [:varNode| varNode comment: nil].
>        litSet do:
>                [:varNode| varNode comment: nil].
>        selectorSet := StdSelectors copy.
>        litIndSet := Dictionary new: 16.
>        literalStream := WriteStream on: (Array new: 32).
> +       addedSelectorAndMethodClassLiterals := false.
> +       optimizedSelectors := Set new!
> -       addedSelectorAndMethodClassLiterals := false!
>
> Item was removed:
> - ----- Method: Encoder>>nTemps:literals:class: (in category 'initialize-release') -----
> - nTemps: n literals: lits class: cl
> -       "Decompile."
> -
> -       supered := false.
> -       class := cl.
> -       nTemps := n.
> -       literalStream := ReadStream on: lits.
> -       literalStream position: lits size.
> -       sourceRanges := Dictionary new: 32.
> -       globalSourceRanges := OrderedCollection new: 32.
> - !
>
> Item was added:
> + ----- Method: Encoder>>noteOptimizedSelector: (in category 'encoding') -----
> + noteOptimizedSelector: aSymbol
> +       "Register a selector as being optimized.
> +       These optimized selectors will later be registered into the literals so that tools can easily browse senders."
> +       optimizedSelectors add: aSymbol!
>
> Item was changed:
>  ----- Method: MessageNode>>sizeCodeForEffect: (in category 'code generation') -----
>  sizeCodeForEffect: encoder
>
>        special > 0
> +               ifTrue:
> +                       [encoder noteOptimizedSelector: originalSelector.
> +                       ^self perform: (MacroSizers at: special) with: encoder with: false].
> -               ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: false].
>        ^super sizeCodeForEffect: encoder!
>
> Item was changed:
>  ----- Method: MessageNode>>sizeCodeForValue: (in category 'code generation') -----
>  sizeCodeForValue: encoder
>        | total |
>        special > 0
> +               ifTrue:
> +                       [encoder noteOptimizedSelector: originalSelector.
> +                       ^self perform: (MacroSizers at: special) with: encoder with: true].
> -               ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: true].
>        receiver == NodeSuper
>                ifTrue: [selector := selector copy "only necess for splOops"].
>        total := selector sizeCode: encoder args: arguments size super: receiver == NodeSuper.
>        receiver == nil
>                ifFalse: [total := total + (receiver sizeCodeForValue: encoder)].
>        sizes := arguments collect:
>                                        [:arg | | argSize |
>                                        argSize := arg sizeCodeForValue: encoder.
>                                        total := total + argSize.
>                                        argSize].
>        ^total!
>
>
>



More information about the Squeak-dev mailing list