[squeak-dev] The Inbox: Compiler-ct.423.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Mar 21 23:09:55 UTC 2020


Christoph Thiede uploaded a new version of Compiler to project The Inbox:
http://source.squeak.org/inbox/Compiler-ct.423.mcz

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

Name: Compiler-ct.423
Author: ct
Time: 22 March 2020, 12:09:52.64956 am
UUID: 7f8f4492-536a-4e44-9890-b3d015655631
Ancestors: Compiler-nice.420

Fixes and refactors interactive selection during parser notifications. In #queryUndefined, do not forget to reset the selection after the parser notification has been skipped. Extract selection-specific logic into #selectFrom:to:during:. See detailed bug report and solution description in Morphic-ct.1640. Load together with Morphic-ct.1640 only.

=============== Diff against Compiler-nice.420 ===============

Item was changed:
  ----- Method: Parser>>ambiguousSelector:inRange: (in category 'error correction') -----
  ambiguousSelector: aString inRange: anInterval
+ 	| correctedSelector offset intervalWithOffset |
- 	| correctedSelector userSelection offset intervalWithOffset |
  	
  	self interactive ifFalse: [
  		"In non interactive mode, compile with backward comapatibility: $- is part of literal argument"
  		Transcript cr; store: encoder classEncoding; nextPutAll:#'>>';store: encoder selector; show: ' would send ' , token , '-'.
  		^super ambiguousSelector: aString inRange: anInterval].
  	
  	"handle the text selection"
- 	userSelection := cue requestor selectionInterval.
  	intervalWithOffset := anInterval first + requestorOffset to: anInterval last + requestorOffset.
+ 	self selectFrom: intervalWithOffset first to: intervalWithOffset last during: [
+ 		"Build the menu with alternatives"
+ 		correctedSelector := AmbiguousSelector 
- 	cue requestor selectFrom: intervalWithOffset first to: intervalWithOffset last.
- 	cue requestor select.
- 
- 	"Build the menu with alternatives"
- 	correctedSelector := AmbiguousSelector 
  			signalName: aString
  			inRange: intervalWithOffset.
+ 		correctedSelector ifNil: [^ self fail]].
+ 	
- 	correctedSelector ifNil: [^self fail].
- 
  	"Execute the selected action"
  	offset := self substituteWord: correctedSelector wordInterval: intervalWithOffset offset: 0.
- 	cue requestor deselect.
- 	cue requestor selectInvisiblyFrom: userSelection first to: userSelection last + offset.
  	token := (correctedSelector readStream upTo: Character space) asSymbol!

Item was changed:
  ----- Method: Parser>>correctSelector:wordIntervals:exprInterval:ifAbort: (in category 'error correction') -----
  correctSelector: proposedKeyword wordIntervals: spots exprInterval: expInt ifAbort: abortAction
  	"Correct the proposedKeyword to some selector symbol, correcting the original text if such action is indicated.  abortAction is invoked if the proposedKeyword couldn't be converted into a valid selector.  Spots is an ordered collection of intervals within the test stream of the for each of the keyword parts."
  
+ 	| correctSelector |
- 	| correctSelector userSelection |
  	"If we can't ask the user, assume that the keyword will be defined later"
+ 	self interactive ifFalse: [^ proposedKeyword asSymbol].
+ 	
+ 	self selectFrom: spots first first to: spots last last during: [
+ 		correctSelector := UnknownSelector name: proposedKeyword.
+ 		correctSelector ifNil: [^ abortAction value]].
+ 	
- 	self interactive ifFalse: [^proposedKeyword asSymbol].
- 
- 	userSelection := cue requestor selectionInterval.
- 	cue requestor selectFrom: spots first first to: spots last last.
- 	cue requestor select.
- 
- 	correctSelector := UnknownSelector name: proposedKeyword.
- 	correctSelector ifNil: [^abortAction value].
- 
- 	cue requestor deselect.
- 	cue requestor selectInvisiblyFrom: userSelection first to: userSelection last.
- 
  	self substituteSelector: correctSelector keywords wordIntervals: spots.
+ 	^ (proposedKeyword last ~~ $:
- 	^(proposedKeyword last ~~ $:
  	   and: [correctSelector last == $:])
  		ifTrue: [abortAction value]
  		ifFalse: [correctSelector]!

Item was changed:
  ----- Method: Parser>>correctVariable:interval: (in category 'error correction') -----
  correctVariable: proposedVariable interval: spot 
+ 	"Correct the proposedVariable to a known variable, or declare it as a new variable if such action is requested.  We support declaring lowercase variables as temps or inst-vars, and uppercase variables as Globals or ClassVars, depending on whether the receiver is nil. Spot is the interval within the test stream of the variable."
- 	"Correct the proposedVariable to a known variable, or declare it as a new
- 	variable if such action is requested.  We support declaring lowercase
- 	variables as temps or inst-vars, and uppercase variables as Globals or 
- 	ClassVars, depending on whether the context is nil (class=UndefinedObject).
- 	Spot is the interval within the test stream of the variable.
- 	rr 3/4/2004 10:26 : adds the option to define a new class. "
  
+ 	| binding action |
+ 	(encoder classEncoding instVarNames includes: proposedVariable) ifTrue: [
+ 		^ InstanceVariableNode new 
- 	"Check if this is an i-var, that has been corrected already (ugly)"
- 
- 	"Display the pop-up menu"
- 
- 	| binding userSelection action |
- 	(encoder classEncoding instVarNames includes: proposedVariable) ifTrue: 
- 		[^InstanceVariableNode new 
  			name: proposedVariable
  			index: (encoder classEncoding allInstVarNames indexOf: proposedVariable)].
+ 	
- 
  	"First check to see if the requestor knows anything about the variable"
  	(binding := cue requestor ifNotNil: [:object | object bindingOf: proposedVariable])
+ 		ifNotNil: [^ encoder global: binding name: proposedVariable].
+ 	
- 		ifNotNil: [^encoder global: binding name: proposedVariable].
- 
  	"If we can't ask the user for correction, make it undeclared"
+ 	self interactive ifFalse: [^ encoder undeclared: proposedVariable].
+ 	
+ 	self selectFrom: spot first to: spot last during: [
+ 		"Build the menu with alternatives"
+ 		action := UndeclaredVariable 
+ 			signalFor: self
+ 			name: proposedVariable
+ 			inRange: spot.
+ 		action ifNil: [^ self fail]].
+ 	
- 	self interactive ifFalse: [^encoder undeclared: proposedVariable].
- 
- 	userSelection := cue requestor selectionInterval.
- 	cue requestor selectFrom: spot first to: spot last.
- 	cue requestor select.
- 
- 	"Build the menu with alternatives"
- 	action := UndeclaredVariable 
- 				signalFor: self
- 				name: proposedVariable
- 				inRange: spot.
- 	action ifNil: [^self fail].
- 
  	"Execute the selected action"
- 	cue requestor deselect.
- 	cue requestor selectInvisiblyFrom: userSelection first to: userSelection last.
  	^action value!

Item was changed:
  ----- Method: Parser>>queryUndefined (in category 'error correction') -----
  queryUndefined
  	| varStart varName | 
  	varName := parseNode key.
  	varStart := self endOfLastToken + requestorOffset - varName size + 1.
+ 	self selectFrom: varStart to: varStart + varName size - 1 during: [
+ 		(UndefinedVariable name: varName) ifFalse: [^ self fail]].!
- 	cue requestor selectFrom: varStart to: varStart + varName size - 1; select.
- 	(UndefinedVariable name: varName) ifFalse: [^ self fail]!

Item was added:
+ ----- Method: Parser>>selectFrom:to:during: (in category 'error correction') -----
+ selectFrom: start to: stop during: aBlock
+ 	
+ 	| userSelection |
+ 	userSelection := cue requestor selectionInterval.
+ 	cue requestor
+ 		selectFrom: start to: stop;
+ 		select.
+ 	aBlock value.
+ 	cue requestor
+ 		deselect;
+ 		selectInvisiblyFrom: userSelection first to: userSelection last.!



More information about the Squeak-dev mailing list