[squeak-dev] The Trunk: Compiler-nice.274.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Sep 23 23:04:46 UTC 2013


Nicolas Cellier uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-nice.274.mcz

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

Name: Compiler-nice.274
Author: nice
Time: 24 September 2013, 1:04:09.905 am
UUID: 3b9c2992-15d5-4c9e-99ea-235b6fe82dd1
Ancestors: Compiler-nice.273, Compiler-nice.272

Merge versions nice 272 and 273 and remove sourceStream inst. var. again.

=============== Diff against Compiler-nice.273 ===============

Item was changed:
  Object subclass: #CompilationCue
+ 	instanceVariableNames: 'source context receiver class environment requestor'
- 	instanceVariableNames: 'source context receiver class environment category requestor'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Kernel'!
  
  !CompilationCue commentStamp: 'nice 9/20/2013 02:07' prior: 0!
  A CompilationCue is a helper class holding enough context for evaluating/compiling Smalltalk code.
  
  That is mainly the source code, and the source code editor to interact with if the Compiler is used interactively.
  But that is also any additional information necessary to resolve variable names.
  
  When compiling a method, the Compiler typically need to know the target class in which to install the method.
  
  When evaluating an expression, the Compiler also needs a receiver (for accessing the value of its instance variables), its class (for resolving instance/class variable names), and optionnally a context of execution when debugging a method (for accessing values of temporaries and parameters).
  
  Instance Variables
  	class:		<Behavior>
  	context:		<ContextPart | nil>
  	environment:		<Environment | nil>
  	receiver:		<Object>
  	requestor:		<TextEditor | nil>
  	source:		<Stream>
  
  class
  	- the target class in which to install the compiled method;
  	  this enables to resolve the instance variable names, class variable names and shared pool variable names.
  	  When evaluating, this should be the receiver class
  
  context
  	- the context introspected when evaluating the code: this is typically for accessing parameters and temporary variables when debugging
  
  environment
  	- the environment in which to resolve global variable names
  
  receiver
  	- the receiver into which to evaluate the code: this is typically for accessing instance variables in an inspector
  
  requestor
  	- typically the text editor containing the source code being compiled/evaluated. This enables the Compiler to interact in case of syntax error.
  
  source
  	- a ReadStream on the source code to be compiled
  !

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: CompilationCue class>>source:requestor: (in category 'instance creation') -----
- source: aTextOrStream requestor: anObject
- 	^ self
- 		source: aTextOrStream
- 		context: nil
- 		class: nil
- 		requestor: anObject!

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

Item was removed:
- ----- 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 isKindOf: PositionableStream)
- 		ifTrue: [ aTextOrString ]
- 		ifFalse: [ ReadStream on: aTextOrString asString ].
- 	context := aContext.
- 	receiver := recObject.
- 	class := aClass.
- 	environment := anEnvironment.
- 	category := aString.
- 	requestor := reqObject!

Item was changed:
  Object subclass: #Compiler
+ 	instanceVariableNames: 'parser cue'
- 	instanceVariableNames: 'sourceStream parser cue'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Kernel'!
  
  !Compiler commentStamp: 'cwp 12/26/2012 23:17' 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 removed:
- ----- 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."
- 
- 	^self
- 		compileCue: (CompilationCue
- 			source: textOrStream
- 			context: nil
- 			class: aClass
- 			category: aCategory
- 			requestor: aRequestor)
- 		noPattern: false
- 		ifFail: failBlock
- !

Item was removed:
- ----- Method: Compiler>>from:class:context:notifying: (in category 'private') -----
- from: textOrStream class: aClass context: aContext notifying: req
- 	self setCue:
- 		(CompilationCue
- 			source: textOrStream
- 			context: aContext
- 			class: aClass
- 			requestor: req)
- !

Item was removed:
- ----- Method: Compiler>>notify: (in category 'error handling') -----
- notify: aString 
- 	"Refer to the comment in Object|notify:."
- 
- 	^self notify: aString at: cue sourceStream position + 1!

Item was removed:
- ----- Method: Compiler>>notify:at: (in category 'error handling') -----
- notify: aString at: location
- 	"Refer to the comment in Object|notify:."
- 
- 	^ cue requestor == nil
- 		ifTrue: [(SyntaxErrorNotification
- 					inClass: cue getClass
- 					category: cue category
- 					withCode: 
- 						(cue sourceStream contents
- 							copyReplaceFrom: location
- 							to: location - 1
- 							with: aString)
- 					doitFlag: false
- 					errorMessage: aString
- 					location: location) signal]
- 		ifFalse: [cue requestor
- 					notify: aString
- 					at: location
- 					in: cue sourceStream]!

Item was removed:
- ----- 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!

Item was removed:
- ----- Method: Encoder>>requestor: (in category 'error handling') -----
- requestor: req
- 	"Often the requestor is a BrowserCodeController"
- 	requestor := req!

Item was removed:
- ----- 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)
- 		failBlock: [^nil].
- 	encoder := self.
- 	result := aBlock value: (self pattern: false inContext: nil).
- 	encoder := failBlock := nil.  "break cycles"
- 	^result!

Item was removed:
- ----- Method: Parser>>method:context:encoder: (in category 'expression types') -----
- method: doit context: ctxt encoder: encoderToUse
- 	" pattern [ | temporaries ] block => MethodNode."
- 
- 	encoder := encoderToUse.
- 	^self method: doit context: ctxt!

Item was removed:
- ----- 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 
- 		parseCue: c 
- 		noPattern: noPattern 
- 		ifFail: aBlock!

Item was removed:
- ----- Method: Parser>>parse:class:noPattern:context:notifying:ifFail: (in category 'public access') -----
- parse: sourceStream class: class noPattern: noPattern context: ctxt notifying: req ifFail: aBlock 
- 	^self parse: sourceStream class: class category: nil noPattern: noPattern context: ctxt notifying: req ifFail: aBlock !

Item was removed:
- ----- Method: Parser>>parseArgsAndTemps:notifying: (in category 'public access') -----
- parseArgsAndTemps: aString notifying: req 
-         "Parse the argument, aString, notifying req if an error occurs. Otherwise, 
-         answer a two-element Array containing Arrays of strings (the argument 
-         names and temporary variable names)."
- 
-         aString == nil ifTrue: [^#()].
-         doitFlag := false.               "Don't really know if a doit or not!!"
-         ^self initPattern: aString
-                 notifying: req
-                 return: [:pattern | (pattern at: 2) , (self temporariesIn: (pattern at: 1))]!

Item was changed:
  ----- Method: Parser>>parseCue:noPattern:ifFail: (in category 'public access') -----
  parseCue: 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 := aCue 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.
+ 			properties := nil. "Avoid accumulating pragmas and primitives Number"
  			myStream := ex newSource 
  				ifNil: [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]]
  				ifNotNil: [:src | myStream := src readStream]].
  	 repeatNeeded] whileTrue:
  		[encoder := self encoder class new].
  	methNode sourceText: s.
  	^methNode
  !

Item was changed:
  Error subclass: #SyntaxErrorNotification
+ 	instanceVariableNames: 'inClass code doitFlag errorMessage location newSource'
- 	instanceVariableNames: 'inClass code category doitFlag errorMessage location newSource'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Exceptions'!
  
  !SyntaxErrorNotification commentStamp: 'nice 9/18/2013 22:16' prior: 0!
  A SyntaxErrorNotification is an Exception occuring when compiling a Smalltalk source code with incorrect syntax.
  Note that in interactive mode, this exception is not raised because the Compiler will interact directly with source code editor.
  The defaultAction is to raise a SyntaxError pop up window so as to enable interactive handling even in non interactive mode.
  
  Instance Variables
  	category:		<String | nil>
  	code:		<String | Text | Stream>
  	doitFlag:		<Boolean>
  	errorMessage:		<String>
  	inClass:		<Behavior>
  	location:		<Integer>
  	newSource:		<String | Text | Stream | nil>
  
  category
  	- the category in which the method will be classified
  
  code
  	- the source code to be compiled or evaluated
  
  doitFlag
  	- true if this is a doIt (code to evaluate), false if this is a method (code of a method to be compiled)
  
  errorMessage
  	- contains information about the syntax error
  
  inClass
  	- target class in which to compile the method
  
  location
  	- position in the source code where the syntax error occured
  
  newSource
  	- eventually hold a source code replacement typically passed by the SyntaxError window
  !

Item was removed:
- ----- Method: SyntaxErrorNotification class>>inClass:category:withCode:doitFlag:errorMessage:location: (in category 'exceptionInstantiator') -----
- inClass: aClass category: aCategory withCode: codeString doitFlag: doitFlag errorMessage: errorString location: location
- 	^self new
- 		setClass: aClass
- 		category: aCategory 
- 		code: codeString
- 		doitFlag: doitFlag
- 		errorMessage: errorString
- 		location: location!

Item was removed:
- ----- Method: SyntaxErrorNotification>>category (in category 'accessing') -----
- category
- 	^category!

Item was removed:
- ----- Method: SyntaxErrorNotification>>setClass:category:code:doitFlag: (in category 'accessing') -----
- setClass: aClass category: aCategory code: codeString doitFlag: aBoolean
- 	inClass := aClass.
- 	category := aCategory.
- 	code := codeString.
- 	doitFlag := aBoolean !

Item was removed:
- ----- Method: SyntaxErrorNotification>>setClass:category:code:doitFlag:errorMessage:location: (in category 'accessing') -----
- setClass: aClass category: aCategory code: codeString doitFlag: aBoolean errorMessage: errorString location: anInteger
- 	inClass := aClass.
- 	category := aCategory.
- 	code := codeString.
- 	doitFlag := aBoolean.
- 	errorMessage := errorString.
- 	location := anInteger!



More information about the Squeak-dev mailing list