Refactoring of class names and namespaces in ClassChange (part 1). jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 12 Jun 2013 11:54:30 +0100
branchjv
changeset 3303 7ed5d48e3756
parent 3302 b5830a86fb93
child 3329 a4cbc797038b
Refactoring of class names and namespaces in ClassChange (part 1). The meaning of instvars in ClassChange was changed (well, actually it was defined), so: - className is the name of the class without any namespace prefix but including all owning classes. - nameSpaceName is the name of the original namespace of the class - nameSpaceOverride is client-enforced namespace namew - ownerClassName is the name of the owning class but without any namespace prefix. This commit actually fixes remaining RegressionTests::ChangeSetTests. CAUTION: currently, class names and namespace names are wrong when reading system changefile. This is due to a conceptual problem because there's no way how distinguish between namespace and owning class solely on the information in the changeset file. Next part of the refactoring should fix this, but at the cost of changing the changefile format. The impact to old tools not using ChangeSet but rather their own implementation must be investigated (tools like ChangesBrowser).
ChangeSet.st
ClassChange.st
ClassClassVariableChange.st
ClassCommentChange.st
ClassDefinitionChange.st
ClassRemoveChange.st
ClassRenameChange.st
Make.proto
Makefile.init
MethodCategoryChange.st
MethodCategoryRenameChange.st
MethodChange.st
MethodDefinitionChange.st
bc.mak
libbasic3.rc
--- a/ChangeSet.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ChangeSet.st	Wed Jun 12 11:54:30 2013 +0100
@@ -2225,6 +2225,7 @@
     timestamp := nil.
     change isClassChange ifTrue:[
         change package: Class packageQuerySignal query.
+        change nameSpace: Class nameSpaceQuerySignal query.
     ].
 
     changeAction 
@@ -2232,7 +2233,7 @@
         and:lineNumber 
         and:position.
 
-    "Modified: / 29-01-2013 / 19:32:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 15:57:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 checkReceiverIsGlobalNamed:expectedName
@@ -2313,6 +2314,13 @@
         clsName := clsName , ' class'.
     ].
 
+    "Strip off the namespace"
+    (classIsJava not and:[ nameSpace ~~ Smalltalk]) ifTrue:[
+        (clsName startsWith: nameSpace name) ifTrue:[
+            clsName := clsName copyFrom: nameSpace name size + 3.
+        ]
+    ].
+
     (nameSpace ~~ Smalltalk and:[(clsName startsWith: nameSpace name) not])
         ifTrue:[
             "/ old: remember namespace in name
@@ -2325,7 +2333,7 @@
             ^ clsName
         ].
 
-    "Modified: / 01-05-2013 / 17:57:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 17:55:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 extractMethodsClassAndSelectorFromReceiver
@@ -2433,7 +2441,6 @@
                         selector:selector
                         source:(parseTree printString)
                         category:(categories first).
-        change nameSpaceOverride:nameSpaceOverride.
         self addChange:change.
     ] ifFalse:[
         self halt:'multiple/missing categories not supported'.
@@ -2456,6 +2463,8 @@
         self halt:'multiple/missing attributes not supported'.
     ].
     ^ true
+
+    "Modified: / 11-06-2013 / 16:11:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleClassCommentChange
@@ -2465,10 +2474,11 @@
 
     change := ClassCommentChange new.
     change className:className comment:(arguments at:1) evaluate.
-    change nameSpaceOverride:nameSpaceOverride.
     change source:(parseTree printString).
     self addChange:change.
     ^ true
+
+    "Modified: / 11-06-2013 / 16:11:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleClassDefinitionChange
@@ -2486,8 +2496,6 @@
 
     change := ClassDefinitionChange new.
     change className:className; source:(parseTree printString).
-    "/ new: remember in override
-    change nameSpaceOverride:nameSpace.
     receiver isVariable ifTrue:[
         change superClassName:receiver name.
     ].
@@ -2505,8 +2513,16 @@
             change category:arg evaluate.
         ].
         kw = #'privateIn:' ifTrue:[
-            change className:(arg name ,'::',change classNameWithoutNamespace).
-            change owningClassName:(arg name).
+            | nm |
+
+            nm := arg name.
+            nameSpace notNil ifTrue:[
+                (nm startsWith: nameSpace name) ifTrue:[
+                    nm := nm copyFrom: nameSpace name size + 3.
+                ].
+            ].
+            change className:(nm ,'::',change classNameWithoutNamespace).
+            change owningClassName:nm.
             change private:true.
         ].
     ].
@@ -2520,6 +2536,7 @@
     ^ true
 
     "Modified: / 30-08-2010 / 13:56:32 / cg"
+    "Modified: / 11-06-2013 / 22:30:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleClassInitializeChange 
@@ -2537,13 +2554,13 @@
 
     change := ClassInstVarDefinitionChange new.
     change className:className.
-    change nameSpaceOverride:nameSpaceOverride.
     change source:(parseTree printString).
     change classInstVarNames:(parseTree arguments first value asCollectionOfWords asArray).
     self addChange:change.
     ^ true
 
     "Modified: / 25-11-2011 / 17:40:49 / cg"
+    "Modified: / 11-06-2013 / 16:11:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleMethodCategoryChange
@@ -2559,11 +2576,11 @@
         selector:methodSelector
         category:(arguments at:1) evaluate.
 
-    change nameSpaceOverride:nameSpaceOverride.
     self addChange:change.
     ^ true
 
     "Modified: / 27-07-2012 / 21:34:42 / cg"
+    "Modified: / 11-06-2013 / 16:11:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleMethodCategoryRenameChange
@@ -2577,9 +2594,10 @@
         oldCategoryName:(arguments at:1) evaluate
         newCategoryName:(arguments at:2) evaluate.
 
-    change nameSpaceOverride:nameSpaceOverride.
     self addChange:change.
     ^ true
+
+    "Modified: / 11-06-2013 / 16:11:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleMethodChange
@@ -2658,7 +2676,6 @@
         "/ huh - where is classIsJava: implemented???
         classIsJava ifTrue:[ change classIsJava: classIsJava ].
 
-        change nameSpaceOverride:nameSpaceOverride.
         self addChange:change.
 
         inputStream skipSeparators.
@@ -2669,7 +2686,7 @@
     ^ true
 
     "Created: / 24-01-2012 / 16:52:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 30-01-2013 / 09:57:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 16:11:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleMethodPackageChange
@@ -2685,11 +2702,11 @@
         selector:methodSelector
         package:(arguments at:1) evaluate.
 
-    change nameSpaceOverride:nameSpaceOverride.
     self addChange:change.
     ^ true
 
     "Created: / 27-07-2012 / 21:31:25 / cg"
+    "Modified: / 11-06-2013 / 16:11:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleMethodPrivacyChange
@@ -2705,11 +2722,11 @@
         selector:methodSelector
         privacy:(arguments at:1) evaluate.
 
-    change nameSpaceOverride:nameSpaceOverride.
     self addChange:change.
     ^ true
 
     "Modified: / 27-07-2012 / 21:35:20 / cg"
+    "Modified: / 11-06-2013 / 16:11:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleNameSpaceCreationChange
@@ -2759,11 +2776,11 @@
         ]
     ].
     change className:className source:primSource.
-    change nameSpaceOverride:nameSpaceOverride.
     self addChange:change.
     ^ true
 
     "Created: / 27-07-2012 / 21:39:55 / cg"
+    "Modified (format): / 11-06-2013 / 16:12:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 handleRemoveClassChange
@@ -3295,7 +3312,7 @@
     "
 
     "Created: / 15-03-2012 / 17:51:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-04-2013 / 11:44:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 17:59:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 changeSetBeingSaved:something
@@ -3611,6 +3628,7 @@
     "Created: / 15-10-1996 / 11:15:19 / cg"
     "Modified: / 22-03-1997 / 16:11:56 / cg"
     "Created: / 15-03-2012 / 19:18:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 22:23:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileOutAllMethodsOf:aClass on:aStream methodFilter:methodFilter
@@ -4023,14 +4041,15 @@
     | nameWithoutNs |
 
     nameWithoutNs := name.
-    namespace notNil ifTrue:[
-        self assert: (name startsWith:namespace).
-        nameWithoutNs := nameWithoutNs copyFrom: namespace size + 3.
-    ].
+"/    namespace notNil ifTrue:[
+"/        self assert: (name startsWith:namespace).
+"/        nameWithoutNs := nameWithoutNs copyFrom: namespace size + 3.
+"/    ].
 
     aStream nextPutAll: nameWithoutNs
 
     "Created: / 19-03-2012 / 18:17:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 17:59:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 printOn:aStream
--- a/ClassChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -12,7 +12,8 @@
 "{ Package: 'stx:libbasic3' }"
 
 Change subclass:#ClassChange
-	instanceVariableNames:'className classIsJava package nameSpaceOverride'
+	instanceVariableNames:'className classIsJava package nameSpaceOverride nameSpaceName
+		owningClassName'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'System-Changes'
@@ -41,6 +42,17 @@
 
     [author:]
         Claus Gittinger
+        Jan Vrany
+
+    [:instvars] incomplete
+        className <String> ............ the class name *without* namespace, 
+                                        but including all owners (if the class
+                                        is private)
+        owningClassName <String|nil> .. class name of the owning class if any
+        nameSpaceName <String|nil> .... namespace name of the change or nil, if
+                                        class is in no namespace.
+        nameSpaceOverride <String|nil>  enforced namespace in which the class will 
+                                        should be installed.
 "
 ! !
 
@@ -79,31 +91,31 @@
 
     "do not autoload an owning class of a private class!!"
 
-    |className class owner altName nsName ns meta|
+    |clsNm class owner altName nsName ns meta|
 
-    className := self className.
-    className isNil ifTrue:[^ nil].
+    clsNm := self className.
+    clsNm isNil ifTrue:[^ nil].
 
     "/ ok, try some heuristics (for example Root.something -> Smalltalk::something)
-    (className includes:$.) ifTrue:[
+    (clsNm includes:$.) ifTrue:[
         "/ VW - namespace prefix - convert to colon-notation
-        className := className copyReplaceAll:$. withAll:'::'.
+        clsNm := clsNm copyReplaceAll:$. withAll:'::'.
     ].       
-    nsName := self nameSpaceOverride ? 'Smalltalk'.
+    nsName := self nameSpaceName ? 'Smalltalk'.
     nsName notNil ifTrue:[
         ns := Smalltalk at:nsName asSymbol.
         ns isNil ifTrue:[
             ns := NameSpace name:nsName
         ]
     ].
-    (meta := (className endsWith:' class')) ifTrue:[    
-        className := className copyButLast:6.
+    (meta := (clsNm endsWith:' class')) ifTrue:[    
+        clsNm := clsNm copyButLast:6.
     ].
 
     ns := (ns ? Smalltalk).
     class := ns isNameSpace 
-                ifTrue:[ ns loadedClassNamed:className ]
-                ifFalse:[ Smalltalk loadedClassNamed:className ].     
+                ifTrue:[ ns loadedClassNamed:clsNm ]
+                ifFalse:[ Smalltalk loadedClassNamed:clsNm ].     
     class isNil ifTrue:[
         self isPrivateClassDefinitionChange ifTrue:[
             ns isNameSpace ifTrue:[
@@ -112,17 +124,17 @@
                 owner := Smalltalk loadedClassNamed:(self owningClassName).
             ].
             owner notNil ifTrue:[
-                class := owner privateClassesAt:className.
+                class := owner privateClassesAt:clsNm.
                 ^ meta ifTrue:[class theMetaclass] ifFalse:[class].
             ].
         ] ifFalse:[
             class := ns isNameSpace 
-                        ifTrue:[ ns classNamed:className ]
-                        ifFalse:[ Smalltalk loadedClassNamed:className ].     
+                        ifTrue:[ ns classNamed:clsNm ]
+                        ifFalse:[ Smalltalk loadedClassNamed:clsNm ].     
 
             "/ class := Parser evaluate:className ifFail:[nil].
             class isNil ifTrue:[
-                (altName := self classNameForWellKnownVisualWorksNamespaceClass:className) notNil
+                (altName := self classNameForWellKnownVisualWorksNamespaceClass:clsNm) notNil
                 ifTrue:[
                     class := ns isNameSpace 
                                 ifTrue:[ ns classNamed:altName ]
@@ -138,11 +150,11 @@
                 self isPrivateClassDefinitionChange ifTrue:[
                     owner := Smalltalk loadedClassNamed:(self owningClassName).
                     owner notNil ifTrue:[
-                        class := owner privateClassesAt:className.
+                        class := owner privateClassesAt:clsNm.
                         ^ meta ifTrue:[class theMetaclass] ifFalse:[class].
                     ].
                 ] ifFalse:[
-                    class := Smalltalk classNamed:className.
+                    class := Smalltalk classNamed:clsNm.
                     "/ class := Parser evaluate:className ifFail:[nil].
                     class isNil ifTrue:[
                         ^ nil.
@@ -158,6 +170,7 @@
     ^ meta ifTrue:[class theMetaclass] ifFalse:[class].
 
     "Modified: / 10-08-2012 / 12:07:26 / cg"
+    "Modified: / 11-06-2013 / 17:00:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 changeClass:aClass
@@ -190,7 +203,11 @@
 !
 
 className
+    "Returns class name of the class *without* namespace, but with
+     all owning classes (if the change class is a private class)"
     ^ className
+
+    "Modified (comment): / 12-06-2013 / 11:33:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 className:aString 
@@ -209,11 +226,12 @@
     self assert:(newSource isString).
     self assert:(newClassName isString).
 
-    className := newClassName.
+    self className: newClassName.
     source := newSource.
 
-    "Created: 3.12.1995 / 14:01:45 / cg"
-    "Modified: 15.7.1996 / 09:28:26 / cg"
+    "Created: / 03-12-1995 / 14:01:45 / cg"
+    "Modified: / 15-07-1996 / 09:28:26 / cg"
+    "Modified: / 11-06-2013 / 17:44:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 classNameForWellKnownVisualWorksNamespaceClass:className
@@ -240,6 +258,10 @@
 !
 
 fullClassName
+    "Returns fully qualified class name, i.e., including namespace in which the
+     class should be installed (i.e., the override namespace if any rather than
+     original namespace)"
+
     |ns|
 
     "/ used to be ^ className;
@@ -250,14 +272,19 @@
     (ns isNil or:[ns = 'Smalltalk']) ifTrue:[^ self className].
 
     ^ ns , '::' , self className
+
+    "Modified (comment): / 12-06-2013 / 11:35:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 localClassName
     "for private classes, this returns the name relative to its owner;
      for non-private ones, this is the regular name.
-     Notice that className always returns the full name (incl. any owner prefix)"
+     Notice that className always returns the full name (incl. any owner prefix)
+     but *without* any namespace prefix"
 
     ^self className
+
+    "Modified (comment): / 12-06-2013 / 11:34:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 nameSpace
@@ -269,45 +296,74 @@
     ^ Smalltalk
 !
 
+nameSpace: aNameSpace
+    self nameSpaceName: aNameSpace name
+
+    "Created: / 11-06-2013 / 15:57:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 nameSpaceName
-    |ns cnm idx|
+    "Return the namespace in which the class should be installed.
+
+     If the user enforces a namespace using nameSpaceOverride or
+     using query signal, then the enforced namespace is returned.
+     Otherwise, changes's original namespace is returned, if any."
+
+    | ns |
 
     className isNil ifTrue:[^ nil].
 
     ns := self nameSpaceOverride.
     ns notNil ifTrue:[ ^ ns ].
 
-    (idx := className indexOf:$:) ~~ 0 ifTrue:[
-        "/ in a namespace
-        ^ className copyTo:(idx - 1).
-    ].
-    (idx := className indexOf:$.) ~~ 0 ifTrue:[
-        "/ in a namespace
-        ns := className copyTo:(idx - 1).
-        cnm := className copyFrom:(idx + 1).
-        "cheat: VW namespaces"
-        ^ self nameSpaceForVWNamespace:ns class:cnm ifAbsent:ns
-    ].
-    ^ nil
+"/  JV: Following code is rubbish because it cannot distiguish
+"/      between namespace and owning class...
+
+"/    (idx := className indexOf:$:) ~~ 0 ifTrue:[
+"/        "/ in a namespace
+"/        ^ className copyTo:(idx - 1).
+"/    ].
+
+"/  JV: I commented following It is not clear to how it is supposed to
+"/      work. If anybody wants this back, he/she should first write
+"/      a testcase to demonstare how it should work.
+
+"/    (idx := className indexOf:$.) ~~ 0 ifTrue:[
+"/        "/ in a namespace
+"/        ns := className copyTo:(idx - 1).
+"/        cnm := className copyFrom:(idx + 1).
+"/        "cheat: VW namespaces"
+"/        ^ self nameSpaceForVWNamespace:ns class:cnm ifAbsent:ns
+"/    ].
+
+    ^ nameSpaceName
 
     "Modified: / 03-08-2006 / 02:04:03 / cg"
-    "Modified: / 09-05-2013 / 13:33:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 15:03:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 12-06-2013 / 11:33:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+nameSpaceName: aString
+    nameSpaceName := aString ~= 'Smalltalk' ifTrue:[aString] ifFalse:[nil].
+
+    "Created: / 11-06-2013 / 15:53:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 nameSpaceOverride
+    "Return namespace enforced by the caller"
+
     |ns|
 
     ns := nameSpaceOverride.
-    Class nameSpaceQuerySignal isHandled ifTrue:[
+    (ns isNil and:[Class nameSpaceQuerySignal isHandled]) ifTrue:[
         ns := Class nameSpaceQuerySignal query.
-    ] ifFalse:[
-        "/ self halt
     ].
     ns isNil ifTrue:[^ nil].
-    "/ ns == Smalltalk ifTrue:[^ nil].
     ^ ns name
 
     "Created: / 07-09-2011 / 20:45:43 / cg"
+    "Modified: / 11-06-2013 / 16:07:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 12-06-2013 / 11:31:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 nameSpaceOverride:aNamespaceOrString
@@ -328,6 +384,18 @@
     "Created: / 06-11-2008 / 17:26:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
+owningClassName
+    ^ owningClassName
+
+    "Modified: / 11-06-2013 / 14:50:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+owningClassName:aStringOrSymbol
+    owningClassName := aStringOrSymbol
+
+    "Created: / 30-08-2010 / 13:55:37 / cg"
+!
+
 package
     "return the value of the instance variable 'package' (automatically generated)"
 
@@ -433,10 +501,6 @@
     ns = 'Smalltalk' ifTrue:[^ 'Smalltalk'].
     ns = 'UI' ifTrue:[^ 'Smalltalk'].
     ^ default value
-!
-
-owningClassName
-    self shouldImplement
 ! !
 
 !ClassChange class methodsFor:'documentation'!
--- a/ClassClassVariableChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassClassVariableChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -12,7 +12,7 @@
 "{ Package: 'stx:libbasic3' }"
 
 ClassChange subclass:#ClassClassVariableChange
-	instanceVariableNames:'variableName nameSpaceName otherParameters'
+	instanceVariableNames:'variableName otherParameters'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'System-Changes'
--- a/ClassCommentChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassCommentChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -44,14 +44,12 @@
 "
 ! !
 
-
 !ClassCommentChange class methodsFor:'others'!
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/ClassCommentChange.st,v 1.35 2013-04-14 06:57:10 cg Exp $'
 ! !
 
-
 !ClassCommentChange methodsFor:'accessing'!
 
 className:clsName comment:aCommentString
@@ -71,7 +69,6 @@
     "Created: / 16.2.1998 / 14:16:45 / cg"
 ! !
 
-
 !ClassCommentChange methodsFor:'comparing'!
 
 isConflict
@@ -112,7 +109,6 @@
         ]
 ! !
 
-
 !ClassCommentChange methodsFor:'converting'!
 
 asAntiChange
@@ -122,7 +118,6 @@
     "Created: / 26-11-2009 / 16:09:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-
 !ClassCommentChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -147,7 +142,6 @@
     aStream nextPutAll:'comment:'
 ! !
 
-
 !ClassCommentChange methodsFor:'queries'!
 
 isClassCommentChange
@@ -156,7 +150,6 @@
 
 ! !
 
-
 !ClassCommentChange methodsFor:'visiting'!
 
 acceptChangeVisitor:aVisitor
@@ -165,7 +158,6 @@
     "Created: / 25-11-2011 / 17:13:02 / cg"
 ! !
 
-
 !ClassCommentChange class methodsFor:'documentation'!
 
 version
--- a/ClassDefinitionChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassDefinitionChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -15,7 +15,7 @@
 	instanceVariableNames:'objectType superClassName classType indexedType otherParameters
 		instanceVariableNames classVariableNames
 		classInstanceVariableNames poolDictionaries category private
-		definitionSelector owningClassName'
+		definitionSelector'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'System-Changes'
@@ -177,15 +177,19 @@
 !
 
 nameSpaceName
+    | nm |
 
-    "/ JV: What is the following good for? Please explain..."
-    objectType == #variable ifTrue:[
-        ^ nil
-    ].
-    ^ self cutNameSpaceOf:(self nameSpaceOverride ? super nameSpaceName)
+    nm := super nameSpaceName.
+    ^nm.
+
+"/    "/ JV: What is the following good for? Please explain..."
+"/    objectType == #variable ifTrue:[
+"/        ^ nil
+"/    ].
+"/    ^ self cutNameSpaceOf:(self nameSpaceOverride ? super nameSpaceName)
 
     "Modified: / 07-09-2011 / 20:47:14 / cg"
-    "Modified (comment): / 09-05-2013 / 13:46:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2013 / 17:18:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 nameSpaceName: aNameSpaceName classType: aClassType otherParameters:otherParametersArg
@@ -398,7 +402,19 @@
 !ClassDefinitionChange methodsFor:'printing & storing'!
 
 definitionString
-    ^ self definitionStringInNamespace: (self nameSpaceOverride)
+    | ns  |
+
+    ns := self nameSpaceName.
+    ns isEmptyOrNil ifTrue:[
+        ^ self definitionStringInNamespace: ns.
+    ].
+    ^String streamContents:[:s|
+        s nextPutAll: '"{ NameSpace: '; nextPutAll: ns; nextPutAll: ' }"'.
+        s cr; cr.
+        s nextPutAll: (self definitionStringInNamespace: ns).
+    ]
+
+    "Modified: / 12-06-2013 / 11:16:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 definitionStringInNamespace: nsOrNil
@@ -422,15 +438,19 @@
     ].
 
     superClassNameUsed := self superClassName.
+    "Strip of namespace"
+    nsOrNil notNil ifTrue:[
+        (superClassNameUsed startsWith: nsOrNil) ifTrue:[
+            superClassNameUsed := superClassNameUsed copyFrom: nsOrNil size + 3
+        ].
+    ].
+
     "/ careful with private classes: the definition MUST give the
     "/ local name as argument, not the full name
     self isPrivateClassDefinitionChange ifTrue:[
         classNameUsed := self localClassName.
     ] ifFalse:[
         classNameUsed := className.
-        nsOrNil notNil ifTrue:[
-            classNameUsed := nsOrNil,'::',classNameUsed.
-        ].
     ].
 
     "/ selPart is the subclass:/variableSubclass/variableByteSubclass:/... - part
@@ -453,7 +473,7 @@
             nextPutLine:(poolDictionaries ? '') storeString.
         self isPrivateClassDefinitionChange ifTrue:[
             ownerNameUsed := self owningClassName.    
-            nsOrNil notNil ifTrue:[
+            nsOrNil ~~ nameSpaceName ifTrue:[
                 ownerNameUsed := nsOrNil,'::',ownerNameUsed.
             ].
             stream 
@@ -469,91 +489,7 @@
       ]
 
     "Modified: / 13-06-2012 / 13:01:58 / cg"
-    "Modified: / 30-04-2013 / 19:52:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-definitionStringWithoutNamespace
-    "cg - huh - who needs that? (the definitionString already does NOT include the classes namespace)"
-
-    |ns classNameUsed superClassNameUsed|
-
-    ns := self nameSpaceOverride.
-
-    objectType == #variable ifTrue:[
-        ^ String streamContents:[:stream |
-            ns notNil ifTrue:[
-                stream 
-                    nextPutAll:((ns asCollectionOfSubstringsSeparatedBy:$.) asStringWith:'::')
-            ] ifFalse:[
-                self halt:'can this happen ?'.
-                stream 
-                    nextPutAll:'Smalltalk'
-            ].
-
-            stream 
-                nextPutAll:' addClassVarName:';
-                nextPutAll:className asString storeString
-          ].
-    ].
-
-    superClassNameUsed := self superClassName.
-    classNameUsed := self classNameWithoutNamespace.
-
-    ^ String streamContents:[:stream |
-        self isPrivateClassDefinitionChange ifFalse:[
-            stream 
-                nextPutAll:superClassNameUsed;
-                nextPutAll:' subclass:';
-                nextPutAll: classNameUsed asSymbol storeString
-                ;
-                cr;
-                tab;
-                nextPutAll:'instanceVariableNames:';
-                nextPutAll:(instanceVariableNames ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'classVariableNames:';
-                nextPutAll:(classVariableNames ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'poolDictionaries:';
-                nextPutAll:(poolDictionaries ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'category:';
-                nextPutAll:(category ? '') storeString;
-                cr
-        ] ifTrue:[
-            stream 
-                nextPutAll:superClassNameUsed;
-                nextPutAll:' subclass:';
-                nextPutAll: (self className copyFrom: owningClassName size + 3) asSymbol storeString
-                ;
-                cr;
-                tab;
-                nextPutAll:'instanceVariableNames:';
-                nextPutAll:(instanceVariableNames ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'classVariableNames:';
-                nextPutAll:(classVariableNames ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'poolDictionaries:';
-                nextPutAll:(poolDictionaries ? '') storeString;
-                cr;
-                tab;
-                nextPutAll:'privateIn:';
-                nextPutAll:
-                    ((ns := self nameSpaceName) isNil
-                        ifTrue:[owningClassName]
-                        ifFalse:[owningClassName copyFrom: ns size + 3]);
-                cr
-        ]
-    ]
-
-    "Modified: / 06-10-2011 / 17:02:05 / cg"
-    "Created: / 20-03-2012 / 16:37:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-06-2013 / 11:24:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 printOn:aStream
@@ -643,12 +579,6 @@
     ^ owningClassName
 
     "Created: / 12-10-2006 / 23:07:25 / cg"
-!
-
-owningClassName:aStringOrSymbol
-    owningClassName := aStringOrSymbol
-
-    "Created: / 30-08-2010 / 13:55:37 / cg"
 ! !
 
 !ClassDefinitionChange methodsFor:'special'!
--- a/ClassRemoveChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassRemoveChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -52,7 +52,6 @@
 "
 ! !
 
-
 !ClassRemoveChange methodsFor:'printing'!
 
 printOn:aStream
@@ -63,7 +62,6 @@
     "Modified: / 13-11-2006 / 10:40:17 / cg"
 ! !
 
-
 !ClassRemoveChange methodsFor:'queries'!
 
 delta
@@ -78,7 +76,6 @@
     ^ true
 ! !
 
-
 !ClassRemoveChange class methodsFor:'documentation'!
 
 version
--- a/ClassRenameChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/ClassRenameChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -45,7 +45,6 @@
 "
 ! !
 
-
 !ClassRenameChange methodsFor:'accessing'!
 
 oldName
@@ -61,7 +60,6 @@
     "Created: / 16.2.1998 / 14:22:38 / cg"
 ! !
 
-
 !ClassRenameChange methodsFor:'applying'!
 
 apply
@@ -88,7 +86,6 @@
     "Created: / 31-07-2012 / 18:58:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-
 !ClassRenameChange methodsFor:'printing'!
 
 printOn:aStream
@@ -100,14 +97,12 @@
     "Created: / 16.2.1998 / 14:23:35 / cg"
 ! !
 
-
 !ClassRenameChange methodsFor:'queries'!
 
 isClassRenameChange
     ^ true
 ! !
 
-
 !ClassRenameChange class methodsFor:'documentation'!
 
 version
--- a/Make.proto	Tue Jun 11 15:50:58 2013 +0100
+++ b/Make.proto	Wed Jun 12 11:54:30 2013 +0100
@@ -148,7 +148,7 @@
 $(OUTDIR)Change.$(O) Change.$(H): Change.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/SmalltalkChunkFileSourceWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(STCHDR)
+$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)/stx/libbasic/OrderedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SmalltalkChunkFileSourceWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(STCHDR)
 $(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Makefile.init	Tue Jun 11 15:50:58 2013 +0100
+++ b/Makefile.init	Wed Jun 12 11:54:30 2013 +0100
@@ -8,7 +8,7 @@
 #
 # MACOSX caveat:
 #   as filenames are not case sensitive (in a default setup),
-#   we cannot use tha above trick. Therefore, this file is now named
+#   we cannot use the above trick. Therefore, this file is now named
 #   "Makefile.init", and you have to execute "make -f Makefile.init" to
 #   get the initial makefile.  This is now also done by the toplevel CONFIG
 #   script.
--- a/MethodCategoryChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/MethodCategoryChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -58,14 +58,12 @@
 "
 ! !
 
-
 !MethodCategoryChange class methodsFor:'others'!
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic3/MethodCategoryChange.st,v 1.22 2012-07-31 12:27:40 vrany Exp $'
 ! !
 
-
 !MethodCategoryChange methodsFor:'accessing'!
 
 class:cls selector:sel category:cat
@@ -114,7 +112,6 @@
     "Created: / 20-03-2012 / 22:26:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-
 !MethodCategoryChange methodsFor:'applying'!
 
 apply
@@ -128,7 +125,6 @@
     "Modified: / 23-11-2006 / 16:59:09 / cg"
 ! !
 
-
 !MethodCategoryChange methodsFor:'testing'!
 
 isMethodCategoryChange
@@ -141,7 +137,6 @@
     ^ false
 ! !
 
-
 !MethodCategoryChange methodsFor:'visiting'!
 
 acceptChangeVisitor:aVisitor
@@ -150,7 +145,6 @@
     "Created: / 25-11-2011 / 17:13:58 / cg"
 ! !
 
-
 !MethodCategoryChange class methodsFor:'documentation'!
 
 version
--- a/MethodCategoryRenameChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/MethodCategoryRenameChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -41,7 +41,6 @@
 "
 ! !
 
-
 !MethodCategoryRenameChange methodsFor:'accessing'!
 
 oldCategoryName:oldCatString newCategoryName:newCatString
@@ -59,7 +58,6 @@
     "Modified: / 6.2.2000 / 02:34:25 / cg"
 ! !
 
-
 !MethodCategoryRenameChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -73,14 +71,12 @@
     "Modified: / 16.2.1998 / 13:36:28 / cg"
 ! !
 
-
 !MethodCategoryRenameChange methodsFor:'queries'!
 
 isMethodCategoryRenameChange
     ^ true
 ! !
 
-
 !MethodCategoryRenameChange class methodsFor:'documentation'!
 
 version
--- a/MethodChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/MethodChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -51,7 +51,6 @@
 "
 ! !
 
-
 !MethodChange class methodsFor:'instance creation'!
 
 class:cls selector:sel category:cat 
@@ -74,7 +73,6 @@
     ^ self basicNew className:clsName selector:sel source:src category:cat
 ! !
 
-
 !MethodChange methodsFor:'accessing'!
 
 category
@@ -260,7 +258,6 @@
     "Created: / 6.2.1998 / 13:29:25 / cg"
 ! !
 
-
 !MethodChange methodsFor:'applying'!
 
 apply
@@ -335,7 +332,6 @@
     "Modified: / 07-09-2011 / 21:09:19 / cg"
 ! !
 
-
 !MethodChange methodsFor:'comparing'!
 
 isConflict
@@ -374,14 +370,12 @@
     "Modified: / 25-07-2006 / 11:23:27 / cg"
 ! !
 
-
 !MethodChange methodsFor:'converting'!
 
 asNamedMethodChange
     ^ NamedMethodChange fromMethodChange:self
 ! !
 
-
 !MethodChange methodsFor:'fileout'!
 
 basicFileOutOn: aStream
@@ -423,7 +417,6 @@
     "Modified: / 05-12-2009 / 12:38:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-
 !MethodChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -500,7 +493,6 @@
     ^ true
 ! !
 
-
 !MethodChange methodsFor:'visiting'!
 
 acceptChangeVisitor:aVisitor
@@ -509,21 +501,18 @@
     "Created: / 25-11-2011 / 17:13:50 / cg"
 ! !
 
-
 !MethodChange::NamedMethodChange class methodsFor:'instance creation'!
 
 fromMethodChange:aMethodChange
     ^ self new cloneInstanceVariablesFrom:aMethodChange
 ! !
 
-
 !MethodChange::NamedMethodChange methodsFor:'accessing'!
 
 changeName:something
     changeName := something.
 ! !
 
-
 !MethodChange::NamedMethodChange methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -534,7 +523,6 @@
     super printOn:aStream
 ! !
 
-
 !MethodChange class methodsFor:'documentation'!
 
 version
--- a/MethodDefinitionChange.st	Tue Jun 11 15:50:58 2013 +0100
+++ b/MethodDefinitionChange.st	Wed Jun 12 11:54:30 2013 +0100
@@ -40,7 +40,6 @@
 "
 ! !
 
-
 !MethodDefinitionChange methodsFor:'accessing'!
 
 attributes
@@ -55,14 +54,12 @@
     attributes := something.
 ! !
 
-
 !MethodDefinitionChange methodsFor:'testing'!
 
 isMethodDefinitionChange
     ^ true
 ! !
 
-
 !MethodDefinitionChange class methodsFor:'documentation'!
 
 version
--- a/bc.mak	Tue Jun 11 15:50:58 2013 +0100
+++ b/bc.mak	Wed Jun 12 11:54:30 2013 +0100
@@ -75,7 +75,7 @@
 $(OUTDIR)Change.$(O) Change.$(H): Change.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeDeltaInformation.$(O) ChangeDeltaInformation.$(H): ChangeDeltaInformation.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeNotificationParameter.$(O) ChangeNotificationParameter.$(H): ChangeNotificationParameter.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\SmalltalkChunkFileSourceWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(STCHDR)
+$(OUTDIR)ChangeSet.$(O) ChangeSet.$(H): ChangeSet.st $(INCLUDE_TOP)\stx\libbasic\OrderedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SmalltalkChunkFileSourceWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(STCHDR)
 $(OUTDIR)ChangeSetDiff.$(O) ChangeSetDiff.$(H): ChangeSetDiff.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ChangeSetDiffComponent.$(O) ChangeSetDiffComponent.$(H): ChangeSetDiffComponent.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ClassOrganizer.$(O) ClassOrganizer.$(H): ClassOrganizer.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/libbasic3.rc	Tue Jun 11 15:50:58 2013 +0100
+++ b/libbasic3.rc	Wed Jun 12 11:54:30 2013 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 1998-2012\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Thu, 09 May 2013 12:49:27 GMT\0"
+      VALUE "ProductDate", "Wed, 12 Jun 2013 10:39:49 GMT\0"
     END
 
   END