[squeak-dev] The Inbox: Kernel-spd.444.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Dec 4 18:30:31 UTC 2010


A new version of Kernel was added to project The Inbox:
http://source.squeak.org/inbox/Kernel-spd.444.mcz

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

Name: Kernel-spd.444
Author: spd
Time: 4 December 2010, 1:30:09.425 pm
UUID: 571950b9-31b4-4f85-b27f-e4b7e6044b27
Ancestors: Kernel-ar.443

* 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:

n.b. no conflicts with trunk as of 12/4/2010

=============== Diff against Kernel-ar.443 ===============

Item was removed:
- ----- Method: BlockContext>>valueWithEnoughArguments: (in category 'evaluating') -----
- valueWithEnoughArguments: anArray
- 	"call me with enough arguments from anArray"
- 	| args |
- 	(anArray size == self numArgs)
- 		ifTrue: [ ^self valueWithArguments: anArray ].
- 
- 	args := Array new: self numArgs.
- 	args replaceFrom: 1
- 		to: (anArray size min: args size)
- 		with: anArray
- 		startingAt: 1.
- 
- 	^ self valueWithArguments: args!

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!

Item was removed:
- ----- Method: MessageSend>>valueWithEnoughArguments: (in category 'evaluating') -----
- valueWithEnoughArguments: anArray
- 	"call the selector with enough arguments from arguments and anArray"
- 	| args |
- 	args := Array new: selector numArgs.
- 	args replaceFrom: 1
- 		to: (arguments size min: args size)
- 		with: arguments
- 		startingAt: 1.
- 	args size > arguments size ifTrue: [
- 		args replaceFrom: arguments size + 1
- 			to: (arguments size + anArray size min: args size)
- 			with: anArray
- 			startingAt: 1.
- 	].
- 	^ receiver perform: selector withArguments: args!

Item was removed:
- ----- Method: Object>>actionsWithReceiver:forEvent: (in category 'events') -----
- actionsWithReceiver: anObject forEvent: anEventSelector
- 
- 	^(self actionSequenceForEvent: anEventSelector)
-                 select: [:anAction | anAction receiver == anObject ]!

Item was removed:
- ----- Method: Object>>assert:description: (in category 'error handling') -----
- assert: aBlock description: aString
- 	"Throw an assertion error if aBlock does not evaluates to true."
- 
- 	aBlock value ifFalse: [AssertionFailure signal: aString ]!

Item was removed:
- ----- Method: Object>>assert:descriptionBlock: (in category 'error handling') -----
- assert: aBlock descriptionBlock: descriptionBlock
- 	"Throw an assertion error if aBlock does not evaluate to true."
- 
- 	aBlock value ifFalse: [AssertionFailure signal: descriptionBlock value asString ]!

Item was removed:
- ----- Method: Object>>perform:withEnoughArguments: (in category 'message handling') -----
- perform: selector withEnoughArguments: anArray
- 	"Send the selector, aSymbol, to the receiver with arguments in argArray.
- 	Only use enough arguments for the arity of the selector; supply nils for missing ones."
- 	| numArgs args |
- 	numArgs := selector numArgs.
- 	anArray size == numArgs
- 		ifTrue: [ ^self perform: selector withArguments: anArray asArray ].
- 
- 	args := Array new: numArgs.
- 	args replaceFrom: 1
- 		to: (anArray size min: args size)
- 		with: anArray
- 		startingAt: 1.
- 
- 	^ self perform: selector withArguments: args!

Item was removed:
- ----- Method: Object>>renameActionsWithReceiver:forEvent:toEvent: (in category 'events') -----
- renameActionsWithReceiver: anObject forEvent: anEventSelector toEvent: newEvent
- 
- 	| oldActions newActions |
- 	oldActions := Set new.
- 	newActions := Set new.
- 	(self actionSequenceForEvent: anEventSelector) do: [ :action |
- 		action receiver == anObject
- 			ifTrue: [ oldActions add: anObject ]
- 			ifFalse: [ newActions add: anObject ]].
- 	self setActionSequence: (ActionSequence withAll: newActions) forEvent: anEventSelector.
- 	oldActions do: [ :act | self when: newEvent evaluate: act ].!

Item was changed:
  ----- Method: StringHolder class>>open (in category 'instance creation') -----
  open
+ 	^ (Smalltalk at: #Workspace ifAbsent:[self]) new openLabel: 'Workspace'
- 	(Smalltalk at: #Workspace ifAbsent:[self]) new openLabel: 'Workspace'
  		"Not to be confused with our own class var 'Workspace'"!




More information about the Squeak-dev mailing list