Skip to content

Commit

Permalink
Introduce ObservableSlot as part of VariableLibrary.
Browse files Browse the repository at this point in the history
This slot is a copy of the spec SpObservableSlot and will replace this one.

This slot comes with tests and I improved the documentation that was started in Spec.
  • Loading branch information
jecisc committed Oct 10, 2019
1 parent dbf8f03 commit a2105f1
Show file tree
Hide file tree
Showing 15 changed files with 420 additions and 8 deletions.
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/ComputedSlotTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #ComputedSlotTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/HistorySlotTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #HistorySlotTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #InitializedClassVariableTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/InitializedSlotTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #InitializedSlotTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/LazyClassVariableTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #LazyClassVariableTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/LazySlotTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #LazySlotTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
42 changes: 42 additions & 0 deletions src/VariablesLibrary-Tests/ObservablePoint.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
"
I am a mock point used to test observable properties. I have an observable property x and a non-observable property y.
I use TObservable that has methods to ease the usage of my observable properties.
"
Class {
#name : #ObservablePoint,
#superclass : #Object,
#traits : 'TObservable',
#classTraits : 'TObservable classTrait',
#instVars : [
'#x => ObservableSlot',
'#y'
],
#category : #'VariablesLibrary-Tests-Observable'
}

{ #category : #initialization }
ObservablePoint >> initialize [
super initialize.
self class initializeSlots: self.
]

{ #category : #accessing }
ObservablePoint >> x [
^ x
]

{ #category : #accessing }
ObservablePoint >> x: anInteger [
x := anInteger
]

{ #category : #accessing }
ObservablePoint >> y [
^ y
]

{ #category : #accessing }
ObservablePoint >> y: anInteger [
y := anInteger
]
104 changes: 104 additions & 0 deletions src/VariablesLibrary-Tests/ObservableSlotTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,104 @@
Class {
#name : #ObservableSlotTest,
#superclass : #TestCase,
#instVars : [
'point'
],
#category : #'VariablesLibrary-Tests-Observable'
}

{ #category : #running }
ObservableSlotTest >> setUp [
super setUp.
point := ObservablePoint new
]

{ #category : #tests }
ObservableSlotTest >> testChangeInInstanceVariableRaisesEventOnlyOnce [
| count |
count := 0.
point property: #x whenChangedDo: [ count := count + 1 ].

point x: 17.

self assert: count equals: 1
]

{ #category : #tests }
ObservableSlotTest >> testExplicitNotificationRaisesEventOnlyOnce [
| count |
count := 0.
point property: #x whenChangedDo: [ count := count + 1 ].

point notifyPropertyChanged: #x.

self assert: count equals: 1
]

{ #category : #tests }
ObservableSlotTest >> testExplicitNotificationRaisesEventWithNewValue [
| newValue |
point x: 17.
point property: #x whenChangedDo: [ :new | newValue := new ].

point notifyPropertyChanged: #x.

self assert: newValue equals: 17
]

{ #category : #tests }
ObservableSlotTest >> testExplicitNotifyUnexistentPropertyChangedRaisesError [
self should: [ point notifyPropertyChanged: #z ] raise: SlotNotFound
]

{ #category : #tests }
ObservableSlotTest >> testObservableSlotWorksAsNormalSlot [
point x: 17.
point y: 299.

self assert: point x equals: 17.
self assert: point y equals: 299
]

{ #category : #tests }
ObservableSlotTest >> testSubscribeBlockWithoutParametersIsCalled [
| called |
called := false.
point property: #x whenChangedDo: [ called := true ].

point x: 17.

self assert: called
]

{ #category : #tests }
ObservableSlotTest >> testSubscribeToChangeRaisesEventWithNewValue [
| newValue |
point property: #x whenChangedDo: [ :new | newValue := new ].

point x: 17.

self assert: newValue equals: 17
]

{ #category : #tests }
ObservableSlotTest >> testSubscribeToExistentNonObservablePropertyRaisesError [

self
should: [
point
property: #y
whenChangedDo: [ self fail: 'This event shouldnt have been subscribed at all' ] ]
raise: NonObservableSlotError
]

{ #category : #tests }
ObservableSlotTest >> testSubscribeToUnexistentPropertyRaisesError [

self
should: [
point
property: #z
whenChangedDo: [ self fail: 'This event shouldnt have been subscribed at all' ] ]
raise: SlotNotFound
]
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/WeakClassVariableTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #WeakClassVariableTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/VariablesLibrary-Tests/WeakSlotTest.class.st
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Class {
#name : #WeakSlotTest,
#superclass : #SlotSilentTest,
#category : #'VariablesLibrary-Tests'
#category : #'VariablesLibrary-Tests-Tests'
}

{ #category : #tests }
Expand Down
8 changes: 8 additions & 0 deletions src/VariablesLibrary/NonObservableSlotError.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
"
I am an error raised when a user try to interact with a slot as an observable slot, but this slot is not observable.
"
Class {
#name : #NonObservableSlotError,
#superclass : #Error,
#category : #'VariablesLibrary-Observable'
}
87 changes: 87 additions & 0 deletions src/VariablesLibrary/ObservableSlot.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,87 @@
"
I am a slot allowing users to register behavior to execute when my value change.
The classes using me should use TObservable alongside with me. This trait will give them methods to interact with me.
I am able to prevent infinit loop by locking the executions of the actions I store while they are executed. This is useful if two observable slots update each other during their registered actions.
Public API and Key Messages
--------------------
My users will not interact directly with me but via TObservable.
Check the class comment of this trait for more information.
Examples
--------------------
Object subclass: #ObservablePoint
uses: TObservable
slots: { #x => ObservableSlot. #y }
classVariables: { }
package: 'VariablesLibrary-Tests-Observable'
Internal Representation and Key Implementation Points.
--------------------
I am wrapping a ObservableValueHolder in order to store the content of the variable and to register the actions to execute when it changes.
"
Class {
#name : #ObservableSlot,
#superclass : #IndexedSlot,
#category : #'VariablesLibrary-Observable'
}

{ #category : #'code generation' }
ObservableSlot >> emitStore: aMethodBuilder [
"generate bytecode for 'varName value: <stackTop>'"

| temp |
temp := Object new. "we need a unique Object as a temp name"
"We pop the value from the stack into a temp to push it back in the right order"
aMethodBuilder addTemp: temp.
aMethodBuilder storeTemp: temp.
aMethodBuilder popTop.

"Push the value holder into the stack, then the value again, then send"
aMethodBuilder pushInstVar: index.
aMethodBuilder pushTemp: temp.
aMethodBuilder send: #value:
]

{ #category : #'code generation' }
ObservableSlot >> emitValue: aMethodBuilder [
"Push the value holder into the stack"
aMethodBuilder pushInstVar: index.
aMethodBuilder send: #value
]

{ #category : #initialization }
ObservableSlot >> initialize: anObject [
super write: ObservableValueHolder new to: anObject
]

{ #category : #testing }
ObservableSlot >> isObservable [
^ true
]

{ #category : #'meta-object-protocol' }
ObservableSlot >> rawRead: anObject [
^ super read: anObject
]

{ #category : #'meta-object-protocol' }
ObservableSlot >> read: anObject [
^ (self rawRead: anObject) value
]

{ #category : #'meta-object-protocol' }
ObservableSlot >> wantsInitialization [
^ true
]

{ #category : #'meta-object-protocol' }
ObservableSlot >> write: aValue to: anObject [
(self rawRead: anObject) ifNotNil: [ :v | v value: aValue ].
^ aValue
]
Loading

0 comments on commit a2105f1

Please sign in to comment.