SelectionInListModelView.st
author Claus Gittinger <cg@exept.de>
Sun, 23 May 1999 14:56:33 +0200
changeset 1390 62dc950b9140
child 1391 83ed7574be4c
permissions -rw-r--r--
initial checkin

ListModelView subclass:#SelectionInListModelView
	instanceVariableNames:'selection multipleSelectOk actionBlock doubleClickActionBlock
		clickLine highlightMode useIndex hilightFgColor hilightBgColor
		hilightLevel hilightFrameColor hilightStyle dragAccessPoint
		dropTarget dropSource'
	classVariableNames:'DefaultHilightStyle DefaultHilightBackgroundColor
		DefaultHilightForegroundColor DefaultHilightLevel
		DefaultHilightFrameColor'
	poolDictionaries:''
	category:'AAA'
!

!SelectionInListModelView class methodsFor:'documentation'!

documentation
"
    SelectionInListModelView is mostly like SelectionInListView,
    but derives from the ListModelView and thus the list is kept
    by the model.

    [Instance variables:]
        selection               <misc>     the current selection. nil, a number or collection of numbers
        multipleSelectOk        <Boolean>  allow/disallow multiple selections( default:false )
        actionBlock             <Block>    action evaluated on single click
        doubleClickActionBlock  <Block>    action evaluated on double click
        clickPosition           <Point>    internal use
        highlightMode           <Symbol>   how to draw the selection
        useIndex                <Boolean>  representation of the model selection
        hilightFgColor          <Color>           
        hilightBgColor          <Color>    how highlighted items are drawn
        hilightLevel            <Integer>  level to draw selections (i.e. for 3D effect)
        hilightFrameColor       <Color>    rectangle around highlighted items
        hilightStyle            <Boolean>  actions on widget are enabled/disabled

    [author:]
        Claus Atzkern

    [see also:]

        ListModelView
        HierarchicalListView
"


!

examples
"
                                                                        [exBegin]
    |top list view|

    list := List new.

    1 to:100 do:[:i| list add:('element: ', i printString) ].
    top  := StandardSystemView new; extent:300@300.
    view := ScrollableView for:SelectionInListModelView miniScroller:true
                        origin:0.0@0.0 corner:1.0@1.0 in:top.
    view list:list.
    top  open.
                                                                        [exEnd]


                                                                        [exBegin]
    |top list view item|

    list := HierarchicalList new.
    item := HierarchicalItem::Example labeled:'Test'.
    item expand.
    list showRoot:false.
    list root:item.

    top  := StandardSystemView new; extent:300@300.
    view := ScrollableView for:SelectionInListModelView miniScroller:true
                        origin:0.0@0.0 corner:1.0@1.0 in:top.

    view list:list.
    view doubleClickAction:[:i| (list at:i) toggleExpand ].
    top  open.
                                                                        [exEnd]

"

! !

!SelectionInListModelView class methodsFor:'defaults'!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style   (
                        #'selection.hilightForegroundColor' #'selection.hilightBackgroundColor'
                        #'selection.hilightFrameColor'      #'selection.hilightLevel'
                        #'selection.foregroundColor'        #'selection.backgroundColor'
                        #'selection.shadowColor'            #'selection.lightColor'
                        #'selection.font'                   #'selection.hilightStyle'
                        #'text.foregroundColor'
                        )>

    DefaultHilightForegroundColor  := StyleSheet colorAt:'selection.hilightForegroundColor'.
    DefaultHilightBackgroundColor  := StyleSheet colorAt:'selection.hilightBackgroundColor'.
    DefaultHilightFrameColor       := StyleSheet colorAt:'selection.hilightFrameColor'.
    DefaultHilightLevel            := StyleSheet at:'selection.hilightLevel' default:0.
    DefaultHilightStyle            := StyleSheet at:'selection.hilightStyle' default:(StyleSheet name).
    DefaultForegroundColor         := StyleSheet colorAt:'selection.foregroundColor'.
    DefaultBackgroundColor         := StyleSheet colorAt:'selection.backgroundColor'.
    DefaultShadowColor             := StyleSheet colorAt:'selection.shadowColor'.
    DefaultLightColor              := StyleSheet colorAt:'selection.lightColor'.

    DefaultForegroundColor isNil ifTrue:[
        DefaultForegroundColor := StyleSheet colorAt:'text.foregroundColor' default:Black
    ].
    "
     self updateStyleCache
    "


! !

!SelectionInListModelView methodsFor:'accessing'!

list:aList
    "get the status of <showRoot> from the list
    "
    selection notNil ifTrue:[
        selection := nil.
        self selectionChanged.
    ].
  ^ super list:aList
! !

!SelectionInListModelView methodsFor:'accessing behavior'!

highlightMode
    "get the mode how to draw a selected line:
        #line           draw whole line selected
        #label          draw label selected
    "
    ^ highlightMode


!

highlightMode:aMode
    "set the mode how to draw a selected line:
        #line           draw whole line selected
        #label          draw label selected
    "
    (aMode ~~ highlightMode and:[(aMode == #label or:[aMode == #line])]) ifTrue:[
        highlightMode := aMode.

        shown ifTrue:[
            self selectionDo:[:i|self redrawSelectionAt:i]
        ]
    ]

!

multipleSelectOk
    "allow/disallow multiple selections; the default is false
    "
    ^ multipleSelectOk


!

multipleSelectOk:aState
    "allow/disallow multiple selections; the default is false
    "
    aState == multipleSelectOk ifFalse:[
        multipleSelectOk := aState.
        selection notNil ifTrue:[
            multipleSelectOk ifTrue:[
                selection := Array with:selection
            ] ifFalse:[
                selection size ~~ 1 ifTrue:[
                    selection := nil.
                    self invalidate.
                    self selectionChanged
                ] ifFalse:[
                    selection := selection at:1
                ]
            ]
        ]
    ]

!

useIndex
    "set/clear the useIndex flag.
     the selection writen to the model are the indices into the list
     or the elements selected.
    "
    ^ useIndex


!

useIndex:aBoolean
    "set/clear the useIndex flag.
     the selection writen to the model are the indices into the list
     or the elements selected.
    "
    useIndex := aBoolean ? true


! !

!SelectionInListModelView methodsFor:'actions'!

action:aOneArgAction
    "set the action block to be performed on select
    "
    actionBlock := aOneArgAction


!

doubleClickAction:aOneArgAction
    "set the action block to be performed on doubleclick
    "
    doubleClickActionBlock := aOneArgAction


! !

!SelectionInListModelView methodsFor:'change & update'!

argForChangeMessage
    "return the argument for a selectionChange;
     depending on the setting of useIndex, this is either the numeric
     index of the selection or the value (i.e. the string)
    "
    useIndex ifFalse:[
        ^ self selectionValue
    ].
    selection isNil ifTrue:[
        ^ multipleSelectOk ifTrue:[#()] ifFalse:[0]
    ].
  ^ multipleSelectOk ifTrue:[selection copy] ifFalse:[selection]
!

getSelectionFromModel
    "get selection from model; returns a selection or nil
    "
    |value newSel|

    (    model isNil
     or:[(value := model value) isNil
     or:[value == 0]]
    ) ifTrue:[
        ^ nil
    ].

    multipleSelectOk ifFalse:[
        useIndex ifFalse:[
            (value := self identityIndexOf:value) == 0 ifTrue:[
                ^ nil
            ]
        ].
        ^ value
    ].

    "/ MULTI SELECT

    value isEmpty ifTrue:[^ nil].
    useIndex      ifTrue:[^ value].

    newSel := OrderedCollection new.

    value do:[:el||index|
        (index := self identityIndexOf:el) ~~ 0 ifTrue:[
            newSel add:index
        ]
    ].

    ^ newSel notEmpty ifTrue:[newSel] ifFalse:[nil]
!

listSizeChanged:aLnNr nLines:aDeltaLines
    "update selection
    "
    |newSel noChg size changed|

    super listSizeChanged:aLnNr nLines:aDeltaLines.

    selection isNil ifTrue:[^ self].

    list size == 0 ifTrue:[
      ^ self deselectWithoutRedraw
    ].
    multipleSelectOk ifFalse:[
        selection >= aLnNr ifTrue:[
            selection := selection + aDeltaLines.

            (aDeltaLines < 0 and:[selection < aLnNr]) ifTrue:[
                self deselectWithoutRedraw
            ] ifFalse:[
                (model notNil and:[useIndex]) ifTrue:[
                    model setValue:selection
                ]
            ]
        ].
        ^ self
    ].

    size    := selection size.
    changed := false.

    aDeltaLines < 0  ifFalse:[
        1 to:size do:[:anIndex|
            newSel := selection at:anIndex.

            newSel >= aLnNr ifTrue:[
                changed := true.
                selection at:anIndex put:(newSel + aDeltaLines)
            ]
        ].
        (changed and:[useIndex and:[model notNil]]) ifTrue:[
            model setValue:(selection copy)
        ].
        ^ self
    ].
    noChg := 0.

    1 to:size do:[:anIndex|
        newSel := selection at:anIndex.

        newSel >= aLnNr ifTrue:[
            newSel  := newSel + aDeltaLines.
            changed := true.

            newSel < aLnNr ifTrue:[
                noChg  := noChg + 1.
                newSel := 0.
            ].
            selection at:anIndex put:newSel
        ]
    ].

    noChg ~~ 0 ifTrue:[
        noChg == size ifTrue:[
            self deselectWithoutRedraw
        ] ifFalse:[
            selection := selection select:[:i| i ~~ 0].
            self selectionChanged
        ]
    ] ifFalse:[
        (changed and:[useIndex and:[model notNil]]) ifTrue:[
            model setValue:(selection copy)
        ]
    ]

!

selectionChanged
    "selection has changed. Call actionblock and/or send changeMessage if defined
    "
    |value arg|

    (model isNil and:[actionBlock isNil]) ifTrue:[
        ^ self
    ].

    arg := self argForChangeMessage.

    model notNil ifTrue:[
        model removeDependent:self.
        self sendChangeMessage:#value: with:arg.
        model addDependent:self.
    ].

    actionBlock notNil ifTrue:[
        (actionBlock numArgs) == 1 ifTrue:[
            actionBlock value:arg
        ] ifFalse:[
            actionBlock value
        ]
    ].

!

update:something with:aParameter from:changedObject
    "one of my models changed
    "
    |newSelection|

    changedObject == model ifTrue:[
        newSelection := self getSelectionFromModel.

        newSelection ~= selection ifTrue:[
            self setSelection:newSelection
        ]
    ] ifFalse:[
        super update:something with:aParameter from:changedObject
    ].
! !

!SelectionInListModelView methodsFor:'drag & drop'!

canDrag
    "returns true if dragging is enabled
    "
    ^ dropSource notNil

!

dropSource
    "returns the dropSource or nil
    "
    ^ dropSource

!

dropSource:aDropSourceOrNil
    "set the dropSource or nil
    "
    dropSource := aDropSourceOrNil.

!

dropTarget
    "returns the dropTarget or nil
    "
    ^ dropTarget


!

dropTarget:aDropTragetOrNil
    "set the dropTarget or nil
    "
    dropTarget := aDropTragetOrNil.

!

startDragAt:aPoint
    "start drag at a point
    "
    dropSource notNil ifTrue:[
        dropSource startDragSelector notNil ifTrue:[
            dropSource startDragIn:self at:aPoint
        ] ifFalse:[
            DragAndDropManager new startDragFrom:self
                                      dropSource:dropSource
                                          offset:#center
        ]
    ]

! !

!SelectionInListModelView methodsFor:'drawing'!

drawFrom:start to:stop x:x y:y width:w
    "draw the lines between start to stop without clearing the background
    "
    |selY selH
     y0       "{ Class:SmallInteger }"
     y1       "{ Class:SmallInteger }"
     hg       "{ Class:SmallInteger }"
    |
    (highlightMode == #line and:[selection notNil]) ifTrue:[
        "/ redraw the background for all selected lines in the invalid range

        self selectionDo:[:lnNr|
            (lnNr between:start and:stop) ifTrue:[
                selY isNil ifTrue:[
                    selY := OrderedCollection new.
                    selH := OrderedCollection new.
                    self paint:hilightBgColor.
                ].
                y0 := self yVisibleOfLine:lnNr.
                y1 := self yVisibleOfLine:(lnNr + 1).
                hg := y1 - y0.
                selY add:y0.
                selH add:hg.
                self fillRectangleX:x y:y0 width:w height:hg.
            ]
        ]
    ].
    self drawElementsFrom:start to:stop x:x y:y width:w.

    "/ draw selection frames
    selY notNil ifTrue:[
        1 to:selY size do:[:i|
            self drawSelectionFrameAtX:x y:(selY at:i) width:w h:(selH at:i)
        ]
    ].



!

drawLabelAt:x y:y h:h index:anIndex
    "draw the label at position x/y without clearing the background
    "
    |label item
     w  "{ Class:SmallInteger }"
     x0 "{ Class:SmallInteger }"
    |
    item := list at:anIndex ifAbsent:[^ self].

    (self isInSelection:anIndex) ifTrue:[
        highlightMode == #label ifTrue:[
            w  := (item widthOn:self) + textStartLeft.
            x0 := x - (textStartLeft // 2).
            self paint:hilightBgColor.
            self fillRectangleX:x0 y:y width:w height:h.
            self drawSelectionFrameAtX:x0 y:y width:w h:h.
        ].
        self paint:hilightFgColor on:hilightBgColor
    ] ifFalse:[
        self paint:fgColor on:bgColor.
    ].
    self displayElement:item atX:x y:y h:h


!

drawSelectionFrameAtX:x0 y:y0 width:w h:h
    "redraw selection frame for a line
    "
    |
     x1 "{ Class: SmallInteger }"
     x  "{ Class: SmallInteger }" 
     y  "{ Class: SmallInteger }" 
    |
    x1 := x0 + w.

    hilightFrameColor notNil ifTrue:[
        hilightLevel == 0 ifTrue:[
            self paint:hilightFrameColor.

            highlightMode == #line ifTrue:[
                self displayLineFromX:x0 y:y0 toX:x1 y:y0.
                y := y0 + h - 1.
                self displayLineFromX:x0 y:y toX:x1 y:y.
            ] ifFalse:[
                self displayRectangleX:x0 y:y0 width:w height:h
            ].
            ^ self.
        ]
    ] ifFalse:[
        hilightStyle == #motif ifTrue:[
            self paint:bgColor.
            y := y0 + 1.
            highlightMode == #line ifTrue:[
                self displayLineFromX:x0 y:y toX:x1 y:y.
                y := y0 + h - 2.
                self displayLineFromX:x0 y:y toX:x1 y:y.
            ] ifFalse:[
                self displayRectangleX:x0 + 1 y:y width:w - 2 height:h - 2
            ]
        ]
    ].

    hilightLevel ~~ 0 ifTrue:[
        "/ draw edge
        highlightMode == #line ifTrue:[
            x  := margin.
            x1 := width - x - x.
        ] ifFalse:[
            x  := x0.
            x1 := w.
        ].
        self drawEdgesForX:x y:y0 width:x1 height:h level:hilightLevel.
    ]

!

redrawSelectionAt:anIndex
    "called to redraw a line caused by a change of the selection
    "
    |item
     h  "{ Class:SmallInteger }"
     y0 "{ Class:SmallInteger }"
     y1 "{ Class:SmallInteger }"
    |
    shown ifFalse:[^ self].

    y0 := (self yVisibleOfLine:anIndex)       max:margin.
    y1 := (self yVisibleOfLine:(anIndex + 1)) min:(height - margin).

    (h := y1 - y0) > 0 ifTrue:[
        (     highlightMode == #label
         and:[(item := list at:anIndex ifAbsent:nil) notNil]
        ) ifTrue:[
            self redrawLabelFromItem:item atY:y0 h:h
        ] ifFalse:[
            self redrawX:margin y:y0 width:(self innerWidth) height:h
        ]
    ]
! !

!SelectionInListModelView methodsFor:'event handling'!

buttonMotion:buttonMask x:x y:y
    "mouse-move while button was pressed - handle selection changes
    "
    |sensor idx  p cY oY lnNr h|

    (enabled and:[selection notNil]) ifFalse:[^ self].

    dragAccessPoint notNil ifTrue:[
        p := x @ y.

        (dragAccessPoint dist:p) > 5.0 ifTrue:[
            dragAccessPoint := nil.
            self startDragAt:p
        ].
        ^ self
    ].

    (multipleSelectOk and:[self sensor leftButtonPressed]) ifFalse:[
        ^ self
    ].

    clickLine isNil ifTrue:[
        ^ self
    ].
    cY := self yVisibleOfLine:clickLine.
    oY := cY.

    y < cY ifTrue:[
        (lnNr := clickLine - 1) == 0 ifTrue:[^ self].
        cY := self yVisibleOfLine:lnNr.
        h  := oY - cY.
    ] ifFalse:[
        (    (lnNr := clickLine + 1) > list size
         or:[(cY   := self yVisibleOfLine:lnNr) > y]
        ) ifTrue:[
            ^ self
        ].
        h  := cY - oY.
    ].
    selection := selection asOrderedCollection.

    (selection removeIdentical:lnNr ifAbsent:nil) isNil ifTrue:[
        selection add:lnNr
    ].
    clickLine := lnNr.

    (cY between:margin and:(height - h)) ifTrue:[
        self redrawSelectionAt:lnNr
    ] ifFalse:[
        self scrollToLine:lnNr.
    ].
    self selectionChanged

!

buttonMultiPress:button x:x y:y
    "button was pressed multiple - handle a doubleClick action
    "
    clickLine := nil.
    dragAccessPoint := nil.

    enabled ifFalse:[^ self].

    ((button == 1) or:[button == #select]) ifFalse:[
        ^ super buttonMultiPress:button x:x y:y
    ].
    self doubleClicked
!

buttonPress:button x:x y:y
    "a button was pressed - handle selection here
    "
    |lnNr sensor start step list changed|

    clickLine       := nil.
    dragAccessPoint := nil.

    enabled ifFalse:[^ self].

    (button == 1 or:[button == #select]) ifFalse:[
        ^ super buttonPress:button x:x y:y
    ].

    (lnNr := self yVisibleToLineNr:y) isNil ifTrue:[
        ^ self
    ].
    clickLine := lnNr.

    (multipleSelectOk and:[(sensor := self sensor) notNil]) ifTrue:[
        sensor ctrlDown ifTrue:[
            (self isInSelection:lnNr) ifTrue:[self removeFromSelection:lnNr]
                                     ifFalse:[self addToSelection:lnNr].
          ^ self selectionChanged

        ].
        (selection notNil and:[sensor shiftDown]) ifTrue:[
            start     := selection at:1.
            step      := lnNr < start ifTrue:[-1] ifFalse:[1].
            list      := selection.
            selection := OrderedCollection new.
            changed   := false.

            start to:lnNr by:step do:[:i|
                selection add:i.
                (list identityIndexOf:i) == 0 ifTrue:[
                    changed := true.
                    self redrawSelectionAt:i    "/ redraw selected
                ]
            ].
            list do:[:i|
                (selection identityIndexOf:i) == 0 ifTrue:[
                    changed := true.
                    self redrawSelectionAt:i    "/ redraw unselected
                ].
            ].
            changed ifTrue:[
                self selectionChanged
            ].
            ^ self
        ]
    ].

    (self canDrag and:[self isInSelection:lnNr]) ifTrue:[
        dragAccessPoint := x @ y
    ] ifFalse:[
        self selectedIndex ~~ lnNr ifTrue:[
            self selectWithoutScroll:lnNr.
            self selectionChanged
        ]
    ]
!

buttonRelease:button x:x y:y
    "a button was released
    "
    enabled ifTrue:[ 
        (dragAccessPoint notNil and:[clickLine notNil]) ifTrue:[
            self selectedIndex ~~ clickLine ifTrue:[
                self selectWithoutScroll:clickLine.
                self selectionChanged
            ]
        ]
    ].
    clickLine       := nil.
    dragAccessPoint := nil.


!

characterPress:aKey x:x y:y
    " a character is pressed - lookup and change selection
    "
    |lnNr size idx sensor stp to1 fr2|

    (enabled and:[(size := self size) > 1]) ifFalse:[
        ^ self
    ].
    lnNr := self firstInSelection ? 0.

    ((sensor := self sensor) notNil and:[sensor shiftDown]) ifTrue:[
        stp := -1.              "/ search backward
        to1 :=  1.
        fr2 := size.
    ] ifFalse:[
        stp := 1.               "/ search forward
        to1 := size.
        fr2 := 1.
    ].

    idx := self findLineFrom:lnNr+stp to:to1 by:stp startingWithCharacter:aKey.

    idx == 0 ifTrue:[
        idx := self findLineFrom:fr2 to:lnNr-stp by:stp startingWithCharacter:aKey
    ].
    idx ~~ 0 ifTrue:[^ self selection:idx]
!

doubleClicked
    "handle a double click
    "
    (doubleClickActionBlock notNil and:[self numberOfSelections == 1]) ifTrue:[
        (doubleClickActionBlock numArgs == 1) ifTrue:[
            doubleClickActionBlock value:(self selectedIndex)
        ] ifFalse:[
            doubleClickActionBlock value
        ]
    ]

!

findLineFrom:aStart to:aStop by:aStep startingWithCharacter:aCharacter
    "find a line starting with a character
    "
    |item char lbl cmp
     size     "{ Class:SmallInteger }"
     start    "{ Class:SmallInteger }"
     stop     "{ Class:SmallInteger }"
    |
    (size := list size) ~~ 0 ifTrue:[
        aStep > 0 ifTrue:[
            aStart > aStop ifTrue:[^ 0].
        ] ifFalse:[
            (aStep == 0 or:[aStop > aStart]) ifTrue:[^ 0]
        ].

        start := aStart < 0 ifTrue:[1] ifFalse:[aStart min:size].
        stop  := aStop  < 0 ifTrue:[1] ifFalse:[aStop  min:size].
        char  := aCharacter asUppercase.

        start to:stop by:aStep do:[:anIndex|
            item := list at:anIndex ifAbsent:[^ 0]. "/ list changed
            lbl  := item perform:#string ifNotUnderstood:nil.

            lbl notNil ifTrue:[
                cmp := lbl string at:1 ifAbsent:nil.

                cmp notNil ifTrue:[
                    (char == cmp or:[char == cmp asUppercase]) ifTrue:[
                        ^ anIndex
                    ]
                ]
            ]
        ]
    ].
    ^ 0


!

keyPress:aKey x:x y:y
    "a key was pressed - handle page-keys here
    "
    <resource: #keyboard( #Return #CursorUp #CursorDown )>

    |sensor n size lineNr|

    enabled ifFalse:[
        ^ super keyPress:aKey x:x y:y
    ].
    aKey == #Return ifTrue:[
        self numberOfSelections == 1 ifTrue:[self doubleClicked].
      ^ self
    ].

    aKey isCharacter ifTrue:[
        ^ self characterPress:aKey x:x y:y
    ].

    (aKey == #CursorUp or:[aKey == #CursorDown]) ifFalse:[
        ^ super keyPress:aKey x:x y:y
    ].

    (size := self size) == 0 ifTrue:[
        ^ self
    ].

    lineNr := self selectedIndex.
    sensor := self sensor.

    sensor notNil ifTrue:[
        n := (1 + (sensor compressKeyPressEventsWithKey:aKey)) \\ size.
        n == 0 ifTrue:[^ self].
    ] ifFalse:[
        n := 1
    ].

    aKey == #CursorUp ifTrue:[
        lineNr == 0 ifTrue:[lineNr := size + 1].
        (n := lineNr - n) <= 0 ifTrue:[n := size + n]
    ] ifFalse:[
        (n := lineNr + n) > size ifTrue:[n := n - size]
    ].
    self selection:n
! !

!SelectionInListModelView methodsFor:'initialize / release'!

fetchResources
    "fetch device colors and ..., to avoid reallocation at redraw time;
     *** called after a create or snapin to fetch all device resources
    "

    super fetchResources.

    hilightFgColor    := self colorOnDevice:hilightFgColor.
    hilightBgColor    := self colorOnDevice:hilightBgColor.
    hilightFrameColor := self colorOnDevice:hilightFrameColor.
!

initStyle
    "setup viewStyle specifics
    "
    |h|

    super initStyle.

    hilightFrameColor := nil.
    hilightLevel      := 0.
    hilightStyle      := DefaultHilightStyle.
    highlightMode     := #line.
    textStartLeft     := 4.

    device hasGrayscales ifTrue:[
        "
         must get rid of these hard codings
        "
        (hilightStyle == #next) ifTrue:[
            hilightFgColor := fgColor.
            hilightBgColor := White.
            hilightFrameColor := fgColor
        ] ifFalse:[
            (hilightStyle == #motif) ifTrue:[
                fgColor := White.
                bgColor := Grey.
                viewBackground := bgColor.
                hilightFgColor := bgColor.
                hilightBgColor := fgColor.
            ] ifFalse:[
                (hilightStyle == #openwin) ifTrue:[
                    hilightFgColor := fgColor.
                    hilightBgColor := Color grey.
                ]
            ]
        ]
    ].

    hilightFgColor isNil ifTrue:[
        hilightFgColor := bgColor.
    ].
    hilightBgColor isNil ifTrue:[
        hilightBgColor := fgColor.
    ].
    DefaultForegroundColor notNil ifTrue:[
        fgColor := DefaultForegroundColor
    ].
    DefaultBackgroundColor notNil ifTrue:[
        bgColor := viewBackground := DefaultBackgroundColor
    ].

    DefaultHilightForegroundColor notNil ifTrue:[
        hilightFgColor := DefaultHilightForegroundColor
    ].
    DefaultHilightBackgroundColor notNil ifTrue:[
        hilightBgColor := DefaultHilightBackgroundColor
    ].
    DefaultHilightFrameColor notNil ifTrue:[
        hilightFrameColor := DefaultHilightFrameColor
    ].
    DefaultHilightLevel notNil ifTrue:[
        hilightLevel := DefaultHilightLevel
    ].
    lineSpacing := 2 * (hilightLevel abs).

    (hilightStyle == #motif) ifTrue:[
        lineSpacing := lineSpacing max:6.
    ] ifFalse:[
        lineSpacing := lineSpacing max:4.
    ].
    hilightFgColor isNil ifTrue:[
        hilightFgColor := bgColor.
        hilightBgColor := fgColor
    ].
!

initialize
    "setup default attributes/behavior
    "
    super initialize.

    multipleSelectOk := false.
    useIndex         := true.

!

realize
    "get selection from model; scroll to selection
    "
    selection := self getSelectionFromModel.

    super realize.

    selection notNil ifTrue:[
        useIndex ifTrue:[selection := selection copy].
        self makeSelectionVisible.
    ]
! !

!SelectionInListModelView methodsFor:'protocol'!

drawElementsFrom:start to:stop x:x y:y width:width
    "draw the items between start to stop without clearing the background
    "
    |y0 "{ Class:SmallInteger }"
     y1 "{ Class:SmallInteger }"
     x0 "{ Class:SmallInteger }"
    |
    x0 := textStartLeft - viewOrigin x.
    y1 := y.

    start to:stop do:[:i|
        y0 := y1.
        y1 := self yVisibleOfLine:(i + 1).
        self drawLabelAt:x0 y:y0 h:(y1 - y0) index:i.
    ].


!

redrawLabelFromItem:anItem atY:y h:h
    "called to redraw a label caused by a selection changed
    "
    |
     x0 "{ Class:SmallInteger }"
     x1 "{ Class:SmallInteger }"
    |
    x0 := textStartLeft // 2 - viewOrigin x.
    x1 := x0 + textStartLeft + (anItem widthOn:self).
    x0 := x0 max:margin.
    x1 := x1 min:(self innerWidth).

    x1 > x0 ifTrue:[
        self redrawX:x0 y:y width:(x1 - x0) height:h.
    ]
! !

!SelectionInListModelView methodsFor:'selection'!

deselect
    "clear selection
    "
    self selection:nil

!

firstInSelection
    "returns line number of first element selected or nil
    "
    |lineNr|

    selection notNil ifTrue:[
        ^ multipleSelectOk ifTrue:[selection at:1] ifFalse:[selection]
    ].
    ^ nil


!

hasSelection
    "returns true if a selection exists
    "
    ^ selection notNil

!

isInSelection:aNumber
    "return true, if line, aNumber is in the selection
    "
    selection isNil ifTrue:[^ false].

    ^ multipleSelectOk ifFalse:[aNumber == selection]
                        ifTrue:[selection includes:aNumber]
!

lastInSelection
    "returns line number of last element selected or nil
    "
    |lineNr|

    selection notNil ifTrue:[
        ^ multipleSelectOk ifTrue:[selection last] ifFalse:[selection]
    ].
    ^ nil


!

numberOfSelections
    "return the number of selected items
    "
    selection isNil   ifTrue:[^ 0].
  ^ multipleSelectOk ifFalse:[1] ifTrue:[selection size]


!

selectElement:anElement
    "select the element. Scroll to make the new selection visible.
     Model and/or actionBlock notification IS done.
    "
    |index|

    (index := self identityIndexOf:anElement) ~~ 0 ifTrue:[
        self selection:index
    ]
        
!

selectedElement
    "return the single selected item or nil
    "
    |index|

    index := self selectedIndex.
  ^ index ~~ 0 ifTrue:[self at:index ifAbsent:nil] ifFalse:[nil]

!

selectedIndex
    "returns the index of the selected line or 0. If more
     lines are selected, 0 is returned
    "
    selection notNil ifTrue:[
        multipleSelectOk    ifFalse:[^ selection].
        selection size == 1 ifTrue:[^ selection at:1]
    ].
    ^ 0
!

selection
    "return the selection index or collection of indices 
     in case of multiple selection enabled
    "
    ^ selection

!

selection:aNumberOrNil
    "select line, aNumber or deselect if argument is nil;
     scroll to make the selected line visible.
     The model and/or actionBlock IS notified.
    "
    |oldSelection|

    oldSelection := selection.
    self setSelection:aNumberOrNil.

    selection ~= oldSelection ifTrue:[
        self selectionChanged
    ]


!

selectionDo:aBlock
    "perform aBlock for each nr in the selection.
     For single selection, it is called once for the items nr.
     For multiple selections, it is called for each.
    "
    selection notNil ifTrue:[
        multipleSelectOk ifTrue:[
            selection do:aBlock
        ] ifFalse:[
            aBlock value:selection
        ].
    ].


!

selectionValue
    "return the selection value. For multiple selections a collection
     containing the elements is returned. Otherwise the selected element
    "
    selection isNil ifTrue:[
        ^ multipleSelectOk ifTrue:[#()] ifFalse:[nil]
    ].
    multipleSelectOk ifTrue:[
         ^ selection collect:[:nr | list at:nr ifAbsent:nil ]
    ].
    ^ list at:selection ifAbsent:nil
!

setSelection:aNumberOrNilOrCollection
    "select line, aNumber or deselect if argument is nil;
     scroll to make the selected line visible.
     *** No model and/or actionBlock notification is done here.
    "
    self selectWithoutScroll:aNumberOrNilOrCollection.

    selection notNil ifTrue:[
        self makeSelectionVisible
    ]

!

toggleSelection:aNumber
    "toggle selection-state of entry, aNumber.
     *** No model and/or actionBlock notification is done here.
    "
    aNumber notNil ifTrue:[
        (self isInSelection:aNumber) ifTrue:[
            self removeFromSelection:aNumber
        ] ifFalse:[
            self addToSelection:aNumber
        ]
    ]
! !

!SelectionInListModelView methodsFor:'selection private'!

addToSelection:aNumber
    "add a number to the selection. No scrolling is done.
     *** No model and/or actionBlock notification is done here.
    "
    |newSelect oldSelect|

    (aNumber notNil and:[aNumber between:1 and:(self size)]) ifFalse:[
        ^ self
    ].
    multipleSelectOk ifFalse:[
        oldSelect == selection ifTrue:[^ self].
        oldSelect := selection.
        selection := aNumber.
        oldSelect notNil ifTrue:[self redrawSelectionAt:oldSelect].
    ] ifTrue:[
        selection isNil ifTrue:[
            selection := Array with:aNumber.
        ] ifFalse:[
            (selection includes:aNumber) ifTrue:[^ self].
            selection := selection copyWith:aNumber.
        ].
    ].
    self redrawSelectionAt:aNumber.
!

deselectWithoutRedraw
    "set selection without redraw, scrolling.
     The model and/or actionBlock IS notified.
    "
    selection notNil ifTrue:[
        selection := nil.
        self selectionChanged
    ]
!

makeSelectionVisible
    "scroll to make the selection line visible
    "
    |lineNr|

    (lineNr := self firstInSelection) notNil ifTrue:[
        self scrollToLine:lineNr
    ]


!

removeFromSelection:aNumber
    "remove aNumber from the selection and redraw line;
     *** No model and/or actionBlock notification is done here.
    "
    selection notNil ifTrue:[
        multipleSelectOk ifTrue:[
            (selection includes:aNumber) ifTrue:[
                selection size == 1 ifTrue:[
                    selection := nil
                ] ifFalse:[
                    selection := selection copyWithout:aNumber
                ].
                self redrawSelectionAt:aNumber
            ]
        ] ifFalse:[
            aNumber == selection ifFalse:[
                selection := nil.
                self redrawSelectionAt:aNumber
            ]
        ]
    ]

!

selectWithoutScroll:aNumberOrNilOrCollection
    "select line, aNumber or deselect if argument is nil;
     scroll to make the selected line visible.
     *** No model and/or actionBlock notification is done here.
    "
    |oldSelect|

    oldSelect := selection.
    selection := self validateSelection:aNumberOrNilOrCollection.

    (shown and:[selection ~= oldSelect]) ifFalse:[
        ^ self
    ].

    multipleSelectOk ifFalse:[
        oldSelect notNil ifTrue:[self redrawSelectionAt:oldSelect].
        selection notNil ifTrue:[self redrawSelectionAt:selection].
    ] ifTrue:[
        selection isNil ifTrue:[
            oldSelect do:[:i|self redrawSelectionAt:i].
        ] ifFalse:[
            oldSelect isNil ifTrue:[
                selection do:[:i|self redrawSelectionAt:i].
            ] ifFalse:[
                selection do:[:i|
                    (oldSelect includes:i) ifFalse:[self redrawSelectionAt:i]
                ].
                oldSelect do:[:i|
                    (selection includes:i) ifFalse:[self redrawSelectionAt:i]
                ].
            ]
        ]
    ].



!

selectionWithoutRedraw:aSelection
    "set selection without redraw, scrolling.
     The model and/or actionBlock IS notified.
    "
    selection ~= aSelection ifTrue:[
        selection := aSelection.
        self selectionChanged
    ]
!

validateSelection:aNumberOrCollection
    "validate the selection; returns a valid selection or nil
    "
    |sz newSelection|

    (aNumberOrCollection notNil and:[aNumberOrCollection ~~ 0]) ifTrue:[
        sz := self size.

        aNumberOrCollection isCollection ifFalse:[
            (aNumberOrCollection between:1 and:sz) ifTrue:[
                ^ multipleSelectOk ifFalse:[aNumberOrCollection ]
                                    ifTrue:[Array with:aNumberOrCollection]
            ]
        ] ifTrue:[
            (aNumberOrCollection notNil and:[multipleSelectOk]) ifTrue:[
                newSelection := OrderedCollection new.

                aNumberOrCollection do:[:anIndex|
                    (anIndex between:1 and:sz) ifFalse:[^ nil].
                    newSelection add:anIndex.
                ].
                ^ newSelection
            ]
        ]
    ].
    ^ nil


! !

!SelectionInListModelView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInListModelView.st,v 1.1 1999-05-23 12:56:29 cg Exp $'
! !