#isNamespace renamed to #isNameSpace
authorClaus Gittinger <cg@exept.de>
Fri, 24 Mar 2000 17:43:04 +0100
changeset 2645 d01d467c5199
parent 2644 8dc04189f7b1
child 2646 bb22d1b835e6
#isNamespace renamed to #isNameSpace
BrowserView.st
DictionaryInspectorView.st
--- a/BrowserView.st	Tue Mar 21 15:11:44 2000 +0100
+++ b/BrowserView.st	Fri Mar 24 17:43:04 2000 +0100
@@ -2474,114 +2474,114 @@
      Use this, to find classes, which need to be reloaded from the repository."
 
     self withBusyCursorDo:[
-	|logMessage classes repVersion clsVersion binVersion
-	 count unloadedCount badCount cat needCheckIn|
-
-	cat := currentClassCategory.
-	(cat = '* hierarchy *') ifTrue:[
-	    cat := '* all *'
-	].
-
-	classes := self listOfAllClassesInCategory:cat names:false.
-	classes isNil ifTrue:[
-	    Transcript showCR:'no classes to validate'.
-	    ^ self
-	].
-
-	count := unloadedCount := badCount := needCheckIn := 0.
-
-	Transcript cr.
-	Transcript showCR:'-------------------------------------------------'.
-	Transcript showCR:'checking class revisions vs. repository ...'.
-	Transcript cr.
-
-	classes do:[:aClass |
-	    |clsName msg sourceCodeManager repSource currentSource aStream|
-
-	    count := count + 1.
-
-	    "/ ignore autoloaded and private classes here
+        |logMessage classes repVersion clsVersion binVersion
+         count unloadedCount badCount cat needCheckIn|
+
+        cat := currentClassCategory.
+        (cat = '* hierarchy *') ifTrue:[
+            cat := '* all *'
+        ].
+
+        classes := self listOfAllClassesInCategory:cat names:false.
+        classes isNil ifTrue:[
+            Transcript showCR:'no classes to validate'.
+            ^ self
+        ].
+
+        count := unloadedCount := badCount := needCheckIn := 0.
+
+        Transcript cr.
+        Transcript showCR:'-------------------------------------------------'.
+        Transcript showCR:'checking class revisions vs. repository ...'.
+        Transcript cr.
+
+        classes do:[:aClass |
+            |clsName msg sourceCodeManager repSource currentSource aStream|
+
+            count := count + 1.
+
+            "/ ignore autoloaded and private classes here
                 
-	    clsName := aClass name.
-
-	    aClass isLoaded ifFalse:[
-		unloadedCount := unloadedCount + 1.
-		(currentClassCategory ~= '* all *'
-		and:[currentClassCategory ~= '* hierarchy *']) ifTrue:[
-		    msg := '?? ''' , clsName , ''' is not loaded - skipped check'.
-		]
-	    ] ifTrue:[
-		((aClass isNamespace not or:[aClass == Smalltalk])
-		and:[aClass topOwningClass isNil]) ifTrue:[
+            clsName := aClass name.
+
+            aClass isLoaded ifFalse:[
+                unloadedCount := unloadedCount + 1.
+                (currentClassCategory ~= '* all *'
+                and:[currentClassCategory ~= '* hierarchy *']) ifTrue:[
+                    msg := '?? ''' , clsName , ''' is not loaded - skipped check'.
+                ]
+            ] ifTrue:[
+                ((aClass isNameSpace not or:[aClass == Smalltalk])
+                and:[aClass topOwningClass isNil]) ifTrue:[
                 
 "/                    self busyLabel:'validating %1 ...' with:aClass name.
                 
-		    sourceCodeManager := aClass sourceCodeManager.
-		    sourceCodeManager isNil ifTrue:[
-			msg := '?? ''' , clsName , ''' has no sourceCodeManager - skipped check'.
-		    ] ifFalse:[
-			repVersion := sourceCodeManager newestRevisionOf:aClass.
-			repVersion isNil ifTrue:[
-			    msg := '-- ' , clsName 
-				    , ' not in repository'
-			] ifFalse:[
-			    clsVersion := aClass revision.
-			    binVersion := aClass binaryRevision.
-
-			    clsName := aClass name.
-			    msg := nil.
-
-			    clsVersion ~= repVersion ifTrue:[
-				badCount := badCount + 1.
-				msg := '** ' , clsName 
-					, ' is not up-to-date (this: '
-					, clsVersion printString
-					, ' repository: '
-					, repVersion printString
-					, ').'.
-				msg := msg asText allBold.
-			    ] ifFalse:[
-				clsVersion ~= binVersion ifTrue:[
-				    binVersion notNil ifTrue:[
-					msg := clsName
-					       , ' up-to-date (but should be stc-recompiled)'
-				    ]
-				] ifFalse:[
+                    sourceCodeManager := aClass sourceCodeManager.
+                    sourceCodeManager isNil ifTrue:[
+                        msg := '?? ''' , clsName , ''' has no sourceCodeManager - skipped check'.
+                    ] ifFalse:[
+                        repVersion := sourceCodeManager newestRevisionOf:aClass.
+                        repVersion isNil ifTrue:[
+                            msg := '-- ' , clsName 
+                                    , ' not in repository'
+                        ] ifFalse:[
+                            clsVersion := aClass revision.
+                            binVersion := aClass binaryRevision.
+
+                            clsName := aClass name.
+                            msg := nil.
+
+                            clsVersion ~= repVersion ifTrue:[
+                                badCount := badCount + 1.
+                                msg := '** ' , clsName 
+                                        , ' is not up-to-date (this: '
+                                        , clsVersion printString
+                                        , ' repository: '
+                                        , repVersion printString
+                                        , ').'.
+                                msg := msg asText allBold.
+                            ] ifFalse:[
+                                clsVersion ~= binVersion ifTrue:[
+                                    binVersion notNil ifTrue:[
+                                        msg := clsName
+                                               , ' up-to-date (but should be stc-recompiled)'
+                                    ]
+                                ] ifFalse:[
     "/                              msg := clsName , ' is up-to-date.'
-				].
-
-				"/ compare the sources;
-				"/ to find classes which need a checkin.
-
-				aStream := sourceCodeManager getMostRecentSourceStreamForClassNamed:aClass name.
-				repSource := aStream contents asString.
-				aStream close.
-
-				aStream := '' writeStream.
-				Method flushSourceStreamCache.
-				aClass fileOutOn:aStream withTimeStamp:false.
-				currentSource := aStream contents asString.
-
-				repSource ~= currentSource ifTrue:[
-				    msg := '-- ' , clsName , ' should be checked into the repository'.
-				    needCheckIn := needCheckIn + 1.
-				].
-			    ].
-			].
-		    ].
-		].
-	    ].
-	    msg notNil ifTrue:[
-		Transcript showCR:msg
-	    ].
-	].
-	Transcript cr.
-	Transcript showCR:'----------------------------------------------------------'.
-	Transcript showCR:('%1 classes / %2 unloaded / %3 need checkout / %4 need checkin.'
-			   bindWith:count with:unloadedCount with:badCount with:needCheckIn).
-	Transcript showCR:'----------------------------------------------------------'.
-
-	self normalLabel.
+                                ].
+
+                                "/ compare the sources;
+                                "/ to find classes which need a checkin.
+
+                                aStream := sourceCodeManager getMostRecentSourceStreamForClassNamed:aClass name.
+                                repSource := aStream contents asString.
+                                aStream close.
+
+                                aStream := '' writeStream.
+                                Method flushSourceStreamCache.
+                                aClass fileOutOn:aStream withTimeStamp:false.
+                                currentSource := aStream contents asString.
+
+                                repSource ~= currentSource ifTrue:[
+                                    msg := '-- ' , clsName , ' should be checked into the repository'.
+                                    needCheckIn := needCheckIn + 1.
+                                ].
+                            ].
+                        ].
+                    ].
+                ].
+            ].
+            msg notNil ifTrue:[
+                Transcript showCR:msg
+            ].
+        ].
+        Transcript cr.
+        Transcript showCR:'----------------------------------------------------------'.
+        Transcript showCR:('%1 classes / %2 unloaded / %3 need checkout / %4 need checkin.'
+                           bindWith:count with:unloadedCount with:badCount with:needCheckIn).
+        Transcript showCR:'----------------------------------------------------------'.
+
+        self normalLabel.
     ]
 
     "Modified: 15.6.1996 / 00:25:58 / stefan"
@@ -2683,35 +2683,35 @@
     newList := Set new.
 
     currentNamespace = '* all *' ifTrue:[
-	nameSpaceList := Array with:Smalltalk.
-	allNameSpaces := true.
+        nameSpaceList := Array with:Smalltalk.
+        allNameSpaces := true.
     ] ifFalse:[
-	nameSpaceList := self listOfNamespaces.
-	allNameSpaces := false.
+        nameSpaceList := self listOfNamespaces.
+        allNameSpaces := false.
     ].
 
     nameSpaceList do:[:aNamespace |
-	aNamespace allBehaviorsDo:[:aClass |
-	    aClass isMeta ifFalse:[
-		(aClass isNamespace not 
-		or:[aClass == Namespace 
-		or:[aClass == Smalltalk]]) ifTrue:[
-		    (allNameSpaces or:[aClass nameSpace == aNamespace]) ifTrue:[
-			cat := aClass category.
-			cat isNil ifTrue:[
-			    cat := '* no category *'
-			].
-			cat ~= 'obsolete' ifTrue:[
-			    newList add:cat
-			]
-		    ]
-		]
-	    ]
-	]
+        aNamespace allBehaviorsDo:[:aClass |
+            aClass isMeta ifFalse:[
+                (aClass isNameSpace not 
+                or:[aClass == Namespace 
+                or:[aClass == Smalltalk]]) ifTrue:[
+                    (allNameSpaces or:[aClass nameSpace == aNamespace]) ifTrue:[
+                        cat := aClass category.
+                        cat isNil ifTrue:[
+                            cat := '* no category *'
+                        ].
+                        cat ~= 'obsolete' ifTrue:[
+                            newList add:cat
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ].
 
     newList notEmpty ifTrue:[
-	newList add:'* all *'; add:'* hierarchy *'.
+        newList add:'* all *'; add:'* hierarchy *'.
     ].
 
     ^ newList asOrderedCollection sort.
@@ -3068,7 +3068,7 @@
             cls := cls soleInstance
         ].
 
-        (cls isNamespace and:[cls ~~ Smalltalk]) ifTrue:[
+        (cls isNameSpace and:[cls ~~ Smalltalk]) ifTrue:[
             cls fileOutDefinitionOn:aStream
         ] ifFalse:[
 
@@ -5012,29 +5012,29 @@
     |classes|
 
     currentNamespace = '* all *' ifTrue:[
-	^ Smalltalk allClassesInCategory:currentClassCategory
+        ^ Smalltalk allClassesInCategory:currentClassCategory
     ].
 
     classes := Set new.
 
     (self listOfNamespaces) do:[:aNamespace |
-	aNamespace allBehaviorsDo:[:aClass |
-	    |actualNamespace nm|
-
-	    aClass isMeta ifFalse:[
-		(aCategory = '* all *'
-		or:[aClass category = aCategory]) ifTrue:[
-		    (aClass isNamespace not
-		    or:[aClass == Smalltalk]) ifTrue:[
-			actualNamespace := aClass nameSpace.
-			(actualNamespace isNamespace not "/ a private class
-			or:[actualNamespace == aNamespace]) ifTrue:[
-			    classes add:aClass
-			]
-		    ]
-		]
-	    ]
-	]
+        aNamespace allBehaviorsDo:[:aClass |
+            |actualNamespace nm|
+
+            aClass isMeta ifFalse:[
+                (aCategory = '* all *'
+                or:[aClass category = aCategory]) ifTrue:[
+                    (aClass isNameSpace not
+                    or:[aClass == Smalltalk]) ifTrue:[
+                        actualNamespace := aClass nameSpace.
+                        (actualNamespace isNameSpace not "/ a private class
+                        or:[actualNamespace == aNamespace]) ifTrue:[
+                            classes add:aClass
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ].
     ^ classes
 
@@ -5597,55 +5597,55 @@
     namesPresent := Set new.
 
     (aCategory = '* hierarchy *') ifTrue:[
-	listOfClassNames := OrderedCollection new.
-	listOfClasses := OrderedCollection new.
-
-	self classHierarchyOf:Object withAutoloaded:true do:[:aClass :lvl|
-	    |indent|
-
-	    (aClass isNamespace not
-	    or:[aClass == Smalltalk]) ifTrue:[
-		aClass isObsolete ifFalse:[
-		    nm := self displayedClassNameOf:aClass.
-
-		    (namesPresent includes:nm) ifFalse:[
-			indent := String new:lvl*2.
-
-			"/ show classes from other nameSpaces in italic
-
-			(allNameSpaces not
-			 and:[(self findClassNamedInNameSpace:nm) isNil]) ifTrue:[
-			    nm := nm asText emphasizeAllWith:#italic.
-			].
-			nm := indent , nm.
-			namesPresent add:nm.
-			listOfClassNames add:nm.
-			listOfClasses add:nm.
-		    ]
-		]
-	    ]
-	].
-	namesFlag ifFalse:[
-	    ^ listOfClasses
-	].
-	^ listOfClassNames
+        listOfClassNames := OrderedCollection new.
+        listOfClasses := OrderedCollection new.
+
+        self classHierarchyOf:Object withAutoloaded:true do:[:aClass :lvl|
+            |indent|
+
+            (aClass isNameSpace not
+            or:[aClass == Smalltalk]) ifTrue:[
+                aClass isObsolete ifFalse:[
+                    nm := self displayedClassNameOf:aClass.
+
+                    (namesPresent includes:nm) ifFalse:[
+                        indent := String new:lvl*2.
+
+                        "/ show classes from other nameSpaces in italic
+
+                        (allNameSpaces not
+                         and:[(self findClassNamedInNameSpace:nm) isNil]) ifTrue:[
+                            nm := nm asText emphasizeAllWith:#italic.
+                        ].
+                        nm := indent , nm.
+                        namesPresent add:nm.
+                        listOfClassNames add:nm.
+                        listOfClasses add:nm.
+                    ]
+                ]
+            ]
+        ].
+        namesFlag ifFalse:[
+            ^ listOfClasses
+        ].
+        ^ listOfClassNames
     ].
 
     (aCategory = '* all *') ifTrue:[
-	anyCategory := true
+        anyCategory := true
     ] ifFalse:[
-	anyCategory := false.
-	(aCategory = '* no category *') ifTrue:[
-	    searchCategory := nil
-	] ifFalse:[
-	    searchCategory := aCategory
-	].
+        anyCategory := false.
+        (aCategory = '* no category *') ifTrue:[
+            searchCategory := nil
+        ] ifFalse:[
+            searchCategory := aCategory
+        ].
     ].
 
     allNameSpaces ifTrue:[
-	nameSpaces := Array with:Smalltalk.
+        nameSpaces := Array with:Smalltalk.
     ] ifFalse:[
-	nameSpaces := self listOfNamespaces.
+        nameSpaces := self listOfNamespaces.
     ].
 
     listOfClasses := OrderedCollection new.
@@ -5653,80 +5653,80 @@
     classesPresent := IdentitySet new.
 
     nameSpaces do:[:aNamespace |
-	aNamespace allBehaviorsDo:[:aClass |
-	    |thisCategory actualNamespace nm owner|
-
-	    aClass isMeta ifFalse:[
-		(aClass isNamespace not
-		or:[aClass == Smalltalk]) ifTrue:[
-		    (classesPresent includes:aClass) ifFalse:[
-
-			match := anyCategory.
-			match ifFalse:[
-			    thisCategory := aClass category.
-			    match := ((thisCategory = searchCategory) 
-				     or:[thisCategory = aCategory]).
-			].
-
-			match ifTrue:[
-			    fullClass ifTrue:[
-				aClass owningClass notNil ifTrue:[
-				    match := false
-				]
-			    ].
-			].
-
-			match ifTrue:[
-			    nm := self displayedClassNameOf:aClass.
-			    (namesPresent includes:nm) ifFalse:[
-
-				allNameSpaces ifFalse:[
-				    (owner := aClass topOwningClass) notNil ifTrue:[
-					actualNamespace := owner nameSpace
-				    ] ifFalse:[
-					actualNamespace := aClass nameSpace.
-				    ].
-				    match := actualNamespace isNamespace not "/ a private class
-					     or:[actualNamespace == aNamespace].
-				].
-				match ifTrue:[
-				    namesPresent add:nm.
-				    classesPresent add:aClass.
-				    listOfClasses add:aClass.
-				    listOfClassNames add:nm.
-				]
-			    ]
-			]
-		    ]
-		]
-	    ]
-	]
+        aNamespace allBehaviorsDo:[:aClass |
+            |thisCategory actualNamespace nm owner|
+
+            aClass isMeta ifFalse:[
+                (aClass isNameSpace not
+                or:[aClass == Smalltalk]) ifTrue:[
+                    (classesPresent includes:aClass) ifFalse:[
+
+                        match := anyCategory.
+                        match ifFalse:[
+                            thisCategory := aClass category.
+                            match := ((thisCategory = searchCategory) 
+                                     or:[thisCategory = aCategory]).
+                        ].
+
+                        match ifTrue:[
+                            fullClass ifTrue:[
+                                aClass owningClass notNil ifTrue:[
+                                    match := false
+                                ]
+                            ].
+                        ].
+
+                        match ifTrue:[
+                            nm := self displayedClassNameOf:aClass.
+                            (namesPresent includes:nm) ifFalse:[
+
+                                allNameSpaces ifFalse:[
+                                    (owner := aClass topOwningClass) notNil ifTrue:[
+                                        actualNamespace := owner nameSpace
+                                    ] ifFalse:[
+                                        actualNamespace := aClass nameSpace.
+                                    ].
+                                    match := actualNamespace isNameSpace not "/ a private class
+                                             or:[actualNamespace == aNamespace].
+                                ].
+                                match ifTrue:[
+                                    namesPresent add:nm.
+                                    classesPresent add:aClass.
+                                    listOfClasses add:aClass.
+                                    listOfClassNames add:nm.
+                                ]
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ].
 
     fullClass ifFalse:[
-	"/
-	"/ mhm - must search through private classes of those
-	"/ in smalltalk (they are not visible in the nameSpace,
-	"/ but should also be displayed)
-	"/
-	Smalltalk allBehaviorsDo:[:aClass |
-	    |actualNamespace owner|
-
-	    aClass isMeta ifFalse:[
-		(classesPresent includes:aClass) ifFalse:[
-		    (owner := aClass topOwningClass) notNil ifTrue:[
-			(classesPresent includes:owner) ifTrue:[
-			    nm := self displayedClassNameOf:aClass.
-			    (namesPresent includes:nm) ifFalse:[
-				namesPresent add:nm.
-				listOfClasses add:aClass.
-				listOfClassNames add:nm.
-			    ]
-			]
-		    ]
-		]
-	    ]
-	].
+        "/
+        "/ mhm - must search through private classes of those
+        "/ in smalltalk (they are not visible in the nameSpace,
+        "/ but should also be displayed)
+        "/
+        Smalltalk allBehaviorsDo:[:aClass |
+            |actualNamespace owner|
+
+            aClass isMeta ifFalse:[
+                (classesPresent includes:aClass) ifFalse:[
+                    (owner := aClass topOwningClass) notNil ifTrue:[
+                        (classesPresent includes:owner) ifTrue:[
+                            nm := self displayedClassNameOf:aClass.
+                            (namesPresent includes:nm) ifFalse:[
+                                namesPresent add:nm.
+                                listOfClasses add:aClass.
+                                listOfClassNames add:nm.
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ].
     ].
 
     (listOfClasses size == 0) ifTrue:[^ nil].
@@ -5735,24 +5735,24 @@
     listOfClassNames sortWith:listOfClasses.
 
     namesFlag ifFalse:[
-	^ listOfClasses
+        ^ listOfClasses
     ].
 
     "/ indent after sorting
     1 to:listOfClassNames size do:[:index |
-	|nm cls owner s|
-
-	cls := listOfClasses at:index.
-	owner := cls.
-	(owner := owner owningClass) notNil ifTrue:[
-	    nm := listOfClassNames at:index.
-	    s := nm.
-	    [owner notNil] whileTrue:[    
-		s := '  ' , s.
-		owner := owner owningClass
-	    ].
-	    listOfClassNames at:index put:s.
-	].
+        |nm cls owner s|
+
+        cls := listOfClasses at:index.
+        owner := cls.
+        (owner := owner owningClass) notNil ifTrue:[
+            nm := listOfClassNames at:index.
+            s := nm.
+            [owner notNil] whileTrue:[    
+                s := '  ' , s.
+                owner := owner owningClass
+            ].
+            listOfClassNames at:index put:s.
+        ].
     ].
 
     ^ listOfClassNames
@@ -11022,14 +11022,14 @@
     |n selectedClass str selectedCategory l newCat|
 
     nsName = '* all *' ifTrue:[
-	currentNamespace := nsName.
+        currentNamespace := nsName.
     ] ifFalse:[
-	n := Smalltalk at:nsName asSymbol.
-	n isNamespace ifTrue:[
-	    currentNamespace := n.
-	] ifFalse:[
-	    ^ self
-	]
+        n := Smalltalk at:nsName asSymbol.
+        n isNameSpace ifTrue:[
+            currentNamespace := n.
+        ] ifFalse:[
+            ^ self
+        ]
     ].
 
     selectedClass := actualClass.
@@ -11038,31 +11038,31 @@
 
     self updateClassCategoryListWithScroll:true.
     selectedCategory notNil ifTrue:[
-	self classCategorySelectionChanged.
+        self classCategorySelectionChanged.
     ].
 
     selectedClass notNil ifTrue:[
-	str := self displayedClassNameOf:selectedClass.
-
-	self switchToClassNamed:str.
-
-	((l := classListView list) isNil
-	or:[(l includes:str) not]) ifTrue:[
-	     currentClassCategory := nil.
-	     currentClass := nil.
-	     aspect := nil.   
-	     self updateMethodCategoryList.
-	     self updateMethodList.
-	     self updateCodeView.
-	].
-
-	(classCategoryListView notNil and:[currentClass notNil]) ifTrue:[
-	    newCat := currentClass category.
-	    (currentClassCategory = newCat) ifFalse:[
-		currentClassCategory := newCat.
-		classCategoryListView setSelectElement:newCat
-	    ]
-	].
+        str := self displayedClassNameOf:selectedClass.
+
+        self switchToClassNamed:str.
+
+        ((l := classListView list) isNil
+        or:[(l includes:str) not]) ifTrue:[
+             currentClassCategory := nil.
+             currentClass := nil.
+             aspect := nil.   
+             self updateMethodCategoryList.
+             self updateMethodList.
+             self updateCodeView.
+        ].
+
+        (classCategoryListView notNil and:[currentClass notNil]) ifTrue:[
+            newCat := currentClass category.
+            (currentClassCategory = newCat) ifFalse:[
+                currentClassCategory := newCat.
+                classCategoryListView setSelectElement:newCat
+            ]
+        ].
     ]
 
     "Created: 3.1.1997 / 11:11:13 / cg"
@@ -11761,25 +11761,25 @@
     nameSpaceList := self listOfNamespaces.
 
     Smalltalk allBehaviorsDo:[:aClass |
-	|actualNamespace match owner|
-
-	aClass isMeta ifFalse:[
-	    (aClass isNamespace not
-	    or:[aClass == Smalltalk]) ifTrue:[
-		match := allNameSpaces.
-		match ifFalse:[
-		    (owner := aClass topOwningClass) notNil ifTrue:[
-			actualNamespace := owner nameSpace
-		    ] ifFalse:[
-			actualNamespace := aClass nameSpace.
-		    ].
-		    match := nameSpaceList includesIdentical:actualNamespace.
-		].
-		match ifTrue:[
-		    classes addAll:(aClass withAllSuperclasses).
-		]
-	    ]
-	]
+        |actualNamespace match owner|
+
+        aClass isMeta ifFalse:[
+            (aClass isNameSpace not
+            or:[aClass == Smalltalk]) ifTrue:[
+                match := allNameSpaces.
+                match ifFalse:[
+                    (owner := aClass topOwningClass) notNil ifTrue:[
+                        actualNamespace := owner nameSpace
+                    ] ifFalse:[
+                        actualNamespace := aClass nameSpace.
+                    ].
+                    match := nameSpaceList includesIdentical:actualNamespace.
+                ].
+                match ifTrue:[
+                    classes addAll:(aClass withAllSuperclasses).
+                ]
+            ]
+        ]
     ].
 
     "/ now, generate a dictionary, which associates a set of subclasses
@@ -11787,15 +11787,15 @@
 
     subclassDict := IdentityDictionary new:classes size.
     classes do:[:aClass |
-	s := aClass superclass.
-	s notNil ifTrue:[
-	    l := subclassDict at:s ifAbsent:[nil].
-	    l isNil ifTrue:[
-		l := OrderedCollection new:5.
-		subclassDict at:s put:l
-	    ].
-	    l add:aClass
-	]
+        s := aClass superclass.
+        s notNil ifTrue:[
+            l := subclassDict at:s ifAbsent:[nil].
+            l isNil ifTrue:[
+                l := OrderedCollection new:5.
+                subclassDict at:s put:l
+            ].
+            l add:aClass
+        ]
     ].
 
     "/
@@ -11808,12 +11808,12 @@
     "/ if autoloaded classes are wanted ...
     "/
     withAutoloaded ifTrue:[
-	(remaining includes:Autoload) ifTrue:[
-	    self classHierarchyOf:Autoload level:0 do:aBlock using:subclassDict removeFrom:remaining.
-	].
-	(remaining asSortedCollection:[:a :b | a name < b name]) do:[:aNilSubclass |
-	    aBlock value:aNilSubclass value:0
-	]
+        (remaining includes:Autoload) ifTrue:[
+            self classHierarchyOf:Autoload level:0 do:aBlock using:subclassDict removeFrom:remaining.
+        ].
+        (remaining asSortedCollection:[:a :b | a name < b name]) do:[:aNilSubclass |
+            aBlock value:aNilSubclass value:0
+        ]
     ].
 
     "Created: 28.5.1996 / 13:46:23 / cg"
@@ -12313,7 +12313,7 @@
         ^ self setAcceptActionForJavaClass.
     ].
 
-    (currentClass isNamespace and:[currentClass ~~ Smalltalk]) ifTrue:[
+    (currentClass isNameSpace and:[currentClass ~~ Smalltalk]) ifTrue:[
         self clearAcceptAction.
     ] ifFalse:[
         codeView acceptAction:[:theCode |
@@ -12450,7 +12450,7 @@
                             codeView modified:false.
                             self classCategoryUpdate.
                             self updateClassListWithScroll:false.
-                            cls isNamespace ifFalse:[
+                            cls isNameSpace ifFalse:[
                                 self switchToClassNamed:(cls name).
                             ]
                         ]
@@ -14064,6 +14064,6 @@
 !BrowserView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.612 2000-03-21 14:11:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.613 2000-03-24 16:42:52 cg Exp $'
 ! !
 BrowserView initialize!
--- a/DictionaryInspectorView.st	Tue Mar 21 15:11:44 2000 +0100
+++ b/DictionaryInspectorView.st	Fri Mar 24 17:43:04 2000 +0100
@@ -49,7 +49,7 @@
 
     |items m idx|
 
-    inspectedObject isNamespace ifTrue:[
+    inspectedObject isNameSpace ifTrue:[
         items := #(
                        ('copy key'             doCopyKey      )
                        ('-')
@@ -283,7 +283,7 @@
 
     |aList n cls|
 
-    inspectedObject isNamespace ifTrue:[
+    inspectedObject isNameSpace ifTrue:[
         keys := SortedCollection new:1000.
 
         (hideClassVars or:[hideClasses or:[hideAliases]]) ifTrue:[
@@ -348,7 +348,7 @@
     "helper - return the index for a named instVar;
      nil, if self or a keyed instvar is selected."
 
-    inspectedObject isNamespace ifTrue:[
+    inspectedObject isNameSpace ifTrue:[
         ^ nil
     ].
     ^ super instVarIndexForLine:lineNr
@@ -357,7 +357,7 @@
 keyIndexForLine:lineNr
     "helper - return the index of the key-list"
 
-    inspectedObject isNamespace ifTrue:[
+    inspectedObject isNameSpace ifTrue:[
         (hideReceiver not
         and:[lineNr == 1 or:[lineNr isNil]]) ifTrue:[
             ^ nil "/ self selected
@@ -370,7 +370,7 @@
 namedFieldList 
     "return a list of instVar names to show in the selectionList."
 
-    inspectedObject isNamespace ifTrue:[
+    inspectedObject isNameSpace ifTrue:[
         "/ empty ...
         ^ OrderedCollection new
     ].
@@ -406,5 +406,5 @@
 !DictionaryInspectorView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.44 1999-07-23 21:04:37 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.45 2000-03-24 16:43:04 cg Exp $'
 ! !