added directions ...
authorca
Wed, 23 Apr 1997 17:17:21 +0200
changeset 369 8f003e44d5ef
parent 368 c99ef22c72f8
child 370 008888fdfc32
added directions ...
TabView.st
TabWidget.st
--- a/TabView.st	Tue Apr 22 19:55:11 1997 +0200
+++ b/TabView.st	Wed Apr 23 17:17:21 1997 +0200
@@ -12,8 +12,8 @@
 
 
 View subclass:#TabView
-	instanceVariableNames:'list listHolder selection action tabStyle sizeChangedNotify
-		useIndex maxLineNr direction'
+	instanceVariableNames:'list listHolder selection action tabStyle sizeChanged useIndex
+		maxRawNr direction fitLastRow moveSelectedRow'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Interactors'
@@ -51,7 +51,7 @@
 
     [see also:]
         NoteBookView
-        SelectionInListView PopUpList ValueHolder
+        SelectionInListView PopUpList ValueHolder TabWidget
 "
 
 !
@@ -223,120 +223,6 @@
     top open.
                                                                                 [exEnd]
 "
-!
-
-test
-    |top sel view x|
-
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:200@350.
-
-
-    sel  := self 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.
-
-"/    sel tabWidget:#Mac.
-    view viewBackground:(sel styleAt:#selectedColor).
-    sel direction:#left.
-
-    sel list:#( 'Button'
-                'Toggle'
-                'Panel'
-                'Scroller'
-                'Claus'
-              ).
-
-    x := sel preferredSizeXorY.
-    sel rightInset:(x negated).
-    view leftInset:x.
-
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
-    top open.
-!
-
-test1
-    |top sel view|
-
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:350@200.
-
-
-    sel  := self origin:5 @ 0.0 corner:1.0 @ 80 in:top.
-    sel rightInset:5.
-"/    sel tabWidget:#Mac.
-    view := View origin:0.0 @ 80 corner:1.0 @ 1.0 in:top.
-    view viewBackground:(sel styleAt:#selectedColor).
-
-    sel list:#( 'Button'
-                'Toggle'
-                'Panel'
-                'Scroller'
-                'Claus'
-              ).
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
-    top open.
-
-!
-
-test3
-    |top sel view y|
-
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:350@200.
-
-
-    view := View origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.
-    sel  := self origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:top.
-"/    sel tabWidget:#Mac.
-    view viewBackground:(sel styleAt:#selectedColor).
-    sel direction:#bottom.
-    sel list:#( 'Button'
-                'Toggle'
-                'Panel'
-                'Scroller'
-                'Claus'
-              ).
-
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
-    top open.
-
-!
-
-test4
-    |top sel view y|
-
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:200@350.
-
-
-    view := View origin:0.0 @ 0.0 corner:0.5 @ 1.0 in:top.
-    sel  := self origin:0.5 @ 0.0 corner:1.0 @ 1.0 in:top.
-
-"/    sel tabWidget:#Mac.
-    view viewBackground:(sel styleAt:#selectedColor).
-    sel direction:#right.
-
-    sel list:#( 'Button'
-                'Toggle'
-                'Panel'
-                'Scroller'
-                'Claus'
-              ).
-
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
-    top open.
 ! !
 
 !TabView class methodsFor:'defaults'!
@@ -345,6 +231,146 @@
     ^ #Window
 ! !
 
+!TabView class methodsFor:'tests'!
+
+testImages
+    |topView view images top bottom left right x y xNeg yNeg last action|
+
+    topView := StandardSystemView new label:'images'; extent:(500 @ 500).
+    view    := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:topView.
+    top     := self origin:0.0 @ 0.0 corner:1.0 @ 0.0 in:topView.
+    bottom  := self origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:topView.
+    left    := self origin:0.0 @ 0.0 corner:0.0 @ 1.0 in:topView.
+    right   := self origin:1.0 @ 0.0 corner:1.0 @ 1.0 in:topView.
+
+    view viewBackground:(top styleAt:#selectedColor).
+
+    top    direction:#top.
+    bottom direction:#bottom.
+    left   direction:#left.
+    right  direction:#right.
+
+    images := #( 'SBrowser' 'FBrowser' 'Debugger' ).
+    images := images collect:[:n| Image fromFile:'bitmaps/' , n , '.xbm'].
+
+    top    list:images.
+    bottom list:images.
+    left   list:images.
+    right  list:images.
+
+    x    := left preferredSizeXorY.
+    xNeg := x negated.
+    y    := top  preferredSizeXorY.
+    yNeg := y negated.
+
+    view  rightInset:x.
+    view   leftInset:x.
+    view bottomInset:y.
+    view    topInset:y.
+
+    last := top.
+    action := [:aTab||wdg|
+        last == aTab ifFalse:[
+            last selection:nil.
+            last := aTab.
+            (aTab tabWidget) == #Mac ifTrue:[aTab tabWidget:#Window]
+                                    ifFalse:[aTab tabWidget:#Mac]
+        ].
+    ].
+
+    top bottomInset:yNeg.
+    top leftInset:x.
+    top rightInset:x.
+    top action:[:d|action value:top].
+
+    bottom topInset:yNeg.
+    bottom leftInset:x.
+    bottom rightInset:x.
+    bottom action:[:d|action value:bottom].
+
+    left rightInset:xNeg.
+    left topInset:y.
+    left bottomInset:y.
+    left action:[:d|action value:left].
+
+    right leftInset:xNeg.
+    right topInset:y.
+    right bottomInset:y.
+    right action:[:d|action value:right].
+
+
+    topView open.
+
+!
+
+testStrings
+    |topView view list top bottom left right x y xNeg yNeg last action|
+
+    topView := StandardSystemView new label:'strings'; extent:(400@400).
+    view    := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:topView.
+    top     := self origin:0.0 @ 0.0 corner:1.0 @ 0.0 in:topView.
+    bottom  := self origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:topView.
+    left    := self origin:0.0 @ 0.0 corner:0.0 @ 1.0 in:topView.
+    right   := self origin:1.0 @ 0.0 corner:1.0 @ 1.0 in:topView.
+
+    view viewBackground:(top styleAt:#selectedColor).
+
+    top    direction:#top.
+    bottom direction:#bottom.
+    left   direction:#left.
+    right  direction:#right.
+
+    list := #( 'foo' 'bar' 'baz' 'gggg' ).
+
+    top    list:list.
+    bottom list:list.
+    left   list:list.
+    right  list:list.
+
+    x    := left preferredSizeXorY.
+    xNeg := x negated.
+    y    := top  preferredSizeXorY.
+    yNeg := y negated.
+
+    view  rightInset:x.
+    view   leftInset:x.
+    view bottomInset:y.
+    view    topInset:y.
+
+    last := top.
+    action := [:aTab||wdg|
+        last == aTab ifFalse:[
+            last selection:nil.
+            last := aTab.
+            (aTab tabWidget) == #Mac ifTrue:[aTab tabWidget:#Window]
+                                    ifFalse:[aTab tabWidget:#Mac]
+        ]
+    ].
+
+    top bottomInset:yNeg.
+    top leftInset:x.
+    top rightInset:x.
+    top action:[:d|action value:top].
+
+    bottom topInset:yNeg.
+    bottom leftInset:x.
+    bottom rightInset:x.
+    bottom action:[:d|action value:bottom].
+
+    left rightInset:xNeg.
+    left topInset:y.
+    left bottomInset:y.
+    left action:[:d|action value:left].
+
+    right leftInset:xNeg.
+    right topInset:y.
+    right bottomInset:y.
+    right action:[:d|action value:right].
+
+    topView open.
+
+! !
+
 !TabView methodsFor:'accessing'!
 
 action:oneArgBlock
@@ -437,10 +463,10 @@
        + ((tabStyle at:#expandSelection) y)
        + (self class viewSpacing).
 
-    (direction == #top or:[direction == #bottom]) ifTrue:[
+    (self isHorizontalDirection) ifTrue:[
         ^ x @ y
     ].
-    ^ y @ x             "/ #left or #right
+    ^ y @ x
 !
 
 preferredSizeXorY
@@ -450,9 +476,9 @@
     |y|
 
     list size == 0 ifFalse:[
-        maxLineNr isNil ifTrue:[self recomputeList].
+        maxRawNr isNil ifTrue:[self recomputeList].
 
-        y := (maxLineNr * (tabStyle at:#maxY))
+        y := (maxRawNr * (tabStyle at:#maxY))
            + ((tabStyle at:#expandSelection) y)
            + (self class viewSpacing).
 
@@ -464,48 +490,83 @@
 !TabView methodsFor:'accessing style'!
 
 direction
-    "returns direction of tabs; on default it's set to #top
-        #top       on top    of a view
-        #bottom    on bottom of a view
-        #left      on left   of a view
-        #right     on right  of a view
+    "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 direction of tabs; on default it's set to #top
-        #top       on top    of a view
-        #bottom    on bottom of a view
-        #left      on left   of a view
-        #right     on right  of a view
+    "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
 
 !
 
+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
+!
+
+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 style
+    "returns the style sheet derived from the current widget class
     "
     ^ tabStyle
 !
 
 styleAt:anIdentifier
-    "returns value for an identifier
+    "returns a specific entry into the widget description. For more information
+     see the specific widget class ( TabWidget ... ).
     "
     ^ tabStyle at:anIdentifier
 !
 
 styleAt:anIdentifier put:something
-    "set value for an identifier
+    "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 tab widget class
+    "returns the current widget class as symbol
     "
     |widget|
 
@@ -515,14 +576,26 @@
 !
 
 tabWidget:aWidget
-    "change tab widget class
+    "change the current widget class. An existing list will be
+     recomputed and redrawn
     "
-    |widget|
+    |widget labels|
+
+    (self tabWidget) ~~ aWidget ifTrue:[
+        widget := TabWidget widgetClass:aWidget.
 
-    list isNil ifTrue:[
-        widget := TabWidget widgetClass:aWidget.
         widget notNil ifTrue:[
-            tabStyle := widget tabStyleOn:self
+            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 redrawFull
+                ]
+            ]
         ]
     ]
 ! !
@@ -530,7 +603,7 @@
 !TabView methodsFor:'change & update'!
 
 update:something with:aParameter from:changedObject
-    "any of my model changed
+    "one of my models changed its value
     "
     changedObject == model ifTrue:[
         self selection:model value
@@ -544,13 +617,14 @@
 !TabView methodsFor:'drawing'!
 
 paintColor:aColorSymbol
-    "set paint to a color from the style identified by its symbol
+    "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)
 !
 
 redrawFull
-    "redraw list
+    "full redraw
     "
     |oldSelect|
 
@@ -558,7 +632,7 @@
         self paint:(self viewBackground).
         self clear.
 
-        maxLineNr to:1 by:-1 do:[:i|self redrawLineUnselected:i].
+        maxRawNr to:1 by:-1 do:[:i|self redrawRawAt:i].
         selection notNil ifTrue:[
             oldSelect := selection.
             selection := nil.
@@ -567,10 +641,10 @@
     ]
 !
 
-redrawLineUnselected:aLineNr
-    "redraw one line
+redrawRawAt:aRawNr
+    "redraw raw at a number; all contained tabs are drawn unselected
     "
-    list do:[:aTab|aTab lineNr == aLineNr ifTrue:[aTab redraw:false]]
+    list do:[:aTab|aTab lineNr == aRawNr ifTrue:[aTab redraw:false]]
 !
 
 redrawSelection
@@ -590,7 +664,7 @@
     expSel := tabStyle at:#expandSelection.
     expDlt := expSel x.
 
-    (direction == #top or:[direction == #bottom]) ifTrue:[
+    (self isHorizontalDirection) ifTrue:[
         newExt := oldExt + ( expDlt @ 0 ).
         newAnc := oldAnc - ((expDlt//2) @ ((expSel y) negated)).
 
@@ -599,7 +673,7 @@
             newAnc x:0.
             x := 0.
         ].
-        (x + newExt x) > (self extent x) ifTrue:[newExt x:((self extent x) - x)].
+        (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)).
@@ -609,7 +683,7 @@
             newAnc y:0.
             y := 0.
         ].
-        (y + newExt y) > (self extent y) ifTrue:[newExt y:((self extent y) - y)].
+        (y + newExt y) > (super extent y) ifTrue:[newExt y:((super extent y) - y)].
     ].
 
     tab anchor:newAnc extent:newExt.
@@ -617,7 +691,7 @@
     tab anchor:oldAnc extent:oldExt.
 
     size := tab lineNr.
-    [(size := size - 1) ~~ 0] whileTrue:[self redrawLineUnselected:size].
+    [(size := size - 1) ~~ 0] whileTrue:[self redrawRawAt:size].
 
 !
 
@@ -630,7 +704,7 @@
 !TabView methodsFor:'event handling'!
 
 buttonPress:button x:x y:y
-    "a button is pressed; find tab under point at set selection
+    "a button is pressed; find tab under point and set the selection
     "
     list notNil ifTrue:[
         list keysAndValuesDo:[:aKey :aTab|
@@ -648,14 +722,14 @@
     |size newSel|
 
     (size := list size) ~~ 0 ifTrue:[
-        aKey == #CursorLeft ifTrue:[
+        (aKey == #CursorLeft or:[aKey == #CursorUp]) ifTrue:[
             (selection isNil or:[selection == size]) ifTrue:[
                 newSel := 1
             ] ifFalse:[
                 newSel := (selection + 1)
             ]
         ] ifFalse:[
-            aKey == #CursorRight ifTrue:[
+            (aKey == #CursorRight or:[aKey == #CursorDown]) ifTrue:[
                 (selection isNil or:[selection == 1]) ifTrue:[
                     newSel := size
                 ] ifFalse:[
@@ -677,10 +751,10 @@
     list notNil ifTrue:[
         self recomputeList.
 
-        sizeChangedNotify ifFalse:[
-            sizeChangedNotify := true.
+        sizeChanged ifFalse:[
+            sizeChanged := true.
             self changed:#preferredExtent.
-            sizeChangedNotify := false.
+            sizeChanged := false.
         ]
     ].
 
@@ -694,180 +768,207 @@
     |widget|
 
     super initialize.
-    widget    := TabWidget widgetClass:(self class defaultTabWidget).
-    tabStyle  := widget tabStyleOn:self.
-    useIndex  := false.
-    direction := #top.
-    sizeChangedNotify := false.
+
+    widget          := TabWidget widgetClass:(self class defaultTabWidget).
+    tabStyle        := widget tabStyleOn:self.
+    useIndex        := false.
+    direction       := #top.
+    sizeChanged     := false.
+    fitLastRow      := true.
+    moveSelectedRow := true.
 ! !
 
 !TabView methodsFor:'layout'!
 
+changeRaw:aRawA with:aRawB
+    "exchange positions of two raws
+    "
+    |tabB tabA ancA ancB hrz|
+
+    tabA := list at:(list findLast:[:aTab|aTab lineNr == aRawA]).
+    tabB := list at:(list findLast:[: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]
+            ]
+        ]
+    ].
+
+    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:first.
+    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:[
+            last to:first by:-1 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:first.
+        ].
+        tab extent x:(max - tab anchor x).
+    ] ifFalse:[
+        max := super extent y.
+        ext := (max - ((tab anchor y) + (tab extent y))) // size.
+
+        ext > 1 ifTrue:[
+            last to:first by:-1 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:first.
+        ].
+        tab extent y:(max - tab anchor y).
+    ]
+!
+
 recomputeList
-    "recompute tabs
+    "recompute list
     "
-    |tab extY size x y width ovl|
+    |tab maxY x y maxSz ovl|
 
     list size ~~ 0 ifTrue:[
-        (direction == #top or:[direction == #bottom]) ifTrue:[
-            self recomputeListHorizontal
+        maxY     := tabStyle at:#maxY.
+        ovl      := tabStyle at:#rightCovered.
+        maxRawNr := 1.
+
+        (self isHorizontalDirection) ifTrue:[
+            maxSz := super extent x.
+            x     := 0.
+            y     := maxY.
+
+            list reverseDo:[:aTab||eX n|
+                eX := aTab preferredExtentX.
+                n  := eX + x - ovl.
+
+                n > maxSz 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:[
-            self recomputeListVertical
-        ]
+            maxSz := super extent y.
+            x     := maxY.
+            y     := 0.
+
+            list reverseDo:[:aTab||eY n|
+                eY := aTab preferredExtentX.
+                n  := eY + y - ovl.
+
+                n > maxSz 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].
     ].
 !
 
-recomputeListHorizontal
-    "recompute horizontal tabs
+unfitLastRaw
+    "use the preferred extent for all tabs in the last raw
     "
-    |tab extY size x y width ovl|
+    |last first tab ovl anchor extent pos offset hrz|
 
-    size  := list size.
-    extY  := tabStyle at:#maxY.
+    fitLastRow ifTrue:[^ self].
+
+    last  := list  findLast:[:aTab| aTab lineNr == maxRawNr ].
+    first := list findFirst:[:aTab| aTab lineNr == maxRawNr ].
     ovl   := tabStyle at:#rightCovered.
-    width := self extent x.
-    x     := 0.
-    y     := extY.
-    maxLineNr := 1.
+    pos   := 0.
+    hrz   := (self isHorizontalDirection).
 
-    list reverseDo:[:aTab||eX n|
-        eX := aTab preferredExtentX.
-        n := eX + x - ovl.
+    last to:first by:-1 do:[:i|
+        tab := list at:i.
+        anchor := tab anchor.
+        extent := tab extent.
+        offset := tab preferredExtentX.
 
-        n > width ifTrue:[
-            maxLineNr := maxLineNr + 1.
-            x := 0.
-            y := y  + extY.
-            n := eX - ovl.
+        hrz ifTrue:[
+            extent x:offset.
+            anchor x:pos
+        ] ifFalse:[
+            extent y:offset.
+            anchor y:pos.
         ].
-        aTab lineNr:maxLineNr.
-        aTab anchor:x@y extent:(eX @ extY).
-        x := n.
+        tab anchor:anchor extent:extent.
+        pos := pos + offset - ovl.
     ].
-
-    "/ fit lines
-    1 to:maxLineNr do:[:aLnNr|
-        |extX orgX last|
+! !
 
-        last := 1 + (list findLast:[:aTab|aTab lineNr ~~ aLnNr] startingAt:size).
-        tab  := list at:last.
-        extX := width - ((tab anchor x) + (tab extent x)).
-        extX := extX // (size - last + 1).
-        orgX := 0.
+!TabView methodsFor:'queries'!
 
-        extX > 1 ifTrue:[
-            size to:last by:-1 do:[:i|
-                tab := list at:i.
-                tab extent x:((tab extent x) + extX).
-                tab anchor x:((tab anchor x) + orgX).
-                orgX := orgX + extX.
-            ]
-        ].
-        tab := list at:last.
-        tab extent x:(width - tab anchor x).
-        size := last - 1.
-    ]
+isHorizontalDirection
+    "returns true in case of direction is #top or #bottom
+    "
+    ^ (direction == #top or:[direction == #bottom])
+
 !
 
-recomputeListVertical
-    "recompute vertical tabs
+isVerticalDirection
+    "returns true in case of direction is #left or #right
     "
-    |tab extX size x y height ovl|
-
-    size   := list size.
-    extX   := tabStyle at:#maxY.
-    ovl    := tabStyle at:#rightCovered.
-    height := self corner y.
-    x      := extX.
-    y      := 0.
-
-    maxLineNr := 1.
-
-    list reverseDo:[:aTab||eY n|
-        eY := aTab preferredExtentX.
-        n  := eY + y - ovl.
-
-        n > height ifTrue:[
-            maxLineNr := maxLineNr + 1.
-            y := 0.
-            x := x  + extX.
-            n := eY - ovl.
-        ].
-        aTab lineNr:maxLineNr.
-        aTab anchor:x@y extent:(extX @ eY).
-        y := n.
-    ].
-
-    "/ fit lines
-    1 to:maxLineNr do:[:aLnNr|
-        |extY orgY last|
-
-        last := 1 + (list findLast:[:aTab|aTab lineNr ~~ aLnNr] startingAt:size).
-        tab  := list at:last.
-        extY := height - ((tab anchor y) + (tab extent y)).
-        extY := extY // (size - last + 1).
-        orgY := 0.
-
-        extY > 1 ifTrue:[
-            size to:last by:-1 do:[:i|
-                tab := list at:i.
-                tab extent y:((tab extent y) + extY).
-                tab anchor y:((tab anchor y) + orgY).
-                orgY := orgY + extY.
-            ]
-        ].
-        tab := list at:last.
-        tab extent y:(height - tab anchor y).
-        size := last - 1.
-    ]
+    ^ (direction == #left or:[direction == #right])
 
 ! !
 
 !TabView methodsFor:'selection'!
 
-lineToBottomWithNumber:aLineNr
-    "exchange the first line with the received line number
-    "
-    |tabN tab1 orgY a1 aN|
-
-    tab1 := list at:(list findLast:[:aTab|aTab lineNr == 1]).
-    tabN := list at:(list findLast:[:aTab|aTab lineNr == aLineNr]).
-
-    (direction == #top or:[direction == #bottom]) ifTrue:[
-        a1 := tab1 anchor y.
-        aN := tabN anchor y.
-
-        list do:[:aTab||ln|
-            ln := aTab lineNr.
-            ln == 1 ifTrue:[
-                aTab anchor y:aN.
-                aTab lineNr:aLineNr.
-            ] ifFalse:[
-                ln == aLineNr ifTrue:[
-                    aTab anchor y:a1.
-                    aTab lineNr:1.
-                ]
-            ]
-        ]
-    ] ifFalse:[
-        a1 := tab1 anchor x.
-        aN := tabN anchor x.
-
-        list do:[:aTab||ln|
-            ln := aTab lineNr.
-            ln == 1 ifTrue:[
-                aTab anchor x:aN.
-                aTab lineNr:aLineNr.
-            ] ifFalse:[
-                ln == aLineNr ifTrue:[
-                    aTab anchor x:a1.
-                    aTab lineNr:1.
-                ]
-            ]
-        ]
-    ]
-!
-
 selection
     "return the selection index or nil
     "
@@ -923,10 +1024,10 @@
     ].
 
     (     index notNil
-     and:[(lnNr := (list at:index) lineNr) > 1
-     and:[(tabStyle at:#selectionAtBottom)]]
+     and:[moveSelectedRow
+     and:[(lnNr := (list at:index) lineNr) > 1]]
     ) ifTrue:[
-        self lineToBottomWithNumber:lnNr.
+        self changeRaw:1 with:lnNr.
         selection := 1.
     ].
 
@@ -941,5 +1042,5 @@
 !TabView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.6 1997-04-22 16:56:16 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.7 1997-04-23 15:17:10 ca Exp $'
 ! !
--- a/TabWidget.st	Tue Apr 22 19:55:11 1997 +0200
+++ b/TabWidget.st	Wed Apr 23 17:17:21 1997 +0200
@@ -19,14 +19,14 @@
 	category:'Views-Interactors'
 !
 
-TabWidget subclass:#Mac
+TabWidget subclass:#Window
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:TabWidget
 !
 
-TabWidget subclass:#Window
+TabWidget subclass:#Mac
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -97,6 +97,11 @@
     style at:#labelAnchor put:( lftIns @ (topIns +level) ).
 
     self validateDimensions:style.
+    maxY := style at:#maxY.
+    maxX := style at:#maxX.
+
+ "/ caused by vertical layout for images
+    maxX < maxY ifTrue:[style at:#maxX put:maxY].
   ^ list
 !
 
@@ -133,7 +138,6 @@
     style at:#unselectedColor    put:unselectedColor.
     style at:#selectedColor      put:selectedColor.
     style at:#labelColor         put:(Color black).
-    style at:#selectionAtBottom  put:true.  "/ true: selected tab always moved to bottom
 
     style at:#expandSelection    put:0@0.    "/ expand selection extent x y when raised
     style at:#tabLevel           put:0.      "/ level
@@ -257,6 +261,65 @@
 
 !TabWidget methodsFor:'drawing'!
 
+redraw:isSelected
+    "redraw tab
+    "
+    |direction origin anchor x y|
+
+    direction := tabView direction.
+    anchor    := tabView styleAt:#labelAnchor.
+    origin    := self computeOrigin.
+
+    (direction == #top or:[direction == #bottom]) ifTrue:[
+        y := origin y.
+        x := origin x + anchor x.
+
+        direction == #top ifTrue:[
+            self redrawAtTop:isSelected.
+            y := y + anchor y.
+        ] ifFalse:[
+            self redrawAtBottom:isSelected.
+            y := y - anchor y - (label heightOn:tabView).
+        ].
+        label isString ifTrue:[y := y + tabView font ascent].
+        tabView paintColor:#labelColor.
+    ] ifFalse:[
+        direction == #right ifTrue:[
+            self redrawAtRight:isSelected.
+            x := origin x - anchor y - (label widthOn:tabView).
+        ] ifFalse:[
+            self redrawAtLeft:isSelected.
+            x := origin x + anchor y.
+        ].
+        tabView paintColor:#labelColor.
+        y := origin y + anchor x.
+
+        label isString ifTrue:[
+            direction == #right ifTrue:[
+                x := x + tabView font ascent.
+            ] ifFalse:[
+                x := x + tabView font descent.
+            ].
+            tabView paintColor:#labelColor.
+            tabView displayString:label x:x y:y angle:90.
+          ^ self.
+        ].
+    ].
+    label displayOn:tabView x:x y:y.
+
+! !
+
+!TabWidget methodsFor:'initialization'!
+
+label:aLabel for:aTabView
+    "initialize attributes
+    "
+    tabView := aTabView.
+    label   := aLabel.
+! !
+
+!TabWidget methodsFor:'private'!
+
 computeCorner
     "compute corner
     "
@@ -286,50 +349,6 @@
     d == #bottom ifTrue:[ ^ anchor ].
 
     self error
-!
-
-redraw:isSelected
-    "full redraw
-    "
-    |x y p a d|
-
-    d := tabView direction.
-
-    (d == #top or:[d == #bottom]) ifTrue:[
-        p := self computeOrigin.
-        a := tabView styleAt:#labelAnchor.
-        x := p x + a x.
-        
-        d == #top ifTrue:[
-            self redrawAtTop:isSelected.
-            y := p y + a y.
-        ] ifFalse:[
-            self redrawAtBottom:isSelected.
-            y := p y - (tabView styleAt:#labelBottomInset)
-                     - (tabView styleAt:#tabLevel)
-                     - (label heightOn:tabView).
-        ].
-        tabView paintColor:#labelColor.
-        label isString ifTrue:[y := y + tabView font ascent].
-        label displayOn:tabView x:x y:y.
-      ^ self
-    ].
-
-    d == #right ifTrue:[
-        ^ self redrawAtRight:isSelected
-    ].
-    d == #left ifTrue:[
-        ^ self redrawAtLeft:isSelected
-    ].
-! !
-
-!TabWidget methodsFor:'initialization'!
-
-label:aLabel for:aTabView
-    "initialize attributes
-    "
-    tabView := aTabView.
-    label   := aLabel.
 ! !
 
 !TabWidget methodsFor:'queries'!
@@ -363,220 +382,6 @@
     ^ false
 ! !
 
-!TabWidget::Mac class methodsFor:'calculate dimensions'!
-
-validateDimensions:aStyle
-    "validate dimensions for a style; could be redifined
-    "
-    |maxY maxX anchor lftIns|
-
-    maxY   := aStyle at:#maxY.
-    maxX   := (aStyle at:#maxX) - (aStyle at:#labelLeftInset).
-    anchor := aStyle at:#labelAnchor.
-    lftIns := maxY // 2.
-
-    anchor x:lftIns.
-
-    aStyle at:#maxX         put:(maxX + lftIns + maxY).
-    aStyle at:#rightCovered put:(maxY // 2).
-! !
-
-!TabWidget::Mac methodsFor:'drawing'!
-
-redrawAtBottom:isSelected
-    "redraw tab at bottom of view
-    "
-    |origin corner polygon x y x1 eX eY color shadowColor lightColor|
-
-    isSelected ifFalse:[
-        color       := tabView styleAt:#unselectedColor.
-        shadowColor := tabView styleAt:#shadowColorUnselected.
-        lightColor  := tabView styleAt:#lightColorUnselected.
-    ] ifTrue:[
-        color       := tabView styleAt:#selectedColor.
-        shadowColor := tabView styleAt:#shadowColorSelected.
-        lightColor  := tabView styleAt:#lightColorSelected.
-    ].
-
-    polygon := Array new:5.
-    origin  := self computeOrigin.
-    corner  := self computeCorner.
-
-    x  := origin x.
-    y  := origin y.
-    eX := corner x.
-    eY := corner y.
-    x1 := eX - (tabView styleAt:#maxY).
-
-    polygon at:1 put:(Point x:x      y:eY).
-    polygon at:2 put:(Point x:x      y:y).
-    polygon at:3 put:(Point x:x1     y:y).
-    polygon at:4 put:(Point x:eX     y:(y-extent y)).
-    polygon at:5 put:(Point x:eX     y:eY).
-
-    tabView paint:color.
-    tabView fillPolygon:polygon.
-
-    tabView paint:lightColor.
-    tabView displayLineFromX:x+1 y:eY toX:x+1 y:y-1.
-    tabView displayLineFromX:x+1 y:y-1 toX:x1-1 y:y-1.
-    tabView displayLineFromX:x+1 y:y-1 toX:x1+1 y:y-1.
-
-    tabView paintColor:#labelColor.
-    tabView displayPolygon:polygon.
-
-    isSelected ifFalse:[
-        tabView paint:shadowColor.
-        tabView displayLineFromX:x y:eY toX:eX y:eY.
-    ]
-
-
-!
-
-redrawAtLeft:isSelected
-    "redraw tab at left of view
-    "
-    |origin corner polygon x y y1 eX eY color shadowColor lightColor|
-
-    isSelected ifFalse:[
-        color       := tabView styleAt:#unselectedColor.
-        shadowColor := tabView styleAt:#shadowColorUnselected.
-        lightColor  := tabView styleAt:#lightColorUnselected.
-    ] ifTrue:[
-        color       := tabView styleAt:#selectedColor.
-        shadowColor := tabView styleAt:#shadowColorSelected.
-        lightColor  := tabView styleAt:#lightColorSelected.
-    ].
-
-    polygon := Array new:5.
-    origin  := self computeOrigin.
-    corner  := self computeCorner.
-
-    x  := origin x.
-    y  := origin y.
-    eX := corner x.
-    eY := corner y.
-    y1 := eY - (tabView styleAt:#maxY).
-
-    polygon at:1 put:(Point x:eX           y:y).
-    polygon at:2 put:(Point x:x            y:y).
-    polygon at:3 put:(Point x:x            y:y1).
-    polygon at:4 put:(Point x:(x+extent x) y:eY).
-    polygon at:5 put:(Point x:eX           y:eY).
-
-    tabView paint:color.
-    tabView fillPolygon:polygon.
-
-    tabView paint:lightColor.
-    tabView displayLineFromX:eX  y:y+1 toX:x+2  y:y+1.
-    tabView displayLineFromX:x+1 y:y+1 toX:x+1  y:y1+1.
-
-    tabView paintColor:#labelColor.
-    tabView displayPolygon:polygon.
-"
-    isSelected ifFalse:[
-        tabView paint:shadowColor.
-        tabView displayLineFromX:0 y:y toX:0 y:eY.
-    ]
-"
-!
-
-redrawAtRight:isSelected
-    "redraw tab at right of view
-    "
-    |origin corner polygon x y y1 eY color shadowColor lightColor|
-
-    isSelected ifFalse:[
-        color       := tabView styleAt:#unselectedColor.
-        shadowColor := tabView styleAt:#shadowColorUnselected.
-        lightColor  := tabView styleAt:#lightColorUnselected.
-    ] ifTrue:[
-        color       := tabView styleAt:#selectedColor.
-        shadowColor := tabView styleAt:#shadowColorSelected.
-        lightColor  := tabView styleAt:#lightColorSelected.
-    ].
-
-    polygon := Array new:5.
-    origin  := self computeOrigin.
-    corner  := self computeCorner.
-
-    x  := origin x.
-    y  := origin y.
-    eY := corner y.
-    y1 := eY - (tabView styleAt:#maxY).
-
-    polygon at:1 put:(Point x:0            y:y).
-    polygon at:2 put:(Point x:x            y:y).
-    polygon at:3 put:(Point x:x            y:y1).
-    polygon at:4 put:(Point x:(x-extent x) y:eY).
-    polygon at:5 put:(Point x:0            y:eY).
-
-    tabView paint:color.
-    tabView fillPolygon:polygon.
-
-    tabView paint:lightColor.
-    tabView displayLineFromX:0   y:y+1 toX:x-1  y:y+1.
-    tabView displayLineFromX:x-1 y:y+1 toX:x-1  y:y1+1.
-
-    tabView paintColor:#labelColor.
-    tabView displayPolygon:polygon.
-
-    isSelected ifFalse:[
-        tabView paint:shadowColor.
-        tabView displayLineFromX:0 y:y toX:0 y:eY.
-    ]
-
-!
-
-redrawAtTop:isSelected
-    "redraw tab at top of view
-    "
-    |origin corner polygon x y x1 eX eY color shadowColor lightColor|
-
-    isSelected ifFalse:[
-        color       := tabView styleAt:#unselectedColor.
-        shadowColor := tabView styleAt:#shadowColorUnselected.
-        lightColor  := tabView styleAt:#lightColorUnselected.
-    ] ifTrue:[
-        color       := tabView styleAt:#selectedColor.
-        shadowColor := tabView styleAt:#shadowColorSelected.
-        lightColor  := tabView styleAt:#lightColorSelected.
-    ].
-
-    polygon := Array new:5.
-    origin  := self computeOrigin.
-    corner  := self computeCorner.
-
-    x  := origin x.
-    y  := origin y.
-    eX := corner x - 1.
-    eY := corner y.
-    x1 := eX - (tabView styleAt:#maxY).
-
-    polygon at:1 put:(Point x:x      y:eY).
-    polygon at:2 put:(Point x:x      y:y).
-    polygon at:3 put:(Point x:x1     y:y).
-    polygon at:4 put:(Point x:eX     y:(y+extent y)).
-    polygon at:5 put:(Point x:eX     y:eY).
-
-    tabView paint:color.
-    tabView fillPolygon:polygon.
-
-    tabView paint:lightColor.
-    tabView displayLineFromX:x+1 y:eY toX:x+1 y:y+1.
-    tabView displayLineFromX:x+1 y:y+1 toX:x1+1 y:y+1.
-
-    tabView paintColor:#labelColor.
-    tabView displayPolygon:polygon.
-
-    isSelected ifFalse:[
-        tabView paint:shadowColor.
-        tabView displayLineFromX:x y:eY-1 toX:eX y:eY-1.
-    ]
-
-
-! !
-
 !TabWidget::Window class methodsFor:'accessing'!
 
 tabStyleOn:aView
@@ -866,8 +671,224 @@
     ].
 ! !
 
+!TabWidget::Mac class methodsFor:'accessing'!
+
+tabStyleOn:aView
+    |style|
+
+    style := super tabStyleOn:aView.
+    style at:#tabLevel put:2.
+  ^ style.
+! !
+
+!TabWidget::Mac class methodsFor:'calculate dimensions'!
+
+validateDimensions:aStyle
+    "validate dimensions for a style; could be redifined
+    "
+    |maxY maxX anchor lftIns|
+
+    maxY   := aStyle at:#maxY.
+    maxX   := (aStyle at:#maxX) - (aStyle at:#labelLeftInset).
+    anchor := aStyle at:#labelAnchor.
+    lftIns := maxY // 2.
+
+    anchor x:lftIns.
+
+    aStyle at:#maxX         put:(maxX + lftIns + maxY).
+    aStyle at:#rightCovered put:(maxY // 2).
+! !
+
+!TabWidget::Mac methodsFor:'drawing'!
+
+redrawAtBottom:isSelected
+    "redraw tab at bottom of view
+    "
+    |origin corner level polygon x y x1 eX eY shadowColor lightColor|
+
+    isSelected ifFalse:[
+        lightColor  := tabView styleAt:#lightColorUnselected.
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        tabView paint:(tabView styleAt:#unselectedColor).
+    ] ifTrue:[
+        lightColor  := tabView styleAt:#lightColorSelected.
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        tabView paint:(tabView styleAt:#selectedColor).
+    ].
+    polygon := Array new:5.
+    origin  := self computeOrigin.
+    corner  := self computeCorner.
+    level   := tabView styleAt:#tabLevel.
+
+    x  := origin x.
+    y  := origin y.
+    eX := corner x.
+    eY := corner y.
+    x1 := eX - (tabView styleAt:#maxY).
+
+    polygon at:1 put:(Point x:x  y:eY).
+    polygon at:2 put:(Point x:x  y:y).
+    polygon at:3 put:(Point x:x1 y:y).
+    polygon at:4 put:(Point x:eX y:(y-extent y)).
+    polygon at:5 put:(Point x:eX y:eY).
+
+    tabView fillPolygon:polygon.
+    tabView paint:lightColor.
+
+    1 to:level do:[:i|
+        tabView displayLineFromX:x+1 y:y-i toX:x1+i y:y-i.
+        tabView displayLineFromX:x+i y:y-1 toX:x+i  y:1.
+    ].
+    tabView paint:shadowColor.
+    tabView displayPolygon:polygon.
+
+    isSelected ifFalse:[
+        tabView displayLineFromX:x y:eY toX:eX y:eY.
+    ]
+!
+
+redrawAtLeft:isSelected
+    "redraw tab at left of view
+    "
+    |origin corner polygon level x y y1 eX eY shadowColor lightColor|
+
+    isSelected ifFalse:[
+        lightColor  := tabView styleAt:#lightColorUnselected.
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        tabView paint:(tabView styleAt:#unselectedColor).
+    ] ifTrue:[
+        lightColor  := tabView styleAt:#lightColorSelected.
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        tabView paint:(tabView styleAt:#selectedColor).
+    ].
+    polygon := Array new:5.
+    origin  := self computeOrigin.
+    corner  := self computeCorner.
+    level   := tabView styleAt:#tabLevel.
+
+    x  := origin x.
+    y  := origin y.
+    eX := corner x.
+    eY := corner y.
+    y1 := eY - (tabView styleAt:#maxY).
+
+    polygon at:1 put:(Point x:eX           y:y).
+    polygon at:2 put:(Point x:x            y:y).
+    polygon at:3 put:(Point x:x            y:y1).
+    polygon at:4 put:(Point x:(x+extent x) y:eY).
+    polygon at:5 put:(Point x:eX           y:eY).
+
+    tabView fillPolygon:polygon.
+    tabView paint:lightColor.
+
+    1 to:level do:[:i|
+        tabView displayLineFromX:eX  y:y+i toX:x+2  y:y+i.
+        tabView displayLineFromX:x+i y:y+1 toX:x+i  y:y1+i.
+    ].
+    tabView paint:shadowColor.
+    tabView displayPolygon:polygon.
+
+    isSelected ifFalse:[
+        tabView displayLineFromX:eX-1 y:y toX:eX-1 y:eY.
+    ]
+!
+
+redrawAtRight:isSelected
+    "redraw tab at right of view
+    "
+    |origin corner level polygon x y y1 eY shadowColor lightColor|
+
+    isSelected ifFalse:[
+        lightColor  := tabView styleAt:#lightColorUnselected.
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        tabView paint:(tabView styleAt:#unselectedColor).
+    ] ifTrue:[
+        lightColor  := tabView styleAt:#lightColorSelected.
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        tabView paint:(tabView styleAt:#selectedColor).
+    ].
+    polygon := Array new:5.
+    origin  := self computeOrigin.
+    corner  := self computeCorner.
+    level   := tabView styleAt:#tabLevel.
+
+    x  := origin x.
+    y  := origin y.
+    eY := corner y.
+    y1 := eY - (tabView styleAt:#maxY).
+
+    polygon at:1 put:(Point x:0            y:y).
+    polygon at:2 put:(Point x:x            y:y).
+    polygon at:3 put:(Point x:x            y:y1).
+    polygon at:4 put:(Point x:(x-extent x) y:eY).
+    polygon at:5 put:(Point x:0            y:eY).
+
+    tabView fillPolygon:polygon.
+    tabView paint:lightColor.
+
+    1 to:level do:[:i|
+        tabView displayLineFromX:0   y:y+i toX:x-1  y:y+i.
+        tabView displayLineFromX:x-i y:y+1 toX:x-i  y:y1+i.
+    ].
+    tabView paint:shadowColor.
+    tabView displayPolygon:polygon.
+
+    isSelected ifFalse:[
+        tabView displayLineFromX:0 y:y toX:0 y:eY.
+    ]
+
+!
+
+redrawAtTop:isSelected
+    "redraw tab at top of view
+    "
+    |origin corner level polygon x y x1 eX eY color shadowColor lightColor|
+
+    isSelected ifFalse:[
+        lightColor  := tabView styleAt:#lightColorUnselected.
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        tabView paint:(tabView styleAt:#unselectedColor).
+    ] ifTrue:[
+        lightColor  := tabView styleAt:#lightColorSelected.
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        tabView paint:(tabView styleAt:#selectedColor).
+    ].
+    polygon := Array new:5.
+    origin  := self computeOrigin.
+    corner  := self computeCorner.
+    level   := tabView styleAt:#tabLevel.
+
+    x  := origin x.
+    y  := origin y.
+    eX := corner x - 1.
+    eY := corner y.
+    x1 := eX - (tabView styleAt:#maxY).
+
+    polygon at:1 put:(Point x:x  y:eY).
+    polygon at:2 put:(Point x:x  y:y).
+    polygon at:3 put:(Point x:x1 y:y).
+    polygon at:4 put:(Point x:eX y:(y+extent y)).
+    polygon at:5 put:(Point x:eX y:eY).
+
+    tabView fillPolygon:polygon.
+    tabView paint:lightColor.
+
+    1 to:level do:[:i|
+        tabView displayLineFromX:x+i y:eY  toX:x+i  y:y+1.
+        tabView displayLineFromX:x+1 y:y+i toX:x1+i y:y+i.
+    ].
+    tabView paint:shadowColor.
+    tabView displayPolygon:polygon.
+
+    isSelected ifFalse:[
+        tabView displayLineFromX:x y:eY-1 toX:eX y:eY-1.
+    ]
+
+
+! !
+
 !TabWidget class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TabWidget.st,v 1.4 1997-04-22 16:56:29 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabWidget.st,v 1.5 1997-04-23 15:17:21 ca Exp $'
 ! !