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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 20 19:40:31 UTC 2013


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

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

Name: Compiler-nice.270
Author: nice
Time: 20 September 2013, 9:39:56.005 pm
UUID: 96ead68a-0990-4917-9e75-4a9d0764ec7c
Ancestors: Compiler-nice.269

More compiler clean-ups.
A Compiler does compile, it does not classify.
So add new messages to avoid passing a category to a Compiler, such category is essentially useless, except for displaying in SyntaxError!
Then, no need to pass a category to CompilationCue, nor to a SyntaxErrorNotification, nor to a SyntaxError (in Tools).
Also add and use new messages to avoid passing a nil context, requestor...
We will remove some unused methods later.

=============== Diff against Compiler-nice.269 ===============

Item was changed:
  Object subclass: #CompilationCue
  	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 changed:
  ----- Method: CompilationCue class>>class: (in category 'instance creation') -----
  class: aClass
  	^ self 
+ 		source: nil
  		context: nil
+ 		receiver: nil
  		class: aClass
+ 		environment: (aClass ifNotNil: [aClass environment])
  		requestor: nil!

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

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

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

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

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

Item was changed:
  ----- 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>>initializeWithSource:context:receiver:class:environment:requestor: (in category 'initialization') -----
+ initializeWithSource: aTextOrString context: aContext receiver: recObject class: aClass environment: anEnvironment requestor: reqObject
+ 	self initialize.
+ 	source := (aTextOrString isKindOf: PositionableStream)
+ 		ifTrue: [ aTextOrString ]
+ 		ifFalse: [ ReadStream on: aTextOrString asString ].
+ 	context := aContext.
+ 	receiver := recObject.
+ 	class := aClass.
+ 	environment := anEnvironment.
+ 	requestor := reqObject!

Item was changed:
  ----- Method: Compiler>>compile:in:notifying:ifFail: (in category 'public access') -----
  compile: textOrStream in: aClass 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
+ 			class: aClass
+ 			requestor: aRequestor)
+ 		noPattern: false
+ 		ifFail: failBlock
+ !
- 	^self compile: textOrStream in: aClass classified: nil notifying: aRequestor ifFail: failBlock !

Item was added:
+ ----- Method: Compiler>>compileNoPattern:in:notifying:ifFail: (in category 'public access') -----
+ compileNoPattern: textOrStream in: aClass notifying: aRequestor ifFail: failBlock
+ 	"Similar to #compile:in:notifying:ifFail:, but the compiled code is
+ 	expected to be a do-it expression, with no message pattern."
+ 
+ 	^self
+ 		compileCue: (CompilationCue
+ 			source: textOrStream
+ 			class: aClass
+ 			requestor: aRequestor)
+ 		noPattern: true
+ 		ifFail: failBlock
+ !

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
  		evaluateCue: (CompilationCue
  			source: textOrStream
  			context: aContext
  			receiver: receiver
  			class: theClass
  			environment: theClass environment
- 			category: nil
  			requestor: aRequestor)
  		ifFail: failBlock
  		logged: logFlag!

Item was changed:
+ ----- Method: Compiler>>format:in:notifying: (in category 'public access') -----
- ----- Method: Compiler>>format:in:notifying: (in category 'private') -----
  format: textOrStream in: aClass notifying: aRequestor
  	"Compile a parse tree from the argument, textOrStream. Answer a string containing the original code, formatted nicely.  If aBoolean is true, then decorate the resulting text with color and hypertext actions"
  
  	| aNode |
  	self from: textOrStream
  		class: aClass
- 		context: nil
  		notifying: aRequestor.
  	aNode := self formatNoPattern: false ifFail: [^ nil].
  
  	"aSymbol == #colorPrint ifTrue:
  		[^aNode asColorizedSmalltalk80Text]." "deprecating #colorPrint in favor of Shout --Ron Spengler"
  
  	^aNode decompileString!

Item was changed:
  ----- Method: Compiler>>format:in:notifying:decorated: (in category 'public access') -----
  format: textOrStream in: aClass notifying: aRequestor decorated: aBoolean
  	"Compile a parse tree from the argument, textOrStream. Answer a string containing the original code, formatted nicely.  If aBoolean is true, then decorate the resulting text with color and hypertext actions"
  	| aNode |
  	self from: textOrStream
  		class: aClass
- 		context: nil
  		notifying: aRequestor.
  	aNode := self formatNoPattern: false ifFail: [^ nil].
  	^ aBoolean
  		ifTrue: [aNode decompileText]
  		ifFalse: [aNode decompileString]!

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

Item was changed:
  ----- Method: Compiler>>parse:in:notifying: (in category 'public access') -----
  parse: textOrStream in: aClass notifying: req
  	"Compile the argument, textOrStream, with respect to the class, aClass, and
  	 answer the MethodNode that is the root of the resulting parse tree.  Notify the
  	 argument, req, if an error occurs. The failBlock is defaulted to an empty block."
  
+ 	self from: textOrStream class: aClass notifying: req.
- 	self from: textOrStream class: aClass context: nil notifying: req.
  	^self parser
  		parseCue: cue
  		noPattern: false
  		ifFail: []!

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

Item was changed:
  ----- Method: Parser>>notify:at: (in category 'error handling') -----
  notify: string at: location
  	cue requestor isNil
  		ifTrue: [| notification |
  			(encoder == self or: [encoder isNil]) ifTrue: [^ self fail  "failure setting up syntax error"].
  			(notification := SyntaxErrorNotification
  					inClass: encoder classEncoding
- 					category: cue category
  					withCode: 
  						(source contents asText
  							copyReplaceFrom: location
  							to: location - 1
  							with: ((string , ' ->') asText allBold 
  								addAttribute: TextColor red; yourself))
  					doitFlag: doitFlag
  					errorMessage: string
  					location: location) signal.
  			notification tryNewSourceIfAvailable]
  		ifFalse: [cue requestor
  					notify: string , ' ->'
  					at: location
  					in: source].
  	^self fail!

Item was changed:
  ----- Method: Parser>>parse:class: (in category 'public access') -----
  parse: sourceStreamOrString class: behavior
  
  	^ self parse: sourceStreamOrString readStream class: behavior
+ 		noPattern: false notifying: nil ifFail: [^nil]!
- 		noPattern: false context: nil notifying: nil ifFail: [^nil]!

Item was changed:
  ----- Method: Parser>>parse:class:noPattern:notifying:ifFail: (in category 'public access') -----
+ parse: sourceStream class: class noPattern: noPattern notifying: req ifFail: aBlock 
+ 	| c |
+ 	c := CompilationCue
+ 			source: sourceStream
+ 			class: class
+ 			requestor: req.
+ 	^ self 
+ 		parseCue: c 
+ 		noPattern: noPattern 
+ 		ifFail: aBlock!
- parse: sourceStream class: class noPattern: noPattern notifying: req ifFail: aBlock
- 
- 	^ self parse: sourceStream class: class noPattern: noPattern context: nil notifying: req ifFail: aBlock!

Item was added:
+ ----- Method: Parser>>parseArgsAndTemps: (in category 'public access') -----
+ parseArgsAndTemps: aString 
+         "Parse the argument, aString, answer nil if an error occurs. Otherwise, 
+         answer an Array 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
+                 return: [:pattern | (pattern at: 2) , (self temporariesIn: (pattern at: 1))]!

Item was changed:
  ----- Method: Parser>>parseMethodComment:setPattern: (in category 'public access') -----
  parseMethodComment: aString setPattern: aBlock
  	"Answer the method comment for the argument, aString. Evaluate aBlock 
  	with the message pattern in the form #(selector, arguments, precedence)."
  
  	self
  		initPattern: aString
- 		notifying: nil
  		return: aBlock.
  	currentComment==nil
  		ifTrue:	[^OrderedCollection new]
  		ifFalse:	[^currentComment]!

Item was changed:
  ----- Method: Parser>>parseParameterNames: (in category 'public access') -----
  parseParameterNames: aString 
  	"Answer the parameter names for the argument, aString, which should 
  	 parse successfully up to the temporary declaration or the end of the 
  	 method header."
  
  	self initScannerForTokenization.
  	^self
  		initPattern: aString
- 		notifying: nil
  		return: [:pattern | pattern at: 2]!

Item was changed:
  ----- Method: Parser>>parseSelector: (in category 'public access') -----
  parseSelector: aString 
  	"Answer the message selector for the argument, aString, which should 
  	 parse successfully up to the temporary declaration or the end of the 
  	 method header."
  
  	self initScannerForTokenization.
  	^self
  		initPattern: aString
- 		notifying: nil
  		return: [:pattern | pattern at: 1]!

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

Item was changed:
  ----- Method: SyntaxErrorNotification>>reparse:notifying:ifFail: (in category 'accessing') -----
  reparse: aString notifying: aController ifFail: failBlock
  	"Try to parse if aString has correct syntax, but do not evaluate/install any code.
  	In case of incorrect syntax, execute failBlock and let a Compiler interact with the requestor.
  	In case of correct syntax, set newSource."
  	doitFlag
+ 		ifTrue: [nil class newCompiler compileNoPattern: aString in: nil class notifying: aController ifFail: failBlock]
+ 		ifFalse: [inClass newCompiler compile: aString in: inClass notifying: aController ifFail: failBlock].
- 		ifTrue: [nil class newCompiler compileNoPattern: aString in: nil class context: nil notifying: aController ifFail: failBlock]
- 		ifFalse: [inClass newCompiler compile: aString in: inClass classified: category notifying: aController ifFail: failBlock].
  	newSource := aString!

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



More information about the Squeak-dev mailing list