RadioButton.st
author Claus Gittinger <cg@exept.de>
Thu, 30 Jul 1998 21:35:47 +0200
changeset 1629 21481cd942f9
parent 1583 147916baf6dc
child 1696 adfae835bac8
permissions -rw-r--r--
cache forms - avoid recreation.

"
 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
		MotifCheckBotForm MotifCheckTopForm Round3DCheckBotForm
		Round3DCheckTopForm RoundHalfLightForm RoundOffForm RoundOnForm'
	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
    MotifCheckBotForm isNil ifTrue:[
        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
                       ].
        MotifCheckBotForm := MotifCheckBotForm onDevice:Display.
    ].
    ^ MotifCheckBotForm

    "Created: / 3.11.1997 / 12:06:45 / cg"
    "Modified: / 30.7.1998 / 21:27:53 / cg"
!

motifCheckTopForm
    MotifCheckTopForm isNil ifTrue:[
        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
                                           ].
        MotifCheckTopForm := MotifCheckTopForm onDevice:Display
    ].
    ^ MotifCheckTopForm

    "Created: / 3.11.1997 / 12:06:45 / cg"
    "Modified: / 30.7.1998 / 21:28:45 / cg"
!

round3DCheckBotForm
    Round3DCheckBotForm isNil ifTrue:[
        Round3DCheckBotForm := Form 
                                width:15 
                                height:15 
                                fromArray:#[2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000010
                                            2r00000000 2r00000010
                                            2r00000000 2r00000110
                                            2r00000000 2r00000110
                                            2r00000000 2r00000110
                                            2r00000000 2r00001110
                                            2r01110000 2r00011100
                                            2r01111000 2r00111100
                                            2r00111111 2r11111000
                                            2r00001111 2r11100000
                                           ].
        Round3DCheckBotForm := Round3DCheckBotForm onDevice:Display.
    ].
    ^ Round3DCheckBotForm

    "Created: / 3.11.1997 / 14:29:37 / cg"
    "Modified: / 30.7.1998 / 21:29:57 / cg"
!

round3DCheckTopForm
    Round3DCheckTopForm isNil ifTrue:[
        Round3DCheckTopForm := Form 
                                width:15 
                                height:15 
                                fromArray:#[2r00000011 2r10000000
                                            2r00011110 2r11110000
                                            2r00111000 2r00011000
                                            2r01110000 2r00001100
                                            2r01100000 2r00001100
                                            2r11000000 2r00000100
                                            2r11000000 2r00000100
                                            2r11000000 2r00000000
                                            2r11000000 2r00000000
                                            2r11000000 2r00000000
                                            2r01100000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                            2r00000000 2r00000000
                                           ].
"/        fromArray:#[2r00000111 2r11000000
"/                    2r00011110 2r11110000
"/                    2r00111000 2r00111000
"/                    2r01110000 2r00011100
"/                    2r01100000 2r00001100
"/                    2r11000000 2r00000100
"/                    2r11000000 2r00000000
"/                    2r11000000 2r00000000
"/                    2r11000000 2r00000000
"/                    2r11000000 2r00000000
"/                    2r01100000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                   ]

        Round3DCheckTopForm := Round3DCheckTopForm onDevice:Display.
    ].
    ^ Round3DCheckTopForm

    "Created: / 3.11.1997 / 14:29:45 / cg"
    "Modified: / 30.7.1998 / 21:30:47 / cg"
!

roundHalfLightForm
    RoundHalfLightForm isNil ifTrue:[
        RoundHalfLightForm := Form
                                width:15 
                                height:15 
                                fromArray:#[2r00001100 2r01100000
                                            2r00110000 2r00010000
                                            2r01100000 2r00001000
                                            2r01000000 2r00000100
                                            2r11000000 2r00000100
                                            2r10000000 2r00000000
                                            2r10000000 2r00000000
                                            2r10000000 2r00000100
                                            2r10000000 2r00000100
                                            2r10000000 2r00000100
                                            2r11000000 2r00001000
                                            2r00110000 2r00010000
                                            2r00011000 2r00110000
                                            2r00000111 2r11000000
                                            2r00000000 2r00000000
                                           ].

"/        fromArray:#[2r00000000 2r00000000
"/                    2r00000011 2r10000000
"/                    2r00001000 2r00100000
"/                    2r00010000 2r00010000
"/                    2r00100000 2r00001000
"/                    2r00000000 2r00000100
"/                    2r01000000 2r00000100
"/                    2r01000000 2r00000100
"/                    2r01000000 2r00000100
"/                    2r00000000 2r00000100
"/                    2r00100000 2r00001000
"/                    2r00010000 2r00010000
"/                    2r00001000 2r00100000
"/                    2r00000011 2r10000000
"/                    2r00000000 2r00000000
"/                   ]

        RoundHalfLightForm := RoundHalfLightForm onDevice:Display.
    ].
    ^ RoundHalfLightForm

    "Created: / 3.11.1997 / 18:26:40 / cg"
    "Modified: / 30.7.1998 / 21:31:55 / cg"
!

roundOffForm
    RoundOffForm isNil ifTrue:[
        RoundOffForm := Form 
            width:15 
            height:15 
            fromArray:#[2r00000011 2r10000000
                        2r00001100 2r01100000
                        2r00010000 2r00010000
                        2r00100000 2r00001000
                        2r01000000 2r00000100
                        2r01000000 2r00000100
                        2r10000000 2r00000010
                        2r10000000 2r00000010
                        2r10000000 2r00000010
                        2r01000000 2r00000100
                        2r01000000 2r00000100
                        2r00100000 2r00001000
                        2r00010000 2r00010000
                        2r00001100 2r01100000
                        2r00000011 2r10000000
                       ].

"/        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
"/                   ]
        RoundOffForm := RoundOffForm onDevice:Display.
    ].
    ^ RoundOffForm

    "Created: / 3.11.1997 / 12:41:13 / cg"
    "Modified: / 30.7.1998 / 21:33:03 / cg"
!

roundOnForm
    RoundOnForm isNil ifTrue:[
        RoundOnForm := Form 
                        width:15 
                        height:15 
"/        fromArray:#[2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000111 2r11000000
"/                    2r00001111 2r11100000
"/                    2r00011111 2r11110000
"/                    2r00011111 2r11110000
"/                    2r00011111 2r11110000
"/                    2r00011111 2r11110000
"/                    2r00011111 2r11110000
"/                    2r00001111 2r11100000
"/                    2r00000111 2r11000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                    2r00000000 2r00000000
"/                   ]
                        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
                                   ].
        RoundOnForm := RoundOnForm onDevice:Display.
    ].
    ^ RoundOnForm

    "Created: / 3.11.1997 / 12:41:17 / cg"
    "Modified: / 30.7.1998 / 21:33:39 / 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:'accessing'!

forceRadioButtonStyle
    "force the radioButton to be displayed as round/motif radio button -
     even if the styleSheet defaults differently.
     (as in IRIS style)"

    buttonStyle isNil ifTrue:[
        styleSheet is3D ifTrue:[
            buttonStyle := #round3D.
            activeBgColor := bgColor. 
            activeFgColor := fgColor.
        ] ifFalse:[
            buttonStyle := #round2D.
                activeFgColor := fgColor.
                activeBgColor := bgColor.
        ].
        buttonOnLevel := DefaultActiveLevel.
        buttonOffLevel := DefaultPassiveLevel.
        onLevel := offLevel := 0.
        self level:0
    ]

    "Modified: / 18.6.1998 / 21:19:01 / cg"
    "Created: / 18.6.1998 / 21:23:58 / cg"
! !

!RadioButton methodsFor:'drawing'!

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

    |x y clrTop clrBot img1 img2 imgH 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.
            imgH := self class roundHalfLightForm 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.
        (imgH notNil and:[halfShadowColor notNil]) ifTrue:[
            self paint:halfShadowColor.
            self displayForm:imgH x:x y:y
        ].
        controller pressed ifTrue:[
            imgOn notNil ifTrue:[
                self paint:lampColor.
                self displayForm:imgOn x:x y:y
            ]
        ]
    ]

    "Created: / 3.11.1997 / 12:16:30 / cg"
    "Modified: / 3.11.1997 / 18:28:43 / cg"
! !

!RadioButton methodsFor:'initialization'!

defaultControllerClass
    ^ RadioButtonController
!

initStyle
    buttonStyle isNil ifTrue:[
        buttonStyle := DefaultButtonStyle.
    ].

    super initStyle.

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

    adjust := #left.
    showLamp := true.
    lampColor := Color black.
    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: / 18.6.1998 / 21:18:07 / cg"
! !

!RadioButton methodsFor:'private'!

computeLabelOrigin
    super computeLabelOrigin.
    buttonStyle notNil ifTrue:[    
        labelOriginX := hSpace + 15 + hSpace  
    ]

    "Modified: / 3.11.1997 / 18:17:58 / cg"
!

computeLabelSize
    "compute the extent needed to hold the label plus the lamp"

    super computeLabelSize.
    buttonStyle notNil ifTrue:[
        labelWidth := labelWidth + 15
    ]
!

lampImageHeight
    buttonStyle isNil ifTrue:[^ super lampImageHeight].
    ^ 15

    "Created: / 3.11.1997 / 14:27:27 / cg"
    "Modified: / 3.11.1997 / 18:10:39 / cg"
!

lampImageWidth
    buttonStyle isNil ifTrue:[^ super lampImageWidth].
    ^ 15

    "Created: / 3.11.1997 / 14:27:23 / cg"
    "Modified: / 3.11.1997 / 18:10:50 / 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/RadioButton.st,v 1.24 1998-07-30 19:35:47 cg Exp $'
! !