CheckBox.st
author Claus Gittinger <cg@exept.de>
Mon, 23 Oct 1995 21:07:23 +0100
changeset 79 76d553a6c034
parent 78 30cd1e737c7f
child 86 4d7dbb5f1719
permissions -rw-r--r--
.

"
 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.
"


'From Smalltalk/X, Version:2.10.5 on 8-may-1995 at 3:48:28 am'!

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

!CheckBox class methodsFor:'documentation'!

version
"
$Header: /cvs/stx/stx/libwidg2/CheckBox.st,v 1.12 1995-10-23 20:07:16 cg Exp $
"
!

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.
"
!

examples
"
  no-op checkBox:

     |b|

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


  no-op checkBox, disabled:

     |b|

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


  changing colors 
  (a demo only: it is no good style to fight the styleSheet):

     |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


  using action-blocks:

     |b|

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


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

     |b model|

     model := ValueHolder newBoolean.

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


  with a model and different changeSelector
  (using a plug here, for demonstration only):

     |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.


  with models, one checkBox disabling the others:

     |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.


  multiple checkBoxes on a single model (using different aspects)

     |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.
     ]
"
!

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.
"

! !

!CheckBox class methodsFor:'instance creation'!

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

    ^ self new model:aModel
!

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"
! !

!CheckBox methodsFor:'accessing-mvc'!

changeMessage:aChangeSelector
    "forward to toggle"

    toggleView changeMessage:aChangeSelector
!

aspectMessage:aspectSymbol
    "forward to label & toggle"

    labelView aspectMessage:aspectSymbol.
    toggleView aspectMessage:aspectSymbol
!

model:aModel
    "forward to label & toggle"

    labelView model:aModel.
    toggleView model:aModel
! !

!CheckBox methodsFor:'accessing-behavior'!

action:aBlock
    "forward to toggle"

    toggleView action:aBlock
!

pressAction:aBlock
    toggleView pressAction:aBlock.

    "Created: 22.9.1995 / 15:54:04 / claus"
!

releaseAction:aBlock
    toggleView releaseAction:aBlock.

    "Created: 22.9.1995 / 15:54:11 / claus"
!

enable
    "forward to toggle & change labels color"

    toggleView enable.
    labelView foregroundColor:(toggleView foregroundColor).
!

disable
    "forward to toggle & change labels color"

    toggleView disable.
    labelView foregroundColor:(toggleView disabledForegroundColor).
!

turnOff
    "forward to toggle"

    toggleView turnOff
!

turnOn
    "forward to toggle"

    toggleView turnOn
! !

!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-state'!

isOn
    ^ toggleView isOn
! !

!CheckBox methodsFor:'accessing-look'!

label:aString
    "forward to label & resize"

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

font:aFont
    "forward to label & resize"

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

font
    "forward from label"

    ^ labelView font
!

label
    "forward from label"

    ^ labelView label
!

activeLogo:anImageOrString
    toggleView activeLogo:anImageOrString

    "Created: 22.9.1995 / 15:44:08 / claus"
!

passiveLogo:anImageOrString
    toggleView passiveLogo:anImageOrString

    "Created: 22.9.1995 / 15:44:14 / claus"
! !

!CheckBox methodsFor:'queries'!

preferredExtent
    |prefCheck prefLabel bw2|

^ 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)
! !

!CheckBox methodsFor:'private'!

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

    toggleView sendChangeMessageWith:aValue
! !

!CheckBox methodsFor:'initialization'!

initialize
    super initialize.

    borderWidth := 0.

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

    toggleView := CheckToggle in:self.

    labelView := Label in:self.
    labelView label:'check'; borderWidth:0.
    labelView forceResize.
    labelView adjust:#left.
    self height:labelView preferredExtent y + ViewSpacing.

    "
     all of my input goes to the toggle
    "
    self delegate:(KeyboardForwarder toView:toggleView).

    "
     |b|

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