NoteBookView.st
author ca
Wed, 26 Jan 2000 11:54:30 +0100
changeset 1657 061c167ce3db
parent 1549 4c09c03efa29
child 1658 3011b6a68e38
permissions -rw-r--r--
if disabled; call super keyPress:x:y to handle focusSequence

"
 COPYRIGHT (c) 1997 by eXept Software AG
              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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


View subclass:#NoteBookView
	instanceVariableNames:'list listHolder foregroundColor selection enabled action useIndex
		direction numberOfLines selectConditionBlock expandSelection
		canvas canvasInset canvasHolder halfLightColor halfShadowColor
		fitLastRow tabModus lastComputedExtent keepCanvas
		activeForegroundColor'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Layout'
!

Object subclass:#Tab
	instanceVariableNames:'label model printableLabel disabledLabel lineNr layout extent'
	classVariableNames:''
	poolDictionaries:''
	privateIn:NoteBookView
!

!NoteBookView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG
              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
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"
    implements the noteBook.
    May also be used on its own (without a surrounding noteBook).

    [author:]
        Claus Atzkern

    [see also:]
        TabView
"

!

examples
"
    tabs at top ( default )
                                                                                [exBegin]                                      
    |top tab|

    top  := StandardSystemView extent:250@100.
    tab := NoteBook origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    tab action:[:aName| Transcript showCR:aName].
    top open.
                                                                                [exEnd]


    tabs at bottom
                                                                                [exBegin]                                      
    |top tab|

    top  := StandardSystemView extent:250@100.
    tab := NoteBook origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab direction:#bottom.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    tab action:[:aName| Transcript showCR:aName].
    top open.
                                                                                [exEnd]

    tabs at left
                                                                                [exBegin]                                      
    |top tab|

    top  := StandardSystemView extent:100@200.
    tab := NoteBook origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab direction:#left.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    tab action:[:aName| Transcript showCR:aName].
    top open.
                                                                                [exEnd]

    tabs at right
                                                                                [exBegin]                                      
    |top tab|

    top  := StandardSystemView extent:100@200.
    tab := NoteBook origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab direction:#right.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    tab action:[:aName| Transcript showCR:aName].
    top open.
                                                                                [exEnd]


"

! !

!NoteBookView class methodsFor:'claus'!

test2:aDirection
    |top tab|

    top := StandardSystemView extent:300@300.
    tab  := NoteBookView origin:0.1 @ 0.1 corner:0.9 @ 0.9 in:top.
    tab direction:aDirection.
    tab tabModus:true.
    tab list:#( 'Tab 1' 'Tab 2' 'Tab 3' 'XgQTab 4' ).
    tab action:[:aLabel| Transcript showCR:aLabel].
    top open.


!

test:aDirection
    |top tab|

    top := StandardSystemView extent:300@300.
    tab  := NoteBookView origin:0.1 @ 0.1 corner:0.9 @ 0.9 in:top.
    tab direction:aDirection.
    tab list:#( 'Tab 1' 'Tab 2' 'Tab 3' 'XgQTab 4' ).
    tab canvas:(ClockView new).
    tab action:[:aLabel| Transcript showCR:aLabel].
    top open.


! !

!NoteBookView class methodsFor:'defaults'!

defaultFont
    ^ MenuView defaultFont
! !

!NoteBookView methodsFor:'accessing'!

action:oneArgBlock
    "set the action block to be performed on select; the argument to
     the block is the selected index or nil in case of no selection.
    "
    action := oneArgBlock.

!

canvas
    ^ canvas
!

canvas:aCanvas
    "change canvas; the containter view
    "
    aCanvas == canvas ifFalse:[
        canvas notNil ifTrue:[
            keepCanvas ifTrue:[
                canvas unmap.
            ] ifFalse:[
                canvas destroy.
            ].
        ].
        (canvas := aCanvas) notNil ifTrue:[
            tabModus := false.
            numberOfLines notNil ifTrue:[
                canvas layout:(self computeCanvasLayout)
            ].
            (keepCanvas not
            or:[subViews size == 0
            or:[(subViews includesIdentical:canvas) not]])
            ifTrue:[
                self addSubView:canvas.
            ].
            realized ifTrue:[canvas realize].
        ]
    ].
!

list
    "return the list of Tabs or Labels
    "
    ^ list collect:[:aTab| aTab label ]

!

list:aList
    "set the list
    "
    |size name|

    name := self selection.

    list do:[:aTab| aTab removeDependent:self].

    aList notNil ifTrue:[
        list := aList collect:[:el| Tab label:el on:self].
        list do:[:aTab| aTab addDependent:self].
    ] ifFalse:[
        list := #()
    ].
    preferredExtent := nil.
    numberOfLines   := nil.

    selection notNil ifTrue:[
        useIndex ifTrue:[
            selection > list size ifTrue:[
                selection := nil.
                self selectionChanged.
            ]
        ] ifFalse:[
            selection := list findFirst:[:el| el label = name ].
            selection == 0 ifTrue:[
                selection := nil.
                self selectionChanged.
            ]
        ]
    ].
    canvas notNil ifTrue:[
        self recomputeList
    ].
    shown ifTrue:[
        self invalidate
    ]

!

listIndexOf:something
    "convert something to an index into list or nil.
    "
    |index|

    something isNil ifTrue:[^ nil ].

    something isNumber ifTrue:[
        index := something
    ] ifFalse:[
        index := list findFirst:[:aTab|aTab label = something].
        index == 0 ifTrue:[
            index := list findFirst:[:aTab|aTab printableLabel = something]
        ]
    ].
    ^ (index between:1 and:list size) ifTrue:[index] ifFalse:[nil]


!

useIndex
    "use index instead of name
    "
    ^ useIndex


!

useIndex:aBoolean
    "set/clear the useIndex flag. If set, both actionBlock and change-messages
     are passed the index(indices) of the selection as argument. 
     If clear, the value(s) (i.e. the selected string) is passed.
     Default is false."

    useIndex := aBoolean


! !

!NoteBookView methodsFor:'accessing behavior'!

enabled
    "returns true if tabs are enabled
    "
    ^ enabled
!

enabled:aState
    "set enabled state
    "
    |state|

    state := aState ? true.

    enabled ~~ state ifTrue:[
        enabled := state.
        self invalidate.
    ]
!

keepCanvas:aBoolean
    "if false (the default), the previous canvas is destroyed, whenever
     a new canvas is set.
     if true, it is unmapped and kept.
     Set this flag, if the application changes the canvas but wants
     them to be kept for fast switching."

    keepCanvas := aBoolean.
!

selectConditionBlock
    "get the conditionBlock; this block is evaluated before a selection
     change is performed; the change will not be done, if the evaluation
     returns false. The argument to the block is the selection index
    "
    ^ selectConditionBlock
!

selectConditionBlock:aOneArgBlock
    "get the conditionBlock; this block is evaluated before a selection
     change is performed; the change will not be done, if the evaluation
     returns false. The argument to the block is the selection index
    "
    selectConditionBlock := aOneArgBlock
! !

!NoteBookView methodsFor:'accessing channels/holders'!

canvasHolder
    "get the model, which keeps the canvas, a kind of SimpleView
    "
    ^ canvasHolder
!

canvasHolder:aValueHolder
    "set the model, which keeps the canvas, a kind of SimpleView
    "
    canvasHolder removeDependent:self. 

    (canvasHolder := aValueHolder) notNil ifTrue:[
        canvasHolder addDependent:self.
        self canvas:(canvasHolder value)
    ]


!

listHolder
    "get the model, which keeps the list of Tabs or Labels
    "
    ^ listHolder
!

listHolder:aValueHolder
    "set the model, which keeps the list of Tabs or Labels
    "
    listHolder removeDependent:self. 

    (listHolder := aValueHolder) notNil ifTrue:[
        listHolder addDependent:self.
        self list:listHolder value.
    ].
!

model:aValueHolder
    "set the model, which keeps the selection
    "
    super model:aValueHolder.

    model notNil ifTrue:[
        self selection:(model value)
    ]
! !

!NoteBookView methodsFor:'accessing dimension'!

maxTabHeight
    |e y|

    e := self preferredExtent.
    y := self isHorizontal ifTrue:[e y] ifFalse:[e x].
  ^ y - (expandSelection y)
!

preferredExtent
    "compute max extent x/y based on one line
    "
    |x "{ Class:SmallInteger }"
     y "{ Class:SmallInteger }"
    |
    preferredExtent isNil ifTrue:[
        y := 0.
        x := 0.

        list notEmpty ifTrue:[
            list do:[:aTab|
                x := x + aTab preferredExtentX.
                y := y max:(aTab preferredExtentY).
            ]
        ].
        y := y + (expandSelection y).
        x := x + (expandSelection x).
        preferredExtent := self isHorizontal ifTrue:[x @ y] ifFalse:[y @ x]
    ].
    ^ preferredExtent
!

preferredSizeXorY
    "returns preferred size dependant on the current view layout and
     the direction of the tabs
    "
    |e y|

    list isEmpty ifTrue:[^ 0].

    y := self maxTabHeight.
    e := expandSelection y.

    numberOfLines isNil ifTrue:[
        self shown ifFalse:[^ y + e ].
        self recomputeList.
    ].
    ^ numberOfLines * y + e
! !

!NoteBookView methodsFor:'accessing look'!

activeForegroundColor
    "get the color to be used for drawing text
    "
    ^ activeForegroundColor
!

backgroundColor
    "get backgroundColor of the notebook view
    "
    ^ viewBackground
!

foregroundColor
    "get the color to be used for drawing text
    "
    ^ foregroundColor
!

foregroundColor:aColor
    "set the color to be used for drawing text
    "
    aColor ~= foregroundColor ifTrue:[
        foregroundColor := aColor.

        shown ifTrue:[
            self invalidate
        ]
    ]

!

halfLightColor
    "get the color to be used for drawing text
    "
    ^ halfLightColor
!

halfShadowColor
    ^ halfShadowColor
!

lightColor
    "get the color to be used for lighted edges
    "
    ^ lightColor
!

shadowColor
    "get the color to be used for shadowed edges
    "
    ^ shadowColor
! !

!NoteBookView methodsFor:'accessing style'!

direction
    "returns the direction of tabs as symbol. On default the value is
     set to #top. Valid symbols are:
	#top       arrange tabs to be on top of a view
	#bottom    arrange tabs to be on bottom of a view
	#left      arrange tabs to be on left of a view
	#right     arrange tabs to be on right of a view
    "
    ^ direction

!

direction:aDirection
    "change the direction of tabs. On default the value is set to #top.
     Valid symbols are:
        #top       arrange tabs to be on top of a view
        #bottom    arrange tabs to be on bottom of a view
        #left      arrange tabs to be on left of a view
        #right     arrange tabs to be on right of a view
    "
    direction ~~ aDirection ifTrue:[
        direction       := aDirection.
        preferredExtent := nil.
        numberOfLines   := nil.
        self invalidate.
    ].
!

fitLastRow
    "in case of true, the last row is expanded to the view  size like all
     other raws. In case of false all the tabs in the last raw keep their
     preferred extent (x or y) dependant on the direction.
    "
    ^ fitLastRow
!

fitLastRow:aBool
    "in case of true, the last row is expanded to the view  size like all
     other raws. In case of false all the tabs in the last raw keep their
     preferred extent (x or y) dependant on the direction.
    "
    fitLastRow := aBool
!

tabModus
    ^ tabModus
!

tabModus:aBoolean

    tabModus ~~ aBoolean ifTrue:[
        (aBoolean and:[canvas notNil]) ifFalse:[
            tabModus := aBoolean.
            numberOfLines := nil.
            shown ifTrue:[self invalidate]
        ]
    ]

! !

!NoteBookView methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "one of my models changed its value
    "
    |idx tab|

    changedObject == model         ifTrue:[^ self selection:model value].
    changedObject == listHolder    ifTrue:[^ self list:(listHolder value)].
    changedObject == enableChannel ifTrue:[^ self enabled:enableChannel value].
    changedObject == canvasHolder  ifTrue:[^ self canvas:canvasHolder value].

    (idx := list findFirst:[:aTab| aTab label == changedObject]) ~~ 0 ifTrue:[
        tab := list at:idx.

        idx == selection ifTrue:[
            tab isEnabled ifFalse:[
                ^ self selection:nil
            ]
        ].
        tab label:(tab label) on:self.
        self invalidateTab:tab
    ]
! !

!NoteBookView methodsFor:'drawing'!

invalidateTab:aTab
    "invalidate a tab
    "
    shown ifTrue:[
        self invalidate:(self computeLayoutForTab:aTab)
    ]
!

redrawX:x y:y width:w height:h
    "a region must be redrawn
    "
    |savClip selTab damage lyt savLyt|

    self shown ifFalse:[
        ^ self
    ].
    numberOfLines isNil ifTrue:[
        self recomputeList.
      ^ self invalidate
    ].
    selTab := selection notNil ifTrue:[list at:selection] ifFalse:[nil].

    (selTab notNil and:[selTab lineNr ~~ 1]) ifTrue:[
        self makeToBaseLine:(selTab lineNr).
      ^ self invalidate
    ].

    self paint:(self viewBackground).
    self fillRectangleX:x y:y width:w height:h.

    savClip := clipRect.
    damage  := Rectangle left:x top:y width:w height:h.
    self clippingRectangle:damage.

    list notEmpty ifTrue:[
        numberOfLines to:1 by:-1 do:[:aLnNr|
            list reverseDo:[:aTab|
                (     aTab lineNr == aLnNr
                 and:[aTab ~~ selTab
                 and:[aTab intersects:damage]]
                ) ifTrue:[
                    aTab redrawAt:direction selected:false on:self
                ]
            ]
        ]
    ] ifFalse:[
        selTab := nil
    ].

    tabModus ifFalse:[
        lyt := self computeBorderLayout.

        self drawEdgesForX:lyt left 
                         y:lyt top
                     width:lyt width 
                    height:lyt height
                     level:2
                    shadow:shadowColor 
                    light:lightColor
                    halfShadow:halfShadowColor 
                    halfLight:halfLightColor 
                    style:#softWin95.
    ].


    selTab notNil ifTrue:[
        lyt := self computeLayoutForTab:selTab.

        (lyt intersects:damage) ifTrue:[
            savLyt := selTab layout.
            selTab layout:lyt.
            selTab redrawAt:direction selected:true on:self.
            selTab layout:savLyt.
        ]
    ].
    self clippingRectangle:savClip
! !

!NoteBookView methodsFor:'event handling'!

buttonPress:button x:x y:y
    "a button is pressed; find tab under point and set the selection
    "
    |idx|

    (enabled and:[list notEmpty]) ifTrue:[
        idx := list findFirst:[:aTab| aTab containsPointX:x y:y ].

        (idx ~~ 0 and:[idx ~~ selection and:[(list at:idx) isEnabled]]) ifTrue:[
            self selection:idx
        ]
    ]
!

keyPress:aKey x:x y:y
    "selection might change; look for corresponding list entry
    "
    <resource: #keyboard (#CursorRight #CursorLeft)>

    |sensor size index n|

    (enabled and:[(size := list size) > 1]) ifFalse:[
        ^ super keyPress:aKey x:x y:y
    ].

    aKey isCharacter ifTrue:[
        (selection isNil or:[selection == size]) ifTrue:[index := 1]
                                                ifFalse:[index := selection + 1].

        n := index - 1.
        [   
            n := self findTabStartingWithKey:aKey startingAt:n + 1.

            (n ~~ 0 and:[self isSelectable:n]) ifTrue:[
                ^ self selection:n
            ].
            n ~~ 0

        ] whileTrue.

        index ~~ 1 ifTrue:[
            (n := self findTabStartingWithKey:aKey startingAt:1) ~~ 0 ifTrue:[
                ^ self selection:n
            ]
        ].
        ^ self
    ].

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

    (sensor := self sensor) notNil ifTrue:[
        n := 1 + (sensor compressKeyPressEventsWithKey:aKey).
        n := (n \\ size) max:1.

        aKey == #CursorRight ifTrue:[
            index := selection ? 1.
            [   (index := index + 1) > size ifTrue:[index := 1].
                (self isSelectable:index)   ifTrue:[n := n - 1].
                n ~~ 0
            ] whileTrue.
        ] ifFalse:[
            index := selection ? size.
            [   (index := index - 1) == 0 ifTrue:[index := size].
                (self isSelectable:index) ifTrue:[n     := n -1].
                n ~~ 0
            ] whileTrue.
        ].
        self selection:index
    ]
!

sizeChanged:how
    "size of view changed 
    "
    super sizeChanged:how.

    list notEmpty ifTrue:[
        lastComputedExtent ~= self extent ifTrue:[
            numberOfLines := nil.
            shown ifTrue:[self invalidate]
        ]
    ]
! !

!NoteBookView methodsFor:'initialize / release'!

destroy
    "remove dependencies
    "
    list removeDependent:self.

    listHolder    removeDependent:self. 
    enableChannel removeDependent:self.
    canvasHolder  removeDependent:self.

    super destroy.
!

initStyle
    "setup style attributes
    "

    |clr|

    super initStyle.

    self font:self class defaultFont.

    foregroundColor := styleSheet at:#'noteBook.foregroundColor' default:nil.
    foregroundColor isNil ifTrue:[
        foregroundColor := styleSheet at:#'button.foregroundColor' default:nil.
        foregroundColor isNil ifTrue:[
            foregroundColor := (Color black).
        ].
    ].
    foregroundColor := foregroundColor onDevice:device.

    activeForegroundColor := styleSheet at:#'noteBook.activeForegroundColor' default:nil.
    activeForegroundColor isNil ifTrue:[
        activeForegroundColor := styleSheet at:#'button.activeForegroundColor' default:nil.
        activeForegroundColor isNil ifTrue:[
            activeForegroundColor := (Color black).
        ].
    ].
    activeForegroundColor := activeForegroundColor onDevice:device.

    clr := styleSheet colorAt:#'noteBook.shadowColor'.
    clr notNil ifTrue:[shadowColor := clr onDevice:device].    
    clr  := styleSheet colorAt:#'noteBook.halfLightColor'.
    clr notNil ifTrue:[halfLightColor := clr onDevice:device].    
    clr  := styleSheet colorAt:#'noteBook.halfShadowColor'.
    clr notNil ifTrue:[halfShadowColor := clr onDevice:device].    

    tabModus        := false.
!

initialize
    "setup default attributes
    "
    super initialize.

    self cursor:Cursor hand.

    list            := #().
    useIndex        := true.
    direction       := #top.
    fitLastRow      := true.
    enabled         := true.
    expandSelection := 6@4.
    canvasInset     := 8.
    keepCanvas      := false.

    self lineWidth:0.

    canvas notNil ifTrue:[
        canvas := canvas in:self.
    ].

!

realize

    (canvas notNil and:[numberOfLines isNil]) ifTrue:[
        self recomputeList
    ].
    super realize.
! !

!NoteBookView methodsFor:'layout'!

computeBorderLayout
    |xL yT xR yB tab|

    self paint:lightColor.
    tab := list detect:[:aTab| aTab lineNr == 1] ifNone:nil.
    xL  := 0.
    yT  := 0.
    xR  := width.
    yB  := height.

    tab notNil ifTrue:[
                 direction == #top    ifTrue:[yT := tab layout bottom]
        ifFalse:[direction == #bottom ifTrue:[yB := tab layout top]
        ifFalse:[direction == #left   ifTrue:[xL := tab layout right]
                                     ifFalse:[xR := tab layout left]]]
    ].
    ^ Rectangle left:xL top:yT right:xR bottom:yB

!

computeCanvasLayout

    ^ self computeBorderLayout expandBy:(canvasInset negated).

!

computeLayoutForTab:aTab
    "calculate extent of a tab
    "
    |layout x y w h level|

    layout := aTab layout.
    level  := 2.

    self selectedTab == aTab ifTrue:[
        layout := layout copy.
        w := expandSelection x.
        h := expandSelection y.
        x := w // 2.
        y := h // 2.

        self isHorizontal ifTrue:[
            layout setLeft:(layout left   - x).
            layout   width:(layout width  + w).
            layout  setTop:(layout top    - y).
            layout  height:(layout height + y + level).
        ] ifFalse:[
            layout setLeft:(layout left       - level).
            layout   width:(layout width  + y + level).
            layout  setTop:(layout top    - x).
            layout  height:(layout height + w).
        ]
    ].
    ^ layout
!

makeToBaseLine:aLnNr
    |layout1 layoutN topN top1 leftN left1
     nr "{ Class:SmallInteger }"
    |
    nr := list findFirst:[:aTab| aTab lineNr == 1].
    layout1 := (list at:nr) layout.

    nr := list findFirst:[:aTab| aTab lineNr == aLnNr].
    layoutN := (list at:nr) layout.

    self isHorizontal ifTrue:[
        top1 := layout1 top.
        topN := layoutN top.

        list do:[:el|
            (nr := el lineNr) == 1 ifTrue:[
                el layout setTop:topN. el lineNr:aLnNr
            ] ifFalse:[
                nr == aLnNr ifTrue:[
                    el layout setTop:top1. el lineNr:1
                ]
            ]
        ]
    ] ifFalse:[
        left1 := layout1 left.
        leftN := layoutN left.

        list do:[:el|
            (nr := el lineNr) == 1 ifTrue:[
                el layout setLeft:leftN. el lineNr:aLnNr
            ] ifFalse:[
                nr == aLnNr ifTrue:[
                    el layout setLeft:left1. el lineNr:1
                ]
            ]
        ]
    ]

!

recomputeList
    "recompute list
    "
    numberOfLines := 1.
    lastComputedExtent := self extent.

    list notEmpty ifTrue:[
        self isHorizontal ifTrue:[
            self recomputeListHorizontal
        ] ifFalse:[
            self recomputeListVertical
        ]
    ].
    canvas notNil ifTrue:[
        canvas layout:(self computeCanvasLayout)
    ]
!

recomputeListHorizontal
    "recompute list
    "
    |layout lastLyt checkDir
     xLeft     "{ Class:SmallInteger }"
     yTop      "{ Class:SmallInteger }"
     tabWidth  "{ Class:SmallInteger }"
     tabHeight "{ Class:SmallInteger }"
     lineWidth "{ Class:SmallInteger }"
     startX    "{ Class:SmallInteger }"
     delta     "{ Class:SmallInteger }"
     first     "{ Class:SmallInteger }"
     last      "{ Class:SmallInteger }"
    |
    startX     := expandSelection x // 2.
    lineWidth  := self width - startX.
    tabHeight  := self maxTabHeight.
    xLeft      := startX.
    yTop       := expandSelection y.

    checkDir := canvas isNil ifTrue:[#top] ifFalse:[#bottom].

    direction == #bottom ifTrue:[
        yTop := self height - tabHeight - yTop
    ].

    list do:[:aTab|
        tabWidth := aTab preferredExtentX.

        (xLeft + tabWidth > lineWidth and:[xLeft ~~ startX]) ifTrue:[
            numberOfLines := numberOfLines + 1.
            xLeft := startX.
        ].
        aTab lineNr:numberOfLines.
        aTab layout:(Rectangle left:xLeft top:yTop width:tabWidth height:tabHeight).
        xLeft := xLeft + tabWidth
    ].

    numberOfLines ~~ 1 ifTrue:[
        last  := numberOfLines.
        delta := direction == #bottom ifFalse:[tabHeight]
                                       ifTrue:[tabHeight negated].

        list reverseDo:[:aTab|
            aTab lineNr ~~ last ifTrue:[
                last := aTab lineNr.
                yTop := yTop + delta
            ].
            aTab layout setTop:yTop
        ]
    ].
    tabModus ifTrue:[
        layout := (list at:1) layout.
        delta  := direction == #top ifTrue:[self height - layout bottom]
                                   ifFalse:[layout top negated].

        list do:[:aTab| aTab layout setTop:(aTab layout top + delta)].
    ].

    "/ FIT LINES
    (numberOfLines ~~ 1 or:[fitLastRow]) ifFalse:[
        ^ self
    ].

    first := 1.

    1 to:numberOfLines do:[:aLnNr|
        last    := list findLast:[:t|t lineNr == aLnNr].
        lastLyt := (list at:last) layout.

        (delta := lineWidth - lastLyt right) ~~ 0 ifTrue:[
            xLeft := startX.
            delta := delta // (last - first + 1).

            delta ~~ 0 ifTrue:[
                list from:first to:last do:[:aTab|
                    layout   := aTab layout.
                    tabWidth := layout width + delta.
                    layout setLeft:xLeft.
                    layout width:tabWidth.
                    xLeft := xLeft + tabWidth.
                ]
            ].
            lastLyt width:(lineWidth - lastLyt left)
        ].
        first := last + 1.
    ]

!

recomputeListVertical
    "recompute list
    "
    |layout lastLyt
     xTop      "{ Class:SmallInteger }"
     yTop      "{ Class:SmallInteger }"
     tabWidth  "{ Class:SmallInteger }"
     tabHeight "{ Class:SmallInteger }"
     lineHeight "{ Class:SmallInteger }"
     startY    "{ Class:SmallInteger }"
     delta     "{ Class:SmallInteger }"
     first     "{ Class:SmallInteger }"
     last      "{ Class:SmallInteger }"
    |
    startY     := expandSelection x // 2.
    lineHeight := self height - startY.
    tabHeight  := self maxTabHeight.
    yTop       := startY.
    xTop       := expandSelection y.

    direction == #right ifTrue:[
        xTop  := self width - tabHeight - xTop
    ].

    list do:[:aTab|
        tabWidth := aTab preferredExtentX.

        (yTop + tabWidth > lineHeight and:[yTop ~~ startY])ifTrue:[
            numberOfLines := numberOfLines + 1.
            yTop := startY.
        ].
        aTab lineNr:numberOfLines.
        aTab layout:(Rectangle left:xTop top:yTop width:tabHeight height:tabWidth).
        yTop := yTop + tabWidth
    ].
    numberOfLines ~~ 1 ifTrue:[
        last  := numberOfLines.
        delta := direction == #left ifTrue:[tabHeight] ifFalse:[tabHeight negated].

        list reverseDo:[:aTab|
            aTab lineNr ~~ last ifTrue:[
                last := aTab lineNr.
                xTop := xTop + delta
            ].
            aTab layout setLeft:xTop
        ]
    ].
    tabModus ifTrue:[
        layout := (list at:1) layout.
        delta  := direction == #left ifTrue:[self width - layout right]
                                    ifFalse:[layout left negated].

        list do:[:aTab| aTab layout setLeft:(aTab layout left + delta)].
    ].

    "/ FIT LINES
    (numberOfLines ~~ 1 or:[fitLastRow]) ifFalse:[
        ^ self
    ].

    first := 1.

    1 to:numberOfLines do:[:aLnNr|
        last    := list findLast:[:t|t lineNr == aLnNr].
        lastLyt := (list at:last) layout.

        (delta := lineHeight - lastLyt bottom) ~~ 0 ifTrue:[
            yTop  := startY.
            delta := delta // (last - first + 1).

            delta ~~ 0 ifTrue:[
                list from:first to:last do:[:aTab|
                    layout   := aTab layout.
                    tabWidth := layout height + delta.
                    layout setTop:yTop.
                    layout height:tabWidth.
                    yTop := yTop + tabWidth.
                ]
            ].
            lastLyt height:(lineHeight - lastLyt top)
        ].
        first := last + 1.
    ]
! !

!NoteBookView methodsFor:'obsolete'!

labels
    "return the list of labels
    "
    ^ self list
!

labels:aListOfLabels
    "set the list of labels
    "
    ^ self list:aListOfLabels
!

labelsHolder
    "get the model, which keeps the list of Tabs or Labels
    "
    ^ self listHolder
!

labelsHolder:aValueHolder
    "set the model, which keeps the list of Tabs or Labels
    "
    self listHolder:aValueHolder. 
!

moveSelectedRow
     ^ true
!

moveSelectedRow:something
!

oneTabPerLine
    ^ false
!

oneTabPerLine:something
!

tabWidget
    ^ nil
!

tabWidget:something
! !

!NoteBookView methodsFor:'private'!

findTabStartingWithKey:aKey startingAt:anIndex
    "get index of tab starting its printableLabel with a key or 0
    "
    |upper lower string char|

    (aKey isCharacter and:[anIndex <= list size]) ifFalse:[ ^ 0 ].

    upper := aKey asUppercase.
    lower := aKey asLowercase.

  ^ list findFirst:[:aTab|
        (     (string := aTab string) size ~~ 0
         and:[((char  := string first) == lower or:[char == upper])]
        )
    ] startingAt:anIndex
! !

!NoteBookView methodsFor:'queries'!

isEnabled
    "returns enabled state
    "
    ^ enabled
!

isFirstTabInLine:aTab
    |idx tab|

    idx := list identityIndexOf:aTab.
    tab := list at:(idx - 1) ifAbsent:nil.
  ^ (tab isNil or:[tab lineNr ~~ aTab lineNr])
!

isHorizontal
    "returns true in case of direction is #top or #bottom
    "
    ^ (direction == #top or:[direction == #bottom])

!

isLastTabInLine:aTab
    |index tab|

    index := list identityIndexOf:aTab.
    tab := list at:(index + 1) ifAbsent:nil.
  ^ (tab isNil or:[tab lineNr ~~ aTab lineNr])
! !

!NoteBookView methodsFor:'selection'!

isSelectable:anIndex
    "returns true if tab at an index is selectable
    "
    (anIndex notNil and:[anIndex between:1 and:list size]) ifTrue:[
        (list at:anIndex) isEnabled ifTrue:[
            ^ selectConditionBlock isNil ifTrue:[true]
                                        ifFalse:[selectConditionBlock value:anIndex]
        ]
    ].
    ^ false
!

selectedTab
    "returns the selected tab ot nil
    "
    ^ selection notNil ifTrue:[list at:selection] ifFalse:[nil]
!

selection
    "return the selection or nil
    "
    selection isNil ifTrue:[
        ^ useIndex ifTrue:[0] ifFalse:[nil]
    ].
    ^ useIndex ifTrue:[selection] ifFalse:[(list at:selection) label]
!

selection:anIndexOrNil
    "change the selection to index or nil. The model and/or actionBlock is notified
    "
    |oldSel|

    anIndexOrNil ~~ selection ifTrue:[
        oldSel := selection.
        self setSelection:anIndexOrNil.
        oldSel ~~ selection ifTrue:[self selectionChanged]
    ]
!

selectionChanged
    "selection has changed; raise notification
    "
    |sel|

    sel := self selection.

    model  notNil ifTrue:[model  value:sel].
    action notNil ifTrue:[action value:sel]

!

setSelection:anIndexOrNil
    "change the selection to index or nil. No notifications are raised
    "
    |newSel lnNr|

    newSel := self listIndexOf:anIndexOrNil.

    (newSel notNil and:[(self isSelectable:newSel) not]) ifTrue:[
        newSel := nil
    ].
    selection == newSel ifTrue:[^ self].

    (shown and:[numberOfLines notNil]) ifFalse:[
        selection := newSel.
        self invalidate
    ] ifTrue:[
        selection notNil ifTrue:[self invalidateTab:(list at:selection)].
        selection := newSel.
        selection notNil ifTrue:[self invalidateTab:(list at:selection)].
    ]
! !

!NoteBookView::Tab class methodsFor:'instance creation'!

label:aLabel on:aGC
    ^ self basicNew label:aLabel on:aGC


! !

!NoteBookView::Tab methodsFor:'accessing'!

label
    "returns my original label
    "
    ^ label


!

label:aLabel on:aGC
    "initialize attributes
    "
    label := aLabel.
    model := (aLabel isKindOf:TabItem) ifTrue:[aLabel] ifFalse:[nil].

    printableLabel := model notNil ifTrue:[model rawLabel]
                                  ifFalse:[aLabel].

    printableLabel notNil ifTrue:[
        printableLabel isImageOrForm ifTrue:[
            printableLabel := printableLabel onDevice:(aGC device)
        ]
    ] ifFalse:[
        printableLabel := ''
    ].
    extent := (printableLabel widthOn:aGC) @ (printableLabel heightOn:aGC).

!

lineNr
    "get the line number
    "
    ^ lineNr

!

lineNr:aLineNr
    "set the line number
    "
    lineNr := aLineNr

!

printableLabel
    "get my printable label
    "
    ^ printableLabel

!

string
    "access the printable string used for steping through a list
     searching for an entry starting with a character.
    "
    ^ printableLabel perform:#string ifNotUnderstood:nil

! !

!NoteBookView::Tab methodsFor:'accessing dimensions'!

extent
    "returns the extent of the label
    "
    ^ extent


!

layout
    "get the tab's layout
    "
    ^ layout


!

layout:aLayout
    "set the tab's layout
    "
    layout := aLayout


!

preferredExtentX
    "returns my preferred extent x
    "
    ^ 4 + extent x


!

preferredExtentY
    "returns my preferred extent y
    "
    ^ 4 + extent y


! !

!NoteBookView::Tab methodsFor:'accessing mvc'!

addDependent:aGC
    "make the noteBook be a dependent of the tab model
    "
    model notNil ifTrue:[model addDependent:aGC]


!

removeDependent:aGC
    "make the noteBook be independent of the tab model
    "
    model notNil ifTrue:[model removeDependent:aGC]


! !

!NoteBookView::Tab methodsFor:'drawing'!

drawAtBottomOn:aGC selected:isSelected
    "redraw tab at bottom of view
    "
    |yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    xL := layout left.
    yT := layout top.
    xR := layout right  - 1.
    yB := layout bottom - 1.

    aGC paint:(aGC halfLightColor).
    aGC displayLineFromX:xL+1 y:yB   toX:xL+1 y:yT.

    aGC paint:(aGC lightColor).
    aGC displayLineFromX:xL   y:yB-1 toX:xL   y:yT.

    aGC paint:(aGC shadowColor).
    aGC displayLineFromX:xL+1 y:yB   toX:xR-2 y:yB.
    aGC displayLineFromX:xR   y:yT   toX:xR   y:yB-2.
    aGC displayPointX:xR-1    y:yB-1.

    aGC paint:(aGC halfShadowColor).
    aGC displayLineFromX:xR-1 y:yT-1 toX:xR-1 y:yB-2.
    aGC displayLineFromX:xL+2 y:yB-1 toX:xR-2 y:yB-1.
    aGC displayPointX:xR-2    y:yB-2.

    isSelected ifTrue:[
        (aGC  isLastTabInLine:self) ifFalse:[aGC displayPointX:xR y:yT].
        (aGC isFirstTabInLine:self) ifFalse:[aGC displayPointX:xL y:yT].
    ]







!

drawAtLeftOn:aGC selected:isSelected
    "redraw tab at left of view
    "
    |yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    xL := layout left.
    yT := layout top.
    xR := layout right  - 1.
    yB := layout bottom - 1.

    aGC paint:(aGC shadowColor).
    aGC displayLineFromX:xR y:yB   toX:xL+2 y:yB.

    aGC paint:(aGC halfShadowColor).
    aGC displayLineFromX:xR y:yB-1 toX:xL+1 y:yB-1.

    aGC paint:(aGC lightColor).
    aGC displayLineFromX:xL+2 y:yT   toX:xR   y:yT.

    aGC paint:(aGC halfLightColor).
    aGC displayLineFromX:xL   y:yT+2 toX:xL   y:yB-3.
    aGC displayLineFromX:xL+1 y:yT+2 toX:xL+1 y:yB-2.
    aGC displayLineFromX:xL+1 y:yT+1 toX:xR   y:yT+1.


    (aGC isLastTabInLine:self)  ifFalse:[aGC displayPointX:xR y:yB].
    (aGC isFirstTabInLine:self) ifFalse:[aGC displayPointX:xR y:yT].



!

drawAtRightOn:aGC selected:isSelected
    "redraw tab at right of view
    "
    |yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    xL := layout left.
    yT := layout top.
    xR := layout right - 1.
    yB := layout bottom - 1.

    aGC paint:(aGC lightColor).
    aGC displayLineFromX:xL   y:yT   toX:xR-2 y:yT.

    aGC paint:(aGC halfLightColor).
    aGC displayLineFromX:xL   y:yT+1 toX:xR-2   y:yT+1.

    aGC paint:(aGC shadowColor).
    aGC displayLineFromX:xR-2   y:yB   toX:xL y:yB.
    aGC displayLineFromX:xR   y:yT+2 toX:xR y:yB-2.
    aGC displayPointX:xR-1 y:yB-1.

    aGC paint:(aGC halfShadowColor).
    aGC displayLineFromX:xR-2 y:yB-1 toX:xL y:yB-1.
    aGC displayLineFromX:xR-1 y:yT+1 toX:xR-1 y:yB-2.

    isSelected ifFalse:[^ self].

    (aGC isLastTabInLine:self)  ifFalse:[aGC displayPointX:xL y:yB].

    (aGC isFirstTabInLine:self) ifFalse:[
        aGC displayPointX:xL y:yT+1.
        aGC displayPointX:xL y:yT
    ].



!

drawAtTopOn:aGC selected:isSelected
    "redraw tab at top of view
    "
    |
     yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    xL := layout left.
    yT := layout top.
    xR := layout right  - 1.
    yB := layout bottom - 1.

    aGC paint:(aGC shadowColor).
    aGC displayLineFromX:xR   y:yB toX:xR   y:yT+2.

    aGC paint:(aGC halfShadowColor).
    aGC displayLineFromX:xR-1 y:yB toX:xR-1 y:yT+1.

    aGC paint:(aGC lightColor).
    aGC displayLineFromX:xL+2 y:yT toX:xR-2 y:yT.
    aGC displayLineFromX:xL   y:yB toX:xL   y:yT+2.

    aGC paint:(aGC halfLightColor).
    aGC displayLineFromX:xL+2 y:yT+1 toX:xR-2 y:yT+1.
    aGC displayLineFromX:xL+1 y:yB toX:xL+1 y:yT+1.

    isSelected ifFalse:[^ self].
    (aGC isLastTabInLine:self)  ifFalse:[aGC displayPointX:xR y:yB].
    (aGC isFirstTabInLine:self) ifFalse:[aGC displayPointX:xL y:yB].




!

redrawAt:aDirection selected:isSelected on:aGC
    "redraw tab
    "
    |dispObj fgColor
     y  "{ Class:SmallInteger }"
     x  "{ Class:SmallInteger }"
     dI "{ Class:SmallInteger }"
    |

    isSelected ifTrue:[
        aGC paint:(aGC backgroundColor).
        layout displayFilledOn:aGC.
    ].
             aDirection == #top    ifTrue:[self drawAtTopOn:aGC    selected:isSelected]
    ifFalse:[aDirection == #bottom ifTrue:[self drawAtBottomOn:aGC selected:isSelected]
    ifFalse:[aDirection == #right  ifTrue:[self drawAtRightOn:aGC  selected:isSelected]
    ifFalse:[aDirection == #left   ifTrue:[self drawAtLeftOn:aGC   selected:isSelected]
    ifFalse:[^ self]]]].

    "/ REDRAW LABEL
    (aGC isEnabled and:[self isEnabled]) ifTrue:[
        dispObj := printableLabel.
        fgColor := aGC foregroundColor.

        model notNil ifTrue:[
           fgColor := model foregroundColor ? fgColor
        ]
    ] ifFalse:[
        fgColor := aGC lightColor.

        (dispObj := disabledLabel) isNil ifTrue:[
            (dispObj := printableLabel) isImageOrForm ifTrue:[
                disabledLabel := printableLabel lightened onDevice:(aGC device)
            ]
        ]
    ].

    isSelected ifTrue:[
        fgColor := aGC activeForegroundColor.
    ].

    aGC paint:fgColor.
    dI := 4.
    (aDirection == #top or:[aDirection == #bottom]) ifTrue:[
        x := (layout left) + (layout width - extent x // 2).

        y := aDirection == #top ifTrue:[layout top + dI]
                               ifFalse:[layout bottom - extent y - dI].

        dispObj isImageOrForm ifFalse:[
            y := y + aGC font ascent
        ].
    ] ifFalse:[
        y := (layout top) + (layout height - extent x // 2).

        x := aDirection == #left ifTrue:[layout left + dI]
                                ifFalse:[layout right - extent y - dI].

        dispObj isImageOrForm ifFalse:[
            x := x + aGC font descent.
            "/ workaround for a bug in display-with-angle,
            "/ iff displayed string is a labelAndIcon.
            "/ (In this case, display is always opaque, and the current
            "/  backgroundPaint color is used to fill the underlying rectangle)
            "/
            aGC backgroundPaint:(aGC paint:fgColor).
          ^ aGC displayString:dispObj x:x y:y angle:90.
        ]
    ].
    dispObj displayOn:aGC x:x y:y





""


! !

!NoteBookView::Tab methodsFor:'testing'!

containsPointX:x y:y
    "return true, if the point defined by x@y is contained in the tab.
    "
    ^ layout notNil ifTrue:[layout containsPointX:x y:y]
                   ifFalse:[false].


!

intersects:aRectangle
    "return true, if the intersection between the argument, aRectangle
     and the tab is not empty
    "
    ^ layout notNil ifTrue:[layout intersects:aRectangle]
                   ifFalse:[false].


!

isEnabled
    "returne true if no model exists or the model is enabled
    "
    ^ (model isNil or:[model isEnabled])


! !

!NoteBookView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/NoteBookView.st,v 1.23 2000-01-26 10:54:30 ca Exp $'
! !