123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302 |
- Smalltalk createPackage: 'Axxord'!
- Object subclass: #Axes
- instanceVariableNames: ''
- package: 'Axxord'!
- !Axes class methodsFor: 'parsing'!
- parse: message
- | result stack anArray |
- anArray := message tokenize: ' '.
- result := #().
- stack := { result }.
- anArray do: [ :each |
- | asNum inner close |
- close := 0.
- inner := each.
- [ inner notEmpty and: [ inner first = '(' ]] whileTrue: [ inner := inner allButFirst. stack add: (stack last add: #()) ].
- [ inner notEmpty and: [ inner last = ')' ]] whileTrue: [ inner := inner allButLast. close := close + 1 ].
- (inner notEmpty and: [ inner first = '~' ]) ifTrue: [ inner := { inner allButFirst } ].
- asNum := inner isString ifTrue: [ (inner ifEmpty: [ 'NaN' ]) asNumber ] ifFalse: [ inner ].
- asNum = asNum ifTrue: [ stack last add: asNum ] ifFalse: [
- inner ifNotEmpty: [ stack last add: inner ] ].
- close timesRepeat: [ stack removeLast ] ].
- ^ result
- ! !
- 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`.
- 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 |
- selector := self first.
- receiver := anObject yourself. "JSObjectProxy hack"
-
- [ result := receiver perform: selector ]
- on: MessageNotUnderstood do: [ :mnu |
- ((mnu message selector = selector
- and: [ mnu receiver == receiver ])
- and: [ mnu message arguments isEmpty ])
- ifFalse: [ mnu resignal ].
- ^ aBlock value ].
- ^ result
- !
- asAxisIn: anObject ifAbsent: aBlock put: anotherObject
- | receiver selector arguments result |
- selector := self first asMutator.
- receiver := anObject yourself. "JSObjectProxy hack"
- arguments := { anotherObject }.
-
- [ result := receiver perform: selector withArguments: arguments ]
- on: MessageNotUnderstood do: [ :mnu |
- ((mnu message selector = selector
- and: [ mnu receiver == receiver ])
- and: [ mnu message arguments = arguments ])
- ifFalse: [ mnu resignal ].
- ^ aBlock value ].
- ^ result
- ! !
- !Number methodsFor: '*Axxord'!
- asAxisIn: anObject ifAbsent: aBlock
- (anObject respondsTo: #at:ifAbsent:)
- ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
- ifFalse: aBlock
- !
- asAxisIn: anObject ifAbsent: aBlock put: anotherObject
- (anObject respondsTo: #at:put:)
- ifTrue: [ ^ anObject at: self put: anotherObject ]
- ifFalse: aBlock
- ! !
- !Object methodsFor: '*Axxord'!
- asAxisIn: anObject ifAbsent: aBlock
- ^ aBlock value
- !
- asAxisIn: anObject ifAbsent: aBlock put: anotherObject
- ^ aBlock value
- !
- atAxes: aCollection ifAbsent: aBlock
- ^ aCollection inject: self into: [ :soFar :segment |
- segment asAxisIn: soFar ifAbsent: [ ^ aBlock value ]]
- !
- atAxes: aCollection ifAbsent: aBlock put: value
- | penultimate |
- penultimate := self atLyst: aCollection allButLast ifAbsent: aBlock.
- ^ aCollection last asAxisIn: penultimate ifAbsent: aBlock put: value
- !
- axes: aCollection consume: aBlock
- | value |
- value := self atLyst: aCollection ifAbsent: [ ^self ].
- ^ aBlock value: 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: '*Axxord'!
- asAxisIn: anObject ifAbsent: aBlock
- (anObject respondsTo: #at:ifAbsent:)
- ifTrue: [ ^ anObject at: self ifAbsent: aBlock ]
- ifFalse: aBlock
- !
- asAxisIn: anObject ifAbsent: aBlock put: anotherObject
- (anObject respondsTo: #at:put:)
- ifTrue: [ ^ anObject at: self put: anotherObject ]
- ifFalse: aBlock
- ! !
|