The Trunk: Compiler-cwp.245.mcz

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

The Trunk: Compiler-cwp.245.mcz

commits-2
Colin Putney uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-cwp.245.mcz

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

Name: Compiler-cwp.245
Author: cwp
Time: 1 January 2013, 6:47:22.812 pm
UUID: ded24bcc-aeee-4129-94fa-2b2da294e964
Ancestors: Compiler-eem.243

Environments bootstrap - stage 1

=============== Diff against Compiler-eem.243 ===============

Item was added:
+ Object subclass: #CompilationCue
+ instanceVariableNames: 'source context receiver class environment category requestor'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Compiler-Kernel'!

Item was added:
+ ----- Method: CompilationCue class>>class: (in category 'instance creation') -----
+ class: aClass
+ ^ self
+ context: nil
+ class: aClass
+ requestor: nil!

Item was added:
+ ----- Method: CompilationCue class>>context:class:requestor: (in category 'instance creation') -----
+ context: aContext class: aClass requestor: anObject
+ ^ self
+ source: nil
+ context: aContext
+ receiver: nil
+ class: aClass
+ environment: (aClass ifNotNil: [aClass environment])
+ category: nil
+ requestor: anObject!

Item was added:
+ ----- Method: CompilationCue class>>source:class:environment:category:requestor: (in category 'instance creation') -----
+ source: aTextOrStream class: aClass environment: anEnvironment category: aString requestor: anObject
+ ^ self
+ source: aTextOrStream
+ context: nil
+ receiver: nil
+ class: aClass
+ environment: anEnvironment
+ category: aString
+ requestor: anObject!

Item was added:
+ ----- Method: CompilationCue class>>source:context:class:category:requestor: (in category 'instance creation') -----
+ source: aTextOrStream context: aContext class: aClass category: aString requestor: anObject
+ ^ self
+ source: aTextOrStream
+ context: aContext
+ receiver: (aContext ifNotNil: [aContext receiver])
+ class: aClass
+ environment: (aClass ifNotNil: [aClass environment])
+ category: aString
+ requestor: anObject!

Item was added:
+ ----- Method: CompilationCue class>>source:context:class:requestor: (in category 'instance creation') -----
+ source: aTextOrStream context: aContext class: aClass requestor: anObject
+ ^ self
+ source: aTextOrStream
+ context: aContext
+ class: aClass
+ category: nil
+ requestor: anObject!

Item was added:
+ ----- Method: CompilationCue class>>source:context:receiver:class:environment:category:requestor: (in category 'instance creation') -----
+ source: aTextOrStream context: aContext receiver: recObject class: aClass environment: anEnvironment category: aString requestor: reqObject
+ ^ self basicNew
+ initializeWithSource: aTextOrStream
+ context: aContext
+ receiver: recObject
+ class: aClass
+ environment: anEnvironment
+ category: aString
+ requestor: reqObject!

Item was added:
+ ----- Method: CompilationCue class>>source:environment: (in category 'instance creation') -----
+ source: aString environment: anEnvironment
+ ^ self
+ source: aString
+ context: nil
+ receiver: nil
+ class: UndefinedObject
+ environment: anEnvironment
+ category: nil
+ requestor: nil!

Item was added:
+ ----- Method: CompilationCue class>>source:requestor: (in category 'instance creation') -----
+ source: aTextOrStream requestor: anObject
+ ^ self
+ source: aTextOrStream
+ context: nil
+ class: nil
+ requestor: anObject!

Item was added:
+ ----- Method: CompilationCue>>bindingOf: (in category 'binding') -----
+ bindingOf: aSymbol
+ ^ class bindingOf: aSymbol environment: environment!

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

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

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

Item was added:
+ ----- Method: CompilationCue>>getClass (in category 'accessing') -----
+ getClass
+ ^ class!

Item was added:
+ ----- Method: CompilationCue>>initializeWithSource:context:receiver:class:environment:category:requestor: (in category 'initialization') -----
+ initializeWithSource: aTextOrString context: aContext receiver: recObject class: aClass environment: anEnvironment category: aString requestor: reqObject
+ self initialize.
+ source := aTextOrString isStream ifTrue: [aTextOrString contents] ifFalse: [aTextOrString].
+ context := aContext.
+ receiver := recObject.
+ class := aClass.
+ environment := anEnvironment.
+ category := aString.
+ requestor := reqObject!

Item was added:
+ ----- Method: CompilationCue>>literalScannedAs:notifying: (in category 'binding') -----
+ literalScannedAs: anObject notifying: anEncoder
+ ^ class literalScannedAs: anObject environment: environment notifying: anEncoder!

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

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

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

Item was added:
+ ----- Method: CompilationCue>>sourceStream (in category 'accessing') -----
+ sourceStream
+ ^ source readStream!

Item was changed:
  Object subclass: #Compiler
+ instanceVariableNames: 'sourceStream requestor class category context parser cue'
- instanceVariableNames: 'sourceStream requestor class category context parser'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Kernel'!
 
+ !Compiler commentStamp: 'cwp 12/26/2012 23:17' prior: 0!
- !Compiler commentStamp: '<historical>' prior: 0!
  The compiler accepts Smalltalk source code and compiles it with respect to a given class. The user of the compiler supplies a context so that temporary variables are accessible during compilation. If there is an error, a requestor (usually a kind of StringHolderController) is sent the message notify:at:in: so that the error message can be displayed. If there is no error, then the result of compilation is a MethodNode, which is the root of a parse tree whose nodes are kinds of ParseNodes. The parse tree can be sent messages to (1) generate code for a CompiledMethod (this is done for compiling methods or evaluating expressions); (2) pretty-print the code (for formatting); or (3) produce a map from object code back to source code (used by debugger program-counter selection). See also Parser, Encoder, ParseNode.!

Item was added:
+ ----- Method: Compiler class>>evaluate:environment: (in category 'evaluating') -----
+ evaluate: aString environment: anEnvironment
+ ^ self
+ evaluate: aString
+ environment: anEnvironment
+ logged: false!

Item was added:
+ ----- Method: Compiler class>>evaluate:environment:logged: (in category 'evaluating') -----
+ evaluate: aString environment: anEnvironment logged: aBoolean
+ | cue |
+ cue := CompilationCue
+ source: aString
+ environment: anEnvironment.
+
+ ^ self new
+ evaluate: aString
+ cue: cue
+ ifFail: [^ nil]
+ logged: aBoolean!

Item was added:
+ ----- Method: Compiler>>compile:ifFail: (in category 'public access') -----
+ compile: aCue ifFail: failBlock
+ "Answer a MethodNode. If the MethodNode can not be created, notify
+ the requestor in the contxt. If the requestor 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 class specified by the context."
+
+ self setCue: aCue.
+ self source: cue source.
+ ^self
+ translate: sourceStream
+ noPattern: false
+ ifFail: failBlock!

Item was added:
+ ----- Method: Compiler>>evaluate:cue:ifFail:logged: (in category 'public access') -----
+ evaluate: textOrStream cue: aCue ifFail: failBlock logged: logFlag
+ "Compiles the sourceStream into a parse tree, then generates code into
+ a method. Finally, the compiled method is invoked from here via withArgs:executeMethod:, hence the system no longer creates Doit method
+ litter on errors."
+
+ | methodNode method value toLog itsSelection itsSelectionString |
+ self setCue: aCue.
+ self source: textOrStream.
+ methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value].
+
+ method := self interactive
+ ifTrue: [methodNode generateWithTempNames]
+ ifFalse: [methodNode generate].
+
+ value := cue receiver
+ withArgs: (cue context ifNil: [#()] ifNotNil: [{cue context}])
+ executeMethod: method.
+
+ logFlag ifTrue:
+ [toLog := ((cue requestor respondsTo: #selection)  
+ and:[(itsSelection := cue requestor selection) notNil
+ and:[(itsSelectionString := itsSelection asString) isEmptyOrNil not]])
+ ifTrue:[itsSelectionString]
+ ifFalse:[sourceStream contents].
+ SystemChangeNotifier uniqueInstance evaluated: toLog context: cue context].
+ ^ value
+ !

Item was added:
+ ----- Method: Compiler>>setCue: (in category 'private') -----
+ setCue: aCue
+ cue := aCue.
+
+ "Set legacy instance variables for methods that don't use cue yet."
+ requestor := cue requestor.
+ class := cue getClass.
+ category := cue category.
+ context := cue context.!

Item was added:
+ ----- Method: Compiler>>source: (in category 'private') -----
+ source: textOrStream
+ sourceStream := (textOrStream isKindOf: PositionableStream)
+ ifTrue: [ textOrStream ]
+ ifFalse: [ ReadStream on: textOrStream asString ]!

Item was added:
+ ----- Method: Dictionary>>bindingOf:ifAbsent: (in category '*Compiler') -----
+ bindingOf: varName ifAbsent: aBlock
+
+ ^self associationAt: varName ifAbsent: aBlock!

Item was changed:
  ParseNode subclass: #Encoder
+ instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals optimizedSelectors cue'
- instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals optimizedSelectors'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Kernel'!
 
+ !Encoder commentStamp: 'cwp 12/26/2012 23:29' prior: 0!
- !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 added:
+ ----- Method: Encoder>>init:notifying: (in category 'initialize-release') -----
+ init: aCue notifying: anObject
+ "The use of the variable requestor is a bit confusing here. This is
+ *not* the original requestor, which is available through the cue.
+ It's the Parser instance that is using the encoder."
+
+ self setCue: aCue.
+ requestor := anObject.
+ nTemps := 0.
+ supered := false.
+ self initScopeAndLiteralTables.
+ cue getClass variablesAndOffsetsDo:
+ [:variable "<String|CFieldDefinition>" :offset "<Integer|nil>" |
+ offset isNil
+ ifTrue: [scopeTable at: variable name put: (FieldNode new fieldDefinition: variable)]
+ ifFalse: [scopeTable
+ at: variable
+ put: (offset >= 0
+ ifTrue: [InstanceVariableNode new
+ name: variable index: offset]
+ ifFalse: [MaybeContextInstanceVariableNode new
+ name: variable index: offset negated])]].
+ cue context ~~ nil ifTrue:
+ [| homeNode |
+ homeNode := self bindTemp: self doItInContextName.
+ "0th temp = aContext passed as arg"
+ cue context tempNames withIndexDo:
+ [:variable :index|
+ scopeTable
+ at: variable
+ put: (MessageAsTempNode new
+ receiver: homeNode
+ selector: #namedTempAt:
+ arguments: (Array with: (self encodeLiteral: index))
+ precedence: 3
+ from: self)]].
+ sourceRanges := Dictionary new: 32.
+ globalSourceRanges := OrderedCollection new: 32
+ !

Item was added:
+ ----- Method: Encoder>>setCue: (in category 'private') -----
+ setCue: aCue
+ cue := aCue.
+
+ "Also set legacy instance variables for methods that
+ don't use cue yet"
+ class := cue getClass.!

Item was changed:
  Scanner subclass: #Parser
+ instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category queriedUnusedTemporaries cue'
- instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category queriedUnusedTemporaries'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Kernel'!
 
+ !Parser commentStamp: 'cwp 12/26/2012 23:34' prior: 0!
- !Parser commentStamp: '<historical>' prior: 0!
  I parse Smalltalk syntax and create a MethodNode that is the root of the parse tree. I look one token ahead.!

Item was added:
+ ----- Method: Parser>>init:cue:failBlock: (in category 'private') -----
+ init: sourceStream cue: aCue failBlock: aBlock
+
+ self setCue: aCue.
+ failBlock := aBlock.
+ requestorOffset := 0.
+ super scan: sourceStream.
+ prevMark := hereMark := mark.
+ self advance
+ !

Item was added:
+ ----- Method: Parser>>parse:cue:noPattern:ifFail: (in category 'public access') -----
+ parse: sourceStream cue: aCue noPattern: noPattern ifFail: aBlock
+ "Answer a MethodNode for the argument, sourceStream, that is the root of
+ a parse tree. Parsing is done with respect to the CompilationCue to
+ resolve variables. Errors in parsing are reported to the cue's requestor;
+ 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 subSelection |
+ myStream := sourceStream.
+ [repeatNeeded := false.
+ p := myStream position.
+ s := myStream upToEnd.
+ myStream position: p.
+ subSelection := aCue requestor notNil and: [aCue requestor selectionInterval = (p + 1 to: p + s size)].
+ self encoder init: aCue notifying: self.
+ self init: myStream cue: aCue failBlock: [^ aBlock value].
+ doitFlag := noPattern.
+ failBlock:= aBlock.
+ [methNode := self method: noPattern context: cue context]
+ on: ReparseAfterSourceEditing
+ do: [ :ex |
+ repeatNeeded := true.
+ myStream := subSelection
+ ifTrue:
+ [ReadStream
+ on: cue requestor text string
+ from: cue requestor selectionInterval first
+ to: cue requestor selectionInterval last]
+ ifFalse:
+ [ReadStream on: cue requestor text string]].
+ repeatNeeded] whileTrue:
+ [encoder := self encoder class new].
+ methNode sourceText: s.
+ ^methNode
+ !

Item was added:
+ ----- Method: Parser>>setCue: (in category 'private') -----
+ setCue: aCue
+ cue := aCue.
+
+ "Also set legacy variables for methods that don't use cue yet."
+ requestor := cue requestor.
+ category := cue category.!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-cwp.245.mcz

Chris Muller-3
Ha, you've just been bustin' at the seams to release this haven't you?   :)

On Tue, Jan 1, 2013 at 5:48 PM,  <[hidden email]> wrote:

> Colin Putney uploaded a new version of Compiler to project The Trunk:
> http://source.squeak.org/trunk/Compiler-cwp.245.mcz
>
> ==================== Summary ====================
>
> Name: Compiler-cwp.245
> Author: cwp
> Time: 1 January 2013, 6:47:22.812 pm
> UUID: ded24bcc-aeee-4129-94fa-2b2da294e964
> Ancestors: Compiler-eem.243
>
> Environments bootstrap - stage 1
>
> =============== Diff against Compiler-eem.243 ===============
>
> Item was added:
> + Object subclass: #CompilationCue
> +       instanceVariableNames: 'source context receiver class environment category requestor'
> +       classVariableNames: ''
> +       poolDictionaries: ''
> +       category: 'Compiler-Kernel'!
>
> Item was added:
> + ----- Method: CompilationCue class>>class: (in category 'instance creation') -----
> + class: aClass
> +       ^ self
> +               context: nil
> +               class: aClass
> +               requestor: nil!
>
> Item was added:
> + ----- Method: CompilationCue class>>context:class:requestor: (in category 'instance creation') -----
> + context: aContext class: aClass requestor: anObject
> +       ^ self
> +               source: nil
> +               context: aContext
> +               receiver: nil
> +               class: aClass
> +               environment: (aClass ifNotNil: [aClass environment])
> +               category: nil
> +               requestor: anObject!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:class:environment:category:requestor: (in category 'instance creation') -----
> + source: aTextOrStream class: aClass environment: anEnvironment category: aString requestor: anObject
> +       ^ self
> +               source: aTextOrStream
> +               context: nil
> +               receiver: nil
> +               class: aClass
> +               environment: anEnvironment
> +               category: aString
> +               requestor: anObject!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:context:class:category:requestor: (in category 'instance creation') -----
> + source: aTextOrStream context: aContext class: aClass category: aString requestor: anObject
> +       ^ self
> +               source: aTextOrStream
> +               context: aContext
> +               receiver: (aContext ifNotNil: [aContext receiver])
> +               class: aClass
> +               environment: (aClass ifNotNil: [aClass environment])
> +               category: aString
> +               requestor: anObject!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:context:class:requestor: (in category 'instance creation') -----
> + source: aTextOrStream context: aContext class: aClass requestor: anObject
> +       ^ self
> +               source: aTextOrStream
> +               context: aContext
> +               class: aClass
> +               category: nil
> +               requestor: anObject!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:context:receiver:class:environment:category:requestor: (in category 'instance creation') -----
> + source: aTextOrStream context: aContext receiver: recObject class: aClass environment: anEnvironment category: aString requestor: reqObject
> +       ^ self basicNew
> +               initializeWithSource: aTextOrStream
> +               context: aContext
> +               receiver: recObject
> +               class: aClass
> +               environment: anEnvironment
> +               category: aString
> +               requestor: reqObject!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:environment: (in category 'instance creation') -----
> + source: aString environment: anEnvironment
> +       ^ self
> +               source: aString
> +               context: nil
> +               receiver: nil
> +               class: UndefinedObject
> +               environment: anEnvironment
> +               category: nil
> +               requestor: nil!
>
> Item was added:
> + ----- Method: CompilationCue class>>source:requestor: (in category 'instance creation') -----
> + source: aTextOrStream requestor: anObject
> +       ^ self
> +               source: aTextOrStream
> +               context: nil
> +               class: nil
> +               requestor: anObject!
>
> Item was added:
> + ----- Method: CompilationCue>>bindingOf: (in category 'binding') -----
> + bindingOf: aSymbol
> +       ^ class bindingOf: aSymbol environment: environment!
>
> Item was added:
> + ----- Method: CompilationCue>>category (in category 'accessing') -----
> + category
> +       ^ category!
>
> Item was added:
> + ----- Method: CompilationCue>>context (in category 'accessing') -----
> + context
> +       ^ context!
>
> Item was added:
> + ----- Method: CompilationCue>>environment (in category 'accessing') -----
> + environment
> +       ^ environment!
>
> Item was added:
> + ----- Method: CompilationCue>>getClass (in category 'accessing') -----
> + getClass
> +       ^ class!
>
> Item was added:
> + ----- Method: CompilationCue>>initializeWithSource:context:receiver:class:environment:category:requestor: (in category 'initialization') -----
> + initializeWithSource: aTextOrString context: aContext receiver: recObject class: aClass environment: anEnvironment category: aString requestor: reqObject
> +       self initialize.
> +       source := aTextOrString isStream ifTrue: [aTextOrString contents] ifFalse: [aTextOrString].
> +       context := aContext.
> +       receiver := recObject.
> +       class := aClass.
> +       environment := anEnvironment.
> +       category := aString.
> +       requestor := reqObject!
>
> Item was added:
> + ----- Method: CompilationCue>>literalScannedAs:notifying: (in category 'binding') -----
> + literalScannedAs: anObject notifying: anEncoder
> +       ^ class literalScannedAs: anObject environment: environment notifying: anEncoder!
>
> Item was added:
> + ----- Method: CompilationCue>>receiver (in category 'accessing') -----
> + receiver
> +       ^ receiver!
>
> Item was added:
> + ----- Method: CompilationCue>>requestor (in category 'accessing') -----
> + requestor
> +       ^ requestor!
>
> Item was added:
> + ----- Method: CompilationCue>>source (in category 'accessing') -----
> + source
> +       ^ source!
>
> Item was added:
> + ----- Method: CompilationCue>>sourceStream (in category 'accessing') -----
> + sourceStream
> +       ^ source readStream!
>
> Item was changed:
>   Object subclass: #Compiler
> +       instanceVariableNames: 'sourceStream requestor class category context parser cue'
> -       instanceVariableNames: 'sourceStream requestor class category context parser'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Compiler-Kernel'!
>
> + !Compiler commentStamp: 'cwp 12/26/2012 23:17' prior: 0!
> - !Compiler commentStamp: '<historical>' prior: 0!
>   The compiler accepts Smalltalk source code and compiles it with respect to a given class. The user of the compiler supplies a context so that temporary variables are accessible during compilation. If there is an error, a requestor (usually a kind of StringHolderController) is sent the message notify:at:in: so that the error message can be displayed. If there is no error, then the result of compilation is a MethodNode, which is the root of a parse tree whose nodes are kinds of ParseNodes. The parse tree can be sent messages to (1) generate code for a CompiledMethod (this is done for compiling methods or evaluating expressions); (2) pretty-print the code (for formatting); or (3) produce a map from object code back to source code (used by debugger program-counter selection). See also Parser, Encoder, ParseNode.!
>
> Item was added:
> + ----- Method: Compiler class>>evaluate:environment: (in category 'evaluating') -----
> + evaluate: aString environment: anEnvironment
> +       ^ self
> +               evaluate: aString
> +               environment: anEnvironment
> +               logged: false!
>
> Item was added:
> + ----- Method: Compiler class>>evaluate:environment:logged: (in category 'evaluating') -----
> + evaluate: aString environment: anEnvironment logged: aBoolean
> +       | cue |
> +       cue := CompilationCue
> +               source: aString
> +               environment: anEnvironment.
> +
> +       ^ self new
> +               evaluate: aString
> +               cue: cue
> +               ifFail: [^ nil]
> +               logged: aBoolean!
>
> Item was added:
> + ----- Method: Compiler>>compile:ifFail: (in category 'public access') -----
> + compile: aCue ifFail: failBlock
> +       "Answer a MethodNode. If the MethodNode can not be created, notify
> +       the requestor in the contxt. If the requestor 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 class specified by the context."
> +
> +       self setCue: aCue.
> +       self source: cue source.
> +       ^self
> +               translate: sourceStream
> +               noPattern: false
> +               ifFail: failBlock!
>
> Item was added:
> + ----- Method: Compiler>>evaluate:cue:ifFail:logged: (in category 'public access') -----
> + evaluate: textOrStream cue: aCue ifFail: failBlock logged: logFlag
> +       "Compiles the sourceStream into a parse tree, then generates code into
> +       a method. Finally, the compiled method is invoked from here via         withArgs:executeMethod:, hence the system no longer creates Doit method
> +       litter on errors."
> +
> +       | methodNode method value toLog itsSelection itsSelectionString |
> +       self setCue: aCue.
> +       self source: textOrStream.
> +       methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value].
> +
> +       method := self interactive
> +                               ifTrue: [methodNode generateWithTempNames]
> +                               ifFalse: [methodNode generate].
> +
> +       value := cue receiver
> +                               withArgs: (cue context ifNil: [#()] ifNotNil: [{cue context}])
> +                               executeMethod: method.
> +
> +       logFlag ifTrue:
> +               [toLog := ((cue requestor respondsTo: #selection)
> +                       and:[(itsSelection := cue requestor selection) notNil
> +                       and:[(itsSelectionString := itsSelection asString) isEmptyOrNil not]])
> +                               ifTrue:[itsSelectionString]
> +                               ifFalse:[sourceStream contents].
> +               SystemChangeNotifier uniqueInstance evaluated: toLog context: cue context].
> +       ^ value
> + !
>
> Item was added:
> + ----- Method: Compiler>>setCue: (in category 'private') -----
> + setCue: aCue
> +       cue := aCue.
> +
> +       "Set legacy instance variables for methods that don't use cue yet."
> +       requestor := cue requestor.
> +       class := cue getClass.
> +       category := cue category.
> +       context := cue context.!
>
> Item was added:
> + ----- Method: Compiler>>source: (in category 'private') -----
> + source: textOrStream
> +       sourceStream := (textOrStream isKindOf: PositionableStream)
> +               ifTrue: [ textOrStream ]
> +               ifFalse: [ ReadStream on: textOrStream asString ]!
>
> Item was added:
> + ----- Method: Dictionary>>bindingOf:ifAbsent: (in category '*Compiler') -----
> + bindingOf: varName ifAbsent: aBlock
> +
> +       ^self associationAt: varName ifAbsent: aBlock!
>
> Item was changed:
>   ParseNode subclass: #Encoder
> +       instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals optimizedSelectors cue'
> -       instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals optimizedSelectors'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Compiler-Kernel'!
>
> + !Encoder commentStamp: 'cwp 12/26/2012 23:29' prior: 0!
> - !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 added:
> + ----- Method: Encoder>>init:notifying: (in category 'initialize-release') -----
> + init: aCue notifying: anObject
> +       "The use of the variable requestor is a bit confusing here. This is
> +       *not* the original requestor, which is available through the cue.
> +       It's the Parser instance that is using the encoder."
> +
> +       self setCue: aCue.
> +       requestor := anObject.
> +       nTemps := 0.
> +       supered := false.
> +       self initScopeAndLiteralTables.
> +       cue getClass variablesAndOffsetsDo:
> +               [:variable "<String|CFieldDefinition>" :offset "<Integer|nil>" |
> +               offset isNil
> +                       ifTrue: [scopeTable at: variable name put: (FieldNode new fieldDefinition: variable)]
> +                       ifFalse: [scopeTable
> +                                               at: variable
> +                                               put: (offset >= 0
> +                                                               ifTrue: [InstanceVariableNode new
> +                                                                                       name: variable index: offset]
> +                                                               ifFalse: [MaybeContextInstanceVariableNode new
> +                                                                                       name: variable index: offset negated])]].
> +       cue context ~~ nil ifTrue:
> +               [| homeNode |
> +                homeNode := self bindTemp: self doItInContextName.
> +                "0th temp = aContext passed as arg"
> +                cue context tempNames withIndexDo:
> +                       [:variable :index|
> +                       scopeTable
> +                               at: variable
> +                               put: (MessageAsTempNode new
> +                                               receiver: homeNode
> +                                               selector: #namedTempAt:
> +                                               arguments: (Array with: (self encodeLiteral: index))
> +                                               precedence: 3
> +                                               from: self)]].
> +       sourceRanges := Dictionary new: 32.
> +       globalSourceRanges := OrderedCollection new: 32
> + !
>
> Item was added:
> + ----- Method: Encoder>>setCue: (in category 'private') -----
> + setCue: aCue
> +       cue := aCue.
> +
> +       "Also set legacy instance variables for methods that
> +       don't use cue yet"
> +       class := cue getClass.!
>
> Item was changed:
>   Scanner subclass: #Parser
> +       instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category queriedUnusedTemporaries cue'
> -       instanceVariableNames: 'here hereType hereMark hereEnd prevMark prevEnd encoder requestor parseNode failBlock requestorOffset tempsMark doitFlag properties category queriedUnusedTemporaries'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Compiler-Kernel'!
>
> + !Parser commentStamp: 'cwp 12/26/2012 23:34' prior: 0!
> - !Parser commentStamp: '<historical>' prior: 0!
>   I parse Smalltalk syntax and create a MethodNode that is the root of the parse tree. I look one token ahead.!
>
> Item was added:
> + ----- Method: Parser>>init:cue:failBlock: (in category 'private') -----
> + init: sourceStream cue: aCue failBlock: aBlock
> +
> +       self setCue: aCue.
> +       failBlock := aBlock.
> +       requestorOffset := 0.
> +       super scan: sourceStream.
> +       prevMark := hereMark := mark.
> +       self advance
> + !
>
> Item was added:
> + ----- Method: Parser>>parse:cue:noPattern:ifFail: (in category 'public access') -----
> + parse: sourceStream cue: aCue noPattern: noPattern ifFail: aBlock
> +       "Answer a MethodNode for the argument, sourceStream, that is the root of
> +        a parse tree. Parsing is done with respect to the CompilationCue to
> +        resolve variables. Errors in parsing are reported to the cue's requestor;
> +        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 subSelection |
> +       myStream := sourceStream.
> +       [repeatNeeded := false.
> +        p := myStream position.
> +        s := myStream upToEnd.
> +        myStream position: p.
> +        subSelection := aCue requestor notNil and: [aCue requestor selectionInterval = (p + 1 to: p + s size)].
> +        self encoder init: aCue notifying: self.
> +        self init: myStream cue: aCue failBlock: [^ aBlock value].
> +        doitFlag := noPattern.
> +        failBlock:= aBlock.
> +        [methNode := self method: noPattern context: cue context]
> +               on: ReparseAfterSourceEditing
> +               do:     [ :ex |
> +                       repeatNeeded := true.
> +                       myStream := subSelection
> +                                                       ifTrue:
> +                                                               [ReadStream
> +                                                                       on: cue requestor text string
> +                                                                       from: cue requestor selectionInterval first
> +                                                                       to: cue requestor selectionInterval last]
> +                                                       ifFalse:
> +                                                               [ReadStream on: cue requestor text string]].
> +        repeatNeeded] whileTrue:
> +               [encoder := self encoder class new].
> +       methNode sourceText: s.
> +       ^methNode
> + !
>
> Item was added:
> + ----- Method: Parser>>setCue: (in category 'private') -----
> + setCue: aCue
> +       cue := aCue.
> +
> +       "Also set legacy variables for methods that don't use cue yet."
> +       requestor := cue requestor.
> +       category := cue category.!
>
>