TabWidget.st
changeset 343 dd49faa984ce
child 350 cb420d4899ab
--- /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 $'
+! !