[Pkg] The Trunk: Compiler-cwp.247.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jan 1 23:59:57 UTC 2013


Colin Putney uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-cwp.247.mcz

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

Name: Compiler-cwp.247
Author: cwp
Time: 1 January 2013, 6:59:31.461 pm
UUID: 22f2cbf1-9186-4d2f-8c9c-dffcc0518ffa
Ancestors: Compiler-cwp.246

Environments bootstrap - stage 3

=============== Diff against Compiler-cwp.246 ===============

Item was changed:
  ----- Method: Compiler>>compiledMethodFor:in:to:notifying:ifFail:logged: (in category 'public access') -----
  compiledMethodFor: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag
  	"Compiles the sourceStream into a parse tree, then generates code
  	 into a method, and answers it.  If receiver is not nil, then the text can
  	 refer to instance variables of that receiver (the Inspector uses this).
  	 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."
  
+ 	| methodNode method theClass |
+ 	theClass := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class.
+ 	self from: textOrStream class: theClass context: aContext notifying: aRequestor.
- 	| methodNode method |
- 	class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class.
- 	self from: textOrStream class: class context: aContext notifying: aRequestor.
  	methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value].
  	method := self interactive ifTrue: [ 	methodNode generateWithTempNames ] 
  		ifFalse: [methodNode generate].
  		
  	logFlag ifTrue:
  		[SystemChangeNotifier uniqueInstance evaluated: sourceStream contents context: aContext].
  	^method!

Item was changed:
  ----- Method: Compiler>>format:noPattern:ifFail: (in category 'private') -----
  format: aStream noPattern: noPattern ifFail: failBlock
  	^(self parser
  		parse: aStream
+ 		cue: cue 
- 		class: class
  		noPattern: noPattern
- 		context: context
- 		notifying: requestor
  		ifFail: [^failBlock value]) preen!

Item was changed:
  ----- Method: Compiler>>interactive (in category 'private') -----
  interactive
  	"Answer true if compilation is interactive"
  
+ 	^ cue requestor notNil!
- 	^requestor notNil!

Item was changed:
  ----- Method: Compiler>>notify:at: (in category 'error handling') -----
  notify: aString at: location
  	"Refer to the comment in Object|notify:."
  
+ 	^ cue requestor == nil
- 	^requestor == nil
  		ifTrue: [SyntaxErrorNotification
+ 					inClass: cue getClass
+ 					category: cue category
- 					inClass: class
- 					category: category
  					withCode: 
  						(sourceStream contents
  							copyReplaceFrom: location
  							to: location - 1
  							with: aString)
  					doitFlag: false
  					errorMessage: aString
  					location: location]
+ 		ifFalse: [cue requestor
- 		ifFalse: [requestor
  					notify: aString
  					at: location
  					in: sourceStream]!

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 context: nil notifying: req.
  	^self parser
  		parse: sourceStream
+ 		cue: cue
- 		class: class
  		noPattern: false
- 		context: context
- 		notifying: requestor
  		ifFail: []!

Item was changed:
  ----- Method: Compiler>>parser (in category 'public access') -----
  parser
  
+ 	parser ifNil: [parser := (cue getClass ifNil: [self class]) newParser].
- 	parser ifNil: [parser := (class ifNil: [self class]) newParser].
  	^parser!

Item was changed:
  ----- Method: Compiler>>translate:noPattern:ifFail: (in category 'private') -----
  translate: aStream noPattern: noPattern ifFail: failBlock
  	^self parser
  		parse: aStream
+ 		cue: cue 
- 		class: class
- 		category: category
  		noPattern: noPattern
- 		context: context
- 		notifying: requestor
  		ifFail: [^failBlock value]!

Item was changed:
  ----- Method: Compiler>>translate:noPattern:ifFail:parser: (in category 'public access') -----
  translate: aStream noPattern: noPattern ifFail: failBlock parser: parser
  	| tree |
  	tree := parser
  			parse: aStream
+ 			cue: cue 
- 			class: class
  			noPattern: noPattern
- 			context: context
- 			notifying: requestor
  			ifFail: [^ failBlock value].
  	^ tree!

Item was changed:
  ----- Method: Encoder>>associationForClass (in category 'results') -----
  associationForClass
  	| assoc |
+ 	assoc := self environment associationAt: cue getClass name ifAbsent: [nil].
+ 	^assoc value == cue getClass
- 	assoc := self environment associationAt: class name ifAbsent: [nil].
- 	^assoc value == class
  		ifTrue: [assoc]
+ 		ifFalse: [Association new value: cue getClass]!
- 		ifFalse: [Association new value: class]!

Item was changed:
  ----- Method: Encoder>>bindTemp:in: (in category 'temps') -----
  bindTemp: name in: methodSelector
  	"Declare a temporary; error not if a field or class variable."
  	scopeTable at: name ifPresent:[:node|
  		"When non-interactive raise the error only if its a duplicate"
  		(node isTemp or:[requestor interactive])
  			ifTrue:[^self notify:'Name is already defined']
  			ifFalse:[Transcript 
+ 				show: '(', name, ' is shadowed in "' , cue getClass printString , '>>' , methodSelector printString , '")']].
- 				show: '(', name, ' is shadowed in "' , class printString , '>>' , methodSelector printString , '")']].
  	^self reallyBind: name!

Item was changed:
  ----- Method: Encoder>>classEncoding (in category 'private') -----
  classEncoding
  	"This is a hack so that the parser may findout what class it was parsing for when it wants to create a syntax error view."
+ 	^ cue getClass!
- 	^ class!

Item was changed:
  ----- Method: Encoder>>encodeLiteral: (in category 'encoding') -----
  encodeLiteral: object
  
  	^self
  		name: object
+ 		key: (cue  literalScannedAs: object notifying: self)
- 		key: (class literalScannedAs: object notifying: self)
  		class: LiteralNode
  		type: LdLitType
  		set: litSet!

Item was changed:
  ----- Method: Encoder>>encodeSelector: (in category 'encoding') -----
+ encodeSelector: aSelector
- encodeSelector: selector
  
  	^self
+ 		name: aSelector
+ 		key: aSelector
- 		name: selector
- 		key: selector
  		class: SelectorNode
  		type: SendType
  		set: selectorSet!

Item was changed:
  ----- Method: Encoder>>environment (in category 'encoding') -----
  environment
  	"Answer the environment of the current compilation context,
  	 be it in a class or global (e.g. a workspace)"
+ 	^cue environment!
- 	^class == nil
- 		ifTrue: [Smalltalk globals]
- 		ifFalse: [class environment]!

Item was changed:
  ----- Method: Encoder>>lookupInPools:ifFound: (in category 'private') -----
  lookupInPools: varName ifFound: assocBlock
  
  	^Symbol
  		hasInterned: varName
  		ifTrue:
  			[:sym|
+ 			(cue bindingOf: sym)
- 			(class bindingOf: sym)
  				ifNil: [^false]
  				ifNotNil: [:assoc| assocBlock value: assoc]]!

Item was changed:
  ----- Method: Encoder>>possibleNamesFor: (in category 'private') -----
  possibleNamesFor: proposedName
  	| results |
+ 	results := cue getClass 
+ 		possibleVariablesFor: proposedName 
+ 		continuedFrom: nil.
- 	results := class possibleVariablesFor: proposedName continuedFrom: nil.
  	^ proposedName correctAgainst: nil continuedFrom: results.
  !

Item was changed:
  ----- Method: Encoder>>possibleVariablesFor: (in category 'private') -----
  possibleVariablesFor: proposedVariable
  
  	| results |
  	results := proposedVariable correctAgainstDictionary: scopeTable
  								continuedFrom: nil.
  	proposedVariable first canBeGlobalVarInitial ifTrue:
+ 		[ results := cue getClass possibleVariablesFor: proposedVariable
- 		[ results := class possibleVariablesFor: proposedVariable
  						continuedFrom: results ].
  	^ proposedVariable correctAgainst: nil continuedFrom: results.
  !

Item was changed:
  ----- Method: Encoder>>undeclared: (in category 'encoding') -----
  undeclared: name
  	| sym |
  	requestor interactive ifTrue:
  		[requestor requestor == #error: ifTrue:
  			[requestor error: 'Undeclared'].
  		 ^self notify: 'Undeclared'].
  	"Allow knowlegeable clients to squash the undeclared warning if they want (e.g.
  	 Diffing pretty printers that are simply formatting text).  As this breaks
  	 compilation it should only be used by clients that want to discard the result
  	 of the compilation.  To squash the warning use e.g.
  		[Compiler format: code in: class notifying: nil decorated: false]
  			on: UndeclaredVariableWarning
  			do: [:ex| ex resume: false]"
  	sym := name asSymbol.
+ 	^(UndeclaredVariableWarning new name: name selector: selector class: cue getClass) signal
- 	^(UndeclaredVariableWarning new name: name selector: selector class: class) signal
  		ifTrue:
+ 			[| undeclared |
+ 			undeclared := cue environment undeclared.
+ 			undeclared at: sym put: nil.
+ 			self global: (undeclared associationAt: sym) name: sym]
- 			[Undeclared at: sym put: nil.
- 			self global: (Undeclared associationAt: sym) name: sym]
  		ifFalse:
  			[self global: (Association key: sym) name: sym]!

Item was changed:
  ----- Method: Encoder>>warnAboutShadowed: (in category 'private') -----
  warnAboutShadowed: name
  	requestor addWarning: name,' is shadowed'.
  	selector ifNotNil:
+ 		[Transcript cr; show: cue getClass name,'>>', selector, '(', name,' is shadowed)']!
- 		[Transcript cr; show: class name,'>>', selector, '(', name,' is shadowed)']!

Item was changed:
  ----- Method: Parser>>ambiguousSelector:inRange: (in category 'error correction') -----
  ambiguousSelector: aString inRange: anInterval
  	| 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.
- 	userSelection := requestor selectionInterval.
  	intervalWithOffset := anInterval first + requestorOffset to: anInterval last + requestorOffset.
+ 	cue requestor selectFrom: intervalWithOffset first to: intervalWithOffset last.
+ 	cue requestor select.
- 	requestor selectFrom: intervalWithOffset first to: intervalWithOffset last.
- 	requestor select.
  
  	"Build the menu with alternatives"
  	correctedSelector := AmbiguousSelector 
  			signalName: aString
  			inRange: intervalWithOffset.
  	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.
- 	requestor deselect.
- 	requestor selectInvisiblyFrom: userSelection first to: userSelection last + offset.
  	token := (correctedSelector readStream upTo: Character space) asSymbol!

Item was changed:
  ----- Method: Parser>>collectTemporaryDeclarationsFrom: (in category 'error correction') -----
  collectTemporaryDeclarationsFrom: methodNode
  	| tempsMarks str |
  	tempsMarks := OrderedCollection new.
+ 	str := cue requestor text asString.
- 	str := requestor text asString.
  	methodNode accept: (ParseNodeEnumerator
  		ofBlock: [ :aNode | 
  			| mark |
  			(aNode class canUnderstand: #tempsMark) 
  				ifTrue: 
  					[mark := aNode tempsMark.
  					(mark notNil and: [ mark between: 1 and: str size ] and: [ (str at: mark) = $| ])
  						ifTrue: [ tempsMarks addLast: aNode ]]]).
  	(tempsMark notNil and: [ tempsMark between: 1 and: str size ] and: [ (str at: tempsMark) = $| ])
  						ifTrue: [ tempsMarks addLast: self ].
  	^ tempsMarks sorted: [ :a :b | a tempsMark > b tempsMark ]!

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 userSelection |
  	"If we can't ask the user, assume that the keyword will be defined later"
  	self interactive ifFalse: [^proposedKeyword asSymbol].
  
+ 	userSelection := cue requestor selectionInterval.
+ 	cue requestor selectFrom: spots first first to: spots last last.
+ 	cue requestor select.
- 	userSelection := requestor selectionInterval.
- 	requestor selectFrom: spots first first to: spots last last.
- 	requestor select.
  
  	correctSelector := UnknownSelector name: proposedKeyword.
  	correctSelector ifNil: [^abortAction value].
  
+ 	cue requestor deselect.
+ 	cue requestor selectInvisiblyFrom: userSelection first to: userSelection last.
- 	requestor deselect.
- 	requestor selectInvisiblyFrom: userSelection first to: userSelection last.
  
  	self substituteSelector: correctSelector keywords wordIntervals: spots.
  	^(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.
  	rr 3/4/2004 10:26 : adds the option to define a new class. "
  
  	"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)].
  
  	"If we can't ask the user for correction, make it undeclared"
  	self interactive ifFalse: [^encoder undeclared: proposedVariable].
  
  	"First check to see if the requestor knows anything about the variable"
+ 	(binding := cue requestor bindingOf: proposedVariable)
- 	(binding := requestor bindingOf: proposedVariable)
  		ifNotNil: [^encoder global: binding name: proposedVariable].
+ 	userSelection := cue requestor selectionInterval.
+ 	cue requestor selectFrom: spot first to: spot last.
+ 	cue requestor select.
- 	userSelection := requestor selectionInterval.
- 	requestor selectFrom: spot first to: spot last.
- 	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.
- 	requestor deselect.
- 	requestor selectInvisiblyFrom: userSelection first to: userSelection last.
  	^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 userSelection blocksToVars |
  	(undeclared := encoder undeclaredTemps) isEmpty ifTrue:
  		[^self].
+ 	userSelection := cue requestor selectionInterval.
- 	userSelection := 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.
- 	requestor selectInvisiblyFrom: userSelection first to: userSelection last + requestorOffset.
  	ReparseAfterSourceEditing signal!

Item was changed:
  ----- Method: Parser>>defineClass: (in category 'error correction') -----
  defineClass: className 
  	"prompts the user to define a new class,  
  	asks for it's category, and lets the users edit further  
  	the definition"
  	| sym cat def d2 |
  	sym := className asSymbol.
  	cat := UIManager default request: 'Enter class category : ' initialAnswer: self encoder classEncoding theNonMetaClass category.
  	cat
  		ifEmpty: [cat := 'Unknown'].
  	def := 'Object subclass: #' , sym , '
  		instanceVariableNames: '''' 
  		classVariableNames: ''''
  		poolDictionaries: ''''
  		category: ''' , cat , ''''.
  	d2 := UIManager default request: 'Edit class definition : ' initialAnswer: def.
  	d2
  		ifEmpty: [d2 := def].
  	Compiler evaluate: d2.
  	^ encoder
+ 		global: (cue environment bindingOf: sym)
- 		global: (Smalltalk globals associationAt: sym)
  		name: sym!

Item was changed:
  ----- Method: Parser>>externalFunctionDeclaration (in category 'primitives') -----
  externalFunctionDeclaration
  	"Parse the function declaration for a call to an external library."
  	| descriptorClass callType modifier retType externalName args argType module fn |
+ 	descriptorClass := cue environment
+ 		valueOf: #ExternalFunction 
+ 		ifAbsent: [^ false].
- 	descriptorClass := Smalltalk at: #ExternalFunction ifAbsent:[nil].
- 	descriptorClass == nil ifTrue:[^false].
  	callType := descriptorClass callingConventionFor: here.
  	callType == nil ifTrue:[^false].
  	[modifier := descriptorClass callingConventionModifierFor: token.
  	 modifier notNil] whileTrue:
  		[self advance.
  		 callType := callType bitOr: modifier].
  	"Parse return type"
  	self advance.
  	retType := self externalType: descriptorClass.
  	retType == nil ifTrue:[^self expected:'return type'].
  	"Parse function name or index"
  	externalName := here.
  	(self match: #string) 
  		ifTrue:[externalName := externalName asSymbol]
  		ifFalse:[(self match:#number) ifFalse:[^self expected:'function name or index']].
  	(self matchToken: #'(') ifFalse:[^self expected:'argument list'].
  	args := WriteStream on: Array new.
  	[here == #')'] whileFalse:[
  		argType := self externalType: descriptorClass.
  		argType == nil ifTrue:[^self expected:'argument'].
  		argType isVoid & argType isPointerType not ifFalse:[args nextPut: argType].
  	].
  	(self matchToken: #')') ifFalse:[^self expected:')'].
  	(self matchToken: 'module:') ifTrue:[
  		module := here.
  		(self match: #string) ifFalse:[^self expected: 'String'].
  		module := module asSymbol].
  	Smalltalk at: #ExternalLibraryFunction ifPresent:[:xfn|
  		fn := xfn name: externalName 
  				module: module 
  				callType: callType
  				returnType: retType
  				argumentTypes: args contents.
  		self allocateLiteral: fn.
  	].
  	(self matchToken: 'error:')
  		ifTrue:
  			[| errorCodeVariable |
  			 errorCodeVariable := here.
  			(hereType == #string
  			 or: [hereType == #word]) ifFalse:[^self expected: 'error code (a variable or string)'].
  			 self advance.
  			 self addPragma: (Pragma keyword: #primitive:error: arguments: (Array with: 120 with: errorCodeVariable)).
  			 fn ifNotNil: [fn setErrorCodeName: errorCodeVariable]]
  		ifFalse:
  			[self addPragma: (Pragma keyword: #primitive: arguments: #(120))].
  	^true
  !

Item was changed:
  ----- Method: Parser>>interactive (in category 'error handling') -----
  interactive
  	"Answer true if compilation is interactive"
  
+ 	^ cue requestor notNil!
- 	^requestor notNil!

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

Item was changed:
  ----- Method: Parser>>pasteTempAtMethodLevel: (in category 'error correction') -----
  pasteTempAtMethodLevel: name
  	| insertion delta theTextString characterBeforeMark |
  
+ 	theTextString := cue requestor text string.
- 	theTextString := requestor text string.
  	characterBeforeMark := theTextString at: tempsMark-1 ifAbsent: [$ ].
  	(theTextString at: tempsMark) = $| ifTrue: [
    		"Paste it before the second vertical bar"
  		insertion := name, ' '.
  		characterBeforeMark isSeparator ifFalse: [insertion := ' ', insertion].
  		delta := 0.
  	] ifFalse: [
  		"No bars - insert some with CR, tab"
  		insertion := '| ' , name , ' |',String cr.
  		delta := 2.	"the bar and CR"
  		characterBeforeMark = Character tab ifTrue: [
  			insertion := insertion , String tab.
  			delta := delta + 1.	"the tab"
  		].
  	].
  	tempsMark := tempsMark +
  		(self substituteWord: insertion
  			wordInterval: (tempsMark to: tempsMark-1)
  			offset: 0) - delta!

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

Item was changed:
  ----- Method: Parser>>removeEmptyTempDeclarationsFrom: (in category 'error correction') -----
  removeEmptyTempDeclarationsFrom: methodNode
  
  	| sourceCode madeChanges tempsMarkHolder |
+ 	sourceCode := cue requestor text asString.
- 	sourceCode := requestor text asString.
  	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
  	madeChanges := false.
  	tempsMarkHolder do: [ :currentBlock | | tempsMarkChar0 tempsMarkChar1 tempsMarkChar2 end start |
  		tempsMarkChar0 := (sourceCode at: currentBlock tempsMark).
  		tempsMarkChar1 := (sourceCode at: currentBlock tempsMark - 1).
  		tempsMarkChar2 := (sourceCode at: currentBlock tempsMark - 2).
  		tempsMarkChar0 = $| & tempsMarkChar1 = $| 
  			ifTrue: 
  				[ end := currentBlock tempsMark. 
  				start := end - 1].
  		tempsMarkChar0 = $| & tempsMarkChar1 = $  & tempsMarkChar2 = $| 
  			ifTrue: 
  				[ end := currentBlock tempsMark. 
  				start := end - 2].
  		
  		start notNil & end notNil ifTrue: [
  			| lineStart lineEnd |
  			lineStart := 1 + (sourceCode 
  				lastIndexOf: Character cr 
  				startingAt: start - 1
  				ifAbsent: [ 0 ]).
  			lineEnd := sourceCode 
  				indexOf: Character cr
  				startingAt: end + 1
  				ifAbsent: [ sourceCode size ].
  			((sourceCode indexOfAnyOf: CharacterSet nonSeparators startingAt: lineStart) >= start 
  				and: [ (sourceCode indexOfAnyOf: CharacterSet nonSeparators startingAt: end + 1) > lineEnd ]) ifTrue: [
  					start := lineStart.
  					end := lineEnd ].
+ 			cue requestor correctFrom: start to: end with: ''.
- 			requestor correctFrom: start to: end with: ''.
  			madeChanges := true.
  			currentBlock tempsMark: nil ] ].
  	madeChanges ifTrue: [ReparseAfterSourceEditing signal]!

Item was changed:
  ----- Method: Parser>>removeUnusedTemporaryNamed:from:lookingAt:movingTempMarksOf: (in category 'error correction') -----
  removeUnusedTemporaryNamed: temp from: str lookingAt: currentBlock movingTempMarksOf: someBlocks
  
  	| start end |
  	end := currentBlock tempsMark - 1.
  	["Beginning at right temp marker..."
  	start := end - temp size + 1.
  	end < temp size or: [ (str at: start) = $| ]
  		or: [ temp = (str copyFrom: start to: end) 
  			and: [ ((str at: start - 1) = $| | (str at: start - 1) isSeparator) 
  				& ((str at: end + 1) = $| | (str at: end + 1) isSeparator) ] ]]
  		whileFalse: [ 
  			"Search left for the unused temp"
+ 			end := cue requestor nextTokenFrom: end direction: -1 ].
- 			end := requestor nextTokenFrom: end direction: -1 ].
  	(end < temp size or: [ (str at: start) = $| ])
  		ifFalse: 
  			[(str at: start - 1) = $ 
  				ifTrue: [ start := start - 1 ].
+ 			cue requestor correctFrom: start to: end with: ''.
- 			requestor correctFrom: start to: end with: ''.
  			someBlocks do: [ :aBlock | aBlock tempsMark: aBlock tempsMark - (end - start + 1)].
  			^true ].
  	^false!

Item was changed:
  ----- Method: Parser>>removeUnusedTemps: (in category 'error correction') -----
  removeUnusedTemps: methodNode
  	"Scan for unused temp names, and prompt the user about the prospect of removing each one found"
  
  	| madeChanges tempsMarkHolder unusedTempNames tempMarkHoldersToChange |
  	madeChanges := false.
  	tempMarkHoldersToChange := OrderedCollection new.
  	tempsMarkHolder := self collectTemporaryDeclarationsFrom: methodNode.
  	unusedTempNames := encoder unusedTempNames select: 
  		[ :temp | (encoder lookupVariable: temp ifAbsent: [ ]) isUndefTemp 
  				and: [ self queriedUnusedTemporaries at: temp ifAbsentPut: [UnusedVariable name: temp] ]].
  	tempsMarkHolder do: [ :currentBlock | 
  		tempMarkHoldersToChange add: currentBlock.
  		unusedTempNames do: 
  			[ :temp |
  			(self 
  				removeUnusedTemporaryNamed: temp 
+ 				from: cue requestor text asString 
- 				from: requestor text asString 
  				lookingAt: currentBlock
  				movingTempMarksOf: tempMarkHoldersToChange) ifTrue: [ madeChanges := true ]]].
  	madeChanges
  		ifTrue: [ self removeEmptyTempDeclarationsFrom: methodNode.
  			ReparseAfterSourceEditing signal ]!

Item was changed:
  ----- Method: Parser>>substituteWord:wordInterval:offset: (in category 'error correction') -----
  substituteWord: correctWord wordInterval: spot offset: o
  	"Substitute the correctSelector into the (presumed interactive) receiver.
  	 Update requestorOffset based on the delta size and answer the updated offset."
  
+ 	cue requestor correctFrom: spot first + o to: spot last + o with: correctWord.
- 	requestor correctFrom: spot first + o to: spot last + o with: correctWord.
  	requestorOffset := requestorOffset + correctWord size - spot size.
  	^o + correctWord size - spot size!

Item was changed:
  ----- Method: Parser>>temporaries (in category 'expression types') -----
  temporaries
  	" [ '|' (variable)* '|' ]"
  	| vars theActualText |
  	(self match: #verticalBar) ifFalse: 
  		["no temps"
  		doitFlag ifTrue:
  			[tempsMark := self interactive
+ 								ifTrue: [cue requestor selectionInterval first]
- 								ifTrue: [requestor selectionInterval first]
  								ifFalse: [1].
  			^ #()].
  		tempsMark := hereMark	"formerly --> prevMark + prevToken".
  		tempsMark > 0 ifTrue:
  			[theActualText := source contents.
  			[tempsMark < theActualText size and: [(theActualText at: tempsMark) isSeparator]]
  				whileTrue: [tempsMark := tempsMark + 1]].
  			^ #()].
  	vars := OrderedCollection new.
  	[hereType == #word]
  		whileTrue: [vars addLast: (encoder bindTemp: self advance)].
  	(self match: #verticalBar) ifTrue: 
  		[tempsMark := prevMark.
  		^ vars].
  	^ self expected: 'Vertical bar'
  !

Item was changed:
  ----- Method: Parser>>temporariesIn: (in category 'expression types') -----
  temporariesIn: methodSelector
  	" [ '|' (variable)* '|' ]"
  	| vars theActualText |
  	(self match: #verticalBar) ifFalse: 
  		["no temps"
  		doitFlag ifTrue:
  			[tempsMark := self interactive
+ 								ifTrue: [cue requestor selectionInterval first]
- 								ifTrue: [requestor selectionInterval first]
  								ifFalse: [1].
  			^ #()].
  		tempsMark := hereMark	"formerly --> prevMark + prevToken".
  		tempsMark > 0 ifTrue:
  			[theActualText := source contents.
  			[tempsMark < theActualText size and: [(theActualText at: tempsMark) isSeparator]]
  				whileTrue: [tempsMark := tempsMark + 1]].
  			^ #()].
  	vars := OrderedCollection new.
  	[hereType == #word]
  		whileTrue: [vars addLast: (encoder bindTemp: self advance in: methodSelector)].
  	(self match: #verticalBar) ifTrue: 
  		[tempsMark := prevMark.
  		^ vars].
  	^ self expected: 'Vertical bar'!



More information about the Packages mailing list