[Pkg] The Trunk: Compiler-ct.450.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Feb 18 13:19:08 UTC 2021


Marcel Taeumel uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-ct.450.mcz

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

Name: Compiler-ct.450
Author: ct
Time: 24 October 2020, 12:16:36.359256 am
UUID: ea5bdd56-7ceb-ae4f-a2d7-1b9d11cda893
Ancestors: Compiler-ct.449

Implements #environment on SyntaxErrorNotification. Sorry I hit the Accept button to soon...

=============== Diff against Compiler-tobe.448 ===============

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

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

Item was changed:
  Error subclass: #SyntaxErrorNotification
+ 	instanceVariableNames: 'cue doitFlag errorMessage location newSource'
- 	instanceVariableNames: 'inClass code doitFlag errorMessage location newSource'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Compiler-Exceptions'!
  
+ !SyntaxErrorNotification commentStamp: 'ct 10/24/2020 00:01' prior: 0!
- !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
+ 	cue:		<CompilationCue>
- 	category:		<String | nil>
- 	code:		<String | Text | Stream>
  	doitFlag:		<Boolean>
  	errorMessage:		<String>
- 	inClass:		<Behavior>
  	location:		<Integer>
  	newSource:		<String | Text | Stream | nil>
  
+ cue
+ 	- the cue for compilation, including receiver class, optional context, and original source code
- 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!
- 	- eventually hold a source code replacement typically passed by the SyntaxError window
- !

Item was added:
+ ----- Method: SyntaxErrorNotification class>>cue:doitFlag:errorMessage:location: (in category 'instance creation') -----
+ cue: aCue doitFlag: doitFlag errorMessage: errorString location: location
+ 
+ 	^ self new
+ 		setCue: aCue
+ 		doitFlag: doitFlag
+ 		errorMessage: errorString
+ 		location: location!

Item was changed:
+ ----- Method: SyntaxErrorNotification class>>inClass:withCode:doitFlag:errorMessage:location: (in category 'instance creation') -----
- ----- Method: SyntaxErrorNotification class>>inClass:withCode:doitFlag:errorMessage:location: (in category 'exceptionInstantiator') -----
  inClass: aClass withCode: codeString doitFlag: doitFlag errorMessage: errorString location: location
+ 
+ 	self deprecated: 'ct: Use #cue:doitFlag:errorMessage:location:'.
+ 	^ self
+ 		cue: (CompilationCue source: codeString class: aClass requestor: nil)
- 	^self new
- 		setClass: aClass
- 		code: codeString
  		doitFlag: doitFlag
  		errorMessage: errorString
  		location: location!

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

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

Item was changed:
  ----- Method: SyntaxErrorNotification>>errorClass (in category 'accessing') -----
  errorClass
+ 
+ 	^ cue getClass!
- 	^inClass!

Item was changed:
  ----- Method: SyntaxErrorNotification>>errorCode (in category 'accessing') -----
  errorCode
+ 
+ 	^ cue source!
- 	^code!

Item was changed:
  ----- Method: SyntaxErrorNotification>>messageText (in category 'accessing') -----
  messageText
  	^ super messageText
+ 		ifEmpty: [messageText := self errorCode]!
- 		ifEmpty: [messageText := code]!

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] ifFalse: [self errorClass]) newCompiler
+ 		compileCue: (cue copy
+ 			source: aString;
+ 			requestor: aController;
+ 			yourself)
+ 		noPattern: doitFlag
+ 		ifFail: failBlock.
+ 	newSource := aString.!
- 	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].
- 	newSource := aString!

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

Item was added:
+ ----- Method: SyntaxErrorNotification>>setCue:doitFlag:errorMessage:location: (in category 'initialize-release') -----
+ setCue: aCue doitFlag: aBoolean errorMessage: errorString location: anInteger
+ 
+ 	cue := aCue.
+ 	doitFlag := aBoolean.
+ 	errorMessage := errorString.
+ 	location := anInteger!



More information about the Packages mailing list