The Trunk: Kernel-nice.274.mcz

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

The Trunk: Kernel-nice.274.mcz

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

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

Name: Kernel-nice.274
Author: nice
Time: 19 October 2009, 11:43:28 am
UUID: e0d13094-6ba6-9a48-8499-d9506f2b1d29
Ancestors: Kernel-nice.273

use #fasterKeys

My guess is that ClassDescription >> #organization and #classVariablesString should be traitified, so I did not publish my changes.
Though I got no warning, no indication of trait, no nothing...
I wonder how to work in a traitified image without trait aware tools...

=============== Diff against Kernel-nice.273 ===============

Item was changed:
  ----- Method: ClassBuilder class>>cleanupClassHierarchyFor: (in category 'cleanup obsolete classes') -----
  cleanupClassHierarchyFor: aClassDescription
 
  | myName mySuperclass |
  mySuperclass := aClassDescription superclass.
  (self isReallyObsolete: aClassDescription) ifTrue: [
 
  "Remove class >>>from SystemDictionary if it is obsolete"
  myName := aClassDescription name asString.
+ Smalltalk fasterKeys do: [:each |
- Smalltalk keys asArray do: [:each |
  (each asString = myName and: [(Smalltalk at: each) == aClassDescription])
  ifTrue: [Smalltalk removeKey: each]].
 
  "Make class officially obsolete if it is not"
  (aClassDescription name asString beginsWith: 'AnObsolete')
  ifFalse: [aClassDescription obsolete].
 
  aClassDescription isObsolete
  ifFalse: [self error: 'Something wrong!!'].
 
  "Add class to obsoleteSubclasses of its superclass"
  mySuperclass
  ifNil: [self error: 'Obsolete subclasses of nil cannot be stored'].
  (mySuperclass obsoleteSubclasses includes: aClassDescription)
  ifFalse: [mySuperclass addObsoleteSubclass: aClassDescription].
  ] ifFalse:[
  "check if superclass has aClassDescription in its obsolete subclasses"
  mySuperclass ifNil:[mySuperclass := Class]. "nil subclasses"
  mySuperclass removeObsoleteSubclass: aClassDescription.
  ].
  "And remove its obsolete subclasses if not actual superclass"
  aClassDescription obsoleteSubclasses do:[:obs|
  obs superclass == aClassDescription ifFalse:[
  aClassDescription removeObsoleteSubclass: obs]].
  !

Item was changed:
  ----- Method: Object>>removeActionsSatisfying: (in category 'events-removing') -----
  removeActionsSatisfying: aBlock
 
+ self actionMap fasterKeys do:
- self actionMap keys do:
  [:eachEventSelector |
  self
      removeActionsSatisfying: aBlock
  forEvent: eachEventSelector
  ]!

Item was changed:
  ----- Method: Class>>fileOutPool:onFileStream: (in category 'fileIn/Out') -----
  fileOutPool: aPool onFileStream: aFileStream
  | aPoolName aValue |
  (aPool  isKindOf: SharedPool class) ifTrue:[^self notify: 'we do not fileout SharedPool type shared pools for now'].
  aPoolName := self environment keyAtIdentityValue: aPool.
  Transcript cr; show: aPoolName.
  aFileStream nextPutAll: 'Transcript show: ''' , aPoolName , '''; cr!!'; cr.
  aFileStream nextPutAll: 'Smalltalk at: #' , aPoolName , ' put: Dictionary new!!'; cr.
+ aPool fasterKeys sort do: [ :aKey |
- aPool keys asSortedCollection do: [ :aKey |
  aValue := aPool at: aKey.
  aFileStream nextPutAll: aPoolName , ' at: #''' , aKey asString , '''', ' put:  '.
  (aValue isKindOf: Number)
  ifTrue: [aValue printOn: aFileStream]
  ifFalse: [aFileStream nextPutAll: '('.
  aValue printOn: aFileStream.
  aFileStream nextPutAll: ')'].
  aFileStream nextPutAll: '!!'; cr].
  aFileStream cr!

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 fasterKeys reject: [:x | newVars includes: x]) do:
- 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 bindingOf: var) notNil
  ifTrue:
  [self error: 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!