Expected value first in tests, use direct comparsion instead of re-find

This commit is contained in:
Juho Teperi 2020-02-03 18:02:32 +02:00
parent 2b5c464f35
commit 2027a2d888
2 changed files with 242 additions and 249 deletions

View File

@ -143,7 +143,7 @@
v2 (r/atom 0) v2 (r/atom 0)
c2 (fn [{val :val}] c2 (fn [{val :val}]
(swap! ran inc) (swap! ran inc)
(is (= @v1 val)) (is (= val @v1))
[:div @v2]) [:div @v2])
c1 (fn [] c1 (fn []
(swap! ran inc) (swap! ran inc)
@ -152,23 +152,23 @@
(with-mounted-component [c1] (with-mounted-component [c1]
(fn [c div] (fn [c div]
(r/flush) (r/flush)
(is (= @ran 2)) (is (= 2 @ran))
(swap! v2 inc) (swap! v2 inc)
(is (= @ran 2)) (is (= 2 @ran))
(r/flush) (r/flush)
(is (= @ran 3)) (is (= 3 @ran))
(swap! v1 inc) (swap! v1 inc)
(r/flush) (r/flush)
(is (= @ran 5)) (is (= 5 @ran))
(swap! v2 inc) (swap! v2 inc)
(swap! v1 inc) (swap! v1 inc)
(r/flush) (r/flush)
(is (= @ran 7)) (is (= 7 @ran))
(swap! v1 inc) (swap! v1 inc)
(swap! v1 inc) (swap! v1 inc)
(swap! v2 inc) (swap! v2 inc)
(r/flush) (r/flush)
(is (= @ran 9))))))) (is (= 9 @ran)))))))
(deftest init-state-test (deftest init-state-test
(when r/is-client (when r/is-client
@ -202,51 +202,51 @@
(with-mounted-component [parent nil nil] (with-mounted-component [parent nil nil]
(fn [c div] (fn [c div]
(r/flush) (r/flush)
(is (= @child-ran 1)) (is (= 1 @child-ran))
(is (= "child-foo" (.-innerText div))) (is (= "child-foo" (.-innerText div)))
(reset! child-props {:style {:display :none}}) (reset! child-props {:style {:display :none}})
(r/flush) (r/flush)
(is (= @child-ran 2)) (is (= 2 @child-ran))
(reset! child-props {:style {:display :none}}) (reset! child-props {:style {:display :none}})
(r/flush) (r/flush)
(is (= @child-ran 2) "keyw is equal") (is (= 2 @child-ran) "keyw is equal")
(reset! child-props {:class :foo}) (r/flush) (reset! child-props {:class :foo}) (r/flush)
(r/flush) (r/flush)
(is (= @child-ran 3)) (is (= 3 @child-ran))
(reset! child-props {:class :foo}) (r/flush) (reset! child-props {:class :foo}) (r/flush)
(r/flush) (r/flush)
(is (= @child-ran 3)) (is (= 3 @child-ran))
(reset! child-props {:class 'foo}) (reset! child-props {:class 'foo})
(r/flush) (r/flush)
(is (= @child-ran 4) "symbols are different from keyw") (is (= 4 @child-ran) "symbols are different from keyw")
(reset! child-props {:class 'foo}) (reset! child-props {:class 'foo})
(r/flush) (r/flush)
(is (= @child-ran 4) "symbols are equal") (is (= 4 @child-ran) "symbols are equal")
(reset! child-props {:style {:color 'red}}) (reset! child-props {:style {:color 'red}})
(r/flush) (r/flush)
(is (= @child-ran 5)) (is (= 5 @child-ran))
(reset! child-props {:on-change (r/partial f)}) (reset! child-props {:on-change (r/partial f)})
(r/flush) (r/flush)
(is (= @child-ran 6)) (is (= 6 @child-ran))
(reset! child-props {:on-change (r/partial f)}) (reset! child-props {:on-change (r/partial f)})
(r/flush) (r/flush)
(is (= @child-ran 6)) (is (= 6 @child-ran))
(reset! child-props {:on-change (r/partial f1)}) (reset! child-props {:on-change (r/partial f1)})
(r/flush) (r/flush)
(is (= @child-ran 7)) (is (= 7 @child-ran))
(r/force-update-all) (r/force-update-all)
(is (= @child-ran 8))))))) (is (= 8 @child-ran)))))))
(deftest dirty-test (deftest dirty-test
(when r/is-client (when r/is-client
@ -254,7 +254,7 @@
state (r/atom 0) state (r/atom 0)
really-simple (fn [] really-simple (fn []
(swap! ran inc) (swap! ran inc)
(if (= @state 1) (if (= 1 @state)
(reset! state 3)) (reset! state 3))
[:div (str "state=" @state)])] [:div (str "state=" @state)])]
(with-mounted-component [really-simple nil nil] (with-mounted-component [really-simple nil nil]
@ -273,14 +273,13 @@
(deftest to-string-test [] (deftest to-string-test []
(let [comp (fn [props] (let [comp (fn [props]
[:div (str "i am " (:foo props))])] [:div (str "i am " (:foo props))])]
(is (re-find #"i am foobar" (is (= "<div>i am foobar</div>" (as-string [comp {:foo "foobar"}])))))
(as-string [comp {:foo "foobar"}])))))
(deftest data-aria-test [] (deftest data-aria-test []
(is (re-find #"data-foo" (is (= "<div data-foo=\"x\"></div>"
(as-string [:div {:data-foo "x"}]))) (as-string [:div {:data-foo "x"}])))
(is (re-find #"aria-labelledby" (is (= "<div aria-labelledby=\"x\"></div>"
(as-string [:div {:aria-labelledby "x"}]))) (as-string [:div {:aria-labelledby "x"}])))
;; Skip test: produces warning in new React ;; Skip test: produces warning in new React
;; (is (not (re-find #"enctype" ;; (is (not (re-find #"enctype"
;; (as-string [:div {"enc-type" "x"}]))) ;; (as-string [:div {"enc-type" "x"}])))
@ -297,10 +296,10 @@
(deftest dynamic-id-class [] (deftest dynamic-id-class []
(is (re-find #"id=.foo" (is (re-find #"id=.foo"
(as-string [:div#foo {:class "bar"}]))) (as-string [:div#foo {:class "bar"}])))
(is (re-find #"class=.foo bar" (is (= "<div class=\"foo bar\"></div>"
(as-string [:div.foo {:class "bar"}]))) (as-string [:div.foo {:class "bar"}])))
(is (re-find #"class=.foo bar" (is (= "<div class=\"foo bar\"></div>"
(as-string [:div.foo.bar]))) (as-string [:div.foo.bar])))
(is (re-find #"id=.foo" (is (re-find #"id=.foo"
(as-string [:div#foo.foo.bar]))) (as-string [:div#foo.foo.bar])))
(is (re-find #"class=.xxx bar" (is (re-find #"class=.xxx bar"
@ -309,8 +308,8 @@
(as-string [:div.bar {:id "foo"}]))) (as-string [:div.bar {:id "foo"}])))
(is (re-find #"id=.foo" (is (re-find #"id=.foo"
(as-string [:div.bar.xxx {:id "foo"}]))) (as-string [:div.bar.xxx {:id "foo"}])))
(is (re-find #"id=.foo" (is (= "<div id=\"foo\"></div>"
(as-string [:div#bar {:id "foo"}])) (as-string [:div#bar {:id "foo"}]))
"Dynamic id overwrites static")) "Dynamic id overwrites static"))
(defmulti my-div :type) (defmulti my-div :type)
@ -320,32 +319,26 @@
(deftest ifn-component [] (deftest ifn-component []
(let [comp {:foo [:div "foodiv"] (let [comp {:foo [:div "foodiv"]
:bar [:div "bardiv"]}] :bar [:div "bardiv"]}]
(is (re-find #"foodiv" (is (= "<div><div>foodiv</div></div>"
(as-string [:div [comp :foo]]))) (as-string [:div [comp :foo]])))
(is (re-find #"bardiv" (is (= "<div><div>bardiv</div></div>"
(as-string [:div [comp :bar]]))) (as-string [:div [comp :bar]])))
(is (re-find #"class=.foo" (is (= "<div class=\"foo\">inner</div>"
(as-string [my-div {:type :fooish :content "inner"}]))))) (as-string [my-div {:type :fooish :content "inner"}])))))
(deftest symbol-string-tag [] (deftest symbol-string-tag []
(is (re-find #"foobar" (is (= "<div>foobar</div>" (as-string ['div "foobar"])))
(as-string ['div "foobar"]))) (is (= "<div>foobar</div>" (as-string ["div" "foobar"])))
(is (re-find #"foobar" (is (= "<div id=\"foo\">x</div>" (as-string ['div#foo "x"])))
(as-string ["div" "foobar"]))) (is (= "<div id=\"foo\">x</div>" (as-string ["div#foo" "x"])))
(is (re-find #"id=.foo" (is (= "<div class=\"foo bar\"></div>" (as-string ['div.foo {:class "bar"}])))
(as-string ['div#foo "x"]))) (is (= "<div class=\"foo bar\"></div>" (as-string ["div.foo.bar"])))
(is (re-find #"id=.foo"
(as-string ["div#foo" "x"])))
(is (re-find #"class=.foo bar"
(as-string ['div.foo {:class "bar"}])))
(is (re-find #"class=.foo bar"
(as-string ["div.foo.bar"])))
(is (re-find #"id=.foo" (is (re-find #"id=.foo"
(as-string ['div#foo.foo.bar])))) (as-string ['div#foo.foo.bar]))))
(deftest partial-test [] (deftest partial-test []
(let [p1 (r/partial vector 1 2)] (let [p1 (r/partial vector 1 2)]
(is (= (p1 3) [1 2 3])) (is (= [1 2 3] (p1 3)))
(is (= p1 (r/partial vector 1 2))) (is (= p1 (r/partial vector 1 2)))
(is (ifn? p1)) (is (ifn? p1))
(is (= (r/partial vector 1 2) p1)) (is (= (r/partial vector 1 2) p1))
@ -356,10 +349,10 @@
(let [null-comp (fn [do-show] (let [null-comp (fn [do-show]
(when do-show (when do-show
[:div "div in test-null-component"]))] [:div "div in test-null-component"]))]
(is (not (re-find #"test-null-component" (is (= ""
(as-string [null-comp false])))) (as-string [null-comp false])))
(is (re-find #"test-null-component" (is (= "<div>div in test-null-component</div>"
(as-string [null-comp true]))))) (as-string [null-comp true])))))
(deftest test-static-markup (deftest test-static-markup
(is (= "<div>foo</div>" (is (= "<div>foo</div>"
@ -433,26 +426,26 @@
(deftest test-create-element (deftest test-create-element
(let [ae r/as-element (let [ae r/as-element
ce r/create-element] ce r/create-element]
(is (= (rstr (ae [:div])) (is (= (rstr (ce "div"))
(rstr (ce "div")))) (rstr (ae [:div]))))
(is (= (rstr (ae [:div])) (is (= (rstr (ce "div" nil))
(rstr (ce "div" nil)))) (rstr (ae [:div]))))
(is (= (rstr (ae [:div "foo"])) (is (= (rstr (ce "div" nil "foo"))
(rstr (ce "div" nil "foo")))) (rstr (ae [:div "foo"]))))
(is (= (rstr (ae [:div "foo" "bar"])) (is (= (rstr (ce "div" nil "foo" "bar"))
(rstr (ce "div" nil "foo" "bar")))) (rstr (ae [:div "foo" "bar"]))))
(is (= (rstr (ae [:div "foo" "bar" "foobar"])) (is (= (rstr (ce "div" nil "foo" "bar" "foobar"))
(rstr (ce "div" nil "foo" "bar" "foobar")))) (rstr (ae [:div "foo" "bar" "foobar"]))))
(is (= (rstr (ae [:div.foo "bar"])) (is (= (rstr (ce "div" #js{:className "foo"} "bar"))
(rstr (ce "div" #js{:className "foo"} "bar")))) (rstr (ae [:div.foo "bar"]))))
(is (= (rstr (ae [:div [:div "foo"]])) (is (= (rstr (ce "div" nil (ce "div" nil "foo")))
(rstr (ce "div" nil (ce "div" nil "foo"))))) (rstr (ae [:div [:div "foo"]]))))
(is (= (rstr (ae [:div [:div "foo"]])) (is (= (rstr (ce "div" nil (ae [:div "foo"])))
(rstr (ce "div" nil (ae [:div "foo"]))))) (rstr (ae [:div [:div "foo"]]))))
(is (= (rstr (ae [:div [:div "foo"]])) (is (= (rstr (ae [:div (ce "div" nil "foo")]))
(rstr (ae [:div (ce "div" nil "foo")])))))) (rstr (ae [:div [:div "foo"]]))))))
(def ndiv (let [cmp (fn [])] (def ndiv (let [cmp (fn [])]
(gobj/extend (gobj/extend
@ -526,23 +519,23 @@
(reset! a args) (reset! a args)
[:p "p:" (:a p) (:children p)]) [:p "p:" (:a p) (:children p)])
c1 (r/reactify-component c1r)] c1 (r/reactify-component c1r)]
(is (= (rstr [:p "p:a"]) (is (= (rstr (ce c1 #js{:a "a"}))
(rstr (ce c1 #js{:a "a"})))) (rstr [:p "p:a"])))
(is (= @a nil)) (is (= nil @a))
(is (= (rstr [:p "p:"]) (is (= (rstr (ce c1 #js{:a nil}))
(rstr (ce c1 #js{:a nil})))) (rstr [:p "p:"])))
(is (= (rstr [:p "p:"]) (is (= (rstr (ce c1 nil))
(rstr (ce c1 nil)))) (rstr [:p "p:"])))
(is (= (rstr [:p "p:a" [:b "b"]]) (is (= (rstr (ce c1 #js{:a "a"}
(rstr (ce c1 #js{:a "a"} (ae [:b "b"])))
(ae [:b "b"]))))) (rstr [:p "p:a" [:b "b"]])))
(is (= @a nil)) (is (= nil @a))
(is (= (rstr [:p "p:a" [:b "b"] [:i "i"]]) (is (= (rstr (ce c1 #js{:a "a"}
(rstr (ce c1 #js{:a "a"}
(ae [:b "b"]) (ae [:b "b"])
(ae [:i "i"]))))) (ae [:i "i"])))
(is (= @a nil)))) (rstr [:p "p:a" [:b "b"] [:i "i"]])))
(is (= nil @a))))
(deftest test-keys (deftest test-keys
(let [a nil ;; (r/atom "a") (let [a nil ;; (r/atom "a")
@ -573,16 +566,16 @@
(first (:warn w))))))))) (first (:warn w)))))))))
(deftest test-extended-syntax (deftest test-extended-syntax
(is (= (rstr [:p>b "foo"]) (is (= "<p><b>foo</b></p>"
"<p><b>foo</b></p>")) (rstr [:p>b "foo"])))
(is (= (rstr [:p.foo>b "x"]) (is (= (rstr [:p.foo [:b "x"]])
(rstr [:p.foo [:b "x"]]))) (rstr [:p.foo>b "x"])))
(is (= (rstr [:div.foo>p.bar.foo>b.foobar "xy"]) (is (= (rstr [:div.foo [:p.bar.foo [:b.foobar "xy"]]])
(rstr [:div.foo [:p.bar.foo [:b.foobar "xy"]]]))) (rstr [:div.foo>p.bar.foo>b.foobar "xy"])))
(is (= (rstr [:div.foo>p.bar.foo>b.foobar {} "xy"]) (is (= (rstr [:div.foo [:p.bar.foo [:b.foobar "xy"]]])
(rstr [:div.foo [:p.bar.foo [:b.foobar "xy"]]]))) (rstr [:div.foo>p.bar.foo>b.foobar {} "xy"])))
(is (= (rstr [:div>p.bar.foo>a.foobar {:href "href"} "xy"]) (is (= (rstr [:div [:p.bar.foo [:a.foobar {:href "href"} "xy"]]])
(rstr [:div [:p.bar.foo [:a.foobar {:href "href"} "xy"]]])))) (rstr [:div>p.bar.foo>a.foobar {:href "href"} "xy"]))))
(deftest extended-syntax-metadata (deftest extended-syntax-metadata
(when r/is-client (when r/is-client
@ -596,35 +589,35 @@
))))) )))))
(deftest test-class-from-collection (deftest test-class-from-collection
(is (= (rstr [:p {:class ["a" "b" "c" "d"]}]) (is (= (rstr [:p {:class "a b c d"}])
(rstr [:p {:class "a b c d"}]))) (rstr [:p {:class ["a" "b" "c" "d"]}])))
(is (= (rstr [:p {:class ["a" nil "b" false "c" nil]}]) (is (= (rstr [:p {:class "a b c"}])
(rstr [:p {:class "a b c"}]))) (rstr [:p {:class ["a" nil "b" false "c" nil]}])))
(is (= (rstr [:p {:class '("a" "b" "c")}]) (is (= (rstr [:p {:class "a b c"}])
(rstr [:p {:class "a b c"}]))) (rstr [:p {:class '("a" "b" "c")}])))
(is (= (rstr [:p {:class #{"a" "b" "c"}}]) (is (= (rstr [:p {:class "a b c"}])
(rstr [:p {:class "a b c"}])))) (rstr [:p {:class #{"a" "b" "c"}}]))))
(deftest class-different-types (deftest class-different-types
(testing "named values are supported" (testing "named values are supported"
(is (= (rstr [:p {:class :a}]) (is (= (rstr [:p {:class "a"}])
(rstr [:p {:class "a"}]))) (rstr [:p {:class :a}])))
(is (= (rstr [:p.a {:class :b}]) (is (= (rstr [:p {:class "a b"}])
(rstr [:p {:class "a b"}]))) (rstr [:p.a {:class :b}])))
(is (= (rstr [:p.a {:class 'b}]) (is (= (rstr [:p {:class "a b"}])
(rstr [:p {:class "a b"}]))) (rstr [:p.a {:class 'b}])))
(is (= (rstr [:p {:class [:a :b]}]) (is (= (rstr [:p {:class "a b"}])
(rstr [:p {:class "a b"}]))) (rstr [:p {:class [:a :b]}])))
(is (= (rstr [:p {:class ['a :b]}]) (is (= (rstr [:p {:class "a b"}])
(rstr [:p {:class "a b"}])))) (rstr [:p {:class ['a :b]}]))))
(testing "non-named values like numbers" (testing "non-named values like numbers"
(is (= (rstr [:p {:class [1 :b]}]) (is (= (rstr [:p {:class "1 b"}])
(rstr [:p {:class "1 b"}])))) (rstr [:p {:class [1 :b]}]))))
(testing "falsey values are filtered from collections" (testing "falsey values are filtered from collections"
(is (= (rstr [:p {:class [:a :b false nil]}]) (is (= (rstr [:p {:class "a b"}])
(rstr [:p {:class "a b"}])))) ) (rstr [:p {:class [:a :b false nil]}])))) )
(deftest test-force-update (deftest test-force-update
(let [v (atom {:v1 0 (let [v (atom {:v1 0
@ -646,23 +639,23 @@
[:div "" (reset! spy @(r/track t1))])] [:div "" (reset! spy @(r/track t1))])]
(with-mounted-component [c2] (with-mounted-component [c2]
(fn [c div] (fn [c div]
(is (= @v {:v1 1 :v2 1})) (is (= {:v1 1 :v2 1} @v))
(r/force-update (:c2 @comps)) (r/force-update (:c2 @comps))
(is (= @v {:v1 1 :v2 2})) (is (= {:v1 1 :v2 2} @v))
(r/force-update (:c1 @comps)) (r/force-update (:c1 @comps))
(is (= @v {:v1 2 :v2 2})) (is (= {:v1 2 :v2 2} @v))
(r/force-update (:c2 @comps) true) (r/force-update (:c2 @comps) true)
(is (= @v {:v1 3 :v2 3})))) (is (= {:v1 3 :v2 3} @v))))
(with-mounted-component [c3] (with-mounted-component [c3]
(fn [c] (fn [c]
(is (= @spy 0)) (is (= 0 @spy))
(swap! state inc) (swap! state inc)
(is (= @spy 0)) (is (= 0 @spy))
(r/force-update (:c3 @comps)) (r/force-update (:c3 @comps))
(is (= @spy 1)))))) (is (= 1 @spy))))))
(deftest test-component-path (deftest test-component-path
(let [a (atom nil) (let [a (atom nil)
@ -681,7 +674,7 @@
[:div (map 1)]) [:div (map 1)])
c2 (fn [] c2 (fn []
[c1 (sorted-map 1 "foo" 2 "bar")])] [c1 (sorted-map 1 "foo" 2 "bar")])]
(is (= (rstr [c2]) "<div>foo</div>")))) (is (= "<div>foo</div>" (rstr [c2])))))
(deftest basic-with-let (deftest basic-with-let
(when r/is-client (when r/is-client
@ -732,10 +725,10 @@
[f @s]))] [f @s]))]
(with-mounted-component [c] (with-mounted-component [c]
(fn [_ div] (fn [_ div]
(is (= @a "foo")) (is (= "foo" @a))
(reset! s "bar") (reset! s "bar")
(r/flush) (r/flush)
(is (= @a "bar"))))))) (is (= "bar" @a)))))))
(deftest with-let-non-reactive (deftest with-let-non-reactive
(let [n1 (atom 0) (let [n1 (atom 0)
@ -808,38 +801,38 @@
cnative (fn [] cnative (fn []
(into [:> @comp] @arg)) (into [:> @comp] @arg))
check (fn [] check (fn []
(is (= (:initial-state @res) (is (= {:at 1 :args [@t]}
{:at 1 :args [@t]})) (:initial-state @res)))
(is (= (:will-mount @res) (is (= {:at 2 :args [@t]}
{:at 2 :args [@t]})) (:will-mount @res)))
(is (= (:render @res) (is (= {:at 3 :args ["a" "b"]}
{:at 3 :args ["a" "b"]})) (:render @res)))
(is (= (:did-mount @res) (is (= {:at 4 :args [@t]}
{:at 4 :args [@t]})) (:did-mount @res)))
(reset! arg ["a" "c"]) (reset! arg ["a" "c"])
(r/flush) (r/flush)
(is (= (:will-receive @res) (is (= {:at 5 :args [@t [@comp "a" "c"]]}
{:at 5 :args [@t [@comp "a" "c"]]})) (:will-receive @res)))
(is (= (:should-update @res) (is (= {:at 6 :args [@t [@comp "a" "b"] [@comp "a" "c"]]}
{:at 6 :args [@t [@comp "a" "b"] [@comp "a" "c"]]})) (:should-update @res)))
(is (= (:will-update @res) (is (= {:at 7 :args [@t [@comp "a" "c"] {:foo "bar"}]}
{:at 7 :args [@t [@comp "a" "c"] {:foo "bar"}]})) (:will-update @res)))
(is (= (:render @res) (is (= {:at 8 :args ["a" "c"]}
{:at 8 :args ["a" "c"]})) (:render @res)))
(is (= (:did-update @res) (is (= {:at 9 :args [@t [@comp "a" "b"] {:foo "bar"} nil]}
{:at 9 :args [@t [@comp "a" "b"] {:foo "bar"} nil]})))] (:did-update @res))))]
(when r/is-client (when r/is-client
(with-mounted-component [c2] check) (with-mounted-component [c2] check)
(is (= (:will-unmount @res) (is (= {:at 10 :args [@t]}
{:at 10 :args [@t]})) (:will-unmount @res)))
(reset! comp (with-meta render2 ls)) (reset! comp (with-meta render2 ls))
(reset! arg defarg) (reset! arg defarg)
(reset! n1 0) (reset! n1 0)
(with-mounted-component [c2] check) (with-mounted-component [c2] check)
(is (= (:will-unmount @res) (is (= {:at 10 :args [@t]}
{:at 10 :args [@t]}))))) (:will-unmount @res))))))
(deftest lifecycle-native (deftest lifecycle-native
@ -856,8 +849,8 @@
(this-as (this-as
c c
(when @newprops (when @newprops
(is (= @newprops) (first args)) (is (= (first args) @newprops))
(is (= @newprops) (r/props c))) (is (= (r/props c) @newprops)))
(is (= c (r/current-component))) (is (= c (r/current-component)))
(is (= (first args) (r/props c))) (is (= (first args) (r/props c)))
(add-args :render (add-args :render
@ -908,43 +901,43 @@
cnative (fn [] cnative (fn []
(into [:> @comp] @arg)) (into [:> @comp] @arg))
check (fn [] check (fn []
(is (= (:initial-state @res) (is (= {:at 1 :args [@t]}
{:at 1 :args [@t]})) (:initial-state @res)))
(is (= (:will-mount @res) (is (= {:at 2 :args [@t]}
{:at 2 :args [@t]})) (:will-mount @res)))
(is (= (:render @res) (is (= {:at 3 :args [[:children ["a" "b"]]]}
{:at 3 :args [[:children ["a" "b"]]]})) (:render @res)))
(is (= (:did-mount @res) (is (= {:at 4 :args [@t]}
{:at 4 :args [@t]})) (:did-mount @res)))
(reset! arg [{:f "oo"} "a" "c"]) (reset! arg [{:f "oo"} "a" "c"])
(r/flush) (r/flush)
(is (= (:will-receive @res) (is (= {:at 5 :args [{:foo "bar"} "a" "b"]}
{:at 5 :args [{:foo "bar"} "a" "b"]})) (:will-receive @res)))
(let [a (:should-update @res) (let [a (:should-update @res)
{at :at {at :at
[this oldv newv] :args} a] [this oldv newv] :args} a]
(is (= at 6)) (is (= 6 at))
(is (= (count (:args a)) 3)) (is (= 3 (count (:args a))))
(is (= (js->clj oldv) (js->clj [@comp @oldprops]))) (is (= (js->clj [@comp @oldprops]) (js->clj oldv)))
(is (= newv [@comp @newprops]))) (is (= [@comp @newprops] newv)))
(let [a (:will-update @res) (let [a (:will-update @res)
{at :at {at :at
[this newv] :args} a] [this newv] :args} a]
(is (= at 7)) (is (= 7 at))
(is (= newv [@comp @newprops]))) (is (= [@comp @newprops] newv)))
(is (= (:render @res) (is (= {:at 8 :args [[:children ["a" "c"]]]}
{:at 8 :args [[:children ["a" "c"]]]})) (:render @res)))
(let [a (:did-update @res) (let [a (:did-update @res)
{at :at {at :at
[this oldv] :args} a] [this oldv] :args} a]
(is (= at 9)) (is (= 9 at))
(is (= oldv [@comp @oldprops]))))] (is (= [@comp @oldprops] oldv))))]
(when r/is-client (when r/is-client
(with-mounted-component [cnative] check) (with-mounted-component [cnative] check)
(is (= (:will-unmount @res) (is (= {:at 10 :args [@t]}
{:at 10 :args [@t]}))))) (:will-unmount @res))))))
(defn foo [] (defn foo []
[:div]) [:div])
@ -1029,8 +1022,8 @@
#(is (thrown-with-msg? #(is (thrown-with-msg?
:default (re "Invalid tag: 'div.' \\(" stack2 "\\)") :default (re "Invalid tag: 'div.' \\(" stack2 "\\)")
(rend [comp2 [:div. "foo"]]))))))] (rend [comp2 [:div. "foo"]]))))))]
(is (= (last (:error e)) (is (= (str "Error rendering component (" stack2 ")")
(str "Error rendering component (" stack2 ")")))) (last (:error e)))))
(let [e (debug/track-warnings (let [e (debug/track-warnings
(wrap-capture-window-error (wrap-capture-window-error
@ -1038,8 +1031,8 @@
#(is (thrown-with-msg? #(is (thrown-with-msg?
:default (re "Invalid tag: 'div.' \\(" stack1 "\\)") :default (re "Invalid tag: 'div.' \\(" stack1 "\\)")
(rend [comp1 [:div. "foo"]]))))))] (rend [comp1 [:div. "foo"]]))))))]
(is (= (last (:error e)) (is (= (str "Error rendering component (" stack1 ")")
(str "Error rendering component (" stack1 ")")))) (last (:error e)))))
(let [e (debug/track-warnings #(r/as-element [nat]))] (let [e (debug/track-warnings #(r/as-element [nat]))]
(is (re-find #"Using native React classes directly" (is (re-find #"Using native React classes directly"
@ -1089,8 +1082,8 @@
(reset! node (r/dom-node this)))})] (reset! node (r/dom-node this)))})]
(with-mounted-component [comp] (with-mounted-component [comp]
(fn [c div] (fn [c div]
(is (= (.-innerHTML @ref) "foobar")) (is (= "foobar" (.-innerHTML @ref)))
(is (= (.-innerHTML @node) "foobar")) (is (= "foobar" (.-innerHTML @node)))
(is (identical? @ref @node)))))) (is (identical? @ref @node))))))
(deftest test-empty-input (deftest test-empty-input
@ -1111,42 +1104,42 @@
state (r/atom 0) state (r/atom 0)
comp (fn [] comp (fn []
(let [old @spy] (let [old @spy]
(is (nil? (r/after-render (r/after-render
(fn [] (fn []
(is (= "DIV" (.-tagName @node))) (is (= "DIV" (.-tagName @node)))
(swap! spy inc))))) (swap! spy inc)))
(is (= old @spy)) (is (= @spy old))
(is (= @exp @val)) (is (= @exp @val))
[:div {:ref #(reset! node %)} @state]))] [:div {:ref #(reset! node %)} @state]))]
(with-mounted-component [comp] (with-mounted-component [comp]
(fn [c div] (fn [c div]
(is (= @spy 1)) (is (= 1 @spy))
(swap! state inc) (swap! state inc)
(is (= @spy 1)) (is (= 1 @spy))
(is (nil? (r/next-tick #(swap! val inc)))) (r/next-tick #(swap! val inc))
(reset! exp 1) (reset! exp 1)
(is (= @val 0)) (is (= 0 @val))
(is (nil? (r/flush)))
(is (= @val 1))
(is (= @spy 2))
(is (nil? (r/force-update c)))
(is (= @spy 3))
(is (nil? (r/next-tick #(reset! spy 0))))
(is (= @spy 3))
(r/flush) (r/flush)
(is (= @spy 0)))) (is (= 1 @val))
(is (= @node nil)))) (is (= 2 @spy))
(r/force-update c)
(is (= 3 @spy))
(r/next-tick #(reset! spy 0))
(is (= 3 @spy))
(r/flush)
(is (= 0 @spy))))
(is (= nil @node))))
(deftest style-property-names-are-camel-cased (deftest style-property-names-are-camel-cased
(is (re-find #"<div style=\"text-align:center(;?)\">foo</div>" (is (= "<div style=\"text-align:center\">foo</div>"
(rstr [:div {:style {:text-align "center"}} "foo"])))) (rstr [:div {:style {:text-align "center"}} "foo"]))))
(deftest custom-element-class-prop (deftest custom-element-class-prop
(is (re-find #"<custom-element class=\"foobar\">foo</custom-element>" (is (= "<custom-element class=\"foobar\">foo</custom-element>"
(rstr [:custom-element {:class "foobar"} "foo"]))) (rstr [:custom-element {:class "foobar"} "foo"])))
(is (re-find #"<custom-element class=\"foobar\">foo</custom-element>" (is (= "<custom-element class=\"foobar\">foo</custom-element>"
(rstr [:custom-element.foobar "foo"])))) (rstr [:custom-element.foobar "foo"]))))
(deftest html-entities (deftest html-entities
(testing "entity numbers can be unescaped always" (testing "entity numbers can be unescaped always"

View File

@ -8,43 +8,43 @@
ws (fn [] (r/wrap (:foo @state) ws (fn [] (r/wrap (:foo @state)
swap! state assoc :foo))] swap! state assoc :foo))]
(let [w1 (ws) w2 (ws)] (let [w1 (ws) w2 (ws)]
(is (= @w1 1)) (is (= 1 @w1))
(is (= w1 w2)) (is (= w1 w2))
(reset! w1 1) (reset! w1 1)
(is (= @w1 1)) (is (= 1 @w1))
(is (= @w1 @w2)) (is (= @w1 @w2))
(is (not= w1 w2))) (is (not= w1 w2)))
(let [w1 (ws) w2 (ws)] (let [w1 (ws) w2 (ws)]
(is (= @w1 1)) (is (= 1 @w1))
(is (= w1 w2)) (is (= w1 w2))
(reset! w2 1) (reset! w2 1)
(is (= @w2 1)) (is (= 1 @w2))
(is (= @w1 @w2)) (is (= @w1 @w2))
(is (not= w1 w2)) (is (not= w1 w2))
(reset! w1 1)) (reset! w1 1))
(let [w1 (ws) w2 (ws)] (let [w1 (ws) w2 (ws)]
(is (= @w1 1)) (is (= 1 @w1))
(is (= w1 w2)) (is (= w1 w2))
(is (= w2 w1)) (is (= w2 w1))
(reset! w1 2) (reset! w1 2)
(is (= @w1 2)) (is (= 2 @w1))
(is (= (:foo @state) 2)) (is (= 2 (:foo @state)))
(is (not= @w1 @w2)) (is (not= @w1 @w2))
(is (not= w1 w2)) (is (not= w1 w2))
(is (not= w2 w1)) (is (not= w2 w1))
(reset! w1 1) (reset! w1 1)
(is (= (:foo @state) 1))) (is (= 1 (:foo @state))))
(let [w1 (ws) w2 (ws)] (let [w1 (ws) w2 (ws)]
(is (= @w1 1)) (is (= 1 @w1))
(is (= w1 w2)) (is (= w1 w2))
(reset! w1 2) (reset! w1 2)
(reset! w2 2) (reset! w2 2)
(is (= @w1 2)) (is (= 2 @w1))
(is (= (:foo @state) 2)) (is (= 2 (:foo @state)))
(is (= @w2 2)) (is (= 2 @w2))
(is (= @w1 @w2)) (is (= @w1 @w2))
(is (not= w1 w2)) (is (not= w1 w2))
(reset! w1 1)))) (reset! w1 1))))
@ -82,7 +82,7 @@
(is (not= b a)) (is (not= b a))
(is (= (swap! a update-in [:k] inc) (is (= (swap! a update-in [:k] inc)
(swap! b update-in [:k] inc))) (swap! b update-in [:k] inc)))
(is (= @a @b {:k 2})) (is (= {:k 2} @a @b))
(is (= (swap! a assoc :k 3 :l 4 :m 7 :n 8 :o) (is (= (swap! a assoc :k 3 :l 4 :m 7 :n 8 :o)
(swap! b assoc :k 3 :l 4 :m 7 :n 8 :o))) (swap! b assoc :k 3 :l 4 :m 7 :n 8 :o)))
(is (= (reset! a 23) (is (= (reset! a 23)
@ -90,7 +90,7 @@
(is (= @a @b)) (is (= @a @b))
(is (= (swap! a inc) (is (= (swap! a inc)
(swap! b inc))) (swap! b inc)))
(is (= @a @b 24)))) (is (= 24 @a @b))))
(deftest test-wrap (deftest test-wrap
(when r/is-client (when r/is-client
@ -113,47 +113,47 @@
(u/run-fns-after-render (u/run-fns-after-render
(fn [] (fn []
(is (= "value:1:" (.-innerText div))) (is (= "value:1:" (.-innerText div)))
(is (= @ran 1)) (is (= 1 @ran))
(reset! @grand-state {:foobar 2})) (reset! @grand-state {:foobar 2}))
(fn [] (fn []
(is (= @state {:foo {:bar {:foobar 2}}})) (is (= {:foo {:bar {:foobar 2}}} @state))
(is (= @ran 2)) (is (= 2 @ran))
(is (= "value:2:" (.-innerText div))) (is (= "value:2:" (.-innerText div)))
(swap! state update-in [:foo :bar] assoc :foobar 3)) (swap! state update-in [:foo :bar] assoc :foobar 3))
(fn [] (fn []
(is (= @ran 3)) (is (= 3 @ran))
(is (= "value:3:" (.-innerText div))) (is (= "value:3:" (.-innerText div)))
(reset! state {:foo {:bar {:foobar 3}} (reset! state {:foo {:bar {:foobar 3}}
:foo1 {}})) :foo1 {}}))
(fn [] (fn []
(is (= @ran 3)) (is (= 3 @ran))
(reset! @grand-state {:foobar 3})) (reset! @grand-state {:foobar 3}))
(fn [] (fn []
(is (= @ran 3)) (is (= 3 @ran))
(reset! state {:foo {:bar {:foobar 2}} (reset! state {:foo {:bar {:foobar 2}}
:foo2 {}})) :foo2 {}}))
(fn [] (fn []
(is (= "value:2:" (.-innerText div))) (is (= "value:2:" (.-innerText div)))
(is (= @ran 4)) (is (= 4 @ran))
(reset! @grand-state {:foobar 2})) (reset! @grand-state {:foobar 2}))
(fn [] (fn []
(is (= "value:2:" (.-innerText div))) (is (= "value:2:" (.-innerText div)))
(is (= @ran 5)) (is (= 5 @ran))
(reset! state {:foo {:bar {:foobar 4}}}) (reset! state {:foo {:bar {:foobar 4}}})
(reset! @grand-state {:foobar 4})) (reset! @grand-state {:foobar 4}))
(fn [] (fn []
(is (= "value:4:" (.-innerText div))) (is (= "value:4:" (.-innerText div)))
(is (= @ran 6)) (is (= 6 @ran))
(reset! @grand-state {:foobar 4})) (reset! @grand-state {:foobar 4}))
(fn [] (fn []
(is (= "value:4:" (.-innerText div))) (is (= "value:4:" (.-innerText div)))
(is (= @ran 7))) (is (= 7 @ran)))
done))))))) done)))))))
(deftest test-cursor (deftest test-cursor
@ -174,25 +174,25 @@
(fn [c div done] (fn [c div done]
(u/run-fns-after-render (u/run-fns-after-render
(fn [] (fn []
(is (= @a-count 1)) (is (= 1 @a-count))
(is (= @b-count 1)) (is (= 1 @b-count))
(swap! state update-in [:a :v] inc) (swap! state update-in [:a :v] inc)
(is (= @a-count 1))) (is (= 1 @a-count)))
(fn [] (fn []
(is (= @a-count 2)) (is (= 2 @a-count))
(is (= @b-count 1)) (is (= 1 @b-count))
(reset! state {:a {:v 2} :b {:v 2}})) (reset! state {:a {:v 2} :b {:v 2}}))
(fn [] (fn []
(is (= @a-count 2)) (is (= 2 @a-count))
(is (= @b-count 1)) (is (= 1 @b-count))
(reset! state {:a {:v 3} :b {:v 2}})) (reset! state {:a {:v 3} :b {:v 2}}))
(fn [] (fn []
(is (= @a-count 3)) (is (= 3 @a-count))
(is (= @b-count 1))) (is (= 1 @b-count)))
done))))))) done)))))))
(deftest test-fn-cursor (deftest test-fn-cursor
@ -212,23 +212,23 @@
[derefer bc]])] [derefer bc]])]
(with-mounted-component [comp] (with-mounted-component [comp]
(fn [c div] (fn [c div]
(is (= @a-count 1)) (is (= 1 @a-count))
(is (= @b-count 1)) (is (= 1 @b-count))
(swap! state update-in [:a :v] inc) (swap! state update-in [:a :v] inc)
(is (= @a-count 1)) (is (= 1 @a-count))
(is (= @b-count 1)) (is (= 1 @b-count))
(r/flush) (r/flush)
(is (= @a-count 2)) (is (= 2 @a-count))
(is (= @b-count 2)) (is (= 2 @b-count))
(reset! state {:a {:v 2} :b {:v 2}}) (reset! state {:a {:v 2} :b {:v 2}})
(r/flush) (r/flush)
(is (= @a-count 2)) (is (= 2 @a-count))
(is (= @b-count 2)) (is (= 2 @b-count))
(reset! state {:a {:v 3} :b {:v 2}}) (reset! state {:a {:v 3} :b {:v 2}})
(r/flush) (r/flush)
(is (= @a-count 3)) (is (= 3 @a-count))
(is (= @b-count 3)))))) (is (= 3 @b-count))))))