|
@@ -1,9 +1,9 @@
|
|
-Smalltalk createPackage: 'Lyst'!
|
|
|
|
-Object subclass: #Lyst
|
|
|
|
|
|
+Smalltalk createPackage: 'Axxord'!
|
|
|
|
+Object subclass: #Axes
|
|
instanceVariableNames: ''
|
|
instanceVariableNames: ''
|
|
- package: 'Lyst'!
|
|
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
|
|
-!Lyst class methodsFor: 'parsing'!
|
|
|
|
|
|
+!Axes class methodsFor: 'parsing'!
|
|
|
|
|
|
parse: message
|
|
parse: message
|
|
| result stack anArray |
|
|
| result stack anArray |
|
|
@@ -24,9 +24,184 @@ parse: message
|
|
^ result
|
|
^ result
|
|
! !
|
|
! !
|
|
|
|
|
|
-!Array methodsFor: '*Lyst'!
|
|
|
|
|
|
+Object subclass: #Axon
|
|
|
|
+ instanceVariableNames: 'factory'
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+!Axon commentStamp!
|
|
|
|
+I represent a pub-sub based on a key (called 'aspect').
|
|
|
|
+I manage aspect-block subscriptions (called 'interests') as well as run blocks of dirtied interests.
|
|
|
|
+The interest objects are responsible of decision if the change of an aspect is relevant for them.
|
|
|
|
+Interest object must be subclasses of `AxonInterest`.
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock
|
|
|
|
|
|
+My subclasses must provide implementation for:
|
|
|
|
+
|
|
|
|
+ - add:
|
|
|
|
+ - do:
|
|
|
|
+ - clean!
|
|
|
|
+
|
|
|
|
+!Axon methodsFor: 'action'!
|
|
|
|
+
|
|
|
|
+addInterest: anInterest
|
|
|
|
+ self
|
|
|
|
+ add: (anInterest flag; yourself);
|
|
|
|
+ dirty: true
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+changed: anAspect
|
|
|
|
+ | needsToRun |
|
|
|
|
+ needsToRun := false.
|
|
|
|
+ self do: [ :each |
|
|
|
|
+ (each accepts: anAspect) ifTrue: [
|
|
|
|
+ each flag.
|
|
|
|
+ needsToRun := true ]].
|
|
|
|
+ self dirty: needsToRun
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+changedAll
|
|
|
|
+ | needsToRun |
|
|
|
|
+ needsToRun := false.
|
|
|
|
+ self do: [ :each |
|
|
|
|
+ each flag.
|
|
|
|
+ needsToRun := true ].
|
|
|
|
+ self dirty: needsToRun
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+dirty: aBoolean
|
|
|
|
+ aBoolean ifTrue: [[ self run ] fork]
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+run
|
|
|
|
+ [
|
|
|
|
+ | needsClean |
|
|
|
|
+ needsClean := false.
|
|
|
|
+ self do: [ :each |
|
|
|
|
+ each isFlagged ifTrue: [ each run ].
|
|
|
|
+ each isEnabled ifFalse: [ needsClean := true ]
|
|
|
|
+ ].
|
|
|
|
+ needsClean ifTrue: [ self clean ]
|
|
|
|
+ ] on: Error do: [ self dirty: true ]
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!Axon methodsFor: 'injecting'!
|
|
|
|
+
|
|
|
|
+registerIn: anObject
|
|
|
|
+<inlineJS: 'anObject.$axon$=self'>
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+Axon subclass: #DumbAxon
|
|
|
|
+ instanceVariableNames: ''
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+!DumbAxon commentStamp!
|
|
|
|
+I am an axon that does nothing.!
|
|
|
|
+
|
|
|
|
+!DumbAxon methodsFor: 'as yet unclassified'!
|
|
|
|
+
|
|
|
|
+add: anInterest
|
|
|
|
+ "pass"
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+clean
|
|
|
|
+ "pass"
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+do: aBlock
|
|
|
|
+ "pass"
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+Axon subclass: #SimpleAxon
|
|
|
|
+ instanceVariableNames: 'queue'
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+
|
|
|
|
+!SimpleAxon methodsFor: 'accessing'!
|
|
|
|
+
|
|
|
|
+add: aSubscription
|
|
|
|
+ queue add: aSubscription.
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!SimpleAxon methodsFor: 'bookkeeping'!
|
|
|
|
+
|
|
|
|
+clean
|
|
|
|
+ queue := queue select: [ :each | each isEnabled ]
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!SimpleAxon methodsFor: 'enumeration'!
|
|
|
|
+
|
|
|
|
+do: aBlock
|
|
|
|
+ queue do: aBlock
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!SimpleAxon methodsFor: 'initialization'!
|
|
|
|
+
|
|
|
|
+initialize
|
|
|
|
+ super initialize.
|
|
|
|
+ queue := OrderedCollection new
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+Object subclass: #AxonInterest
|
|
|
|
+ instanceVariableNames: 'aspect actionBlock flagged'
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+
|
|
|
|
+!AxonInterest methodsFor: 'accessing'!
|
|
|
|
+
|
|
|
|
+aspect: anAspect block: aBlock
|
|
|
|
+ aspect := anAspect.
|
|
|
|
+ actionBlock := aBlock
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+flag
|
|
|
|
+ flagged := true
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!AxonInterest methodsFor: 'action'!
|
|
|
|
+
|
|
|
|
+run
|
|
|
|
+ [ flagged := false. actionBlock value ]
|
|
|
|
+ on: AxonOff do: [ actionBlock := nil ]
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!AxonInterest methodsFor: 'initialization'!
|
|
|
|
+
|
|
|
|
+initialize
|
|
|
|
+ super initialize.
|
|
|
|
+ aspect := nil.
|
|
|
|
+ actionBlock := nil.
|
|
|
|
+ flagged := false.
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+!AxonInterest methodsFor: 'testing'!
|
|
|
|
+
|
|
|
|
+accepts: anAspect
|
|
|
|
+ "Should return true if change for anAspect is relevant for this AxonInterest"
|
|
|
|
+ self subclassResponsibility
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+isEnabled
|
|
|
|
+ ^actionBlock notNil
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+isFlagged
|
|
|
|
+ ^flagged
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+AxonInterest subclass: #InterestedInEqual
|
|
|
|
+ instanceVariableNames: ''
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+
|
|
|
|
+!InterestedInEqual methodsFor: 'testing'!
|
|
|
|
+
|
|
|
|
+accepts: anAspect
|
|
|
|
+ ^ anAspect = aspect
|
|
|
|
+! !
|
|
|
|
+
|
|
|
|
+Error subclass: #AxonOff
|
|
|
|
+ instanceVariableNames: ''
|
|
|
|
+ package: 'Axxord'!
|
|
|
|
+!AxonOff commentStamp!
|
|
|
|
+Signal me from the subscription block to unsubscribe it.!
|
|
|
|
+
|
|
|
|
+!Array methodsFor: '*Axxord'!
|
|
|
|
+
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock
|
|
| receiver selector result |
|
|
| receiver selector result |
|
|
selector := self first.
|
|
selector := self first.
|
|
receiver := anObject yourself. "JSObjectProxy hack"
|
|
receiver := anObject yourself. "JSObjectProxy hack"
|
|
@@ -41,7 +216,7 @@ atYndexIn: anObject ifAbsent: aBlock
|
|
^ result
|
|
^ result
|
|
!
|
|
!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock put: anotherObject
|
|
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock put: anotherObject
|
|
| receiver selector arguments result |
|
|
| receiver selector arguments result |
|
|
selector := self first asMutator.
|
|
selector := self first asMutator.
|
|
receiver := anObject yourself. "JSObjectProxy hack"
|
|
receiver := anObject yourself. "JSObjectProxy hack"
|
|
@@ -57,50 +232,69 @@ atYndexIn: anObject ifAbsent: aBlock put: anotherObject
|
|
^ result
|
|
^ result
|
|
! !
|
|
! !
|
|
|
|
|
|
-!Number methodsFor: '*Lyst'!
|
|
|
|
|
|
+!Number methodsFor: '*Axxord'!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock
|
|
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock
|
|
(anObject respondsTo: #at:ifAbsent:)
|
|
(anObject respondsTo: #at:ifAbsent:)
|
|
ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
|
|
ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
|
|
ifFalse: aBlock
|
|
ifFalse: aBlock
|
|
!
|
|
!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock put: anotherObject
|
|
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock put: anotherObject
|
|
(anObject respondsTo: #at:put:)
|
|
(anObject respondsTo: #at:put:)
|
|
ifTrue: [ ^ anObject at: self put: anotherObject ]
|
|
ifTrue: [ ^ anObject at: self put: anotherObject ]
|
|
ifFalse: aBlock
|
|
ifFalse: aBlock
|
|
! !
|
|
! !
|
|
|
|
|
|
-!Object methodsFor: '*Lyst'!
|
|
|
|
|
|
+!Object methodsFor: '*Axxord'!
|
|
|
|
+
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock
|
|
|
|
+ ^ aBlock value
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock put: anotherObject
|
|
|
|
+ ^ aBlock value
|
|
|
|
+!
|
|
|
|
|
|
-atLyst: aCollection ifAbsent: aBlock
|
|
|
|
|
|
+atAxes: aCollection ifAbsent: aBlock
|
|
^ aCollection inject: self into: [ :soFar :segment |
|
|
^ aCollection inject: self into: [ :soFar :segment |
|
|
- segment atYndexIn: soFar ifAbsent: [ ^ aBlock value ]]
|
|
|
|
|
|
+ segment asAxisIn: soFar ifAbsent: [ ^ aBlock value ]]
|
|
!
|
|
!
|
|
|
|
|
|
-atLyst: aCollection ifAbsent: aBlock put: value
|
|
|
|
|
|
+atAxes: aCollection ifAbsent: aBlock put: value
|
|
| penultimate |
|
|
| penultimate |
|
|
penultimate := self atLyst: aCollection allButLast ifAbsent: aBlock.
|
|
penultimate := self atLyst: aCollection allButLast ifAbsent: aBlock.
|
|
- ^ aCollection last atYndexIn: penultimate ifAbsent: aBlock put: value
|
|
|
|
|
|
+ ^ aCollection last asAxisIn: penultimate ifAbsent: aBlock put: value
|
|
!
|
|
!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock
|
|
|
|
- ^ aBlock value
|
|
|
|
|
|
+axes: aCollection consume: aBlock
|
|
|
|
+ | value |
|
|
|
|
+ value := self atLyst: aCollection ifAbsent: [ ^self ].
|
|
|
|
+ ^ aBlock value: value
|
|
!
|
|
!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock put: anotherObject
|
|
|
|
- ^ aBlock value
|
|
|
|
|
|
+axes: aCollection transform: aBlock
|
|
|
|
+ | value |
|
|
|
|
+ aCollection last. "raise if empty"
|
|
|
|
+ value := self atLyst: aCollection ifAbsent: [ ^self ].
|
|
|
|
+ value := aBlock value: value.
|
|
|
|
+ value := self atLyst: aCollection ifAbsent: [ ^self ] put: value.
|
|
|
|
+ self registeredAxon ifNotNil: [:axon | axon changed: aCollection]
|
|
|
|
+!
|
|
|
|
+
|
|
|
|
+registeredAxon
|
|
|
|
+<inlineJS: 'return self.$axon$'>
|
|
! !
|
|
! !
|
|
|
|
|
|
-!String methodsFor: '*Lyst'!
|
|
|
|
|
|
+!String methodsFor: '*Axxord'!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock
|
|
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock
|
|
(anObject respondsTo: #at:ifAbsent:)
|
|
(anObject respondsTo: #at:ifAbsent:)
|
|
ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
|
|
ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
|
|
ifFalse: aBlock
|
|
ifFalse: aBlock
|
|
!
|
|
!
|
|
|
|
|
|
-atYndexIn: anObject ifAbsent: aBlock put: anotherObject
|
|
|
|
|
|
+asAxisIn: anObject ifAbsent: aBlock put: anotherObject
|
|
(anObject respondsTo: #at:put:)
|
|
(anObject respondsTo: #at:put:)
|
|
ifTrue: [ ^ anObject at: self put: anotherObject ]
|
|
ifTrue: [ ^ anObject at: self put: anotherObject ]
|
|
ifFalse: aBlock
|
|
ifFalse: aBlock
|