NoteBookView.st
author Stefan Vogel <sv@exept.de>
Mon, 27 Sep 2004 10:50:27 +0200
changeset 2746 2c614cc1559c
parent 2740 c9812e019351
child 2758 89a2c0da11ec
permissions -rw-r--r--
Do not hardcode noteBook.tabTobMargin for windows into NotebookView. Set styleSheet instead.

"
 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 accessTabMenuAction
		canvas canvasInset canvasHolder halfLightColor halfShadowColor
		fitLastRow tabModus lastComputedExtent keepCanvas
		activeForegroundColor drawLightColor edgeStyle tabInset
		tabLabelInset disabledForegroundColor tabLevel tabTopMargin
		tabBottomMargin selectionInsetX selectionInsetY translateLabel
		buttonPrev buttonNext tabRightMargin tabLeftMargin'
	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:[:index| Transcript showCR:index].
    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:[:index| Transcript showCR:index].
    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:[:index| Transcript showCR:index].
    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:[:index| Transcript showCR:index].
    top open.
                                                                                [exEnd]


"
! !

!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
    "called if the contents of a tab changed; test whether the old layout can
     be reused otherwise we must recompute the whole list
    "
    |tab layout prefX prefY tabExtent|

    "/ 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.
        tabExtent := self preferredExtentForTab:tab.

        (     (prefX := tabExtent x) <= layout width
         and:[(prefY := tabExtent y) <= 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
    "returns the canvas; the containter view
    "
    ^ canvas
!

canvas:newCanvas
    "change the canvas; the containter view
    "
    |oldCanvas|

    oldCanvas := canvas.

    newCanvas ~~ oldCanvas ifTrue:[
        oldCanvas notNil ifTrue:[
            (keepCanvas or:[(oldCanvas objectAttributeAt:#isTabItem) == true]) ifTrue:[
                oldCanvas unmap.
            ] ifFalse:[
                oldCanvas destroy.
            ].
        ].
        canvas := newCanvas.
        newCanvas notNil ifTrue:[
            tabModus := false.

            self resizeCanvas.

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

            realized ifTrue:[
                newCanvas realize.
                newCanvas 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 the list;
     returns the index or nil if not found
    "
    |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 tab 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 of tabs
    "
    |state|

    state := aState ? true.

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

isEnabled
    "returns enabled state
    "
    ^ enabled
!

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
!

translateLabel
    "true if labels are translated
    "
    ^ translateLabel    
!

translateLabel:aBoolean
    "set to true if labels should be translated
    "
    translateLabel := aBoolean.
!

translateToDisplayLabel:aString
    "translate the label
    "
    |application builder string|

    translateLabel ifFalse:[ ^ aString ].

    aString isEmptyOrNil ifTrue:[ ^ aString ].

    application := self application.
    application isNil ifTrue:[^ aString ].

    builder := application builder.

    builder isNil ifTrue:[
        string := application resources string:aString.
    ] ifFalse:[
        
        string := builder aspectAt:(aString asSymbol).
        string notNil ifTrue:[^ string ].
        string := builder resources string:aString.
    ].
    ^ string ? aString
! !

!NoteBookView methodsFor:'accessing-colors'!

activeForegroundColor
    "returns the color used when drawing enabled tab labels
    "
    ^ activeForegroundColor
!

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

disabledForegroundColor
    "returns the color used when drawing disabled tab labels
    "
    ^ 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.
        self invalidate
    ]
!

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

halfShadowColor
    ^ halfShadowColor
!

viewBackground:aColor
    "get backgroundColor of the notebook view
    "
    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
"/    ].
! !

!NoteBookView methodsFor:'accessing-dimension'!

preferredExtent
    "compute max extent x/y based on one line
    "
    |level size x y isHorizontal insetX insetY extent|

    preferredExtent notNil ifTrue:[ ^ preferredExtent ].

    x := y := 0.
    level := (tabLevel abs) max:1.
    size  := list size.

    size ~~ 0 ifTrue:[
        list do:[:aTab|
            extent := self preferredExtentForTab:aTab.
            x := extent x + x.
            y := extent y max:y.
        ].
    ].
    y := y + selectionInsetY + level + tabTopMargin + tabBottomMargin.
    x := x + selectionInsetX + selectionInsetX + (level + level * size).

    isHorizontal := self isHorizontal.

    isHorizontal ifTrue:[
        x := x + self tabLeftMargin + self tabRightMargin
    ] ifFalse:[
        y := y + self tabLeftMargin + self tabRightMargin
    ].

    tabModus ifFalse:[
        canvasInset isPoint ifTrue:[
            insetX := canvasInset x.
            insetY := canvasInset y.
        ] ifFalse:[
            insetX := insetY := canvasInset.
        ].
        canvas notNil ifTrue:[ extent := canvas preferredExtent ]
                     ifFalse:[ extent := 100@100 ].

        y := y + insetY + insetY + extent y.
        x := x max:extent x.
        x := x + insetX + insetX + level + level.
    ].

    isHorizontal ifTrue:[ ^ x @ y ].
    ^ y @ x
!

preferredExtentForTab:aTab
    "returns the preferred extent of a tabulator
    "
    ^ aTab extent + tabLabelInset
! !

!NoteBookView methodsFor:'accessing-mvc'!

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

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.
        self styleChanged.
    ].
!

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 ifTrue:[
        fitLastRow := aBool.
        self styleChanged.
    ].
!

hasScrollButtons
    ^ buttonNext notNil
!

hasScrollButtons:aBoolean
    |hasScrollButtons|

    hasScrollButtons := self hasScrollButtons.
    hasScrollButtons == aBoolean ifTrue:[^ self].

    hasScrollButtons ifTrue:[
        buttonNext destroy.
        buttonPrev destroy.
        buttonNext := buttonPrev := nil.
    ] ifFalse:[
        buttonNext := ArrowButton in:self.
        buttonPrev := ArrowButton in:self.

        buttonNext beInvisible.
        buttonPrev beInvisible.
        
"/        realized ifTrue:[
"/            buttonNext create. "/ realize.
"/            buttonPrev create. "/ realize.
"/        ].
        buttonNext action:[ self scrollButtonPressed:#scrollRight  ].
        buttonPrev action:[ self scrollButtonPressed:#scrollLeft  ].
    ].
    self styleChanged.
!

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

tabBottomMargin
    "returns the margin between the tabs and the canvas
    "
    ^ tabBottomMargin
!

tabBottomMargin:aMargin
    "set the margin between the tabs and the canvas
    "
    |margin|

    margin := aMargin max:0.

    margin ~~ tabBottomMargin ifTrue:[
        tabBottomMargin := margin.
        self styleChanged.
    ].
!

tabLabelInset
    "inset (a point) of the label relative to its frame
         preferredExtent of Tab: label extent + tabLabelInset
    "
    ^ tabLabelInset
!

tabLabelInset:aPoint
    "inset (a point) of the label relative to its frame
         preferredExtent of Tab: label extent + tabLabelInset
    "
    |p|

    aPoint isNumber ifTrue:[ p := Point x:aPoint y:aPoint ]
                   ifFalse:[ p := aPoint ].

    p ~= tabLabelInset ifTrue:[
        tabLabelInset := p.
        self styleChanged.
    ].
!

tabLeftMargin
    "margin to the first visible tab or scroller button
    "
    ^ tabLeftMargin
!

tabLeftMargin:aMargin
    "margin to the first visible tab or scroller button
    "
    |margin|

    margin := aMargin max:0.

    margin ~~ tabLeftMargin ifTrue:[
        tabLeftMargin := margin.
        self styleChanged.
    ].
!

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

tabRightMargin
    "margin from the last visible tab or scroller button to the view
    "
    ^ tabRightMargin
!

tabRightMargin:aMargin
    "margin from the last visible tab or scroller button to the view
    "
    |margin|

    margin := aMargin max:0.

    margin ~~ tabRightMargin ifTrue:[
        tabRightMargin := margin.
        self styleChanged.
    ].
!

tabTopMargin
    "returns the margin between the tabs and the widget (not canvas)
    "
    ^ tabTopMargin
!

tabTopMargin:aMargin
    "set the margin between the tabs and the widget (not canvas)
    "
    |margin|

    margin := aMargin max:0.

    margin ~~ tabTopMargin ifTrue:[
        tabTopMargin := margin.
        self styleChanged.
    ].
! !

!NoteBookView methodsFor:'change & update'!

styleChanged
    "called if the tab style changed
     list must be recomputed
    "
    preferredExtent := nil.

    numberOfLines isNil ifTrue:[
        ^ self.         "/ layout not yet computed
    ].
    self recomputeList.
    self invalidate
!

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.
        ^ self.
    ].

    ^ super update:something with:aParameter from:changedObject

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

!NoteBookView methodsFor:'drawing'!

computeDrawingClipX:x y:y width:w height:h
    |trans xOrY wOrHInset|

    self hasScrollButtons ifFalse:[^ nil].

    trans     := self transformation.
    xOrY      := self tabLeftMargin.
    wOrHInset := self tabRightMargin + xOrY.

    self isHorizontal ifTrue:[
        trans notNil ifTrue:[
            xOrY := trans applyInverseToX:xOrY.
        ].
        ^ Rectangle left:xOrY top:y width:(self width - wOrHInset) height:h.
    ].
    trans notNil ifTrue:[
        xOrY := trans applyInverseToY:xOrY.
    ].
    ^ Rectangle left:x top:xOrY width:w height:(self height - wOrHInset)
!

drawBorderEdges
    |layout x0 x1 y0 y1 trans|

    "/ test whether TabView and not NoteBookView
    tabModus ifTrue:[^ self].

    layout := self computeBorderLayout.

    tabLevel ~~ 0 ifTrue:[
        self drawEdgesForX:(layout left)
                         y:(layout top)
                     width:(layout width) 
                    height:(layout height)
                     level:tabLevel.
      ^ self
    ].
    list size > 1 ifFalse:[^ self].

    self paint:lightColor ? lightColor.
    trans := self transformation.

    (direction == #top or:[direction == #bottom]) ifTrue:[
        direction == #top ifTrue:[ y0 := layout top - 1 ]
                         ifFalse:[ y0 := layout bottom ].
        y1 := y0.
        x0 := 0.
        trans notNil ifTrue:[
            x0 := trans applyInverseToX:x0.
        ].
        x1 := x0 + self width.
    ] ifFalse:[
        direction == #left ifTrue:[ x0 := layout left - 1 ]
                          ifFalse:[ x0 := layout right    ].
        x1 := x0.
        y0 := 0.
        trans notNil ifTrue:[
            y0 := trans applyInverseToY:y0.
        ].
        y1 := y0 + self height.
    ].
    self displayLineFromX:x0 y:y0 toX:x1 y:y1.
!

drawTabEdgesFor:aTab
    |layout count leftFg leftHalfFg rightFg x0 x1 y0 y1 isSelected
     yT "{ Class:SmallInteger }"
     xL "{ Class:SmallInteger }"
     xR "{ Class:SmallInteger }"
     yB "{ Class:SmallInteger }"
    |
    count      := tabLevel.
    isSelected := (self selectedTab == aTab).

    count <= 0 ifTrue:[
        isSelected ifFalse:[ ^ self ].

        count == 0 ifTrue:[
            list size > 1 ifFalse:[^ self].
            count := 1
        ] ifFalse:[
            count := count negated
        ].

        rightFg    := lightColor.
        leftFg     := shadowColor.
        leftHalfFg := halfShadowColor.
    ] 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.
        ].
        (isSelected and:[count > 1]) 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.
        ].

        (isSelected and:[count > 1]) 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.
        ].

        (isSelected and:[count > 1]) 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.
    ].

    (isSelected and:[count > 1]) 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.
    ]
!

redrawTab:aTab
    "redraw a tab
    "
    |isSelected layout fgColor extent voffs hoffs|

    isSelected := self selectedTab == aTab.

    layout := aTab layout.

    isSelected ifTrue:[
        self paint:(self viewBackground).
        self fillRectangle:layout.
    ].

    (enabled and:[aTab isEnabled]) ifFalse:[
        fgColor := disabledForegroundColor.
    ] ifTrue:[
        fgColor := aTab foregroundColor.
        fgColor isNil ifTrue:[
            isSelected ifTrue:[ fgColor := activeForegroundColor ]
                      ifFalse:[ fgColor := foregroundColor ].
        ]
    ].
    self paint:fgColor.
    aTab displayOn:self inset:(tabLevel abs) direction:direction.
    self drawTabEdgesFor:aTab.

    (     isSelected
     and:[self hasFocus
     and:[self supportsFocusOnTab]]
    ) ifFalse:[
        ^ self
    ].

    "/ drawing the focus

    extent := aTab extent.

    self isHorizontal ifTrue:[
        voffs  := (layout height - extent y) // 2 max:0.
        hoffs  := (layout width  - extent x) // 2 max:0.
    ] ifFalse:[
        voffs  := (layout height - extent x) // 2 max:0.
        hoffs  := (layout width  - extent y) // 2 max:0.
    ].

    self paint:(Color black).

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





""
!

redrawX:x y:y width:w height:h
    "a region must be redrawn
    "
    |selectedTab line damage layout selectedLayout clip|

    shown ifFalse:[ ^ self ].

    numberOfLines isNil ifTrue:[
        self recomputeList.

        numberOfLines notNil ifTrue:[
            self invalidate
        ].
        ^ self
    ].
    selectedTab := self selectedTab.

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

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

    list size == 0 ifTrue:[ ^ self ].

    self drawBorderEdges.

    damage := Rectangle left:x top:y width:w height:h.
    clip   := self computeDrawingClipX:x y: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:[
                clip notNil ifTrue:[
                    self clippingRectangle:clip.
                    clip := nil.
                ].
                self redrawTab:aTab.
            ]
        ]
    ].
    selectedTab isNil ifTrue:[
        ^ self
    ].
    layout := self computeLayoutForTab:selectedTab.

    (layout intersects:damage) ifTrue:[
        clip notNil ifTrue:[
            self clippingRectangle:clip.
            clip := nil.
        ].
        selectedLayout := selectedTab layout.
        selectedTab layout:layout.
        self redrawTab:selectedTab.
        selectedTab layout:selectedLayout.
    ].
! !

!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)).
        ]
    ].
    self startUpMenu:menu
!

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.
    sensor notNil ifTrue:[
        n := 1 + (sensor compressKeyPressEventsWithKey:aKey).
        n := (n \\ size) max:1.
    ] ifFalse:[
        n := 1.
    ].
    index := selection ? 0.

    key == #CursorRight ifTrue:[
        n timesRepeat:[
            index := self nextSelectableAfter:index wrapAtEnd:true.
            index == 0 ifTrue:[^ self].
        ].
    ] ifFalse:[
        n timesRepeat:[
            index := self previousSelectableBefore:index wrapAtBegin:true.
            index == 0 ifTrue:[^ self].
        ].
    ].
    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.
        ]
    ].
    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.

    list notEmptyOrNil ifTrue:[
        list do:[:anItem| |model|
            model := anItem model.
            model notNil ifTrue:[
                model destroyCanvas.
            ]
        ]
    ].
    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.

    (clr := DefaultShadowColor) notNil ifTrue:[shadowColor := clr onDevice:device].
    (clr := DefaultLightColor) notNil ifTrue:[lightColor := clr onDevice:device].

    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.

        (clr := DefaultHalfShadowColor) notNil ifTrue:[
            halfShadowColor := clr onDevice:device.
        ].

        (clr := DefaultHalfLightColor) notNil ifTrue:[
            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

    super initialize.

    self cursor:Cursor hand.

    list             := #().
    useIndex         := true.
    direction        := #top.
    fitLastRow       := true.
    enabled          := true.
    canvasInset      := StyleSheet at:#'noteBook.canvasInset'      default:1@1.
    keepCanvas       := false.
    tabLevel         := StyleSheet at:#'noteBook.tabLevel'         default:1.
    tabLabelInset    := StyleSheet at:#'noteBook.tabLabelInset'    default:6@4.
    selectionInsetX  := (2 max:(tabLevel abs)) + 1.
    selectionInsetY  := (2 max:(tabLevel abs)) + 1.
    translateLabel   := false.

    tabRightMargin   := 0.
    tabLeftMargin    := 0.

    tabTopMargin    := StyleSheet at:#'noteBook.tabTopMargin' default:4.
    tabBottomMargin := StyleSheet at:#'noteBook.tabBottomMargin' default:1.

    self lineWidth:0.

"/    canvas notNil ifTrue:[
"/        canvas := canvas in:self.
"/    ].
!

mapped

    super mapped.

    canvas notNil ifTrue:[
        canvas raise
    ].
!

postRealize
    "automatically set the initially selected notebook tab;
     unless it has been set already (by setup code)"

    selection isNil ifTrue:[
        self setSelection:1.
    ].
    super postRealize.
!

realize

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

!NoteBookView methodsFor:'layout'!

computeBorderLayout
    "returns the layout of the frame araound the canvas
    "
    |xL yT xR yB tab l|

    xL  := 0.
    yT  := 0.
    xR  := self width.
    yB  := self 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
            ]]]
        ]
    ].
    self buttonLayoutUpdate.        

    ^ Rectangle left:xL top:yT right:xR bottom:yB
!

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

    aTab isNil ifTrue:[^ nil].

    layout := aTab layout.

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

    bwAbs  := tabLevel abs.
    left   := layout left.
    right  := layout right.
    top    := layout top.
    bottom := layout bottom.

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

        bwAbs == 0 ifTrue:[
            left  == 0          ifTrue:[ left  := left  - 1 ].
            right == self width ifTrue:[ right := right + 1 ].
        ].

        direction == #top  ifTrue:[
            bottom := bottom + bwAbs.
            top    := top - selectionInsetY.
        ] ifFalse:[
            top    := top    - bwAbs.
            bottom := bottom + selectionInsetY.
        ].
    ] ifFalse:[
        top    := top    - selectionInsetX.
        bottom := bottom + selectionInsetX.

        bwAbs == 0 ifTrue:[
            top    == 0           ifTrue:[ top    := top    - 1 ].
            bottom == self height ifTrue:[ bottom := bottom + 1 ].
        ].

        direction == #left ifTrue:[
            right := right + bwAbs.
            left  := left  - selectionInsetY
        ] ifFalse:[
            left  := left  - bwAbs.
            right := right + selectionInsetY.
        ]
    ].
    ^ 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
    "
    |tab|

    numberOfLines      := 1.
    lastComputedExtent := self extent.

    self transformation:nil.

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

        tab := self selectedTab.
        tab isNil ifTrue:[tab := list first].

    ].
    self validateVisibleCanvas.
    self resizeCanvas.

    self hasScrollButtons ifTrue:[
        self isHorizontal ifTrue:[
            buttonNext direction:#right.
            buttonPrev direction:#left.
        ] ifFalse:[
            buttonNext direction:#down.
            buttonPrev direction:#up.
        ].
        self makeVisible:tab.
    ].
!

recomputeListHorizontal
    "recompute list
    "
    |layout lastLyt tabExtent isScrollable
     xLeft       "{ Class:SmallInteger }"
     xRight      "{ Class:SmallInteger }"
     yTop        "{ Class:SmallInteger }"
     tabWidth    "{ Class:SmallInteger }"
     tabHeight   "{ Class:SmallInteger }"
     delta       "{ Class:SmallInteger }"
     first       "{ Class:SmallInteger }"
     last        "{ Class:SmallInteger }"
     border      "{ Class:SmallInteger }"
     lastLnNr    "{ Class:SmallInteger }"
     tabLvlAbs   "{ Class:SmallInteger }"
     minLeft     "{ Class:SmallInteger }"
     maxRight    "{ Class:SmallInteger }"
     leftMargin  "{ Class:SmallInteger }"
     rightMargin "{ Class:SmallInteger }"
    |
    numberOfLines := 1.
    tabLvlAbs     := tabLevel abs max:1.
    border        := tabLevel * 2.
    tabHeight     := 0.
    leftMargin    := self tabLeftMargin.
    rightMargin   := self tabRightMargin.
    minLeft       := leftMargin + selectionInsetX.
    maxRight      := self width - rightMargin - selectionInsetX.
    xLeft         := minLeft.
    isScrollable  := self hasScrollButtons.

    list do:[:aTab|
        tabExtent := self preferredExtentForTab:aTab.
        tabWidth  := tabExtent x + border.
        tabHeight := tabExtent y max:tabHeight.
        xRight    := xLeft + tabWidth.

        (isScrollable not and:[xRight > maxRight]) ifTrue:[
            xLeft ~~ minLeft ifTrue:[
                numberOfLines := numberOfLines + 1.
                xLeft  := minLeft.
                xRight := xLeft + tabWidth.
            ].
            xRight > maxRight ifTrue:[
                tabWidth := maxRight - minLeft.
                xRight   := maxRight.
            ].
        ].
        aTab lineNr:numberOfLines.
        aTab layout:(Rectangle left:xLeft top:0 width:tabWidth height:tabHeight).
        xLeft := xRight.
    ].
    tabHeight := tabHeight + tabLvlAbs.
    yTop      := selectionInsetY + tabTopMargin.

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

    lastLnNr := numberOfLines.

    list reverseDo:[:aTab|
        aTab lineNr ~~ lastLnNr ifTrue:[
            lastLnNr := aTab lineNr.
            yTop := yTop + delta
        ].
        layout := aTab layout.
        layout setTop:yTop.
        layout height:tabHeight.
    ].

    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 := maxRight - lastLyt right) > 0 ifTrue:[
            xLeft := minLeft.
            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:(maxRight - lastLyt left)
        ].
        first := last + 1.
    ]
!

recomputeListVertical
    "recompute list
    "
    |layout lastLyt tabExtent isScrollable
     xTop        "{ Class:SmallInteger }"
     yTop        "{ Class:SmallInteger }"
     yBottom     "{ Class:SmallInteger }"
     tabWidth    "{ Class:SmallInteger }"
     tabHeight   "{ Class:SmallInteger }"
     delta       "{ Class:SmallInteger }"
     first       "{ Class:SmallInteger }"
     last        "{ Class:SmallInteger }"
     border      "{ Class:SmallInteger }"
     tabLvlAbs   "{ Class:SmallInteger }"
     minTop      "{ Class:SmallInteger }"
     maxBottom   "{ Class:SmallInteger }"
     leftMargin  "{ Class:SmallInteger }"
     rightMargin "{ Class:SmallInteger }"
    |

    numberOfLines := 1.
    tabLvlAbs     := (tabLevel abs) max:1.
    border        := tabLvlAbs * 2.
    tabHeight     := 0.
    leftMargin    := self tabLeftMargin.
    rightMargin   := self tabRightMargin.
    minTop        := leftMargin + selectionInsetX.
    maxBottom     := self height - rightMargin - selectionInsetX.    
    yTop          := minTop.
    isScrollable  := self hasScrollButtons.

    list do:[:aTab|
        tabExtent := self preferredExtentForTab:aTab.
        tabWidth  := tabExtent x + border.
        tabHeight := tabExtent y max:tabHeight.
        yBottom   := yTop + tabWidth.

        (isScrollable not and:[yBottom > maxBottom]) ifTrue:[
            yTop ~~ minTop ifTrue:[
                numberOfLines := numberOfLines + 1.
                yTop    := minTop.
                yBottom := yTop + tabWidth.
            ].
            yBottom > maxBottom ifTrue:[
                tabWidth := maxBottom - minTop.
                yBottom  := maxBottom.
            ].
        ].
        aTab lineNr:numberOfLines.
        aTab layout:(Rectangle left:0 top:yTop width:tabHeight height:tabWidth).
        yTop := yBottom
    ].
    tabHeight := tabHeight + tabLvlAbs.
    xTop      := selectionInsetY + tabTopMargin.

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

    last  := numberOfLines.

    list reverseDo:[:aTab|
        aTab lineNr ~~ last ifTrue:[
            last := aTab lineNr.
            xTop := xTop + delta
        ].
        layout := aTab layout.
        layout setLeft:xTop.
        layout   width:tabHeight.
    ].

    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 := maxBottom - lastLyt bottom) > 0 ifTrue:[
            yTop  := minTop.
            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:(maxBottom - 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).

            tabBottomMargin > 0 ifTrue:[
                (direction == #top or:[direction == #bottom]) ifTrue:[
                    layout height:(layout height - tabBottomMargin).
                    direction == #top ifTrue:[
                        layout setTop:(layout top + tabBottomMargin)
                    ]
                ] ifFalse:[
                    layout width:(layout width - tabBottomMargin).

                    direction == #left ifTrue:[
                        layout setLeft:(layout left + tabBottomMargin)
                    ]
                ]
                
            ].
        ].
        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:'private-buttons'!

buttonLayoutUpdate
    |layout bW h y w x e|

    self hasScrollButtons ifFalse:[^ self].

    (numberOfLines isNil or:[list size == 0]) ifTrue:[
        self transformation:nil.
        self hideButton:buttonPrev.
        self hideButton:buttonNext.
        ^ self
    ].
    layout := list first layout.
    bW := self buttonWidth.

    self isHorizontal ifTrue:[
        y := layout top.
        h := layout height.
        e := bW @ h.
        buttonPrev origin:(self tabLeftMargin)@y extent:e.
        buttonNext origin:(self width - self tabRightMargin - bW) @ y extent:e.
    ] ifFalse:[
        x := layout left.
        w := layout width.
        e := w @ bW.
        buttonPrev origin:x@(self tabLeftMargin) extent:e.
        buttonNext origin:x@(self height - self tabRightMargin - bW) extent:e.
    ].
!

buttonWidth
    "returns the button extent x or y dependent on the layout
    "
    ^ 16
!

hideButton:aButton
    aButton controller buttonRelease:#select x:0 y:0.
    aButton unmap.
!

makeVisible:aTab
    "setup transformation to make the selection visible;
     returns true if the transformation has changed otherwise false.
    "
    |layoutLast isHorizontal max maxAllowed oldTrans newTrans leftMargin rightMargin|

    (numberOfLines notNil and:[self hasScrollButtons]) ifFalse:[
        ^ false
    ].

    aTab isNil ifTrue:[
        list size == 0 ifTrue:[
            self hideButton:buttonPrev.
            self hideButton:buttonNext.
            self transformation:nil.
        ].
        ^ false.
    ].
    oldTrans     := self transformation.
    isHorizontal := self isHorizontal.
    layoutLast   := list last layout.
    leftMargin   := self tabLeftMargin.
    rightMargin  := self tabRightMargin.

    isHorizontal ifTrue:[
        max        := layoutLast right.
        maxAllowed := self width - rightMargin.

        max > maxAllowed ifTrue:[
            self makeVisibleHorizontal:aTab.
        ] ifFalse:[
            self transformation:nil.
        ].
    ] ifFalse:[
        max        := layoutLast bottom.
        maxAllowed := self height - rightMargin.

        max > maxAllowed ifTrue:[
            self makeVisibleVertical:aTab.
        ] ifFalse:[
            self transformation:nil.
        ].
    ].                
    newTrans := self transformation.

    newTrans isNil ifTrue:[
        self hideButton:buttonPrev.
    ] ifFalse:[
        buttonPrev map.

        max := isHorizontal ifTrue:[newTrans applyToX:max]
                           ifFalse:[newTrans applyToY:max].
    ].

    max > maxAllowed ifTrue:[
        buttonNext map
    ] ifFalse:[
        self hideButton:buttonNext.
    ].
    ^ oldTrans ~~ newTrans
!

makeVisibleHorizontal:aTab
    "setup transformation to make the horizontal selection visible
    "
    |trans bounds xL xR xI minLeft maxRight|

    trans  := self transformation.
    bounds := self computeLayoutForTab:aTab.
    xL     := bounds left.
    xI     := self buttonWidth.

    trans notNil ifTrue:[ xL := trans applyToX:xL ].

    minLeft := self tabLeftMargin.

    xL < (xI + minLeft) ifTrue:[
        list first == aTab ifTrue:[
            trans := nil.
        ] ifFalse:[
            trans := WindowingTransformation scale:nil translation:(((xI + minLeft) - bounds left) @ 0).
        ].
        self transformation:trans.
        ^ self
    ].
    xR       := xL + bounds width.
    maxRight := self width - self tabRightMargin.

    xR > (maxRight - xI) ifTrue:[
        list last == aTab ifTrue:[
            xI := 0.
        ].
        trans := WindowingTransformation scale:nil translation:((maxRight - xI - bounds right) @ 0).
        self transformation:trans.
    ].
!

makeVisibleVertical:aTab
    "setup transformation to make the vertical selection visible
    "
    |trans bounds xL xR xI minTop maxBot|

    trans   := self transformation.
    bounds  := self computeLayoutForTab:aTab.
    xL      := bounds top.
    xI      := self buttonWidth.

    trans notNil ifTrue:[ xL := trans applyToY:xL ].
    minTop := self tabLeftMargin.

    xL < (xI + minTop) ifTrue:[
        list first == aTab ifTrue:[
            trans := nil
        ] ifFalse:[
            trans := WindowingTransformation scale:nil translation:(0@((minTop + xI) - bounds top)).
        ].
        self transformation:trans.
        ^ self
    ].
    xR := xL + bounds height.
    maxBot := self height - self tabRightMargin.

    xR > (maxBot - xI) ifTrue:[
        list last == aTab ifTrue:[
            xI := 0.
        ].
        trans := WindowingTransformation scale:nil translation:(0@ (maxBot - xI - bounds bottom)).
        self transformation:trans.
    ].
!

scrollButtonPressed:whichButton
    |trans idx isNext nIdx pIdx|

    list isEmptyOrNil ifTrue:[^ self].

    whichButton == #scrollRight ifTrue:[
        isNext := true
    ] ifFalse:[
        whichButton == #scrollLeft ifFalse:[^ self].
        isNext := false.
    ].
    trans := self transformation.

    self isHorizontal ifTrue:[ |y xN xP|
        y  := list first layout top.
        xN := buttonNext origin x + 2.
        xP := buttonPrev corner x - 2.   

        trans notNil ifTrue:[
            xN := trans applyInverseToX:xN.
            xP := trans applyInverseToX:xP.
        ].
        nIdx := list findFirst:[:aTab| aTab containsPointX:xN y:y ].
        pIdx := list findFirst:[:aTab| aTab containsPointX:xP y:y ].
    ] ifFalse:[ |x yN yP|
        x  := list first layout left.
        yN := buttonNext origin y + 2.
        yP := buttonPrev corner y - 2.

        trans notNil ifTrue:[
            yN := trans applyInverseToY:yN.
            yP := trans applyInverseToY:yP.
        ].
        nIdx := list findFirst:[:aTab| aTab containsPointX:x y:yN ].
        pIdx := list findFirst:[:aTab| aTab containsPointX:x y:yP ].
    ].
    idx := isNext ifTrue:[nIdx] ifFalse:[pIdx].

    idx == 0 ifTrue:[
        idx := isNext ifTrue:[list size] ifFalse:[1].
    ] ifFalse:[ |revIdx|
        revIdx := isNext ifTrue:[pIdx] ifFalse:[nIdx].

        revIdx == idx ifTrue:[
            isNext ifTrue:[
                idx := revIdx + 1 min:(list size).
            ] ifFalse:[
                idx := revIdx - 1 max:1.
            ]
        ].
    ].

    (self makeVisible:(list at:idx ifAbsent:nil)) ifTrue:[
        self invalidate.
    ].
! !

!NoteBookView methodsFor:'queries'!

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

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
!

nextSelectableAfter:anIndex wrapAtEnd:wrapAtEnd
    "return the index of the next selectable entry after the index;
     wrap at end if the wrapAtEnd flag is set to true.
    "
    |size idx|

    size := list size.

    size > 1 ifTrue:[
        idx := anIndex + 1.
        idx to:size do:[:i| (self isSelectable:i) ifTrue:[^ i] ].

        wrapAtEnd ifTrue:[
            idx := anIndex - 1.
            1 to:idx do:[:i| (self isSelectable:i) ifTrue:[^ i] ].
        ]
    ].
    ^ 0
!

previousSelectableBefore:anIndex wrapAtBegin:wrapAtBegin
    "return the index of the previous selectable entry before the index;
     wrap at begin if the wrapAtBegin flag is set to true.
    "
    |size idx|

    size := list size.

    size > 1 ifTrue:[
        idx := anIndex - 1.
        idx to:1 by:-1 do:[:i| (self isSelectable:i) ifTrue:[^ i] ].

        wrapAtBegin ifTrue:[
            idx := anIndex + 1.
            size to:idx by:-1 do:[:i| (self isSelectable:i) ifTrue:[^ i] ].
        ]
    ].
    ^ 0
!

selectedTab
    "returns the selected tab or nil
    "
    (selection notNil and:[selection ~~ 0]) ifTrue:[
        ^ list at:selection ifAbsent:nil
    ].
    ^ nil
!

selection
    "return the selection or nil/o; caring for the useIndex setting.
    "
    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; update model and evaluate change action"

    |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 oldSel oldBounds newBounds|

    newSel := self listIndexOf:anIndexOrNil.

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

    numberOfLines isNil ifTrue:[
        selection := newSel.
        ^ self.
    ].
    oldSel    := selection.
    selection := newSel.
    newBounds := self computeLayoutForTab:(self selectedTab).

    (self makeVisible:(self selectedTab)) ifTrue:[
        self invalidate.
    ] ifFalse:[
        shown ifTrue:[
            oldSel notNil ifTrue:[
                selection := oldSel.
                oldBounds := self computeLayoutForTab:(self selectedTab).
                selection := newSel.

                (newBounds notNil and:[newBounds intersects:oldBounds]) ifTrue:[
                    newBounds := newBounds merge:oldBounds.
                ] ifFalse:[
                    self invalidate:oldBounds
                ].
            ].
            newBounds notNil ifTrue:[
                self invalidate:newBounds.
            ]
        ].
    ].
    self validateVisibleCanvas.
!

validateVisibleCanvas
    |model newCanvas selectedTab|

    selectedTab := self selectedTab.

    selectedTab notNil ifTrue:[
        model := selectedTab model.

        model isNil ifTrue:[
            ^ self
        ].
        newCanvas := model canvasView.
    ].

    newCanvas == canvas ifTrue:[
        ^ self
    ].

    canvas notNil ifTrue:[
        (canvas objectAttributeAt:#isTabItem) == true ifFalse:[
            ^ self.
        ]
    ].
    self canvas:newCanvas.

    canvasHolder notNil ifTrue:[
        canvasHolder value:newCanvas.
    ].
! !

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

foregroundColor
    "returns the foregroundColor or nil
    "
    model notNil ifTrue:[
        ^ model foregroundColor
    ].
    ^ nil
!

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 on:aGC.
            ] ifFalse:[
                printableLabel class == LabelAndIcon ifTrue:[
                    printableLabel string:(self resolveDisplayStringFor:(printableLabel string) on:aGC)
                ]
            ].
        ]
    ] 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


! !

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

displayOn:aGC inset:inset direction:aDirection
    "redraw tab
    "
    |dispObj lft wdt top hgt
     y  "{ Class:SmallInteger }"
     x  "{ Class:SmallInteger }"
    |

    "/ REDRAW LABEL
    (aGC isEnabled and:[self isEnabled]) ifTrue:[
        dispObj := printableLabel.
    ] ifFalse:[
        (dispObj := disabledLabel) isNil ifTrue:[
            (dispObj := printableLabel) isImageOrForm ifTrue:[
                disabledLabel := printableLabel lightened onDevice:(aGC device)
            ]
        ]
    ].

    (aDirection == #top or:[aDirection == #bottom]) ifTrue:[
        lft := layout left  + inset.
        wdt := layout right - inset - lft.
        wdt > 4 ifFalse:[^ self].

        x := (wdt - extent x) // 2.
        x < 0 ifTrue:[
            dispObj := '...'.
            x := 0.
        ].
        x := x + lft.
        y := layout top  + (layout height - inset - extent y // 2).

        aDirection == #top ifTrue:[ y := y + inset ].

        y := y + (dispObj ascentOn:aGC).
"/        dispObj isImageOrForm ifFalse:[
"/            y := y + aGC font ascent
"/        ].
        dispObj displayOn:aGC x:x y:y.
        ^ self
    ].
    top := layout  top   + inset.
    hgt := layout bottom - inset - top.
    hgt > 4 ifFalse:[^ self].

    y := (hgt - extent x) // 2.
    y < 0 ifTrue:[
        dispObj := '...'.
        y := 0.
    ].
    y := y + top.
    x := layout left + (layout width  - inset - extent y // 2).

    aDirection == #left ifTrue:[ x := x + inset ].

    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 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 on:aNoteBook
    |string size rest pos idx|

    accessCharacter := nil.
    string := aNoteBook translateToDisplayLabel:aString.
    size   := string size.
    pos    := 0.

    size == 0 ifTrue:[ ^ string ].

    (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
    ].
    ^ 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.98 2004-09-27 08:50:27 stefan Exp $'
! !