The Trunk: Compiler-nice.428.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Compiler-nice.428.mcz

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

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

Name: Compiler-nice.428
Author: nice
Time: 9 May 2020, 12:24:17.077079 am
UUID: 04b649b2-1b1b-486b-aa82-15b219803431
Ancestors: Compiler-nice.427

Use the idea from Compiler-ct.423: define selectFrom:to:during: in Parser for handling temporary change of text selection - see method comment.

=============== Diff against Compiler-nice.427 ===============

Item was changed:
  ----- Method: Parser>>ambiguousSelector:inRange: (in category 'error correction') -----
  ambiguousSelector: aString inRange: anInterval
+ | correctedSelector intervalWithOffset |
- | correctedSelector userSelection 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
+ signalName: aString
+ inRange: intervalWithOffset.
+ correctedSelector ifNil: [^self fail]].
- cue requestor selectFrom: intervalWithOffset first to: intervalWithOffset last.
-
- "Build the menu with alternatives"
- correctedSelector := AmbiguousSelector
- signalName: aString
- inRange: intervalWithOffset.
- correctedSelector ifNil: [^self fail].
-
- "Restore the user selection state, but do not display selection yet
- This will avoid flashing effect when chaining multiple corrections."
- cue requestor selectIntervalInvisibly: userSelection.
 
  "Execute the selected action"
  self substituteWord: correctedSelector wordInterval: intervalWithOffset offset: 0.
  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.
-
- correctSelector := UnknownSelector name: proposedKeyword.
- correctSelector ifNil: [^abortAction value].
-
- "Restore the user selection state, but do not display selection yet
- This will avoid flashing effect when chaining multiple corrections."
- cue requestor selectIntervalInvisibly: userSelection.
-
  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 context is nil (class=UndefinedObject).
+ Spot is the interval within the test stream of the variable."
- 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 |
  "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].
 
  "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]].
- userSelection := cue requestor selectionInterval.
- cue requestor selectFrom: spot first to: spot last.
 
- "Build the menu with alternatives"
- action := UndeclaredVariable
- signalFor: self
- name: proposedVariable
- inRange: spot.
- action ifNil: [^self fail].
-
- "Restore the user selection state, but do not display selection yet
- This will avoid flashing effect when chaining multiple corrections."
- cue requestor selectIntervalInvisibly: userSelection.
-
  "Execute the selected action"
  ^action value!

Item was changed:
  ----- Method: Parser>>declareUndeclaredTemps: (in category 'error correction') -----
  declareUndeclaredTemps: methodNode
  "Declare any undeclared temps, declaring them at the smallest enclosing scope."
 
+ | undeclared blocksToVars |
- | undeclared userSelection blocksToVars |
  (undeclared := encoder undeclaredTemps) isEmpty ifTrue:
  [^self].
- userSelection := cue requestor selectionInterval.
  blocksToVars := IdentityDictionary new.
  undeclared do:
  [:var|
  (blocksToVars
  at: (var tag == #method
  ifTrue: [methodNode block]
  ifFalse: [methodNode accept: (VariableScopeFinder new ofVariable: var)])
  ifAbsentPut: [SortedCollection new]) add: var name].
  (blocksToVars removeKey: methodNode block ifAbsent: []) ifNotNil:
  [:rootVars|
  rootVars do: [:varName| self pasteTempAtMethodLevel: varName]].
  (blocksToVars keys sorted: [:a :b| a tempsMark < b tempsMark]) do:
  [:block| | decl |
  decl := (blocksToVars at: block) reduce: [:a :b| a, ' ', b].
  block temporaries isEmpty
  ifTrue:
  [self substituteWord: ' | ', decl, ' |'
  wordInterval: (block tempsMark + 1 to: block tempsMark)
  offset: requestorOffset]
  ifFalse:
  [self substituteWord: decl, ' '
  wordInterval: (block tempsMark to: block tempsMark - 1)
  offset: requestorOffset]].
- cue requestor selectInvisiblyFrom: userSelection first to: userSelection last + requestorOffset.
  ReparseAfterSourceEditing signal!

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.
- (UndefinedVariable name: varName) ifFalse: [^ self fail]!

Item was added:
+ ----- Method: Parser>>selectFrom:to:during: (in category 'error correction') -----
+ selectFrom: start to: stop during: aBlock
+ "Temporarily focus user attention on a zone of error thru text section.
+ Then restore original user selection.
+ Note: the original selection is restored invisibly (not displayed).
+ This will avoid flickering when chaining multiple corrections."
+
+ | userSelection |
+ userSelection := cue requestor selectionInterval.
+ cue requestor selectFrom: start to: stop.
+ aBlock value.
+ cue requestor selectIntervalInvisibly: userSelection!