TabView.st
author Stefan Vogel <sv@exept.de>
Wed, 31 Mar 1999 07:53:11 +0200
changeset 1296 ab26ea632b56
parent 1118 a49afa5a9f10
child 1329 e0dff849cf82
permissions -rw-r--r--
Move common channels to View.

"
 COPYRIGHT (c) 1997 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


View subclass:#TabView
	instanceVariableNames:'list listHolder selection enabled action tabStyle useIndex
		maxRawNr direction fitLastRow moveSelectedRow
		selectConditionBlock oldExtent oneTabPerLine fontAscent
		fontDescent'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Interactors'
!

!TabView 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 tabs-view component of a noteBook.
    May also be used on its own (without a surrounding noteBook).

    The functionality is basically the same as provided by a
    PopUpList or SelectionInListView, in that a valueHolder
    gets a value assigned corresponding to the selected tab
    from a list of possible tabs.

    [author:]
	Claus Atzkern

    [see also:]
	NoteBookView
	SelectionInListView PopUpList ValueHolder TabWidget
"

!

examples
"
    tabs at top of a view
										[exBegin]                                      
    |top tab view inset|

    top := StandardSystemView new label:'tabs at top'; extent:250@100.
    tab  := TabView origin:0.0 @ 0.0 corner:1.0 @ 0.0 in:top.
    view := View    origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.

    view viewBackground:(tab styleAt:#selectedColor).
    tab direction:#top.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    inset := tab preferredSizeXorY.
    tab  bottomInset:(inset negated).
    view topInset:inset.
    tab action:[:aName|Transcript showCR:aName].
    top open.
										[exEnd]

    tabs at bottom of a view; changing widget to MAC style
										[exBegin]                                      
    |top tab view inset|

    top := StandardSystemView new label:'tabs at bottom'; extent:250@100.
    view := View    origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab  := TabView origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:top.

    view viewBackground:(tab styleAt:#selectedColor).
    tab direction:#bottom.
    tab tabWidget:#Mac.

    tab list:#( 'Foo' 'Bar' 'Baz' ).
    inset := tab preferredSizeXorY.
    tab  topInset:(inset negated).
    view bottomInset:inset.
    tab action:[:aName|Transcript showCR:aName].
    top open.
										[exEnd]

    tabs at right of a view
										[exBegin]                                      
    |top tab view inset|

    top := StandardSystemView new label:'tabs at right'; extent:100@250.
    view := View    origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab  := TabView origin:1.0 @ 0.0 corner:1.0 @ 1.0 in:top.

    view viewBackground:(tab styleAt:#selectedColor).
    tab direction:#right.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    inset := tab preferredSizeXorY.
    tab leftInset:(inset negated).
    view rightInset:inset.
    tab action:[:aName|Transcript showCR:aName].
    top open.
										[exEnd]

    tabs at left of a view
										[exBegin]                                      
    |top tab view inset|

    top := StandardSystemView new label:'tabs at left'; extent:100@250.
    tab  := TabView origin:0.0 @ 0.0 corner:0.0 @ 1.0 in:top.
    view := View    origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.

    view viewBackground:(tab styleAt:#selectedColor).
    tab direction:#left.
    tab list:#( 'Foo' 'Bar' 'Baz' ).
    inset := tab preferredSizeXorY.
    tab rightInset:(inset negated).
    view leftInset:inset.
    tab action:[:aName|Transcript showCR:aName].
    top open.
										[exEnd]

    changing default style( see TabWidget class ); useing index
										[exBegin]                                      
    |top tab view|

    top := StandardSystemView new label:'example'; extent:450@300.
    tab := TabView origin:0.0 @ 0.0 corner:1.0 @ 40 in:top.
    tab horizontalInset:10.
    view := NoteBookFrameView origin:0.0 @ 40  corner:1.0 @ 1.0 in:top.
    view horizontalInset:10.
    view bottomInset:10.
    view level:2.
    view viewBackground:(Image fromFile:'bitmaps/gifImages/garfield.gif').

    tab styleAt:#selectedColor    put:(view viewBackground).
    tab styleAt:#unselectedColor  put:(Color grey:60).
    tab styleAt:#expandSelection  put:9@7.

    tab list:#( 'Foo' 'Bar' 'Baz').
    tab useIndex:true.
    tab action:[:aName| Transcript showCR:aName ].

    top open.
										[exEnd]


    using images and text
										[exBegin]
    |top tab view list|

    top := StandardSystemView new label:'example'.
    tab := TabView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    list := #( 'SBrowser' 'FBrowser' 'Debugger' ).
    list := list collect:[:n | Image fromFile:'bitmaps/' , n , '.xbm'].
    list add:'A Text'.
    tab list:list.
    tab action:[:indexOrNil| Transcript showCR:indexOrNil ].
    top extent:(tab preferredExtent).
    top open.
										[exEnd]

    using images and text; MAC style
										[exBegin]
    |top tab view list|

    top := StandardSystemView new label:'example'.
    tab := TabView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    tab tabWidget:#Mac.
    list := #( 'SBrowser' 'FBrowser' 'Debugger' ).
    list := list collect:[:n | Image fromFile:'bitmaps/' , n , '.xbm'].
    list add:'A Text'.
    tab list:list.
    tab action:[:indexOrNil| Transcript showCR:indexOrNil ].
    top extent:(tab preferredExtent).
    top open.
										[exEnd]

    tabs at top of view dealing with other models

										[exBegin]
    |top sel view l top2 s top3 p|

    l := SelectionInList new.
    l list:#('foo' 'bar' 'baz').
    l selectionIndex:1.

    top2 := StandardSystemView new.
    top2 extent:100@100.
    s := SelectionInListView origin:0.0@0.0 corner:1.0@1.0 in:top2.
    s model:l.
    top2 open.

    top3 := StandardSystemView new.
    top3 extent:100@100.
    s := PopUpList in:top3.
    s model:l.
    top3 open.

    top := StandardSystemView new label:'example'; extent:200@50.
    sel := TabView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
    sel useIndex:true.
    sel model:(l selectionIndexHolder).
    sel listHolder:(l listHolder).
    sel action:[:indexOrNil|Transcript showCR:indexOrNil].
    top open.
										[exEnd]
"
! !

!TabView class methodsFor:'defaults'!

defaultTabWidget
    ^ #Window
! !

!TabView methodsFor:'accessing'!

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

!

backgroundColor
    ^ viewBackground
!

fontAscent
    fontAscent isNil ifTrue:[
	fontAscent := self font ascent
    ].
    ^ fontAscent
!

fontDescent
    fontDescent isNil ifTrue:[
	fontDescent := self font descent
    ].
    ^ fontDescent
!

list
    "return the list
    "
    ^ list
!

list:aList
    "set the list
    "
    |hasChanged newSel model|

    aList size == list size ifTrue:[
	list notNil ifTrue:[
	    list keysAndValuesDo:[:aKey :aTab|
		(aTab label) = (aList at:aKey) ifFalse:[
		    hasChanged := true
		]
	    ]
	].
	hasChanged == true ifFalse:[^ self ].
    ].

    self removeListDependencies.

    aList size ~~ 0 ifTrue:[
	(newSel := self tabAt:selection) notNil ifTrue:[
	    newSel := newSel printableLabel
	].
	list := (tabStyle at:#widget) labels:aList for:self.

	list do:[:aTab|
	    (model := aTab model) notNil ifTrue:[
		model addDependent:self
	    ]
	].

	newSel notNil ifTrue:[
	    (newSel := list findFirst:[:aTab| aTab printableLabel = newSel]) == 0 ifTrue:[
		newSel := nil
	    ]
	].
    ] ifFalse:[
	list := nil.
    ].
    selection := newSel.

    self shown ifTrue:[
	self recomputeList.
	self invalidateRepairNow:true.
	self changed:#preferredExtent
    ].
!

oneTabPerLine
    ^ oneTabPerLine
!

oneTabPerLine:aBool
    oneTabPerLine := aBool.
!

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


!

viewBackground:aColor
    "update colors
    "
    super viewBackground:aColor.
    TabWidget computeColorsOn:self style:tabStyle.
    shown ifTrue:[
	self invalidate.
    ]

    "Modified: / 6.6.1998 / 19:55:59 / cg"
! !

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

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

!TabView methodsFor:'accessing channels/holders'!

listHolder
    "returns the list holder
    "
    ^ listHolder
!

listHolder:aValueHolder
    "change the list holder
    "
    listHolder notNil ifTrue:[
	listHolder removeDependent:self. 
    ].

    listHolder := aValueHolder.
    listHolder notNil ifTrue:[
	listHolder addDependent:self.
	self list:listHolder value.
	self selection:model value.
    ].
!

model:aValueHolder
    super model:aValueHolder.

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

!TabView methodsFor:'accessing dimension'!

preferredExtent
    "compute max extent x/y based on one line
    "
    |x y ovl size maxY|

    (size := list size) == 0 ifTrue:[^ 0 @ 0 ].

    maxY := tabStyle at:#maxY.
    y    := maxY + self viewSpacing.

    oneTabPerLine ifTrue:[
	y := y + ((size - 1) * maxY).

	(self isHorizontalDirection) ifTrue:[x := super extent x]
				    ifFalse:[x := super extent y]
    ] ifFalse:[
	x := ovl := tabStyle at:#rightCovered.
	list do:[:aTab|x := x - ovl + aTab preferredExtentX]
    ].

    (self isHorizontalDirection) ifTrue:[^ x @ y]
				ifFalse:[^ y @ x]
!

preferredSizeXorY
    "returns preferred size dependant on the current view layout and
     the direction of the tabs
    "
    list size == 0 ifFalse:[
	maxRawNr isNil ifTrue:[self recomputeList].

	oneTabPerLine ifTrue:[
	    self isHorizontalDirection ifTrue:[^ super extent y]
				      ifFalse:[^ super extent x]
	].
	^ ((maxRawNr * (tabStyle at:#maxY)) + self viewSpacing).
    ].
    ^ 0
!

viewSpacing
    "returns my view spacing
    "
    ^ ((tabStyle at:#expandSelection) y) + (self class viewSpacing)
! !

!TabView 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.
	self changed:#direction
    ].
!

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
!

font:aFont
    (aFont ~= font) ifTrue:[
	super font:aFont.
	fontAscent := fontDescent := nil
    ]

!

moveSelectedRow
    "in case of true, the raw assigned to the tab will be moved
     to the first line (to the view). Otherwise the position of
     the view will be kept.
    "
    ^ moveSelectedRow
!

moveSelectedRow:aBool
    "in case of true, the raw assigned to the tab will be moved
     to the first line (to the view). Otherwise the position of
     the view will be kept.
    "
    moveSelectedRow := aBool
!

style
    "returns the style sheet derived from the current widget class
    "
    ^ tabStyle
!

styleAt:anIdentifier
    "returns a specific entry into the widget description. For more information
     see the specific widget class ( TabWidget ... ).
    "
    ^ tabStyle at:anIdentifier
!

styleAt:anIdentifier put:something
    "change a specific entry from the widget description. For more information
     see the specific widget class ( TabWidget ... ).
    "
    tabStyle at:anIdentifier put:something.
!

tabWidget
    "returns the current widget class as symbol
    "
    |widget|

    widget := tabStyle at:#widget.
    widget := widget nameWithoutPrefix asSymbol.
  ^ widget
!

tabWidget:aWidget
    "change the current widget class. An existing list will be
     recomputed and redrawn
    "
    |widget labels|

    (self tabWidget) ~~ aWidget ifTrue:[
	widget := TabWidget widgetClass:aWidget.

	widget notNil ifTrue:[
	    tabStyle := widget tabStyleOn:self.

	    list notNil ifTrue:[
		labels := list collect:[:aTab| aTab label].
		list   := widget labels:labels for:self.

		self shown ifTrue:[
		    self recomputeList.
		    self invalidate.
		]
	    ]
	]
    ]

    "Modified: / 6.6.1998 / 19:56:26 / cg"
! !

!TabView methodsFor:'accessing tabs'!

tabAt:anIndex
    "get tab at an index or nil
    "
    ^ anIndex notNil ifTrue:[list at:anIndex ifAbsent:nil] ifFalse:[nil]
! !

!TabView methodsFor:'change & update'!

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

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

    (    list isNil
     or:[(idx := list findFirst:[:aTab| aTab model == changedObject]) == 0]
    ) ifTrue:[
        ^ self
    ].

    self shown ifTrue:[
        tab := list at:idx.

        something == #foregroundColor ifTrue:[
            ^ self redrawLabelOfTab:tab
        ].
        
        something == #enabled ifTrue:[
            idx == selection ifTrue:[
                ^ self selection:nil
            ].
            ^ self redrawLabelOfTab:tab
        ].
        tab labelChanged.
        self recomputeList.
        self invalidate.
        self changed:#preferredExtent
    ]

    "Modified: / 6.6.1998 / 19:56:16 / cg"
    "Modified: / 30.3.1999 / 14:28:43 / stefan"
! !

!TabView methodsFor:'drawing'!

paintColor:aColorSymbol
    "set the paint color derived from the symbol used as key into the current
     style sheet to access the color
    "
    self paint:(tabStyle at:aColorSymbol)
!

redraw
    "redraw"

    self redrawX:0 y:0 width:width height:height.

!

redrawLabelOfTab:aTab
    "redraw only the label of the tab
    "
    shown ifTrue:[
	aTab == (self tabAt:selection) ifTrue:[
	    self selectedTab:aTab redrawBlock:[aTab redrawLabel]
	] ifFalse:[
	    aTab redrawLabel
	]
    ].
!

redrawLabels
    "redraw all the labels
    "
    |selectedTab|

    (shown and:[list size ~~ 0]) ifTrue:[
	selectedTab := self tabAt:selection.

	list reverseDo:[:aTab|
	    aTab ~~ selectedTab ifTrue:[
		aTab redrawLabel
	    ] ifFalse:[
		self selectedTab:aTab redrawBlock:[aTab redrawLabel]
	    ]
	]
    ].
!

redrawRawAt:aRawNr
    "redraw raw at a number; all contained tabs are drawn unselected
    "
    list reverseDo:[:aTab|aTab lineNr == aRawNr ifTrue:[aTab redraw:false]].
!

redrawRawAt:aRawNr in:aRectangle
    "redraw raw at a number; all contained tabs are drawn unselected
    "
    list reverseDo:[:aTab|
	aTab lineNr == aRawNr ifTrue:[
	    (aTab intersects:aRectangle) ifTrue:[
		aTab redraw:false
	    ]
	]
    ].
!

redrawSelection
    "redraw current selection
    "
    |tab idx|

    (selection notNil and:[self shown and:[list size ~~ 0]]) ifTrue:[
	tab := list at:selection.
	idx := tab lineNr.
	self selectedTab:tab redrawBlock:[tab redraw:true].
	[(idx := idx - 1) ~~ 0] whileTrue:[self redrawRawAt:idx].
    ].
!

redrawX:x y:y width:w height:h
    "a region must be redrawn
    "
    |rectangle oldSelect prevClipArea|

    self shown ifFalse:[
	^ self
    ].

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

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

    prevClipArea := clipRect.
    clipRect     := nil.
    device setClipX:x y:y width:w height:h in:drawableId gc:gcId.
    rectangle := Rectangle left:x top:y width:w height:h.

    maxRawNr to:1 by:-1 do:[:i| self redrawRawAt:i in:rectangle].

    selection notNil ifTrue:[
	oldSelect := selection.
	selection := nil.
	self setSelection:oldSelect.
    ].

    prevClipArea isNil ifTrue:[device noClipIn:drawableId  gc:gcId]
		      ifFalse:[self clippingRectangle:prevClipArea].

    "Modified: / 18.4.1998 / 16:19:58 / cg"
!

selectedTab:aTab redrawBlock:aRedrawBlock
    "calculate extent of selection and evaluate the block which will
     perform a redraw action
    "
    |tab oldAnc newAnc oldExt newExt expSel expDlt x y|

    tab    := list at:selection.
    oldAnc := tab anchor.
    oldExt := tab extent.
    expSel := tabStyle at:#expandSelection.
    expDlt := expSel x.

    (self isHorizontalDirection) ifTrue:[
	newExt := oldExt + ( expDlt @ 0 ).
	newAnc := oldAnc - ((expDlt//2) @ ((expSel y) negated)).

	(x := newAnc x) < 0 ifTrue:[
	    newExt x:(newExt x + x).
	    newAnc x:0.
	    x := 0.
	].
	(x + newExt x) > (super extent x) ifTrue:[newExt x:((super extent x) - x)].
    ] ifFalse:[
	newExt := oldExt + ( 0 @ expDlt ).
	newAnc := oldAnc - (((expSel y) negated) @ (expDlt//2)).

	(y := newAnc y) < 0 ifTrue:[
	    newExt y:(newExt y + y).
	    newAnc y:0.
	    y := 0.
	].
	(y + newExt y) > (super extent y) ifTrue:[newExt y:((super extent y) - y)].
    ].

    tab anchor:newAnc extent:newExt.
    aRedrawBlock value.
    tab anchor:oldAnc extent:oldExt.

! !

!TabView methodsFor:'event handling'!

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

    (     self isEnabled
     and:[list notNil
     and:[(idx := list findFirst:[:aTab|aTab containsPoint:(x@y)]) ~~ 0]]
    ) ifTrue:[
	self selection:idx
    ].
!

keyPress:aKey x:x y:y
    "selection might change; look for corresponding list entry
    "
    |size index n|

    (self isEnabled and:[(size := list size) > 1]) ifFalse:[
	^ self
    ].

    (aKey == #CursorRight or:[aKey == #CursorDown]) ifTrue:[
	n := selection ? 0.

	(size - 1) timesRepeat:[
	    (n := n + 1) > size ifTrue:[n := 1].

	    (self canSelectTabAtIndex:n) ifTrue:[
		^ self selection:n
	    ]
	].
	^ self
    ].

    (aKey == #CursorLeft or:[aKey == #CursorUp]) ifTrue:[
	n := selection ? size.

	(size - 1) timesRepeat:[
	    (n := n - 1) < 1 ifTrue:[n := size].

	    (self canSelectTabAtIndex:n) ifTrue:[
		^ self selection:n
	    ]
	].
	^ self
    ].

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

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

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

	] whileTrue.

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

    super keyPress:aKey x:x y:y
!

sizeChanged:how
    "size of view changed 
    "
    |extent delta dX dY|

    super sizeChanged:how.

    list size ~~ 0 ifTrue:[
	shown ifTrue:[
	    self invalidate
	].

	extent := super extent.
	delta  := oldExtent - extent.

	((dX := delta x) > 1 or:[dX < -1 
	or:[(dY := delta y) > 1 or:[dY < -1]]]) ifTrue:[
	    oldExtent := extent.
	    self recomputeList.
	    self changed:#preferredExtent.
	].
    ].

    "Modified: / 22.4.1998 / 14:20:31 / cg"
! !

!TabView methodsFor:'initialization'!

destroy
    listHolder notNil ifTrue:[
	listHolder removeDependent:self. 
    ].
    enableChannel notNil ifTrue:[
	enableChannel removeDependent:self. 
    ].
    self  removeListDependencies.
    super destroy.
!

initStyle
    "setup style attributes
    "

    super initStyle.
    self font:(MenuView defaultFont on:device).

    "Created: / 5.9.1998 / 17:36:37 / cg"
    "Modified: / 5.9.1998 / 17:37:38 / cg"
!

initialize
    "setup default attributes
    "
    |widget|

    super initialize.

    self cursor:Cursor hand.

    widget          := TabWidget widgetClass:(self class defaultTabWidget).
    tabStyle        := widget tabStyleOn:self.
    useIndex        := false.
    oneTabPerLine   := false.
    direction       := #top.
    fitLastRow      := true.
    moveSelectedRow := true.
    enabled         := true.
    oldExtent       := 0@0.

    "Modified: 23.10.1997 / 03:28:02 / cg"
! !

!TabView methodsFor:'layout'!

changeRaw:aRawA with:aRawB
    "exchange positions of two raws
    "
    |tabB tabA ancA ancB hrz|

    tabA := list at:(list findFirst:[:aTab|aTab lineNr == aRawA]).
    tabB := list at:(list findFirst:[:aTab|aTab lineNr == aRawB]).
    hrz  := (self isHorizontalDirection).

    hrz ifTrue:[
	ancA := tabA anchor y.
	ancB := tabB anchor y.
    ] ifFalse:[   
	ancA := tabA anchor x.
	ancB := tabB anchor x.
    ].

    list do:[:aTab||ln|
	(ln := aTab lineNr) == aRawB ifTrue:[
	    aTab lineNr:aRawA.
	    hrz ifTrue:[aTab anchor y:ancA]
	       ifFalse:[aTab anchor x:ancA]
	] ifFalse:[
	    ln == aRawA ifTrue:[
		aTab lineNr:aRawB.
		hrz ifTrue:[aTab anchor y:ancB]
		   ifFalse:[aTab anchor x:ancB]
	    ]
	]
    ].

    oneTabPerLine ifFalse:[
	aRawB == maxRawNr ifTrue:[
	    self fitRawAt:aRawA.
	    self unfitLastRaw.
	] ifFalse:[
	    aRawA == maxRawNr ifTrue:[
		self fitRawAt:aRawB.
		self unfitLastRaw.
	    ]
	]
    ]
!

fitRawAt:aRawNr
    "fit raw to view's size
    "
    |last first tab ext org max size|

    (aRawNr ~~ maxRawNr or:[fitLastRow]) ifFalse:[
	^ self
    ].

    last  := list  findLast:[:aTab| aTab lineNr == aRawNr ].
    first := list findFirst:[:aTab| aTab lineNr == aRawNr ].
    tab   := list at:last.
    size  := last - first + 1.
    org   := 0.

    (self isHorizontalDirection) ifTrue:[
	max := super extent x.
	ext := (max - ((tab anchor x) + (tab extent x))) // size.

	ext > 1 ifTrue:[
	    first to:last do:[:i|
		tab := list at:i.
		tab extent x:((tab extent x) + ext).
		tab anchor x:((tab anchor x) + org).
		org := org + ext.
	    ].
	    tab := list at:last.
	].
	tab extent x:(max - tab anchor x).
    ] ifFalse:[
	max := super extent y.
	ext := (max - ((tab anchor y) + (tab extent y))) // size.

	ext > 1 ifTrue:[
	    first to:last do:[:i|
		tab := list at:i.
		tab extent y:((tab extent y) + ext).
		tab anchor y:((tab anchor y) + org).
		org := org + ext.
	    ].
	    tab := list at:last.
	].
	tab extent y:(max - tab anchor y).
    ]
!

recomputeList
    "recompute list
    "
    |maxY x y maxSz ovl|

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

    maxY     := tabStyle at:#maxY.
    ovl      := tabStyle at:#rightCovered.
    maxRawNr := 1.

    (self isHorizontalDirection) ifTrue:[
	maxSz := super extent x.
	x     := 0.
	y     := maxY.
        
	oneTabPerLine ifTrue:[
	    list do:[:aTab|
		aTab lineNr:maxRawNr.
		aTab anchor:x@y extent:(maxSz @ maxY).
		maxRawNr := maxRawNr + 1.
		y := y + maxY.
	    ].
	    ^ self
	].
	list do:[:aTab||eX n|
	    eX := aTab preferredExtentX.
	    n  := eX + x - ovl.

	    (n > maxSz and:[x ~~ 0]) ifTrue:[
		maxRawNr := maxRawNr + 1.
		x := 0.
		y := y  + maxY.
		n := eX - ovl.
	    ].
	    aTab lineNr:maxRawNr.
	    aTab anchor:x@y extent:(eX @ maxY).
	    x := n.
	]
    ] ifFalse:[
	maxSz := super extent y.
	x     := maxY.
	y     := 0.

	oneTabPerLine ifTrue:[
	    list do:[:aTab|
		aTab lineNr:maxRawNr.
		aTab anchor:x@y extent:(maxY @ maxSz).
		maxRawNr := maxRawNr + 1.
		x := x + maxY.
	    ].
	    ^ self
	].
	list do:[:aTab||eY n|
	    eY := aTab preferredExtentX.
	    n  := eY + y - ovl.

	    (n > maxSz and:[y ~~ 0]) ifTrue:[
		maxRawNr := maxRawNr + 1.
		y := 0.
		x := x  + maxY.
		n := eY - ovl.
	    ].
	    aTab lineNr:maxRawNr.
	    aTab anchor:x@y extent:(maxY @ eY).
	    y := n.
	]
    ].
 "/ fit raws to view
    1 to:maxRawNr do:[:aLnNr|self fitRawAt:aLnNr].
!

unfitLastRaw
    "use the preferred extent for all tabs in the last raw
    "
    |last first tab ovl anchor extent pos offset hrz|

    fitLastRow ifTrue:[
	^ self
    ].
    last  := list  findLast:[:aTab| aTab lineNr == maxRawNr ].
    first := list findFirst:[:aTab| aTab lineNr == maxRawNr ].
    ovl   := tabStyle at:#rightCovered.
    pos   := 0.
    hrz   := (self isHorizontalDirection).

    first to:last do:[:i|
	tab := list at:i.
	anchor := tab anchor.
	extent := tab extent.
	offset := tab preferredExtentX.

	hrz ifTrue:[
	    extent x:offset.
	    anchor x:pos
	] ifFalse:[
	    extent y:offset.
	    anchor y:pos.
	].
	tab anchor:anchor extent:extent.
	pos := pos + offset - ovl.
    ].
! !

!TabView methodsFor:'private'!

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

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

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

  ^ list findFirst:[:aTab||l c|
	(    (l := aTab printableLabel) isString
	 and:[((c := l first) == lower or:[c == upper])]
	)
    ] startingAt:anIndex
!

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 ~~ 0 ifTrue:[index] ifFalse:[nil]
!

removeListDependencies
    |model|

    list notNil ifTrue:[
	list do:[:aTab|
	    (model := aTab model) notNil ifTrue:[
		model removeDependent:self
	    ]
	]
    ]
! !

!TabView methodsFor:'queries'!

canSelectTabAtIndex:anIndex
    "returns true if tab at an index is selectable
    "
    (list at:anIndex) isEnabled ifTrue:[
	^ selectConditionBlock isNil ifTrue:[true]
				    ifFalse:[selectConditionBlock value:anIndex]
    ].
    ^ false
!

getBackgroundPaintForTab:aTab
    "returns background color of the tab
    "
    |key|

    key := aTab == (self tabAt:selection) ifFalse:[#unselectedColor]
					   ifTrue:[#selectedColor].

    ^ tabStyle at:key
!

isEnabled
    "returns enabled state
    "
  ^ enabled
!

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

!

isVerticalDirection
    "returns true in case of direction is #left or #right
    "
    ^ (direction == #left or:[direction == #right])

! !

!TabView methodsFor:'selection'!

isTabSelected:aTab
    "returns true if tab is selected
    "
    ^ aTab == (self tabAt:selection)
!

selection
    "return the selection index or nil
    "
    |tab|

    useIndex ifTrue:[
	^ selection ? 0
    ].
    tab := self tabAt:selection.
  ^ tab notNil ifTrue:[tab label] ifFalse:[nil]
!

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

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

selectionHasChanged
    "selection might change; raise notification
    "
    |sel|

    sel := self selection.

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

!

setSelection:something
    "change the selection to index or nil. No notifications are raised
    "
    |newSel lnNr tab last first exp x y w h|

    list size == 0 ifTrue:[^ self].
    newSel := self listIndexOf:something.
    selection == newSel ifTrue:[^ self].

    newSel notNil ifTrue:[
	(self tabAt:newSel) isNil ifTrue:[
	    newSel := nil
	] ifFalse:[
	    (self canSelectTabAtIndex:newSel) ifFalse:[^ self ].
	]
    ].

    self shown ifFalse:[
	selection := newSel.
      ^ self
    ].

    maxRawNr isNil ifTrue:[
	selection := newSel.
	self recomputeList.
	self invalidate.
	^ self.
    ].

    (newSel notNil 
	 and:[moveSelectedRow
	 and:[(lnNr := (list at:newSel) lineNr) > 1]]
    ) ifTrue:[
	self changeRaw:1 with:lnNr.
	selection := 1.                                 "/ force a redraw
    ].

    selection notNil ifTrue:[
	maxRawNr > 1 ifTrue:[
	    self paint:(self viewBackground).           "/ total redraw
	    self clear.
	    selection := nil.
	    maxRawNr to:1 by:-1 do:[:i| self redrawRawAt:i ].
	] ifFalse:[
	    first := 1.

	    (selection ~~ 1 and:[(tabStyle at:#rightCovered) == 0]) ifTrue:[
		first := selection - 1
	    ].

	    (last := selection + 1) > list size ifTrue:[
		last := selection
	    ].
	    exp := (tabStyle at:#expandSelection) x.
	    tab := list at:selection.

	    self isHorizontalDirection ifTrue:[
		(x := tab anchor x - (exp // 2)) < 0 ifTrue:[x := 0].
		w := tab extent x + exp.
		h := super extent y.
		y := 0.
	    ] ifFalse:[
		(y := tab anchor y - (exp // 2)) < 0 ifTrue:[y := 0].
		h := tab extent y + exp.
		w := super extent x.
		x := 0.
	    ].
	    self paint:(self viewBackground).
	    self clearRectangleX:x y:y width:w height:h.

	    last to:first by:-1 do:[:i|
		tab := list at:i.
		tab redraw:false
	    ]
	]
    ].
    selection := newSel.
    self redrawSelection.

    "Modified: / 6.6.1998 / 19:56:45 / cg"
! !

!TabView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.38 1999-03-31 05:53:11 stefan Exp $'
! !