NoteBookView.st
author ca
Sat, 12 Oct 2002 14:28:21 +0200
changeset 2279 5a50cd5af676
parent 2278 1ce91d0009e8
child 2280 93b2df2d91fd
permissions -rw-r--r--
*** empty log message ***

"
 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.
"


"{ Package: 'stx:libwidg2' }"

View subclass:#NoteBookView
	instanceVariableNames:'list listHolder foregroundColor selection enabled action useIndex
		direction numberOfLines selectConditionBlock tabMenuActionBlock
		accessTabMenuAction expandSelection canvas canvasInset
		canvasHolder halfLightColor halfShadowColor fitLastRow tabModus
		lastComputedExtent keepCanvas tabMargin activeForegroundColor
		drawLightColor edgeStyle tabBgColor activeTabBgColor
		disabledForegroundColor tabLevel'
	classVariableNames:'DefaultForegroundColor DefaultActiveForegroundColor
		DefaultShadowColor DefaultHalfShadowColor DefaultLightColor
		DefaultHalfLightColor DefaultEdgeStyle DisabledForegroundColor'
	poolDictionaries:''
	category:'Views-Layout'
!

Object subclass:#Tab
	instanceVariableNames:'label model printableLabel disabledLabel lineNr layout extent
		accessCharacter'
	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 := NoteBookView 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 := NoteBookView 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 := NoteBookView 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 := NoteBookView 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]


"

!

test:aDirection level:aLevel
"
NoteBookView test:#top    level:1
NoteBookView test:#bottom level:2
NoteBookView test:#left   level:1
NoteBookView test:#right  level:2
"
    |top tab|

    top  := StandardSystemView extent:250@250.
    tab := NoteBookView origin:0.0@0.0 corner:1.0@1.0 in:top.
    tab tabLevel:aLevel.
    tab direction:aDirection.

    tab list:#( 'Foo1' 'Bar1' 'Baz1' 'Foo2' 'Bar2' 'Baz2').
    top open.
! !

!NoteBookView class methodsFor:'defaults'!

defaultFont
    ^ MenuView defaultFont
!

updateStyleCache
"
self updateStyleCache
"
    DefaultForegroundColor := StyleSheet colorAt:#'noteBook.foregroundColor'.
    DefaultForegroundColor isNil ifTrue:[
        DefaultForegroundColor := StyleSheet colorAt:#'button.foregroundColor'.
    ].

    DefaultActiveForegroundColor := StyleSheet colorAt:#'noteBook.activeForegroundColor'.
    DefaultActiveForegroundColor isNil ifTrue:[
        DefaultActiveForegroundColor := StyleSheet colorAt:#'button.activeForegroundColor'
    ].

    DefaultLightColor := StyleSheet colorAt:#'noteBook.lightColor'.
    DefaultLightColor isNil ifTrue:[
        DefaultLightColor := StyleSheet colorAt:'button.lightColor'
    ].
    DefaultHalfLightColor := StyleSheet colorAt:#'noteBook.halfLightColor'.
    DefaultHalfLightColor isNil ifTrue:[
        DefaultHalfLightColor := StyleSheet colorAt:#'button.halfLightColor'
    ].    

    DefaultShadowColor := StyleSheet colorAt:#'noteBook.shadowColor'.
    DefaultShadowColor isNil ifTrue:[
        DefaultShadowColor := StyleSheet colorAt:'button.shadowColor'
    ].
    DefaultHalfShadowColor := StyleSheet colorAt:#'noteBook.halfShadowColor'.
    DefaultHalfShadowColor isNil ifTrue:[
        DefaultHalfShadowColor := StyleSheet colorAt:#'button.halfShadowColor'
    ].
    DefaultEdgeStyle := StyleSheet at:#'noteBook.edgeStyle'.
    DefaultEdgeStyle isNil ifTrue:[
        DefaultEdgeStyle := StyleSheet at:#'button.edgeStyle'
    ].

    DefaultEdgeStyle == #softWin95 ifFalse:[
        DefaultEdgeStyle := nil
    ].

! !

!NoteBookView methodsFor:'accepting - items'!

tabAtIndex:tabIndex put:newLabel
    |tab layout prefX prefY|

    "/ a single items label has changed
    tab := list at:tabIndex ifAbsent:nil.
    tab notNil ifTrue:[
        tab label:newLabel on:self.

        "/ no resizing, if the new string fits
        "/ and is not too small for current tab-layout
        layout := tab layout.

        (     (prefX := tab preferredExtentX) <= layout width
         and:[(prefY := tab preferredExtentY) <= layout height]
        ) ifTrue:[
            "/ the new string fits into current tab-layout

            numberOfLines == 1 ifTrue:[         "/ do not change the layout
                ^ self invalidateTab:tab
            ].

            "/ check whether the string is not too small for current tab-layout
            ((layout width <= (prefX * 1.5)) and:[layout height <= (prefY * 1.5)]) ifTrue:[
                ^ self invalidateTab:tab.      "/ do not change the layout
            ].
        ].
        self recomputeList.
        self invalidate.
        ^ self.
    ].
    "/ can this happen ?

    "Created: / 25.2.2000 / 14:13:59 / cg"
! !

!NoteBookView methodsFor:'accessing'!

canvas
    ^ canvas
!

canvas:aCanvas
    "change the canvas; the containter view
    "
    aCanvas == canvas ifFalse:[
        canvas notNil ifTrue:[
            (keepCanvas or:[(canvas objectAttributeAt:#isTabItem) == true]) ifTrue:[
                canvas unmap.
            ] ifFalse:[
                canvas destroy.
            ].
        ].
        (canvas := aCanvas) notNil ifTrue:[
            tabModus := false.

            self resizeCanvas.

            (subViews size == 0 or:[(subViews includesIdentical:canvas) not]) ifTrue:[
                self addSubView:canvas
            ].

            realized ifTrue:[
                (keepCanvas or:[(canvas objectAttributeAt:#isTabItem) == true]) ifTrue:[
                    canvas id isNil ifTrue:[
                        canvas realize
                    ] ifFalse:[
                        canvas map.
                    ]
                ] ifFalse:[
                    canvas realize.
                ].
                canvas raise.
            ].
        ]
    ].
!

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

!

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

    name    := self selection.
    newList := OrderedCollection new.

    aList size == 0 ifTrue:[
        list do:[:aTab| aTab removeDependent:self].
    ] ifFalse:[
        list do:[:aTab| |m|
            (     (m := aTab model) notNil
             and:[(aList includesIdentical:m)]
            ) ifFalse:[
                aTab removeDependent:self
            ]
        ].

        aList do:[:el| |i tab|
            (    el isNil
             or:[(tab := list detect:[:t| t model == el] ifNone:nil) isNil]
            ) ifTrue:[
                tab := Tab label:el on:self.
                tab addDependent:self.
            ].
            newList add:tab
        ]
    ].

    list            := newList.
    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.
            ]
        ]
    ].
    self recomputeList.
    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-actions'!

accessTabMenuAction
    "callback to retrieve the menu for a specific tab.
     the argument to the block is the index of the tab
    "
    ^ accessTabMenuAction
!

accessTabMenuAction:aOneArgAction
    "callback to retrieve the menu for a specific tab.
     the argument to the block is the index of the tab
    "
    accessTabMenuAction := aOneArgAction.
!

action
    "get 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
!

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.

! !

!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-colors'!

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

activeTabBackgroundColor
    "get the backgroundColor of the tabs
    "
    ^ activeTabBgColor
!

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

disabledForegroundColor
    ^ disabledForegroundColor
!

drawLightColor
    "get the color to be used for lighted edges; bug fix caused by common
     drawEdge
    "
    ^ drawLightColor
!

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
!

tabBackgroundColor
    "get the backgroundColor of the tabs
    "
    ^ tabBgColor
!

viewBackground:aColor
    "get backgroundColor of the notebook view
    "
    |sameTab sameActiveTab|

    sameTab := tabBgColor == viewBackground.
    sameActiveTab := activeTabBgColor == viewBackground.

    super viewBackground:aColor.

    (edgeStyle isNil and:[viewBackground isColor]) ifTrue:[
        halfShadowColor := shadowColor.
        halfLightColor  := lightColor.
        drawLightColor  := lightColor.
    ].

    DefaultShadowColor isNil ifTrue:[
        shadowColor := aColor darkened onDevice:device
    ].
    DefaultLightColor isNil ifTrue:[
        lightColor := aColor lightened onDevice:device
    ].

    sameTab ifTrue:[
        tabBgColor := viewBackground.
    ].
    sameActiveTab ifTrue:[
        activeTabBgColor := viewBackground.
    ]
! !

!NoteBookView methodsFor:'accessing-dimension'!

maxTabHeight
    "returns my preferred tab-height
    "
    |preferredExtent preferredHeight|

    preferredExtent := self preferredExtent.

    self isHorizontal ifTrue:[ preferredHeight := preferredExtent y ]
                     ifFalse:[ preferredHeight := preferredExtent x ].

    ^ preferredHeight - (expandSelection y)
!

preferredExtent
    "compute max extent x/y based on one line
    "
    |x "{ Class:SmallInteger }"
     y "{ Class:SmallInteger }"
     b "{ Class:SmallInteger }"
     c "{ Class:SmallInteger }"
    |
    preferredExtent notNil ifTrue:[ ^ preferredExtent ].

    y := 0.
    x := expandSelection x.
    b := (tabLevel abs) max:1.
    c := b + b.

    list notEmpty ifTrue:[
        list do:[:aTab|
            x := x + c + (aTab preferredExtentX).
            y := y max:(aTab preferredExtentY).
        ]
    ].
    y := y + b + (expandSelection y).

    self isHorizontal ifTrue:[ preferredExtent := x @ y ]
                     ifFalse:[ preferredExtent := 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-style'!

canvasInset
    "inset of the canvas relative to my frame
        tabLevel + canvasInset == origin of canvas
    "
    ^ canvasInset
!

canvasInset:anInset
    "inset of the canvas relative to my frame
        tabLevel + canvasInset == origin of canvas
    "
    anInset ~~ canvasInset ifTrue:[
        canvasInset := anInset.
        self recomputeList.
        self invalidate.
    ].
!

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
!

tabLevel
    "the level of the tabs and noteBook frame
    "
    ^ tabLevel
!

tabLevel:aLevel
    "the level of the tabs and noteBook frame
    "
    aLevel ~~ tabLevel ifTrue:[
        tabLevel := aLevel.
        self recomputeList.
        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:[
        something == #at: ifTrue:[
            "/ a single items label has changed
            self tabAtIndex:aParameter put:(listHolder value at:aParameter).
            ^ self.
        ].
        ^ 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
    ]

    "Modified: / 25.2.2000 / 14:14:29 / cg"
! !

!NoteBookView methodsFor:'defaults'!

updateStyleCache
"
self updateStyleCache
"
    DefaultForegroundColor := StyleSheet colorAt:#'noteBook.foregroundColor'.
    DefaultForegroundColor isNil ifTrue:[
        DefaultForegroundColor := StyleSheet colorAt:#'button.foregroundColor'.
    ].

    DefaultActiveForegroundColor := StyleSheet colorAt:#'noteBook.activeForegroundColor'.
    DefaultActiveForegroundColor isNil ifTrue:[
        DefaultActiveForegroundColor := StyleSheet colorAt:#'button.activeForegroundColor'
    ].

    DefaultLightColor := StyleSheet colorAt:#'noteBook.lightColor'.
    DefaultLightColor isNil ifTrue:[
        DefaultLightColor := StyleSheet colorAt:'button.lightColor'
    ].
    DefaultHalfLightColor := StyleSheet colorAt:#'noteBook.halfLightColor'.
    DefaultHalfLightColor isNil ifTrue:[
        DefaultHalfLightColor := StyleSheet colorAt:#'button.halfLightColor'
    ].    

    DefaultShadowColor := StyleSheet colorAt:#'noteBook.shadowColor'.
    DefaultShadowColor isNil ifTrue:[
        DefaultShadowColor := StyleSheet colorAt:'button.shadowColor'
    ].
    DefaultHalfShadowColor := StyleSheet colorAt:#'noteBook.halfShadowColor'.
    DefaultHalfShadowColor isNil ifTrue:[
        DefaultHalfShadowColor := StyleSheet colorAt:#'button.halfShadowColor'
    ].
    DefaultEdgeStyle := StyleSheet at:#'noteBook.edgeStyle'.
    DefaultEdgeStyle isNil ifTrue:[
        DefaultEdgeStyle := StyleSheet at:#'button.edgeStyle'
    ].

    DisabledForegroundColor := StyleSheet at:#'noteBook.disabledForegroundColor'.

    DefaultEdgeStyle == #softWin95 ifFalse:[
        DefaultEdgeStyle := nil
    ].



! !

!NoteBookView methodsFor:'drawing'!

drawFocusFor:aTab
    "draw focus frame if supported
    "
    |layout extent voffs hoffs|

    self supportsFocusOnTab ifFalse:[^ self].

    layout  := aTab layout.
    extent  := aTab extent.

    voffs := (layout height - extent y) // 2 max:0.
    hoffs := (layout width  - extent x) // 2 max:0.

    self displayDottedRectangleX:(layout left   + hoffs         - 1)
                               y:(layout top    + voffs         - 1)
                           width:(layout width  - hoffs - hoffs + 2)
                          height:(layout height - voffs - voffs + 2).
!

drawTabEdgesFor:aTab
    |layout count leftFg leftHalfFg rightFg x0 x1 y0 y1
     yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    count := tabLevel.
    count == 0 ifTrue:[ count := 1 ].

    (count < 0) ifTrue:[
        rightFg    := lightColor.
        leftFg     := shadowColor.
        leftHalfFg := halfShadowColor.
        count := count negated.
    ] ifFalse:[
        ((edgeStyle == #soft) and:[tabLevel > 1]) ifTrue:[ rightFg := halfShadowColor ]
                                                       ifFalse:[ rightFg := shadowColor ].
        leftFg     := lightColor.
        leftHalfFg := halfLightColor.
    ].

    (leftHalfFg notNil and:[edgeStyle == #soft and:[tabLevel > 0]]) ifTrue:[
        leftFg := leftHalfFg
    ].

    layout := aTab layout.
    xL := layout left.
    yT := layout top.
    xR := layout right  - 1.
    yB := layout bottom - 1.

    x0 := xL + count.
    x1 := xR - count.
    y0 := yT + count.
    y1 := yB - count.

    direction == #top ifTrue:[
        self paint:rightFg.

        0 to:count - 1 do:[:i|              "/ vertical: right
            self displayLineFromX:xR - i y:yB toX:xR - i  y:y0 - i.
        ].

        self paint:leftFg.

        0 to:count - 1 do:[:i|              "/ horizontal: left       
            self displayLineFromX:xL + i y:y0 - i toX:xL + i y:yB.
        ].

        0 to:count - 1 do:[:i|              "/ horizontal: top
            self displayLineFromX:x0 - i y:yT + i toX:x1 y:yT + i.
        ].

        count > 1 ifFalse:[^ self].
        (self selectedTab == aTab) ifFalse:[^ self].
        (self isLastTabInLine:aTab) ifTrue:[^ self].

        y0 := yB + 1.
        x1 := x1 + 1.

        1 to:count - 1 do:[:i|              "/ horizontal line
            self displayLineFromX:x1 + i y:y0 - i toX:xR  y:y0 - i.
        ].
        ^ self
    ].

    direction == #bottom ifTrue:[
        self paint:leftFg.

        0 to:count - 1 do:[:i|              "/ vertical : left
            self displayLineFromX:xL + i y:yT toX:xL + i y:y1+i.
        ].

        self paint:rightFg.

        0 to:count - 1 do:[:i|              "/ horizontal: bottom
            self displayLineFromX:x0 y:yB-i toX:x1 + i y:yB-i.
        ].


        0 to:count - 1 do:[:i|              "/ vertical: right
            self displayLineFromX:xR-i y:yT toX:xR-i y:y1+i.
        ].

        count > 1 ifFalse:[^ self].

        (self selectedTab == aTab) ifFalse:[^ self].
        (self isFirstTabInLine:aTab) ifTrue:[^ self].

        x0 := x0 - 1.
        y0 := yT - 1.

        1 to:count - 1 do:[:i|              "/ selection shadow
            self displayLineFromX:xL y:y0 + i toX:x0-i  y:y0 + i.
        ].
        ^ self
    ].

    direction == #right ifTrue:[
        self paint:leftFg.

        0 to:count - 1 do:[:i|              "/ horizontal: top
            self displayLineFromX:xL y:yT + i toX:x1+i  y:yT + i.
        ].

        self paint:rightFg.

        0 to:count - 1 do:[:i|              "/ vertical: right
            self displayLineFromX:xR-i y:y0 toX:xR-i  y:y1.
        ].

        1 to:count do:[:i|              "/ horizontal: bottom
            self displayLineFromX:xL y:y1+i toX:xR-i  y:y1+i.
        ].

        count > 1 ifFalse:[^ self].
        (self selectedTab  == aTab) ifFalse:[^ self].
        (self isFirstTabInLine:aTab)  ifTrue:[^ self].

        x0 := x0 - 1.
        y0 := yT - 1.

        1 to:count - 1 do:[:i|              "/ selection shadow
            self displayLineFromX:xL y:y0 + i toX:x0-i  y:y0 + i.
        ].
        ^ self
    ].

    "/ direction == #left
    self paint:rightFg.

    x0 := xL + count.
    x1 := xR - count.
    y0 := yT + count.
    y1 := yB - count.

    0 to:count - 1 do:[:i|      "/ horizontal: bottom
        self displayLineFromX:x0 - i y:yB - i toX:xR  y:yB - i.
    ].

    self paint:leftFg.

    0 to:count - 1 do:[:i|      "/ vertical: left
        self displayLineFromX:xL + i y:y0 toX:xL + i y:y1.
    ].

    1 to:count do:[:i|          "/ horizontal: top
        self displayLineFromX:xL + i y:y0 - i toX:xR y:y0 - i.
    ].

    count > 1 ifFalse:[^ self].

    (self selectedTab  == aTab) ifFalse:[^ self].
    (self isLastTabInLine:aTab)  ifTrue:[^ self].

    x1 := x1 + 1.
    y0 := yB + 1.

    1 to:count - 1 do:[:i|      "/ selection shadow
        self displayLineFromX:x1+i y:yB + 1 - i toX:xR  y:yB + 1 - i.
    ].
!

invalidateTab:aTab
    "invalidate a tab
    "
    |tabBounds|

    shown ifTrue:[
        tabBounds := self computeLayoutForTab:aTab.
        self invalidate:tabBounds.
    ]
!

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

    shown ifFalse:[ ^ self ].

    list size == 0 ifTrue:[
        self paint:(self viewBackground).
        self fillRectangleX:x y:y width:w height:h.
      ^ self
    ].

    numberOfLines ifNil:[
        self recomputeList.

        numberOfLines ifNotNil:[
            self invalidate
        ].
        ^ self
    ].
    selectedTab := self selectedTab.

    (selectedTab notNil 
    and:[(selectedTabsLineNr := selectedTab lineNr) ~~ 1]) 
    ifTrue:[
        self makeToBaseLine:selectedTabsLineNr.
        ^ self
    ].

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

    damage := Rectangle left:x top:y width:w height:h.

    numberOfLines to:1 by:-1 do:[:aLnNr|
        list reverseDo:[:aTab|
            (     aTab lineNr == aLnNr
             and:[aTab ~~ selectedTab
             and:[aTab intersects:damage]]
            ) ifTrue:[
                tabBgColor ~~ viewBackground ifTrue:[
                    self paint:tabBgColor.
                    self fillRectangle:aTab layout.
                ].
                self drawTabEdgesFor:aTab.
                aTab drawSelected:false direction:direction on:self.
            ]
        ]
    ].

    tabModus ifFalse:[
        lyt := self computeBorderLayout.

        tabLevel ~~ 0 ifTrue:[
            self drawEdgesForX:lyt left 
                             y:lyt top
                         width:lyt width 
                        height:lyt height
                         level:tabLevel
        ]
    ].

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

        (lyt intersects:damage) ifTrue:[
            savLyt := selectedTab layout.
            selectedTab layout:lyt.

            self paint:(self activeTabBackgroundColor).
            self fillRectangle:lyt.
            self drawTabEdgesFor:selectedTab.
            selectedTab drawSelected:true direction:direction on:self.

            self hasFocus ifTrue:[
                self drawFocusFor:selectedTab
            ].
            selectedTab 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 tab recv menu|

    enabled     ifFalse:[ ^ self ].
    list isEmpty ifTrue:[ ^ self ].

    idx := list findFirst:[:aTab| aTab containsPointX:x y:y ].
    idx == 0 ifTrue:[ ^ self ].

    tab := list at:idx.
    tab isEnabled ifFalse:[ ^ self ].

    ((button == 2) or:[button == #menu]) ifFalse:[
        "/ change the selection
        ^ self selection:idx
    ].
    accessTabMenuAction isNil ifTrue:[ ^ self ].
    menu := accessTabMenuAction value:idx.
    menu isNil ifTrue:[ ^ self ].

    menu isArray ifTrue:[
        menu := menu decodeAsLiteralArray
    ].

    menu receiver isNil ifTrue:[
        (recv := self application) isNil ifTrue:[
            recv := tab model
        ].
        recv notNil ifTrue:[
            menu receiver:recv
        ] ifFalse:[
            Transcript showCR:('%1 : MENU HAS NO RECEIVER' bindWith:(self class name)).
        ]
    ].
    menu startUp
!

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

    |sensor size index n key|

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

    (self processAccessCharacter:aKey) ifTrue:[
        ^ self
    ].

    (self processShortcutKey:aKey) ifTrue:[
        ^ self
    ].

    (size > 1 and:[aKey isSymbol and:[aKey startsWith:'Cursor']]) ifFalse:[
        ^ super keyPress:aKey x:x y:y
    ].

    self isHorizontal ifTrue:[
        (aKey == #CursorRight or:[aKey == #CursorLeft]) ifFalse:[
            ^ self
        ].
        key := aKey.
    ] ifFalse:[
                 aKey == #CursorUp   ifTrue:[key := #CursorLeft]
        ifFalse:[aKey == #CursorDown ifTrue:[key := #CursorRight]
        ifFalse:[ ^ self]].
    ].

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

        key == #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
    ]
!

processShortcutKeyEvent:event
    ^ self processShortcutKey:(event key)
!

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

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

!NoteBookView methodsFor:'focus handling'!

showFocus:explicit
    "got the keyboard focus 
    "
    |selectedTab|

    self supportsFocusOnTab ifTrue:[
        selectedTab := self selectedTab.
        selectedTab notNil ifTrue:[
            self invalidateTab:selectedTab
        ]
    ] ifFalse:[
        super showFocus:explicit
    ]
!

showNoFocus:explicit
    "lost the keyboard focus 
    "
    |selectedTab|

    self supportsFocusOnTab ifTrue:[
        selectedTab := self selectedTab.

        selectedTab notNil ifTrue:[
            self invalidateTab:selectedTab
        ].
    ] ifFalse:[
        super showNoFocus:explicit
    ]
!

supportsFocusOnTab
    "returns true if focus is supported
    "
    ^ (styleSheet at:#'focusHighlightStyle') == #win95
! !

!NoteBookView methodsFor:'help'!

helpText
    "return the helpText for the currently selected item (empty if none)
    "
    ^ self helpTextForItemAt:selection


!

helpTextAt:srcPoint
    "return the helpText for aPoint (i.e. when mouse-pointer is moved over an item).
    "
    |x y i|

    x := srcPoint x.
    y := srcPoint y.
    i := list findFirst:[:aTab| aTab containsPointX:x y:y ].

  ^ self helpTextForItemAt:i
!

helpTextForItemAt:anIndex
    |tab|

    (     anIndex notNil
     and:[anIndex ~~ 0
     and:[(tab := list at:anIndex ifAbsent:nil) notNil
     and:[(tab := tab model) notNil]]]
    ) ifTrue:[
        ^ tab activeHelpText ? ''
    ].
    ^ ''
! !

!NoteBookView methodsFor:'initialization & release'!

destroy
    "remove dependencies
    "
    list removeDependent:self.

    listHolder    removeDependent:self. 
    canvasHolder  removeDependent:self.

    super destroy.
!

initStyle
    "setup style attributes
    "
    |clr|

    super initStyle.
    tabModus  := false.
    edgeStyle := DefaultEdgeStyle.

    self font:self class defaultFont.
    drawLightColor := Color veryLightGray onDevice:device.

    clr := DefaultForegroundColor ? Black.
    foregroundColor := clr onDevice:device.

    clr := DefaultForegroundColor ? foregroundColor.
    activeForegroundColor := clr onDevice:device.

    (clr := DefaultShadowColor) isNil ifTrue:[clr := viewBackground darkened].
    shadowColor := clr onDevice:device.

    (clr := DefaultLightColor) isNil ifTrue:[clr := viewBackground lightened].
    lightColor := clr onDevice:device.

    tabBgColor := viewBackground.
    activeTabBgColor := viewBackground.

    edgeStyle isNil ifTrue:[
        halfShadowColor := shadowColor.
        halfLightColor  := lightColor.
        drawLightColor  := lightColor.
    ] ifFalse:[

        (clr := DefaultHalfShadowColor) isNil ifTrue:[
            clr := shadowColor lightened
        ].
        halfShadowColor := clr onDevice:device.

        (clr := DefaultHalfLightColor) isNil ifTrue:[
            clr := lightColor darkened.
        ].
        halfLightColor := clr onDevice:device.

        edgeStyle == #soft ifTrue:[
            drawLightColor := halfShadowColor
        ] ifFalse:[
            drawLightColor := Color veryLightGray onDevice:device.
        ]
    ].
    (clr := DisabledForegroundColor) notNil ifTrue:[
        disabledForegroundColor := clr onDevice:device
    ]ifFalse:[
        disabledForegroundColor := drawLightColor
    ].
!

initialize
    "setup default attributes
    "
    super initialize.

    self cursor:Cursor hand.

    list             := #().
    useIndex         := true.
    direction        := #top.
    fitLastRow       := true.
    enabled          := true.
    expandSelection  := StyleSheet at:#'noteBook.expandSelection'  default:8@8.
    canvasInset      := StyleSheet at:#'noteBook.canvasInset'      default:1@1.
    tabMargin        := StyleSheet at:#'noteBook.canvasTabMargin'  default:2.
    keepCanvas       := false.
    tabLevel         := StyleSheet at:#'noteBook.tabLevel'         default:1.

    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 l|

    xL  := 0.
    yT  := 0.
    xR  := width.
    yB  := height.

    list notEmpty ifTrue:[
        tab := list detect:[:aTab| aTab lineNr == 1] ifNone:nil.

        tab notNil ifTrue:[
            l := tab layout.

                      direction == #top    ifTrue:[ yT := l bottom ]
            ifFalse:[ direction == #bottom ifTrue:[ yB := l top    ]
            ifFalse:[ direction == #left   ifTrue:[ xL := l right  ]
            ifFalse:[
                xR := l left
            ]]]
        ]
    ].
    ^ Rectangle left:xL top:yT right:xR bottom:yB
!

computeLayoutForTab:aTab
    "calculate extent of a tab
    "
    |layout bwAbs left right top bottom expY expX|

    layout := aTab layout.

    self selectedTab == aTab ifFalse:[
        ^ layout
    ].

    layout := layout copy.

    bwAbs := tabLevel abs.
    expX  := expandSelection x // 2.
    expY  := expandSelection y // 2.

    left   := layout left.
    right  := layout right.
    top    := layout top.
    bottom := layout bottom.

    (direction == #top or:[direction == #bottom]) ifTrue:[
        left   := left  - expX.
        right  := right + expX.

        direction == #top  ifTrue:[
            bottom := bottom + bwAbs.
            top    := top - expY.
        ] ifFalse:[
            top    := top    - bwAbs.
            bottom := bottom + expY.
        ].
    ] ifFalse:[
        bottom := bottom + expX.
        top    := top    - expX.

        direction == #left ifTrue:[
            right := right + bwAbs.
            left  := left  - expY
        ] ifFalse:[
            left  := left  - bwAbs.
            right := right + expY.
        ]
    ].
    ^ Rectangle left:left top:top right:right bottom:bottom
!

makeToBaseLine:aLnNr
    "rotate lines to make the line #aLnNr be the new base line (i.e.
     subtract (aLnNr-1) from all lines and take modulu the number of lines"

    |lineTopsOrLefts isHorizontal|

    isHorizontal := self isHorizontal.

    "collect per-lineNr offsets"
    lineTopsOrLefts := (1 to:numberOfLines) collect:[:lnr |
                            |tabNr layout|

                            tabNr := list findFirst:[:aTab| aTab lineNr == lnr].
                            layout := (list at:tabNr) layout.
                            isHorizontal ifTrue:[
                                layout top.
                            ] ifFalse:[
                                layout left.
                            ].
                       ].

    "change offsets of all tabs"
    list do:[:el |
        |layout topOrLeft nr newNr|

        nr := el lineNr.
        newNr := nr - aLnNr + 1.
        newNr <= 0 ifTrue:[ newNr := newNr + numberOfLines].
        newNr := ((newNr - 1) \\ numberOfLines) + 1.
        topOrLeft := lineTopsOrLefts at:newNr.
        layout := el layout.
        isHorizontal ifTrue:[
            layout setTop:topOrLeft.
        ] ifFalse:[
            layout setLeft:topOrLeft.            
        ].
        el lineNr:newNr.
    ].

    self invalidate.
!

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

    list size ~~ 0 ifTrue:[
        self isHorizontal ifTrue:[
            self recomputeListHorizontal
        ] ifFalse:[
            self recomputeListVertical
        ]
    ].
    self resizeCanvas.
!

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 }"
     border    "{ Class:SmallInteger }"
    |

    startX     := expandSelection x // 2.
    lineWidth  := self width - startX.
    tabHeight  := self maxTabHeight.
    xLeft      := startX.
    yTop       := expandSelection y // 2 + tabMargin.
    border     := (tabLevel abs) max:1.
    border     := border + border.
    checkDir := canvas isNil ifTrue:[#top] ifFalse:[#bottom].

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

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

        (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 }"
     border   "{ Class:SmallInteger }"
    |

    startY     := expandSelection x // 2.
    lineHeight := self height - startY.
    tabHeight  := self maxTabHeight.
    yTop       := startY.
    xTop       := expandSelection y // 2 + tabMargin.
    border     := (tabLevel abs) max:1.
    border     := border + border.

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

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

        (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.
    ]
!

resizeCanvas
    |layout borderWd|

    canvas notNil ifTrue:[
        layout := self computeBorderLayout.

        list notEmpty ifTrue:[
            borderWd := tabLevel abs.
            layout   := layout insetBy:(canvasInset + borderWd).
        ].
        layout = canvas layout ifFalse:[
            canvas layout:layout.
        ].
    ]
! !

!NoteBookView methodsFor:'obsolete'!

canvasFrameLevel
    "ignorred
    "
    ^ 0
!

canvasFrameLevel:anInteger
    "ignorred
    "
!

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. 
! !

!NoteBookView methodsFor:'private'!

processAccessCharacter:aKey
    "a character is pressed; check for tab identified y the character
     select the tab and return true or if no tab detected return false
    "
    |j size char blck|

    (aKey isCharacter and:[(size := list size) ~~ 0]) ifFalse:[
        ^ false
    ].

    size == selection ifTrue:[
        size == 1 ifTrue:[^ false].
        j := 1
    ] ifFalse:[
        j := selection isNil ifTrue:[1] ifFalse:[selection + 1]
    ].

    char := aKey asLowercase.
    blck := [:i| ((list at:i) accessCharacter == char and:[self isSelectable:i]) ifTrue:[
                      self selection:i.
                    ^ true
                  ]        
            ].

    j to:size  do:blck.
    1 to:(j-1) do:blck.
  ^ false

!

processShortcutKey:aKey
    "if there is a short-key for that character, process it
     and return true. Otherwise, return false.
    "
    |j k size rawKey blck|

    (size := list size) == 0 ifTrue:[
        ^ false
    ].
    rawKey := device keyboardMap keyAtValue:aKey ifAbsent:aKey.

    size == selection ifTrue:[
        size == 1 ifTrue:[^ false].
        j := 1
    ] ifFalse:[
        j := selection isNil ifTrue:[1] ifFalse:[selection + 1]
    ].

    blck := [:i| k := (list at:i) shortcutKey.

                 (k notNil and:[(self isSelectable:i) and:[(k == aKey or:[k == rawKey])]]) ifTrue:[
                     self selection:i.
                   ^ true
                 ]
            ].

    j to:size  do:blck.
    1 to:(j-1) do:blck.
  ^ false
! !

!NoteBookView methodsFor:'queries'!

isEnabled
    "returns enabled state
    "
    ^ enabled
!

isFirstTabInLine:aTab
    "returns true if the tab is the first tab in the line
     used by drawing
    "
    |idx prevTab|

    idx := list identityIndexOf:aTab.
    prevTab := list at:(idx - 1) ifAbsent:nil.

  ^ prevTab isNil or:[prevTab lineNr ~~ aTab lineNr]
!

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

isLastTabInLine:aTab
    "returns true if the tab is the last tab in the line
     used by drawing
    "
    |index nextTab|

    index   := list identityIndexOf:aTab.
    nextTab := list at:(index + 1) ifAbsent:nil.

  ^ nextTab isNil or:[nextTab 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 and:[selection ~~ 0]) ifTrue:[
        ^ list at:selection ifAbsent:nil
    ].
    ^ nil
!

selection
    "return the selection or nil
    "
    selection isNil ifTrue:[
        ^ useIndex ifTrue:[0] ifFalse:[nil]
    ].
    ^ useIndex ifTrue:[selection] ifFalse:[self selectedTab 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 tappl model oldBounds newBounds|

    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:[
        oldBounds := newBounds := nil.

        selection ifNotNil:[
            oldBounds := self computeLayoutForTab:(self selectedTab)
        ].
        selection := newSel.

        selection ifNotNil:[
            newBounds := self computeLayoutForTab:(self selectedTab).

            (oldBounds notNil and:[newBounds intersects:oldBounds]) ifTrue:[
                oldBounds := oldBounds merge:newBounds.
                newBounds := nil.
            ].
        ].
        oldBounds ifNotNil:[ self invalidate:oldBounds ].
        newBounds ifNotNil:[ self invalidate:newBounds ].
    ].

    (canvas notNil and:[(canvas objectAttributeAt:#isTabItem) == true]) ifTrue:[
        canvas unmap.
        canvas := nil.
    ].

    (     selection notNil
     and:[(model := self selectedTab model) notNil
     and:[(tappl := model canvasView) notNil]]
    ) ifFalse:[
        ^ self
    ].

    canvasHolder notNil ifTrue:[
        canvasHolder value:tappl
    ] ifFalse:[
        self canvas:tappl
    ].
! !

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

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


! !

!NoteBookView::Tab methodsFor:'accessing'!

accessCharacter
    "returns the access character or nil
    "
    ^ accessCharacter
!

label
    "returns my original label
    "
    ^ label


!

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

    printableLabel notNil ifTrue:[
        printableLabel isImageOrForm ifTrue:[
            printableLabel := printableLabel onDevice:(aGC device)
        ] ifFalse:[
            printableLabel isString ifTrue:[
                printableLabel := self resolveDisplayStringFor:printableLabel
            ] ifFalse:[
                printableLabel class == LabelAndIcon ifTrue:[
                    printableLabel string:(self resolveDisplayStringFor:(printableLabel string))
                ]
            ].
        ]
    ] ifFalse:[
        printableLabel := ''
    ].
    extent := (printableLabel widthOn:aGC) @ (printableLabel heightOn:aGC).

!

lineNr
    "get the line number within the noteBook view
     1 -> on top of the wizard
    "
    ^ lineNr
!

lineNr:aLineNr
    "set the line number within the noteBook view
     1 -> on top of the wizard
    "
    lineNr := aLineNr
!

model
    "returns the model, a TabItem or nil
    "
    ^ model
!

printableLabel
    "get my printable label
    "
    ^ printableLabel

!

shortcutKey
    "get the  key to press to select the tab item from the keyboard
    "
    model notNil ifTrue:[
        ^ model shortcutKey
    ].
    ^ nil
!

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, the minimum size required by the tab
    "
    ^ extent
!

layout
    "get the tab's layout, set by the noteBook view
    "
    ^ layout
!

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


!

preferredExtentX
    "returns my preferred extent x
    "
    ^ 2 + extent x
!

preferredExtentY
    "returns my preferred extent y
    "
    ^ 2 + 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 destroyCanvas.
        model removeDependent:aGC.
    ]


! !

!NoteBookView::Tab methodsFor:'drawing'!

drawSelected:isSelected direction:aDirection on:aGC
    "redraw tab
    "
    |dispObj fgColor
     y  "{ Class:SmallInteger }"
     x  "{ Class:SmallInteger }"
    |

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

        (model isNil or:[(fgColor := model foregroundColor) isNil]) ifTrue:[
            fgColor := isSelected ifTrue:[aGC activeForegroundColor]
                                 ifFalse:[aGC foregroundColor].
        ]
    ] ifFalse:[
        fgColor := aGC disabledForegroundColor.

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

    aGC paint:fgColor.

    (aDirection == #top or:[aDirection == #bottom]) ifTrue:[
        x := layout left + (layout width  - extent x // 2).
        y := layout top  + (layout height - extent y // 2).

        aDirection == #bottom ifTrue:[y := y - 1] ifFalse:[y := y + 1].

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

        aDirection == #left ifTrue:[
            x := x + 1.
        ] ifFalse:[
            x := x - 1.
        ].

        dispObj isImageOrForm ifFalse:[

            dispObj isString ifTrue:[ 
                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 paint:fgColor.
            aGC backgroundPaint:aGC backgroundColor.
            aGC displayString:dispObj x:x y:y angle:90.
        ] ifTrue:[
            (dispObj rotated:90) displayOn:aGC x:x y:y.
        ]
    ]
! !

!NoteBookView::Tab methodsFor:'private'!

resolveDisplayStringFor:aString
    |string size rest pos idx|

    size   := aString size.
    string := aString.
    pos    := 0.

    size > 1 ifTrue:[
        (model notNil and:[(pos := model accessCharacterPosition) ~~ 0]) ifTrue:[
            pos > size ifTrue:[pos := 0]
        ] ifFalse:[
            idx := 1.

            [((idx := string indexOf:$& startingAt:idx) ~~ 0 and:[idx < size])] whileTrue:[
                rest := string copyFrom:(idx+1).

                idx == 1 ifTrue:[string := rest]
                        ifFalse:[string := (string copyFrom:1 to:(idx-1)), rest].

                (string at:idx) == $& ifTrue:[idx := idx + 1]
                                     ifFalse:[pos := idx].
                size := size - 1.
            ]
        ]
    ].
    size ~~ 0 ifTrue:[
        pos == 0 ifTrue:[
            pos := 1
        ] ifFalse:[
            string isText ifFalse:[
                string := Text string:string
            ].
            string emphasisAt:pos add:#underline
        ].
        accessCharacter := (string at:pos) asLowercase
    ] ifFalse:[
        accessCharacter := nil
    ].
    ^ string
! !

!NoteBookView::Tab methodsFor:'testing'!

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

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

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.61 2002-10-12 12:28:21 ca Exp $'
! !