Merge branch 'with-let'

This commit is contained in:
Dan Holmsand 2015-09-24 11:00:32 +02:00
commit be1dfaeba7
15 changed files with 1334 additions and 142 deletions

View File

@ -29,10 +29,23 @@
[:input {:value @val
:on-change #(reset! val (.-target.value %))}]])
(defn name-part [key]
(get-in @person [:name key]))
(def track reagent.ratom/track)
(defn foo [])
(defn name-edit [n]
(let [{:keys [first-name last-name]} @n]
[:div
[:p "I'm editing " first-name " " last-name "."]
[:p "I'm editing " @(track name-part :first-name) " "
@(track name-part :last-name) "."]
[:p "I'm editing " @(track name-part :first-name) " "
@(track name-part :last-name) "."]
[:p "I'm editing " @(track name-part :first-name) " "
@(track name-part :last-name) "."]
[input "First name: " (r/wrap first-name
swap! n assoc :first-name)]

View File

@ -47,6 +47,7 @@
{:compiler {:optimizations :advanced
:elide-asserts true
:pretty-print false
;; :pseudo-names true
:output-dir "target/client"}}}}}]
:prod-test [:test :prod]

5
src/reagent/core.clj Normal file
View File

@ -0,0 +1,5 @@
(ns reagent.core
(:require [reagent.ratom :as ra]))
(defmacro with-let [bindings & body]
`(ra/with-let ~bindings ~@body))

View File

@ -1,5 +1,5 @@
(ns reagent.core
(:require-macros [reagent.core])
(:refer-clojure :exclude [partial atom flush])
(:require [cljsjs.react]
[reagent.impl.template :as tmpl]
@ -221,6 +221,19 @@ re-rendered."
([x] (ratom/atom x))
([x & rest] (apply ratom/atom x rest)))
(defn track
[f & args]
{:pre [(ifn? f)]}
(ratom/make-track f args))
(defn track!
[f & args]
{:pre [(ifn? f)]}
(ratom/make-track! f args))
(defn dispose!
[x]
(ratom/dispose! x))
(defn wrap
"Provide a combination of value and callback, that looks like an atom.
@ -277,6 +290,27 @@ another cursor) these cursors are equivalent:
;; Utilities
(defn rswap!
"Swaps the value of a to be (apply f current-value-of-atom args).
rswap! works like swap!, except that recursive calls to rswap! on
the same atom are allowed and it always returns nil."
[a f & args]
{:pre [(satisfies? IAtom a)
(ifn? f)]}
(if a.rswapping
(-> (or a.rswapfs (set! a.rswapfs (array)))
(.push #(apply f % args)))
(do (set! a.rswapping true)
(try (swap! a (fn [state]
(loop [s (apply f state args)]
(if-some [sf (some-> a.rswapfs .shift)]
(recur (sf s))
s))))
(finally
(set! a.rswapping false)))))
nil)
(defn next-tick
"Run f using requestAnimationFrame or equivalent."
[f]

View File

@ -37,7 +37,10 @@
(dotimes [i (alength a)]
(let [c (aget a i)]
(when (.' c :cljsIsDirty)
(.' c forceUpdate)))))
(let [a (.' c :cljsRatom)]
(if (ratom/-check-clean a)
(.! c :cljsIsDirty false)
(.' c forceUpdate)))))))
(defn run-funs [a]
(dotimes [i (alength a)]
@ -56,14 +59,17 @@
(set! scheduled? true)
(next-tick #(.run-queue this))))
(run-queue [_]
(let [q queue aq after-render]
(ratom/flush!)
(let [q queue
aq after-render]
(set! queue (array))
(set! after-render (array))
(set! scheduled? false)
(run-queue q)
(run-funs aq))))
(def render-queue (RenderQueue. (array) false (array)))
(defonce render-queue (RenderQueue. (array) false (array)))
(set! ratom/render-queue render-queue)
(defn flush []
(.run-queue render-queue))
@ -98,7 +104,8 @@
(.! c :cljsRatom
(ratom/make-reaction run
:auto-run #(queue-render c)
:derefed derefed)))
:capture derefed
:no-cache true)))
res)
(ratom/run rat))))

View File

@ -12,3 +12,42 @@
:auto-run true)]
(deref co#)
co#))
(defmacro with-let [bindings & body]
(assert (vector? bindings))
(let [v (gensym "bind-v")
bs (->> bindings
(map-indexed (fn [i x]
(if (even? i)
x
(let [pos (quot i 2)]
`(if (> (alength ~v) ~pos)
(aget ~v ~pos)
(aset ~v ~pos ~x))))))
vec)
[forms destroy] (let [fin (last body)]
(if (and (list? fin)
(= 'finally (first fin)))
[(butlast body) `(fn [] ~@(rest fin))]
[body nil]))
destroy-obj (when destroy
`(cljs.core/js-obj))
asserting (if *assert* true false)]
`(let [destroy-obj# ~destroy-obj
~v (reagent.ratom/get-cached-values (quote ~v) destroy-obj#)]
(when ~asserting
(when-some [c# reagent.ratom/*ratom-context*]
(when (== (.-ratomGeneration c#)
(.-generation ~v))
(js/console.error
"The same with-let is being used more than once in the
same reactive context."))
(set! (.-generation ~v) (.-ratomGeneration c#))))
(let ~bs
(let [destroy# ~destroy
res# (do ~@forms)]
(when-not (nil? destroy#)
(if (reagent.ratom/reactive?)
(set! (.-destroy destroy-obj#) destroy#)
(destroy#)))
res#)))))

View File

@ -5,19 +5,34 @@
[reagent.debug :refer-macros [dbg log warn dev?]]))
(declare ^:dynamic *ratom-context*)
(defonce cached-reactions {})
(defonce debug false)
(defn ^boolean reactive? []
(some? *ratom-context*))
(defonce ^boolean debug false)
(defonce ^boolean silent false)
(defonce generation 0)
(defonce -running (clojure.core/atom 0))
(defn running [] @-running)
(defn running []
(+ @-running
(count cached-reactions)))
(defn capture-derefed [f obj]
(set! (.-cljsCaptured obj) nil)
(when (dev?)
(set! (.-ratomGeneration obj)
(set! generation (inc generation))))
(binding [*ratom-context* obj]
(f)))
(defn captured [obj]
(when (some? (.-cljsCaptured obj))
obj))
(defn- -captured [obj]
(let [c (.-cljsCaptured obj)]
(set! (.-cljsCaptured obj) nil)
c))
@ -30,6 +45,11 @@
(conj (if (nil? captured) #{} captured)
derefable))))))
(defn- check-watches [old new]
(when debug
(swap! -running + (- (count new) (count old))))
new)
;;; Atom
@ -83,9 +103,9 @@
nil)
nil watches))
(-add-watch [this key f]
(set! watches (assoc watches key f)))
(set! watches (check-watches watches (assoc watches key f))))
(-remove-watch [this key]
(set! watches (dissoc watches key)))
(set! watches (check-watches watches (dissoc watches key))))
IHash
(-hash [this] (goog/getUid this)))
@ -97,11 +117,74 @@
;;; cursor
;;; track
(declare make-reaction)
(deftype RCursor [ratom path ^:mutable reaction]
(defn- cached-reaction [f key obj destroy]
(if-some [r (get cached-reactions key)]
(-deref r)
(if (some? *ratom-context*)
(let [r (make-reaction
f :on-dispose (fn []
(set! cached-reactions
(dissoc cached-reactions key))
(when (some? obj)
(set! (.-reaction obj) nil))
(when (some-> destroy .-destroy some?)
(.destroy destroy))))
v (-deref r)]
(set! cached-reactions (assoc cached-reactions key r))
(when (some? obj)
(set! (.-reaction obj) r))
v)
(f))))
(deftype Track [f key ^:mutable reaction]
IReactiveAtom
IDeref
(-deref [this]
(if-some [r reaction]
(-deref r)
(cached-reaction f key this nil)))
IEquiv
(-equiv [o other]
(and (instance? Track other)
(= key (.-key other))))
IHash
(-hash [this] (hash key))
IPrintWithWriter
(-pr-writer [a writer opts]
(-write writer (str "#<Track: " key " "))
(binding [*ratom-context* nil]
(pr-writer (-deref a) writer opts))
(-write writer ">")))
(defn make-track [f args]
(Track. #(apply f args) [f args] nil))
(defn make-track! [f args]
(let [r (make-reaction #(-deref (make-track f args))
:auto-run :async)]
@r
r))
(defn track [f & args]
{:pre [(ifn? f)]}
(make-track f args))
(defn track! [f & args]
{:pre [(ifn? f)]}
(make-track! f args))
;;; cursor
(deftype RCursor [ratom path ^:mutable reaction
^:mutable state ^:mutable watches]
IAtom
IReactiveAtom
@ -112,39 +195,48 @@
(= ratom (.-ratom other))))
Object
(_reaction [this]
(if (nil? reaction)
(set! reaction
(if (satisfies? IDeref ratom)
(make-reaction #(get-in @ratom path)
:on-set (if (= path [])
#(reset! ratom %2)
#(swap! ratom assoc-in path %2)))
(make-reaction #(ratom path)
:on-set #(ratom path %2))))
reaction))
(_peek [this]
(binding [*ratom-context* nil]
(-deref (._reaction this))))
(-deref this)))
(_set-state [this oldstate newstate]
(when-not (identical? oldstate newstate)
(set! state newstate)
(when (some? watches)
(-notify-watches this oldstate newstate))))
IDeref
(-deref [this]
(-deref (._reaction this)))
(let [oldstate state
newstate (if-some [r reaction]
(-deref r)
(let [f (if (satisfies? IDeref ratom)
#(get-in @ratom path)
#(ratom path))]
(cached-reaction f [::cursor ratom path] this nil)))]
(._set-state this oldstate newstate)
newstate))
IReset
(-reset! [this new-value]
(-reset! (._reaction this) new-value))
(let [oldstate state]
(._set-state this oldstate new-value)
(if (satisfies? IDeref ratom)
(if (= path [])
(reset! ratom new-value)
(swap! ratom assoc-in path new-value))
(ratom path new-value))
new-value))
ISwap
(-swap! [a f]
(-swap! (._reaction a) f))
(-reset! a (f (._peek a))))
(-swap! [a f x]
(-swap! (._reaction a) f x))
(-reset! a (f (._peek a) x)))
(-swap! [a f x y]
(-swap! (._reaction a) f x y))
(-reset! a (f (._peek a) x y)))
(-swap! [a f x y more]
(-swap! (._reaction a) f x y more))
(-reset! a (apply f (._peek a) x y more)))
IPrintWithWriter
(-pr-writer [a writer opts]
@ -154,36 +246,46 @@
IWatchable
(-notify-watches [this oldval newval]
(-notify-watches (._reaction this) oldval newval))
(doseq [[key f] watches]
(f key this oldval newval)))
(-add-watch [this key f]
(-add-watch (._reaction this) key f))
(set! watches (assoc watches key f)))
(-remove-watch [this key]
(-remove-watch (._reaction this) key))
(set! watches (dissoc watches key)))
IHash
(-hash [this] (hash [ratom path])))
(defn cursor
[src path]
(if (satisfies? IDeref path)
(do
(warn "Calling cursor with an atom as the second arg is "
"deprecated, in (cursor "
src " " (pr-str path) ")")
(assert (satisfies? IReactiveAtom path)
(str "src must be a reactive atom, not "
(pr-str path)))
(RCursor. path src nil))
(do
(assert (or (satisfies? IReactiveAtom src)
(and (ifn? src)
(not (vector? src))))
(str "src must be a reactive atom or a function, not "
(pr-str src)))
(RCursor. src path nil))))
(assert (or (satisfies? IReactiveAtom src)
(and (ifn? src)
(not (vector? src))))
(str "src must be a reactive atom or a function, not "
(pr-str src)))
(RCursor. src path nil nil nil))
;;; with-let support
(def reaction-counter 0)
(defn reaction-key []
(when-some [c *ratom-context*]
(if-some [k (.-reaction-id c)]
k
(->> reaction-counter inc
(set! reaction-counter)
(set! (.-reaction-id c))))))
(defn get-cached-values [key destroy]
(if-some [k (reaction-key)]
(cached-reaction #(array)
[k key] nil destroy)
(array)))
;;;; reaction
(defprotocol IDisposable
@ -193,13 +295,18 @@
(run [this]))
(defprotocol IComputedImpl
(-update-watching [this derefed])
(-handle-change [k sender oldval newval])
(-peek-at [this]))
(-peek-at [this])
(^boolean -check-clean [this])
(-handle-change [this sender oldval newval])
(-update-watching [this derefed]))
(deftype Reaction [f ^:mutable state ^:mutable dirty? ^:mutable active?
(def ^:const clean 0)
(def ^:const maybe-dirty 1)
(def ^:const dirty 2)
(deftype Reaction [f ^:mutable state ^:mutable ^number dirtyness
^:mutable watching ^:mutable watches
auto-run on-set on-dispose]
^:mutable auto-run on-set on-dispose ^boolean nocache?]
IAtom
IReactiveAtom
@ -208,24 +315,24 @@
(reduce-kv (fn [_ key f]
(f key this oldval newval)
nil)
nil watches))
nil watches)
nil)
(-add-watch [this k wf]
(set! watches (assoc watches k wf)))
(-add-watch [_ key f]
(set! watches (check-watches watches (assoc watches key f))))
(-remove-watch [this k]
(set! watches (dissoc watches k))
(-remove-watch [this key]
(set! watches (check-watches watches (dissoc watches key)))
(when (and (empty? watches)
(not auto-run))
(nil? auto-run))
(dispose! this)))
IReset
(-reset! [a newval]
(assert (ifn? on-set) "Reaction is read only.")
(let [oldval state]
(set! state newval)
(when on-set
(set! dirty? true)
(on-set oldval newval))
(on-set oldval newval)
(-notify-watches a oldval newval)
newval))
@ -240,56 +347,102 @@
(-reset! a (apply f (-peek-at a) x y more)))
IComputedImpl
(-peek-at [this]
(if (== dirtyness clean)
state
(binding [*ratom-context* nil]
(-deref this))))
(-check-clean [this]
(when (== dirtyness maybe-dirty)
(let [ar auto-run]
(set! auto-run nil)
(doseq [w watching]
(when (and (instance? Reaction w)
(not (-check-clean w)))
(._try-run this w)))
(set! auto-run ar))
(when (== dirtyness maybe-dirty)
(set! dirtyness clean)))
(== dirtyness clean))
(-handle-change [this sender oldval newval]
(when (and active? (not (identical? oldval newval)))
(set! dirty? true)
((or auto-run run) this)))
(let [old-dirty dirtyness
new-dirty (if (identical? oldval newval)
(if (instance? Reaction sender)
maybe-dirty clean)
dirty)]
(when (> new-dirty old-dirty)
(set! dirtyness new-dirty)
(when (== old-dirty clean)
(if-some [ar auto-run]
(when-not (and (identical? ar run)
(-check-clean this))
(ar this))
(-notify-watches this state state)))))
nil)
(-update-watching [this derefed]
(doseq [w derefed]
(when-not (contains? watching w)
(add-watch w this -handle-change)))
(-add-watch w this -handle-change)))
(doseq [w watching]
(when-not (contains? derefed w)
(remove-watch w this)))
(set! watching derefed))
(-remove-watch w this)))
(set! watching derefed)
nil)
(-peek-at [this]
(if-not dirty?
state
(binding [*ratom-context* nil]
(-deref this))))
Object
(_try-run [_ parent]
(try
(if-some [ar (.-auto-run parent)]
(ar parent)
(run parent))
(catch :default e
;; Just log error: it will most likely pop up again at deref time.
(when-not silent
(js/console.error "Error in reaction:" e))
(set! (.-dirtyness parent) dirty)
(set! dirtyness dirty))))
IRunnable
(run [this]
(let [oldstate state
res (capture-derefed f this)
derefed (captured this)]
derefed (-captured this)]
(when (not= derefed watching)
(-update-watching this derefed))
(when-not active?
(when debug (swap! -running inc))
(set! active? true))
(set! dirty? false)
(set! state res)
(-notify-watches this oldstate state)
(set! dirtyness clean)
(when-not nocache?
(set! state res)
;; Use = to determine equality from reactions, since
;; they are likely to produce new data structures.
(when (and (some? watches)
(not= oldstate res))
(-notify-watches this oldstate res)))
res))
IDeref
(-deref [this]
(if (or auto-run (some? *ratom-context*))
(-check-clean this)
(if (and (nil? *ratom-context*)
(nil? auto-run))
(do
(when-not (== dirtyness clean)
(let [oldstate state
newstate (f)]
(set! state newstate)
(when (and (some? watches)
(not= oldstate newstate))
(-notify-watches this oldstate newstate))))
(when (and (some? on-dispose)
(nil? watches))
(on-dispose)))
(do
(notify-deref-watcher! this)
(if dirty?
(run this)
state))
(do
(when dirty?
(let [oldstate state]
(set! state (f))
(when-not (identical? oldstate state)
(-notify-watches this oldstate state))))
state)))
(when-not (== dirtyness clean)
(run this))))
state)
IDisposable
(dispose! [this]
@ -297,12 +450,11 @@
(remove-watch w this))
(set! watching nil)
(set! state nil)
(set! dirty? true)
(when active?
(when debug (swap! -running dec))
(set! active? false))
(when on-dispose
(on-dispose)))
(set! auto-run nil)
(set! dirtyness dirty)
(when (some? on-dispose)
(on-dispose))
nil)
IEquiv
(-equiv [o other] (identical? o other))
@ -316,16 +468,54 @@
IHash
(-hash [this] (goog/getUid this)))
(defn make-reaction [f & {:keys [auto-run on-set on-dispose derefed]}]
(let [runner (if (= auto-run true) run auto-run)
active (not (nil? derefed))
dirty (not active)
reaction (Reaction. f nil dirty active
nil nil
runner on-set on-dispose)]
;;; Queueing
;; Gets set up from batching
;; TODO: Refactor so that isn't needed
(defonce render-queue nil)
(def dirty-queue nil)
(defn enqueue [r]
(when (nil? dirty-queue)
(set! dirty-queue (array))
(.schedule render-queue))
(.push dirty-queue r))
(defn flush! []
(let [q dirty-queue]
(when (some? q)
(set! dirty-queue nil)
(dotimes [i (alength q)]
(let [r (aget q i)]
(when-not (or (nil? (.-auto-run r))
(-check-clean r))
(run r)))))))
(defn make-reaction [f & {:keys [auto-run on-set on-dispose derefed no-cache
capture]}]
(let [runner (case auto-run
true run
:async enqueue
auto-run)
derefs (if-some [c capture]
(-captured c)
derefed)
dirty (if (nil? derefs) dirty clean)
nocache (if (nil? no-cache) false no-cache)
reaction (Reaction. f nil dirty nil nil
runner on-set on-dispose nocache)]
(when-some [rid (some-> capture .-reaction-id)]
(set! (.-reaction-id reaction) rid))
(when-not (nil? derefed)
(when debug (swap! -running inc))
(-update-watching reaction derefed))
(warn "using derefed is deprecated"))
(when-not (nil? derefs)
(when (dev?)
(set! (.-ratomGeneration reaction)
(.-ratomGeneration derefs)))
(-update-watching reaction derefs))
reaction))
@ -397,3 +587,24 @@
(util/partial-ifn. callback-fn args nil)
false nil))
(comment
(def perf-check 0)
(defn ratom-perf []
(dbg "ratom-perf")
(set! debug false)
(dotimes [_ 10]
(set! perf-check 0)
(let [nite 100000
a (atom 0)
mid (make-reaction (fn [] (inc @a)))
res (make-reaction (fn []
(set! perf-check (inc perf-check))
(inc @mid))
:auto-run true)]
@res
(time (dotimes [x nite]
(swap! a inc)))
(dispose! res)
(assert (= perf-check (inc nite))))))
(enable-console-print!)
(ratom-perf))

View File

@ -1,8 +1,12 @@
(ns reagenttest.runtests
(ns ^:figwheel-always
reagenttest.runtests
(:require [reagenttest.testreagent]
[reagenttest.testcursor]
[reagenttest.testinterop]
[reagenttest.testratom]
[reagenttest.testratomasync]
[reagenttest.testtrack]
[reagenttest.testwithlet]
[reagenttest.testwrap]
[cljs.test :as test :include-macros true]
[reagent.core :as r]
@ -51,7 +55,6 @@
(run-tests)))
(defn reload []
(demo/init!)
(init!))
(demo/init!))
(init!)

View File

@ -11,6 +11,8 @@
(rv/running))
(defn dispose [v] (rv/dispose! v))
(def testite 10)
(deftest basic-cursor
(let [runs (running)
start-base (rv/atom {:a {:b {:c 0}}})
@ -29,7 +31,7 @@
(is (= @out 2))
(reset! start 1)
(is (= @out 3))
(is (= @count 4))
(is (= @count 2))
(dispose const)
(is (= @start-base {:a {:b {:c 1}}}))
(is (= (running) runs))))
@ -85,7 +87,7 @@
(deftest test-unsubscribe
(dotimes [x 10]
(dotimes [x testite]
(let [runs (running)
a-base (rv/atom {:test {:unsubscribe 0 :value 42}})
a (r/cursor a-base [:test :unsubscribe])
@ -171,7 +173,7 @@
(is (= runs (running)))))
(deftest test-dispose
(dotimes [x 10]
(dotimes [x testite]
(let [runs (running)
a-base (rv/atom {:a 0 :b 0})
a (r/cursor a-base [:a])
@ -191,19 +193,19 @@
:on-dispose #(reset! disposed-cns true))]
@cns
(is (= @res 2))
(is (= (+ 4 runs) (running)))
(is (= (+ 6 runs) (running)))
(is (= @count-b 1))
(is (= {:a 0 :b 0} @a-base))
(reset! a -1)
(is (= @res 1))
(is (= @disposed nil))
(is (= @count-b 2))
(is (= (+ 4 runs) (running)) "still running")
(is (= (+ 6 runs) (running)) "still running")
(is (= {:a -1 :b 0} @a-base))
(reset! a 2)
(is (= @res 1))
(is (= @disposed true))
(is (= (+ 3 runs) (running)) "less running count")
(is (= (+ 4 runs) (running)) "less running count")
(is (= {:a 2 :b 0} @a-base))
(reset! disposed nil)

View File

@ -8,19 +8,28 @@
(set! rv/debug true)
(rv/running))
(def testite 10)
(defn dispose [v]
(rv/dispose! v))
(def perf-check 0)
(defn ratom-perf []
(dbg "ratom-perf")
(let [a (rv/atom 0)
(set! rv/debug false)
(set! perf-check 0)
(let [nite 100000
a (rv/atom 0)
mid (reaction (inc @a))
res (run!
(set! perf-check (inc perf-check))
(inc @mid))]
(time (dotimes [x 100000]
(time (dotimes [x nite]
(swap! a inc)))
(dispose res)))
(dispose res)
(assert (= perf-check (inc nite)))))
(enable-console-print!)
;; (ratom-perf)
(deftest basic-ratom
@ -40,7 +49,7 @@
(is (= @out 2))
(reset! start 1)
(is (= @out 3))
(is (= @count 4))
(is (= @count 2))
(dispose const)
(is (= (running) runs))))
@ -89,7 +98,7 @@
(deftest test-unsubscribe
(dotimes [x 10]
(dotimes [x testite]
(let [runs (running)
a (rv/atom 0)
a1 (reaction (inc @a))
@ -166,7 +175,7 @@
(is (= runs (running)))))
(deftest test-dispose
(dotimes [x 10]
(dotimes [x testite]
(let [runs (running)
a (rv/atom 0)
disposed (rv/atom nil)
@ -185,13 +194,13 @@
:on-dispose #(reset! disposed-cns true))]
@cns
(is (= @res 2))
(is (= (+ 3 runs) (running)))
(is (= (+ 4 runs) (running)))
(is (= @count-b 1))
(reset! a -1)
(is (= @res 1))
(is (= @disposed nil))
(is (= @count-b 2))
(is (= (+ 3 runs) (running)) "still running")
(is (= (+ 4 runs) (running)) "still running")
(reset! a 2)
(is (= @res 1))
(is (= @disposed true))
@ -238,15 +247,52 @@
(is (= @b 6))
(is (= runs (running)))))
;; (deftest catching
;; (let [runs (running)
;; a (rv/atom false)
;; catch-count (atom 0)
;; b (reaction (if @a (throw {})))
;; c (run! (try @b (catch js/Object e
;; (swap! catch-count inc))))]
;; (is (= @catch-count 0))
;; (reset! a false)
;; (is (= @catch-count 0))
;; (reset! a true)
;; (is (= @catch-count 1))))
(deftest catching
(let [runs (running)
a (rv/atom false)
catch-count (atom 0)
b (reaction (if @a (throw (js/Error. "fail"))))
c (run! (try @b (catch :default e
(swap! catch-count inc))))]
(set! rv/silent true)
(is (= @catch-count 0))
(reset! a false)
(is (= @catch-count 0))
(reset! a true)
(is (= @catch-count 1))
(reset! a false)
(is (= @catch-count 1))
(set! rv/silent false)
(dispose c)
(is (= runs (running)))))
(deftest test-rswap
(let [a (atom {:foo 1})]
(is (nil? (r/rswap! a update-in [:foo] inc)))
(is (= (:foo @a) 2))
(is (nil? (r/rswap! a identity)))
(is (= (:foo @a) 2))
(is (nil? (r/rswap! a #(assoc %1 :foo %2) 3)))
(is (= (:foo @a) 3))
(is (nil? (r/rswap! a #(assoc %1 :foo %3) 0 4)))
(is (= (:foo @a) 4))
(is (nil? (r/rswap! a #(assoc %1 :foo %4) 0 0 5)))
(is (= (:foo @a) 5))
(is (nil? (r/rswap! a #(assoc %1 :foo %5) 0 0 0 6)))
(is (= (:foo @a) 6))
(let [disp (atom nil)
f (fn [o v]
(assert (= v :add))
(if (< (:foo o) 10)
(do
(is (nil? (@disp v)))
(update-in o [:foo] inc))
o))
_ (reset! disp #(r/rswap! a f %))]
(@disp :add)
(is (= (:foo @a) 10)))))

View File

@ -0,0 +1,292 @@
(ns reagenttest.testratomasync
(:require [cljs.test :as t :refer-macros [is deftest testing]]
[reagent.ratom :as rv :refer-macros [run! reaction]]
[reagent.debug :refer-macros [dbg]]
[reagent.core :as r]))
(defn running []
(set! rv/debug true)
(rv/running))
(def testite 1)
(defn dispose [v]
(rv/dispose! v))
(defn sync [] (r/flush))
(defn ar [f] (rv/make-reaction f :auto-run :async))
(deftest basic-ratom
(sync)
(let [runs (running)
start (rv/atom 0)
sv (reaction @start)
comp (reaction @sv (+ 2 @sv))
c2 (reaction (inc @comp))
count (rv/atom 0)
out (rv/atom 0)
res (reaction
(swap! count inc)
@sv @c2 @comp)
const (ar (fn []
(reset! out @res)))]
(is (= @count 0))
@const
(is (= @count 1) "constrain ran")
(is (= @out 2))
(reset! start 1)
(is (= @count 1))
(sync)
(is (= @out 3))
(is (= @count 2))
(reset! start 2)
(dispose const)
(is (= (running) runs) "did dispose")
(sync)
(is (= (running) runs) "should not awaken")))
(deftest double-dependency
(sync)
(let [runs (running)
start (rv/atom 0)
c3-count (rv/atom 0)
c1 (reaction @start 1)
c2 (reaction @start)
c3 (rv/make-reaction
(fn []
(swap! c3-count inc)
(+ @c1 @c2))
:auto-run :async)]
(is (= @c3-count 0) "t0")
(sync)
(is (= @c3 1))
(is (= @c3-count 1) "t1")
(swap! start inc)
(is (= @c3-count 1))
(sync)
(is (= @c3-count 2) "t2")
(is (= @c3 2))
(is (= @c3-count 2) "t3")
(dispose c3)
(is (= (running) runs))
(sync)
(is (= @c3 2))
(is (= (running) runs))))
(deftest test-from-reflex
(sync)
(let [runs (running)]
(let [!counter (rv/atom 0)
!signal (rv/atom "All I do is change")
co (ar (fn []
;;when I change...
@!signal
;;update the counter
(swap! !counter inc)))]
(is (= 0 @!counter))
@co
(is (= 1 @!counter) "Constraint run on init")
(reset! !signal "foo")
(sync)
(is (= 2 @!counter)
"Counter auto updated")
(dispose co))
(let [!x (rv/atom 0)
!co (rv/make-reaction #(inc @!x) :auto-run :async)]
@!co
(is (= 1 @!co) "CO has correct value on first deref")
(swap! !x inc)
(sync)
(is (= 2 @!co) "CO auto-updates")
(dispose !co))
(is (= runs (running)))))
(deftest test-unsubscribe
(sync)
(dotimes [x testite]
(let [runs (running)
a (rv/atom 0)
a1 (reaction (inc @a))
a2 (reaction @a)
b-changed (rv/atom 0)
c-changed (rv/atom 0)
b (reaction
(swap! b-changed inc)
(inc @a1))
c (reaction
(swap! c-changed inc)
(+ 10 @a2))
res (ar (fn []
(if (< @a2 1) @b @c)))]
(is (= @res (+ 2 @a)))
(is (= @b-changed 1))
(is (= @c-changed 0))
(reset! a -1)
(is (= @b-changed 1))
@res
(is (= @b-changed 2))
(is (= @c-changed 0))
(is (= @res (+ 2 @a)))
(reset! a 2)
(sync)
(is (= @b-changed 3))
(is (= @c-changed 1))
(is (= @res (+ 10 @a)))
(reset! a 3)
(sync)
(is (= @b-changed 3))
(is (= @c-changed 2))
(is (= @res (+ 10 @a)))
(reset! a 3)
(sync)
(is (= @b-changed 3))
(is (= @c-changed 2))
(is (= @res (+ 10 @a)))
(reset! a -1)
(is (= @res (+ 2 @a)))
(dispose res)
(is (= runs (running))))))
(deftest maybe-broken
(sync)
(let [runs (running)]
(let [runs (running)
a (rv/atom 0)
b (reaction (inc @a))
c (reaction (dec @a))
d (reaction (str @b))
res (rv/atom 0)
cs (ar
#(reset! res @d))]
@cs
(is (= @res "1"))
(dispose cs))
;; should be broken according to https://github.com/lynaghk/reflex/issues/1
;; but isnt
(let [a (rv/atom 0)
b (reaction (inc @a))
c (reaction (dec @a))
d (ar (fn [] [@b @c]))]
(is (= @d [1 -1]))
(dispose d))
(let [a (rv/atom 0)
b (reaction (inc @a))
c (reaction (dec @a))
d (ar (fn [] [@b @c]))
res (rv/atom 0)]
(is (= @d [1 -1]))
(let [e (ar #(reset! res @d))]
@e
(is (= @res [1 -1]))
(dispose e))
(dispose d))
(is (= runs (running)))))
(deftest test-dispose
(dotimes [x testite]
(let [runs (running)
a (rv/atom 0)
disposed (rv/atom nil)
disposed-c (rv/atom nil)
disposed-cns (rv/atom nil)
count-b (rv/atom 0)
b (rv/make-reaction (fn []
(swap! count-b inc)
(inc @a))
:on-dispose #(reset! disposed true))
c (rv/make-reaction #(if (< @a 1) (inc @b) (dec @a))
:on-dispose #(reset! disposed-c true))
res (rv/atom nil)
cns (rv/make-reaction #(reset! res @c)
:auto-run :async
:on-dispose #(reset! disposed-cns true))]
@cns
(is (= @res 2))
(is (= (+ 4 runs) (running)))
(is (= @count-b 1))
(reset! a -1)
(is (= @res 2))
(sync)
(is (= @res 1))
(is (= @disposed nil))
(is (= @count-b 2))
(is (= (+ 4 runs) (running)) "still running")
(reset! a 2)
(sync)
(is (= @res 1))
(is (= @disposed true))
(is (= (+ 2 runs) (running)) "less running count")
(reset! disposed nil)
(reset! a -1)
(sync)
;; This fails sometimes on node. I have no idea why.
(is (= 1 @res) "should be one again")
(is (= @disposed nil))
(reset! a 2)
(sync)
(is (= @res 1))
(is (= @disposed true))
(dispose cns)
(is (= @disposed-c true))
(is (= @disposed-cns true))
(is (= runs (running))))))
(deftest test-on-set
(sync)
(let [runs (running)
a (rv/atom 0)
b (rv/make-reaction #(+ 5 @a)
:auto-run :async
:on-set (fn [oldv newv]
(reset! a (+ 10 newv))))]
(sync)
(is (= 5 @b))
(reset! a 1)
(sync)
(is (= 6 @b))
(reset! b 1)
(sync)
(is (= 11 @a))
(is (= 16 @b))
(dispose b)
(is (= runs (running)))))
(deftest non-reactive-deref
(let [runs (running)
a (rv/atom 0)
b (rv/make-reaction #(+ 5 @a))]
(is (= @b 5))
(is (= runs (running)))
(reset! a 1)
(is (= @b 6))
(is (= runs (running)))))
(deftest catching
(let [runs (running)
a (rv/atom false)
catch-count (atom 0)
b (reaction (if @a (throw (js/Error. "reaction fail"))))
c (ar (fn [] (try @b (catch js/Object e
(swap! catch-count inc)))))]
(set! rv/silent true)
(is (= @catch-count 0))
(reset! a false)
@c
(is (= @catch-count 0))
(reset! a true)
(is (= @catch-count 0))
(sync)
(is (= @catch-count 1))
(set! rv/silent false)
(dispose c)
(is (= runs (running)))))

View File

@ -103,7 +103,8 @@
runs (running)
val (r/atom 0)
secval (r/atom 0)
v1 (reaction @val)
v1-ran (atom 0)
v1 (reaction (swap! v1-ran inc) @val)
comp (fn []
(swap! ran inc)
[:div (str "val " @v1 @val @secval)])]
@ -119,15 +120,20 @@
(reset! val 1)
(reset! val 2)
(reset! val 1)
(is (= 1 @ran))
(is (= 1 @v1-ran))
(r/flush)
(is (found-in #"val 1" div))
(is (= 2 @ran))
(is (= 2 @ran) "ran once more")
(is (= 2 @v1-ran))
;; should not be rendered
(reset! val 1)
(is (= 2 @v1-ran))
(r/flush)
(is (= 2 @v1-ran))
(is (found-in #"val 1" div))
(is (= 2 @ran))))
(is (= 2 @ran) "did not run")))
(is (= runs (running)))
(is (= 2 @ran)))))
@ -559,3 +565,50 @@
c2 (fn []
[c1 (sorted-map 1 "foo" 2 "bar")])]
(is (= (rstr [c2]) "<div>foo</div>"))))
(deftest basic-with-let
(let [n1 (atom 0)
n2 (atom 0)
n3 (atom 0)
val (r/atom 0)
c (fn []
(r/with-let [v (swap! n1 inc)]
(swap! n2 inc)
[:div @val]
(finally
(swap! n3 inc))))]
(with-mounted-component [c]
(fn [_ div]
(is (= [1 1 0] [@n1 @n2 @n3]))
(swap! val inc)
(is (= [1 1 0] [@n1 @n2 @n3]))
(r/flush)
(is (= [1 2 0] [@n1 @n2 @n3]))))
(is (= [1 2 1] [@n1 @n2 @n3]))))
(deftest with-let-destroy-only
(let [n1 (atom 0)
n2 (atom 0)
c (fn []
(r/with-let []
(swap! n1 inc)
[:div]
(finally
(swap! n2 inc))))]
(with-mounted-component [c]
(fn [_ div]
(is (= [1 0] [@n1 @n2]))))
(is (= [1 1] [@n1 @n2]))))
(deftest with-let-non-reactive
(let [n1 (atom 0)
n2 (atom 0)
n3 (atom 0)
c (fn []
(r/with-let [a (swap! n1 inc)]
(swap! n2 inc)
[:div a]
(finally
(swap! n3 inc))))]
(is (= (rstr [c]) (rstr [:div 1])))
(is (= [1 1 1] [@n1 @n2 @n3]))))

View File

@ -0,0 +1,218 @@
(ns reagenttest.testtrack
(:require [cljs.test :as t :refer-macros [is deftest testing]]
[reagent.ratom :as rv :refer [track] :refer-macros [run! reaction]]
[reagent.debug :refer-macros [dbg]]
[reagent.core :as r]))
(defn running []
(set! rv/debug true)
(rv/running))
(def testite 10)
(defn dispose [v]
(rv/dispose! v))
(defn sync [] (r/flush))
(enable-console-print!)
(deftest basic-ratom
(let [runs (running)
start (rv/atom 0)
svf (fn [] @start)
sv (track svf)
compf (fn [x] @sv (+ x @sv))
comp (track compf 2)
c2f (fn [] (inc @comp))
count (rv/atom 0)
out (rv/atom 0)
resf (fn []
(swap! count inc)
(+ @sv @(track c2f) @comp))
res (track resf)
const (run!
(reset! out @res))]
(is (= @count 1) "constrain ran")
(is (= @out 5))
(reset! start 1)
(is (= @out 8))
(is (= @count 2))
(dispose const)
(is (= (running) runs))))
(deftest test-track!
(sync)
(let [runs (running)
start (rv/atom 0)
svf (fn [] @start)
sv (track svf)
compf (fn [x] @sv (+ x @sv))
comp (track compf 2)
c2f (fn [] (inc @comp))
count (rv/atom 0)
out (rv/atom 0)
resf (fn []
(swap! count inc)
(+ @sv @(track c2f) @comp))
res (track resf)
const (rv/track!
#(reset! out @res))]
(is (= @count 1) "constrain ran")
(is (= @out 5))
(reset! start 1)
(is (= @count 1))
(sync)
(is (= @out 8))
(is (= @count 2))
(dispose const)
(swap! start inc)
(sync)
(is (= @count 2))
(is (= @const 11))
(is (= @count 3))
(is (= (running) runs))))
(deftest double-dependency
(let [runs (running)
start (rv/atom 0)
c3-count (rv/atom 0)
c1f (fn [] @start 1)
c2f (fn [] @start)
c3 (rv/make-reaction
(fn []
(swap! c3-count inc)
(+ @(track c1f) @(track c2f)))
:auto-run true)]
(is (= @c3-count 0))
(is (= @c3 1))
(is (= @c3-count 1) "t1")
(swap! start inc)
(is (= @c3-count 2) "t2")
(is (= @c3 2))
(is (= @c3-count 2) "t3")
(dispose c3)
(is (= (running) runs))))
(deftest test-from-reflex
(let [runs (running)]
(let [!x (rv/atom 0)
f #(inc @!x)
!co (run! @(track f))]
(is (= 1 @!co) "CO has correct value on first deref")
(swap! !x inc)
(is (= 2 @!co) "CO auto-updates")
(dispose !co))
(is (= runs (running)))))
(deftest test-unsubscribe
(dotimes [x testite]
(let [runs (running)
a (rv/atom 0)
af (fn [x] (+ @a x))
a1 (track af 1)
a2 (track af 0)
b-changed (rv/atom 0)
c-changed (rv/atom 0)
mf (fn [v x spy]
(swap! spy inc)
(+ @v x))
res (run!
(if (< @a2 1)
@(track mf a1 1 b-changed)
@(track mf a2 10 c-changed)))]
(is (= @res (+ 2 @a)))
(is (= @b-changed 1))
(is (= @c-changed 0))
(reset! a -1)
(is (= @res (+ 2 @a)))
(is (= @b-changed 2))
(is (= @c-changed 0))
(reset! a 2)
(is (= @res (+ 10 @a)))
(is (<= 2 @b-changed 3))
(is (= @c-changed 1))
(reset! a 3)
(is (= @res (+ 10 @a)))
(is (<= 2 @b-changed 3))
(is (= @c-changed 2))
(reset! a 3)
(is (= @res (+ 10 @a)))
(is (<= 2 @b-changed 3))
(is (= @c-changed 2))
(reset! a -1)
(is (= @res (+ 2 @a)))
(dispose res)
(is (= runs (running))))))
(deftest maybe-broken
(let [runs (running)]
(let [runs (running)
a (rv/atom 0)
f (fn [x] (+ x @a))
b (track f 1)
c (track f -1)
d (track #(str @b))
res (rv/atom 0)
cs (run!
(reset! res @d))]
(is (= @res "1"))
(dispose cs))
;; should be broken according to https://github.com/lynaghk/reflex/issues/1
;; but isnt
(let [a (rv/atom 0)
f (fn [x] (+ x @a))
b (track f 1)
d (run! [@b @(track f -1)])]
(is (= @d [1 -1]))
(dispose d))
(let [a (rv/atom 0)
f (fn [x] (+ x @a))
c (track f -1)
d (run! [@(track f 1) @c])
res (rv/atom 0)]
(is (= @d [1 -1]))
(let [e (run! (reset! res @d))]
(is (= @res [1 -1]))
(dispose e))
(dispose d))
(is (= runs (running)))))
(deftest non-reactive-deref
(let [runs (running)
a (rv/atom 0)
b (track #(+ 5 @a))]
(is (= @b 5))
(is (= runs (running)))
(reset! a 1)
(is (= @b 6))
(is (= runs (running)))))
(deftest catching
(let [runs (running)
a (rv/atom false)
catch-count (atom 0)
b (track #(if @a (throw (js/Error. "fail"))))
c (run! (try @b (catch :default e
(swap! catch-count inc))))]
(set! rv/silent true)
(is (= @catch-count 0))
(reset! a false)
(is (= @catch-count 0))
(reset! a true)
(is (= @catch-count 1))
(reset! a false)
(is (= @catch-count 1))
(set! rv/silent false)
(dispose c)
(is (= runs (running)))))

View File

@ -0,0 +1,218 @@
(ns reagenttest.testwithlet
(:require [cljs.test :as t :refer-macros [is deftest testing]]
[reagent.ratom :as rv]
[reagent.debug :refer-macros [dbg]]
[reagent.core :as r
:refer [flush track track! dispose!] :refer-macros [with-let]]
[clojure.walk :as w]))
(defn running []
(r/flush)
(set! rv/debug true)
(rv/running))
(deftest basic-with-let
(let [runs (running)
n1 (atom 0)
n2 (atom 0)
n3 (atom 0)
a (r/atom 10)
f1 (fn []
(with-let [v (swap! n1 inc)]
(swap! n2 inc)
[@a v]
(finally
(swap! n3 inc))))
r (atom nil)
t (track! (fn []
(reset! r @(track f1))))]
(is (= [[10 1] 1 1 0] [@r @n1 @n2 @n3]))
(swap! a inc)
(is (= [[10 1] 1 1 0] [@r @n1 @n2 @n3]))
(flush)
(is (= [[11 1] 1 2 0] [@r @n1 @n2 @n3]))
(is (= [11 1] @t))
(dispose! t)
(is (= [[11 1] 1 2 1] [@r @n1 @n2 @n3]))
(is (= runs (running)))
(swap! a inc)
(flush)
(is (= [[11 1] 1 2 1] [@r @n1 @n2 @n3]))
(is (= [12 2] @t))
(is (= [[12 2] 2 3 2] [@r @n1 @n2 @n3]))
(is (= [12 3] (f1)))
(is (= [[12 2] 3 4 3] [@r @n1 @n2 @n3]))
(is (= runs (running)))))
(deftest test-with-let-args
(let [runs (running)
n1 (atom 0)
n2 (atom 0)
a (r/atom 0)
ran (fn []
(swap! n2 inc)
@a)
f1 #(with-let []
(ran)
[])
f2 #(with-let [x1 (swap! n1 inc)]
(ran)
[x1])
f3 #(with-let [x1 (swap! n1 inc)
x2 (swap! n1 inc)]
(ran)
[x1 x2])
f4 #(with-let [x1 (swap! n1 inc)
x2 (swap! n1 inc)
x3 (swap! n1 inc)]
(ran)
[x1 x2 x3])
f5 #(with-let [x1 (swap! n1 inc)
x2 (swap! n1 inc)
x3 (swap! n1 inc)
x4 (swap! n1 inc)]
(ran)
[x1 x2 x3 x4])
f6 #(with-let [x1 (swap! n1 inc)
x2 (swap! n1 inc)
x3 (swap! n1 inc)
x4 (swap! n1 inc)
x5 (swap! n1 inc)]
(ran)
[x1 x2 x3 x4 x5])
f7 #(with-let [x1 (swap! n1 inc)
x2 (swap! n1 inc)
x3 (swap! n1 inc)
x4 (swap! n1 inc)
x5 (swap! n1 inc)
x6 (swap! n1 inc)]
(ran)
[x1 x2 x3 x4 x5 x6])
r (atom nil)
all (fn [] {:f1 @(track f1)
:f2 @(track f2)
:f3 @(track f3)
:f4 @(track f4)
:f5 @(track f5)
:f6 @(track f6)
:f7 @(track f7)})
t (track! (fn [] (reset! r (all))))
expected {:f1 []
:f2 [1]
:f3 [2 3]
:f4 [4 5 6]
:f5 [7 8 9 10]
:f6 [11 12 13 14 15]
:f7 [16 17 18 19 20 21]}]
(is (< runs (running)))
(is (= @n2 7))
(is (= @r expected))
(is (= (all) expected))
(is (= @t expected))
(swap! a inc)
(is (= @n2 7))
(flush)
(is (= @n2 14))
(is (= @r expected))
(is (= (all) expected))
(is (= @t expected))
(is (= @n2 14))
(dispose! t)
(is (= runs (running)))
(is (= @r expected))
(is (= @n2 14))
(is (= (all) (w/postwalk #(if (number? %) (+ 21 %) %)
expected)))
(is (= @n2 21))
(is (= @t (w/postwalk #(if (number? %) (+ 42 %) %)
expected)))
(is (= @n2 28))
(is (= runs (running)))))
(deftest non-reactive-with-let
(let [n1 (atom 0)
n2 (atom 0)
n3 (atom 0)
n4 (atom 0)
f1 (fn []
(with-let []
(swap! n2 inc)))
f2 (fn []
(with-let [v (swap! n1 inc)]
v))
f3 (fn []
(with-let [v (swap! n1 inc)]
(swap! n2 inc)
(finally (swap! n3 inc))))
f4 (fn []
(with-let []
(finally (swap! n3 inc)
(swap! n4 inc))))
f5 (fn []
[(f1) (f2) (f4)])
tst (fn [f]
[(f) @n1 @n2 @n3])]
(is (= [1 0 1 0] (tst f1)))
(is (= [1 1 1 0] (tst f2)))
(is (= [2 2 2 1] (tst f3)))
(is (= 0 @n4))
(is (= [nil 2 2 2] (tst f4)))
(is (= 1 @n4))
(is (= [[3 3 nil] 3 3 3] (tst f5)))))
(deftest with-let-args
(let [runs (running)
active (atom 0)
n1 (atom 0)
f1 (fn [x y]
(with-let [_ (swap! active inc)
v (r/atom @x)]
(swap! n1 inc)
(+ y @v)
(finally
(reset! v nil)
(swap! active dec))))
f2 (fn [x y]
(with-let [t1 (track f1 x y)
t2 (track f1 x y)]
(let [v @(track f1 x y)]
(is (= v @t1 @t2))
v)))
f2t (partial track f2)
res (atom nil)
val (r/atom 1)
valtrack (track deref val)
t (track! #(reset! res (let [v valtrack]
(if (> @v 2)
[@(f2t v 10)]
[@(f2t val 0)
@(f2t val 0)
@(f2t v 10)
(f1 v 10)]))))]
(is (= [1 1 11 11] @res))
(is (= [3 3] [@n1 @active]))
(reset! val 1)
(flush)
(is (= [1 1 11 11] @res))
(is (= [3 3] [@n1 @active]))
(swap! val inc)
(is (= [3 3] [@n1 @active]))
(flush)
(is (= [6 3] [@n1 @active]))
(is (= [1 1 11 11] @res))
(swap! val inc)
(flush)
(is (= [6 1] [@n1 @active]))
(is (= [11] @res))
(dispose! t)
(is (= [6 0] [@n1 @active]))
(is (= runs (running)))))

View File

@ -175,8 +175,8 @@
(is (= @ran 7)))))))
(deftest test-cursor
(let [state (r/atom {:a 0
:b 0})
(let [state (r/atom {:a {:v 1}
:b {:v 2}})
a-count (r/atom 0)
b-count (r/atom 0)
derefer (fn derefer [cur count]
@ -191,7 +191,57 @@
(is (= @a-count 1))
(is (= @b-count 1))
(swap! state update-in [:a] inc)
(swap! state update-in [:a :v] inc)
(is (= @a-count 1))
(r/flush)
(is (= @a-count 2))
(is (= @b-count 1))
(reset! state {:a {:v 2} :b {:v 2}})
(r/flush)
(is (= @a-count 2))
(is (= @b-count 1))
(reset! state {:a {:v 3} :b {:v 2}})
(r/flush)
(is (= @a-count 3))
(is (= @b-count 1))))))
(deftest test-fn-cursor
(let [state (r/atom {:a {:v 1}
:b {:v 2}})
statec (r/cursor state [])
a-count (r/atom 0)
b-count (r/atom 0)
derefer (fn derefer [cur count]
[:div @cur])
f (fn [[x y]] (swap! y inc) (get-in @statec x))
ac (r/cursor f [[:a] a-count])
bc (r/cursor f [[:b] b-count])
comp (fn test-cursor []
[:div
[derefer ac]
[derefer bc]])]
(with-mounted-component [comp]
(fn [c div]
(is (= @a-count 1))
(is (= @b-count 1))
(swap! state update-in [:a :v] inc)
(is (= @a-count 1))
(is (= @b-count 1))
(r/flush)
(is (= @a-count 2))
(is (= @b-count 2))
(reset! state {:a {:v 2} :b {:v 2}})
(r/flush)
(is (= @a-count 2))
(is (= @b-count 2))
(reset! state {:a {:v 3} :b {:v 2}})
(r/flush)
(is (= @a-count 3))
(is (= @b-count 3))))))