intitial checkin
authorca
Mon, 13 Jan 1997 17:43:30 +0100
changeset 33 eeb1fd7f92aa
parent 32 9dfc1899e849
child 34 0f083a268b66
intitial checkin
InspectorList.st
NewInspectorList.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/InspectorList.st	Mon Jan 13 17:43:30 1997 +0100
@@ -0,0 +1,437 @@
+"{ NameSpace: NewInspector }"
+
+Object subclass:#InspectorList
+	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Inspector'
+!
+
+
+!InspectorList class methodsFor:'instance creation'!
+
+for:anObject
+    "create a new list for an instance
+    "
+    ^ self basicNew for:anObject
+
+
+! !
+
+!InspectorList class methodsFor:'testing'!
+
+isDirectory:anInstance
+    "returns true if the class is a directory
+    "
+    |cls|
+
+    anInstance notNil ifTrue:[
+        cls := anInstance class.
+
+        cls == Character  ifTrue:[ ^ false ].
+        cls == Symbol     ifTrue:[ ^ false ].
+        cls == String     ifTrue:[ ^ false ].
+
+        cls allInstVarNames notEmpty ifTrue:[
+            ^ true
+        ].
+
+        anInstance isVariable ifTrue:[
+            ^ true
+        ].
+    ].
+    ^ false
+
+
+! !
+
+!InspectorList methodsFor:'accessing'!
+
+includesSelf
+    "returns true if 'self' is included in the list
+    "
+    ^ (self instanceTypeAt:1) == #self
+
+
+!
+
+includesSelf:aBoolean
+    "includes 'self' dependant on the boolean
+    "
+    (self includesSelf) ~~ aBoolean ifTrue:[
+        aBoolean ifTrue:[
+            instanceNames addFirst:'self'.
+            instanceTypes addFirst:#self.
+
+            selection isNil ifTrue:[selection := 1]
+                           ifFalse:[selection := selection + 1]
+        ] ifFalse:[
+            instanceNames removeFirst.
+            instanceTypes removeFirst.
+
+            selection isNil ifFalse:[
+                (selection := selection - 1) == 0 ifTrue:[
+                    selection := nil
+                ]
+            ]
+        ]
+    ]
+
+
+!
+
+size
+    "returns current list size
+    "
+    ^ instanceNames size
+
+! !
+
+!InspectorList methodsFor:'accessing contents'!
+
+inspectedObject
+    "returns current inspected object
+    "
+    ^ inspectedObject
+
+
+!
+
+instanceNameAt:anIndex
+    "returns the name assigned to the index
+    "
+    |idx nm|
+
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        nm := instanceNames at:anIndex.
+
+        (nm at:1) isDigit ifFalse:[
+            ^ nm
+        ].
+        idx := Number readFrom:nm onError:0.
+        ^ '[', idx printString, ']'.
+    ].
+    ^ nil
+
+
+!
+
+instanceNames
+    "returns list of instance names
+    "
+    ^ instanceNames
+
+
+!
+
+instanceTypeAt:anIndex
+    "returns type assigned to the list entry (#directory #normal #self)
+    "
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        ^ instanceTypes at:anIndex
+    ].
+    ^ nil
+
+
+!
+
+instanceTypes
+    "returns list of types (#directory #normal #self)
+    "
+    ^ instanceTypes
+
+
+!
+
+instanceVarAt:anIndex
+    "returns the instnace variable assigned to the index
+    "
+    |idx nm|
+
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        nm := instanceNames at:anIndex.
+
+        (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
+
+
+! !
+
+!InspectorList methodsFor:'actions'!
+
+accept:aText notifying:aView
+    "on error #Error is returned otherwise the inspected object instance
+    "
+    |txt slNr value|
+
+    (selection isNil or:[(txt := self textToString:aText) isNil]) ifTrue:[
+        ^ #Error
+    ].
+
+    self includesSelf ifFalse:[slNr := selection]
+                       ifTrue:[slNr := selection -1].
+
+    value := inspectedObject class evaluatorClass 
+               evaluate:txt
+               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
+
+
+!
+
+doIt:aCode notifying:aView
+    "on success the value returned from parser is returned otherwise #Error
+    "
+    |code result evaluator selInstVar state|
+
+    (selection isNil or:[(code := self textToString:aCode) isNil]) ifFalse:[
+        selInstVar := self selectedInstanceVar.
+        evaluator  := selInstVar class evaluatorClass.
+        state      := true.
+
+        evaluator notNil ifTrue:[
+            result := evaluator evaluate:code 
+                                      in:nil 
+                                receiver:selInstVar 
+                               notifying:aView 
+                                  logged:true 
+                                  ifFail:[state := false].
+
+            state ifTrue:[
+                self update.
+              ^ result
+            ]
+        ]
+    ].
+    ^ #Error.
+
+
+! !
+
+!InspectorList methodsFor:'initialization'!
+
+for:anObject
+    "setup a new instance
+    "
+    |varNamesSize|
+
+    inspectedObject := anObject.
+    selection       := nil.
+
+    (self class isDirectory:inspectedObject) 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
+            ]
+        ]
+    ] ifFalse:[
+        instanceNames := OrderedCollection new.
+        instanceTypes := OrderedCollection new.
+    ].
+    self update.
+! !
+
+!InspectorList methodsFor:'private'!
+
+lastVariableId
+    "returns last variable id or nil if not growable
+    "
+    |lstId bscSz|
+
+    (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
+        ^ nil
+    ].
+
+    bscSz := inspectedObject class instSize.
+
+    self includesSelf ifTrue:[
+        bscSz := bscSz + 1.
+    ].
+    lstId := instanceTypes size - bscSz.
+
+    (lstId ~~ 0 and:[instanceTypes last == #grow]) ifTrue:[^ lstId-1]
+                                                  ifFalse:[^ lstId].
+!
+
+resizeVariableList:toNumber
+    "resize variable list
+    "
+    |lstVarId basicSize newLastId obj|
+
+    (lstVarId := self lastVariableId) isNil ifTrue:[
+        ^ self
+    ].
+
+    basicSize := inspectedObject basicSize.
+
+    (toNumber <= lstVarId or:[basicSize == lstVarId]) ifTrue:[
+        ^ self
+    ].
+    newLastId := (toNumber + 49) roundTo:100.
+
+    newLastId > basicSize ifTrue:[
+        newLastId := basicSize
+    ].
+
+    lstVarId ~~ 0 ifTrue:[
+        instanceTypes last == #grow ifTrue:[
+            instanceNames removeLast.       " ..    "
+            instanceTypes removeLast.       " #grow "
+        ]
+    ].
+
+    [lstVarId ~~ newLastId] whileTrue:[
+        lstVarId := lstVarId + 1.
+        obj := inspectedObject basicAt:lstVarId.
+
+        (self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
+                                    ifFalse:[instanceTypes add:#normal].
+
+        instanceNames add:(lstVarId printString, '   ', obj class name printString).
+    ].
+
+    lstVarId ~~ basicSize ifTrue:[
+        instanceNames add:'..'.
+        instanceTypes add:#grow
+    ].
+
+
+!
+
+textToString:aText
+    "converts a text to a string
+    "
+    |s|
+
+    aText isString ifTrue:[
+        s := aText string
+    ] ifFalse:[
+        aText isCollection ifTrue:[
+            s := ''.
+            aText do:[:el|el notNil ifTrue:[s := s, el string]].
+        ]
+    ].
+
+    s notNil ifTrue:[
+        (s := s withoutSeparators) notEmpty ifTrue:[
+            ^ s
+        ]
+    ].
+    ^ nil.
+
+
+!
+
+update
+    "update contents
+    "
+    |delNr lstVarId|
+
+    (lstVarId := self lastVariableId) isNil ifFalse:[
+        lstVarId == 0 ifTrue:[
+            lstVarId := 100
+        ] ifFalse:[
+            instanceTypes last == #grow ifTrue:[delNr := lstVarId+1]
+                                       ifFalse:[delNr := lstVarId].
+
+            instanceTypes removeLast:delNr.     
+            instanceNames removeLast:delNr.
+        ].
+        self resizeVariableList:lstVarId.
+    ]
+! !
+
+!InspectorList methodsFor:'selections'!
+
+selectedInstanceName
+    "returns name of current selection or nil
+    "
+    ^ self instanceNameAt:selection
+
+
+!
+
+selectedInstanceType
+    "returns type of current selection or nil
+    "
+    ^ self instanceTypeAt:selection
+
+
+!
+
+selectedInstanceVar
+    "returns current inspected instance variable or nil
+    "
+    ^ self instanceVarAt:selection
+
+
+!
+
+selection
+    "returns current selection number or nil
+    "
+    ^ selection
+
+
+!
+
+selection:aNrOrNil
+    "change current selection to a number or nil; may grow a variable list
+    "
+    |rsz|
+
+    aNrOrNil isNil ifTrue:[
+        self includesSelf ifTrue:[selection := 1]
+                         ifFalse:[selection := nil]
+    ] ifFalse:[
+        aNrOrNil >= instanceNames size ifTrue:[
+            (rsz := self lastVariableId) notNil ifTrue:[
+                rsz := rsz * 2.
+
+                rsz < aNrOrNil ifTrue:[
+                    rsz := aNrOrNil
+                ].
+                self resizeVariableList:rsz
+            ]
+        ].
+        aNrOrNil > instanceNames size ifFalse:[selection := aNrOrNil]
+                                       ifTrue:[selection := nil]
+    ]
+
+! !
+
+!InspectorList class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/NewInspectorList.st	Mon Jan 13 17:43:30 1997 +0100
@@ -0,0 +1,437 @@
+"{ NameSpace: NewInspector }"
+
+Object subclass:#InspectorList
+	instanceVariableNames:'inspectedObject instanceNames instanceTypes selection'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Inspector'
+!
+
+
+!InspectorList class methodsFor:'instance creation'!
+
+for:anObject
+    "create a new list for an instance
+    "
+    ^ self basicNew for:anObject
+
+
+! !
+
+!InspectorList class methodsFor:'testing'!
+
+isDirectory:anInstance
+    "returns true if the class is a directory
+    "
+    |cls|
+
+    anInstance notNil ifTrue:[
+        cls := anInstance class.
+
+        cls == Character  ifTrue:[ ^ false ].
+        cls == Symbol     ifTrue:[ ^ false ].
+        cls == String     ifTrue:[ ^ false ].
+
+        cls allInstVarNames notEmpty ifTrue:[
+            ^ true
+        ].
+
+        anInstance isVariable ifTrue:[
+            ^ true
+        ].
+    ].
+    ^ false
+
+
+! !
+
+!InspectorList methodsFor:'accessing'!
+
+includesSelf
+    "returns true if 'self' is included in the list
+    "
+    ^ (self instanceTypeAt:1) == #self
+
+
+!
+
+includesSelf:aBoolean
+    "includes 'self' dependant on the boolean
+    "
+    (self includesSelf) ~~ aBoolean ifTrue:[
+        aBoolean ifTrue:[
+            instanceNames addFirst:'self'.
+            instanceTypes addFirst:#self.
+
+            selection isNil ifTrue:[selection := 1]
+                           ifFalse:[selection := selection + 1]
+        ] ifFalse:[
+            instanceNames removeFirst.
+            instanceTypes removeFirst.
+
+            selection isNil ifFalse:[
+                (selection := selection - 1) == 0 ifTrue:[
+                    selection := nil
+                ]
+            ]
+        ]
+    ]
+
+
+!
+
+size
+    "returns current list size
+    "
+    ^ instanceNames size
+
+! !
+
+!InspectorList methodsFor:'accessing contents'!
+
+inspectedObject
+    "returns current inspected object
+    "
+    ^ inspectedObject
+
+
+!
+
+instanceNameAt:anIndex
+    "returns the name assigned to the index
+    "
+    |idx nm|
+
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        nm := instanceNames at:anIndex.
+
+        (nm at:1) isDigit ifFalse:[
+            ^ nm
+        ].
+        idx := Number readFrom:nm onError:0.
+        ^ '[', idx printString, ']'.
+    ].
+    ^ nil
+
+
+!
+
+instanceNames
+    "returns list of instance names
+    "
+    ^ instanceNames
+
+
+!
+
+instanceTypeAt:anIndex
+    "returns type assigned to the list entry (#directory #normal #self)
+    "
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        ^ instanceTypes at:anIndex
+    ].
+    ^ nil
+
+
+!
+
+instanceTypes
+    "returns list of types (#directory #normal #self)
+    "
+    ^ instanceTypes
+
+
+!
+
+instanceVarAt:anIndex
+    "returns the instnace variable assigned to the index
+    "
+    |idx nm|
+
+    (anIndex notNil and:[anIndex <= instanceTypes size]) ifTrue:[
+        nm := instanceNames at:anIndex.
+
+        (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
+
+
+! !
+
+!InspectorList methodsFor:'actions'!
+
+accept:aText notifying:aView
+    "on error #Error is returned otherwise the inspected object instance
+    "
+    |txt slNr value|
+
+    (selection isNil or:[(txt := self textToString:aText) isNil]) ifTrue:[
+        ^ #Error
+    ].
+
+    self includesSelf ifFalse:[slNr := selection]
+                       ifTrue:[slNr := selection -1].
+
+    value := inspectedObject class evaluatorClass 
+               evaluate:txt
+               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
+
+
+!
+
+doIt:aCode notifying:aView
+    "on success the value returned from parser is returned otherwise #Error
+    "
+    |code result evaluator selInstVar state|
+
+    (selection isNil or:[(code := self textToString:aCode) isNil]) ifFalse:[
+        selInstVar := self selectedInstanceVar.
+        evaluator  := selInstVar class evaluatorClass.
+        state      := true.
+
+        evaluator notNil ifTrue:[
+            result := evaluator evaluate:code 
+                                      in:nil 
+                                receiver:selInstVar 
+                               notifying:aView 
+                                  logged:true 
+                                  ifFail:[state := false].
+
+            state ifTrue:[
+                self update.
+              ^ result
+            ]
+        ]
+    ].
+    ^ #Error.
+
+
+! !
+
+!InspectorList methodsFor:'initialization'!
+
+for:anObject
+    "setup a new instance
+    "
+    |varNamesSize|
+
+    inspectedObject := anObject.
+    selection       := nil.
+
+    (self class isDirectory:inspectedObject) 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
+            ]
+        ]
+    ] ifFalse:[
+        instanceNames := OrderedCollection new.
+        instanceTypes := OrderedCollection new.
+    ].
+    self update.
+! !
+
+!InspectorList methodsFor:'private'!
+
+lastVariableId
+    "returns last variable id or nil if not growable
+    "
+    |lstId bscSz|
+
+    (inspectedObject isVariable and:[self class isDirectory:inspectedObject]) ifFalse:[
+        ^ nil
+    ].
+
+    bscSz := inspectedObject class instSize.
+
+    self includesSelf ifTrue:[
+        bscSz := bscSz + 1.
+    ].
+    lstId := instanceTypes size - bscSz.
+
+    (lstId ~~ 0 and:[instanceTypes last == #grow]) ifTrue:[^ lstId-1]
+                                                  ifFalse:[^ lstId].
+!
+
+resizeVariableList:toNumber
+    "resize variable list
+    "
+    |lstVarId basicSize newLastId obj|
+
+    (lstVarId := self lastVariableId) isNil ifTrue:[
+        ^ self
+    ].
+
+    basicSize := inspectedObject basicSize.
+
+    (toNumber <= lstVarId or:[basicSize == lstVarId]) ifTrue:[
+        ^ self
+    ].
+    newLastId := (toNumber + 49) roundTo:100.
+
+    newLastId > basicSize ifTrue:[
+        newLastId := basicSize
+    ].
+
+    lstVarId ~~ 0 ifTrue:[
+        instanceTypes last == #grow ifTrue:[
+            instanceNames removeLast.       " ..    "
+            instanceTypes removeLast.       " #grow "
+        ]
+    ].
+
+    [lstVarId ~~ newLastId] whileTrue:[
+        lstVarId := lstVarId + 1.
+        obj := inspectedObject basicAt:lstVarId.
+
+        (self class isDirectory:obj) ifTrue:[instanceTypes add:#directory]
+                                    ifFalse:[instanceTypes add:#normal].
+
+        instanceNames add:(lstVarId printString, '   ', obj class name printString).
+    ].
+
+    lstVarId ~~ basicSize ifTrue:[
+        instanceNames add:'..'.
+        instanceTypes add:#grow
+    ].
+
+
+!
+
+textToString:aText
+    "converts a text to a string
+    "
+    |s|
+
+    aText isString ifTrue:[
+        s := aText string
+    ] ifFalse:[
+        aText isCollection ifTrue:[
+            s := ''.
+            aText do:[:el|el notNil ifTrue:[s := s, el string]].
+        ]
+    ].
+
+    s notNil ifTrue:[
+        (s := s withoutSeparators) notEmpty ifTrue:[
+            ^ s
+        ]
+    ].
+    ^ nil.
+
+
+!
+
+update
+    "update contents
+    "
+    |delNr lstVarId|
+
+    (lstVarId := self lastVariableId) isNil ifFalse:[
+        lstVarId == 0 ifTrue:[
+            lstVarId := 100
+        ] ifFalse:[
+            instanceTypes last == #grow ifTrue:[delNr := lstVarId+1]
+                                       ifFalse:[delNr := lstVarId].
+
+            instanceTypes removeLast:delNr.     
+            instanceNames removeLast:delNr.
+        ].
+        self resizeVariableList:lstVarId.
+    ]
+! !
+
+!InspectorList methodsFor:'selections'!
+
+selectedInstanceName
+    "returns name of current selection or nil
+    "
+    ^ self instanceNameAt:selection
+
+
+!
+
+selectedInstanceType
+    "returns type of current selection or nil
+    "
+    ^ self instanceTypeAt:selection
+
+
+!
+
+selectedInstanceVar
+    "returns current inspected instance variable or nil
+    "
+    ^ self instanceVarAt:selection
+
+
+!
+
+selection
+    "returns current selection number or nil
+    "
+    ^ selection
+
+
+!
+
+selection:aNrOrNil
+    "change current selection to a number or nil; may grow a variable list
+    "
+    |rsz|
+
+    aNrOrNil isNil ifTrue:[
+        self includesSelf ifTrue:[selection := 1]
+                         ifFalse:[selection := nil]
+    ] ifFalse:[
+        aNrOrNil >= instanceNames size ifTrue:[
+            (rsz := self lastVariableId) notNil ifTrue:[
+                rsz := rsz * 2.
+
+                rsz < aNrOrNil ifTrue:[
+                    rsz := aNrOrNil
+                ].
+                self resizeVariableList:rsz
+            ]
+        ].
+        aNrOrNil > instanceNames size ifFalse:[selection := aNrOrNil]
+                                       ifTrue:[selection := nil]
+    ]
+
+! !
+
+!InspectorList class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !