aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/control/function
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux/control/function')
-rw-r--r--stdlib/source/test/lux/control/function/contract.lux40
-rw-r--r--stdlib/source/test/lux/control/function/inline.lux6
-rw-r--r--stdlib/source/test/lux/control/function/memo.lux106
-rw-r--r--stdlib/source/test/lux/control/function/mixin.lux166
-rw-r--r--stdlib/source/test/lux/control/function/mutual.lux4
5 files changed, 161 insertions, 161 deletions
diff --git a/stdlib/source/test/lux/control/function/contract.lux b/stdlib/source/test/lux/control/function/contract.lux
index def434469..cf12b1fbf 100644
--- a/stdlib/source/test/lux/control/function/contract.lux
+++ b/stdlib/source/test/lux/control/function/contract.lux
@@ -22,24 +22,24 @@
(do [! random.monad]
[expected random.nat])
(all _.and
- (_.cover [/.pre /.pre_condition_failed]
- (case (try (/.pre (n.even? expected)
- true))
- {try.#Success output}
- output
-
- {try.#Failure error}
- (and (text.contains? (the exception.#label /.pre_condition_failed)
- error)
- (not (n.even? expected)))))
- (_.cover [/.post /.post_condition_failed]
- (case (try (/.post n.odd?
- expected))
- {try.#Success actual}
- (same? expected actual)
-
- {try.#Failure error}
- (and (text.contains? (the exception.#label /.post_condition_failed)
- error)
- (not (n.odd? expected)))))
+ (_.coverage [/.pre /.pre_condition_failed]
+ (case (try (/.pre (n.even? expected)
+ true))
+ {try.#Success output}
+ output
+
+ {try.#Failure error}
+ (and (text.contains? (the exception.#label /.pre_condition_failed)
+ error)
+ (not (n.even? expected)))))
+ (_.coverage [/.post /.post_condition_failed]
+ (case (try (/.post n.odd?
+ expected))
+ {try.#Success actual}
+ (same? expected actual)
+
+ {try.#Failure error}
+ (and (text.contains? (the exception.#label /.post_condition_failed)
+ error)
+ (not (n.odd? expected)))))
)))
diff --git a/stdlib/source/test/lux/control/function/inline.lux b/stdlib/source/test/lux/control/function/inline.lux
index 09cbff8c5..98bc73c3b 100644
--- a/stdlib/source/test/lux/control/function/inline.lux
+++ b/stdlib/source/test/lux/control/function/inline.lux
@@ -26,7 +26,7 @@
m0 measurement
m1 measurement])
(all _.and
- (_.cover [/.inline:]
- (i.= (..!quadrance/2 m0 m1)
- (..quadrance/2 m0 m1)))
+ (_.coverage [/.inline:]
+ (i.= (..!quadrance/2 m0 m1)
+ (..quadrance/2 m0 m1)))
)))
diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux
index 96c401be0..84abe3905 100644
--- a/stdlib/source/test/lux/control/function/memo.lux
+++ b/stdlib/source/test/lux/control/function/memo.lux
@@ -63,60 +63,60 @@
[input (|> random.nat (# ! each (|>> (n.% 5) (n.+ 21))))])
(_.for [/.Memo])
(all _.and
- (_.cover [/.closed /.none]
- (io.run!
- (do io.monad
- [.let [slow (/.none n.hash ..fibonacci)
- fast (/.closed n.hash fibonacci)]
- [slow_time slow_output] (..time slow input)
- [fast_time fast_output] (..time fast input)
- .let [same_output!
- (n.= slow_output
- fast_output)
+ (_.coverage [/.closed /.none]
+ (io.run!
+ (do io.monad
+ [.let [slow (/.none n.hash ..fibonacci)
+ fast (/.closed n.hash fibonacci)]
+ [slow_time slow_output] (..time slow input)
+ [fast_time fast_output] (..time fast input)
+ .let [same_output!
+ (n.= slow_output
+ fast_output)
- memo_is_faster!
- (n.< (n.+ ..wiggle_room (milli_seconds slow_time))
- (milli_seconds fast_time))]]
- (in (and same_output!
- memo_is_faster!)))))
- (_.cover [/.open]
- (io.run!
- (do io.monad
- [.let [none (/.none n.hash ..fibonacci)
- memory (dictionary.empty n.hash)
- open (/.open fibonacci)]
- [none_time none_output] (..time none input)
- [open_time [memory open_output]] (..time open [memory input])
- [open_time/+1 _] (..time open [memory (++ input)])
- .let [same_output!
- (n.= none_output
- open_output)
+ memo_is_faster!
+ (n.< (n.+ ..wiggle_room (milli_seconds slow_time))
+ (milli_seconds fast_time))]]
+ (in (and same_output!
+ memo_is_faster!)))))
+ (_.coverage [/.open]
+ (io.run!
+ (do io.monad
+ [.let [none (/.none n.hash ..fibonacci)
+ memory (dictionary.empty n.hash)
+ open (/.open fibonacci)]
+ [none_time none_output] (..time none input)
+ [open_time [memory open_output]] (..time open [memory input])
+ [open_time/+1 _] (..time open [memory (++ input)])
+ .let [same_output!
+ (n.= none_output
+ open_output)
- memo_is_faster!
- (n.< (n.+ ..wiggle_room (milli_seconds none_time))
- (milli_seconds open_time))
+ memo_is_faster!
+ (n.< (n.+ ..wiggle_room (milli_seconds none_time))
+ (milli_seconds open_time))
- incrementalism_is_faster!
- (n.< (n.+ ..wiggle_room (milli_seconds open_time))
- (milli_seconds open_time/+1))]]
- (in (and same_output!
- memo_is_faster!
- incrementalism_is_faster!)))))
- (_.cover [/.memoization]
- (let [memo (<| //.fixed
- (//.mixed /.memoization)
- (is (//.Mixin Nat (State (Dictionary Nat Nat) Nat))
- (function (factorial delegate again input)
- (case input
- (^.or 0 1) (# state.monad in 1)
- _ (do state.monad
- [output' (again (-- input))]
- (in (n.* input output')))))))
- expected (|> (list.indices input)
- (list#each ++)
- (list#mix n.* 1))
- actual (|> (memo input)
- (state.result (dictionary.empty n.hash))
- product.right)]
- (n.= expected actual)))
+ incrementalism_is_faster!
+ (n.< (n.+ ..wiggle_room (milli_seconds open_time))
+ (milli_seconds open_time/+1))]]
+ (in (and same_output!
+ memo_is_faster!
+ incrementalism_is_faster!)))))
+ (_.coverage [/.memoization]
+ (let [memo (<| //.fixed
+ (//.mixed /.memoization)
+ (is (//.Mixin Nat (State (Dictionary Nat Nat) Nat))
+ (function (factorial delegate again input)
+ (case input
+ (^.or 0 1) (# state.monad in 1)
+ _ (do state.monad
+ [output' (again (-- input))]
+ (in (n.* input output')))))))
+ expected (|> (list.indices input)
+ (list#each ++)
+ (list#mix n.* 1))
+ actual (|> (memo input)
+ (state.result (dictionary.empty n.hash))
+ product.right)]
+ (n.= expected actual)))
)))
diff --git a/stdlib/source/test/lux/control/function/mixin.lux b/stdlib/source/test/lux/control/function/mixin.lux
index 7e41c7be7..8cb2ae3c6 100644
--- a/stdlib/source/test/lux/control/function/mixin.lux
+++ b/stdlib/source/test/lux/control/function/mixin.lux
@@ -49,89 +49,89 @@
(_.for [/.monoid]
($monoid.spec equivalence /.monoid generator))
- (_.cover [/.fixed]
- (let [factorial (/.fixed
- (function (_ delegate again input)
- (case input
- (^.or 0 1) 1
- _ (n.* input (again (-- input))))))]
- (n.= expected
- (factorial input))))
- (_.cover [/.mixed]
- (let [bottom (is (/.Mixin Nat Nat)
- (function (_ delegate again input)
- (case input
- (^.or 0 1) 1
- _ (delegate input))))
- multiplication (is (/.Mixin Nat Nat)
- (function (_ delegate again input)
- (n.* input (again (-- input)))))
- factorial (/.fixed (/.mixed bottom multiplication))]
- (n.= expected
- (factorial input))))
- (_.cover [/.nothing]
- (let [loop (is (/.Mixin Nat Nat)
- (function (_ delegate again input)
- (case input
- (^.or 0 1) 1
- _ (n.* input (delegate (-- input))))))
- left (/.fixed (/.mixed /.nothing loop))
- right (/.fixed (/.mixed loop /.nothing))]
- (and (n.= expected
- (left input))
- (n.= expected
- (right input)))))
- (_.cover [/.advice]
- (let [bottom (is (/.Mixin Nat Nat)
- (function (_ delegate again input)
- 1))
- bottom? (is (Predicate Nat)
- (function (_ input)
- (case input
- (^.or 0 1) true
- _ false)))
- multiplication (is (/.Mixin Nat Nat)
- (function (_ delegate again input)
- (n.* input (again (-- input)))))
- factorial (/.fixed (/.mixed (/.advice bottom? bottom)
- multiplication))]
- (n.= expected
- (factorial input))))
- (_.cover [/.before]
- (let [implant (is (-> Nat (State Nat []))
- (function (_ input)
- (function (_ state)
- [shift []])))
- meld (is (/.Mixin Nat (State Nat Nat))
- (function (_ delegate again input)
- (function (_ state)
- [state (n.+ state input)])))
- function (/.fixed (/.mixed (/.before state.monad implant)
- meld))]
- (n.= (n.+ shift input)
- (|> input function (state.result dummy) product.right))))
- (_.cover [/.after]
- (let [implant (is (-> Nat Nat (State Nat []))
- (function (_ input output)
- (function (_ state)
- [shift []])))
- meld (is (/.Mixin Nat (State Nat Nat))
- (function (_ delegate again input)
- (function (_ state)
- [state (n.+ state input)])))
- function (/.fixed (/.mixed (/.after state.monad implant)
- meld))]
- (n.= (n.+ dummy input)
- (|> input function (state.result dummy) product.right))))
+ (_.coverage [/.fixed]
+ (let [factorial (/.fixed
+ (function (_ delegate again input)
+ (case input
+ (^.or 0 1) 1
+ _ (n.* input (again (-- input))))))]
+ (n.= expected
+ (factorial input))))
+ (_.coverage [/.mixed]
+ (let [bottom (is (/.Mixin Nat Nat)
+ (function (_ delegate again input)
+ (case input
+ (^.or 0 1) 1
+ _ (delegate input))))
+ multiplication (is (/.Mixin Nat Nat)
+ (function (_ delegate again input)
+ (n.* input (again (-- input)))))
+ factorial (/.fixed (/.mixed bottom multiplication))]
+ (n.= expected
+ (factorial input))))
+ (_.coverage [/.nothing]
+ (let [loop (is (/.Mixin Nat Nat)
+ (function (_ delegate again input)
+ (case input
+ (^.or 0 1) 1
+ _ (n.* input (delegate (-- input))))))
+ left (/.fixed (/.mixed /.nothing loop))
+ right (/.fixed (/.mixed loop /.nothing))]
+ (and (n.= expected
+ (left input))
+ (n.= expected
+ (right input)))))
+ (_.coverage [/.advice]
+ (let [bottom (is (/.Mixin Nat Nat)
+ (function (_ delegate again input)
+ 1))
+ bottom? (is (Predicate Nat)
+ (function (_ input)
+ (case input
+ (^.or 0 1) true
+ _ false)))
+ multiplication (is (/.Mixin Nat Nat)
+ (function (_ delegate again input)
+ (n.* input (again (-- input)))))
+ factorial (/.fixed (/.mixed (/.advice bottom? bottom)
+ multiplication))]
+ (n.= expected
+ (factorial input))))
+ (_.coverage [/.before]
+ (let [implant (is (-> Nat (State Nat []))
+ (function (_ input)
+ (function (_ state)
+ [shift []])))
+ meld (is (/.Mixin Nat (State Nat Nat))
+ (function (_ delegate again input)
+ (function (_ state)
+ [state (n.+ state input)])))
+ function (/.fixed (/.mixed (/.before state.monad implant)
+ meld))]
+ (n.= (n.+ shift input)
+ (|> input function (state.result dummy) product.right))))
+ (_.coverage [/.after]
+ (let [implant (is (-> Nat Nat (State Nat []))
+ (function (_ input output)
+ (function (_ state)
+ [shift []])))
+ meld (is (/.Mixin Nat (State Nat Nat))
+ (function (_ delegate again input)
+ (function (_ state)
+ [state (n.+ state input)])))
+ function (/.fixed (/.mixed (/.after state.monad implant)
+ meld))]
+ (n.= (n.+ dummy input)
+ (|> input function (state.result dummy) product.right))))
))
(_.for [/.Recursive]
- (_.cover [/.of_recursive]
- (let [factorial (/.fixed
- (/.of_recursive
- (function (_ again input)
- (case input
- (^.or 0 1) 1
- _ (n.* input (again (-- input)))))))]
- (n.= expected
- (factorial input)))))
+ (_.coverage [/.of_recursive]
+ (let [factorial (/.fixed
+ (/.of_recursive
+ (function (_ again input)
+ (case input
+ (^.or 0 1) 1
+ _ (n.* input (again (-- input)))))))]
+ (n.= expected
+ (factorial input)))))
)))
diff --git a/stdlib/source/test/lux/control/function/mutual.lux b/stdlib/source/test/lux/control/function/mutual.lux
index 161cb954b..1b5c38f78 100644
--- a/stdlib/source/test/lux/control/function/mutual.lux
+++ b/stdlib/source/test/lux/control/function/mutual.lux
@@ -20,7 +20,7 @@
(do [! random.monad]
[sample (# ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
- (<| (_.cover [/.let])
+ (<| (_.coverage [/.let])
(/.let [(even? number)
(-> Nat Bit)
(case number
@@ -53,7 +53,7 @@
(do [! random.monad]
[sample (# ! each (n.% 10) random.nat)
.let [expected (n.even? sample)]]
- (<| (_.cover [/.def:])
+ (<| (_.coverage [/.def:])
(and (bit#= expected (..even? sample))
(bit#= (not expected) (..odd? sample))))))