BlockValue.st
author tz
Mon, 29 Jun 1998 16:45:52 +0200
changeset 988 daebc00918d4
parent 979 cd28a5d673c9
child 1045 c501e3553048
permissions -rw-r--r--
images placed here

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

    Notice: 
        this class was implemented using protocol information
        from alpha testers - it may not be complete or compatible to
        the corresponding ST-80 class. 
        If you encounter any incompatibilities, please forward a note 
        describing the incompatibility verbal (i.e. no code) to the ST/X team.

    [author:]
        Claus Gittinger
"

!

examples
"
    checkToggle 3 shows the value of toggle1 AND toggle2
                                                                        [exBegin]
        |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 addOkButton.
        box open
                                                                        [exEnd]

    the same, using a convenient instance creation message:
                                                                        [exBegin]
        |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) disable.
        box addOkButton.
        box open
                                                                        [exEnd]

    logical or:
                                                                        [exBegin]
        |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 addOkButton.
        box open
                                                                        [exEnd]

    example use: enabling an element depending on two others:
                                                                        [exBegin]
        |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 (both of the above)' on:val3) enableChannel:enabler.
        box addOkButton.
        box open
                                                                        [exEnd]


    like above, using a logical-or block:
                                                                        [exBegin]
        |val1 val2 enabler val3 box|

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

        box := Dialog new.
        box addCheckBox:'one' on:val1.
        box addCheckBox:'two' on:val2.
        box addHorizontalLine.
        (box addCheckBox:'three (any of the above)' on:val3) enableChannel:enabler.
        box addOkButton.
        box open
                                                                        [exEnd]


    like above, using a bunch of toggles:
                                                                        [exBegin]
        |values anyValue box|

        values := (1 to:10) collect:[:i | false asValue].
        anyValue := BlockValue forLogicalOrAll:values.
        anyValue onChangeSend:#value to:[Transcript showCR:'any is true'].

        box := Dialog new.
        values keysAndValuesDo:[:index :aValueHolder |
            box addCheckBox:index printString on:aValueHolder.
        ].
        box addHorizontalLine.
        (box addOkButton) enableChannel:anyValue.
        box open
                                                                        [exEnd]
"
! !

!BlockValue class methodsFor:'initialization'!

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

!BlockValue class methodsFor:'instance creation'!

block:aBlock arguments:aCollectionOfArguments
    "return a new BlockValue computing aBlock.
     Same as #with:arguments: for ST80 compatibility"

    ^ self with:aBlock arguments:aCollectionOfArguments

    "Created: / 20.6.1998 / 14:00:16 / cg"
!

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

forLogicalAndAll:argArray
    "return a new BlockValue computing the logical OR of all elements
     in the passed argArray"

    ^ (super new) 
        setBlock:[:a | (argArray findFirst:[:a | a value not]) == 0]
        argumentArray:argArray asArray

    "Created: / 22.1.1997 / 19:12:44 / cg"
    "Modified: / 28.4.1998 / 20:16:38 / ca"
!

forLogicalOrAll:argArray
    "return a new BlockValue computing the logical OR of all elements
     in the passed argArray"

    ^ (super new) 
        setBlock:[:arg | (arg findFirst:[:el | el value]) ~~ 0]
        argumentArray:argArray asArray

    "Created: / 22.1.1997 / 19:13:01 / cg"
    "Modified: / 17.6.1997 / 18:05:12 / cg"
    "Modified: / 28.4.1998 / 20:20:09 / ca"
!

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

computeValue
    "evaluate the receivers action block"

    |sz|

    arguments isNil ifTrue:[
        ^ block value
    ].
    sz := arguments size.
    sz == 0 ifTrue:[
        ^ block value
    ].
    sz == 1 ifTrue:[
        ^ block value:(arguments at:1) value
    ].
    sz == 2 ifTrue:[
        ^ block value:(arguments at:1) value
                value:(arguments at:2) value
    ].
    sz == 3 ifTrue:[
        ^ block value:(arguments at:1) value
                value:(arguments at:2) value
                value:(arguments at:3) value
    ].
    ^ block 
        valueWithArguments:(arguments collect:[:arg | arg value]) asArray

    "Created: 16.12.1995 / 19:27:40 / cg"
    "Modified: 22.1.1997 / 19:05:57 / cg"
!

dependOn:someObject
    "arrange for the blockValue to be reevaluated, whenever someObject
     changes (i.e. sends a change notification)"

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

    "Modified: 22.1.1997 / 19:05:26 / cg"
!

evaluate
    "evaluate the receivers action block"

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

    "Created: 16.12.1995 / 19:27:40 / cg"
    "Modified: 22.1.1997 / 19:05:57 / cg"
!

setBlock:aBlock
    "set the receivers action block"

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

    "Created: 16.12.1995 / 19:16:59 / cg"
    "Modified: 22.1.1997 / 19:05:54 / cg"
!

setBlock:aBlock argumentArray:anArgumentCollection
    "set the receivers action block, and define an arguments collection
     to be passed to it.
     A change in any element of the collection will force reevaluation of the 
     action block (passing the collection as a single argument)
     - possibly generating another change from myself"

    block := aBlock.
    arguments notNil ifTrue:[
        self release
    ].
    arguments := Array with:anArgumentCollection.
    anArgumentCollection do:[:arg |
        arg addDependent:self
    ].
    cachedValue := NeverComputed.

    "Modified: 22.1.1997 / 19:08:51 / cg"
    "Created: 22.1.1997 / 19:22:13 / cg"
!

setBlock:aBlock arguments:aCollectionOfArguments
    "set the receivers action block, and define arguments to be passed to it.
     A change in any of the arguments will force reevaluation of the action
     block - possibly generating another change from myself"

    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: 22.1.1997 / 19:08:51 / cg"
!

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

    ^ self


!

value
    "retrieve my value - this does not always evaluate the action block,
     since the returned value is cached internally"

    cachedValue == NeverComputed ifTrue:[
        cachedValue := self computeValue
    ].
    ^ cachedValue

    "Created: 16.12.1995 / 19:23:26 / cg"
    "Modified: 22.1.1997 / 19:06:59 / cg"
! !

!BlockValue methodsFor:'change & update'!

update:something with:aParameter from:someone
    "the one I depend on has changed - reevaluate may actionBlock,
     and possibly send a change notification to my dependents"

    |oldValue|

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

    "Created: 16.12.1995 / 19:22:54 / cg"
    "Modified: 22.1.1997 / 19:07:39 / cg"
! !

!BlockValue methodsFor:'release'!

release
    "release any dependencies upon the arguments"

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

    "Modified: 22.1.1997 / 19:08:06 / cg"
! !

!BlockValue class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/BlockValue.st,v 1.13 1998-06-20 12:00:51 cg Exp $'
! !
BlockValue initialize!