CheckToggle.st
author claus
Wed, 03 May 1995 02:30:14 +0200
changeset 118 3ee5ea99d0e2
parent 77 565b052f5277
child 127 462396b08e30
permissions -rw-r--r--
.

"
 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:#CheckToggle
	 instanceVariableNames:''
	 classVariableNames:'DefaultCheckForm'
	 poolDictionaries:''
	 category:'Views-Interactors'
!

CheckToggle comment:'
COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/CheckToggle.st,v 1.8 1995-05-03 00:28:49 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libwidg/CheckToggle.st,v 1.8 1995-05-03 00:28:49 claus Exp $
"
!

documentation
"
    CheckButtons are like Toggles in toggling their state when pressed.
    However, they show an ok-marker if on; nothing if off.
    CheckButtons are mostly used as part of a checkBox (since normally,
    you want to have some label along the check)
"
!

examples 
"
    checkToggle alone:

	|top check|

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

	check := CheckToggle in:top.
	check origin:10@10.

	top open

    give it an action:

	|top check|

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

	check := CheckToggle in:top.
	check origin:10@10.
	check action:[:value | Transcript showCr:'changed to: ' , value printString].

	top open

    give it a model:

	|top check model|

	model := false asValue.

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

	check := CheckToggle in:top.
	check origin:10@10.
	check model:model.

	top openModal.

	Transcript showCr:'value after closing box: ' , model value printString

    multiple checks on a single model (with different change selectors):
    (using a checkBox here, for the demonstration ...)

	|top model panel ext1 ext2
	 readFlag writeFlag executeFlag|

	readFlag := writeFlag := true.
	executeFlag := false.

	model := Plug new.
	model respondTo:#read with:[readFlag].
	model respondTo:#write with:[writeFlag].
	model respondTo:#execute with:[executeFlag].
	model respondTo:#read: with:[:val | readFlag := val].
	model respondTo:#write: with:[:val | writeFlag := val].
	model respondTo:#execute: with:[:val | executeFlag := val].

	top := StandardSystemView new.
	top extent:200@200.
	top label:'File permissions:'.

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

	#(read write execute) do:[:sym |
	    |check|

	    check := CheckBox in:panel.
	    check label:sym.
	    check model:model; aspect:sym; change:(sym , ':') asSymbol.
	].

	top openModal.

	Transcript showCr:'settings after closing box:'.
	Transcript showCr:'  read -> ' , readFlag printString.
	Transcript showCr:'  write -> ' , writeFlag printString.
	Transcript showCr:'  execute -> ' , executeFlag printString.
"
! !

!CheckToggle class methodsFor:'defaults'!

checkFormOn:aDevice
    "answer the form used when checkToggle is turned on"

    DefaultCheckForm isNil ifTrue:[
	DefaultCheckForm := Form fromFile:'CheckOn.xbm' 
			       resolution:100
				       on:aDevice
    ].
    DefaultCheckForm isNil ifTrue:[
	DefaultCheckForm :=
	    Form width:16 height:16 fromArray:#[2r00000000 2r00000000
						2r00000000 2r00000010
						2r00000000 2r00000010
						2r00000000 2r00000100
						2r00000000 2r00000100
						2r00000000 2r00001000
						2r00000000 2r00001000
						2r00000000 2r00010000
						2r01000000 2r00010000
						2r00100000 2r00100000
						2r00010000 2r00100000
						2r00001000 2r01000000
						2r00000100 2r01000000
						2r00000010 2r10000000
						2r00000001 2r10000000
						2r00000000 2r00000000]
					    on:aDevice
    ].
    ^ DefaultCheckForm
! !

!CheckToggle methodsFor:'initialization'!

initialize
    super initialize.

    onLevel := offLevel.
    activeLogo := self class checkFormOn:device.
    passiveLogo := nil.
    self form:activeLogo
!

initStyle
    super initStyle.

    self activeForegroundColor:(StyleSheet at:'checkToggleCheckColor' default:activeFgColor).
    showLamp := false
! !

!CheckToggle methodsFor:'redrawing'!

redraw
    controller pressed ifTrue:[
	logo := activeLogo.
	super redraw
    ] ifFalse:[
	logo := nil.
	super redraw
    ]
! !