tabs at top, bottom, left and right
authorca
Tue, 22 Apr 1997 18:56:29 +0200
changeset 367 cff1a140978f
parent 366 34e1870524f1
child 368 c99ef22c72f8
tabs at top, bottom, left and right
TabView.st
TabWidget.st
--- a/TabView.st	Sat Apr 19 12:23:56 1997 +0200
+++ b/TabView.st	Tue Apr 22 18:56:29 1997 +0200
@@ -12,8 +12,8 @@
 
 
 View subclass:#TabView
-	instanceVariableNames:'leftInset list listHolder selection action tabStyle
-		sizeChangedNotify useIndex selectionToFirstLine maxLineNr'
+	instanceVariableNames:'list listHolder selection action tabStyle sizeChangedNotify
+		useIndex maxLineNr direction'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Interactors'
@@ -58,100 +58,141 @@
 
 examples
 "
+    tabs at top of a view
                                                                                 [exBegin]                                      
-    |top sel view|
+    |top tab view inset|
+
+    top := StandardSystemView new label:'tabs at top'; extent:250@100.
+    tab  := self 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]
 
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:300@200.
+    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  := self origin:0.0 @ 1.0 corner:1.0 @ 1.0 in:top.
 
+    view viewBackground:(tab styleAt:#selectedColor).
+    tab direction:#bottom.
+    tab tabWidget:#Mac.
 
-    sel  := self origin:0.0 @ 0.0 corner:1.0 @ 0.7 in:top.
-    view := View origin:0.0 @ 0.7 corner:1.0 @ 1.0 in:top.
-    view viewBackground:(sel styleAt:#selectedColor).
+    tab list:#( 'Foo' 'Bar' 'Baz' ).
+    inset := tab preferredSizeXorY.
+    tab  topInset:(inset negated).
+    view bottomInset:inset.
+    tab action:[:aName|Transcript showCR:aName].
+    top open.
+                                                                                [exEnd]
 
-    sel list:#( 'Button'
-                'Toggle'
-                'Panel'
-                'Text'
-                'View'
-                'Combo View'
-                'Menu'
-                'Scroller'
-              ).
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
+    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  := self 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]                                      
-
+                                                                                [exEnd]
 
-
+    tabs at left of a view
                                                                                 [exBegin]                                      
-    |top sel view y|
+    |top tab view inset|
+
+    top := StandardSystemView new label:'tabs at left'; extent:100@250.
+    tab  := 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.
 
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:450@300.
+    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]
 
-    y    := 150.
-    sel  := self origin:0.0 @ 0.0 corner:1.0 @ y in:top.
-    sel horizontalInset:10.
-    view := NoteBookFrameView origin:0.0 @ y  corner:1.0 @ 1.0 in:top.
+    changing default style( see TabWidget class ); useing index
+                                                                                [exBegin]                                      
+    |top tab view|
+
+    top := StandardSystemView new label:'example'; extent:450@300.
+    tab := self 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').
 
-    sel styleAt:#selectedColor    put:(view viewBackground).
-    sel styleAt:#unselectedColor  put:(Color grey:60).
-    sel styleAt:#hspace           put:10.
-    sel styleAt:#expandSelection  put:9@7.
+    tab styleAt:#selectedColor    put:(view viewBackground).
+    tab styleAt:#unselectedColor  put:(Color grey:60).
+    tab styleAt:#expandSelection  put:9@7.
 
-    sel list:#( 'Button'
-                'Toggle'
-                'Claus Atzkern'
-                'Panel'
-                'Text'
-                'Peter'
-                'Loechgau'
-                'Text'
-              ).
-    sel useIndex:true.
-    sel action:[:aName|
-        Transcript showCR:aName
-    ].
+    tab list:#( 'Foo' 'Bar' 'Baz').
+    tab useIndex:true.
+    tab action:[:aName| Transcript showCR:aName ].
 
     top open.
-                                                                                [exEnd]                                      
-
-
+                                                                                [exEnd]
 
 
-                                                                                [exBegin]                                      
-    |top sel view ctr l|
+    using images and text
+                                                                                [exBegin]
+    |top tab view list|
+
+    top := StandardSystemView new label:'example'.
 
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:420@100.
-
-
-    sel  := self origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+    tab := self 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]
 
-    l := #(     'SBrowser'
-                'FBrowser'
-                'Debugger'
-              ).
-    sel list:(l collect:[:n | Image fromFile:'bitmaps/' , n , '.xbm']).
+    using images and text; MAC style
+                                                                                [exBegin]
+    |top tab view list|
+
+    top := StandardSystemView new label:'example'.
 
-    ctr := 0.
-    sel action:[:indexOrNil|
-        Transcript showCR:indexOrNil
-    ].
+    tab := self 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]                                      
+                                                                                [exEnd]
 
-                                                                                [exBegin]                                      
+    tabs at top of view dealing with other models
+
+                                                                                [exBegin]
     |top sel view l top2 s top3 p|
 
     l := SelectionInList new.
@@ -159,99 +200,149 @@
     l selectionIndex:1.
 
     top2 := StandardSystemView new.
-    top2 extent:100@200.
+    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@200.
+    top3 extent:100@100.
     s := PopUpList in:top3.
     s model:l.
     top3 open.
 
     top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:400@100.
-
+        label:'example';
+        extent:200@50.
 
     sel  := self origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+    sel useIndex:true.
     sel model:(l selectionIndexHolder).
     sel listHolder:(l listHolder).
-
-    sel useIndex:true.
-    sel action:[:indexOrNil|
-        Transcript showCR:indexOrNil
-    ].
-    top open.
-                                                                                [exEnd]
-
-
-                                                                                [exBegin]
-    |top sel view y|
-
-    top := StandardSystemView new
-        label:'UI-Selection Panel';
-        extent:500@200.
-
-    y    := 60.
-    sel  := self origin:0.0 @ 0.0 corner:1.0 @ y in:top.
-    sel horizontalInset:10.
-    view := NoteBookFrameView origin:0.0 @ y  corner:1.0 @ 1.0 in:top.
-    view horizontalInset:10.
-    view bottomInset:10.
-    view level:2.
-    view viewBackground:(Image fromFile:'bitmaps/gifImages/garfield.gif').
-
-    sel tabWidget:#Window.
-    sel styleAt:#selectedColor   put:(view viewBackground).
-    sel styleAt:#unselectedColor put:(Color grey:60).
-
-    sel list:#( 'Button'
-                'Toggle'
-                'Claus'
-                'Panel'
-                'Text'
-                'Peter'
-                'Text'
-              ).
+    sel action:[:indexOrNil|Transcript showCR:indexOrNil].
     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:300@200.
+        extent:350@200.
 
 
-    sel  := self origin:0.0 @ 0.0 corner:1.0 @ 0.7 in:top.
-    view := View origin:0.0 @ 0.7 corner:1.0 @ 1.0 in:top.
+    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'
-                'Text'
-                'View'
-                'Combo View'
-                'Menu'
                 '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'!
 
 defaultTabWidget
-    ^ #Folder
+    ^ #Window
 ! !
 
 !TabView methodsFor:'accessing'!
@@ -280,7 +371,7 @@
 
     aList size ~~ 0 ifTrue:[
         widget := tabStyle at:#widget.
-        list   := aList collect:[:aLabel|widget label:aLabel for:self].
+        list   := widget labels:aList for:self.
     ].
 
     self shown ifTrue:[
@@ -316,41 +407,6 @@
     ]
 !
 
-preferredExtent
-    "compute max extent x/y
-    "
-    |x y ovl size hspace vspace|
-
-    ovl    := tabStyle at:#leftOverLap.
-    hspace := tabStyle at:#hspace.
-    vspace := tabStyle at:#vspace.
-    x := ovl + leftInset.
-    y := 0.
-
-    size := list size.
-    size == 0 ifTrue:[ ^ 100@32 ].
-
-    list do:[:aTab||ext|
-        ext := aTab preferredExtent.
-        ext y > y ifTrue:[
-            y := ext y.
-        ].
-        x := x + ext x - ovl + hspace.
-    ].
-    y := y + (size * vspace) + (tabStyle at:#expandSelection) y.
-  ^ x @ y.
-
-!
-
-preferredHeight
-    "returns preferred height
-    "
-    list notNil ifTrue:[
-      ^ (self extent y) - ((list first) origin y) + ((tabStyle at:#expandSelection) y)
-    ].
-    ^ 0
-!
-
 useIndex:aBoolean
     "set/clear the useIndex flag. If set, both actionBlock and change-messages
      are passed the index(indices) of the selection as argument. 
@@ -362,8 +418,80 @@
 
 ! !
 
+!TabView methodsFor:'accessing dimension'!
+
+preferredExtent
+    "compute max extent x/y based on one line
+    "
+    |x y ovl ext|
+
+    list size == 0 ifTrue:[^ 0 @ 0 ].
+
+    ovl := tabStyle at:#rightCovered.
+    x   := ovl.
+
+    list do:[:aTab|
+        x := x - ovl + aTab preferredExtentX
+    ].
+    y := (tabStyle at:#maxY)
+       + ((tabStyle at:#expandSelection) y)
+       + (self class viewSpacing).
+
+    (direction == #top or:[direction == #bottom]) ifTrue:[
+        ^ x @ y
+    ].
+    ^ y @ x             "/ #left or #right
+!
+
+preferredSizeXorY
+    "returns preferred size dependant on the current view layout and
+     the direction of the tabs
+    "
+    |y|
+
+    list size == 0 ifFalse:[
+        maxLineNr isNil ifTrue:[self recomputeList].
+
+        y := (maxLineNr * (tabStyle at:#maxY))
+           + ((tabStyle at:#expandSelection) y)
+           + (self class viewSpacing).
+
+      ^ y
+    ].
+    ^ 0
+! !
+
 !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
+    "
+
+    ^ 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
+    "
+    direction := aDirection
+
+!
+
+style
+    "returns style
+    "
+    ^ tabStyle
+!
+
 styleAt:anIdentifier
     "returns value for an identifier
     "
@@ -374,10 +502,6 @@
     "set value for an identifier
     "
     tabStyle at:anIdentifier put:something.
-
-    list notNil ifTrue:[
-        list first styleChanged:anIdentifier to:something
-    ].
 !
 
 tabWidget
@@ -395,17 +519,12 @@
     "
     |widget|
 
-    (tabStyle at:#widget) = aWidget ifFalse:[
-        (widget := TabWidget widgetClass:aWidget) notNil ifTrue:[
-            tabStyle := widget tabStyleOn:self.
-
-            self shown ifTrue:[
-                self recomputeList.
-                self redrawFull.
-            ]
+    list isNil ifTrue:[
+        widget := TabWidget widgetClass:aWidget.
+        widget notNil ifTrue:[
+            tabStyle := widget tabStyleOn:self
         ]
-    ].
-
+    ]
 ! !
 
 !TabView methodsFor:'change & update'!
@@ -431,47 +550,75 @@
 !
 
 redrawFull
-    "redraw list and boarders
+    "redraw list
     "
-    |size x1 x2 y1 y2 space sel|
+    |oldSelect|
+
+    (list size ~~ 0 and:[self shown]) ifTrue:[
+        self paint:(self viewBackground).
+        self clear.
+
+        maxLineNr to:1 by:-1 do:[:i|self redrawLineUnselected:i].
+        selection notNil ifTrue:[
+            oldSelect := selection.
+            selection := nil.
+            self setSelection:oldSelect.
+        ]
+    ]
+!
+
+redrawLineUnselected:aLineNr
+    "redraw one line
+    "
+    list do:[:aTab|aTab lineNr == aLineNr ifTrue:[aTab redraw:false]]
+!
+
+redrawSelection
+    "redraw current selection
+    "
+    |tab size oldAnc newAnc oldExt newExt expSel expDlt x y|
 
     size := list size.
 
-    (size ~~ 0 and:[self shown]) ifFalse:[
+    (selection notNil and:[self shown and:[size ~~ 0]]) ifFalse:[
         ^ self
     ].
-    space := tabStyle at:#vspace.
 
-    self paint:(self viewBackground).
-    self clear.
+    tab    := list at:selection.
+    oldAnc := tab anchor.
+    oldExt := tab extent.
+    expSel := tabStyle at:#expandSelection.
+    expDlt := expSel x.
+
+    (direction == #top or:[direction == #bottom]) ifTrue:[
+        newExt := oldExt + ( expDlt @ 0 ).
+        newAnc := oldAnc - ((expDlt//2) @ ((expSel y) negated)).
 
- "/ redraw view boarders
-    space ~~ 0 ifTrue:[
-        x1 := tabStyle at:#hspace.
-        y1 := self extent y - space.
-        x2 := self extent x.
+        (x := newAnc x) < 0 ifTrue:[
+            newExt x:(newExt x + x).
+            newAnc x:0.
+            x := 0.
+        ].
+        (x + newExt x) > (self extent x) ifTrue:[newExt x:((self extent x) - x)].
+    ] ifFalse:[
+        newExt := oldExt + ( 0 @ expDlt ).
+        newAnc := oldAnc - (((expSel y) negated) @ (expDlt//2)).
 
-        self paintColor:#labelColor.
-
-        (size+1) timesRepeat:[
-            self displayLineFrom:(0 @ y1) to:(x2 @ y1).
-            y1 := y1 - space.
-        ]
+        (y := newAnc y) < 0 ifTrue:[
+            newExt y:(newExt y + y).
+            newAnc y:0.
+            y := 0.
+        ].
+        (y + newExt y) > (self extent y) ifTrue:[newExt y:((self extent y) - y)].
     ].
 
- "/ redraw list
-    maxLineNr to:1 by:-1 do:[:i|self redrawLineAt:i].
-    selection notNil ifTrue:[
-        sel := selection.
-        selection := nil.
-        self setSelection:sel.
-    ].
-!
+    tab anchor:newAnc extent:newExt.
+    tab redraw:true.
+    tab anchor:oldAnc extent:oldExt.
 
-redrawLineAt:aLineNr
-    "redraw one line
-    "
-    list do:[:aTab|aTab lineNr == aLineNr ifTrue:[aTab redraw:false]]
+    size := tab lineNr.
+    [(size := size - 1) ~~ 0] whileTrue:[self redrawLineUnselected:size].
+
 !
 
 redrawX:x y:y width:w height:h
@@ -483,25 +630,15 @@
 !TabView methodsFor:'event handling'!
 
 buttonPress:button x:x y:y
-    "a button is pressed
+    "a button is pressed; find tab under point at set selection
     "
-    |lnNr index|
-
     list notNil ifTrue:[
-        index := nil.
-        lnNr  := 99999.
-
-     "/ find tab under point; update selection
-
         list keysAndValuesDo:[:aKey :aTab|
             (aTab containsPoint:(x@y)) ifTrue:[
-                aTab lineNr < lnNr ifTrue:[
-                    index := aKey.
-                    lnNr  := aTab lineNr.
-                ]
+                ^ self selection:aKey
             ]
         ].
-        self selection:index
+        self selection:nil
     ]
 !
 
@@ -539,9 +676,10 @@
     "
     list notNil ifTrue:[
         self recomputeList.
+
         sizeChangedNotify ifFalse:[
             sizeChangedNotify := true.
-            self changed:#preferredHeight.
+            self changed:#preferredExtent.
             sizeChangedNotify := false.
         ]
     ].
@@ -556,171 +694,133 @@
     |widget|
 
     super initialize.
-    widget   := TabWidget widgetClass:(self class defaultTabWidget).
-    tabStyle := widget tabStyleOn:self.
-    leftInset := 0.
+    widget    := TabWidget widgetClass:(self class defaultTabWidget).
+    tabStyle  := widget tabStyleOn:self.
+    useIndex  := false.
+    direction := #top.
     sizeChangedNotify := false.
-    useIndex := false.
-    selectionToFirstLine := false.
 ! !
 
 !TabView methodsFor:'layout'!
 
-fitLineAt:aLnNr
-    "fit line at a lineNr
-    "
-    |dltExtX dltOrgX tab sIdx eIdx width|
-
-    eIdx := list findFirst:[:aTab| aTab lineNr == aLnNr].
-    eIdx == 0 ifTrue:[^ false].
-
-    sIdx  := list findLast:[:aTab| aTab lineNr == aLnNr].
-    tab   := list at:eIdx.
-    width := self extent x.
-
-    dltExtX := width - ((tab origin x) + (tab extent x)).
-    dltExtX := dltExtX // (sIdx - eIdx + 1).
-    dltOrgX := 0.
-
-    dltExtX > 0 ifTrue:[
-        sIdx to:eIdx by:-1 do:[:i|
-            tab := list at:i.
-            tab extent x:((tab extent x) + dltExtX).
-            tab origin x:((tab origin x) + dltOrgX).
-            dltOrgX := dltOrgX + dltExtX.
-        ]
-    ].
-    tab := list at:eIdx.
-    tab extent x:(width - tab origin x).
-  ^ true
-
-
-
-!
-
-recomputeFixedLayout
-    "recompute tabs
-    "
-    |vspace tab lnNr deltaY vspCtr size x y hspace width ovlap noLn|
-
-    size := list size.
-    hspace := tabStyle at:#hspace.
-    width  := self extent x - leftInset.
-    vspace := tabStyle at:#vspace.
-    vspCtr := vspace.
-
-    deltaY := list first preferredExtent y.
-    x := leftInset.
-    y := self extent y.
-    lnNr  := 1.
-    ovlap := tabStyle at:#leftOverLap.
-    maxLineNr := 1.
-
-    list reverseDo:[:aTab||e n|
-        e := aTab preferredExtent.
-        n := e x + x - ovlap.
-
-        n > width ifTrue:[
-            maxLineNr := maxLineNr + 1.
-            lnNr := lnNr + 1.
-            x := leftInset.
-            y := y - deltaY.
-            n := e x + x - ovlap.
-            vspCtr := 0.
-        ].
-        aTab lineNr:lnNr.
-        aTab origin:x@(y - deltaY - vspCtr) extent:e inset:vspCtr.
-        x := n + hspace.
-        size := size - 1.
-        vspCtr := vspCtr + vspace.
-    ].
-
-    "/ fit lines
-    noLn := 1.
-    [self fitLineAt:noLn] whileTrue:[noLn := noLn + 1].
-!
-
 recomputeList
     "recompute tabs
     "
-    |numCols lnNr tabOffset size extent width x y 
-     ovlap extX hspace origin ctr bottomInset vspace|
+    |tab extY size x y width ovl|
 
-    size := list size.
-    size == 0 ifTrue:[^ self].
+    list size ~~ 0 ifTrue:[
+        (direction == #top or:[direction == #bottom]) ifTrue:[
+            self recomputeListHorizontal
+        ] ifFalse:[
+            self recomputeListVertical
+        ]
+    ].
+!
+
+recomputeListHorizontal
+    "recompute horizontal tabs
+    "
+    |tab extY size x y width ovl|
 
-    (tabStyle at:#fixedLabelSize) ifTrue:[
-        ^ self recomputeFixedLayout
-    ].
-    extent := self preferredExtent.
-    (extent x) <= (self extent x) ifTrue:[
-        ^ self recomputeFixedLayout
+    size  := list size.
+    extY  := tabStyle at:#maxY.
+    ovl   := tabStyle at:#rightCovered.
+    width := self extent x.
+    x     := 0.
+    y     := extY.
+    maxLineNr := 1.
+
+    list reverseDo:[:aTab||eX n|
+        eX := aTab preferredExtentX.
+        n := eX + x - ovl.
+
+        n > width ifTrue:[
+            maxLineNr := maxLineNr + 1.
+            x := 0.
+            y := y  + extY.
+            n := eX - ovl.
+        ].
+        aTab lineNr:maxLineNr.
+        aTab anchor:x@y extent:(eX @ extY).
+        x := n.
     ].
 
- "/ compute preferred extent
+    "/ fit lines
+    1 to:maxLineNr do:[:aLnNr|
+        |extX orgX last|
 
-    x     := 10.
-    y     := 10.
-    hspace:= tabStyle at:#hspace.
-    ovlap := tabStyle at:#leftOverLap.
+        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.
 
-    list do:[:aTab|
-        extent := aTab preferredExtent.
-        extent x > x ifTrue:[x := extent x].
-        extent y > y ifTrue:[y := extent y].
-    ].
-    width   := self extent x - ovlap - leftInset.
-    extent  := x@y.
-    extX    := x - ovlap.
-    numCols := width // (extX + hspace).
+        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.
+    ]
+!
 
- "/ calculate tabOffset, numCols and lnNr
+recomputeListVertical
+    "recompute vertical tabs
+    "
+    |tab extX size x y height ovl|
 
-    numCols < 2 ifTrue:[
-        numCols := 1.
-        maxLineNr := size.
-    ] ifFalse:[
-        numCols > size ifTrue:[
-            numCols := size
-        ].
+    size   := list size.
+    extX   := tabStyle at:#maxY.
+    ovl    := tabStyle at:#rightCovered.
+    height := self corner y.
+    x      := extX.
+    y      := 0.
 
-        maxLineNr := (size + numCols - 1) // numCols.
-        tabOffset := (maxLineNr * hspace) + extX.
+    maxLineNr := 1.
 
-        (numCols * tabOffset) > width ifTrue:[
-            numCols := numCols - 1.
-            maxLineNr := (size + numCols - 1) // numCols.
-        ]
-    ].
-    tabOffset := width // numCols.
+    list reverseDo:[:aTab||eY n|
+        eY := aTab preferredExtentX.
+        n  := eY + y - ovl.
 
- "/ calculate extent x
-    extent x:(tabOffset - (maxLineNr * hspace) + ovlap).
+        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.
+    ].
 
-    vspace := tabStyle at:#vspace.
-    bottomInset := vspace.
-    y    := self extent y - vspace - extent y.
-    x    := leftInset.
-    ctr  := 1.
-    lnNr := 1.
+    "/ fit lines
+    1 to:maxLineNr do:[:aLnNr|
+        |extY orgY last|
 
-    list reverseDo:[:aTab|
-        aTab lineNr:lnNr.
-        aTab origin:x@y extent:extent inset:bottomInset.
-        bottomInset := bottomInset + vspace.
+        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.
 
-        (ctr := ctr + 1) > numCols ifTrue:[
-            origin := (list at:size) origin.
-            size   := size - numCols.
-            y      := origin y - extent y.
-            x      := origin x + hspace.
-            ctr    := 1.
-            lnNr   := lnNr + 1.
-        ] ifFalse:[
-            x := x + tabOffset.
-            y := y - vspace.
-        ]
+        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.
     ]
+
 ! !
 
 !TabView methodsFor:'selection'!
@@ -728,21 +828,41 @@
 lineToBottomWithNumber:aLineNr
     "exchange the first line with the received line number
     "
-    |tabN tab1 orgY|
+    |tabN tab1 orgY a1 aN|
 
     tab1 := list at:(list findLast:[:aTab|aTab lineNr == 1]).
     tabN := list at:(list findLast:[:aTab|aTab lineNr == aLineNr]).
-    orgY := tab1 origin y - tabN origin y.
+
+    (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 origin y:(aTab origin y - orgY).
-            aTab lineNr:aLineNr.
-        ] ifFalse:[
-            ln == aLineNr ifTrue:[
-                aTab origin y:(aTab origin y + orgY).
-                aTab lineNr:1.
+        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.
+                ]
             ]
         ]
     ]
@@ -772,13 +892,8 @@
     (sel ~~ selection) ifTrue:[
         sel := self selection.
 
-        model notNil ifTrue:[
-            model value:sel
-        ].
-
-        action notNil ifTrue:[
-            action value:sel
-        ]
+        model  notNil ifTrue:[model  value:sel].
+        action notNil ifTrue:[action value:sel]
     ]
 
 !
@@ -809,8 +924,7 @@
 
     (     index notNil
      and:[(lnNr := (list at:index) lineNr) > 1
-     and:[(tabStyle at:#selectionAtBottom)
-     and:[(tabStyle at:#vspace) == 0]]]
+     and:[(tabStyle at:#selectionAtBottom)]]
     ) ifTrue:[
         self lineToBottomWithNumber:lnNr.
         selection := 1.
@@ -821,57 +935,11 @@
         self redrawFull
     ].
     selection := index.
-    self showSelected.
-!
-
-showSelected
-    "draw current selection as selected
-    "
-    |leftExtX rightExtX vspace tab size savOrg savExt expSel savIns setIns newExt x newOrg|
-
-    size := list size.
-
-    (selection notNil and:[self shown and:[size ~~ 0]]) ifFalse:[
-        ^ self
-    ].
-    tab       := list at:selection.
-    savOrg    := tab origin.
-    savExt    := tab extent.
-    savIns    := tab inset.
-    expSel    := tabStyle at:#expandSelection.
-    rightExtX := expSel x.
-
-    (vspace := tabStyle at:#vspace) == 0 ifTrue:[
-        leftExtX := rightExtX := rightExtX//2.
-        setIns := 0
-    ] ifFalse:[
-        leftExtX := 0.
-        setIns   := savIns
-    ].
-
-    newExt := savExt + ((leftExtX + rightExtX)@0).
-    newOrg := savOrg - ( leftExtX @ (expSel y)).
-
-    (x := newOrg x) < 0 ifTrue:[
-        newExt x:(newExt x + x).
-        newOrg x:0.
-        x := 0.
-    ].
-
-    (x + newExt x) > (self extent x) ifTrue:[
-        newExt x:((self extent x) - x)
-    ].
-
-    tab origin:newOrg extent:newExt inset:setIns.
-    tab redraw:true.
-    tab origin:savOrg extent:savExt inset:savIns.
-
-    x := tab lineNr.
-    [(x := x - 1) ~~ 0] whileTrue:[self redrawLineAt:x].
+    self redrawSelection.
 ! !
 
 !TabView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.5 1997-04-08 15:23:53 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.6 1997-04-22 16:56:16 ca Exp $'
 ! !
--- a/TabWidget.st	Sat Apr 19 12:23:56 1997 +0200
+++ b/TabWidget.st	Tue Apr 22 18:56:29 1997 +0200
@@ -13,19 +13,12 @@
 
 
 Object subclass:#TabWidget
-	instanceVariableNames:'tabView label origin extent inset lineNr'
+	instanceVariableNames:'tabView label anchor extent lineNr'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Interactors'
 !
 
-TabWidget subclass:#Window
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:TabWidget
-!
-
 TabWidget subclass:#Mac
 	instanceVariableNames:''
 	classVariableNames:''
@@ -33,7 +26,7 @@
 	privateIn:TabWidget
 !
 
-TabWidget subclass:#Folder
+TabWidget subclass:#Window
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -72,10 +65,44 @@
 
 !TabWidget class methodsFor:'instance creation'!
 
-label:aLabel for:aTabView
-    "create tab
+labels:aList for:aTabView
+    "create tabs based on labels for a tabview
     "
-    ^ self new label:aLabel for:aTabView
+    |list maxX maxY lftIns topIns level style|
+
+    maxX   := 0.
+    maxY   := 0.
+    style  := aTabView style.
+    lftIns := style at:#labelLeftInset.
+    topIns := style at:#lableTopInset.
+    level  := style at:#tabLevel.
+
+    list := aList collect:[:aLabel||y x|
+        (y := aLabel heightOn:aTabView) > maxY ifTrue:[maxY := y].
+        (x := aLabel  widthOn:aTabView) > maxX ifTrue:[maxX := x].
+        self new label:aLabel for:aTabView
+    ].
+
+    style at:#labelMaxX put:maxX.
+    style at:#labelMaxY put:maxY.
+
+    maxY  := maxY + topIns
+                  + (style at:#labelBottomInset)
+                  + (2 * level).
+
+    maxX := maxX + lftIns + (style at:#labelRightInset).
+
+    style at:#maxX put:maxX.
+    style at:#maxY put:maxY.
+    style at:#labelAnchor put:( lftIns @ (topIns +level) ).
+
+    self validateDimensions:style.
+  ^ list
+!
+
+validateDimensions:aStyle
+    "validate dimensions for a style; could be redifined
+    "
 ! !
 
 !TabWidget class methodsFor:'accessing'!
@@ -106,49 +133,74 @@
     style at:#unselectedColor    put:unselectedColor.
     style at:#selectedColor      put:selectedColor.
     style at:#labelColor         put:(Color black).
-    style at:#selectionAtBottom  put:false.  "/ true: selected tab always moved to bottom
+    style at:#selectionAtBottom  put:true.  "/ true: selected tab always moved to bottom
 
-    style at:#vspace             put:0.      "/ vertical   tab space
-    style at:#hspace             put:0.      "/ horizontal tab space
-    style at:#leftOverLap        put:0.      "/ right tab overlaps left tab n pixels
+    style at:#expandSelection    put:0@0.    "/ expand selection extent x y when raised
+    style at:#tabLevel           put:0.      "/ level
     style at:#lableTopInset      put:4.      "/ additional top label inset
     style at:#labelBottomInset   put:4.      "/ additional bottom inset
-    style at:#expandSelection    put:0@0.    "/ expand selection extent x y when raised
-    style at:#fixedLabelSize     put:false.  "/ true: label size derives from preferred extent
-
+    style at:#labelLeftInset     put:4.      "/ label left  inset
+    style at:#labelRightInset    put:4.      "/ label right inset
+    style at:#rightCovered       put:0.      "/ covers right tab for n pixels
 
   ^ style
 !
 
 widgetClass:aWidget
-    |wdg nm|
+    |wdgt name|
 
-    nm := aWidget asString.
+    name := aWidget asString.
+    wdgt := Smalltalk classNamed:( self name asString, '::', name ).
 
-    (wdg := Smalltalk classNamed:(self name asString, '::', nm)) notNil ifTrue:[
-        ^ wdg
+    wdgt notNil ifTrue:[
+        ^ wdgt
     ].
-    ^ Smalltalk classNamed:nm
+    ^ Smalltalk classNamed:name
 ! !
 
-!TabWidget class methodsFor:'constants'!
+!TabWidget methodsFor:'accessing'!
+
+label
+    ^ label
+!
+
+lineNr
+    "returns line number
+    "
+    ^ lineNr
+!
+
+lineNr:aLineNr
+    "change line number
+    "
+    lineNr := aLineNr
+! !
+
+!TabWidget methodsFor:'accessing dimensions'!
 
-defaultExtent
-    ^ 80 @ 25
+anchor
+    "returns the tab origin
+    "
+    ^ anchor
+
+!
+
+anchor:anAnchor
+    "change the tab anchor; no redraw
+    "
+    anchor := anAnchor
+
+!
+
+anchor:anAnchor extent:anExtent
+    "change anchor and extent; no redraw
+    "
+    anchor := anAnchor.
+    extent := anExtent.
 
 
 !
 
-labelLeftInset
-    ^ 4
-!
-
-labelRightInset
-    ^ 4
-! !
-
-!TabWidget methodsFor:'accessing'!
-
 extent
     "return the tab extent
     "
@@ -161,100 +213,114 @@
     extent := anExtent
 !
 
-inset
-    "returns the bottom inset starting from 1.0
-    "
-    ^ inset
-!
-
-inset:anInset
-    "change the bottom inset starting from 1.0; no redraw
+preferredExtentX
+    "returns my preferred extent x
     "
-    inset := anInset
-!
-
-label
-    ^ label
-!
-
-labelOrigin
-    "returns origin of label
-    "
-  ^ (self labelOriginWithinFrame)
-     + ((tabView styleAt:#leftOverLap) @ (tabView styleAt:#lableTopInset))
-!
-
-lineNr
-    "returns line number
-    "
-    ^ lineNr
-!
-
-lineNr:aLineNr
-    "change line number
-    "
-    lineNr := aLineNr
+    ^    (tabView styleAt:#maxX)
+       - (tabView styleAt:#labelMaxX)
+       + (label  widthOn:tabView).
 !
 
-origin
-    "returns the tab origin
+preferredExtentY
+    "returns my preferred extent y
     "
-    ^ origin
+    ^    (tabView styleAt:#maxY)
+       - (tabView styleAt:#labelMaxY)
+       + (label  heightOn:tabView).
+! !
 
-!
+!TabWidget methodsFor:'basic drawing'!
 
-origin:anOrigin
-    "change the tab origin; no redraw
+redrawAtBottom:isSelected
+    "redraw tab at bottom of view
     "
-    origin := anOrigin
-
+    ^ self subclassResponsibility
 !
 
-origin:anOrigin extent:anExtent inset:anInset
-    "change origin, extent and bottom inset starting from 1.0; no redraw
+redrawAtLeft:isSelected
+    "redraw tab at left of view
     "
-    origin := anOrigin.
-    extent := anExtent.
-    inset  := anInset.
-
-
+    ^ self subclassResponsibility
 !
 
-preferredExtent
-    "returns my preferred extent
+redrawAtRight:isSelected
+    "redraw tab at right of view
     "
-    |x y|
+    ^ self subclassResponsibility
+!
 
-    label isNil ifTrue:[
-        ^ self class defaultExtent
-    ].
-    x := (label widthOn:tabView)
-        + (self class labelRightInset)
-        + (self class labelLeftInset).
-
-    y :=   (label heightOn:tabView)
-         + (tabView styleAt:#labelBottomInset)
-         + (tabView styleAt:#lableTopInset).
-
-  ^ ((self labelOrigin) + (x@y))
+redrawAtTop:isSelected
+    "redraw tab at top of view
+    "
+    ^ self subclassResponsibility
 ! !
 
 !TabWidget methodsFor:'drawing'!
 
+computeCorner
+    "compute corner
+    "
+    |d c|
+
+    c := anchor + extent.
+    d := tabView direction.
+
+    d == #top    ifTrue:[^ ( c x @ (tabView extent y) )].
+    d == #left   ifTrue:[^ ( (tabView extent x) @ c y ) ].
+    d == #right  ifTrue:[^ ( 0 @ c y )].
+    d == #bottom ifTrue:[^ ( c x @ 0 )].
+
+    self error.
+!
+
+computeOrigin
+    "compute origin
+    "
+    |d|
+
+    d := tabView direction.
+
+    d == #top    ifTrue:[ ^ anchor x @ ((tabView extent y) - anchor y) ].
+    d == #left   ifTrue:[ ^ ((tabView extent x) - anchor x) @ anchor y ].
+    d == #right  ifTrue:[ ^ anchor ].
+    d == #bottom ifTrue:[ ^ anchor ].
+
+    self error
+!
+
 redraw:isSelected
     "full redraw
     "
-    |p y|
+    |x y p a d|
+
+    d := tabView direction.
 
-    self redrawSelected:isSelected.
-    tabView paintColor:#labelColor.
-    p := origin  + self labelOrigin.
-    y := p y.
+    (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
+    ].
 
-    label isString ifTrue:[
-        y := y + tabView font ascent
+    d == #right ifTrue:[
+        ^ self redrawAtRight:isSelected
     ].
-    label displayOn:tabView x:(p x) y:y.
+    d == #left ifTrue:[
+        ^ self redrawAtLeft:isSelected
+    ].
 ! !
 
 !TabWidget methodsFor:'initialization'!
@@ -262,103 +328,65 @@
 label:aLabel for:aTabView
     "initialize attributes
     "
-    tabView     := aTabView.
-    label       := aLabel.
+    tabView := aTabView.
+    label   := aLabel.
 ! !
 
 !TabWidget methodsFor:'queries'!
 
 containsPoint:aPoint
-    "return true, if the aPoint is contained in the tab
+    "return true, if a point is contained in the tab
     "
-    |x|
+    |d x y top bot origin|
 
+    d := tabView direction.
     x := aPoint x.
+    y := aPoint y.
 
-    (x >= origin x and:[aPoint y >= origin y]) ifTrue:[
-        ^ x < (origin x + extent x)
+    origin := self computeOrigin.
+
+    (d == #top or:[d == #bottom]) ifTrue:[
+        ((x >= origin x) and:[x <= (origin x + extent x)]) ifTrue:[
+            d == #top ifTrue:[
+                ^ ((y >=  origin y) and:[y <= (origin y + extent y)])
+            ].
+            ^ ((y <=  origin y) and:[y >= (origin y - extent y)])
+        ]
+    ] ifFalse:[
+        ((y >= origin y) and:[y <= (origin y + extent y)]) ifTrue:[
+            d == #right ifTrue:[
+                ^ ((x <= origin x) and:[x >= (origin x - extent x)])
+            ].
+            ^ ((x >= origin x) and:[x <= (origin x + extent x)])
+        ]
     ].
-    ^ false.
+    ^ false
 ! !
 
-!TabWidget methodsFor:'redefine'!
-
-labelOriginWithinFrame
-    "returns the offset from origin to the origin of the label
-    "
-    ^ (self class labelLeftInset) @ 0
+!TabWidget::Mac class methodsFor:'calculate dimensions'!
 
-!
-
-redrawSelected:isSelected
-    "full redraw excluding the label
+validateDimensions:aStyle
+    "validate dimensions for a style; could be redifined
     "
-    ^ self subclassResponsibility
-!
+    |maxY maxX anchor lftIns|
 
-styleChanged:anIdentifier to:someThing
-    "any style changed; could be redifined in subclass
-    "
-    |dark light|
+    maxY   := aStyle at:#maxY.
+    maxX   := (aStyle at:#maxX) - (aStyle at:#labelLeftInset).
+    anchor := aStyle at:#labelAnchor.
+    lftIns := maxY // 2.
 
-    anIdentifier == #selectedColor ifTrue:[
-        dark  := #shadowColorSelected.
-        light := #lightColorSelected.
-    ] ifFalse:[
-        anIdentifier == #unselectedColor ifFalse:[
-            ^ self
-        ].
-        dark  := #shadowColorUnselected.
-        light := #lightColorUnselected.
-    ].
-    tabView styleAt:dark  put:((someThing averageColorIn:(0@0 corner:7@7)) darkened  on:tabView device).
-    tabView styleAt:light put:((someThing averageColorIn:(0@0 corner:7@7)) lightened on:tabView device).
+    anchor x:lftIns.
 
+    aStyle at:#maxX         put:(maxX + lftIns + maxY).
+    aStyle at:#rightCovered put:(maxY // 2).
 ! !
 
-!TabWidget::Window class methodsFor:'accessing'!
-
-tabStyleOn:aView
-    |style col|
-
-    style := super tabStyleOn:aView.
-
-    style at:#fixedLabelSize     put:true.
-    style at:#tabLevel           put:2.
-    style at:#roundedEdges       put:true.
-    style at:#expandSelection    put:4@4.
-    style at:#selectionAtBottom  put:true.
-
-  ^ style
-
-
-
-! !
-
-!TabWidget::Window methodsFor:'redifined'!
+!TabWidget::Mac methodsFor:'drawing'!
 
-labelOriginWithinFrame
-    |org|
-
-    org := super labelOriginWithinFrame.
-  ^ org + (tabView styleAt:#tabLevel)
-
-
-!
-
-redrawSelected:isSelected
-    "redraw; set fill-color to aColor.
+redrawAtBottom:isSelected
+    "redraw tab at bottom of view
     "
-    |polygon color y x ext xR yB tabLevel light roundedEdges shadowColor lightColor|
-
-    ext := (extent x) @ (tabView extent y - inset).
-    x   := origin x.
-    y   := origin y.
-    xR  := x + ext x - 1.
-    yB  := ext y - 1.
-
-    roundedEdges := tabView styleAt:#roundedEdges.
-    tabLevel     := tabView styleAt:#tabLevel.
+    |origin corner polygon x y x1 eX eY color shadowColor lightColor|
 
     isSelected ifFalse:[
         color       := tabView styleAt:#unselectedColor.
@@ -368,94 +396,95 @@
         color       := tabView styleAt:#selectedColor.
         shadowColor := tabView styleAt:#shadowColorSelected.
         lightColor  := tabView styleAt:#lightColorSelected.
-        yB := yB + 1
     ].
 
+    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 fillRectangle:(Rectangle left:x top:y extent:ext).
-
-    roundedEdges ifTrue:[
-        tabView displayLineFromX:x y:y-1 toX:xR y:y-1.          
-        tabView displayLineFromX:x+1 y:y-2 toX:xR-1 y:y-2.
-        tabView displayLineFromX:x+2 y:y-3 toX:xR-2 y:y-3.
-        
-        tabView paint:lightColor.
-
-        0 to:tabLevel-1 do:[:i |
-            tabView displayPointX:x+i y:y-1.
-            tabView displayPointX:x+1+i y:y-1-1.
-            tabView displayLineFromX:x+2+i y:y-3-i toX:xR-1-i y:y-3-i.  "/ top
-        ].
-
-        tabView paint:shadowColor.
-        0 to:tabLevel-1 do:[:i |
-            tabView displayPointX:xR-i y:y.
-            tabView displayPointX:xR-i y:y-1.
-            tabView displayPointX:xR-1-i y:y-1-1.
-        ].
-        tabView displayPointX:xR-2 y:y-1-1-1.
-        tabView displayPointX:xR-3 y:y-1-1-1.
-    ].
+    tabView fillPolygon:polygon.
 
     tabView paint:lightColor.
-    0 to:tabLevel-1 do:[:i |
-        roundedEdges ifFalse:[
-            tabView displayLineFromX:x y:y+i toX:xR y:y+i.    "/ upper edge
-        ].
-        tabView displayLineFromX:x+i y:y toX:x+i y:yB.    "/ left edge
-    ].
-    tabView paint:shadowColor.
-    0 to:tabLevel-1 do:[:i |
-        tabView displayLineFromX:xR-i y:y+i toX:xR-i y:yB.  "/ right edge
-    ].
+    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:[
-        "/ bottom edge
-        tabView paint:lightColor.
-        tabView displayLineFromX:x-tabLevel-1 y:yB toX:xR+tabLevel+1 y:yB.    "/ bottom edge
-    ] ifTrue:[
-"/        tabView paintColor:#labelColor.
-"/        tabView lineStyle:#dashed.
-"/        tabView displayRectangle:((origin extent:extent) insetBy:(3@4)).
-"/        tabView lineStyle:#solid
+        tabView paint:shadowColor.
+        tabView displayLineFromX:x y:eY toX:eX y:eY.
     ]
 
 
-! !
-
-!TabWidget::Mac class methodsFor:'accessing'!
-
-tabStyleOn:aView
-    |style col|
-
-    style := super tabStyleOn:aView.
-
-    style at:#fixedLabelSize     put:true.
-    style at:#leftOverLap        put:10.
-    style at:#selectionAtBottom  put:true.
-  ^ style
-
-
-! !
-
-!TabWidget::Mac class methodsFor:'constants'!
-
-rightInset
-    ^ 25 "/ 23
-! !
-
-!TabWidget::Mac methodsFor:'redefine'!
-
-preferredExtent
-
-  ^ (super preferredExtent) + ((self class rightInset) @ 0).
 !
 
-redrawSelected:isSelected
-    "full redraw; excluding the label
+redrawAtLeft:isSelected
+    "redraw tab at left of view
     "
-    |polygon x y x1 eX eY color shadowColor lightColor|
+    |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.
@@ -468,11 +497,61 @@
     ].
 
     polygon := Array new:5.
+    origin  := self computeOrigin.
+    corner  := self computeCorner.
+
     x  := origin x.
     y  := origin y.
-    eX := x + extent x - 1.
-    eY := tabView extent y - inset.
-    x1 := eX - self class rightInset.
+    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).
@@ -485,7 +564,7 @@
 
     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.
@@ -498,102 +577,297 @@
 
 ! !
 
-!TabWidget::Folder class methodsFor:'accessing'!
+!TabWidget::Window class methodsFor:'accessing'!
 
 tabStyleOn:aView
-    |style|
+    |style col|
 
     style := super tabStyleOn:aView.
 
-    style at:#hspace             put:2.
-    style at:#vspace             put:2.
-    style at:#labelBottomInset   put:10.
-    style at:#expandSelection    put:4@8.
+    style at:#expandSelection    put:4@4.
+    style at:#tabLevel           put:2.
+    style at:#lableTopInset      put:2.
+    style at:#labelBottomInset   put:2.
+    style at:#roundedEdges       put:true.
+  ^ style
 
-  ^ style
 
 
 ! !
 
-!TabWidget::Folder class methodsFor:'constants'!
+!TabWidget::Window class methodsFor:'calculate dimensions'!
+
+validateDimensions:aStyle
+    "validate dimensions for a style; could be redifined
+    "
+    |maxY anchor|
 
-folderTabSize
-    ^ 4@4
+    (aStyle at:#roundedEdges) ifTrue:[
+        maxY := aStyle at:#maxY.
+        aStyle at:#maxY put:(maxY + 3).
+        anchor := aStyle at:#labelAnchor.
+        anchor y:(anchor y + 1).
+        aStyle at:#labelAnchor put:anchor.
+    ]
+
+
+
 
 
 ! !
 
-!TabWidget::Folder methodsFor:'redefined'!
+!TabWidget::Window methodsFor:'drawing'!
+
+redrawAtBottom:isSelected
+    "redraw tab at bottom of view
+    "
+    |origin corner y x xR yB tabLevel light roundedEdges shadowColor lightColor|
+
+    origin := self computeOrigin.
+    corner := self computeCorner.
+    x   := origin x.
+    y   := origin y.
+    xR  := corner x - 1.
+    yB  := 0.
+
+    roundedEdges := tabView styleAt:#roundedEdges.
+    tabLevel     := (tabView styleAt:#tabLevel) - 1.
+
+    isSelected ifFalse:[
+        tabView paint:(tabView styleAt:#unselectedColor).
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        lightColor  := tabView styleAt:#lightColorUnselected.
+    ] ifTrue:[
+        tabView paint:(tabView styleAt:#selectedColor).
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        lightColor  := tabView styleAt:#lightColorSelected.
+    ].
+
+    roundedEdges ifTrue:[y := y - 2].
+    tabView fillRectangle:(Rectangle left:x top:yB extent:(extent x @ y)).
 
-labelOriginWithinFrame
-    |org|
+    roundedEdges ifTrue:[
+        tabView displayLineFromX:x-1 y:y toX:xR y:y.
+        y := y - 1.
+
+        tabView paint:lightColor.
+        tabView displayPointX:x   y:y+1.
+        tabView displayPointX:x+1 y:y+1.
+        tabView displayLineFromX:x+1 y:y+2 toX:xR-1 y:y+2.
+        tabView displayLineFromX:x+2 y:y+3 toX:xR-2 y:y+3.
+
+        tabView paint:shadowColor.
 
-    org := super labelOriginWithinFrame.
-    org  y:(org y + self class folderTabSize y).
-  ^ org
+        0 to:tabLevel do:[:i |
+            tabView displayPointX:xR-i   y:y.
+            tabView displayPointX:xR-i   y:y+1.
+            tabView displayPointX:xR-1-i y:y+2.
+        ].
+        tabView displayPointX:xR-2 y:y+3.
+        tabView displayPointX:xR-3 y:y+3.
+    ].
+
+    tabView paint:lightColor.
+
+    0 to:tabLevel do:[:i |
+        roundedEdges ifFalse:[
+            tabView displayLineFromX:x y:y-i toX:xR y:y-i   "/ upper edge
+        ].
+        tabView displayLineFromX:x+i y:y+1 toX:x+i y:yB.    "/ left edge
+    ].
+    y := y + 1.
+    tabView paint:shadowColor.
+
+    0 to:tabLevel do:[:i |
+        tabView displayLineFromX:xR-i y:y-i toX:xR-i y:yB.  "/ right edge
+    ].
 
 !
 
-redrawSelected:isSelected
-    "full redraw; excluding the label
+redrawAtLeft:isSelected
+    "redraw tab at left of view
     "
-    |lightColor shadowColor polygon fs x y y1 y2 x1 x2 x3 eX eY level|
+    |origin corner y x xR yB tabLevel light roundedEdges shadowColor lightColor|
+
+    origin := self computeOrigin.
+    corner := self computeCorner.
+    x   := origin x.
+    y   := origin y.
+    xR  := corner x.
+    yB  := corner y.
+
+    roundedEdges := tabView styleAt:#roundedEdges.
+    tabLevel     := (tabView styleAt:#tabLevel) - 1.
+
+    isSelected ifFalse:[
+        tabView paint:(tabView styleAt:#unselectedColor).
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        lightColor  := tabView styleAt:#lightColorUnselected.
+    ] ifTrue:[
+        tabView paint:(tabView styleAt:#selectedColor).
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        lightColor  := tabView styleAt:#lightColorSelected.
+    ].
+    tabView fillRectangle:(Rectangle left:x top:y extent:(xR @ extent y)).
+
+    roundedEdges ifTrue:[
+        tabView displayLineFromX:x y:y toX:x y:yB.
+
+        tabView paint:lightColor.
+        tabView displayPointX:x y:y+1.
+        tabView displayPointX:x y:y+2.
+        tabView displayLineFromX:x-1 y:y+2 toX:x-1 y:yB-1.
+        tabView displayLineFromX:x-2 y:y+3 toX:x-2 y:yB-1.
+
+        tabView paint:shadowColor.
 
-    polygon := Array new:8.
-    x  := origin x.
-    y  := origin y.
-    eX := x + extent x - 1.
-    eY := tabView extent y - inset.
-    fs := self class folderTabSize.
-    x1 := fs x.
-    y1 := fs y.
-    y2 := y + y1.
-    x3 := x + x1.
-    x2 := 10.
-    level := 2.
+        0 to:tabLevel do:[:i |
+            tabView displayPointX:x   y:yB-i.
+            tabView displayPointX:x-1 y:yB-i-1.
+            tabView displayPointX:x-2 y:yB-i-2.
+        ].
+    ].
+    tabView paint:lightColor.
+
+    0 to:tabLevel do:[:i |
+        roundedEdges ifFalse:[
+            tabView displayLineFromX:x+i y:y+i toX:x+i y:yB.    "/ upper edge
+        ].
+        tabView displayLineFromX:x y:y+i toX:xR y:y+i.          "/ left edge
+    ].
+    tabView paint:shadowColor.
 
-    polygon at:1 put:(Point x:x            y:eY).
-    polygon at:2 put:(Point x:x            y:y2).
-    polygon at:3 put:(Point x:x3           y:y).
-    polygon at:4 put:(Point x:(x3+x2)      y:y).
-    polygon at:5 put:(Point x:(x3+x2+x1)   y:y2).
-    polygon at:6 put:(Point x:(eX-x1)      y:y2).
-    polygon at:7 put:(Point x:(eX)         y:(y2+y1)).
-    polygon at:8 put:(Point x:(eX)         y:eY).
+    0 to:tabLevel do:[:i |
+        tabView displayLineFromX:x+i y:yB-i toX:xR y:yB-i.       
+    ].
+
+!
+
+redrawAtRight:isSelected
+    "redraw tab at right of view
+    "
+    |origin corner y x xR yB tabLevel light roundedEdges shadowColor lightColor|
+
+    origin := self computeOrigin.
+    corner := self computeCorner.
+    x   := origin x.
+    y   := origin y.
+    xR  := corner x - 1.
+    yB  := corner y.
+
+    roundedEdges := tabView styleAt:#roundedEdges.
+    tabLevel     := (tabView styleAt:#tabLevel) - 1.
 
     isSelected ifFalse:[
-        tabView paintColor:#unselectedColor.
-        lightColor := tabView styleAt:#lightColorUnselected.
+        tabView paint:(tabView styleAt:#unselectedColor).
         shadowColor := tabView styleAt:#shadowColorUnselected.
+        lightColor  := tabView styleAt:#lightColorUnselected.
     ] ifTrue:[
-        tabView paintColor:#selectedColor.
-        lightColor := tabView styleAt:#lightColorSelected.
+        tabView paint:(tabView styleAt:#selectedColor).
         shadowColor := tabView styleAt:#shadowColorSelected.
+        lightColor  := tabView styleAt:#lightColorSelected.
     ].
+    tabView fillRectangle:(Rectangle left:0 top:y extent:(x @ extent y)).
+
+    roundedEdges ifTrue:[
+        tabView displayLineFromX:x y:y toX:x y:yB.
 
-    tabView fillPolygon:polygon.
+        tabView paint:lightColor.
+        tabView displayPointX:x y:y+1.
+        tabView displayPointX:x y:y+2.
+        tabView displayLineFromX:x+1 y:y+2 toX:x+1 y:yB-1.
+        tabView displayLineFromX:x+2 y:y+3 toX:x+2 y:yB-1.
+
+        tabView paint:shadowColor.
+
+        0 to:tabLevel do:[:i |
+            tabView displayPointX:x   y:yB-i.
+            tabView displayPointX:x+1 y:yB-i-1.
+            tabView displayPointX:x+2 y:yB-i-2.
+        ].
+    ].
     tabView paint:lightColor.
 
-    0 to:level do:[:i|
-        tabView displayLineFromX:(x+i)      y:(eY)     toX:(x+i)        y:(y2).
-        tabView displayLineFromX:(x+1)      y:(y2+i-1) toX:(x3+1)       y:(y+i-1).
-        tabView displayLineFromX:(x3+1)     y:(y+i)    toX:(x3+x2)      y:(y+i).
-        tabView displayLineFromX:(x3+x2)    y:(y+i)    toX:(x3+x2+x1)   y:(y2+i).
-        tabView displayLineFromX:(x3+x2+x1) y:(y2+i)   toX:(eX-x1)      y:(y2+i).
+    0 to:tabLevel do:[:i |
+        roundedEdges ifFalse:[
+            tabView displayLineFromX:x-i y:y+i toX:x-i y:yB.    "/ upper edge
+        ].
+        tabView displayLineFromX:x y:y+i+1 toX:0 y:y+i+1.       "/ left edge
+    ].
+    tabView paint:shadowColor.
+
+    0 to:tabLevel do:[:i |
+        tabView displayLineFromX:x-i+1 y:yB-i toX:1 y:yB-i.       
+    ].
+!
+
+redrawAtTop:isSelected
+    "redraw tab at top of view
+    "
+    |polygon origin corner y x xR yB tabLevel light roundedEdges shadowColor lightColor|
+
+    origin := self computeOrigin.
+    corner := self computeCorner.
+    x   := origin x.
+    y   := origin y.
+    xR  := corner x - 1.
+    yB  := corner y.
+
+    roundedEdges := tabView styleAt:#roundedEdges.
+    tabLevel     := (tabView styleAt:#tabLevel) - 1.
+
+    isSelected ifFalse:[
+        tabView paint:(tabView styleAt:#unselectedColor).
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+        lightColor  := tabView styleAt:#lightColorUnselected.
+    ] ifTrue:[
+        tabView paint:(tabView styleAt:#selectedColor).
+        shadowColor := tabView styleAt:#shadowColorSelected.
+        lightColor  := tabView styleAt:#lightColorSelected.
     ].
 
-    tabView paint:shadowColor.
-    0 to:level do:[:i|
-        tabView displayLineFromX:(eX-x1) y:(y2+i+1) toX:eX     y:(y2+y1+i).
-        tabView displayLineFromX:(eX-i)  y:(y2+y1)  toX:(eX-i) y:(eY).
-        tabView displayPointX:eX-x1-i y:y2+level
+    roundedEdges ifTrue:[ y :=  y + 2].
+    tabView fillRectangle:(Rectangle left:x top:y extent:((extent x) @ yB)).
+
+    roundedEdges ifTrue:[
+        y :=  y + 1.
+        tabView displayLineFromX:x y:y-1   toX:xR y:y-1.          
+        tabView displayLineFromX:x+1 y:y-2 toX:xR-1 y:y-2.
+        tabView displayLineFromX:x+2 y:y-3 toX:xR-2 y:y-3.
+        
+        tabView paint:lightColor.
+
+        0 to:tabLevel do:[:i |
+            tabView displayPointX:x+i y:y-1.
+            tabView displayPointX:x+1+i y:y-1-1.
+            tabView displayLineFromX:x+2+i y:y-3-i toX:xR-1-i y:y-3-i.  "/ top
+        ].
+
+        tabView paint:shadowColor.
+        0 to:tabLevel do:[:i |
+            tabView displayPointX:xR-i y:y.
+            tabView displayPointX:xR-i y:y-1.
+            tabView displayPointX:xR-1-i y:y-1-1.
+        ].
+        tabView displayPointX:xR-2 y:y-1-1-1.
+        tabView displayPointX:xR-3 y:y-1-1-1.
     ].
 
-
+    tabView paint:lightColor.
+    0 to:tabLevel do:[:i |
+        roundedEdges ifFalse:[
+            tabView displayLineFromX:x y:y+i toX:xR y:y+i.    "/ upper edge
+        ].
+        tabView displayLineFromX:x+i y:y toX:x+i y:yB.    "/ left edge
+    ].
+    tabView paint:shadowColor.
+    0 to:tabLevel do:[:i |
+        tabView displayLineFromX:xR-i y:y+i toX:xR-i y:yB.  "/ right edge
+    ].
 ! !
 
 !TabWidget class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TabWidget.st,v 1.3 1997-04-08 15:23:20 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabWidget.st,v 1.4 1997-04-22 16:56:29 ca Exp $'
 ! !