NewInspectorListView.st
author ca
Mon, 13 Jan 1997 17:46:56 +0100
changeset 34 0f083a268b66
child 39 03af455029eb
permissions -rw-r--r--
intitial checkin

"{ NameSpace: NewInspector }"

SelectionInListView subclass:#InspectorListView
	instanceVariableNames:'actionHolder listHolder includesSelf'
	classVariableNames:''
	poolDictionaries:''
	category:'Inspector'
!

!InspectorListView class methodsFor:'documentation'!

examples
"

        |top slv a|

        a := OrderedCollection new.
        a add:1.

        top := StandardSystemView new
                label:'select';
                extent:200@200.

        slv := ScrollableView for:self in:top.
        slv origin:0.0@0.0 corner:1.0@1.0.
        slv := slv scrolledView.
        slv inspect:top.
        slv action:[:el|Transcript showCR:(el printString)].
        top open
"
! !

!InspectorListView methodsFor:'accessing actions'!

action:aOneArgAction
    "set the single click action block.
     If non-nil, that one is evaluated on single click, passing the
     selected instance as argument
    "
    actionHolder := aOneArgAction
! !

!InspectorListView methodsFor:'accessing attributes'!

includesSelf
    ^ includesSelf
!

includesSelf:aBool
    includesSelf := aBool
!

inspectedObject
    ^ listHolder inspectedObject
!

isEmpty
    "returns true if view is empty
    "
    ^ listHolder size == 0
!

listHolder
    ^ listHolder
!

notEmpty
    "returns true if view is empty
    "
    ^ listHolder size ~~ 0
! !

!InspectorListView methodsFor:'accessing contents'!

updateFromList:aListHolder
    "set the lists contents from a list
    "
    listHolder := aListHolder.
    listHolder includesSelf:includesSelf.

    super list:(listHolder instanceNames).
    self setSelection:(listHolder selection).

!

updateFromView:aInspectorListView
    "update contents from other view
    "
    self updateFromList:(aInspectorListView listHolder)
!

updateList 
    "set the lists contents dependant on the object
    "
    self updateList:(listHolder inspectedObject) selection:selection.
! !

!InspectorListView methodsFor:'actions'!

accept:aText notifying:aView
    "on error #Error is returned otherwise the inspected object instance
    "
    |res|

    res := listHolder accept:aText notifying:aView.

    res ~~ #Error ifTrue:[
        super list:(listHolder instanceNames).
        self setSelection:(listHolder selection)
    ].
    ^ res
!

doIt:aCode notifying:aView
    "on success the value returned from parser is returned otherwise #Error
    "
    |res|

    res := listHolder doIt:aCode notifying:aView.

    res ~~ #Error ifTrue:[
        super list:(listHolder instanceNames).
        self setSelection:(listHolder selection)
    ].
    ^ res

!

inspect:anObject
    "inspect an object
    "
    ^ self inspect:anObject selection:nil
!

inspect:anObject selection:aNumber
    "inspect an object and set the selection
    "
    aNumber notNil ifTrue:[
        selection := aNumber
    ] ifFalse:[
        (listHolder inspectedObject) ~~ anObject ifTrue:[
            selection := nil
        ]
    ].
    self updateList:anObject selection:selection
! !

!InspectorListView methodsFor:'drawing'!

drawVisibleLineSelected:visLineNr with:fg and:bg
    "redraw a single line as selected."

    |nr| 

    (nr := self visibleLineToListLine:visLineNr) notNil ifTrue:[
        ^ self drawVisibleLine:visLineNr with:fg and:bg.
    ].
    ^ super drawVisibleLine:visLineNr with:fg and:bg

!

redrawArrowVisibleLine:visLineNr
    "draw a right arrow for visible line"

    |nr|

    nr := self visibleLineToListLine:visLineNr.

    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
        self drawRightArrowInVisibleLine:visLineNr
    ]


!

redrawFromVisibleLine:startVisLineNr to:endVisLineNr
    "redefined to look for directory in every line
    "
    super redrawFromVisibleLine:startVisLineNr to:endVisLineNr.

    startVisLineNr to:endVisLineNr do:[:visLineNr|
        self redrawArrowVisibleLine:visLineNr
    ]
!

redrawVisibleLine:visLineNr
    "if the line is one for a directory, draw a right arrow
    "
    super redrawVisibleLine:visLineNr.
    self  redrawArrowVisibleLine:visLineNr.
!

visibleLineNeedsSpecialCare:visLineNr
    |nr|

    (listHolder instanceTypeAt:nr) == #directory ifTrue:[
        ^ true
    ].
    ^ super visibleLineNeedsSpecialCare:visLineNr

!

widthForScrollBetween:firstLine and:lastLine
    "return the width in pixels for a scroll between firstLine and lastLine
     - return full width here since there might be directory marks
    "
    ^ (width - margin - margin)


! !

!InspectorListView methodsFor:'event handling'!

sizeChanged:how
    "redraw marks"

    super sizeChanged:how.
    shown ifTrue:[self invalidate]

! !

!InspectorListView methodsFor:'initialization'!

initialize
    "initialization
    "
    super initialize.

    ignoreReselect := false.
    includesSelf   := false.
    actionHolder   := [:el|].
    listHolder     := InspectorList for:nil.

    actionBlock := [:dummy|
        self setSelection:selection.
        actionHolder value:(self selectedInstanceVar)
    ].
! !

!InspectorListView methodsFor:'private'!

updateList:inspObject selection:aSelection
    "set the lists contents dependant on the object
    "
    listHolder := InspectorList for:inspObject.
    listHolder includesSelf:includesSelf.
    super list:(listHolder instanceNames).

    aSelection notNil ifTrue:[
        self setSelection:aSelection
    ] ifFalse:[
        includesSelf ifTrue:[
            self setSelection:1
        ]
    ]
! !

!InspectorListView methodsFor:'selections'!

selectedInstanceName
    "returns the name assigned to the selected instance or nil
    "
    ^ listHolder instanceNameAt:selection

!

selectedInstanceType
    "returns the type of the selected instance or nil
     known types are: #directory #normal or:#self
    "
    ^ listHolder instanceTypeAt:selection
!

selectedInstanceVar
    "returns the value assigned to the selected instance or nil
    "
    ^ listHolder instanceVarAt:selection

!

setSelection:aNumberOrNil
    "select line, aNumber or deselect if argument is nil
    "
    |type|

    aNumberOrNil notNil ifTrue:[
        type := listHolder instanceTypeAt:aNumberOrNil.
        listHolder selection:aNumberOrNil.

        type == #grow ifTrue:[
            super list:(listHolder instanceNames)
        ]
    ].
    super setSelection:aNumberOrNil

! !

!InspectorListView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !