NewInspectorList.st
changeset 2621 285fa261cbcb
parent 1213 6cf7a4c2dfce
child 3612 959a338e5888
--- a/NewInspectorList.st	Wed Oct 14 08:13:10 2009 +0200
+++ b/NewInspectorList.st	Wed Oct 14 13:43:27 2009 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,7 +11,7 @@
 "
 
 
-"{ NameSpace: NewInspector }"
+"{ NameSpace: Tools }"
 
 Object subclass:#NewInspectorList
 	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
@@ -25,7 +25,7 @@
 copyright
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -64,19 +64,19 @@
     |string|
 
     aCollection isCollection ifTrue:[
-        aCollection isString ifTrue:[
-            string := aCollection
-        ] ifFalse:[
-            string := aCollection asStringWith:Character space
-                                          from:1 to:(aCollection size)
-                                  compressTabs:true 
-                                         final:nil
-        ].
-        string := string withoutSeparators.
+	aCollection isString ifTrue:[
+	    string := aCollection
+	] ifFalse:[
+	    string := aCollection asStringWith:Character space
+					  from:1 to:(aCollection size)
+				  compressTabs:true
+					 final:nil
+	].
+	string := string withoutSeparators.
 
-        string notEmpty ifTrue:[
-            ^ string
-        ]
+	string notEmpty ifTrue:[
+	    ^ string
+	]
     ].
     ^ nil
 
@@ -91,21 +91,21 @@
     |cls|
 
     anInstance notNil ifTrue:[
-        cls := anInstance class.
+	cls := anInstance class.
 
-        cls == Character  ifTrue:[ ^ false ].
-        cls == Symbol     ifTrue:[ ^ false ].
-        cls == String     ifTrue:[ ^ false ].
-        cls == Float      ifTrue:[ ^ false ].
-        cls == ShortFloat ifTrue:[ ^ false ].
+	cls == Character  ifTrue:[ ^ false ].
+	cls == Symbol     ifTrue:[ ^ false ].
+	cls == String     ifTrue:[ ^ false ].
+	cls == Float      ifTrue:[ ^ false ].
+	cls == ShortFloat ifTrue:[ ^ false ].
 
-        cls allInstVarNames notEmpty ifTrue:[
-            ^ true
-        ].
+	cls allInstVarNames notEmpty ifTrue:[
+	    ^ true
+	].
 
-        anInstance isVariable ifTrue:[
-            ^ true
-        ].
+	anInstance isVariable ifTrue:[
+	    ^ true
+	].
     ].
     ^ false
 
@@ -118,12 +118,12 @@
     |cls|
 
     anInstance notNil ifTrue:[
-        cls := anInstance class.
+	cls := anInstance class.
 
       ^ (     cls ~~ True
-         and:[cls ~~ False
-         and:[cls ~~ SmallInteger]]
-        )
+	 and:[cls ~~ False
+	 and:[cls ~~ SmallInteger]]
+	)
     ].
     ^ false.
 
@@ -135,23 +135,23 @@
     "includes 'self' dependant on the boolean
     "
     (self includesSelf) ~~ aBoolean ifTrue:[
-        aBoolean ifTrue:[
-            instanceNames addFirst:'self'.
-            instanceTypes addFirst:#self.
+	aBoolean ifTrue:[
+	    instanceNames addFirst:'self'.
+	    instanceTypes addFirst:#self.
 
-            selection notNil ifTrue:[selection := selection + 1]
-                            ifFalse:[selection := 1]
+	    selection notNil ifTrue:[selection := selection + 1]
+			    ifFalse:[selection := 1]
 
-        ] ifFalse:[
-            instanceNames removeFirst.
-            instanceTypes removeFirst.
+	] ifFalse:[
+	    instanceNames removeFirst.
+	    instanceTypes removeFirst.
 
-            selection isNil ifFalse:[
-                (selection := selection - 1) == 0 ifTrue:[
-                    selection := nil
-                ]
-            ]
-        ]
+	    selection isNil ifFalse:[
+		(selection := selection - 1) == 0 ifTrue:[
+		    selection := nil
+		]
+	    ]
+	]
     ]
 
 
@@ -176,19 +176,19 @@
     |start stop size|
 
     inspectedObject isVariable ifTrue:[
-        start := instanceNames findFirst:[:el|(el at:1) isDigit].
-        stop  := instanceTypes size.
+	start := instanceNames findFirst:[:el|(el at:1) isDigit].
+	stop  := instanceTypes size.
 
-        start == 0 ifTrue:[
-            size := stop + 10.  "must be > 1: force a resize the first time"   
-        ] ifFalse:[
-            instanceTypes last ~~ #grow ifTrue:[size := stop]
-                                       ifFalse:[size := stop-1].
+	start == 0 ifTrue:[
+	    size := stop + 10.  "must be > 1: force a resize the first time"
+	] ifFalse:[
+	    instanceTypes last ~~ #grow ifTrue:[size := stop]
+				       ifFalse:[size := stop-1].
 
-            instanceTypes removeFromIndex:start toIndex:stop.
-            instanceNames removeFromIndex:start toIndex:stop.
-        ].
-        self resizeTo:size.
+	    instanceTypes removeFromIndex:start toIndex:stop.
+	    instanceNames removeFromIndex:start toIndex:stop.
+	].
+	self resizeTo:size.
     ]
 
     "Modified: / 4.2.1999 / 20:00:38 / cg"
@@ -217,7 +217,7 @@
      In case of an invalid index nil is returned.
     "
     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[^ instanceTypes at:anIndex]
-                                                       ifTrue:[^ nil].
+						       ifTrue:[^ nil].
 
 
 !
@@ -231,21 +231,21 @@
 !
 
 instanceVarAt:anIndex
-    "returns the instnace variable assigned to the index or 
+    "returns the instnace variable assigned to the index or
      nil in case of an invalid index.
     "
     |nm|
 
     (anIndex isNil or:[anIndex > instanceTypes size]) ifFalse:[
-        nm := instanceNames at:anIndex.
+	nm := instanceNames at:anIndex.
 
-        (nm at:1) isDigit ifFalse:[
-            self includesSelf ifFalse:[
-                ^ inspectedObject instVarAt:anIndex
-            ].
-            anIndex == 1 ifFalse:[^ inspectedObject instVarAt:(anIndex-1)]
-                          ifTrue:[^ inspectedObject]
-        ].
+	(nm at:1) isDigit ifFalse:[
+	    self includesSelf ifFalse:[
+		^ inspectedObject instVarAt:anIndex
+	    ].
+	    anIndex == 1 ifFalse:[^ inspectedObject instVarAt:(anIndex-1)]
+			  ifTrue:[^ inspectedObject]
+	].
       ^ inspectedObject basicAt:(Number readFrom:nm onError:0)
     ].
     ^ nil
@@ -273,46 +273,46 @@
     |lstVarId basicSize newLastId obj instSize|
 
     (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
-        ^ self
+	^ self
     ].
 
     instanceTypes size == 0 ifTrue:[
-        lstVarId := 0
+	lstVarId := 0
     ] ifFalse:[
-        instSize := inspectedObject class instSize.
+	instSize := inspectedObject class instSize.
 
-        instanceTypes first == #self ifTrue:[
-            instSize := instSize + 1
-        ].
-        instanceTypes last == #grow ifTrue:[
-            instanceNames removeLast.       " ..    "
-            instanceTypes removeLast.       " #grow "
-        ].
-        lstVarId := instanceTypes size - instSize.
+	instanceTypes first == #self ifTrue:[
+	    instSize := instSize + 1
+	].
+	instanceTypes last == #grow ifTrue:[
+	    instanceNames removeLast.       " ..    "
+	    instanceTypes removeLast.       " #grow "
+	].
+	lstVarId := instanceTypes size - instSize.
     ].
 
     (basicSize := inspectedObject basicSize) == lstVarId ifTrue:[
-        ^ self
+	^ self
     ].
     newLastId := (1 bitShift:((aNumber-1) highBit)) max:128.
 
     (newLastId + 64) > basicSize ifTrue:[
-        newLastId := basicSize
+	newLastId := basicSize
     ].
 
     [lstVarId ~~ newLastId] whileTrue:[
-        lstVarId := lstVarId + 1.
-        obj := inspectedObject basicAt:lstVarId.
+	lstVarId := lstVarId + 1.
+	obj := inspectedObject basicAt:lstVarId.
 
-        (self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
-                                    ifFalse:[instanceTypes add:#normal].
+	(self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
+				    ifFalse:[instanceTypes add:#normal].
 
-        instanceNames add:(lstVarId printString, '   ', obj class name printString).
+	instanceNames add:(lstVarId printString, '   ', obj class name printString).
     ].
 
     lstVarId ~~ basicSize ifTrue:[
-        instanceNames add:'..'.
-        instanceTypes add:#grow
+	instanceNames add:'..'.
+	instanceTypes add:#grow
     ].
 ! !
 
@@ -349,12 +349,12 @@
     selection := aNrOrNil.
 
     (selection isNil or:[instanceTypes size > selection]) ifFalse:[
-        self resizeTo:selection.
+	self resizeTo:selection.
 
-        selection > instanceTypes size ifTrue:[
-            selection := nil
-        ]
-    ]    
+	selection > instanceTypes size ifTrue:[
+	    selection := nil
+	]
+    ]
 ! !
 
 !NewInspectorList methodsFor:'testing'!
@@ -391,33 +391,33 @@
     |text slNr value|
 
     selection notNil ifTrue:[
-        text := self class asString:aText.
+	text := self class asString:aText.
 
-        text notNil ifTrue:[
-            self includesSelf ifFalse:[slNr := selection]
-                               ifTrue:[slNr := selection-1].
+	text notNil ifTrue:[
+	    self includesSelf ifFalse:[slNr := selection]
+			       ifTrue:[slNr := selection-1].
 
-            value := inspectedObject class evaluatorClass 
-                       evaluate:text
-                       receiver:inspectedObject 
-                      notifying:aView.
+	    value := inspectedObject class evaluatorClass
+		       evaluate:text
+		       receiver:inspectedObject
+		      notifying:aView.
 
-            slNr ~~ 0 ifTrue:[
-                (inspectedObject class isVariable) ifFalse:[
-                    inspectedObject instVarAt:slNr put:value
-                ] ifTrue:[
-                    slNr <= (inspectedObject class instSize) ifTrue:[
-                        inspectedObject instVarAt:slNr put:value
-                    ] ifFalse:[
-                        slNr := slNr - inspectedObject class instSize.
-                        inspectedObject basicAt:slNr put:value
-                    ]
-                ]
-            ].
-            inspectedObject changed.
-            self update.
-          ^ inspectedObject
-        ]
+	    slNr ~~ 0 ifTrue:[
+		(inspectedObject class isVariable) ifFalse:[
+		    inspectedObject instVarAt:slNr put:value
+		] ifTrue:[
+		    slNr <= (inspectedObject class instSize) ifTrue:[
+			inspectedObject instVarAt:slNr put:value
+		    ] ifFalse:[
+			slNr := slNr - inspectedObject class instSize.
+			inspectedObject basicAt:slNr put:value
+		    ]
+		]
+	    ].
+	    inspectedObject changed.
+	    self update.
+	  ^ inspectedObject
+	]
     ].
     ^ #Error
 !
@@ -432,26 +432,26 @@
     selInstVar := self selectedInstanceVar.
 
     selInstVar notNil ifTrue:[
-        code := self class asString:aCode.
+	code := self class asString:aCode.
 
-        code notNil ifTrue:[
-            evaluator := selInstVar class evaluatorClass.
-            successFg := true.
+	code notNil ifTrue:[
+	    evaluator := selInstVar class evaluatorClass.
+	    successFg := true.
 
-            evaluator notNil ifTrue:[
-                result := evaluator evaluate:code 
-                                          in:nil 
-                                    receiver:selInstVar 
-                                   notifying:aView 
-                                      logged:true 
-                                      ifFail:[successFg := false].
+	    evaluator notNil ifTrue:[
+		result := evaluator evaluate:code
+					  in:nil
+				    receiver:selInstVar
+				   notifying:aView
+				      logged:true
+				      ifFail:[successFg := false].
 
-                successFg ifTrue:[
-                    self update. 
-                  ^ result 
-                ]
-            ]
-        ]
+		successFg ifTrue:[
+		    self update.
+		  ^ result
+		]
+	    ]
+	]
     ].
     ^ #Error.
 
@@ -466,24 +466,24 @@
     selection := nil.
 
     anObject == inspectedObject ifFalse:[
-        inspectedObject := anObject.
+	inspectedObject := anObject.
 
-        (self class isDirectory:inspectedObject) ifFalse:[
-            instanceNames := OrderedCollection new.
-            instanceTypes := OrderedCollection new.
-        ] ifTrue:[    
-            instanceNames := inspectedObject class allInstVarNames.
-            varNamesSize  := instanceNames size.
-            instanceTypes := OrderedCollection new:varNamesSize.
+	(self class isDirectory:inspectedObject) ifFalse:[
+	    instanceNames := OrderedCollection new.
+	    instanceTypes := OrderedCollection new.
+	] ifTrue:[
+	    instanceNames := inspectedObject class allInstVarNames.
+	    varNamesSize  := instanceNames size.
+	    instanceTypes := OrderedCollection new:varNamesSize.
 
-            1 to:varNamesSize do:[:i|
-                (self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
-                    instanceTypes add:#directory
-                ] ifFalse:[
-                    instanceTypes add:#normal
-                ]
-            ].
-        ]
+	    1 to:varNamesSize do:[:i|
+		(self class isDirectory:(inspectedObject instVarAt:i)) ifTrue:[
+		    instanceTypes add:#directory
+		] ifFalse:[
+		    instanceTypes add:#normal
+		]
+	    ].
+	]
     ].
     self update
 ! !