[squeak-dev] The Trunk: Kernel-nice.545.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Feb 13 20:26:02 UTC 2011


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

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

Name: Kernel-nice.545
Author: nice
Time: 13 February 2011, 9:25:27.036 pm
UUID: e5d876d4-c609-4776-b5e6-7266e46f842e
Ancestors: Kernel-nice.544

Merge Kernel-spd.444 to allow shadowing of a global namespace variable by a local class variable or shared pool variable.
RATIONALE: forbiding this shadowing works against encapsulation. It prevents packages with a local class var from loading when a concurrent package defined a global. Forbiding is thus like reserving every class var name. Non sense.

Kernel-spd.444 did also remove some methods, but I did not replay those changes as they are unrelated and undocumented.

* fixed Class>>canFindWithoutEnvironment: (it was actually checking the environment, making the behavior like bindingOf:) and added test to KernelTests
* changed Class>>declare: and Class>>addClassVarName:
	- no longer check the environment for conflicts
	- conflict error message clarified
* made conflict error in #addClassVarName: resumable to match the behavior of #declare:

=============== Diff against Kernel-nice.544 ===============

Item was changed:
  ----- Method: Class>>addClassVarName: (in category 'class variables') -----
  addClassVarName: aString 
  	"Add the argument, aString, as a class variable of the receiver.
  	Signal an error if the first character of aString is not capitalized,
  	or if it is already a variable named in the class."
  	| symbol oldState |
  	oldState := self copy.
  	aString first canBeGlobalVarInitial
  		ifFalse: [^self error: aString, ' class variable name should be capitalized; proceed to include anyway.'].
  	symbol := aString asSymbol.
  	self withAllSubclasses do: 
  		[:subclass | 
+ 		(self canFindWithoutEnvironment: symbol) ifTrue: [
+ 			(DuplicateVariableError new)
+ 				superclass: superclass; "fake!!!!!!"
+ 				variable: aString;
+ 				signal: aString, ' is already defined']].
- 		(subclass bindingOf: symbol) ifNotNil:[
- 			^ self error: aString 
- 				, ' is already used as a variable name in class ' 
- 				, subclass name]].
  	classPool == nil ifTrue: [classPool := Dictionary new].
  	(classPool includesKey: symbol) ifFalse: 
  		["Pick up any refs in Undeclared"
  		classPool declare: symbol from: Undeclared.
  		SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: oldState to: self]!

Item was changed:
  ----- Method: Class>>canFindWithoutEnvironment: (in category 'compiling') -----
  canFindWithoutEnvironment: varName
  	"This method is used for analysis of system structure -- see senders."
  	"Look up varName, in the context of the receiver. Return true if it can be found without using the declared environment."
  
  	"First look in classVar dictionary."
  	(self classPool bindingOf: varName) ifNotNil:[^true].
  
  	"Next look in shared pools."
  	self sharedPools do:[:pool | 
  		(pool bindingOf: varName) ifNotNil:[^true].
  	].
  
  	"Finally look higher up the superclass chain and fail at the end."
  	superclass == nil
  		ifTrue: [^ false]
+ 		ifFalse: [^ superclass canFindWithoutEnvironment: varName].
- 		ifFalse: [^ (superclass bindingOf: varName) notNil].
  
  !

Item was changed:
  ----- Method: Class>>declare: (in category 'initialize-release') -----
  declare: varString 
  	"Declare class variables common to all instances. Answer whether 
  	recompilation is advisable."
  
  	| newVars conflicts |
+ 	
  	newVars := 
  		(Scanner new scanFieldNames: varString)
  			collect: [:x | x asSymbol].
  	newVars do:
  		[:var | var first canBeGlobalVarInitial
  			ifFalse: [self error: var, ' class variable name should be capitalized; proceed to include anyway.']].
  	conflicts := false.
  	classPool == nil 
  		ifFalse: [(classPool keys reject: [:x | newVars includes: x]) do: 
  					[:var | self removeClassVarName: var]].
  	(newVars reject: [:var | self classPool includesKey: var])
  		do: [:var | "adding"
  			"check if new vars defined elsewhere"
+ 			(self canFindWithoutEnvironment: var) ifTrue: [
- 			(self bindingOf: var) ifNotNil:[
  					(DuplicateVariableError new)
  						superclass: superclass; "fake!!!!!!"
  						variable: var;
+ 						signal: var, ' is already defined'.
- 						signal: var , ' is defined elsewhere'.
  					conflicts := true]].
  	newVars size > 0
  		ifTrue: 
  			[classPool := self classPool.
  			"in case it was nil"
  			newVars do: [:var | classPool declare: var from: Undeclared]].
  	^conflicts!




More information about the Squeak-dev mailing list