TabWidget.st
changeset 367 cff1a140978f
parent 351 6c46f186d84f
child 369 8f003e44d5ef
--- 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 $'
 ! !