Toggle.st
author claus
Wed, 03 May 1995 02:39:07 +0200
changeset 119 59758ff5b841
parent 105 3d064ba4a0cc
child 121 4e63bbdb266a
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1989 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 14-mar-1995 at 11:03:45 am'!

Button subclass:#Toggle
	 instanceVariableNames:'showLamp lampColor lampWidth lampHeight'
	 classVariableNames:'DefaultShowLamp DefaultLampColor'
	 poolDictionaries:''
	 category:'Views-Interactors'
!

Toggle comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Toggle.st,v 1.15 1995-05-03 00:38:26 claus Exp $
'!

!Toggle class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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/Toggle.st,v 1.15 1995-05-03 00:38:26 claus Exp $
"
!

documentation
"
    this button changes state whenever pressed and stays pressed until pressed
    again. All the main action is in Button, Toggle just redefines buttonpress/
    release behavior.

    The toggle may optionally display a little kind-of-lamp (or LED), which
    is turned on when the toggle is pressed. (i.e. as in the Interviews toolkit).

    whenever the Toggle changes its change, it will evaluate one of
    pressAction or releaseAction.

    For ST-80 compatibility, if the model is nonNil, this one gets a new
    value and is sent a changed message.
    If nonNil, the model is supposed to be a ValueHolder holding true or false.


    instance variables:
	showLamp          <Boolean>     true if a lamp should be displayed
	lampColor         <Color>       color of the lamp
	lampWidth         <Integer>     width of the lamp in pixel
	lampHeight        <Integer>     height of the lamp in pixel

    styleSheet values:
	toggleShowLamp    <Boolean>     if true, a lamp is shown; default:false.
	toggleLampColor   <Color>       lamps color; default:yellow.
"
!

examples
"
    Examples:
	Try these, to see what is possible.

	(notice, that these examples are meant to show what can be done;
	 usually, all style-related stuff is preinitialized - you should not
	 normally play around with onLevel, offLevel, showLamp: etc)

      simple:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'press here' in:v.
	t origin:10 @ 10.
	t action:[:value | Transcript show:'toggle state: '; showCr:value.].
	v open

      separate press/release actions:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'press here' in:v.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'toggle pressed'.].
	t releaseAction:[Transcript showCr:'toggle released'.].
	v open

      changing logo:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'eat me' in:v.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'smaller'. t label:'drink me'].
	t releaseAction:[Transcript showCr:'larger'. t label:'eat me'].
	v open

      changing logo and freezing size (looks better):

	|v t|

	v := StandardSystemView new extent:200@200.
	'create with large logo; freeze; change to small logo'.
	t := Toggle label:'drink me' in:v. 
	t sizeFixed:true.
	t label:'eat me'.

	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'smaller'. t label:'drink me'].
	t releaseAction:[Transcript showCr:'larger'. t label:'eat me'].
	v open

      adding a lamp (in some view styles, this is the default anyway):

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'].
	t releaseAction:[Transcript showCr:'off'. t label:'off'].
	v open

      changing lamps color:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t lampColor:Color red.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'.].
	t releaseAction:[Transcript showCr:'off'. t label:'off'.].
	v open

      changing lamps color & size:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t lampColor:Color red.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'.].
	t releaseAction:[Transcript showCr:'off'. t label:'off'.].
	v open

      lamp only - no '3D going-in' (this is the default with IRIS style)

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t onLevel:(t offLevel).
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'].
	t releaseAction:[Transcript showCr:'off'. t label:'off'].
	v open

      lamp and freezing size of the label (looks better):

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t sizeFixed:true.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'].
	t releaseAction:[Transcript showCr:'off'. t label:'off'].
	v open

      another variation:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t sizeFixed:true.
	t onLevel:(t offLevel).
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t label:'on'].
	t releaseAction:[Transcript showCr:'off'. t label:'off'].
	v open

      and another one:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t showLamp:true.
	t sizeFixed:true.

	t showLamp:false.
	t offLevel:3.
	t onLevel:3.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'. t showLamp:true. t label:'on'].
	t releaseAction:[Transcript showCr:'off'. t showLamp:false. t label:'off'].
	v open

      another font:

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t font:(Font family:'times' face:'bold' style:'roman' size:24).
	t label:'hello'.
	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'.].
	t releaseAction:[Transcript showCr:'off'.].
	v open

      another font (no, I dont know what it means :-):

	|v t|

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'off' in:v.
	t font:(Font family:'k14' face:nil style:nil size:nil).
	t label:(TwoByteString with:(Character value:16r3021)).

	t origin:10 @ 10.
	t pressAction:[Transcript showCr:'on'.].
	t releaseAction:[Transcript showCr:'off'.].
	v open

    using a model (look at value of model in inspector):

	|m v t|

	m := ValueHolder newBoolean.
	m inspect.

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'press here to change value' in:v.
	t origin:10 @ 10.
	t model:m.
	v open

    using a model with different changeSelector:

	|m v t|

	m := Plug new.
	m respondTo:#setValue1: with:[:value | Transcript show:'value 1 changed to: '; showCr:value].
	m respondTo:#setValue2: with:[:value | Transcript show:'value 2 changed to: '; showCr:value].

	v := StandardSystemView new extent:200@200.
	t := Toggle label:'press here for value1' in:v.
	t origin:10 @ 10.
	t model:m; change:#setValue1:.
	t := Toggle label:'press here for value2' in:v.
	t origin:10 @ 50.
	t model:m; change:#setValue2:.
	v open
"
! !

!Toggle class methodsFor:'defaults'!

updateStyleCache
    DefaultShowLamp := StyleSheet at:'toggleShowLamp' default:false.
    DefaultLampColor := StyleSheet colorAt:'toggleLampColor' default:Color yellow.
! !

!Toggle methodsFor:'initialization'!

defaultControllerClass
    ^ ToggleController
!

initStyle
    super initStyle.

    showLamp := DefaultShowLamp.
    showLamp ifTrue:[
	onLevel := offLevel.

	"dont know, if I like this ..."
	"
	activeBgColor := bgColor
	"
    ].

    lampColor := DefaultLampColor on:device.
    lampWidth := (device horizontalPixelPerMillimeter * 1.8) rounded.
    lampHeight := (device verticalPixelPerMillimeter * 3.5) rounded.
!

realize
    "/
    "/ get my initial state from the model (if there is one)
    "/
    self getValueFromModel.
    super realize
! !

!Toggle methodsFor:'accessing'!

showLamp
    "return true, if I show a lamp"

    ^ showLamp
!

showLamp:aBoolean
    "enable/disable drawing of the lamp"

    showLamp ~~ aBoolean ifTrue:[
	showLamp := aBoolean.
	self computeLabelSize.
	fixSize ifFalse:[
	    self resize
	]
    ]
!

lampColor:aColor
    "change the color of the toggle-lamp"

    lampColor := aColor.
    (shown and:[showLamp and:[controller pressed]]) ifTrue:[
	self redraw
    ]
! !

!Toggle methodsFor:'private'!

getValueFromModel
    (model notNil and:[aspectMsg notNil]) ifTrue:[
	controller pressed:(model perform:aspectMsg)
    ].
!

computeLabelOrigin
    "compute the origin of the form/text.
     redefined to move label to the right if there is a lamp."

    super computeLabelOrigin.
    showLamp ifTrue:[
	labelOriginX := labelOriginX + hSpace + lampWidth + hSpace.
    ]
!

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

    super computeLabelSize.
    showLamp ifTrue:[
	labelWidth := labelWidth + hSpace + lampWidth + hSpace.
	labelHeight := labelHeight max: lampHeight
    ]
! !

!Toggle methodsFor:'redrawing'!

drawWith:fg and:bg
    "redraw myself with fg/bg. Use super to draw the label, 
     drawing of the lamp is done here."

    |x y clr|

    super drawWith:fg and:bg.   "this draws the text"

    showLamp ifTrue:[
	x := hSpace + margin.
	y := (height - lampHeight) // 2.
	self drawEdgesForX:x y:y width:lampWidth height:lampHeight level:-1.
	controller pressed ifTrue:[
	    clr := lampColor.
	] ifFalse:[
	    clr := bgColor.
	].
	self paint:clr.
	self fillRectangleX:x+2 y:y+2 width:lampWidth - 4 height:lampHeight - 4
    ]
! !