[squeak-dev] The Trunk: Tools-nice.497.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Sep 18 20:37:31 UTC 2013


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

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

Name: Tools-nice.497
Author: nice
Time: 18 September 2013, 10:36:39.208 pm
UUID: 54ac91af-d8e1-4710-b47f-ff29a702655a
Ancestors: Tools-fbs.496

Refactor SyntaxError
1) add an inst var pointing on the SyntaxErrorNotification instance
2) don't mess directly with the Compiler, because we don't know its final intention
    (For compiling or just parsing source code?
     For installing or not the compiledMethod in target class?
     For logging or not the source code? etc...)
3) instead act thru the support methods provided by SyntaxErrorNotification
4) remove unsed methods and instance variables
   (The SyntaxError is an old lady, it's time to erase some injuries of the past)

The main spirit of these changes is that we do not substitute to the failing Compiler, but let it restart graciously. On accept, we arrange to pass the edited source code to the compiler thru known intermediates.
The SyntaxErrorNotification knows the compiler via its signalerContext.
The Compiler knows the notification because it generated it.
So all is OK, we just have to raise already existing ReparseAfterSourceEditing when the compilation process is resumed from the signalerContext.

=============== Diff against Tools-fbs.496 ===============

Item was changed:
  ----- Method: StandardToolSet class>>debugSyntaxError: (in category 'debugging') -----
+ debugSyntaxError: aSyntaxErrorNotification
- debugSyntaxError: anError
  	"Handle a syntax error"
  	| notifier |
+ 	notifier :=  SyntaxError new setNotification: aSyntaxErrorNotification.
- 	notifier :=  SyntaxError new
- 		setClass: anError errorClass
- 		code: anError errorCode
- 		debugger: (Debugger context: anError signalerContext)
- 		doitFlag: anError doitFlag.
- 	notifier category: anError category.
  	SyntaxError open: notifier.!

Item was changed:
  StringHolder subclass: #SyntaxError
+ 	instanceVariableNames: 'class selector category debugger notification'
- 	instanceVariableNames: 'class selector category debugger doitFlag'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-Debugger'!
  
  !SyntaxError commentStamp: '<historical>' prior: 0!
  I represent syntax error report for syntax errors encountered when filing in class descriptions from a non-interactive source such as an external file. As a StringHolder, the string to be viewed is the method code or expression containing the error.
  
  The user may fix the error and accept the method to continue the fileIn.
  !

Item was removed:
- ----- Method: SyntaxError class>>errorInClass:withCode:doitFlag: (in category 'instance creation') -----
- errorInClass: aClass withCode: codeString doitFlag: doit
- 	"Open a view whose model is a syntax error. The error occurred when trying to add the given method code to the given class."
- 
- 	self open:
- 		(self new setClass: aClass
- 			code: codeString
- 			debugger: (Debugger context: thisContext)
- 			doitFlag: doit).
- !

Item was removed:
- ----- Method: SyntaxError>>category: (in category 'accessing') -----
- category: aSymbol
- 	"Record the message category of method being compiled. This is used when the user corrects the error and accepts."
- 
- 	category := aSymbol.
- !

Item was changed:
  ----- Method: SyntaxError>>contents:notifying: (in category 'other') -----
  contents: aString notifying: aController
+ 	"Accept the code editions if syntax is correct.
+ 	Then let the notification signalerContext proceed and restart compilation with these newSource."
- 	"Compile the code in aString and notify aController of any errors. If there are no errors, then automatically proceed."
  
+ 	"In case of failure, return false so as to not accept the edits"
+ 	notification reparse: aString notifying: aController ifFail: [^false].
- 	doitFlag
- 	ifTrue: [Compiler new evaluate: aString in: nil to: nil
- 						notifying: aController ifFail: [^ false]]
- 	ifFalse: [(class compile: aString classified: category
- 						notifying: aController) ifNil: [^ false]].
  
+ 	"else accept edits and proceed"
  	aController hasUnacceptedEdits: false.
  	self proceed!

Item was changed:
  ----- Method: SyntaxError>>list (in category 'message list') -----
  list
  	"Answer an array of one element made up of the class name, message category, and message selector in which the syntax error was found. This is the single item in the message list of a view/browser on the receiver."
  
+ 	^ Array with: (class name, '  ', (notification category ifNil: ['<none>']), '  ', (selector ifNil: ['<none>']))
- 	^ Array with: (class name, '  ', (category ifNil: ['<none>']), '  ', (selector ifNil: ['<none>']))
  !

Item was removed:
- ----- Method: SyntaxError>>notify:at:in: (in category 'other') -----
- notify: error at: location in: source
- 	"Open a syntax error view, inserting the given error message into the given source at the given location. This message is sent to the 'requestor' when the parser or compiler finds a syntax error."
- 
- 	| aClass aString |
- 	aClass := thisContext sender receiver encoder classEncoding.
- 	aString :=
- 		source contents
- 			copyReplaceFrom: location
- 			to: location - 1
- 			with: error.
- 	self setClass: aClass
- 		code: aString
- 		debugger: (Debugger context: thisContext)
- 		doitFlag: false.
- 	self class open: self.
- !

Item was changed:
  ----- Method: SyntaxError>>release (in category 'initialize-release') -----
  release
+ 	debugger ifNotNil:
+ 		[debugger interruptedProcess ifNotNil:
+ 			[:p |	p isTerminated ifFalse:
+ 				[p terminate]]].!
- 	| p |
- 	(debugger isNil or: [
- 		(p := debugger interruptedProcess) isNil or: [
- 			p isTerminated]]) ifTrue: [^self].
- 
- 	p terminate!

Item was removed:
- ----- Method: SyntaxError>>setClass:code:debugger:doitFlag: (in category 'accessing') -----
- setClass: aClass code: aString debugger: aDebugger doitFlag: flag
- 
- 	| types printables badChar |
- 	class := aClass.
- 	debugger := aDebugger.
- 	selector := aClass newParser parseSelector: aString.
- 	types := Scanner classPool at: #TypeTable.	"dictionary"
- 	printables := '!!@#$%&*-_=+<>{}?/\,·£¢§¶ªº–—“‘”’…Úæگ׿«»`~`' asSet.
- 	badChar := aString detect: [:aChar | (types at: aChar asciiValue ifAbsent: [#xLetter]) == #xBinary and: [
- 			(printables includes: aChar) not]] ifNone: [nil].
- 	contents := badChar 
- 		ifNil: [aString]
- 		ifNotNil: ['<<<This string contains a character (ascii value ', 
- 			badChar asciiValue printString,
- 			') that is not normally used in code>>> ', aString].
- 	category ifNil: [category := aClass organization categoryOfElement: selector].
- 	category ifNil: [category := ClassOrganizer default].
- 	doitFlag := flag!

Item was added:
+ ----- Method: SyntaxError>>setNotification: (in category 'accessing') -----
+ setNotification: aSyntaxErrorNotification
+ 
+ 	| types printables badChar code |
+ 	notification := aSyntaxErrorNotification.
+ 	class := aSyntaxErrorNotification errorClass.
+ 	debugger := Debugger context: aSyntaxErrorNotification signalerContext.
+ 	code := aSyntaxErrorNotification errorCode.
+ 	selector := class newParser parseSelector: code.
+ 	category := aSyntaxErrorNotification category.
+ 	types := Scanner classPool at: #TypeTable.	"dictionary"
+ 	printables := '!!@#$%&*-_=+<>{}?/\,·£¢§¶ªº–—“‘”’…Úæگ׿«»`~`' asSet.
+ 	badChar := code detect: [:aChar | (types at: aChar asciiValue ifAbsent: [#xLetter]) == #xBinary and: [
+ 			(printables includes: aChar) not]] ifNone: [nil].
+ 	contents := badChar 
+ 		ifNil: [code]
+ 		ifNotNil: ['<<<This string contains a character (ascii value ', 
+ 			badChar asciiValue printString,
+ 			') that is not normally used in code>>> ', code].
+ 	category ifNil: [category := class organization categoryOfElement: selector].
+ 	category ifNil: [category := ClassOrganizer default].!



More information about the Squeak-dev mailing list