RButton.st
author Claus Gittinger <cg@exept.de>
Mon, 03 Nov 1997 16:24:30 +0100
changeset 1384 e4acb2c5b10b
parent 1087 171cdcfe0274
child 1391 33fef737601f
permissions -rw-r--r--
more styles (motif, round3D and round2D)

"
 COPYRIGHT (c) 1991 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.
"

Toggle subclass:#RadioButton
	instanceVariableNames:'buttonStyle buttonOnLevel buttonOffLevel'
	classVariableNames:'DefaultButtonStyle DefaultActiveLevel DefaultPassiveLevel'
	poolDictionaries:''
	category:'Views-Interactors'
!

!RadioButton class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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
"
    like a Toggle, but do not turn off when pressed again, instead only
    turn off when another RadioButton is pressed (see RadioButtonGroup).

    written fall 91 by claus

    [author:]
        Claus Gittinger
"
!

examples 
"
  See more examples in RadioButtonGroup class>>examples

  example1: one on behavior (using RadioButtons)
                                                                        [exBegin]
    |top panel b group|

    top := StandardSystemView new.
    top extent:200@200.

    panel := HorizontalPanelView
                origin:0.0@0.0
                corner:1.0@1.0
                    in:top.

    group := RadioButtonGroup new.

    b := RadioButton label:'am' in:panel.
    group add:b.

    b := RadioButton label:'fm' in:panel.
    group add:b.

    b := RadioButton label:'off' in:panel.
    group add:b.

    group value:1.
    top open
                                                                        [exEnd]


  example2: zero or one on behavior (using Toggles)
                                                                        [exBegin]
    |top panel b group|

    top := StandardSystemView new.
    top extent:200@200.

    panel := HorizontalPanelView
                origin:0.0@0.0
                corner:1.0@1.0
                    in:top.

    group := RadioButtonGroup new.

    b := Toggle label:'am' in:panel.
    group add:b.

    b := Toggle label:'fm' in:panel.
    group add:b.

    b := Toggle label:'off' in:panel.
    group add:b.

    group value:1.
    top open
                                                                        [exEnd]


  a selectionInListView and a group displaying the same value:
                                                                        [exBegin]
    |top top2 panel b sv group selectionInList|

    top := StandardSystemView extent:200@200.

    panel := HorizontalPanelView
                origin:0.0@0.0 corner:1.0@1.0 in:top.

    group := RadioButtonGroup new.
    selectionInList := SelectionInList new.
    selectionInList list:#('am' 'fm' 'off').
    selectionInList selectionIndexHolder:group.

    b := Toggle label:'am' in:panel.
    group add:b.

    b := Toggle label:'fm' in:panel.
    group add:b.

    b := Toggle label:'off' in:panel.
    group add:b.

    group value:1.
    top open.

    top2 := StandardSystemView extent:200@200.
    sv := SelectionInListView in:top2.
    sv model:selectionInList.
    sv origin:0.0@0.0 corner:1.0@1.0.
    top2 open.

                                                                        [exEnd]
"
! !

!RadioButton class methodsFor:'defaults'!

motifCheckBotForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00001110
                    2r01110000 2r00011100
                    2r00111000 2r00111000
                    2r00011100 2r01110000
                    2r00001110 2r11100000
                    2r00000111 2r11000000
                    2r00000011 2r10000000
                    2r00000001 2r00000000
                   ]

    "Created: / 3.11.1997 / 12:06:45 / cg"
    "Modified: / 3.11.1997 / 12:10:50 / cg"
!

motifCheckTopForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000001 2r00000000
                    2r00000011 2r10000000
                    2r00000111 2r11000000
                    2r00001110 2r11100000
                    2r00011100 2r01110000
                    2r00111000 2r00111000
                    2r01110000 2r00011100
                    2r11100000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                   ]

    "Created: / 3.11.1997 / 12:06:45 / cg"
    "Modified: / 3.11.1997 / 12:11:03 / cg"
!

round3DCheckBotForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00001100
                    2r00000000 2r00000110
                    2r00000000 2r00000110
                    2r00000000 2r00000110
                    2r00000000 2r00001100
                    2r00000000 2r00001100
                    2r00110000 2r00011000
                    2r00111100 2r01111000
                    2r00001111 2r11100000
                    2r00000011 2r10000000
                   ]

    "Modified: / 3.11.1997 / 13:32:17 / cg"
    "Created: / 3.11.1997 / 14:29:37 / cg"
!

round3DCheckTopForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000011 2r10000000
                    2r00001111 2r11100000
                    2r00111100 2r01111000
                    2r00110000 2r00011000
                    2r01100000 2r00001100
                    2r01100000 2r00001100
                    2r11000000 2r00000000
                    2r11000000 2r00000000
                    2r11000000 2r00000000
                    2r01100000 2r00000000
                    2r01100000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                   ]

    "Modified: / 3.11.1997 / 13:31:49 / cg"
    "Created: / 3.11.1997 / 14:29:45 / cg"
!

roundOffForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000011 2r10000000
                    2r00001111 2r11100000
                    2r00111100 2r01111000
                    2r00110000 2r00011000
                    2r01100000 2r00001100
                    2r01100000 2r00001100
                    2r11000000 2r00000110
                    2r11000000 2r00000110
                    2r11000000 2r00000110
                    2r01100000 2r00001100
                    2r01100000 2r00001100
                    2r00110000 2r00011000
                    2r00111100 2r01111000
                    2r00001111 2r11100000
                    2r00000011 2r10000000
                   ]

    "Created: / 3.11.1997 / 12:41:13 / cg"
    "Modified: / 3.11.1997 / 13:25:03 / cg"
!

roundOnForm
    ^ Form 
        width:15 
        height:15 
        fromArray:#[2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000011 2r10000000
                    2r00000111 2r11000000
                    2r00001111 2r11100000
                    2r00001111 2r11100000
                    2r00001111 2r11100000
                    2r00000111 2r11000000
                    2r00000011 2r10000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                    2r00000000 2r00000000
                   ]

    "Created: / 3.11.1997 / 12:41:17 / cg"
    "Modified: / 3.11.1997 / 14:10:59 / cg"
!

updateStyleCache
    |l|

    DefaultButtonStyle := StyleSheet at:'radioButton.style'.
    l := -1.
    DefaultButtonStyle == #round2D ifTrue:[l := 0].
    DefaultActiveLevel := StyleSheet at:'radioButton.activeLevel' default:l.
    DefaultButtonStyle == #motif ifTrue:[l := 1].
    DefaultPassiveLevel := StyleSheet at:'radioButton.passivelLevel' default:l.

    "
     self updateStyleCache
    "

    "Modified: / 3.11.1997 / 14:20:21 / cg"
! !

!RadioButton methodsFor:'drawing'!

drawToggleImage
    "drawing of the radio image is done here."

    |x y clrTop clrBot img1 img2 img imgOn threeD lvl|

    buttonStyle isNil ifTrue:[
        ^ super drawToggleImage
    ].

    threeD := true.
    buttonStyle == #motif ifTrue:[
        img1 := self class motifCheckTopForm onDevice:device.
        img2 := self class motifCheckBotForm onDevice:device.
    ] ifFalse:[
        buttonStyle == #round3D ifTrue:[
            img1 := self class round3DCheckTopForm onDevice:device.
            img2 := self class round3DCheckBotForm onDevice:device.
            buttonOnLevel == buttonOffLevel ifTrue:[
                controller pressed ifTrue:[
                    imgOn := self class roundOnForm onDevice:device.
                ]
            ].
        ] ifFalse:[
            img1 := self class roundOffForm onDevice:device.
            controller pressed ifTrue:[
                imgOn := self class roundOnForm onDevice:device.
            ].
            threeD := false.
        ]
    ].

    x := hSpace + margin.
    y := (height - img1 height) // 2.

    threeD ifFalse:[
        self paint:fgColor.
        self displayForm:img1 x:x y:y.
        controller pressed ifTrue:[
            self paint:activeFgColor.
            self displayForm:imgOn x:x y:y
        ]
    ] ifTrue:[
        controller pressed ifTrue:[
            lvl := buttonOnLevel
        ] ifFalse:[
            lvl := buttonOffLevel.
        ].
        lvl < 0 ifTrue:[
            clrTop := shadowColor.
            clrBot := lightColor.
        ] ifFalse:[
            clrTop := lightColor.
            clrBot := shadowColor.
        ].
        self paint:clrTop.
        self displayForm:img1 x:x y:y.
        self paint:clrBot.
        self displayForm:img2 x:x y:y.

        controller pressed ifTrue:[
            imgOn notNil ifTrue:[
                self paint:fgColor.
                self displayForm:imgOn x:x y:y
            ]
        ]
    ]

    "Created: / 3.11.1997 / 12:16:30 / cg"
    "Modified: / 3.11.1997 / 14:46:41 / cg"
! !

!RadioButton methodsFor:'initialization'!

defaultControllerClass
    ^ RadioButtonController
!

initStyle
    buttonStyle := DefaultButtonStyle.
    super initStyle.

    buttonStyle isNil ifTrue:[
        showLamp := styleSheet at:'radioButton.showLamp' default:showLamp.
        ^ self
    ].

    showLamp := true.
    buttonOnLevel := DefaultActiveLevel.
    buttonOffLevel := DefaultPassiveLevel.

    onLevel := offLevel := 0.
    self level:0.

    (buttonStyle == #motif 
    or:[buttonStyle == #round3D]) ifTrue:[
        activeBgColor := bgColor. 
        activeFgColor := fgColor.
    ] ifFalse:[
        buttonStyle == #round2D ifTrue:[
            activeFgColor := fgColor.
            activeBgColor := bgColor.
        ]
    ]

    "Modified: / 3.11.1997 / 14:38:11 / cg"
! !

!RadioButton methodsFor:'private'!

lampImageHeight
    ^ 15

    "Created: / 3.11.1997 / 14:27:27 / cg"
!

lampImageWidth
    ^ 15

    "Created: / 3.11.1997 / 14:27:23 / cg"
! !

!RadioButton methodsFor:'queries'!

is3D
    buttonStyle == #round2D ifTrue:[^ false.].
    ^ super is3D

    "Created: / 3.11.1997 / 14:39:36 / cg"
! !

!RadioButton class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Attic/RButton.st,v 1.15 1997-11-03 15:24:30 cg Exp $'
! !