The Trunk: Compiler-eem.165.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.165.mcz

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

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

Name: Compiler-eem.165
Author: eem
Time: 17 August 2010, 2:29:01.49 pm
UUID: f895af78-0bd4-4e18-94ba-0c69837d298e
Ancestors: Compiler-eem.164

Stage two cleanup of the old parse node sizers & emitters

Also:
Streamline Compiler>>#compile:in:classified:notifying:ifFail: .  requestor: send is unnecessary.
Fix comment typo inScanner>>scanAllTokenPositionsInto:

=============== Diff against Compiler-eem.164 ===============

Item was changed:
  ParseNode subclass: #MessageNode
  instanceVariableNames: 'receiver selector precedence special arguments sizes equalNode caseErrorNode'
+ classVariableNames: 'MacroEmitters MacroPrinters MacroSelectors MacroSizers MacroTransformers StdTypers ThenFlag'
- classVariableNames: 'MacroEmitters MacroPrinters MacroSelectors MacroSizers MacroTransformers NewStyleMacroEmitters NewStyleMacroSizers StdTypers ThenFlag'
  poolDictionaries: ''
  category: 'Compiler-ParseNodes'!
 
  !MessageNode commentStamp: '<historical>' prior: 0!
  I represent a receiver and its message.
 
  Precedence codes:
  1 unary
  2 binary
  3 keyword
  4 other
 
  If special>0, I compile special code in-line instead of sending messages with literal methods as remotely copied contexts.!

Item was changed:
  ----- Method: MethodNode>>printWithClosureAnalysisOn: (in category 'printing') -----
  printWithClosureAnalysisOn: aStream
+ self ensureClosureAnalysisDone.
-
  precedence = 1
  ifTrue:
  [(self selector includesSubString: '()/')
  ifTrue: [aStream nextPutAll: (self selector copyUpTo: $)).
  arguments
  do: [:arg| aStream nextPutAll: arg key]
  separatedBy: [aStream nextPutAll: ', '].
  aStream nextPut: $)]
  ifFalse: [aStream nextPutAll: self selector]]  "no node for method selector"
  ifFalse:
  [self selector keywords with: arguments do:
  [:kwd :arg |
  aStream nextPutAll: kwd; space.
  arg printDefinitionForClosureAnalysisOn: aStream.
  aStream space]].
  comment == nil ifFalse:
  [aStream crtab: 1.
  self printCommentOn: aStream indent: 1].
  temporaries size > 0 ifTrue:
  [aStream crtab: 1; nextPut: $|.
  temporaries do: [:temp |
  aStream space.
  temp printDefinitionForClosureAnalysisOn: aStream].
  aStream space; nextPut: $|].
  primitive > 0 ifTrue:
  [(primitive between: 255 and: 519) ifFalse:  "Dont decompile quick prims  e.g, ^ self or ^instVar"
  [aStream crtab: 1.
  self printPrimitiveOn: aStream]].
  self printPropertiesOn: aStream.
  self printPragmasOn: aStream.
  aStream crtab: 1.
  block printWithClosureAnalysisStatementsOn: aStream indent: 0!

Item was changed:
  ParseNode subclass: #MethodNode
  instanceVariableNames: 'selectorOrFalse precedence arguments block primitive encoder temporaries properties sourceText locationCounter localsPool'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-ParseNodes'!
 
+ !MethodNode commentStamp: 'eem 8/15/2010 10:49' prior: 0!
+ I am the root of the parse tree..
+
+ Instance Variables
+ arguments: <SequenceableCollection>
+ block: <BlockNode>
+ encoder: <BytecodeEncoder>
+ localsPool: <IdentitySet>
+ locationCounter: <Integer>
+ precedence: <Integer>
+ primitive: <Integer>
+ properties: <AdditionalMethodState|nil>
+ selectorOrFalse: <Object>
+ sourceText: <String|Text>
+ temporaries: <SequenceableCollection>
+
+ arguments
+ - the collection of parsed or decompiled method arguments
+
+ block
+ - the BlockNode holding the method's statements
+
+ encoder
+ - the object that comprises the copiler's scope table, literal pool and back-end bytecode generator
+
+ localsPool
+ - a set used to determine the set of copied values for each block in the method
+
+ locationCounter
+ - an integer used to mark block scopes for the purposes of the closure transformation.  See BlockNode>>#analyseArguments:temporaries:rootNode:
+
+ precedence
+ - the precedence of the method's selector (see Symbol>>precedence)
+
+ primitive
+ - if non-zero this is the integer code of the method's primitive
+
+ properties
+ - the object used to accumulate method properties (a.k.a. pragmas)
+
+ selectorOrFalse
+ - the method's selector or false if this is a doit
+
+ sourceText
+ - the source test from which the method was compiled
+
+ temporaries
+ - the collection of parsed or decompiled method temporaries
+ !
- !MethodNode commentStamp: '<historical>' prior: 0!
- I am the root of the parse tree.!

Item was changed:
  ----- Method: MessageNode>>emitCodeForEffect:encoder: (in category 'code generation') -----
  emitCodeForEffect: stack encoder: encoder
  "For #ifTrue:ifFalse: and #whileTrue: / #whileFalse: style messages, the pc is set to the jump instruction, so that mustBeBoolean exceptions can be shown correctly."
  special > 0
  ifTrue:
  [pc := 0.
+ self perform: (MacroEmitters at: special) with: stack with: encoder with: false]
- self perform: (NewStyleMacroEmitters at: special) with: stack with: encoder with: false]
  ifFalse:
  [super emitCodeForEffect: stack encoder: encoder]!

Item was changed:
  ParseNodeVisitor subclass: #VariableScopeFinder
  instanceVariableNames: 'theVariable'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Support'!
 
+ !VariableScopeFinder commentStamp: 'eem 8/14/2010 19:45' prior: 0!
+ A VariableScopeFinder is used to find the minimum enclosing scope of a variable in a method.  This is used when auto-declaring temporaries to find the smallest enclosing block in which to declare the temp.
- !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 changed:
  ----- Method: DecompilerConstructorForClosures>>codeMethod:block:tempVars:primitive:class: (in category 'constructor') -----
  codeMethod: selector block: block tempVars: vars primitive: primitive class: class
 
  | blockNode selectorNode visibleTemps invisibleTemps arguments temporaries |
  selectorNode := self codeSelector: selector code: nil.
  tempVars := vars.
  visibleTemps := OrderedCollection new.
  invisibleTemps := OrderedCollection new.
  tempVars do: [:t|
    ((t isIndirectTempVector or: [t scope >= 0])
  ifTrue: [visibleTemps]
  ifFalse: [invisibleTemps]) addLast: t].
  arguments := visibleTemps copyFrom: 1 to: nArgs.
  temporaries := visibleTemps copyFrom: nArgs + 1 to: visibleTemps size.
  block
  arguments: arguments;
  temporaries: temporaries.
+ blockNode := MethodNode new
- blockNode := BytecodeAgnosticMethodNode new
  selector: selectorNode
  arguments: arguments
  precedence: selector precedence
  temporaries: temporaries
  block: block
  encoder: (EncoderForV3PlusClosures new initScopeAndLiteralTables
  temps: visibleTemps, invisibleTemps
  literals: literalValues
  class: class)
  primitive: primitive
  properties: method properties copy.
  blockNode properties method: blockNode.
  ^blockNode!

Item was changed:
  ----- Method: MethodNode>>properties (in category 'code generation') -----
  properties
+ ^properties!
- ^ properties!

Item was changed:
  ----- Method: MethodNode>>generate: (in category 'code generation') -----
  generate: trailer
+ "The receiver is the root of a parse tree. Answer a CompiledMethod.
+ The argument, trailer, is arbitrary but is typically either the reference
+ to the source code that is stored with every CompiledMethod, or an
+ encoding of the method's temporary names."
- "The receiver is the root of a parse tree. Answer a CompiledMethod. The
- argument, trailer, is the references to the source code that is stored with
- every CompiledMethod."
 
+ | primErrNode blkSize nLits literals stack method |
+ self generate: trailer ifQuick:
+ [:m |
+  m literalAt: 2 put: encoder associationForClass;
+ properties: properties.
+ ^m].
- | literals blkSize method nArgs nLits primErrNode stack strm |
- self generate: trailer ifQuick:
- [:m |
- literals := encoder allLiterals.
- (nLits := literals size) > 255 ifTrue:
- [^self error: 'Too many literals referenced'].
- 1 to: nLits do: [:lit | m literalAt: lit put: (literals at: lit)].
- m properties: properties.
- ^m].
  primErrNode := self primitiveErrorVariableName ifNotNil:
  [encoder fixTemp: self primitiveErrorVariableName].
+ encoder supportsClosureOpcodes ifTrue:
+ [self ensureClosureAnalysisDone.
+ encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"].
+ blkSize := (block sizeCodeForEvaluatedValue: encoder)
+ + (primErrNode
+ ifNil: [0]
+ ifNotNil: [primErrNode sizeCodeForStore: encoder "The VM relies on storeIntoTemp: (129)"]).
+ method := CompiledMethod
- nArgs := arguments size.
- blkSize := (block sizeForEvaluatedValue: encoder)
- + (primErrNode ifNil: [0] ifNotNil: [2 "We force store-long (129)"]).
- (nLits := (literals := encoder allLiterals) size) > 255 ifTrue:
- [^self error: 'Too many literals referenced'].
- method := CompiledMethod "Dummy to allocate right size"
  newBytes: blkSize
  trailerBytes: trailer
+ nArgs: arguments size
+ nTemps: (encoder supportsClosureOpcodes
+ ifTrue: [| locals |
+ locals := arguments,
+  temporaries,
+  (primErrNode
+ ifNil: [#()]
+ ifNotNil: [{primErrNode}]).
+ encoder
+ noteBlockExtent: block blockExtent
+ hasLocals: locals.
+ locals size]
+ ifFalse: [encoder maxTemp])
- nArgs: nArgs
- nTemps: encoder maxTemp
  nStack: 0
+ nLits: (nLits := (literals := encoder allLiterals) size)
- nLits: nLits
  primitive: primitive.
+ nLits > 255 ifTrue:
+ [^self error: 'Too many literals referenced'].
+ 1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
+ encoder streamToMethod: method.
- strm := ReadWriteStream with: method.
- strm position: method initialPC - 1.
  stack := ParseStack new init.
+ primErrNode ifNotNil: [primErrNode emitCodeForStore: stack encoder: encoder].
+ stack position: method numTemps.
+ block emitCodeForEvaluatedValue: stack encoder: encoder.
+ stack position ~= (method numTemps + 1) ifTrue:
- primErrNode ifNotNil: [primErrNode emitStore: stack on: strm].
- block emitForEvaluatedValue: stack on: strm.
- stack position ~= 1 ifTrue:
  [^self error: 'Compiler stack discrepancy'].
+ encoder methodStreamPosition ~= (method size - trailer size) ifTrue:
- strm position ~= (method size - trailer size) ifTrue:
  [^self error: 'Compiler code size discrepancy'].
+ method needsFrameSize: stack size - method numTemps.
- method needsFrameSize: stack size.
- 1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
  method properties: properties.
  ^method!

Item was changed:
  ----- Method: MessageNode>>sizeCodeForEffect: (in category 'code generation') -----
  sizeCodeForEffect: encoder
 
  special > 0
+ ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: false].
- ifTrue: [^self perform: (NewStyleMacroSizers at: special) with: encoder with: false].
  ^super sizeCodeForEffect: encoder!

Item was changed:
  ----- Method: Compiler>>compile:in:classified:notifying:ifFail: (in category 'public access') -----
  compile: textOrStream in: aClass classified: aCategory notifying: aRequestor ifFail: failBlock
  "Answer a MethodNode for the argument, textOrStream. If the
  MethodNode can not be created, notify the argument, aRequestor; if
  aRequestor is nil, evaluate failBlock instead. The MethodNode is the root
  of a parse tree. It can be told to generate a CompiledMethod to be
  installed in the method dictionary of the argument, aClass."
+
-
- | methodNode |
  self from: textOrStream
  class: aClass
  classified: aCategory
  context: nil
  notifying: aRequestor.
+ ^self
+ translate: sourceStream
+ noPattern: false
+ ifFail: failBlock
- methodNode := self translate: sourceStream noPattern: false ifFail: failBlock.
- methodNode encoder requestor: requestor.
- ^methodNode.
  !

Item was changed:
  ----- Method: MessageNode class>>initialize (in category 'class initialization') -----
  initialize "MessageNode initialize"
  MacroSelectors :=
  #( ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
  and: or:
  whileFalse: whileTrue: whileFalse whileTrue
  to:do: to:by:do:
  caseOf: caseOf:otherwise:
  ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:).
  MacroTransformers :=
  #( transformIfTrue: transformIfFalse: transformIfTrueIfFalse: transformIfFalseIfTrue:
  transformAnd: transformOr:
  transformWhile: transformWhile: transformWhile: transformWhile:
  transformToDo: transformToDo:
  transformCase: transformCase:
  transformIfNil: transformIfNil:  transformIfNilIfNotNil: transformIfNotNilIfNil:).
+ MacroEmitters :=
- MacroEmitters := NewStyleMacroEmitters :=
  #( emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:
  emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:
  emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:
  emitCodeForWhile:encoder:value: emitCodeForWhile:encoder:value:
  emitCodeForWhile:encoder:value: emitCodeForWhile:encoder:value:
  emitCodeForToDo:encoder:value: emitCodeForToDo:encoder:value:
  emitCodeForCase:encoder:value: emitCodeForCase:encoder:value:
  emitCodeForIfNil:encoder:value: emitCodeForIfNil:encoder:value:
  emitCodeForIf:encoder:value: emitCodeForIf:encoder:value:).
+ MacroSizers :=
- MacroSizers := NewStyleMacroSizers :=
  #( sizeCodeForIf:value: sizeCodeForIf:value: sizeCodeForIf:value: sizeCodeForIf:value:
  sizeCodeForIf:value: sizeCodeForIf:value:
  sizeCodeForWhile:value: sizeCodeForWhile:value: sizeCodeForWhile:value: sizeCodeForWhile:value:
  sizeCodeForToDo:value: sizeCodeForToDo:value:
  sizeCodeForCase:value: sizeCodeForCase:value:
  sizeCodeForIfNil:value: sizeCodeForIfNil:value: sizeCodeForIf:value: sizeCodeForIf:value:).
  MacroPrinters :=
  #( printIfOn:indent: printIfOn:indent: printIfOn:indent: printIfOn:indent:
  printIfOn:indent: printIfOn:indent:
  printWhileOn:indent: printWhileOn:indent: printWhileOn:indent: printWhileOn:indent:
  printToDoOn:indent: printToDoOn:indent:
  printCaseOn:indent: printCaseOn:indent:
  printIfNil:indent: printIfNil:indent: printIfNilNotNil:indent: printIfNilNotNil:indent:)!

Item was changed:
  ----- Method: Scanner>>scanAllTokenPositionsInto: (in category 'expression types') -----
  scanAllTokenPositionsInto: aBlock
  "Evaluate aBlock with the start and end positions of all separate non-white-space tokens, including comments."
 
  | lastMark |
  lastMark := 1.
  [currentComment notNil ifTrue:
  [currentComment do:
  [:cmnt| | idx |
  idx := source originalContents indexOfSubCollection: cmnt startingAt: lastMark.
  (idx > 0 and: [idx < mark]) ifTrue:
  [aBlock value: idx - 1 value: (lastMark := idx + cmnt size)]].
  currentComment := nil].
  mark notNil ifTrue:
  [(token == #-
   and: [(self typeTableAt: hereChar) = #xDigit]) ifTrue:
  [| savedMark |
  savedMark := mark.
  self scanToken.
  token := token negated.
  mark := savedMark].
  "Compensate for the fact that the parser uses two character lookahead.  Normally we must
+  remove the extra two characters.  But this mustn't happen for the last token at the end of stream."
-  remove the extra two chaacters.  But this mustn't happen for the last token at the end of stream."
  aBlock
  value: mark
  value: (source atEnd
  ifTrue: [tokenType := #doIt. "to cause an immediate ^self" source position]
  ifFalse: [source position - 2])].
  (tokenType = #rightParenthesis
   or: [tokenType == #doIt]) ifTrue:
  [^self].
  tokenType = #leftParenthesis
  ifTrue:
  [self scanToken; scanAllTokenPositionsInto: aBlock]
  ifFalse:
  [(tokenType = #word or: [tokenType = #keyword or: [tokenType = #colon]])
  ifTrue:
  [self scanLitWord.
  token = #true ifTrue: [token := true].
  token = #false ifTrue: [token := false].
  token = #nil ifTrue: [token := nil]]
  ifFalse:
  [(token == #-
   and: [(self typeTableAt: hereChar) = #xDigit])
  ifTrue:
  [self scanToken.
  token := token negated]]].
  self scanToken.
  true] whileTrue!

Item was changed:
  ----- Method: MessageNode>>sizeCodeForValue: (in category 'code generation') -----
  sizeCodeForValue: encoder
  | total |
  special > 0
+ ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: true].
- ifTrue: [^self perform: (NewStyleMacroSizers 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!

Item was changed:
  ----- Method: MessageNode>>emitCodeForValue:encoder: (in category 'code generation') -----
  emitCodeForValue: stack encoder: encoder
  "For #ifTrue:ifFalse: and #whileTrue: / #whileFalse: style messages, the pc is set to the jump instruction, so that mustBeBoolean exceptions can be shown correctly."
  special > 0
  ifTrue:
  [pc := 0.
+ self perform: (MacroEmitters at: special) with: stack with: encoder with: true]
- self perform: (NewStyleMacroEmitters at: special) with: stack with: encoder with: true]
  ifFalse:
  [receiver ~~ nil ifTrue: [receiver emitCodeForValue: stack encoder: encoder].
  arguments do: [:argument | argument emitCodeForValue: stack encoder: encoder].
  pc := encoder methodStreamPosition + 1. "debug pc is first byte of the send, i.e. the next byte".
  selector
  emitCode: stack
  args: arguments size
  encoder: encoder
  super: receiver == NodeSuper]!