intitial checkin
authorca
Thu, 03 Apr 1997 19:35:04 +0200
changeset 343 dd49faa984ce
parent 342 9e7148fb27c4
child 344 deae51987b20
intitial checkin
TabView.st
TabWidget.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/TabView.st	Thu Apr 03 19:35:04 1997 +0200
@@ -0,0 +1,691 @@
+"
+ COPYRIGHT (c) 1997 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+
+View subclass:#TabView
+	instanceVariableNames:'leftInset list listHolder selection action tabStyle
+		lastIdInFirstLine'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Interactors'
+!
+
+!TabView class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1997 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+!
+
+documentation
+"
+    implements the tabs-view component of a noteBook.
+    May also be used on its own (without a surrounding noteBook).
+
+    The functionality is basically the same as provided by a
+    PopUpList or SelectionInListView, in that a valueHolder
+    gets a value assigned corresponding to the selected tab
+    from a list of possible tabs.
+
+    [author:]
+        Claus Atzkern
+
+    [see also:]
+        NoteBookView
+        SelectionInListView PopUpList ValueHolder
+"
+
+!
+
+examples
+"
+                                                                                [exBegin]                                      
+    |top sel view|
+
+    top := StandardSystemView new
+        label:'UI-Selection Panel';
+        extent:300@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.
+    view viewBackground:(sel styleAt:#selectedColor).
+
+    sel list:#( 'Button'
+                'Toggle'
+                'Panel'
+                'Text'
+                'View'
+                'Combo View'
+                'Menu'
+                'Scroller'
+              ).
+    sel action:[:indexOrNil|
+        Transcript showCR:indexOrNil
+    ].
+    top open.
+                                                                                [exEnd]                                      
+
+
+
+                                                                                [exBegin]                                      
+    |top sel view y|
+
+    top := StandardSystemView new
+        label:'UI-Selection Panel';
+        extent:450@300.
+
+    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.
+    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.
+
+    sel list:#( 'Button'
+                'Toggle'
+                'Claus Atzkern'
+                'Panel'
+                'Text'
+                'Peter'
+                'Loechgau'
+                'Text'
+              ).
+    top open.
+                                                                                [exEnd]                                      
+
+
+
+
+                                                                                [exBegin]                                      
+    |top sel view ctr l|
+
+    top := StandardSystemView new
+        label:'UI-Selection Panel';
+        extent:420@100.
+
+
+    sel  := self origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+
+    l := #(     'SBrowser'
+                'FBrowser'
+                'Debugger'
+              ).
+    sel list:(l collect:[:n | Image fromFile:'bitmaps/' , n , '.xbm']).
+
+    ctr := 0.
+    sel action:[:indexOrNil|
+        Transcript showCR:indexOrNil
+    ].
+    top open.
+                                                                                [exEnd]                                      
+
+                                                                                [exBegin]                                      
+    |top sel view ctr l top2 s top3 p|
+
+    l := SelectionInList new.
+    l list:#('foo' 'bar' 'baz').
+    l selectionIndex:1.
+
+    top2 := StandardSystemView new.
+    top2 extent:100@200.
+    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.
+    s := PopUpList in:top3.
+    s model:l.
+    top3 open.
+
+    top := StandardSystemView new
+        label:'UI-Selection Panel';
+        extent:400@100.
+
+
+    sel  := self origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
+    sel model:(l selectionIndexHolder).
+    sel listHolder:(l listHolder).
+
+    ctr := 0.
+    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'
+              ).
+    top open.
+                                                                                [exEnd]
+"
+! !
+
+!TabView class methodsFor:'defaults'!
+
+defaultTabWidget
+    ^ #Folder
+! !
+
+!TabView methodsFor:'accessing'!
+
+action:oneArgBlock
+    "set the action block to be performed on select; the argument to
+     the block is the selected index or nil in case of no selection.
+    "
+    action := oneArgBlock.
+
+!
+
+list
+    "return the list
+    "
+    ^ list
+!
+
+list:aList
+    "set the list
+    "
+    |widget|
+
+    selection := nil.
+    list := nil.
+
+    aList size ~~ 0 ifTrue:[
+        widget := tabStyle at:#widget.
+        list   := aList collect:[:aLabel|widget label:aLabel for:self].
+    ].
+
+    self shown ifTrue:[
+        self recomputeList.
+        self redrawFull.
+    ]
+!
+
+listHolder
+    "returns the list holder
+    "
+    ^ listHolder
+!
+
+listHolder:aValueHolder
+    "change the list holder
+    "
+    listHolder notNil ifTrue:[
+        listHolder removeDependent:self. 
+    ].
+    listHolder := aValueHolder.
+    listHolder notNil ifTrue:[
+        listHolder addDependent:self.
+        self list:listHolder value.
+        self selection:model value.
+    ].
+!
+
+model:aValueHolder
+    super model:aValueHolder.
+    model notNil ifTrue:[
+        self selection:(model value)
+    ]
+! !
+
+!TabView methodsFor:'accessing style'!
+
+styleAt:anIdentifier
+    "returns value for an identifier
+    "
+    ^ tabStyle at:anIdentifier
+!
+
+styleAt:anIdentifier put:something
+    "set value for an identifier
+    "
+    |list|
+
+    tabStyle at:anIdentifier put:something.
+    list := self list.
+
+    list size ~~ 0 ifTrue:[
+        list first styleChanged:anIdentifier to:something
+    ].
+!
+
+tabWidget:aWidget
+    "change tab widget class
+    "
+    |widget|
+
+    (tabStyle at:#widget) = aWidget ifFalse:[
+        (widget := TabWidget widgetClass:aWidget) notNil ifTrue:[
+            tabStyle := widget tabStyleOn:self.
+
+            self shown ifTrue:[
+                self recomputeList.
+                self redrawFull.
+            ]
+        ]
+    ].
+
+! !
+
+!TabView methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "any of my model changed
+    "
+    changedObject == model ifTrue:[
+        self selection:model value
+    ] ifFalse:[
+        changedObject == listHolder ifTrue:[
+            self list:(listHolder value)
+        ]
+    ]
+! !
+
+!TabView methodsFor:'drawing'!
+
+paintColor:aColorSymbol
+    "set paint to a color from the style identified by its symbol
+    "
+    self paint:(tabStyle at:aColorSymbol)
+!
+
+redrawFull
+    "redraw list and boarders
+    "
+    |list size x1 x2 y1 y2 space|
+
+    list := self list.
+    size := list size.
+
+    (size ~~ 0 and:[self shown]) ifFalse:[
+        ^ self
+    ].
+    space := tabStyle at:#vspace.
+
+    self paint:(self viewBackground).
+    self clear.
+
+ "/ redraw view boarders
+    space ~~ 0 ifTrue:[
+        x1 := tabStyle at:#hspace.
+        y1 := self extent y - space.
+        x2 := self extent x.
+
+        self paintColor:#labelColor.
+
+        (size+1) timesRepeat:[
+            self displayLineFrom:(0 @ y1) to:(x2 @ y1).
+            y1 := y1 - space.
+        ]
+    ].
+
+ "/ redraw list
+    list do:[:aTab|aTab redraw:false].
+    selection notNil ifTrue:[self showSelected].
+!
+
+redrawX:x y:y width:w height:h
+    "a region must be redrawn
+    "
+    self redrawFull
+! !
+
+!TabView methodsFor:'event handling'!
+
+buttonPress:button x:x y:y
+    "a button is pressed
+    "
+    |size list|
+
+    list := self list.
+    size := list size.
+
+ "/ find tab under point; update selection
+    size to:1 by:-1 do:[:anIndex|
+        ((list at:anIndex) containsPoint:(x@y)) ifTrue:[
+            ^ self selection:anIndex
+        ]
+    ].
+    self selection:nil
+!
+
+sizeChanged:how
+    "size of view changed 
+    "
+    self recomputeList.
+
+! !
+
+!TabView methodsFor:'initialization'!
+
+initialize
+    "setup default attributes
+    "
+    |widget|
+
+    super initialize.
+    widget   := TabWidget widgetClass:(self class defaultTabWidget).
+    tabStyle := widget tabStyleOn:self.
+    leftInset := 0.
+! !
+
+!TabView methodsFor:'layout'!
+
+fitLines
+    "fit line
+    "
+    |stop start y extX orgX list width tab dlt|
+
+    list  := self list.
+    stop  := list size.
+    width := self extent x.
+
+    [stop ~~ 0] whileTrue:[
+        start := stop.
+        y := (list at:start) origin y.
+
+        [ ((stop := stop -1) ~~ 0 and:[((list at:stop) origin y) == y])]whileTrue.
+
+        stop == 0 ifTrue:[
+            start == list size ifFalse:[^ 0]
+        ].
+        stop  := stop + 1.
+        tab   := list at:stop.
+        orgX  := width - (tab origin x + tab extent x).
+        (dlt  := start - stop) <= 0 ifTrue:[^ self].
+        extX  := orgX // dlt.
+        orgX  := 0.
+
+        start to:stop by:-1 do:[:i||ext org|
+            tab := list at:i.
+            ext := tab extent.
+            org := tab origin.
+            org x:(org x + orgX).
+
+            i ~~ stop ifTrue:[ext x:(ext x + extX)]
+                     ifFalse:[ext x:(width - org x)].
+
+            tab extent:ext.
+            tab origin:org.
+            orgX := orgX + extX.
+        ].
+        stop := stop - 1.
+    ]
+
+!
+
+recomputeFixedLayout
+    "recompute tabs
+    "
+    |tab lnNr list deltaY size x y hspace width ovlap noLn|
+
+    list := self list.
+    size := list size.
+    hspace := tabStyle at:#hspace.
+    width  := self extent x - leftInset.
+
+    deltaY := list first preferredExtent y.
+    x := leftInset.
+    y := self extent y.
+    lnNr  := 1.
+    ovlap := tabStyle at:#leftOverLap.
+    noLn := 1.
+    lastIdInFirstLine := nil.
+
+    list reverseDo:[:aTab||e n|
+        e := aTab preferredExtent.
+        n := e x + x - ovlap.
+
+        n > width ifTrue:[
+            lastIdInFirstLine isNil ifTrue:[
+                lastIdInFirstLine := size+1.
+            ].
+            noLn := noLn + 1.
+            lnNr := lnNr + 1.
+            x := leftInset.
+            y := y - deltaY.
+            n := e x + x - ovlap.
+        ].
+        aTab origin:x@(y - deltaY) extent:e inset:0.
+        x := n + hspace.
+        size := size - 1.
+    ].
+    lastIdInFirstLine isNil ifTrue:[
+        lastIdInFirstLine := 1
+    ].
+    self fitLines.
+!
+
+recomputeList
+    "recompute tabs
+    "
+    |list numCols numLn tabOffset size extent width x y 
+     ovlap extX hspace origin ctr bottomInset vspace|
+
+    list := self list.
+    size := list size.
+    size == 0 ifTrue:[^ self].
+
+    (tabStyle at:#fixedLabelSize) ifTrue:[
+        ^ self recomputeFixedLayout
+    ].
+
+ "/ compute preferred extent
+
+    x     := 10.
+    y     := 10.
+    hspace:= tabStyle at:#hspace.
+    ovlap := tabStyle at:#leftOverLap.
+
+    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).
+
+ "/ calculate tabOffset, numCols and numLn
+
+    numCols < 2 ifTrue:[
+        numCols   := 1.
+        numLn := size.
+    ] ifFalse:[
+        numCols > size ifTrue:[
+            numCols := size
+        ].
+
+        numLn := (size + numCols - 1) // numCols.
+        tabOffset := (numLn * hspace) + extX.
+
+        (numCols * tabOffset) > width ifTrue:[
+            numCols := numCols - 1.
+            numLn := (size + numCols - 1) // numCols.
+        ]
+    ].
+    tabOffset := width // numCols.
+
+ "/ calculate extent x
+    extent x:(tabOffset - (numLn * hspace) + ovlap).
+
+    vspace := tabStyle at:#vspace.
+    bottomInset := vspace.
+    y   := self extent y - vspace - extent y.
+    x   := leftInset.
+    ctr := 1.
+    lastIdInFirstLine := size - numCols + 1.
+
+    list reverseDo:[:aTab|
+        aTab origin:x@y extent:extent inset:bottomInset.
+        bottomInset := bottomInset + vspace.
+
+        (ctr := ctr + 1) > numCols ifTrue:[
+            origin := (list at:size) origin.
+            size   := size - numCols.
+            y      := origin y - extent y.
+            x      := origin x + hspace.
+            ctr    := 1.
+        ] ifFalse:[
+            x := x + tabOffset.
+            y := y - vspace.
+        ]
+    ]
+! !
+
+!TabView methodsFor:'selection'!
+
+selection
+    "return the selection index or nil
+    "
+    ^ selection
+!
+
+selection:anIndexOrNil
+    "change the selection to index or nil. The model and/or actionBlock is notified
+    "
+    |oldSelection|
+
+    oldSelection := selection.
+    self setSelection:anIndexOrNil.
+
+    (oldSelection ~~ selection) ifTrue:[
+        model notNil ifTrue:[
+            model value:selection
+        ].
+
+        action notNil ifTrue:[
+            action value:selection
+        ]
+    ]
+
+!
+
+setSelection:anIndexOrNil
+    "change the selection to index or nil. No notifications are raised
+    "
+    selection ~~ anIndexOrNil ifTrue:[
+        selection notNil ifTrue:[
+            selection := nil.
+            self redrawFull
+        ].
+        selection := anIndexOrNil.
+        self showSelected
+    ]
+
+!
+
+showSelected
+    "draw current selection as selected
+    "
+    |tab list size savOrg savExt expSel savIns setIns newExt ctr x1 x2|
+
+    list := self list.
+    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.
+    newExt   := savExt + (expSel x@0).
+
+    (tabStyle at:#vspace) == 0 ifTrue:[setIns := 0]
+                              ifFalse:[setIns := savIns].
+
+    x1  := savOrg x.
+    ctr := self extent x.
+    (x2  := x1 + newExt x) > ctr ifTrue:[
+        x2 := ctr - x1.
+        newExt x:x2.
+    ].
+
+    tab origin:(savOrg - (0 @ (expSel y))) extent:newExt inset:setIns.
+    tab redraw:true.
+    tab origin:savOrg extent:savExt inset:savIns.
+
+    (selection < lastIdInFirstLine or:[(tabStyle at:#hspace) ~~ 0]) ifTrue:[
+        ctr := selection + 1.
+
+        ctr to:size do:[:i||tX1 tX2 draw|
+            tab := list at:i.
+            tX1 := tab origin x.
+            tX2 := tX1 + tab extent x.
+
+            tX1 >= x1 ifTrue:[draw := tX1 < x2]
+                     ifFalse:[draw := tX2 > x1].
+
+            draw ifTrue:[
+                tab redraw:false.
+                x1 > tX1 ifTrue:[x1 := tX1].
+                x2 < tX2 ifTrue:[x2 := tX2].
+            ]
+        ]
+    ]
+
+! !
+
+!TabView class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabView.st,v 1.1 1997-04-03 17:34:45 ca Exp $'
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/TabWidget.st	Thu Apr 03 19:35:04 1997 +0200
@@ -0,0 +1,573 @@
+"
+ COPYRIGHT (c) 1997 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+
+
+Object subclass:#TabWidget
+	instanceVariableNames:'tabView label origin extent inset'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Interactors'
+!
+
+TabWidget subclass:#Folder
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:TabWidget
+!
+
+TabWidget subclass:#Window
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:TabWidget
+!
+
+TabWidget subclass:#Mac
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:TabWidget
+!
+
+!TabWidget class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1997 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+
+!
+
+documentation
+"
+    instances represent (& draw) the tabs of a tabWidget.
+
+    [author:]
+        Claus Atzkern
+
+    [see also:]
+        TabView
+"
+! !
+
+!TabWidget class methodsFor:'instance creation'!
+
+label:aLabel for:aTabView
+    "create tab
+    "
+    ^ self new label:aLabel for:aTabView
+! !
+
+!TabWidget class methodsFor:'accessing'!
+
+tabStyleOn:aView
+    "returns default tab style
+    "
+    |style selectedColor unselectedColor|
+
+    style    := IdentityDictionary new.
+    selectedColor   := Color gray:90.
+    unselectedColor := Color gray:75.
+
+    style at:#widget put:self.
+
+    style at:#shadowColorSelected
+         put:((selectedColor averageColorIn:(0@0 corner:7@7)) darkened  on:aView device).
+
+    style at:#lightColorSelected
+         put:((selectedColor averageColorIn:(0@0 corner:7@7)) lightened on:aView device).
+
+    style at:#shadowColorUnselected
+         put:((unselectedColor averageColorIn:(0@0 corner:7@7)) darkened  on:aView device).
+
+    style at:#lightColorUnselected
+         put:((unselectedColor averageColorIn:(0@0 corner:7@7)) lightened on:aView device).
+
+    style at:#unselectedColor  put:unselectedColor.
+    style at:#selectedColor    put:selectedColor.
+    style at:#labelColor       put:(Color black).
+
+    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:#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
+!
+
+widgetClass:aWidget
+    |wdg nm|
+
+    nm := aWidget asString.
+
+    (wdg := Smalltalk classNamed:(self name asString, '::', nm)) notNil ifTrue:[
+        ^ wdg
+    ].
+    ^ Smalltalk classNamed:nm
+! !
+
+!TabWidget class methodsFor:'constants'!
+
+defaultExtent
+    ^ 80 @ 25
+
+
+!
+
+labelLeftInset
+    ^ 4
+! !
+
+!TabWidget methodsFor:'accessing'!
+
+extent
+    "return the tab extent
+    "
+    ^ extent
+!
+
+extent:anExtent
+    "change the tab extent; no redraw
+    "
+    extent := anExtent
+!
+
+inset
+    "returns the bottom inset starting from 1.0
+    "
+    ^ inset
+!
+
+inset:anInset
+    "change the bottom inset starting from 1.0; no redraw
+    "
+    inset := anInset
+!
+
+labelOrigin
+    "returns origin of label
+    "
+  ^ (self labelOriginWithinFrame)
+     + ((tabView styleAt:#leftOverLap) @ (tabView styleAt:#lableTopInset))
+!
+
+origin
+    "returns the tab origin
+    "
+    ^ origin
+
+!
+
+origin:anOrigin
+    "change the tab origin; no redraw
+    "
+    origin := anOrigin
+
+!
+
+origin:anOrigin extent:anExtent inset:anInset
+    "change origin, extent and bottom inset starting from 1.0; no redraw
+    "
+    origin := anOrigin.
+    extent := anExtent.
+    inset  := anInset.
+
+
+!
+
+preferredExtent
+    "returns my preferred extent
+    "
+    |x y|
+
+    label isNil ifTrue:[
+        ^ self class defaultExtent
+    ].
+    x := 2 + (label  widthOn:tabView).
+    y :=   (label heightOn:tabView)
+         + (tabView styleAt:#labelBottomInset)
+         + (tabView styleAt:#lableTopInset).
+
+  ^ ((self labelOrigin) + (x@y))
+! !
+
+!TabWidget methodsFor:'drawing'!
+
+redraw:isSelected
+    "full redraw
+    "
+    |p y|
+
+    self redrawSelected:isSelected.
+    tabView paintColor:#labelColor.
+    p := origin  + self labelOrigin.
+    y := p y.
+
+    label isString ifTrue:[
+        y := y + tabView font ascent
+    ].
+    label displayOn:tabView x:(p x) y:y.
+! !
+
+!TabWidget methodsFor:'initialization'!
+
+label:aLabel for:aTabView
+    "initialize attributes
+    "
+    tabView     := aTabView.
+    label       := aLabel.
+! !
+
+!TabWidget methodsFor:'queries'!
+
+containsPoint:aPoint
+    "return true, if the aPoint is contained in the tab
+    "
+    |x|
+
+    x := aPoint x.
+
+    (x > origin x and:[aPoint y > origin y]) ifTrue:[
+        ^ x < (origin x + extent x)
+    ].
+    ^ false.
+! !
+
+!TabWidget methodsFor:'redefine'!
+
+labelOriginWithinFrame
+    "returns the offset from origin to the origin of the label
+    "
+    ^ (self class labelLeftInset) @ 0
+
+!
+
+redrawSelected:isSelected
+    "full redraw excluding the label
+    "
+    ^ self subclassResponsibility
+!
+
+styleChanged:anIdentifier to:someThing
+    "any style changed; could be redifined in subclass
+    "
+    |dark light|
+
+    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).
+
+! !
+
+!TabWidget::Folder class methodsFor:'accessing'!
+
+tabStyleOn:aView
+    |style|
+
+    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
+
+
+! !
+
+!TabWidget::Folder class methodsFor:'constants'!
+
+folderTabSize
+    ^ 4@4
+
+
+! !
+
+!TabWidget::Folder methodsFor:'redefined'!
+
+labelOriginWithinFrame
+    |org|
+
+    org := super labelOriginWithinFrame.
+    org  y:(org y + self class folderTabSize y).
+  ^ org
+
+!
+
+redrawSelected:isSelected
+    "full redraw; excluding the label
+    "
+    |lightColor shadowColor polygon fs x y y1 y2 x1 x2 x3 eX eY level|
+
+    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.
+
+    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).
+
+    isSelected ifFalse:[
+        tabView paintColor:#unselectedColor.
+        lightColor := tabView styleAt:#lightColorUnselected.
+        shadowColor := tabView styleAt:#shadowColorUnselected.
+    ] ifTrue:[
+        tabView paintColor:#selectedColor.
+        lightColor := tabView styleAt:#lightColorSelected.
+        shadowColor := tabView styleAt:#shadowColorSelected.
+    ].
+
+    tabView fillPolygon:polygon.
+    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).
+    ].
+
+    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
+    ].
+
+
+! !
+
+!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
+
+
+
+! !
+
+!TabWidget::Window methodsFor:'redifined'!
+
+labelOriginWithinFrame
+    |org|
+
+    org := super labelOriginWithinFrame.
+  ^ org + (tabView styleAt:#tabLevel)
+
+
+!
+
+redrawSelected:isSelected
+    "redraw; set fill-color to aColor.
+    "
+    |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.
+
+    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.
+        yB := yB + 1
+    ].
+
+
+    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 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
+    ].
+
+    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
+    ]
+
+
+! !
+
+!TabWidget::Mac class methodsFor:'accessing'!
+
+tabStyleOn:aView
+    |style col|
+
+    style := super tabStyleOn:aView.
+
+    style at:#fixedLabelSize   put:true.
+    style at:#leftOverLap      put:10.
+  ^ 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
+    "
+    |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.
+    x  := origin x.
+    y  := origin y.
+    eX := x + extent x - 1.
+    eY := tabView extent y - inset.
+    x1 := eX - self class rightInset.
+
+    polygon at:1 put:(Point x:x      y:eY).
+    polygon at:2 put:(Point x:x      y:y).
+    polygon at:3 put:(Point x:x1     y:y).
+    polygon at:4 put:(Point x:eX     y:(y+extent y)).
+    polygon at:5 put:(Point x:eX     y:eY).
+
+    tabView paint:color.
+    tabView fillPolygon:polygon.
+
+    tabView paint:lightColor.
+    tabView displayLineFromX:x+1 y:eY toX:x+1 y:y+1.
+    tabView displayLineFromX:x+1 y:y+1 toX:x1-1 y:y+1.
+
+    tabView paintColor:#labelColor.
+    tabView displayPolygon:polygon.
+
+    isSelected ifFalse:[
+        tabView paint:shadowColor.
+        tabView displayLineFromX:x y:eY-1 toX:eX y:eY-1.
+    ]
+
+
+! !
+
+!TabWidget class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabWidget.st,v 1.1 1997-04-03 17:35:04 ca Exp $'
+! !