BlockValue.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:32:07 +0200
changeset 221 ea942fe5dc04
parent 158 16f2237474fe
child 223 b65dc250db8d
permissions -rw-r--r--
documentation

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


ValueModel subclass:#BlockValue
	instanceVariableNames:'cachedValue arguments block'
	classVariableNames:'NeverComputed'
	poolDictionaries:''
	category:'Interface-Support-Models'
!

!BlockValue 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
"
    BlockValues depend on multiple other objects (typically valueHolders)
    and recompute a value whenever one of them changes.
    If the new value is different, it triggers itself a change to its dependents.

    Example use is to base an enableChannels value on multiple other boolean values.
    (See example for how this is done)
"

!

examples
"
    checkToggle 3 shows the value of toggle1 AND toggle2

	|val1 val2 both box|

	val1 := false asValue.
	val2 := false asValue.
	both := BlockValue 
		    with:[:v1 :v2 | 
			    Transcript showCr:'evaluating ...'.
			    v1 value and:[v2 value]
			 ] 
		    arguments:(Array with:val1 with:val2).

	box := Dialog new.
	box addCheckBox:'one' on:val1.
	box addCheckBox:'two' on:val2.
	box addHorizontalLine.
	box addCheckBox:'both' on:both.
	box open

    the same, using a convenient instance creation message:

	|val1 val2 both box|

	val1 := false asValue.
	val2 := false asValue.
	both := BlockValue forLogical:val1 and:val2.

	box := Dialog new.
	box addCheckBox:'one' on:val1.
	box addCheckBox:'two' on:val2.
	box addHorizontalLine.
	box addCheckBox:'both' on:both.
	box open

    logical or:

	|val1 val2 both box|

	val1 := false asValue.
	val2 := false asValue.
	both := BlockValue forLogical:val1 or:val2.

	box := Dialog new.
	box addCheckBox:'one' on:val1.
	box addCheckBox:'two' on:val2.
	box addHorizontalLine.
	box addCheckBox:'both' on:both.
	box open

    example use: enabling an element depending on two others:

	|val1 val2 enabler val3 box|

	val1 := false asValue.
	val2 := false asValue.
	val3 := false asValue.
	enabler := BlockValue forLogical:val1 and:val2.

	box := Dialog new.
	box addCheckBox:'one' on:val1.
	box addCheckBox:'two' on:val2.
	box addHorizontalLine.
	(box addCheckBox:'three' on:val3) enableChannel:enabler.
	box open
"
! !

!BlockValue class methodsFor:'initialization'!

initialize
    NeverComputed isNil ifTrue:[
	NeverComputed := Object new.
    ]
! !

!BlockValue class methodsFor:'instance creation'!

forLogical:arg1 and:arg2
    "return a new BlockValue computing the logical AND of its args"

    ^ (super new) 
	setBlock:[:a :b | a value and:[b value]]
	arguments:(Array with:arg1 with:arg2) 

    "Created: 16.12.1995 / 19:20:14 / cg"
!

forLogical:arg1 or:arg2
    "return a new BlockValue computing the logical OR of its args"

    ^ (super new) 
	setBlock:[:a :b | a value or:[b value]]
	arguments:(Array with:arg1 with:arg2) 

    "Created: 16.12.1995 / 19:20:14 / cg"
!

with:aBlock
    "return a new BlockValue computing aBlock"

    ^ (super new) setBlock:aBlock

    "Created: 16.12.1995 / 19:16:33 / cg"
!

with:aBlock argument:anArgument
    "return a new BlockValue computing aBlock"

    ^ (super new) setBlock:aBlock arguments:(Array with:anArgument)

    "Created: 16.12.1995 / 19:20:14 / cg"
!

with:aBlock arguments:aCollectionOfArguments
    "return a new BlockValue computing aBlock"

    ^ (super new) setBlock:aBlock arguments:aCollectionOfArguments

    "Created: 16.12.1995 / 19:20:14 / cg"
! !

!BlockValue methodsFor:'accessing'!

dependOn:someObject
    arguments isNil ifTrue:[
	arguments := Array with:someObject
    ] ifFalse:[
	arguments := arguments copyWith:someObject
    ].
    someObject addDependent:self

    "Modified: 16.12.1995 / 19:18:31 / cg"
!

evaluate
    arguments isNil ifTrue:[
	^ block value
    ].
    ^ block valueWithArguments:(arguments asArray)

    "Created: 16.12.1995 / 19:27:40 / cg"
!

setBlock:aBlock
    block := aBlock.
    arguments notNil ifTrue:[
	self release
    ].
    arguments := nil.
    cachedValue := NeverComputed.

    "Created: 16.12.1995 / 19:16:59 / cg"
    "Modified: 16.12.1995 / 19:51:23 / cg"
!

setBlock:aBlock arguments:aCollectionOfArguments
    block := aBlock.
    arguments notNil ifTrue:[
	self release
    ].
    arguments := aCollectionOfArguments.
    arguments do:[:arg |
	arg addDependent:self
    ].
    cachedValue := NeverComputed.

    "Created: 16.12.1995 / 19:21:41 / cg"
    "Modified: 16.12.1995 / 19:51:28 / cg"
!

setValue:newValue 
    "physically set my value, without change notifications.
     This is a noop here, since my value is computed."

    ^ self


!

value
    cachedValue == NeverComputed ifTrue:[
	cachedValue := self evaluate
    ].
    ^ cachedValue

    "Created: 16.12.1995 / 19:23:26 / cg"
    "Modified: 17.12.1995 / 15:59:16 / cg"
! !

!BlockValue methodsFor:'change and update'!

update:something with:aParameter from:someone
    |oldValue|

    oldValue := cachedValue.
    cachedValue := self evaluate.
    oldValue ~~ cachedValue ifTrue:[
	self changed:#value
    ].

    "Created: 16.12.1995 / 19:22:54 / cg"
    "Modified: 17.12.1995 / 15:58:56 / cg"
! !

!BlockValue methodsFor:'release'!

release
    arguments notNil ifTrue:[
	arguments do:[:arg | arg removeDependent:self].
    ].

    "Modified: 16.12.1995 / 19:21:11 / cg"
! !

!BlockValue class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/BlockValue.st,v 1.4 1996-01-27 18:36:36 cg Exp $'
! !
BlockValue initialize!