CheckBox.st
author Claus Gittinger <cg@exept.de>
Wed, 22 Jan 1997 18:17:59 +0100
changeset 284 8e6ed630468b
parent 282 95209b20eaca
child 299 740258e44b3c
permissions -rw-r--r--
commentary

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


HorizontalPanelView subclass:#CheckBox
	instanceVariableNames:'toggleView labelView labelForegroundColor
		disabledLabelForegroundColor'
	classVariableNames:'DefaultLabelForegroundColor DefaultDisabledLabelForegroundColor'
	poolDictionaries:''
	category:'Views-Interactors'
!

!CheckBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    CheckBox has been added somwehat in a hurry 
    - obviously, much more protocol is needed.

    For now, set actions etc. via sends to the components,
    labelView and toggleView.

    [author:]
	Claus Gittinger

    [see also:]
	Button CheckToggle
	DialogBox
	ValueHolder
"
!

examples
"
  no-op checkBox without a label:
									[exBegin]
     |b|

     b := CheckBox new.
     b open
									[exEnd]


  no-op checkBox:
									[exBegin]
     |b|

     b := CheckBox new.
     b label:'foo'.
     b open
									[exEnd]


  no-op checkBox, disabled:
									[exBegin]
     |b|

     b := CheckBox new.
     b label:'foo'.
     b disable.
     b open
									[exEnd]


  changing colors 
  (a demo only: it is no good style to fight the styleSheet):
									[exBegin]
     |panel b|

     panel := VerticalPanelView new.

     b := CheckBox in:panel.
     b label:'foo'.

     b := CheckBox in:panel.
     b label:'bar'.
     b labelView foregroundColor:Color red.

     b := CheckBox in:panel.
     b label:'baz'.
     b toggleView activeForegroundColor:Color blue.

     panel open
									[exEnd]


  using action-blocks:
									[exBegin]
     |b|

     b := CheckBox new.
     b label:'check'.
     b action:[:value | Transcript show:'set to: '; showCR:value].
     b open.
									[exEnd]


  with a model (default ST-80 behavior, sending #value: to the model):
  (see changing value in the inspector)
									[exBegin]
     |b model|

     model := ValueHolder newBoolean.

     b := CheckBox new.
     b label:'check'.
     b model:model.
     b open.
     model inspect.
									[exEnd]


  with a model and different changeSelector
  (using a plug here, for demonstration only):
									[exBegin]
     |b model|

     model := Plug new.
     model respondTo:#changeCheck: with:[:arg | Transcript showCR:'change to ' , arg printString].

     b := CheckBox new.
     b label:'check'.
     b model:model; changeMessage:#changeCheck:.
     b open.
									[exEnd]


  with a model and an enableChannel
									[exBegin]
     |b enaToggle enaHolder|

     enaHolder := true asValue.

     enaToggle := Toggle label:'enable'.
     enaToggle model:enaHolder.
     enaToggle open.

     b := CheckBox new.
     b label:'check'.
     b action:[:value | Transcript show:'set to: '; showCR:value].
     b enableChannel:enaHolder.
     b open.
									[exEnd]


  with models, one checkBox disabling the others:
									[exBegin]
     |dialog translator enableChannel val1 val2 val3 eBox box1 box2 box3|

     translator := Plug new.
     translator respondTo:#enableDisable 
		with:[
			enableChannel value
			    ifTrue:[
				box1 enable.
				box2 enable.
				box3 enable.
			    ]
			    ifFalse:[
				box1 disable.
				box2 disable.
				box3 disable.
			    ]
		     ].

     enableChannel := true asValue.
     enableChannel onChangeSend:#enableDisable to:translator.
     val1 := true asValue.
     val2 := false asValue.
     val3 := true asValue.

     dialog := Dialog new.
     dialog addCheckBox:'enable' on:enableChannel.
     dialog addVerticalSpace.
     dialog leftIndent:30.
     box1 := dialog addCheckBox:'value1' on:val1.
     dialog addVerticalSpace.
     box2 := dialog addCheckBox:'value2' on:val2.
     dialog addVerticalSpace.
     box3 := dialog addCheckBox:'value3' on:val3.
     dialog addVerticalSpace.
     dialog addOkButton.

     dialog open.
									[exEnd]


  multiple checkBoxes on a single model (using different aspects)
									[exBegin]
     |top panel b model value1 value2|

     value1 := true.
     value2 := false.
     model := Plug new.
     model respondTo:#value1 with:[value1].
     model respondTo:#value1: with:[:val | value1 := val].
     model respondTo:#value2 with:[value2].
     model respondTo:#value2: with:[:val | value2 := val].

     top := DialogBox new.
     top extent:200@300.

     panel := VerticalPanelView new.

     b := CheckBox in:panel.
     b label:'check1'.
     b model:model; aspect:#value1; changeMessage:#value1:.

     b := CheckBox in:panel.
     b label:'check2'.
     b model:model; aspect:#value2; changeMessage:#value2:.

     top addComponent:panel.
     top addAbortButton; addOkButton.
     top openModal.

     top accepted ifTrue:[
	 Transcript show:'value1: '; showCR:model value1.
	 Transcript show:'value2: '; showCR:model value2.
     ]
									[exEnd]
"
! !

!CheckBox class methodsFor:'instance creation'!

label:aStringOrImage model:aModel
    "create & return a new checkBox, on aModel (typically a ValueHolder),
     with aStringOrImage as label."

    ^ (self new model:aModel) label:aStringOrImage

    "Created: 17.9.1995 / 14:20:58 / claus"
!

model:aModel
    "create & return a new checkBox, on aModel (typically a ValueHolder)"

    ^ self new model:aModel
! !

!CheckBox class methodsFor:'defaults'!

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

    <resource: #style (#checkBoxLabelForegroundColor 
		       #checkBoxDisabledLabelForegroundColor)>

    DefaultLabelForegroundColor := StyleSheet colorAt:'checkBoxLabelForegroundColor'.
    DefaultDisabledLabelForegroundColor := StyleSheet colorAt:'checkBoxDisabledLabelForegroundColor'.

    "
     self updateStyleCache
    "

    "Created: 14.12.1995 / 14:47:22 / cg"
    "Modified: 1.3.1996 / 13:45:47 / cg"
! !

!CheckBox methodsFor:'accessing'!

labelView
    "return the labelView; allows manipulation of the
     labels attributes (colors etc.)"

    ^ labelView
!

toggleView
    "return the toggleView; allows manipulation of the
     toggles attributes (colors etc.)"

    ^ toggleView
! !

!CheckBox methodsFor:'accessing-behavior'!

action:aBlock
    "set the actionBlock; forwarded to the toggle"

    toggleView action:aBlock

    "Modified: 25.4.1996 / 16:31:19 / cg"
!

disable
    "disable the checkBox; forwarded to toggle & change labels color"

    |clr|

    toggleView disable.
    clr := disabledLabelForegroundColor.
    clr isNil ifTrue:[ clr := toggleView disabledForegroundColor ].
    labelView foregroundColor:clr.

    "Modified: 25.4.1996 / 16:31:31 / cg"
!

enable
    "enable the checkBox; forwarded to toggle & change labels color"

    |clr|

    toggleView enable.
    clr := labelForegroundColor.
    clr isNil ifTrue:[ clr := toggleView foregroundColor ].
    labelView foregroundColor:clr.

    "Modified: 25.4.1996 / 16:31:40 / cg"
!

pressAction:aBlock
    "set the pressAction; forwarded to the toggle"

    toggleView pressAction:aBlock.

    "Created: 22.9.1995 / 15:54:04 / claus"
    "Modified: 25.4.1996 / 16:31:52 / cg"
!

releaseAction:aBlock
    "set the releaseAction; forwarded to the toggle"

    toggleView releaseAction:aBlock.

    "Created: 22.9.1995 / 15:54:11 / claus"
    "Modified: 25.4.1996 / 16:32:00 / cg"
! !

!CheckBox methodsFor:'accessing-channels'!

enableChannel
    "return a valueHolder for enable/disable"

    ^ toggleView enableChannel

    "Created: 30.4.1996 / 15:11:13 / cg"
!

enableChannel:aChannel
    "set the enableChannel"

    |wasEnabled|

    wasEnabled := toggleView enabled.
    toggleView enableChannel:aChannel.
    aChannel onChangeSend:#enableStateChanged to:self.
    aChannel value ~~ wasEnabled ifTrue:[
	self enableStateChanged
    ]

    "Created: 17.12.1995 / 16:07:59 / cg"
    "Modified: 25.4.1996 / 16:32:34 / cg"
! !

!CheckBox methodsFor:'accessing-look'!

activeLogo:anImageOrString
    "set the activeLogo; forwarded to the toggle"

    toggleView activeLogo:anImageOrString

    "Created: 22.9.1995 / 15:44:08 / claus"
    "Modified: 25.4.1996 / 16:32:50 / cg"
!

disabledLabelForegroundColor
    "set the disabledLabelForegroundColor; forwarded to the toggle"

    disabledLabelForegroundColor isNil ifTrue:[ ^ toggleView disabledForegroundColor ].
    ^ disabledLabelForegroundColor

    "Created: 16.12.1995 / 19:47:45 / cg"
    "Modified: 22.5.1996 / 13:16:55 / cg"
!

font
    "return the font. Forward from label"

    ^ labelView font

    "Modified: 22.5.1996 / 13:17:07 / cg"
!

font:aFont
    "set the font. Forward to the label & resize myself.
     CAVEAT: with the addition of Text objects,
	     this method is going to be obsoleted by a textStyle
	     method, which allows specific control over
	     normalFont/boldFont/italicFont parameters."

    labelView font:aFont.
    labelView forceResize.
    self layoutChanged.
    self resize.

    "Modified: 22.5.1996 / 13:17:28 / cg"
!

label
    "return the labels logo"

    ^ labelView label

    "Modified: 25.4.1996 / 16:33:08 / cg"
!

label:aString
    "set the logo; forward to label & resize"

    labelView label:aString.
    labelView forceResize.
    self layoutChanged.
    self resize.

    "Modified: 25.4.1996 / 16:33:14 / cg"
!

labelForegroundColor
    "return the labels foregroundColor"

    labelForegroundColor isNil ifTrue:[ ^ toggleView foregroundColor ].
    ^ labelForegroundColor

    "Created: 16.12.1995 / 19:47:20 / cg"
    "Modified: 25.4.1996 / 16:33:26 / cg"
!

passiveLogo:anImageOrString
    "set the passiveLogo; forwarded to the toggle"

    toggleView passiveLogo:anImageOrString

    "Created: 22.9.1995 / 15:44:14 / claus"
    "Modified: 25.4.1996 / 16:33:41 / cg"
! !

!CheckBox methodsFor:'accessing-mvc'!

aspectMessage:aspectSymbol
    "set the aspectMessage; forward to label & toggle"

    labelView aspectMessage:aspectSymbol.
    toggleView aspectMessage:aspectSymbol

    "Modified: 25.4.1996 / 16:33:49 / cg"
!

changeMessage:aChangeSelector
    "set the changeMessage; forward to toggle"

    toggleView changeMessage:aChangeSelector

    "Modified: 25.4.1996 / 16:33:55 / cg"
!

model:aModel
    "set the model; forward to label & toggle"

    labelView model:aModel.
    toggleView model:aModel

    "Modified: 25.4.1996 / 16:34:00 / cg"
! !

!CheckBox methodsFor:'accessing-state'!

isOn
    "return true, if the check is on; false otherwise"

    ^ toggleView isOn

    "Modified: 25.4.1996 / 16:34:15 / cg"
!

turnOff
    "turn the check off; forwarded to the toggle"

    toggleView turnOff

    "Modified: 25.4.1996 / 16:32:14 / cg"
!

turnOn
    "turn the check on; forwarded to the toggle"

    toggleView turnOn

    "Modified: 25.4.1996 / 16:32:21 / cg"
! !

!CheckBox methodsFor:'change & update'!

enableStateChanged
    "handle changes on the enableChannel"

    |clr|

    toggleView enabled ifTrue:[
	clr := self labelForegroundColor
    ] ifFalse:[
	clr := self disabledLabelForegroundColor
    ].
    labelView foregroundColor:clr

    "Modified: 25.4.1996 / 16:34:30 / cg"
! !

!CheckBox methodsFor:'event handling'!

keyPress:aKey x:x y:y
    aKey == Character space ifTrue:[
	self hasFocus ifTrue:[
	    ^ toggleView toggle
	]
    ].
    super keyPress:aKey x:x y:y

    "Created: 10.7.1996 / 11:24:16 / cg"
    "Modified: 10.7.1996 / 11:54:52 / cg"
! !

!CheckBox methodsFor:'initialization'!

defaultControllerClass
    ^ ToggleController

    "Created: 18.7.1996 / 11:57:01 / cg"
!

initStyle
    "setup viewStyle specifics"

    super initStyle.

    DefaultLabelForegroundColor notNil ifTrue:[
        labelForegroundColor := DefaultLabelForegroundColor on:device.
    ].
    DefaultDisabledLabelForegroundColor notNil ifTrue:[
        disabledLabelForegroundColor := DefaultDisabledLabelForegroundColor on:device.
    ].

    "Created: 14.12.1995 / 14:50:03 / cg"
    "Modified: 22.1.1997 / 11:57:03 / cg"
!

initialize
    <resource: #style (#name)>

    super initialize.

    borderWidth := 0.

    hLayout := #fixLeftSpace.
    vLayout := #center.

    toggleView := CheckToggle in:self.

    labelView := Label in:self.
    "/ a kludge
    styleSheet name ~~ #motif ifTrue:[
        labelView label:'check'; borderWidth:0.
    ].
    labelView forceResize.
    labelView adjust:#left.
    self initialHeight:labelView preferredExtent y + ViewSpacing.

    "/ actions in the label are handled by my controller
    labelView setController:controller.

    "
     all of my input goes to the toggle
     disabled - normally there is already an outer delegate
    "
"/    self delegate:(KeyboardForwarder toView:toggleView).

    "
     |b|

     b := CheckBox new.
     b label:'foo'.
     b open
    "

    "Modified: 17.1.1997 / 23:16:37 / cg"
! !

!CheckBox methodsFor:'private'!

sendChangeMessageWith:aValue
    "redefined to have mimic changes being sent from the toggle
     instead of myself"

    toggleView sendChangeMessageWith:aValue
! !

!CheckBox methodsFor:'queries'!

preferredExtent
    "compute & return the boxes preferredExtent from the components' sizes"

    |prefCheck prefLabel bw2|

    "/ If I have an explicit preferredExtent ..

    preferredExtent notNil ifTrue:[
	^ preferredExtent
    ].

    (labelView isNil or:[labelView label isEmpty]) ifTrue:[
	^ super preferredExtent
    ].
    ^ super preferredExtent + (10@0).

"/    prefCheck := toggleView preferredExtent.
"/    prefLabel := labelView preferredExtent.
"/    bw2 := borderWidth * 2.
"/    ^ (prefCheck x + prefLabel x + (3 * ViewSpacing)) @ ((prefCheck y max:prefLabel y) + bw2 + 2)

    "Modified: 19.7.1996 / 20:43:47 / cg"
! !

!CheckBox class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/CheckBox.st,v 1.37 1997-01-22 17:17:59 cg Exp $'
! !