The Inbox: Compiler-eem.158.mcz

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

The Inbox: Compiler-eem.158.mcz

commits-2
A new version of Compiler was added to project The Inbox:
http://source.squeak.org/inbox/Compiler-eem.158.mcz

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

Name: Compiler-eem.158
Author: eem
Time: 14 August 2010, 8:56:07.496 pm
UUID: b4bd7630-a3ba-4a84-885a-023af67b5e1e
Ancestors: Compiler-eem.157

Declare temps at the minimum enclosing block scope.  Requires
deferring temp declarations until after the parse has completed.
So introduces an UndeclaredVariableNode type to stand in until
parse completes.  VariableScopeFinder visitor finds scopes.

Fix Parser>>#parse:class:category:noPattern:context:notifying:ifFail:'s
selection of the stream after ReparseAfterSourceEditing.  It must
grab the selectionInterval from the requestor's string, not the entire
string.

Resolve the ambiguous time stamp (almost certainly my fault) in
Compiler>>#from:class:classified:context:notifying:  between our
rep and trunk's rep by neatening method.

Submitting to inbox because (at least in trunk) this is still a little green.
Try selecting the first doit beginning with 1 to: 1 do: in the following
and delaring the three unused temps.  When the parse after declaration
completes the compiler will state that aTemp is unused and offer to
delete it.  But the selection is wrong (somewhere after cTemp's decl)
and if one says "yes, go delete" it the compiler syntax errors.
=================8<===============
        | x y |
        [:a :b | x := a. y := b. x+y] decompile

        | x y |
        [:a :b | x := a. y := b. x+y] method decompileWithTemps

(CompiledMethod>>#decompileWithTemps) decompileWithTemps

1 to: 1 do:
                [:i|
                true ifTrue: [aTemp := i] ifFalse: [aTemp := i].
                true ifTrue: [bTemp := i] ifFalse: [bTemp := i].
                1 to: 1 do:
                        [:j|
                        true ifTrue: [cTemp := i] ifFalse: [cTemp := i]]].
        bTemp
       

(1 to: 1 do:
                [:i|
                true ifTrue: [aTemp := i] ifFalse: [aTemp := i].
                true ifTrue: [bTemp := i] ifFalse: [bTemp := i].
                1 to: 1 do:
                        [:j|
                        true ifTrue: [cTemp := i] ifFalse: [cTemp := i]]].
        bTemp)

=============== Diff against Compiler-eem.157 ===============

Item was added:
+ VariableNode subclass: #UndeclaredVariableNode
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Compiler-ParseNodes'!

Item was changed:
  ----- Method: Parser>>temporaryBlockVariablesFor: (in category 'expression types') -----
  temporaryBlockVariablesFor: aBlockNode
  "Scan and answer temporary block variables."
 
  | variables |
  (self match: #verticalBar) ifFalse:
  "There are't any temporary variables."
+ [aBlockNode tempsMark: prevMark + requestorOffset.
+ ^#()].
- [^#()].
 
  variables := OrderedCollection new.
  [hereType == #word] whileTrue:
  [variables addLast: (encoder bindBlockTemp: self advance within: aBlockNode)].
+ (self match: #verticalBar) ifFalse:
+ [^self expected: 'Vertical bar'].
+ aBlockNode tempsMark: prevMark + requestorOffset.
+ ^variables!
- ^(self match: #verticalBar)
- ifTrue: [variables]
- ifFalse: [self expected: 'Vertical bar']!

Item was changed:
  ----- Method: Parser>>temporariesIn: (in category 'expression types') -----
  temporariesIn: methodSelector
  " [ '|' (variable)* '|' ]"
  | vars theActualText |
  (self match: #verticalBar) ifFalse:
  ["no temps"
+ doitFlag ifTrue:
+ [tempsMark := self interactive
+ ifTrue: [requestor selectionInterval first]
+ ifFalse: [1].
- doitFlag ifTrue: [self interactive
- ifFalse: [tempsMark := 1]
- ifTrue: [tempsMark := requestor selectionInterval first].
  ^ #()].
- tempsMark := (prevEnd ifNil: [0]) + 1.
  tempsMark := hereMark "formerly --> prevMark + prevToken".
-
  tempsMark > 0 ifTrue:
  [theActualText := source contents.
  [tempsMark < theActualText size and: [(theActualText at: tempsMark) isSeparator]]
  whileTrue: [tempsMark := tempsMark + 1]].
  ^ #()].
  vars := OrderedCollection new.
  [hereType == #word]
  whileTrue: [vars addLast: (encoder bindTemp: self advance in: methodSelector)].
  (self match: #verticalBar) ifTrue:
  [tempsMark := prevMark.
  ^ vars].
  ^ self expected: 'Vertical bar'!

Item was added:
+ ----- Method: VariableScopeFinder>>visitUndeclaredVariableNode: (in category 'visiting') -----
+ visitUndeclaredVariableNode: aVariableNode
+ ^theVariable name = aVariableNode name ifTrue: [theVariable]!

Item was added:
+ ----- Method: ParseNodeVisitor>>visitUndeclaredVariableNode: (in category 'visiting') -----
+ visitUndeclaredVariableNode: aVariableNode!

Item was added:
+ ----- Method: VariableScopeFinder>>visitFieldNode: (in category 'visiting') -----
+ visitFieldNode: aNode
+ ^nil!

Item was added:
+ ----- Method: BlockNode>>tempsMark: (in category 'accessing') -----
+ tempsMark: anInteger
+ tempsMark := anInteger!

Item was added:
+ ----- Method: Parser>>pasteTempAtMethodLevel: (in category 'error correction') -----
+ pasteTempAtMethodLevel: name
+ | insertion delta theTextString characterBeforeMark |
+
+ theTextString := requestor text string.
+ characterBeforeMark := theTextString at: tempsMark-1 ifAbsent: [$ ].
+ (theTextString at: tempsMark) = $| ifTrue: [
+   "Paste it before the second vertical bar"
+ insertion := name, ' '.
+ characterBeforeMark isSeparator ifFalse: [ insertion := ' ', insertion].
+ delta := 0.
+ ] ifFalse: [
+ "No bars - insert some with CR, tab"
+ insertion := '| ' , name , ' |',String cr.
+ delta := 2. "the bar and CR"
+ characterBeforeMark = Character tab ifTrue: [
+ insertion := insertion , String tab.
+ delta := delta + 1. "the tab"
+ ].
+ ].
+ tempsMark := tempsMark +
+ (self substituteWord: insertion
+ wordInterval: (tempsMark to: tempsMark-1)
+ offset: 0) - delta!

Item was added:
+ ----- Method: VariableScopeFinder>>visitVariableNode: (in category 'visiting') -----
+ visitVariableNode: aVariableNode
+ ^nil!

Item was added:
+ ----- Method: VariableScopeFinder>>enclosingNodeFor:of: (in category 'private') -----
+ enclosingNodeFor: enumerator of: rootNode
+ "Answer the minimum enclosing root node for aVariabe or nil if none.
+ If the variable is accessed in more than one subnode then the rootNode is the
+ enclosing node, otherwise it is which ever single subnode node that includes it, if any.
+ enumerator applies its argument to all relevant subnodes of rootNode."
+ | enclosingNodeOrNil |
+ enclosingNodeOrNil := nil.
+ enumerator value:
+ [:subnode|
+ (subnode accept: self) ifNotNil:
+ [:enclosingNode|
+ enclosingNodeOrNil := enclosingNodeOrNil
+ ifNil: [enclosingNode]
+ ifNotNil: [rootNode]]].
+ ^enclosingNodeOrNil!

Item was added:
+ ----- Method: VariableScopeFinder>>visitNewArrayNode: (in category 'visiting') -----
+ visitNewArrayNode: aNode
+ ^nil!

Item was changed:
  ----- Method: Parser>>declareTempAndPaste: (in category 'error correction') -----
  declareTempAndPaste: name
+ "Defer declaring the temp until the parse has completed.  This allows
+ the parser to declare the temp in the minimum enclosing block instead
+ of always at method level.  See Parser>>declareUndeclaredTemps:"
+ ^encoder bindUndeclaredTemp: name!
- | insertion delta theTextString characterBeforeMark |
-
- theTextString := requestor text string.
- characterBeforeMark := theTextString at: tempsMark-1 ifAbsent: [$ ].
- (theTextString at: tempsMark) = $| ifTrue: [
-   "Paste it before the second vertical bar"
- insertion := name, ' '.
- characterBeforeMark isSeparator ifFalse: [ insertion := ' ', insertion].
- delta := 0.
- ] ifFalse: [
- "No bars - insert some with CR, tab"
- insertion := '| ' , name , ' |',String cr.
- delta := 2. "the bar and CR"
- characterBeforeMark = Character tab ifTrue: [
- insertion := insertion , String tab.
- delta := delta + 1. "the tab"
- ].
- ].
- tempsMark := tempsMark +
- (self substituteWord: insertion
- wordInterval: (tempsMark to: tempsMark-1)
- offset: 0) - delta.
- ^ encoder bindAndJuggle: name!

Item was added:
+ ----- Method: VariableScopeFinder>>visitLiteralNode: (in category 'visiting') -----
+ visitLiteralNode: aNode
+ ^nil!

Item was added:
+ ----- Method: Encoder>>newUndeclaredTemp: (in category 'temps') -----
+ newUndeclaredTemp: name
+ ^UndeclaredVariableNode new name: name!

Item was changed:
  ParseNode subclass: #BlockNode
+ instanceVariableNames: 'arguments statements returns nArgsNode size remoteCopyNode temporaries optimized optimizedMessageNode actualScopeIfOptimized blockExtent remoteTempNode copiedValues closureCreationNode startOfLastStatement tempsMark'
- instanceVariableNames: 'arguments statements returns nArgsNode size remoteCopyNode temporaries optimized optimizedMessageNode actualScopeIfOptimized blockExtent remoteTempNode copiedValues closureCreationNode startOfLastStatement'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-ParseNodes'!
 
  !BlockNode commentStamp: '<historical>' prior: 0!
  I represent a bracketed block with 0 or more arguments and 1 or more statements. If I am initialized with no statements, I create one. I have a flag to tell whether my last statement returns a value from the enclosing method. My last three fields remember data needed for code generation. I can emit for value in the usual way, in which case I create a literal method (actually a context remotely copied) to be evaluated by sending it value: at run time. Or I can emit code to be evaluated in line; this only happens at the top level of a method and in conditionals and while-loops, none of which have arguments.!

Item was added:
+ ----- Method: VariableScopeFinder>>visitRemoteTempVectorNode: (in category 'visiting') -----
+ visitRemoteTempVectorNode: aNode
+ ^nil!

Item was added:
+ ----- Method: UndeclaredVariableNode>>accept: (in category 'visiting') -----
+ accept: aVisitor
+ ^aVisitor visitUndeclaredVariableNode: self!

Item was added:
+ ----- Method: VariableScopeFinder>>visitLiteralVariableNode: (in category 'visiting') -----
+ visitLiteralVariableNode: aNode
+ ^nil!

Item was changed:
  ----- Method: Compiler>>from:class:classified:context:notifying: (in category 'public access') -----
  from: textOrStream class: aClass classified: aCategory context: aContext notifying: req
 
+ sourceStream := (textOrStream isKindOf: PositionableStream)
+ ifTrue: [textOrStream]
+ ifFalse: [ReadStream on: textOrStream asString].
+ class := aClass.
+ context := aContext.
+ requestor := req.
+ category := aCategory
- (textOrStream isKindOf: PositionableStream)
- ifTrue: [sourceStream  := textOrStream]
- ifFalse: [sourceStream  := ReadStream on: textOrStream asString].
- class  := aClass.
- context  := aContext.
- requestor  := req.
- category  := aCategory
  !

Item was changed:
  ----- Method: Parser>>method:context: (in category 'expression types') -----
  method: doit context: ctxt
  " pattern [ | temporaries ] block => MethodNode."
 
  | sap blk prim temps messageComment methodNode |
  sap := self pattern: doit inContext: ctxt.
  "sap={selector, arguments, precedence}"
  self properties selector: (sap at: 1).
  encoder selector: (sap at: 1).
  (sap at: 2) do: [:argNode | argNode beMethodArg].
  doit ifFalse: [self pragmaSequence].
  temps := self temporaries.
  messageComment := currentComment.
  currentComment := nil.
  doit ifFalse: [self pragmaSequence].
  prim := self pragmaPrimitives.
  self statements: #() innerBlock: doit.
  blk := parseNode.
  doit ifTrue: [blk returnLast]
  ifFalse: [blk returnSelfIfNoOther: encoder].
  hereType == #doIt ifFalse: [^self expected: 'Nothing more'].
- self interactive ifTrue: [self removeUnusedTemps].
  methodNode := self newMethodNode comment: messageComment.
+ methodNode
- ^methodNode
  selector: (sap at: 1)
  arguments: (sap at: 2)
  precedence: (sap at: 3)
  temporaries: temps
  block: blk
  encoder: encoder
  primitive: prim
+ properties: properties.
+ self interactive ifTrue:
+ [self declareUndeclaredTemps: methodNode.
+ self removeUnusedTemps].
+ ^methodNode!
- properties: properties!

Item was added:
+ ----- Method: VariableScopeFinder>>visitAssignmentNode: (in category 'visiting') -----
+ visitAssignmentNode: anAssignmentNode
+ "Answer the minimum enclosing node for aVariabe or nil if none.
+ If the variable is accessed in more than one subexpression then anAssignmentNode
+ is the enclosing node, otherwise it is which ever single node that includes it, if any."
+ ^self
+ enclosingNodeFor: [:aBlock|
+ aBlock
+ value: anAssignmentNode value;
+ value: anAssignmentNode variable]
+ of: anAssignmentNode!

Item was added:
+ ----- Method: VariableScopeFinder>>ofVariable: (in category 'initialize-release') -----
+ ofVariable: aVariableNode
+ theVariable := aVariableNode!

Item was added:
+ ----- Method: VariableScopeFinder>>visitMessageNode: (in category 'visiting') -----
+ visitMessageNode: aMessageNode
+ "Answer the minimum enclosing node for aVariabe or nil if none.
+ If the variable is accessed in more than one subexpression then aMessageNode is the
+ enclosing node, otherwise it is which ever single node that includes it, if any."
+ ^self
+ enclosingNodeFor: [:aBlock|
+ aBlock value: aMessageNode receiver.
+ aMessageNode argumentsInEvaluationOrder do: aBlock]
+ of: aMessageNode!

Item was added:
+ ----- Method: VariableScopeFinder>>visitInstanceVariableNode: (in category 'visiting') -----
+ visitInstanceVariableNode: aNode
+ ^nil!

Item was added:
+ ----- Method: UndeclaredVariableNode>>isUndeclared (in category 'testing') -----
+ isUndeclared
+ ^true!

Item was added:
+ ----- Method: VariableScopeFinder>>visitSelectorNode: (in category 'visiting') -----
+ visitSelectorNode: aNode
+ ^nil!

Item was added:
+ ----- Method: VariableScopeFinder>>visitFutureNode: (in category 'visiting') -----
+ visitFutureNode: aFutureNode
+ ^aFutureNode receiver accept: self!

Item was added:
+ ----- Method: VariableScopeFinder>>visitTempVariableNode: (in category 'visiting') -----
+ visitTempVariableNode: aNode
+ ^nil!

Item was added:
+ ----- Method: VariableScopeFinder>>visitCascadeNode: (in category 'visiting') -----
+ visitCascadeNode: aCascadeNode
+ "Answer the minimum enclosing node for aVariabe or nil if none.
+ If the variable is accessed in more than one subexpression then aMessageNode is the
+ enclosing node, otherwise it is which ever single node that includes it, if any."
+ ^self
+ enclosingNodeFor: [:aBlock|
+ aBlock value: aCascadeNode receiver.
+ aCascadeNode messages do:
+ [:each| aCascadeNode argumentsInEvaluationOrder do: aBlock]]
+ of: aCascadeNode!

Item was added:
+ ParseNodeVisitor subclass: #VariableScopeFinder
+ instanceVariableNames: 'theVariable'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Compiler-Support'!
+
+ !VariableScopeFinder commentStamp: 'eem 8/12/2010 16:17' prior: 0!
+ A VariableScopeFinder is used to find the minimum enclosing scope of a variable oin a method.  This is used when auto-declaring temporaries to find the smallest enclosing block in which to decare the temp.
+
+ Instance Variables
+ theVariable: <VariableNode>
+
+ theVariable
+ - the varable whose scope is to be determined
+ !

Item was added:
+ ----- Method: VariableScopeFinder>>visitCommentNode: (in category 'visiting') -----
+ visitCommentNode: aNode
+ ^nil!

Item was added:
+ ----- Method: BlockNode>>tempsMark (in category 'accessing') -----
+ tempsMark
+ ^tempsMark!

Item was added:
+ ----- Method: VariableScopeFinder>>visitBlockNode: (in category 'visiting') -----
+ visitBlockNode: aBlockNode
+ "Answer the minimum enclosing node for aVariabe or nil if none.
+ If the variable is accessed in more than one statement then aBlockNode is the
+ enclosing node, otherwise it is which ever single block node that includes it, if any."
+ ^(self enclosingNodeFor: [:aBlock| aBlockNode statements do: aBlock] of: aBlockNode) ifNotNil:
+ [:aNode|
+ aNode isBlockNode ifTrue: [aNode] ifFalse: [aBlockNode]]!

Item was added:
+ ----- Method: VariableScopeFinder>>visitBraceNode: (in category 'visiting') -----
+ visitBraceNode: aBraceNode
+ "Answer the minimum enclosing node for aVariabe or nil if none.
+ If the variable is accessed in more than one subexpression then aBraceNode
+ is the enclosing node, otherwise it is which ever single node that includes it, if any."
+ ^self
+ enclosingNodeFor: [:aBlock| aBraceNode elements do: aBlock]
+ of: aBraceNode!

Item was changed:
  ----- Method: Parser>>parse:class:category:noPattern:context:notifying:ifFail: (in category 'public access') -----
  parse: sourceStream class: class category: aCategory noPattern: noPattern context: ctxt notifying: req ifFail: aBlock
  "Answer a MethodNode for the argument, sourceStream, that is the root of
  a parse tree. Parsing is done with respect to the argument, class, to find
  instance, class, and pool variables; and with respect to the argument,
  ctxt, to find temporary variables. Errors in parsing are reported to the
  argument, req, if not nil; otherwise aBlock is evaluated. The argument
  noPattern is a Boolean that is true if the the sourceStream does not
  contain a method header (i.e., for DoIts)."
 
  | methNode repeatNeeded myStream s p |
  category := aCategory.
  myStream := sourceStream.
  [repeatNeeded := false.
  p := myStream position.
  s := myStream upToEnd.
  myStream position: p.
  self encoder init: class context: ctxt notifying: self.
  self init: myStream notifying: req failBlock: [^ aBlock value].
  doitFlag := noPattern.
  failBlock:= aBlock.
  [methNode := self
  method: noPattern
  context: ctxt]
  on: ReparseAfterSourceEditing
  do: [ :ex |
  repeatNeeded := true.
+ myStream := ReadStream
+ on: requestor text string
+ from: requestor selectionInterval first
+ to: requestor selectionInterval last].
- myStream := ReadStream on: requestor text string].
  repeatNeeded] whileTrue:
  [encoder := self encoder class new].
  methNode sourceText: s.
  ^methNode
  !

Item was changed:
  ----- Method: Parser>>substituteWord:wordInterval:offset: (in category 'error correction') -----
  substituteWord: correctWord wordInterval: spot offset: o
+ "Substitute the correctSelector into the (presumed interactive) receiver.
+ Update requestorOffset based on the delta size and answer the updated offset."
- "Substitute the correctSelector into the (presuamed interactive) receiver."
 
+ requestor correctFrom: spot first + o to: spot last + o with: correctWord.
- requestor correctFrom: (spot first + o)
- to: (spot last + o)
- with: correctWord.
-
  requestorOffset := requestorOffset + correctWord size - spot size.
+ ^o + correctWord size - spot size!
- ^ o + correctWord size - spot size!

Item was added:
+ ----- Method: VariableScopeFinder>>visitReturnNode: (in category 'visiting') -----
+ visitReturnNode: aReturnNode
+ ^aReturnNode expr accept: self!

Item was changed:
  ----- Method: Parser>>temporaries (in category 'expression types') -----
  temporaries
  " [ '|' (variable)* '|' ]"
  | vars theActualText |
  (self match: #verticalBar) ifFalse:
  ["no temps"
+ doitFlag ifTrue:
+ [tempsMark := self interactive
+ ifTrue: [requestor selectionInterval first]
+ ifFalse: [1].
- doitFlag ifTrue: [self interactive
- ifFalse: [tempsMark := 1]
- ifTrue: [tempsMark := requestor selectionInterval first].
  ^ #()].
- tempsMark := (prevEnd ifNil: [0]) + 1.
  tempsMark := hereMark "formerly --> prevMark + prevToken".
-
  tempsMark > 0 ifTrue:
  [theActualText := source contents.
  [tempsMark < theActualText size and: [(theActualText at: tempsMark) isSeparator]]
  whileTrue: [tempsMark := tempsMark + 1]].
  ^ #()].
  vars := OrderedCollection new.
  [hereType == #word]
  whileTrue: [vars addLast: (encoder bindTemp: self advance)].
  (self match: #verticalBar) ifTrue:
  [tempsMark := prevMark.
  ^ vars].
  ^ self expected: 'Vertical bar'
  !

Item was added:
+ ----- Method: Encoder>>undeclaredTemps (in category 'results') -----
+ undeclaredTemps
+ ^(scopeTable select: [:var | var isVariableNode and: [var isUndeclared]]) values!

Item was added:
+ ----- Method: VariableNode>>isUndeclared (in category 'testing') -----
+ isUndeclared
+ ^false!

Item was added:
+ ----- Method: Parser>>declareUndeclaredTemps: (in category 'error correction') -----
+ declareUndeclaredTemps: methodNode
+ "Declare any undeclared temps, declaring them at the smallest enclosing scope."
+
+ | undeclared userSelection blocksToVars |
+ (undeclared := encoder undeclaredTemps) isEmpty ifTrue:
+ [^self].
+ userSelection := requestor selectionInterval.
+ blocksToVars := IdentityDictionary new.
+ undeclared do:
+ [:var|
+ (blocksToVars
+ at: (methodNode accept: (VariableScopeFinder new ofVariable: var))
+ ifAbsentPut: [SortedCollection new]) add: var name].
+ (blocksToVars removeKey: methodNode block ifAbsent: []) ifNotNil:
+ [:rootVars|
+ rootVars do: [:varName| self pasteTempAtMethodLevel: varName]].
+ (blocksToVars keys sorted: [:a :b| a tempsMark < b tempsMark]) do:
+ [:block| | decl |
+ decl := (blocksToVars at: block) reduce: [:a :b| a, ' ', b].
+ block temporaries isEmpty
+ ifTrue:
+ [self substituteWord: ' | ', decl, ' |'
+ wordInterval: (block tempsMark + 1 to: block tempsMark)
+ offset: requestorOffset]
+ ifFalse:
+ [self substituteWord: decl, ' '
+ wordInterval: (block tempsMark to: block tempsMark - 1)
+ offset: requestorOffset]].
+ requestor selectInvisiblyFrom: userSelection first to: userSelection last + requestorOffset.
+ ReparseAfterSourceEditing signal!

Item was added:
+ ----- Method: Encoder>>bindUndeclaredTemp: (in category 'private') -----
+ bindUndeclaredTemp: name
+ ^scopeTable at: name put: (self newUndeclaredTemp: name)!

Item was added:
+ ----- Method: VariableScopeFinder>>visitMethodNode: (in category 'visiting') -----
+ visitMethodNode: aMethodNode
+ ^aMethodNode block accept: self!