The Trunk: Kernel-ar.401.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-ar.401.mcz

commits-2
Andreas Raab uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-ar.401.mcz

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

Name: Kernel-ar.401
Author: ar
Time: 13 February 2010, 3:13:52.934 pm
UUID: a3240363-adee-4943-ba9b-a4e36a98b628
Ancestors: Kernel-nice.400

Raise DuplicateVariableError in ClassBuilder.

=============== Diff against Kernel-nice.400 ===============

Item was changed:
  ----- Method: ClassBuilder>>validateClassvars:from:forSuper: (in category 'validation') -----
  validateClassvars: classVarArray from: oldClass forSuper: newSuper
  "Check if any of the classVars of oldClass conflict with the new superclass"
  | usedNames classVars temp |
  classVarArray isEmpty ifTrue:[^true]. "Okay"
 
  "Validate the class var names"
  usedNames := classVarArray asSet.
  usedNames size = classVarArray size
  ifFalse:[ classVarArray do:[:var|
  usedNames remove: var ifAbsent:[temp := var]].
  self error: temp,' is multiply defined'. ^false].
  (usedNames includesAnyOf: self reservedNames)
  ifTrue:[ self reservedNames do:[:var|
  (usedNames includes: var) ifTrue:[temp := var]].
  self error: temp,' is a reserved name'. ^false].
 
  newSuper == nil ifFalse:[
  usedNames := newSuper allClassVarNames asSet.
  classVarArray do:[:iv|
  (usedNames includes: iv) ifTrue:[
  newSuper withAllSuperclassesDo:[:cl|
  (cl classVarNames includes: iv) ifTrue:[temp := cl]].
+ (DuplicateVariableError new)
+ superclass: temp;
+ variable: iv;
+ signal: iv,' is already defined in ', temp name]]].
- self error: iv, ' is already defined in ', temp name.
- ^false]]].
 
  oldClass == nil ifFalse:[
  usedNames := Set new: 20.
  oldClass allSubclassesDo:[:cl| usedNames addAll: cl classVarNames].
  classVars := classVarArray.
  newSuper == nil ifFalse:[classVars := classVars, newSuper allClassVarNames asArray].
  classVars do:[:iv|
  (usedNames includes: iv) ifTrue:[
+ (DuplicateVariableError new)
+ superclass: oldClass;
+ variable: iv;
+ signal: iv, ' is already defined in a subclass of ', oldClass name]]].
- self error: iv, ' is already defined in a subclass of ', oldClass name.
- ^false]]].
  ^true!

Item was changed:
  ----- Method: ClassDescription>>instVarMappingFrom: (in category 'private') -----
  instVarMappingFrom: oldClass
  "Return the mapping from instVars of oldClass to new class that is used for converting old instances of oldClass."
  | oldInstVarNames |
  oldInstVarNames := oldClass allInstVarNames.
+ "Using #lastIndexOf: to ensure proper behavior in case where we have duplicate ivars."
+ ^self allInstVarNames collect: [:instVarName | oldInstVarNames lastIndexOf: instVarName].!
- ^self allInstVarNames
- collect: [:instVarName | oldInstVarNames indexOf: instVarName].!

Item was changed:
  ----- Method: ClassBuilder>>validateInstvars:from:forSuper: (in category 'validation') -----
  validateInstvars: instVarArray from: oldClass forSuper: newSuper
  "Check if any of the instVars of oldClass conflict with the new superclass"
  | instVars usedNames temp |
  instVarArray isEmpty ifTrue:[^true]. "Okay"
  newSuper allowsSubInstVars ifFalse: [
  self error: newSuper printString, ' does not allow subclass inst vars. See allowsSubInstVars.'. ^ false].
 
  "Validate the inst var names"
  usedNames := instVarArray asSet.
  usedNames size = instVarArray size
  ifFalse:[ instVarArray do:[:var|
  usedNames remove: var ifAbsent:[temp := var]].
  self error: temp,' is multiply defined'. ^false].
  (usedNames includesAnyOf: self reservedNames)
  ifTrue:[ self reservedNames do:[:var|
  (usedNames includes: var) ifTrue:[temp := var]].
  self error: temp,' is a reserved name'. ^false].
 
  newSuper == nil ifFalse:[
  usedNames := newSuper allInstVarNames asSet.
  instVarArray do:[:iv|
  (usedNames includes: iv) ifTrue:[
  newSuper withAllSuperclassesDo:[:cl|
  (cl instVarNames includes: iv) ifTrue:[temp := cl]].
+ (DuplicateVariableError new)
+ superclass: temp;
+ variable: iv;
+ signal: iv,' is already defined in ', temp name]]].
- self error: iv,' is already defined in ', temp name.
- ^false]]].
  oldClass == nil ifFalse:[
  usedNames := Set new: 20.
  oldClass allSubclassesDo:[:cl| usedNames addAll: cl instVarNames].
  instVars := instVarArray.
  newSuper == nil ifFalse:[instVars := instVars, newSuper allInstVarNames].
  instVars do:[:iv|
  (usedNames includes: iv) ifTrue:[
+ (DuplicateVariableError new)
+ superclass: oldClass;
+ variable: iv;
+ signal: iv,' is already defined in a subclass of ', temp name]]].
- self error: iv, ' is already defined in a subclass of ', oldClass name.
- ^false]]].
  ^true!

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 bindingOf: var) ifNotNil:[
+ (DuplicateVariableError new)
+ superclass: superclass; "fake!!!!!!"
+ variable: var;
+ signal: var , ' is 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!

Item was changed:
  SystemOrganization addCategory: #'Kernel-Chronology'!
  SystemOrganization addCategory: #'Kernel-Classes'!
  SystemOrganization addCategory: #'Kernel-Methods'!
  SystemOrganization addCategory: #'Kernel-Numbers'!
  SystemOrganization addCategory: #'Kernel-Objects'!
  SystemOrganization addCategory: #'Kernel-Processes'!
  SystemOrganization addCategory: #'Kernel-Models'!
+ SystemOrganization addCategory: #'Kernel-Tests-ClassBuilder'!