The Trunk: Compiler-cwp.246.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-cwp.246.mcz

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

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

Name: Compiler-cwp.246
Author: cwp
Time: 1 January 2013, 6:57:00.489 pm
UUID: 54460c3c-db04-4159-8269-3bd83cc3c9f3
Ancestors: Compiler-cwp.245

Environments bootstrap - stage 2

=============== Diff against Compiler-cwp.245 ===============

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."
+
+ | theClass |
+ theClass := ((aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class).
+ self setCue: (CompilationCue
+ source: textOrStream
+ context: aContext
+ receiver: receiver
+ class: theClass
+ environment: theClass environment
+ category: nil
+ requestor: aRequestor).
+ ^ self evaluate: textOrStream cue: cue ifFail: failBlock logged: logFlag!
-
- | 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].
-
- method := self interactive
- ifTrue: [methodNode generateWithTempNames]
- ifFalse: [methodNode generate].
-
- value := receiver
- withArgs: (context ifNil: [#()] ifNotNil: [{context}])
- executeMethod: method.
-
- 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: Compiler>>from:class:classified:context:notifying: (in category 'public access') -----
  from: textOrStream class: aClass classified: aCategory context: aContext notifying: req
+ self source: textOrStream.
+ self setCue:
+ (CompilationCue
+ source: textOrStream
+ context: aContext
+ class: aClass
+ category: aCategory
+ requestor: req)!
-
- sourceStream := (textOrStream isKindOf: PositionableStream)
- ifTrue: [textOrStream]
- ifFalse: [ReadStream on: textOrStream asString].
- class := aClass.
- context := aContext.
- requestor := req.
- category := aCategory
- !

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

Item was changed:
  ----- Method: Encoder>>init:context:notifying: (in category 'initialize-release') -----
+ init: aClass context: aContext notifying: anObject
+ | c |
+ c := CompilationCue
+ context: aContext
+ class: aClass
+ requestor: nil.
+ self init: c notifying: anObject!
- init: aClass context: aContext notifying: req
- requestor := req.
- class := aClass.
- nTemps := 0.
- supered := false.
- self initScopeAndLiteralTables.
- class 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])]].
- aContext ~~ nil ifTrue:
- [| homeNode |
- homeNode := self bindTemp: self doItInContextName.
- "0th temp = aContext passed as arg"
- aContext 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 changed:
  ----- Method: Encoder>>temps:literals:class: (in category 'initialize-release') -----
  temps: tempVars literals: lits class: cl
  "Initialize this encoder for decompilation."
 
+ self setCue: (CompilationCue class: cl).
  supered := false.
- class := cl.
  nTemps := tempVars size.
  tempVars do: [:node | scopeTable at: node name put: node].
  literalStream := WriteStream on: (Array new: lits size).
  literalStream nextPutAll: lits.
  sourceRanges := Dictionary new: 32.
  globalSourceRanges := OrderedCollection new: 32.!

Item was changed:
  ----- Method: Parser>>initPattern:notifying:return: (in category 'private') -----
  initPattern: aString notifying: req return: aBlock
 
  | result |
  self
  init: (ReadStream on: aString asString)
+ cue: (CompilationCue source: aString requestor: req)
- notifying: req
  failBlock: [^nil].
  encoder := self.
  result := aBlock value: (self pattern: false inContext: nil).
  encoder := failBlock := nil.  "break cycles"
  ^result!

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: aContext notifying: req ifFail: aBlock
+ | c |
+ c := CompilationCue
+ source: sourceStream
+ context: aContext
+ class: class
+ category: aCategory
+ requestor: req.
+ ^ self
+ parse: sourceStream
+ cue: c
+ noPattern: noPattern
+ ifFail: aBlock!
- 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 subSelection |
- category := aCategory.
- myStream := sourceStream.
- [repeatNeeded := false.
- p := myStream position.
- s := myStream upToEnd.
- myStream position: p.
- subSelection := req notNil and: [req selectionInterval = (p + 1 to: p + s size)].
- 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 := subSelection
- ifTrue:
- [ReadStream
- on: requestor text string
- from: requestor selectionInterval first
- to: requestor selectionInterval last]
- ifFalse:
- [ReadStream on: requestor text string]].
- repeatNeeded] whileTrue:
- [encoder := self encoder class new].
- methNode sourceText: s.
- ^methNode!