extensions.st
author Stefan Vogel <sv@exept.de>
Fri, 18 Jan 2008 20:40:51 +0100
changeset 1922 be14f1a04953
parent 1759 78e481899a63
child 2149 329461c02e84
permissions -rw-r--r--
#add:beforeIndex: - make immune against redefinition of #add: using #add:beforeIndex in subclasses (and leading to recursion).

"{ Package: 'stx:libbasic2' }"
!

!Object methodsFor:'dependents-interests'!

addInterest:anInterest
    "install an interest forwarder.
     Here, we use the nonWeakDependencies."

    self addNonWeakDependent:anInterest

    "Created: 14.10.1996 / 22:27:34 / stefan"
! !

!Object methodsFor:'dependents-interests'!

expressInterestIn:aspect for:anObject sendBack:aSelector
    "arrange for aSelector to be sent to anObject whenever the receiver
     changes aspect."

    "/ for now, use an interestConverter, which is somewhat less efficient.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    self addInterest:(InterestConverter 
                            destination:anObject 
                            selector:aSelector 
                            aspect:aspect)

    "
     |p b|

     b := [Transcript showCR:' -> the point changed'].

     p := Point new.
     Transcript showCR:'interest in #foo:'.
     p expressInterestIn:#foo for:b sendBack:#value.
     p x:1.
     Transcript showCR:'now changing #bar ... (expect no notification)'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'now changing #foo ... (expect notification)'.
     p changed:#foo.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interest in #foo:'.
     p retractInterestIn:#foo for:b.
     Transcript showCR:'now changing #foo ... (expect no notification)'.
     p changed:#foo.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest in #bar now:'.
     p expressInterestIn:#bar for:b sendBack:#value.
     Transcript showCR:'now changing #foo ... (expect no notification)'.
     p changed:#foo.
     Transcript showCR:'now changing #bar ... (expect notification)'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest in #foo now:'.
     p expressInterestIn:#foo for:b sendBack:#value.
     Transcript showCR:'now changing #foo ... (expect notification)'.
     p changed:#foo.
     Transcript showCR:'now changing #bar ... (expect notification)'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interests:'.
     p retractInterestsFor:b.
     Transcript showCR:'now changing #foo ... (expect no notification)'.
     p changed:#foo.
     Transcript showCR:'now changing #bar...  (expect no notification)'.
     p changed:#bar.
     Transcript cr.

     p release.
    "

    "Created: 19.4.1996 / 10:26:22 / cg"
    "Modified: 19.4.1996 / 12:34:08 / cg"
    "Modified: 14.10.1996 / 22:28:20 / stefan"
! !

!Object methodsFor:'dependents-interests'!

interests
    "return a Collection of interests - empty if there is none.
     Here, we use the nonWeakDependents for interests."

    ^ self nonWeakDependents

    "Created: / 14.10.1996 / 22:20:51 / stefan"
    "Modified: / 30.1.1998 / 14:07:35 / cg"
! !

!Object methodsFor:'dependents-interests'!

interestsFor:someOne
    "return a collection of interests of someOne - empty if there is none."

    |coll deps|

    deps := self interests.
    deps size == 0 ifTrue:[^ #()].

    coll := IdentitySet new.

    deps do:[:dep |
        (dep isInterestConverter) ifTrue:[
            dep destination == someOne ifTrue:[
                coll add:dep.
            ]
        ]
    ].
    ^ coll

    "Created: / 30.1.1998 / 14:02:26 / cg"
    "Modified: / 30.1.1998 / 14:08:24 / cg"
! !

!Object methodsFor:'dependents-interests'!

onChangeEvaluate:aBlock
    "arrange for aBlock to be evaluated whenever the receiver changes."

    ^ self onChangeSend:#value to:aBlock

    "
     |p b|

     b := [Transcript showCR:' -> the point changed'].

     p := Point new.
     Transcript showCR:'interest in #foo:'.
     p onChangeEvaluate:b.
     p x:1.
     Transcript showCR:'now changing #bar ... (expect no notification)'.
     p changed:#bar.

     p retractInterests.
     p changed:#bar.
    "
! !

!Object methodsFor:'dependents-interests'!

onChangeSend:aSelector to:anObject
    "arrange for aSelector to be sent to anObject whenever the receiver
     changes."

    "/ for now, use an interestConverter, which is somewhat less efficient.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    ((self interests ? #())
        contains:[:anInterest |
            (anInterest isInterestConverter)
            and:[ anInterest destination == anObject
            and:[ anInterest selector == aSelector]]
        ])
            ifTrue:[^ self].

    self addInterest:(InterestConverter 
                          destination:anObject 
                          selector:aSelector)

    "
     |p b|

     b := [Transcript showCR:'the point changed'].

     p := Point new.
     p onChangeSend:#value to:b.
     p x:1.
     Transcript showCR:'now changing'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'now changing'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interest'.
     p retractInterestsFor:b.
     Transcript showCR:'now changing again'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest again'.
     p onChangeSend:#value to:b.
     Transcript showCR:'now changing again'.
     p changed.
     Transcript cr.
    "

    "Created: 19.4.1996 / 10:26:38 / cg"
    "Modified: 19.4.1996 / 12:34:26 / cg"
    "Modified: 14.10.1996 / 22:28:27 / stefan"
! !

!Object methodsFor:'dependents-interests'!

removeInterest:anInterest
    "remove an interest forwarder.
     Here, we use the nonWeakDependencies."

    self removeNonWeakDependent:anInterest

    "Created: 14.10.1996 / 22:21:59 / stefan"
! !

!Object methodsFor:'dependents-interests'!

retractInterestIn:aspect for:someOne
    "remove the interest of someOne in the receiver changing aspect
     (as installed with #expressInterestIn:for:sendBack:)."

    "/ for now, remove the interestConverter.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    self retractInterestsForWhich:[:i | (i aspect == aspect) and:[i destination == someOne]]

    "
     |p b|

     b := [Transcript showCR:'the point changed'].

     p := Point new.
     Transcript showCR:'interest in #foo'.
     p expressInterestIn:#foo for:b sendBack:#value.
     p x:1.
     Transcript showCR:'now changing #bar'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'now changing #foo'.
     p changed:#foo.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interest in #foo'.
     p retractInterestIn:#foo for:b.
     Transcript showCR:'now changing #foo'.
     p changed:#foo.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest in #bar now'.
     p expressInterestIn:#bar for:b sendBack:#value.
     Transcript showCR:'now changing #foo'.
     p changed:#foo.
     Transcript showCR:'now changing #bar'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest in #foo now'.
     p expressInterestIn:#foo for:b sendBack:#value.
     Transcript showCR:'now changing #foo'.
     p changed:#foo.
     Transcript showCR:'now changing #bar'.
     p changed:#bar.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interests'.
     p retractInterestsFor:b.
     Transcript showCR:'now changing #foo'.
     p changed:#foo.
     Transcript showCR:'now changing #bar'.
     p changed:#bar.
     Transcript cr.
    "

    "Created: / 19.4.1996 / 10:27:11 / cg"
    "Modified: / 14.10.1996 / 22:21:19 / stefan"
    "Modified: / 30.1.1998 / 14:05:34 / cg"
! !

!Object methodsFor:'dependents-interests'!

retractInterests
    "remove all interests in the receiver changing aspect
     (as installed with #expressInterestIn:for:sendBack:)."

    "/ for now, remove the interestConverter.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    self retractInterestsForWhich:[:i | true ]
! !

!Object methodsFor:'dependents-interests'!

retractInterestsFor:someOne
    "remove the interest of someOne in the receiver 
     (as installed with #onChangeSend:to:)."

    "/ for now, remove the interestConverter.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    self retractInterestsForWhich:[:i | i destination == someOne ]

    "
     |p b|

     b := [Transcript showCR:'the point changed'].

     p := Point new.
     p onChangeSend:#value to:b.
     p x:1.
     Transcript showCR:'now changing'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'now changing'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'no more interest'.
     p retractInterestsFor:b.
     Transcript showCR:'now changing again'.
     p changed.
     Transcript cr.

     Delay waitForSeconds:1.
     Transcript showCR:'interest again'.
     p onChangeSend:#value to:b.
     Transcript showCR:'now changing again'.
     p changed.
     Transcript cr.
    "

    "Created: / 19.4.1996 / 10:23:46 / cg"
    "Modified: / 14.10.1996 / 22:21:25 / stefan"
    "Modified: / 30.1.1998 / 14:04:52 / cg"
! !

!Object methodsFor:'dependents-interests'!

retractInterestsForWhich:aBlock
    "remove all interests in the receiver changing aspect
     (as installed with #expressInterestIn:for:sendBack:)."

    "/ for now, remove the interestConverter.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    |deps coll|

    deps := self interests.
    deps size ~~ 0 ifTrue:[
        "/ cannot removeDependent within the loop - the interests collection rehashes
        coll := OrderedCollection new.
        deps do:[:dep |
            dep isInterestConverter ifTrue:[
                (aBlock value:dep) ifTrue:[coll add:dep].
            ]
        ].
        coll do:[:dep |
            self removeInterest:dep.
        ].
    ].
! !

!Object methodsFor:'dependents-interests'!

retractInterestsIn:aspect
    "remove all interests in the receiver changing aspect
     (as installed with #expressInterestIn:for:sendBack:)."

    "/ for now, remove the interestConverter.
    "/ In the future, a more intelligent DependencyCollection class is planned for

    self retractInterestsForWhich:[:i | i aspect == aspect ]
! !

!Object methodsFor:'dependents-st/v event simulation'!

when:eventSymbol send:selector to:anObject
    "install an ST/V-style interest forwarder.
     Here, we use the nonWeakDependencies."

    self addInterest:(InterestConverterWithParameters
                            destination:anObject 
                            selector:selector 
                            aspect:eventSymbol).

    "
     |p b|

     b := [Transcript showCR:'the point changed'].

     p := Point new.
     p whem:#foo:bar: send:#value:value: to:[:a :b | Transcript show:'foo: '; show:a; show:' bar: '; showCR:b].
     Transcript showCR:'now changing'.
     p triggerEvent:#foo:bar: withArguments:#('fooArg' 'barArg').
     p retracrtInterests.
    "
! !