NoteBookView.st
author Claus Gittinger <cg@exept.de>
Tue, 18 Sep 2001 11:55:56 +0200
changeset 2010 644587a3b8e2
parent 2002 d8a0fba7b75a
child 2035 6cc4d73f17e1
permissions -rw-r--r--
added tabLevel

"
 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
		canvasFrameLevel 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]


"

! !

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

canvasFrameLevel
    "inset of the canvas relative to my canvas boundery
    "
    ^ canvasFrameLevel
!

canvasFrameLevel:anInteger
    "set the inset of the canvas relative to my canvas boundery
    "
    canvasFrameLevel ~~ anInteger ifTrue:[
        canvasFrameLevel := anInteger.
        self recomputeList.
        self invalidate.
    ].
!

canvasInset
    "inset of the canvas relativr to my frame
    "
    ^ canvasInset
!

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

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

!

list:aList
    "set the list
    "
    |size 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]


!

tabLevel
    "level of the tab relative to the canvas
    "
    ^ tabLevel
!

tabLevel:anInteger
    "set the level of the tab relative to the canvas
    "
    tabLevel ~~ anInteger ifTrue:[
        tabLevel := anInteger.
"/        self recomputeList.
        self invalidate.
    ].
!

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

maxTabHeight
    |e y|

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

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

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

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

    list isEmpty ifTrue:[^ 0].

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

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

!NoteBookView methodsFor:'accessing-look'!

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

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
!

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

shadowColor:aColor
    "get the color to be used for shadowed edges
    "
    super shadowColor:aColor
!

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

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

!

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

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

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

tabModus
    ^ tabModus
!

tabModus:aBoolean

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

! !

!NoteBookView methodsFor:'change & update'!

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

    changedObject == model         ifTrue:[^ self selection:model value].
    changedObject == listHolder    ifTrue:[
        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'!

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

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

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

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

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

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

                    aTab redrawAt:direction selected:false on:self
                ]
            ]
        ]
    ] ifFalse:[
        selectedTab := nil
    ].

    tabModus ifFalse:[
        lyt := self computeBorderLayout.
        canvasFrameLevel ~~ 0 ifTrue:[
            self drawEdgesForX:lyt left 
                             y:lyt top
                         width:lyt width 
                        height:lyt height
                         level:canvasFrameLevel
                        shadow:shadowColor 
                         light:lightColor
                    halfShadow:halfShadowColor 
                     halfLight:halfLightColor
                         style:edgeStyle
        ] ifFalse:[
            (tabLevel notNil and:[tabLevel ~~ 0]) ifTrue:[
                list size > 0 ifTrue:[
                    right := lyt left + lyt width - 1.
                    self paint:lightColor.
                    1 to:tabLevel do:[:i |
                        |y|

                        y := lyt top + tabLevel - i.
                        self displayDeviceLineFromX:(lyt left) y:y toX:right y:y.
                    ]       
                ]       
            ]
        ]
    ].

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

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

            activeTabBgColor ~~ viewBackground ifTrue:[
                self paint:activeTabBgColor.
                self fillRectangle:lyt.
            ].
            selectedTab redrawAt:direction selected:true on:self.

            (self hasFocus 
            and:[(styleSheet at:#'focusHighlightStyle') == #win95]) ifTrue:[
                selectedTab drawWin95FocusFrameOn:self
            ].
            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 and:[list notEmpty]) ifFalse:[
        ^ self
    ].
    (    (idx := list findFirst:[:aTab|aTab containsPointX:x y:y]) == 0
     or:[(tab := list at:idx ifAbsent:nil) isNil
     or:[tab isEnabled not]]
    ) ifTrue:[
        ^ self
    ].

    ((button == 2) or:[button == #menu]) ifFalse:[
        "/ change the selection
        ^ self selection:idx
    ].
    (accessTabMenuAction notNil and:[(menu := accessTabMenuAction value:idx) notNil]) ifFalse:[
        ^ 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 
    "
    |tab|

    (styleSheet at:#'focusHighlightStyle') == #win95 ifTrue:[
        (tab := self selectedTab) notNil ifTrue:[
            self invalidateTab:tab
        ]
    ] ifFalse:[
        super showFocus:explicit
    ]

!

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

    (styleSheet at:#'focusHighlightStyle') == #win95 ifTrue:[
        (tab := self selectedTab) notNil ifTrue:[
            self invalidateTab:tab
        ]
    ] ifFalse:[
        super showNoFocus:explicit
    ]
! !

!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.
    canvasFrameLevel := StyleSheet at:#'noteBook.canvasFrameLevel' default:2.
    tabMargin        := StyleSheet at:#'noteBook.canvasTabMargin'  default:2.
    keepCanvas       := false.

    self lineWidth:0.

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

realize

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

!NoteBookView methodsFor:'layout'!

XXmakeToBaseLine:aLnNr
"/ the old, obsolete algorithm.
"/ does NOT preserve the tab-order.
"/
"/    |layout1 layoutN topN top1 leftN left1 lineTops
"/     nr "{ Class:SmallInteger }"
"/    |
"/
"/    lineTops := (1 to:numberOfLines) collect:[:lnr |
"/                    |tabNr layout|
"/
"/                    tabNr := list findFirst:[:aTab| aTab lineNr == lnr].
"/                    layout := (list at:tabNr) layout.
"/                    layout top.
"/                ].
"/
"/    nr := list findFirst:[:aTab| aTab lineNr == 1].
"/    layout1 := (list at:nr) layout.
"/
"/    nr := list findFirst:[:aTab| aTab lineNr == aLnNr].
"/    layoutN := (list at:nr) layout.
"/
"/    self isHorizontal ifTrue:[
"/        top1 := layout1 top.
"/        topN := layoutN top.
"/
"/        list do:[:el|
"/            (nr := el lineNr) == 1 ifTrue:[
"/                el layout setTop:topN. el lineNr:aLnNr
"/            ] ifFalse:[
"/                nr == aLnNr ifTrue:[
"/                    el layout setTop:top1. el lineNr:1
"/                ]
"/            ]
"/        ]
"/    ] ifFalse:[
"/        left1 := layout1 left.
"/        leftN := layoutN left.
"/
"/        list do:[:el|
"/            (nr := el lineNr) == 1 ifTrue:[
"/                el layout setLeft:leftN. el lineNr:aLnNr
"/            ] ifFalse:[
"/                nr == aLnNr ifTrue:[
"/                    el layout setLeft:left1. el lineNr:1
"/                ]
"/            ]
"/        ]
"/    ].
"/    self invalidate
!

computeBorderLayout
    |xL yT xR yB tab|

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

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

!

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

    layout := aTab layout.

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

    level  := tlevel := canvasFrameLevel abs.
    level == 0 ifTrue:[ tlevel := tabLevel ? 0].

    layout := layout copy.
    w := expandSelection x.
    h := expandSelection y.
    x := w // 2.
    y := h // 2.

    (direction == #top or:[direction == #bottom]) ifTrue:[
        layout setLeft:(layout left   - x).
        layout   width:(layout width  + w).
        layout  height:(layout height + y + tlevel).

        direction == #top ifTrue:[
            layout setTop:(layout top - y).
        ] ifFalse:[
            layout setTop:(layout top - tlevel).
        ].
        ^ layout
    ].

    layout  setTop:(layout top    - x).
    layout  height:(layout height + w).
    layout   width:(layout width  + y + level).

    direction == #left ifTrue:[
        layout setLeft:(layout left - y).
    ] ifFalse:[
        layout setLeft:(layout left - level)
    ].

  ^ layout
!

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

    startX     := expandSelection x // 2 + canvasFrameLevel abs - 2.
    lineWidth  := self width - startX.
    tabHeight  := self maxTabHeight.
    xLeft      := startX.
    yTop       := expandSelection y // 2 + tabMargin.

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

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

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

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

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

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

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

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

    first := 1.

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

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

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

recomputeListVertical
    "recompute list
    "
    |layout lastLyt
     xTop      "{ Class:SmallInteger }"
     yTop      "{ Class:SmallInteger }"
     tabWidth  "{ Class:SmallInteger }"
     tabHeight "{ Class:SmallInteger }"
     lineHeight "{ Class:SmallInteger }"
     startY    "{ Class:SmallInteger }"
     delta     "{ Class:SmallInteger }"
     first     "{ Class:SmallInteger }"
     last      "{ Class:SmallInteger }"
    |

    startY     := expandSelection x // 2 + canvasFrameLevel abs - 2.
    lineHeight := self height - startY.
    tabHeight  := self maxTabHeight.
    yTop       := startY.
    xTop       := expandSelection y // 2 + tabMargin.

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

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

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

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

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

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

    first := 1.

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

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

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

resizeCanvas
    |layout lvl|

    canvas notNil ifTrue:[
        layout := self computeBorderLayout.
        lvl := canvasFrameLevel abs.
        layout := layout insetBy:(canvasInset + lvl).
        lvl == 0 ifTrue:[
            tabLevel notNil ifTrue:[
                layout := Rectangle
                                left:layout left
                                top:layout top + tabLevel
                                width:layout width
                                height:layout height - tabLevel.
            ]
        ].
"/        ((direction == #top) or:[direction ==#bottom]) ifTrue:[
"/            layout := layout insetBy:((0@canvasInset y) + canvasFrameLevel abs).
"/        ] ifFalse:[
"/            layout := layout insetBy:((canvasInset x @ 0) + canvasFrameLevel abs).
"/        ].
        canvas layout:layout.
    ]
! !

!NoteBookView methodsFor:'obsolete'!

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

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

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

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

moveSelectedRow
     ^ true
!

moveSelectedRow:something
!

oneTabPerLine
    ^ false
!

oneTabPerLine:something
!

tabWidget
    ^ nil
!

tabWidget:something
! !

!NoteBookView methodsFor:'private'!

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
    |idx tab|

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

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

!

isLastTabInLine:aTab
    |index tab|

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

!NoteBookView methodsFor:'selection'!

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

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

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

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

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

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

    sel := self selection.

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

!

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

    newSel := self listIndexOf:anIndexOrNil.

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

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

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

    (     selection notNil
     and:[(model := (list at:selection) 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
    ^ 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
    "
    ^ lineNr

!

lineNr:aLineNr
    "set the line number
    "
    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
    "
    ^ extent


!

layout
    "get the tab's layout
    "
    ^ layout


!

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


!

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


!

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


! !

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

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


!

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


! !

!NoteBookView::Tab methodsFor:'drawing'!

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

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

    aGC paint:(aGC drawLightColor).
    aGC displayLineFromX:xL y:yB-2 toX:xL   y:yT.

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

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

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








!

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

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

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

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

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


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





!

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

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

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

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

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

    isSelected ifFalse:[^ self].

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

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





!

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

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

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

    aGC paint:(aGC drawLightColor).
    aGC displayLineFromX:xL+2 y:yT toX:xR-2 y:yT.          "/ top line
    aGC displayLineFromX:xL   y:yB toX:xL   y:yT+2.        "/ left line
    aGC displayPointX:xL+1    y:yT+1.

    aGC paint:(aGC halfLightColor).
    aGC displayLineFromX:xL+2 y:yT+1 toX:xR-2 y:yT+1.      "/ top line 2
    aGC displayLineFromX:xL+1 y:yB toX:xL+1 y:yT+2.        "/ left line 2

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






!

drawWin95FocusFrameOn:aGC

"/aGC notNil ifTrue:[^ self].

    aGC displayDottedRectangleX:(layout left   + 4)
                              y:(layout top    + 4)
                          width:(layout width  - 8)
                         height:(layout height - 8).
!

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

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

    "/ 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 notNil ifTrue:[layout containsPointX:x y:y]
                   ifFalse:[false].


!

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


!

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


! !

!NoteBookView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/NoteBookView.st,v 1.53 2001-09-18 09:55:56 cg Exp $'
! !