Change the name of a classes Metaclass from e.g. "SmallIntegerclass" to
authorStefan Vogel <sv@exept.de>
Thu, 20 Jun 1996 00:29:27 +0200
changeset 290 d1650b17b9e9
parent 289 7134d1233ba6
child 291 c0d5159014be
Change the name of a classes Metaclass from e.g. "SmallIntegerclass" to "SmallInteger class".
Explainer.st
Parser.st
--- a/Explainer.st	Mon Jun 17 16:13:49 1996 +0200
+++ b/Explainer.st	Thu Jun 20 00:29:27 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 18-jun-1996 at 15:30:47'                   !
+
 Parser subclass:#Explainer
 	instanceVariableNames:''
 	classVariableNames:''
@@ -50,42 +52,44 @@
     |common found|
 
     listOfClassNames do:[:className |
-	|class|
+        |class|
 
-	((className endsWith:'class') and:[className ~= 'Metaclass']) ifTrue:[
-	    class := (Smalltalk at:(className copyWithoutLast:5 "copyTo:(className size - 5)") asSymbol) class
-	] ifFalse:[
-	    class := Smalltalk at:(className asSymbol).
-	].
-	common isNil ifTrue:[
-	    common := class
-	] ifFalse:[
-	    (class isSubclassOf:common) ifTrue:[
-		"keep common"
-	    ] ifFalse:[
-		(common isSubclassOf:class) ifTrue:[
-		    common := class
-		] ifFalse:[
-		    "walk up, checking"
-		    found := false.
-		    common allSuperclassesDo:[:sup |
-			(class isSubclassOf:sup) ifTrue:[
-			    common := sup
-			]
-		    ].
-		    found ifFalse:[
-			class allSuperclassesDo:[:sup |
-			    (common isSubclassOf:sup) ifTrue:[
-				common := sup
-			    ]
-			].
-		    ].
-		]
-	    ].
-	].
-	common == Object ifTrue:[^ common]
+        ((className endsWith:' class') and:[className ~= 'Metaclass']) ifTrue:[
+            class := (Smalltalk at:(className copyWithoutLast:6 "copyTo:(className size - 5)") asSymbol) class
+        ] ifFalse:[
+            class := Smalltalk at:(className asSymbol).
+        ].
+        common isNil ifTrue:[
+            common := class
+        ] ifFalse:[
+            (class isSubclassOf:common) ifTrue:[
+                "keep common"
+            ] ifFalse:[
+                (common isSubclassOf:class) ifTrue:[
+                    common := class
+                ] ifFalse:[
+                    "walk up, checking"
+                    found := false.
+                    common allSuperclassesDo:[:sup |
+                        (class isSubclassOf:sup) ifTrue:[
+                            common := sup
+                        ]
+                    ].
+                    found ifFalse:[
+                        class allSuperclassesDo:[:sup |
+                            (common isSubclassOf:sup) ifTrue:[
+                                common := sup
+                            ]
+                        ].
+                    ].
+                ]
+            ].
+        ].
+        common == Object ifTrue:[^ common]
     ].
     ^ common
+
+    "Modified: 17.6.1996 / 17:09:21 / stefan"
 !
 
 explain:someText in:source forClass:aClass
@@ -208,26 +212,26 @@
     "try globals"
 
     (Smalltalk includesKey:sym) ifTrue:[
-	tmp := string , ' is a global variable.'.
-	val := Smalltalk at:sym.
-	val isBehavior ifTrue:[
-	    val name = string ifTrue:[
-		tmp := tmp , '
+        tmp := string , ' is a global variable.'.
+        val := Smalltalk at:sym.
+        val isBehavior ifTrue:[
+            val name = string ifTrue:[
+                tmp := tmp , '
 
 ' , string , ' is a class categorized as ' , val category , '
 in the ''' , val package , ''' package.'
-	    ] ifFalse:[
-		tmp := tmp , '
+            ] ifFalse:[
+                tmp := tmp , '
 
 ' , string , ' is bound to the class ' , val name ,
 ' in category ' , val category , '.'
-	    ]
-	] ifFalse:[
-	    tmp := tmp , '
+            ]
+        ] ifFalse:[
+            tmp := tmp , '
 
 Its current value is ' , val classNameWithArticle , '.'
-	].
-	^ tmp.
+        ].
+        ^ tmp.
     ].
 
     "
@@ -236,59 +240,61 @@
     "
     list := Set new.
     Smalltalk allBehaviorsDo:[:c|
-	(c implements:sym) ifTrue:[
-	    list add:(c name)
-	].
-	(c class implements:sym) ifTrue:[
-	    list add:(c name , 'class')
-	]
+        (c implements:sym) ifTrue:[
+            list add:(c name)
+        ].
+        (c class implements:sym) ifTrue:[
+            list add:(c name , ' class')
+        ]
     ].
 
     count := list size.
     (count ~~ 0) ifTrue:[
-	"
-	 for up-to 4 implementing classes,
-	 list them
-	"
-	list := list asOrderedCollection sort.
-	tmp := ' is a selector implemented in '.
-	(count == 1) ifTrue:[
-	    ^ string , tmp , (list at:1) , '.'
-	].
+        "
+         for up-to 4 implementing classes,
+         list them
+        "
+        list := list asOrderedCollection sort.
+        tmp := ' is a selector implemented in '.
+        (count == 1) ifTrue:[
+            ^ string , tmp , (list at:1) , '.'
+        ].
 
-	(count == 2) ifTrue:[
-	    ^ string , tmp , (list at:1) , ' and ' , (list at:2) , '.'
-	].
-	(count == 3) ifTrue:[
-	    ^ string , tmp , '
+        (count == 2) ifTrue:[
+            ^ string , tmp , (list at:1) , ' and ' , (list at:2) , '.'
+        ].
+        (count == 3) ifTrue:[
+            ^ string , tmp , '
 ' , (list at:1) , ', ' , (list at:2) , ' and ' , (list at:3) , '.'
-	].
-	(count == 4) ifTrue:[
-	    ^ string , tmp , '
+        ].
+        (count == 4) ifTrue:[
+            ^ string , tmp , '
 ' , (list at:1) , ', ' , (list at:2) , ', ' , (list at:3), ' and ' , (list at:4) , '.'
-	].
+        ].
 
-	"
-	 if there are more, look for a common
-	 superclass and show it ...
-	"
-	commonSuperClass := self commonSuperClassOf:list.
-	commonSuperClass ~~ Object ifTrue:[
-	    (list includes:commonSuperClass) ifTrue:[
-		^ string , tmp, count printString , commonSuperClass name 
-			 , ' and redefined in ' , (count - 1) printString  
-			 , ' subclasses'
-	    ].
-	    ^ string , tmp, count printString , ' subclasses of ' , commonSuperClass name
-	].
+        "
+         if there are more, look for a common
+         superclass and show it ...
+        "
+        commonSuperClass := self commonSuperClassOf:list.
+        commonSuperClass ~~ Object ifTrue:[
+            (list includes:commonSuperClass) ifTrue:[
+                ^ string , tmp, count printString , commonSuperClass name 
+                         , ' and redefined in ' , (count - 1) printString  
+                         , ' subclasses'
+            ].
+            ^ string , tmp, count printString , ' subclasses of ' , commonSuperClass name
+        ].
 
-	"
-	 otherwise just give the number.
-	"
-	^ string , tmp , count printString , ' classes.'
+        "
+         otherwise just give the number.
+        "
+        ^ string , tmp , count printString , ' classes.'
     ].
 
     ^ nil
+
+    "Modified: 17.6.1996 / 17:09:30 / stefan"
 !
 
 explainPseudoVariable:string in:aClass
@@ -497,5 +503,5 @@
 !Explainer class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.17 1996-04-25 17:06:15 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.18 1996-06-19 22:29:26 stefan Exp $'
 ! !
--- a/Parser.st	Mon Jun 17 16:13:49 1996 +0200
+++ b/Parser.st	Thu Jun 20 00:29:27 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 18-jun-1996 at 15:31:11'                   !
+
 Scanner subclass:#Parser
 	instanceVariableNames:'classToCompileFor selfValue contextToEvaluateIn selector
 		methodArgs methodArgNames methodVars methodVarNames tree
@@ -2333,12 +2335,12 @@
 
     aClass := classToCompileFor.
     aClass isMeta ifTrue:[
-	className := aClass name.
-	className := className copyWithoutLast:5.
-	baseClass := Smalltalk at:(className asSymbol).
-	baseClass notNil ifTrue:[
-	    aClass := baseClass
-	]
+        className := aClass name.
+        className := className copyWithoutLast:6.
+        baseClass := Smalltalk at:(className asSymbol).
+        baseClass notNil ifTrue:[
+            aClass := baseClass
+        ]
     ].
     ^ aClass whichClassDefinesClassVar:aString
 "/    [aClass notNil] whileTrue:[
@@ -2346,6 +2348,8 @@
 "/        aClass := aClass superclass
 "/    ].
 "/    ^ nil
+
+    "Modified: 17.6.1996 / 17:18:41 / stefan"
 !
 
 keywordExpression
@@ -3276,18 +3280,20 @@
     |aClass className|
 
     PrevClassVarNames isNil ifTrue:[
-	aClass := classToCompileFor.
-	classToCompileFor isMeta ifTrue:[
-	    className := aClass name.
-	    className := className copyWithoutLast:5.
-	    aClass := Smalltalk at:(className asSymbol).
-	    aClass isNil ifTrue:[
-		aClass := classToCompileFor
-	    ]
-	].
-	PrevClassVarNames := aClass allClassVarNames
+        aClass := classToCompileFor.
+        classToCompileFor isMeta ifTrue:[
+            className := aClass name.
+            className := className copyWithoutLast:6.
+            aClass := Smalltalk at:(className asSymbol).
+            aClass isNil ifTrue:[
+                aClass := classToCompileFor
+            ]
+        ].
+        PrevClassVarNames := aClass allClassVarNames
     ].
     ^ PrevClassVarNames
+
+    "Modified: 17.6.1996 / 17:15:53 / stefan"
 !
 
 hasNonOptionalPrimitiveCode
@@ -3499,6 +3505,6 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.80 1996-05-29 15:41:46 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.81 1996-06-19 22:29:27 stefan Exp $'
 ! !
 Parser initialize!