The Trunk: Compiler-eem.154.mcz

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

The Trunk: Compiler-eem.154.mcz

commits-2
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.154.mcz

==================== Summary ====================

Name: Compiler-eem.154
Author: eem
Time: 12 August 2010, 2:04:48.383 pm
UUID: 38a702f7-88c0-4176-9213-ce25c77bd3ef
Ancestors: Compiler-nice.153

Fix decompilation of blocks with indirect temps, e.g.
        | x y |
        [:a :b | x := a. y := b. x+y] decompile
Correct comment of evaluate:in:to:notifying:ifFail:logged: not
we no longer install doits in dictionaries but use withArgs:executeMethod:

=============== Diff against Compiler-nice.153 ===============

Item was changed:
  ----- Method: Decompiler>>pushClosureCopyNumCopiedValues:numArgs:blockSize: (in category 'instruction decoding') -----
  pushClosureCopyNumCopiedValues: numCopied numArgs: numArgs blockSize: blockSize
  | copiedValues |
  self sawClosureBytecode.
+ copiedValues := ((1 to: numCopied) collect: [:ign| stack removeLast]) reversed.
- numCopied > 0
- ifTrue:
- [copiedValues := Array new: numCopied.
- numLocalTemps == #decompileBlock: ifTrue: "Hack fake temps for copied values"
- [1 to: numCopied do: [:i| stack addLast: (constructor codeTemp: i - 1)]].
- numCopied to: 1 by: -1 do:
- [:i|
- copiedValues at: i put: stack removeLast]]
- ifFalse:
- [copiedValues := #()].
  self doClosureCopyCopiedValues: copiedValues numArgs: numArgs blockSize: blockSize!

Item was changed:
  ----- Method: Compiler>>evaluate:in:to:notifying:ifFail:logged: (in category 'public access') -----
  evaluate: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag
+ "Compiles the sourceStream into a parse tree, then generates code into
+ a method. If aContext is not nil, the text can refer to temporaries in that
+ context (the Debugger uses this). If aRequestor is not nil, then it will receive
+ a notify:at: message before the attempt to evaluate is aborted. Finally, the
+ compiled method is invoked from here via withArgs:executeMethod:, hence
+ the system no longer creates Doit method litter on errors."
- "Compiles the sourceStream into a parse tree, then generates code into a
- method. This method is then installed in the receiver's class so that it
- can be invoked. In other words, if receiver is not nil, then the text can
- refer to instance variables of that receiver (the Inspector uses this). If
- aContext is not nil, the text can refer to temporaries in that context (the
- Debugger uses this). If aRequestor is not nil, then it will receive a
- notify:at: message before the attempt to evaluate is aborted. Finally, the
- compiled method is invoked from here as DoIt or (in the case of
- evaluation in aContext) DoItIn:. The method is subsequently removed
- from the class, but this will not get done if the invocation causes an
- error which is terminated. Such garbage can be removed by executing:
- Smalltalk allBehaviorsDo: [:cl | cl removeSelector: #DoIt; removeSelector:
- #DoItIn:]."
 
  | methodNode method value toLog itsSelection itsSelectionString |
  class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class.
  self from: textOrStream class: class context: aContext notifying: aRequestor.
+ methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value].
- methodNode := self translate: sourceStream noPattern: true ifFail:
- [^failBlock value].
 
+ method := self interactive
+ ifTrue: [methodNode generateWithTempNames]
+ ifFalse: [methodNode generate].
+
- method := self interactive ifTrue: [ methodNode generateWithTempNames ]
- ifFalse: [methodNode generate].
-
  value := receiver
  withArgs: (context ifNil: [#()] ifNotNil: [{context}])
  executeMethod: method.
 
+ logFlag ifTrue:
+ [toLog := ((requestor respondsTo: #selection)  
- logFlag ifTrue:[
- toLog := ((requestor respondsTo: #selection)  
  and:[(itsSelection := requestor selection) notNil
  and:[(itsSelectionString := itsSelection asString) isEmptyOrNil not]])
  ifTrue:[itsSelectionString]
  ifFalse:[sourceStream contents].
  SystemChangeNotifier uniqueInstance evaluated: toLog context: aContext].
  ^ value!

Item was changed:
  ----- Method: Decompiler>>decompileBlock: (in category 'public access') -----
  decompileBlock: aBlock
  "Decompile aBlock, returning the result as a BlockNode.  
  Show temp names from source if available."
  "Decompiler new decompileBlock: [3 + 4]"
+ | startpc end homeClass blockNode methodNode home |
- | startpc end homeClass blockNode methodNode home source |
  (home := aBlock home) ifNil: [^ nil].
  method := home method.
  (homeClass := home methodClass) == #unknown ifTrue: [^ nil].
+ aBlock isClosure ifTrue:
+ [(methodNode := method decompileWithTemps)
+ ifNil: [^nil]
+ ifNotNil: [methodNode nodesDo: [:node| node pc = aBlock startpc ifTrue: [^node]]].
+ ^self error: 'cannot find block node matching aBlock'].
  constructor := self constructorForMethod: aBlock method.
+
+ self withTempNames: method methodNode tempNames.
+
- self withTempNames: (method tempNamesString ifNil:[
- method fileIndex ~~ 0 ifTrue: "got any source code?"
- [source := [method getSourceFromFile]
- on: Error
- do: [:ex | ^ nil].
- methodNode := [homeClass compilerClass new
- parse: source
- in: homeClass
- notifying: nil]
- on: SyntaxErrorNotification
- do: [:ex | ^ nil].
- methodNode schematicTempNamesString]]).
  self initSymbols: homeClass.
  startpc := aBlock startpc.
+ end := aBlock endPC.
- end := aBlock isClosure
- ifTrue: [(method at: startpc - 2) * 256
-  + (method at: startpc - 1) + startpc - 1]
- ifFalse:
- [(method at: startpc - 2) \\ 16 - 4 * 256
- + (method at: startpc - 1) + startpc - 1].
  stack := OrderedCollection new: method frameSize.
  caseExits := OrderedCollection new.
  statements := OrderedCollection new: 20.
+ super method: method pc: startpc - 5.
- super
- method: method
- pc: (aBlock isClosure ifTrue: [startpc - 4] ifFalse: [startpc - 5]).
- aBlock isClosure ifTrue:
- [numLocalTemps := #decompileBlock: "Get pushClosureCopy... to hack fake temps for copied values"].
  blockNode := self blockTo: end.
  stack isEmpty ifFalse: [self error: 'stack not empty'].
  ^blockNode statements first!

Item was changed:
  ----- Method: Decompiler>>doClosureCopyCopiedValues:numArgs:blockSize: (in category 'control') -----
  doClosureCopyCopiedValues: blockCopiedValues numArgs: numArgs blockSize: blockSize
+ | startpc savedTemps savedTempVarCount savedNumLocalTemps
- | savedTemps savedTempVarCount savedNumLocalTemps
   jump blockArgs blockTemps blockTempsOffset block |
  savedTemps := tempVars.
  savedTempVarCount := tempVarCount.
  savedNumLocalTemps := numLocalTemps.
+ jump := blockSize + (startpc := pc).
- jump := blockSize + pc.
  numLocalTemps := BlockLocalTempCounter tempCountForBlockAt: pc - 4 in: method.
  blockTempsOffset := numArgs + blockCopiedValues size.
  (blockStartsToTempVars notNil "implies we were intialized with temp names."
  and: [blockStartsToTempVars includesKey: pc])
  ifTrue:
  [tempVars := blockStartsToTempVars at: pc]
  ifFalse:
  [blockArgs := (1 to: numArgs) collect:
  [:i| (constructor
  codeTemp: i - 1
  named: 't', (tempVarCount + i) printString)
   beBlockArg].
  blockTemps := (1 to: numLocalTemps) collect:
  [:i| constructor
  codeTemp: i + blockTempsOffset - 1
  named: 't', (tempVarCount + i + numArgs) printString].
  tempVars := blockArgs, blockCopiedValues, blockTemps].
  numLocalTemps timesRepeat:
  [self interpretNextInstructionFor: self.
  stack removeLast].
  tempVarCount := tempVarCount + numArgs + numLocalTemps.
  block := self blockTo: jump.
+ stack addLast: ((constructor
+ codeArguments: (tempVars copyFrom: 1 to: numArgs)
+ temps: (tempVars copyFrom: blockTempsOffset + 1 to: blockTempsOffset + numLocalTemps)
+ block: block)
+ pc: startpc;
+ yourself).
- stack addLast: (constructor
- codeArguments: (tempVars copyFrom: 1 to: numArgs)
- temps: (tempVars copyFrom: blockTempsOffset + 1 to: blockTempsOffset + numLocalTemps)
- block: block).
  tempVars := savedTemps.
  tempVarCount := savedTempVarCount.
  numLocalTemps := savedNumLocalTemps!