ArrowButton.st
author Claus Gittinger <cg@exept.de>
Thu, 06 Mar 1997 22:44:17 +0100
changeset 1105 980fe41d7f0a
parent 1053 b9f8bf97815c
child 1137 5ec9db9453f1
permissions -rw-r--r--
assign colorMap AFTER conversion to a device form if image is a deep form. Otherwise, the colors may be reclaimed, leading to wrong colors on the screen.

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      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.
"

Button subclass:#ArrowButton
	instanceVariableNames:'arrowStyle direction'
	classVariableNames:'DownArrowForm UpArrowForm LeftArrowForm RightArrowForm
		CachedStyle DefaultArrowStyle DefaultBackgroundColor
		DefaultForegroundColor DefaultActiveBackgroundColor
		DefaultActiveForegroundColor DefaultEnteredBackgroundColor
		DefaultEnteredForegroundColor DefaultDisabledForegroundColor
		DefaultArrowButtonActiveLevel DefaultArrowButtonPassiveLevel
		DownArrowFormFile UpArrowFormFile LeftArrowFormFile
		RightArrowFormFile'
	poolDictionaries:''
	category:'Views-Interactors'
!

!ArrowButton class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      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
"
    ArrowButtons display an arrow as their label; they are mainly
    used for scrollbars, but can be useful on their own in some applications.
    Beside the contents, their default behavior is to perform their action
    when pressed - not (as is the default for normal buttons) when released.

    Indivdual ArrowButtons can be created by sending one of:
            ArrowButton upIn:aView /downIn: / leftIn: or rightIn:
    passing the parent view as argument.

    See examples.


    [styleSheet parameters:]

        arrowButtonStyle            <Symbol>        the style of the button;
                                                    #motif, #st80 or nil (default)
        arrowButtonForegroundColor  <nil | Color>   foregroundColor 
        arrowButtonBackgroundColor  <nil | Color>   backgroundColor 

        arrowButtonActiveForegroundColor            foregroundColor when pressed
        arrowButtonActiveBackgroundColor            backgroundColor when pressed

        arrowButtonEnteredForegroundColor           foregroundColor when mouse pointer entered
        arrowButtonEnteredBackgroundColor           backgroundColor when mouse pointer entered

    [author:]
        Claus Gittinger

    [See also:]
         Button  Toggle CheckToggle CheckBox
         ScrollBar

"
!

examples 
"
    example1:
                                                                        [exBegin]
        |v p b1 b2 b3 b4|

        v := StandardSystemView extent:200@200.
        p := HorizontalPanelView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:v.
        b1 := ArrowButton upIn:p.
        b2 := ArrowButton downIn:p.
        b3 := ArrowButton leftIn:p.
        b4 := ArrowButton rightIn:p.

        b1 action:['whatEver you like here ...'].
        b2 action:['whatEver you like here ...'].
        b3 action:['whatEver you like here ...'].
        b4 action:['whatEver you like here ...'].

        v open
                                                                        [exEnd]


    example2:
                                                                        [exBegin]
        |v p b1 b2 b3 b4|

        v := StandardSystemView extent:200@200.
        p := HorizontalPanelView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:v.
        b1 := (ArrowButton upIn:p) extent:30@30.
        b2 := (ArrowButton downIn:p) extent:30@30.
        b3 := (ArrowButton leftIn:p) extent:30@30.
        b4 := (ArrowButton rightIn:p) extent:30@30.

        b1 action:['whatEver you like here ...'].
        b2 action:['whatEver you like here ...'].
        b3 action:['whatEver you like here ...'].
        b4 action:['whatEver you like here ...'].

        v open
                                                                        [exEnd]


    example3:
                                                                        [exBegin]
        |v p b1 b2 b3 b4|

        v := StandardSystemView extent:200@200.
        p := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:v.
        b1 := (ArrowButton upIn:p) origin:(0.33 @ 0.0) corner:(0.67 @ 0.33).
        b3 := (ArrowButton leftIn:p) origin:(0.0 @ 0.33) corner:(0.33 @ 0.67).
        b4 := (ArrowButton rightIn:p) origin:(0.67 @ 0.33) corner:(1.0 @ 0.67).
        b2 := (ArrowButton downIn:p) origin:(0.33 @ 0.67) corner:(0.67 @ 1.0).

        b1 action:['whatEver you like here ...'].
        b2 action:['whatEver you like here ...'].
        b3 action:['whatEver you like here ...'].
        b4 action:['whatEver you like here ...'].

        v open
                                                                        [exEnd]


    example4 (not good coding style, to explicitely use a particular style,
              just a demonstration how it looks ..):
                                                                        [exBegin]
        |v p b1 b2 b3 b4 oldStyle|

        oldStyle := View defaultStyle.
        View defaultStyle:#motif.

        v := StandardSystemView extent:100@100.
        p := View origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:v.

        b1 := (ArrowButton upIn:p) origin:(0.33 @ 0.0) corner:(0.67 @ 0.33).
        b3 := (ArrowButton leftIn:p) origin:(0.0 @ 0.33) corner:(0.33 @ 0.67).
        b4 := (ArrowButton rightIn:p) origin:(0.67 @ 0.33) corner:(1.0 @ 0.67).
        b2 := (ArrowButton downIn:p) origin:(0.33 @ 0.67) corner:(0.67 @ 1.0).

        b1 action:['whatEver you like here ...'].
        b2 action:['whatEver you like here ...'].
        b3 action:['whatEver you like here ...'].
        b4 action:['whatEver you like here ...'].

        View defaultStyle:oldStyle.
        v open
                                                                        [exEnd]
"
! !

!ArrowButton class methodsFor:'instance creation'!

downIn:aView
    "create and return a new down-button in aView"

    ^ (super in:aView) direction:#down

    "Modified: 22.1.1997 / 11:59:08 / cg"
!

leftIn:aView
    "create and return a new left-button in aView"

    ^ (super in:aView) direction:#left

    "Modified: 22.1.1997 / 11:59:14 / cg"
!

new
    "return a new arrowButton - direction defaults to #up"

    ^ super new direction:#up
!

rightIn:aView
    "create and return a new right-button in aView"

    ^ (super in:aView) direction:#right

    "Modified: 22.1.1997 / 11:59:21 / cg"
!

upIn:aView
    "create and return a new up-button in aView"

    ^ (super in:aView) direction:#up

    "Modified: 22.1.1997 / 11:59:27 / cg"
! !

!ArrowButton class methodsFor:'defaults'!

defaultDownArrowButtonForm
    "return the default form used for the scrollDown Button 
     (if no styleSheet value is defined, and no form can be constructed)"

    <resource: #image>

    ^ Form width:16 height:16 
                  fromArray:#[2r00000000 2r00000000
                              2r00001111 2r11110000
                              2r00001000 2r00010000
                              2r00001000 2r00010000
                              2r00001000 2r00010000
                              2r00001000 2r00010000
                              2r00001000 2r00010000
                              2r01111000 2r00011110
                              2r01000000 2r00000010
                              2r00100000 2r00000100
                              2r00010000 2r00001000
                              2r00001000 2r00010000
                              2r00000100 2r00100000
                              2r00000010 2r01000000
                              2r00000001 2r10000000
                              2r00000000 2r00000000]

    "
     self defaultDownArrowButtonForm
    "

!

defaultLeftArrowButtonForm
    "return the default form used for the scrollLeft Button
     (if no styleSheet value is defined, and no form can be constructed)"

    <resource: #image>

    ^ Form width:16 height:16 
                     fromArray:#[2r00000000 2r00000000
                                 2r00000001 2r10000000
                                 2r00000010 2r10000000
                                 2r00000100 2r10000000
                                 2r00001000 2r11111110
                                 2r00010000 2r00000010
                                 2r00100000 2r00000010
                                 2r01000000 2r00000010
                                 2r01000000 2r00000010
                                 2r00100000 2r00000010
                                 2r00010000 2r00000010
                                 2r00001000 2r11111110
                                 2r00000100 2r10000000
                                 2r00000010 2r10000000
                                 2r00000001 2r10000000
                                 2r00000000 2r00000000]

    "
     self defaultLeftArrowButtonForm
    "

!

defaultRightArrowButtonForm
    "return the default form used for the scrollRight Button 
     (if no styleSheet value is defined, and no form can be constructed)"

    <resource: #image>

    ^ Form width:16 height:16 
                     fromArray:#[2r00000000 2r00000000
                                 2r00000001 2r10000000
                                 2r00000001 2r01000000
                                 2r00000001 2r00100000
                                 2r01111111 2r00010000
                                 2r01000000 2r00001000
                                 2r01000000 2r00000100
                                 2r01000000 2r00000010
                                 2r01000000 2r00000010
                                 2r01000000 2r00000100
                                 2r01000000 2r00001000
                                 2r01111111 2r00010000
                                 2r00000001 2r00100000
                                 2r00000001 2r01000000
                                 2r00000001 2r10000000
                                 2r00000000 2r00000000]

    "
     self defaultRightArrowButtonForm
    "

!

defaultUpArrowButtonForm
    "return the default form used for the scrollUp Button 
     (if no styleSheet value is defined, and no form can be constructed)"

    <resource: #image>

    ^ Form width:16 height:16 
                     fromArray:#[2r00000000 2r00000000
                                 2r00000001 2r10000000
                                 2r00000010 2r01000000
                                 2r00000100 2r00100000
                                 2r00001000 2r00010000
                                 2r00010000 2r00001000
                                 2r00100000 2r00000100
                                 2r01000000 2r00000010
                                 2r01111000 2r00011110
                                 2r00001000 2r00010000
                                 2r00001000 2r00010000
                                 2r00001000 2r00010000
                                 2r00001000 2r00010000
                                 2r00001000 2r00010000
                                 2r00001111 2r11110000
                                 2r00000000 2r00000000]

    "
     self defaultUpArrowButtonForm
    "

!

downArrowButtonForm:style on:aDevice
    "return the form used for the scrollDown Button"

    <resource: #style (#arrowButtonDownForm)>

    |form|

    "
     use cached form, if device is appropriate
    "
    CachedStyle ~~ style ifTrue:[
        UpArrowForm := DownArrowForm := LeftArrowForm := RightArrowForm := nil
    ].

    ((aDevice == Display) and:[DownArrowForm notNil]) ifTrue:[
        ^ DownArrowForm
    ].

    DownArrowForm := StyleSheet at:'arrowButtonDownForm' default:nil.
    DownArrowForm notNil ifTrue:[
        ^ DownArrowForm
    ].

    "
     special treatment for st80 arrows 
     - they do not really fit into the general (bitmap) scheme ...
     (i.e. they are computed instead of drawn from a bitmap)
    "
    style ~~ #st80 ifTrue:[
        DownArrowFormFile notNil ifTrue:[
            form := Image fromFile:DownArrowFormFile resolution:100 on:aDevice.
            form isNil ifTrue:[
                form := Image fromFile:('bitmaps/' , DownArrowFormFile) resolution:100 on:aDevice.
                form isNil ifTrue:[
                    'ArrowButton [info]: no bitmapFile: ' infoPrint. DownArrowFormFile infoPrintCR.
                ]
            ]
        ]
    ].

    "
     form to use as a fallback, if no bitmap file is present
     (actually not really needed - just to show something useful, in
      case of a bad installation)
    "
    form isNil ifTrue:[
        style == #st80 ifTrue:[
            form := Form width:9 height:9 depth:1 on:Display.
            form isNil ifTrue:[^ nil].
            form clear.
            form lineWidth:2.
            form capStyle:#round.
            form paint:(Color colorId:1).
            form displayLineFromX:0 y:2 toX:4 y:6.
            form displayLineFromX:4 y:6 toX:8 y:2.
            form beImmediateForm.
        ] ifFalse:[
            form  := self defaultDownArrowButtonForm on:aDevice.
            form isNil ifTrue:[^ nil].
        ].
    ].

    "
     remember form for next use
    "
    (aDevice == Display) ifTrue:[
        CachedStyle := style.
        DownArrowForm := form
    ].

    ^ form

    "Modified: 17.1.1997 / 23:15:17 / cg"
!

leftArrowButtonForm:style on:aDevice
    "return the form used for the scrollLeft Button"

    <resource: #style (#arrowButtonLeftForm)>

    |form|

    "
     use cached form, if device is appropriate
    "
    CachedStyle ~~ style ifTrue:[
        UpArrowForm := DownArrowForm := LeftArrowForm := RightArrowForm := nil
    ].

    ((aDevice == Display) and:[LeftArrowForm notNil]) ifTrue:[
        ^ LeftArrowForm
    ].

    LeftArrowForm := StyleSheet at:'arrowButtonLeftForm' default:nil.
    LeftArrowForm notNil ifTrue:[
        ^ LeftArrowForm
    ].

    "
     special treatment for st80 arrows 
     - they do not really fit into the general (bitmap) scheme ...
     (i.e. they are computed instead of drawn from a bitmap)
    "
    style ~~ #st80 ifTrue:[
        LeftArrowFormFile notNil ifTrue:[
            form := Image fromFile:LeftArrowFormFile resolution:100 on:aDevice.
            form isNil ifTrue:[
                form := Image fromFile:'bitmaps/' , LeftArrowFormFile resolution:100 on:aDevice.
                form isNil ifTrue:[
                    'ArrowButton [info]: no bitmapFile: ' infoPrint. LeftArrowFormFile infoPrintCR.
                ]
            ]
        ]
    ].

    "
     form to use as a fallback, if no bitmap file is present
     (actually not really needed - just to show something useful, in
      case of a bad installation)
    "
    form isNil ifTrue:[
        style == #st80 ifTrue:[
            form := Form width:9 height:9 depth:1 on:Display.
            form isNil ifTrue:[^ nil].
            form clear.
            form lineWidth:2.
            form capStyle:#round.
            form paint:(Color colorId:1).
            form displayLineFromX:6 y:0 toX:2 y:4.
            form displayLineFromX:2 y:4 toX:6 y:8.
            form beImmediateForm.
        ] ifFalse:[
            form  := self defaultLeftArrowButtonForm on:aDevice.
            form isNil ifTrue:[^ nil].
        ].
    ].

    "
     remember form for next use
    "
    (aDevice == Display) ifTrue:[
        CachedStyle := style.
        LeftArrowForm := form
    ].

    ^ form

    "Modified: 17.1.1997 / 23:15:14 / cg"
!

rightArrowButtonForm:style on:aDevice
    "return the form used for the scrollRight Button"

    <resource: #style (#arrowButtonRightForm)>

    |form|

    "
     use cached form, if device is appropriate
    "
    CachedStyle ~~ style ifTrue:[
        UpArrowForm := DownArrowForm := LeftArrowForm := RightArrowForm := nil
    ].

    ((aDevice == Display) and:[RightArrowForm notNil]) ifTrue:[
        ^ RightArrowForm
    ].

    RightArrowForm := StyleSheet at:'arrowButtonRightForm' default:nil.
    RightArrowForm notNil ifTrue:[
        ^ RightArrowForm
    ].

    "
     special treatment for st80 arrows 
     - they do not really fit into the general (bitmap) scheme ...
     (i.e. they are computed instead of drawn from a bitmap)
    "
    style ~~ #st80 ifTrue:[
        RightArrowFormFile notNil ifTrue:[
            form := Image fromFile:RightArrowFormFile resolution:100 on:aDevice.
            form isNil ifTrue:[
                form := Image fromFile:'bitmaps/' , RightArrowFormFile resolution:100 on:aDevice.
                form isNil ifTrue:[
                    'ArrowButton [info]: no bitmapFile: ' infoPrint. RightArrowFormFile infoPrintCR.
                ]
            ]
        ]
    ].

    "
     form to use as a fallback, if no bitmap file is present
     (actually not really needed - just to show something useful, in
      case of a bad installation)
    "
    form isNil ifTrue:[
        style == #st80 ifTrue:[
            form := Form width:9 height:9 depth:1 on:Display.
            form isNil ifTrue:[^ nil].
            form clear.
            form lineWidth:2.
            form capStyle:#round.
            form paint:(Color colorId:1).
            form displayLineFromX:2 y:0 toX:6 y:4.
            form displayLineFromX:6 y:4 toX:2 y:8.
            form beImmediateForm.
        ] ifFalse:[
            form  := self defaultRightArrowButtonForm on:aDevice.
            form isNil ifTrue:[^ nil].
        ].
    ].

    "
     remember form for next use
    "
    (aDevice == Display) ifTrue:[
        CachedStyle := style.
        RightArrowForm := form
    ].

    ^ form

    "Modified: 17.1.1997 / 23:15:20 / cg"
!

upArrowButtonForm:style on:aDevice
    "return the form used for the scrollUp Button"

    <resource: #style (#arrowButtonUpForm)>

    |form|

    "
     use cached form, if device is appropriate
    "
    CachedStyle ~~ style ifTrue:[
        UpArrowForm := DownArrowForm := LeftArrowForm := RightArrowForm := nil
    ].

    ((aDevice == Display) and:[UpArrowForm notNil]) ifTrue:[
        ^ UpArrowForm
    ].

    UpArrowForm := StyleSheet at:'arrowButtonUpForm' default:nil.
    UpArrowForm notNil ifTrue:[
        ^ UpArrowForm
    ].

    "
     special treatment for st80 arrows 
     - they do not really fit into the general (bitmap) scheme ...
     (i.e. they are computed instead of drawn from a bitmap)
    "
    style ~~ #st80 ifTrue:[
        UpArrowFormFile notNil ifTrue:[
            form := Image fromFile:UpArrowFormFile resolution:100 on:aDevice.
            form isNil ifTrue:[
                form := Image fromFile:'bitmaps/' , UpArrowFormFile resolution:100 on:aDevice.
                form isNil ifTrue:[
                    'ArrowButton [info]: no bitmapFile: ' infoPrint. UpArrowFormFile infoPrintCR.
                ]
            ]
        ]
    ].

    "
     form to use as a fallback, if no bitmap file is present
     (actually not really needed - just to show something useful, in
      case of a bad installation)
    "
    form isNil ifTrue:[
        style == #st80 ifTrue:[
            form := Form width:9 height:9 depth:1 on:aDevice.
            form isNil ifTrue:[^ nil].
            form clear.
            form lineWidth:2.
            form capStyle:#round.
            form paint:(Color colorId:1).
            form displayLineFromX:0 y:6 toX:4 y:2.
            form displayLineFromX:4 y:2 toX:8 y:6.
            form beImmediateForm.
        ] ifFalse:[
            form  := self defaultUpArrowButtonForm on:aDevice.
            form isNil ifTrue:[^ nil].
        ].
    ].

    "
     remember form for next use
    "
    (aDevice == Display) ifTrue:[
        CachedStyle := style.
        UpArrowForm := form
    ].

    ^ form

    "Modified: 10.1.1997 / 15:15:20 / cg"
!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style (#arrowButtonStyle 
                       #arrowButtonActiveLevel #arrowButtonPassiveLevel
                       #arrowButtonBackgroundColor #arrowButtonForegroundColor
                       #arrowButtonActiveBackgroundColor #arrowButtonActiveForegroundColor
                       #arrowButtonEnteredBackgroundColor #arrowButtonEnteredForegroundColor
                       #arrowButtonDisabledForegroundColor 
                       #arrowButtonDownForm #arrowButtonUpForm
                       #arrowButtonLeftForm #arrowButtonRightForm
                       #arrowButtonDownFormFile #arrowButtonUpFormFile
                       #arrowButtonLeftFormFile #arrowButtonRightFormFile)>

    DefaultArrowStyle := StyleSheet at:'arrowButtonStyle' default:StyleSheet name.
    DefaultArrowStyle := DefaultArrowStyle asSymbol.

    DefaultArrowButtonActiveLevel := StyleSheet at:'arrowButtonActiveLevel' default:nil.
    DefaultArrowButtonPassiveLevel := StyleSheet at:'arrowButtonPassiveLevel' default:nil.

    DefaultBackgroundColor := StyleSheet colorAt:'arrowButtonBackgroundColor'.
    DefaultForegroundColor := StyleSheet colorAt:'arrowButtonForegroundColor'.
    DefaultActiveBackgroundColor := StyleSheet colorAt:'arrowButtonActiveBackgroundColor'.
    DefaultActiveForegroundColor := StyleSheet colorAt:'arrowButtonActiveForegroundColor'.
    DefaultEnteredBackgroundColor := StyleSheet colorAt:'arrowButtonEnteredBackgroundColor'.
    DefaultEnteredForegroundColor := StyleSheet colorAt:'arrowButtonEnteredForegroundColor'.
    DefaultDisabledForegroundColor := StyleSheet colorAt:'arrowButtonDisabledForegroundColor'.

    DownArrowForm := StyleSheet at:'arrowButtonDownForm' default:nil.
    UpArrowForm := StyleSheet at:'arrowButtonUpForm' default:nil.
    LeftArrowForm := StyleSheet at:'arrowButtonLeftForm' default:nil.
    RightArrowForm := StyleSheet at:'arrowButtonRightForm' default:nil.

    UpArrowFormFile := DownArrowFormFile := LeftArrowFormFile := RightArrowFormFile := nil.
    UpArrowForm isNil ifTrue:[
        UpArrowFormFile := StyleSheet at:'arrowButtonUpFormFile' default:'ScrollUp.xbm'.
    ].
    DownArrowForm isNil ifTrue:[
        DownArrowFormFile := StyleSheet at:'arrowButtonDownFormFile' default:'ScrollDn.xbm'.
    ].
    LeftArrowForm isNil ifTrue:[
        LeftArrowFormFile := StyleSheet at:'arrowButtonLeftFormFile' default:'ScrollLt.xbm'.
    ].
    RightArrowForm isNil ifTrue:[
        RightArrowFormFile := StyleSheet at:'arrowButtonRightFormFile' default:'ScrollRt.xbm'.
    ].

    "
     self updateStyleCache
    "

    "Modified: 31.8.1995 / 03:01:14 / claus"
    "Modified: 1.3.1996 / 13:45:57 / cg"
! !

!ArrowButton methodsFor:'accessing'!

direction
    "return the buttons direction - a symbol"

    ^ direction
!

direction:aDirectionSymbol
    "create and return a new arrow button in aView"

    |form|

    aDirectionSymbol == #up ifTrue:[
        form := (self class upArrowButtonForm:arrowStyle on:device).
    ].
    aDirectionSymbol == #down ifTrue:[
        form := (self class downArrowButtonForm:arrowStyle on:device).
    ].
    aDirectionSymbol == #left ifTrue:[
        form := (self class leftArrowButtonForm:arrowStyle on:device).
    ].
    aDirectionSymbol == #right ifTrue:[
        form := (self class rightArrowButtonForm:arrowStyle on:device).
    ].
    direction := aDirectionSymbol.
    self form:form

    "Modified: 24.2.1997 / 21:19:59 / cg"
! !

!ArrowButton methodsFor:'initialization'!

initStyle
    "setup viewStyle specifics"

    super initStyle.

    DefaultBackgroundColor notNil ifTrue:[
        bgColor := DefaultBackgroundColor on:device
    ].
    DefaultForegroundColor notNil ifTrue:[
        fgColor := DefaultForegroundColor on:device
    ].
    DefaultActiveForegroundColor notNil ifTrue:[
        activeFgColor := DefaultActiveForegroundColor on:device
    ].
    DefaultActiveBackgroundColor notNil ifTrue:[
        activeBgColor := DefaultActiveBackgroundColor on:device
    ].
    DefaultEnteredForegroundColor notNil ifTrue:[
        enteredFgColor := DefaultEnteredForegroundColor on:device
    ].
    DefaultEnteredBackgroundColor notNil ifTrue:[
        enteredBgColor := DefaultEnteredBackgroundColor on:device
    ].
    DefaultDisabledForegroundColor notNil ifTrue:[
        disabledFgColor := DefaultDisabledForegroundColor on:device
    ].

    arrowStyle := DefaultArrowStyle.

    DefaultArrowButtonActiveLevel notNil ifTrue:[onLevel := DefaultArrowButtonActiveLevel].
    DefaultArrowButtonPassiveLevel notNil ifTrue:[offLevel := DefaultArrowButtonPassiveLevel].
    offLevel ~~ level ifTrue:[self level:offLevel].

"/    "
"/     special treatment for motif arrows 
"/     - they do not really fit into the general (bitmap) scheme ...
"/    "
"/    arrowStyle == #motif ifTrue:[
"/        onLevel := 0.
"/        offLevel := 0.
"/        self level:0.
"/    ]

    "Modified: 22.1.1997 / 11:57:00 / cg"
!

initialize

    super initialize.
    hSpace := vSpace := 0.
    controller beTriggerOnDown.

    "Modified: 6.3.1997 / 20:58:49 / cg"
! !

!ArrowButton methodsFor:'redrawing'!

drawWith:fg and:bg
    "this is a q&d hack for motif ..."

    |topLeft botRight noColor allColor isString orgX orgY r|

    arrowStyle ~~ #motif ifTrue:[
        ^ super drawWith:fg and:bg.
    ].

    "
     the code below does a lot of bitmap drawing, but allows
     to 3D-ify any logo (it draws it displaced by some pixels
     to the upper left in one-color and displaced to the 
     lower right in the other color). It should be rewritten to
     cache the result for later drawing operations.
    "
    logo notNil ifTrue:[
        self paint:bg.
        self fillRectangleX:0 y:0 width:width height:height.

        shadowColor := shadowColor on:device.
        lightColor := lightColor on:device.

        controller pressed ifTrue:[
            topLeft := shadowColor.
            botRight := lightColor
        ] ifFalse:[
            topLeft := lightColor.
            botRight := shadowColor
        ].

        isString := logo isString.

        isString ifFalse:[
            logo depth ~~ 1 ifTrue:[
                "/ allow for deep logos (for motif)
                "/ one catch: if the view background is a complex pixmap
                "/ we cannot use this as colorMap entry.
                "/ therefore, compute the average colors and take these
                "/ (this looks ok for buttons ...)

                logo graphicsDevice ~~ device ifTrue:[
"/ 'deep logo: ' print. logo depth printCR.
                    r := (0@0 corner:10@10).

                    logo photometric:#palette.
                    logo := logo on:device.
                    logo colorMap:(Array with:(bg averageColorIn:r)
                                         with:(topLeft averageColorIn:r)
                                         with:(botRight averageColorIn:r)
                                         with:(fg averageColorIn:r)).
                ].
                self displayForm:logo x:labelOriginX  y:labelOriginY.
                ^ self
            ].
            logo := logo on:device.
        ].

        isString ifTrue:[
            orgY := height - font height // 2 + font ascent.
            orgX := width - labelOriginX // 4 - 1.
        ].

        self paint:topLeft.
        #(-1 0 -1) with:#(-1 -1 0) do:[:dX :dY |
            isString ifTrue:[
                self displayString:logo x:orgX+dX  y:orgY+dY.
            ] ifFalse:[
                self displayForm:logo x:labelOriginX+dX  y:labelOriginY+dY.
            ]    
        ].

        self paint:botRight.
        #(1 1 0) with:#(0 1 1) do:[:dX :dY |
            isString ifTrue:[
                self displayString:logo x:orgX+dX  y:orgY+dY.
            ] ifFalse:[
                self displayForm:logo x:labelOriginX+dX  y:labelOriginY+dY.
            ]    
        ].

        "
         finally, the form itself
        "
        self paint:fg.
        isString ifTrue:[
            self displayString:logo x:orgX y:orgY.
        ] ifFalse:[
            self displayForm:logo x:labelOriginX  y:labelOriginY.
        ]    
    ]

    "Modified: 31.8.1995 / 03:03:12 / claus"
    "Modified: 6.3.1997 / 20:42:06 / cg"
! !

!ArrowButton class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/ArrowButton.st,v 1.40 1997-03-06 21:44:17 cg Exp $'
! !