aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux.lux')
-rw-r--r--stdlib/source/test/lux.lux1364
1 files changed, 682 insertions, 682 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux
index e0798b844..0dc505bb0 100644
--- a/stdlib/source/test/lux.lux
+++ b/stdlib/source/test/lux.lux
@@ -77,91 +77,91 @@
[expected random.nat
dummy random.nat]
(_.for [/.Bit /.if]
- ($_ _.and
- (_.cover [/.false]
- (n.= expected
- (/.if /.false
- dummy
- expected)))
- (_.cover [/.true]
- (n.= expected
- (/.if /.true
- expected
- dummy)))
- (_.cover [/.or]
- (and (not (/.or /.false /.false))
- (/.or /.false /.true)
- (/.or /.true /.false)
- (/.or /.true /.true)))
- (_.cover [/.and]
- (and (not (/.and /.false /.false))
- (not (/.and /.false /.true))
- (not (/.and /.true /.false))
- (/.and /.true /.true)))
- (_.cover [/.not]
- (and (bit#= /.true (/.not /.false))
- (bit#= /.false (/.not /.true))))
- (_.cover [/.cond]
- (and (n.= expected
- (/.cond /.true
- expected
-
- ... else
- dummy))
- (n.= expected
- (/.cond /.false
- dummy
-
- ... else
- expected))
- (n.= expected
- (/.cond /.true
- expected
-
- /.false
- dummy
-
- ... else
- dummy))
- (n.= expected
- (/.cond /.false
- dummy
-
- /.true
- expected
-
- ... else
- dummy))))
- ))))
+ (all _.and
+ (_.cover [/.false]
+ (n.= expected
+ (/.if /.false
+ dummy
+ expected)))
+ (_.cover [/.true]
+ (n.= expected
+ (/.if /.true
+ expected
+ dummy)))
+ (_.cover [/.or]
+ (and (not (/.or /.false /.false))
+ (/.or /.false /.true)
+ (/.or /.true /.false)
+ (/.or /.true /.true)))
+ (_.cover [/.and]
+ (and (not (/.and /.false /.false))
+ (not (/.and /.false /.true))
+ (not (/.and /.true /.false))
+ (/.and /.true /.true)))
+ (_.cover [/.not]
+ (and (bit#= /.true (/.not /.false))
+ (bit#= /.false (/.not /.true))))
+ (_.cover [/.cond]
+ (and (n.= expected
+ (/.cond /.true
+ expected
+
+ ... else
+ dummy))
+ (n.= expected
+ (/.cond /.false
+ dummy
+
+ ... else
+ expected))
+ (n.= expected
+ (/.cond /.true
+ expected
+
+ /.false
+ dummy
+
+ ... else
+ dummy))
+ (n.= expected
+ (/.cond /.false
+ dummy
+
+ /.true
+ expected
+
+ ... else
+ dummy))))
+ ))))
(def: for_try
Test
(do random.monad
[expected_error (random.ascii/lower 5)
expected random.nat]
- ($_ _.and
- (_.cover [/.try]
- (case (/.try expected)
- {.#Left _}
- false
-
- {.#Right actual}
- (n.= expected actual)))
- (_.cover [/.undefined]
- (case (/.try (/.undefined))
- {.#Left _}
- true
-
- {.#Right _}
- false))
- (_.cover [/.panic!]
- (case (/.try (/.panic! expected_error))
- {.#Left actual_error}
- (text.contains? expected_error actual_error)
-
- {.#Right _}
- false))
- )))
+ (all _.and
+ (_.cover [/.try]
+ (case (/.try expected)
+ {.#Left _}
+ false
+
+ {.#Right actual}
+ (n.= expected actual)))
+ (_.cover [/.undefined]
+ (case (/.try (/.undefined))
+ {.#Left _}
+ true
+
+ {.#Right _}
+ false))
+ (_.cover [/.panic!]
+ (case (/.try (/.panic! expected_error))
+ {.#Left actual_error}
+ (text.contains? expected_error actual_error)
+
+ {.#Right _}
+ false))
+ )))
(def: for_list
Test
@@ -170,26 +170,26 @@
e/1 random.nat
e/2 random.nat
e/3 random.nat]
- ($_ _.and
- (_.cover [/.list]
- (case (/.list e/0 e/1)
- (pattern (/.list a/0 a/1))
- (and (n.= e/0 a/0)
- (n.= e/1 a/1))
-
- _
- false))
- (_.cover [/.partial_list]
- (case (/.partial_list e/0 e/1 (/.list e/2 e/3))
- (pattern (/.partial_list a/0 a/1 (/.list a/2 a/3)))
- (and (n.= e/0 a/0)
- (n.= e/1 a/1)
- (n.= e/2 a/2)
- (n.= e/3 a/3))
-
- _
- false))
- )))
+ (all _.and
+ (_.cover [/.list]
+ (case (/.list e/0 e/1)
+ (pattern (/.list a/0 a/1))
+ (and (n.= e/0 a/0)
+ (n.= e/1 a/1))
+
+ _
+ false))
+ (_.cover [/.partial_list]
+ (case (/.partial_list e/0 e/1 (/.list e/2 e/3))
+ (pattern (/.partial_list a/0 a/1 (/.list a/2 a/3)))
+ (and (n.= e/0 a/0)
+ (n.= e/1 a/1)
+ (n.= e/2 a/2)
+ (n.= e/3 a/3))
+
+ _
+ false))
+ )))
(type: (Returner a)
(/.Interface
@@ -215,32 +215,32 @@
(def: (return _)
expected)))]]
(_.for [/.Interface]
- ($_ _.and
- (_.cover [/.implementation:]
- (n.= expected (# (global_returner expected) return [])))
- (_.cover [/.implementation]
- (n.= expected (# local_returner return [])))
- (_.cover [/.open:]
- (n.= static_return (global#return [])))
- (_.cover [/.open]
- (let [(/.open "local#[0]") local_returner]
- (n.= expected (local#return []))))
- (_.cover [/.#]
- (n.= expected (/.# local_returner return [])))
- ))))
+ (all _.and
+ (_.cover [/.implementation:]
+ (n.= expected (# (global_returner expected) return [])))
+ (_.cover [/.implementation]
+ (n.= expected (# local_returner return [])))
+ (_.cover [/.open:]
+ (n.= static_return (global#return [])))
+ (_.cover [/.open]
+ (let [(/.open "local#[0]") local_returner]
+ (n.= expected (local#return []))))
+ (_.cover [/.#]
+ (n.= expected (/.# local_returner return [])))
+ ))))
(def: for_module
Test
- ($_ _.and
- (let [[module short] (/.symbol .example)]
- (_.cover [/.symbol /.prelude_module]
- (and (text#= /.prelude_module module)
- (text#= short "example"))))
- (let [[module short] (/.symbol ..example)]
- (_.cover [/.module_separator]
- (and (text.contains? /.module_separator module)
- (not (text.contains? /.module_separator short)))))
- ))
+ (all _.and
+ (let [[module short] (/.symbol .example)]
+ (_.cover [/.symbol /.prelude_module]
+ (and (text#= /.prelude_module module)
+ (text#= short "example"))))
+ (let [[module short] (/.symbol ..example)]
+ (_.cover [/.module_separator]
+ (and (text.contains? /.module_separator module)
+ (not (text.contains? /.module_separator short)))))
+ ))
(def: for_pipe
Test
@@ -248,20 +248,20 @@
[start random.nat
factor random.nat
.let [expected (n.* factor (++ start))]]
- ($_ _.and
- (_.cover [/.|>]
- (n.= expected
- (/.|> start ++ (n.* factor))))
- (_.cover [/.|>>]
- (n.= expected
- ((/.|>> ++ (n.* factor)) start)))
- (_.cover [/.<|]
- (n.= expected
- (/.<| (n.* factor) ++ start)))
- (_.cover [/.<<|]
- (n.= expected
- ((/.<<| (n.* factor) ++) start)))
- )))
+ (all _.and
+ (_.cover [/.|>]
+ (n.= expected
+ (/.|> start ++ (n.* factor))))
+ (_.cover [/.|>>]
+ (n.= expected
+ ((/.|>> ++ (n.* factor)) start)))
+ (_.cover [/.<|]
+ (n.= expected
+ (/.<| (n.* factor) ++ start)))
+ (_.cover [/.<<|]
+ (n.= expected
+ ((/.<<| (n.* factor) ++) start)))
+ )))
(def: example_symbol "YOLO")
(def: i8 8)
@@ -363,18 +363,18 @@
Test
(do [! random.monad]
[example (# ! each code.nat random.nat)]
- ($_ _.and
- (_.for [/.Code /.Code']
- ($_ _.and
- ..for_code/'
- ..for_code/`
- ..for_code/`'
- ))
- (_.cover [/.Ann]
- (|> example
- (the /.#meta)
- (location#= location.dummy)))
- )))
+ (all _.and
+ (_.for [/.Code /.Code']
+ (all _.and
+ ..for_code/'
+ ..for_code/`
+ ..for_code/`'
+ ))
+ (_.cover [/.Ann]
+ (|> example
+ (the /.#meta)
+ (location#= location.dummy)))
+ )))
(/.macro: (identity_macro tokens)
(# meta.monad in tokens))
@@ -409,132 +409,132 @@
{.#Right [lux (list)]}))]
(do random.monad
[expected random.nat]
- (`` (`` ($_ _.and
- (_.cover [/.Macro']
- (|> macro
- (is /.Macro')
- (same? macro)))
- (_.cover [/.Macro]
- (|> macro
- "lux macro"
- (is /.Macro)
- (is Any)
- (same? (is Any macro))))
- (_.cover [/.macro:]
- (same? expected (..identity_macro expected)))
- (~~ (for @.old (~~ (these))
- (_.cover [/.Source]
- (..found_crosshair?))))
- (_.cover [/.macro]
- (with_expansions [n/0 (static.random_nat)
- n/1 (static.random_nat)
- n/1 (static.random_nat)]
- (n.= (..sum n/0 n/1 n/1)
- (..sum' n/0 n/1 n/1))))
- (_.cover [/.using]
- (`` (with_expansions [<referral> ("lux in-module" "library/lux" library/lux.refer)
- <alias> (static.random code.text (random.ascii/lower 1))
- <definition> (static.random code.local (random.ascii/lower 1))
- <module/0> (static.random code.text (random.ascii/lower 2))
- <module/0>' (template.symbol [<module/0>])
- <module/1> (static.random code.text (random.ascii/lower 3))
- <module/1>' (template.symbol [<module/1>])
- <module/2> (static.random code.text (random.ascii/lower 4))
- <module/2>' (template.symbol [<module/2>])
- <m0/1> (template.text [<module/0> "/" <module/1>])
- <//> (template.text [// <module/2>'])
- <//>' (template.symbol [<//>])
- <\\> (template.text [\\ <module/2>'])
- <\\>' (template.symbol [<\\>])
- <m0/2> (template.text [<module/0> "/" <module/2>])
- <m2/1> (template.text [<module/2> "/" <module/1>])
- <m0/1/2> (template.text [<module/0> "/" <module/1> "/" <module/2>])
- <open/0> (template.text [<module/0> "#[0]"])]
- (and (~~ (template [<input> <module> <referrals>]
- [(with_expansions [<input>' (macro.final <input>)]
- (let [scenario (is (-> Any Bit)
- (function (_ _)
- ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter.
- (`` (for @.python (case (' [<input>'])
- (^.` [<module>
- ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0)
- (~~ (template.spliced <referrals>))])
- true
-
- _
- false)
- (case (' [<input>'])
- (^.` [<module> (~~ (template.spliced <referrals>))])
- true
-
- _
- false)))))]
- (scenario [])))]
-
- [(.using [<module/0>'])
- ("lux def module" [])
- []]
-
- [(.using [<alias> <module/0>' "*"])
- ("lux def module" [[<module/0> <alias>]])
- [(<referral> <module/0> "*")]]
-
- [(.using [<alias> <module/0>' {"+" <definition>}])
- ("lux def module" [[<module/0> <alias>]])
- [(<referral> <module/0> {"+" <definition>})]]
-
- [(.using [<alias> <module/0>' {"-" <definition>}])
- ("lux def module" [[<module/0> <alias>]])
- [(<referral> <module/0> {"-" <definition>})]]
-
- [(.using [<alias> <module/0>' "_"])
- ("lux def module" [])
- []]
-
- [(.using [<module/0>'
- [<alias> <module/1>']])
- ("lux def module" [[<m0/1> <alias>]])
- [(<referral> <m0/1>)]]
-
- [(.using ["[0]" <module/0>'
- ["[0]" <module/1>']])
- ("lux def module" [[<module/0> <module/0>]
- [<m0/1> <module/1>]])
- [(<referral> <module/0>)
- (<referral> <m0/1>)]]
-
- [(.using ["[0]" <module/0>' "_"
- ["[1]" <module/1>']])
- ("lux def module" [[<m0/1> <module/0>]])
- [(<referral> <m0/1>)]]
-
- [(.using ["[0]" <module/0>' "_"
- ["[1]" <module/1>' "_"
- ["[2]" <module/2>']]])
- ("lux def module" [[<m0/1/2> <module/0>]])
- [(<referral> <m0/1/2>)]]
-
- [(.using [<module/0>'
- ["[0]" <module/1>'
- ["[0]" <//>']]])
- ("lux def module" [[<m0/1> <module/1>]
- [<m0/2> <//>]])
- [(<referral> <m0/1>)
- (<referral> <m0/2>)]]
-
- [(.using ["[0]" <module/0>'
- [<module/1>'
- ["[0]" <\\>']]])
- ("lux def module" [[<module/0> <module/0>]
- [<m2/1> <\\>]])
- [(<referral> <module/0>)
- (<referral> <m2/1>)]]
-
- [(.using ["[0]" <module/0>' ("[1]#[0]" <definition>)])
- ("lux def module" [[<module/0> <module/0>]])
- [(<referral> <module/0> (<open/0> <definition>))]]
- ))))))
- ))))))
+ (`` (`` (all _.and
+ (_.cover [/.Macro']
+ (|> macro
+ (is /.Macro')
+ (same? macro)))
+ (_.cover [/.Macro]
+ (|> macro
+ "lux macro"
+ (is /.Macro)
+ (is Any)
+ (same? (is Any macro))))
+ (_.cover [/.macro:]
+ (same? expected (..identity_macro expected)))
+ (~~ (for @.old (~~ (these))
+ (_.cover [/.Source]
+ (..found_crosshair?))))
+ (_.cover [/.macro]
+ (with_expansions [n/0 (static.random_nat)
+ n/1 (static.random_nat)
+ n/1 (static.random_nat)]
+ (n.= (..sum n/0 n/1 n/1)
+ (..sum' n/0 n/1 n/1))))
+ (_.cover [/.using]
+ (`` (with_expansions [<referral> ("lux in-module" "library/lux" library/lux.refer)
+ <alias> (static.random code.text (random.ascii/lower 1))
+ <definition> (static.random code.local (random.ascii/lower 1))
+ <module/0> (static.random code.text (random.ascii/lower 2))
+ <module/0>' (template.symbol [<module/0>])
+ <module/1> (static.random code.text (random.ascii/lower 3))
+ <module/1>' (template.symbol [<module/1>])
+ <module/2> (static.random code.text (random.ascii/lower 4))
+ <module/2>' (template.symbol [<module/2>])
+ <m0/1> (template.text [<module/0> "/" <module/1>])
+ <//> (template.text [// <module/2>'])
+ <//>' (template.symbol [<//>])
+ <\\> (template.text [\\ <module/2>'])
+ <\\>' (template.symbol [<\\>])
+ <m0/2> (template.text [<module/0> "/" <module/2>])
+ <m2/1> (template.text [<module/2> "/" <module/1>])
+ <m0/1/2> (template.text [<module/0> "/" <module/1> "/" <module/2>])
+ <open/0> (template.text [<module/0> "#[0]"])]
+ (and (~~ (template [<input> <module> <referrals>]
+ [(with_expansions [<input>' (macro.final <input>)]
+ (let [scenario (is (-> Any Bit)
+ (function (_ _)
+ ... TODO: Remove this hack once Jython is no longer being used as the Python interpreter.
+ (`` (for @.python (case (' [<input>'])
+ (^.` [<module>
+ ("lux def" (~ [_ {.#Symbol ["" _]}]) [] #0)
+ (~~ (template.spliced <referrals>))])
+ true
+
+ _
+ false)
+ (case (' [<input>'])
+ (^.` [<module> (~~ (template.spliced <referrals>))])
+ true
+
+ _
+ false)))))]
+ (scenario [])))]
+
+ [(.using [<module/0>'])
+ ("lux def module" [])
+ []]
+
+ [(.using [<alias> <module/0>' "*"])
+ ("lux def module" [[<module/0> <alias>]])
+ [(<referral> <module/0> "*")]]
+
+ [(.using [<alias> <module/0>' {"+" <definition>}])
+ ("lux def module" [[<module/0> <alias>]])
+ [(<referral> <module/0> {"+" <definition>})]]
+
+ [(.using [<alias> <module/0>' {"-" <definition>}])
+ ("lux def module" [[<module/0> <alias>]])
+ [(<referral> <module/0> {"-" <definition>})]]
+
+ [(.using [<alias> <module/0>' "_"])
+ ("lux def module" [])
+ []]
+
+ [(.using [<module/0>'
+ [<alias> <module/1>']])
+ ("lux def module" [[<m0/1> <alias>]])
+ [(<referral> <m0/1>)]]
+
+ [(.using ["[0]" <module/0>'
+ ["[0]" <module/1>']])
+ ("lux def module" [[<module/0> <module/0>]
+ [<m0/1> <module/1>]])
+ [(<referral> <module/0>)
+ (<referral> <m0/1>)]]
+
+ [(.using ["[0]" <module/0>' "_"
+ ["[1]" <module/1>']])
+ ("lux def module" [[<m0/1> <module/0>]])
+ [(<referral> <m0/1>)]]
+
+ [(.using ["[0]" <module/0>' "_"
+ ["[1]" <module/1>' "_"
+ ["[2]" <module/2>']]])
+ ("lux def module" [[<m0/1/2> <module/0>]])
+ [(<referral> <m0/1/2>)]]
+
+ [(.using [<module/0>'
+ ["[0]" <module/1>'
+ ["[0]" <//>']]])
+ ("lux def module" [[<m0/1> <module/1>]
+ [<m0/2> <//>]])
+ [(<referral> <m0/1>)
+ (<referral> <m0/2>)]]
+
+ [(.using ["[0]" <module/0>'
+ [<module/1>'
+ ["[0]" <\\>']]])
+ ("lux def module" [[<module/0> <module/0>]
+ [<m2/1> <\\>]])
+ [(<referral> <module/0>)
+ (<referral> <m2/1>)]]
+
+ [(.using ["[0]" <module/0>' ("[1]#[0]" <definition>)])
+ ("lux def module" [[<module/0> <module/0>]])
+ [(<referral> <module/0> (<open/0> <definition>))]]
+ ))))))
+ ))))))
(/.type: for_type/variant
(Variant
@@ -562,104 +562,104 @@
expected/0 existential_type
expected/1 existential_type]
(<| (_.for [/.Type])
- ($_ _.and
- (_.cover [/.is]
- (|> expected
- (/.is Any)
- (same? (/.is Any expected))))
- (_.cover [/.as]
- (|> expected
- (/.is Any)
- (/.as /.Nat)
- (same? expected)))
- (_.cover [/.as_expected]
- (|> expected
- (/.is Any)
- /.as_expected
- (/.is /.Nat)
- (same? expected)))
- (_.cover [/.type_of]
- (same? /.Nat (/.type_of expected)))
- (_.cover [/.Primitive]
- (case (/.Primitive "foo" [expected/0 expected/1])
- (pattern {.#Primitive "foo" (list actual/0 actual/1)})
- (and (same? expected/0 actual/0)
- (same? expected/1 actual/1))
-
- _
- false))
- (_.cover [/.type]
- (and (case (/.type [expected/0 expected/1])
- {.#Product actual/0 actual/1}
- (and (same? expected/0 actual/0)
- (same? expected/1 actual/1))
-
- _
- false)
- (case (/.type (/.Or expected/0 expected/1))
- {.#Sum actual/0 actual/1}
- (and (same? expected/0 actual/0)
- (same? expected/1 actual/1))
-
- _
- false)
- (case (/.type (-> expected/0 expected/1))
- {.#Function actual/0 actual/1}
- (and (same? expected/0 actual/0)
- (same? expected/1 actual/1))
-
- _
- false)
- (case (/.type (expected/0 expected/1))
- {.#Apply actual/1 actual/0}
- (and (same? expected/0 actual/0)
- (same? expected/1 actual/1))
-
- _
- false)))
- (_.cover [/.type:]
- (exec
- (is /.Type ..for_type/variant)
- (is /.Type ..for_type/record)
- (is /.Type ..for_type/all)
- true))
- (_.cover [/.Variant]
- (exec
- (is for_type/variant
- {#Case/1 expected_left})
- true))
- (_.cover [/.Record]
- (exec
- (is for_type/record
- [#slot/0 (n.= expected_left expected_right)
- #slot/1 (.rev expected_right)])
- true))
- ))))
+ (all _.and
+ (_.cover [/.is]
+ (|> expected
+ (/.is Any)
+ (same? (/.is Any expected))))
+ (_.cover [/.as]
+ (|> expected
+ (/.is Any)
+ (/.as /.Nat)
+ (same? expected)))
+ (_.cover [/.as_expected]
+ (|> expected
+ (/.is Any)
+ /.as_expected
+ (/.is /.Nat)
+ (same? expected)))
+ (_.cover [/.type_of]
+ (same? /.Nat (/.type_of expected)))
+ (_.cover [/.Primitive]
+ (case (/.Primitive "foo" [expected/0 expected/1])
+ (pattern {.#Primitive "foo" (list actual/0 actual/1)})
+ (and (same? expected/0 actual/0)
+ (same? expected/1 actual/1))
+
+ _
+ false))
+ (_.cover [/.type]
+ (and (case (/.type [expected/0 expected/1])
+ {.#Product actual/0 actual/1}
+ (and (same? expected/0 actual/0)
+ (same? expected/1 actual/1))
+
+ _
+ false)
+ (case (/.type (/.Or expected/0 expected/1))
+ {.#Sum actual/0 actual/1}
+ (and (same? expected/0 actual/0)
+ (same? expected/1 actual/1))
+
+ _
+ false)
+ (case (/.type (-> expected/0 expected/1))
+ {.#Function actual/0 actual/1}
+ (and (same? expected/0 actual/0)
+ (same? expected/1 actual/1))
+
+ _
+ false)
+ (case (/.type (expected/0 expected/1))
+ {.#Apply actual/1 actual/0}
+ (and (same? expected/0 actual/0)
+ (same? expected/1 actual/1))
+
+ _
+ false)))
+ (_.cover [/.type:]
+ (exec
+ (is /.Type ..for_type/variant)
+ (is /.Type ..for_type/record)
+ (is /.Type ..for_type/all)
+ true))
+ (_.cover [/.Variant]
+ (exec
+ (is for_type/variant
+ {#Case/1 expected_left})
+ true))
+ (_.cover [/.Record]
+ (exec
+ (is for_type/record
+ [#slot/0 (n.= expected_left expected_right)
+ #slot/1 (.rev expected_right)])
+ true))
+ ))))
(def: for_i64
Test
(do random.monad
[expected random.i64]
- ($_ _.and
- (_.cover [/.i64]
- (same? (is Any expected)
- (is Any (/.i64 expected))))
- (_.cover [/.nat]
- (same? (is Any expected)
- (is Any (/.nat expected))))
- (_.cover [/.int]
- (same? (is Any expected)
- (is Any (/.int expected))))
- (_.cover [/.rev]
- (same? (is Any expected)
- (is Any (/.rev expected))))
- (_.cover [/.++]
- (n.= 1 (n.- expected
- (/.++ expected))))
- (_.cover [/.--]
- (n.= 1 (n.- (/.-- expected)
- expected)))
- )))
+ (all _.and
+ (_.cover [/.i64]
+ (same? (is Any expected)
+ (is Any (/.i64 expected))))
+ (_.cover [/.nat]
+ (same? (is Any expected)
+ (is Any (/.nat expected))))
+ (_.cover [/.int]
+ (same? (is Any expected)
+ (is Any (/.int expected))))
+ (_.cover [/.rev]
+ (same? (is Any expected)
+ (is Any (/.rev expected))))
+ (_.cover [/.++]
+ (n.= 1 (n.- expected
+ (/.++ expected))))
+ (_.cover [/.--]
+ (n.= 1 (n.- (/.-- expected)
+ expected)))
+ )))
(def: for_function
Test
@@ -683,22 +683,22 @@
(def: for_template
Test
- (`` ($_ _.and
- (_.cover [/.template]
- (let [bits (list (~~ (/.template [_]
- [true]
-
- [0] [1] [2]
- )))]
- (and (n.= 3 (list.size bits))
- (list.every? (bit#= true) bits))))
- (do random.monad
- [left random.nat
- right random.nat]
- (_.cover [/.template:]
- (n.= (n.+ left right)
- (!n/+ left right))))
- )))
+ (`` (all _.and
+ (_.cover [/.template]
+ (let [bits (list (~~ (/.template [_]
+ [true]
+
+ [0] [1] [2]
+ )))]
+ (and (n.= 3 (list.size bits))
+ (list.every? (bit#= true) bits))))
+ (do random.monad
+ [left random.nat
+ right random.nat]
+ (_.cover [/.template:]
+ (n.= (n.+ left right)
+ (!n/+ left right))))
+ )))
(def: option/0 "0")
(def: option/1 "1")
@@ -709,17 +709,17 @@
(do random.monad
[sample (random.either (in option/0)
(in option/1))]
- ($_ _.and
- (_.cover [/.static]
- (case sample
- (pattern (/.static option/0)) true
- (pattern (/.static option/1)) true
- _ false))
- (_.cover [/.char]
- (|> (`` (/.char (~~ (/.static static_char))))
- text.of_char
- (text#= static_char)))
- )))
+ (all _.and
+ (_.cover [/.static]
+ (case sample
+ (pattern (/.static option/0)) true
+ (pattern (/.static option/1)) true
+ _ false))
+ (_.cover [/.char]
+ (|> (`` (/.char (~~ (/.static static_char))))
+ text.of_char
+ (text#= static_char)))
+ )))
(type: Small
(Record
@@ -745,75 +745,75 @@
sample [#big_left start/b
#big_right [#small_left start/s
#small_right text]]]]
- ($_ _.and
- (_.cover [/.the]
- (and (and (|> sample
- (/.the #big_left)
- (same? start/b))
- (|> sample
- ((/.the #big_left))
- (same? start/b)))
- (and (|> sample
- (/.the [#big_right #small_left])
- (same? start/s))
- (|> sample
- ((/.the [#big_right #small_left]))
- (same? start/s)))))
- (_.cover [/.has]
- (and (and (|> sample
- (/.has #big_left shift/b)
- (/.the #big_left)
- (same? shift/b))
- (|> sample
- ((/.has #big_left shift/b))
- (/.the #big_left)
- (same? shift/b))
- (|> sample
- ((/.has #big_left) shift/b)
- (/.the #big_left)
- (same? shift/b)))
- (and (|> sample
- (/.has [#big_right #small_left] shift/s)
- (/.the [#big_right #small_left])
- (same? shift/s))
- (|> sample
- ((/.has [#big_right #small_left] shift/s))
- (/.the [#big_right #small_left])
- (same? shift/s))
- (|> sample
- ((/.has [#big_right #small_left]) shift/s)
- (/.the [#big_right #small_left])
- (same? shift/s)))))
- (_.cover [/.revised]
- (and (and (|> sample
- (/.revised #big_left (n.+ shift/b))
- (/.the #big_left)
- (n.= expected/b))
- (|> sample
- ((/.revised #big_left (n.+ shift/b)))
- (/.the #big_left)
- (n.= expected/b))
- (|> sample
- ((is (-> (-> Nat Nat) (-> Big Big))
- (/.revised #big_left))
- (n.+ shift/b))
- (/.the #big_left)
- (n.= expected/b)))
- (and (|> sample
- (/.revised [#big_right #small_left] (n.+ shift/s))
- (/.the [#big_right #small_left])
- (n.= expected/s))
- (|> sample
- ((/.revised [#big_right #small_left] (n.+ shift/s)))
- (/.the [#big_right #small_left])
- (n.= expected/s))
- (|> sample
- ((is (-> (-> Nat Nat) (-> Big Big))
- (/.revised [#big_right #small_left]))
- (n.+ shift/s))
- (/.the [#big_right #small_left])
- (n.= expected/s)))))
- )))
+ (all _.and
+ (_.cover [/.the]
+ (and (and (|> sample
+ (/.the #big_left)
+ (same? start/b))
+ (|> sample
+ ((/.the #big_left))
+ (same? start/b)))
+ (and (|> sample
+ (/.the [#big_right #small_left])
+ (same? start/s))
+ (|> sample
+ ((/.the [#big_right #small_left]))
+ (same? start/s)))))
+ (_.cover [/.has]
+ (and (and (|> sample
+ (/.has #big_left shift/b)
+ (/.the #big_left)
+ (same? shift/b))
+ (|> sample
+ ((/.has #big_left shift/b))
+ (/.the #big_left)
+ (same? shift/b))
+ (|> sample
+ ((/.has #big_left) shift/b)
+ (/.the #big_left)
+ (same? shift/b)))
+ (and (|> sample
+ (/.has [#big_right #small_left] shift/s)
+ (/.the [#big_right #small_left])
+ (same? shift/s))
+ (|> sample
+ ((/.has [#big_right #small_left] shift/s))
+ (/.the [#big_right #small_left])
+ (same? shift/s))
+ (|> sample
+ ((/.has [#big_right #small_left]) shift/s)
+ (/.the [#big_right #small_left])
+ (same? shift/s)))))
+ (_.cover [/.revised]
+ (and (and (|> sample
+ (/.revised #big_left (n.+ shift/b))
+ (/.the #big_left)
+ (n.= expected/b))
+ (|> sample
+ ((/.revised #big_left (n.+ shift/b)))
+ (/.the #big_left)
+ (n.= expected/b))
+ (|> sample
+ ((is (-> (-> Nat Nat) (-> Big Big))
+ (/.revised #big_left))
+ (n.+ shift/b))
+ (/.the #big_left)
+ (n.= expected/b)))
+ (and (|> sample
+ (/.revised [#big_right #small_left] (n.+ shift/s))
+ (/.the [#big_right #small_left])
+ (n.= expected/s))
+ (|> sample
+ ((/.revised [#big_right #small_left] (n.+ shift/s)))
+ (/.the [#big_right #small_left])
+ (n.= expected/s))
+ (|> sample
+ ((is (-> (-> Nat Nat) (-> Big Big))
+ (/.revised [#big_right #small_left]))
+ (n.+ shift/s))
+ (/.the [#big_right #small_left])
+ (n.= expected/s)))))
+ )))
(def: for_associative
Test
@@ -822,15 +822,15 @@
mid (random.ascii/lower 1)
right (random.ascii/lower 1)
.let [expected (text.interposed "" (list left mid right))]]
- (_.cover [/.$_ /._$]
- (with_expansions [<left_association> (/._$ format
- left
- mid
- right)
- <right_association> (/.$_ format
- left
- mid
- right)]
+ (_.cover [/.all /.left]
+ (with_expansions [<left_association> (/.left format
+ left
+ mid
+ right)
+ <right_association> (/.all format
+ left
+ mid
+ right)]
(and (text#= <left_association>
<right_association>)
(not (code#= (' <left_association>)
@@ -843,39 +843,39 @@
right random.nat
dummy random.nat
.let [expected (n.+ left right)]]
- ($_ _.and
- (_.cover [/.these]
- (`` (and (~~ (these true
- true
- true)))))
- (_.cover [/.with_expansions]
- (/.with_expansions [<operands> (these left right)]
- (n.= expected
- (n.+ <operands>))))
- (_.cover [/.comment]
- (/.with_expansions [<dummy> (/.comment dummy)
- <operands> (these left right)]
- (n.= expected
- ($_ n.+ <operands> <dummy>))))
- (_.cover [/.``]
- (n.= expected
- (/.`` ($_ n.+
- (~~ (these left right))
- (~~ (/.comment dummy))))))
- (_.cover [/.for]
- (and (n.= expected
- (/.for "fake host" dummy
- expected))
- (n.= expected
- (/.for @.old expected
- @.jvm expected
- @.js expected
- @.python expected
- @.lua expected
- @.ruby expected
- @.php expected
- dummy))))
- )))
+ (all _.and
+ (_.cover [/.these]
+ (`` (and (~~ (these true
+ true
+ true)))))
+ (_.cover [/.with_expansions]
+ (/.with_expansions [<operands> (these left right)]
+ (n.= expected
+ (n.+ <operands>))))
+ (_.cover [/.comment]
+ (/.with_expansions [<dummy> (/.comment dummy)
+ <operands> (these left right)]
+ (n.= expected
+ (all n.+ <operands> <dummy>))))
+ (_.cover [/.``]
+ (n.= expected
+ (/.`` (all n.+
+ (~~ (these left right))
+ (~~ (/.comment dummy))))))
+ (_.cover [/.for]
+ (and (n.= expected
+ (/.for "fake host" dummy
+ expected))
+ (n.= expected
+ (/.for @.old expected
+ @.jvm expected
+ @.js expected
+ @.python expected
+ @.lua expected
+ @.ruby expected
+ @.php expected
+ dummy))))
+ )))
(def: for_value
Test
@@ -886,78 +886,78 @@
item/0 random.nat
item/1 random.nat
item/2 random.nat]
- ($_ _.and
- (_.cover [/.Either]
- (and (exec
- (is (/.Either Nat Text)
- {.#Left left})
- true)
- (exec
- (is (/.Either Nat Text)
- {.#Right right})
- true)))
- (_.cover [/.Any]
- (and (exec
- (is /.Any
- left)
- true)
- (exec
- (is /.Any
- right)
- true)))
- (_.cover [/.Nothing]
- (and (exec
- (is (-> /.Any /.Nothing)
- (function (_ _)
- (undefined)))
- true)
- (exec
- (is (-> /.Any /.Int)
- (function (_ _)
- (is /.Int (undefined))))
- true)))
- (_.for [/.__adjusted_quantified_type__]
- ($_ _.and
- (_.cover [/.All]
- (let [identity (is (/.All (_ a) (-> a a))
- (|>>))]
- (and (exec
- (is Nat
- (identity left))
- true)
- (exec
- (is Text
- (identity right))
- true))))
- (_.cover [/.Ex]
- (let [hide (is (/.Ex (_ a) (-> Nat a))
- (|>>))]
- (exec
- (is /.Any
- (hide left))
- true)))))
- (_.cover [/.same?]
- (let [not_left (atom.atom left)
- left (atom.atom left)]
- (and (/.same? left left)
- (/.same? not_left not_left)
- (not (/.same? left not_left)))))
- (_.cover [/.Rec]
- (let [list (is (/.Rec NList
- (Maybe [Nat NList]))
- {.#Some [item/0
- {.#Some [item/1
- {.#Some [item/2
- {.#None}]}]}]})]
- (case list
- {.#Some [actual/0 {.#Some [actual/1 {.#Some [actual/2 {.#None}]}]}]}
- (and (same? item/0 actual/0)
- (same? item/1 actual/1)
- (same? item/2 actual/2))
-
- _
- false)))
- )))
+ (all _.and
+ (_.cover [/.Either]
+ (and (exec
+ (is (/.Either Nat Text)
+ {.#Left left})
+ true)
+ (exec
+ (is (/.Either Nat Text)
+ {.#Right right})
+ true)))
+ (_.cover [/.Any]
+ (and (exec
+ (is /.Any
+ left)
+ true)
+ (exec
+ (is /.Any
+ right)
+ true)))
+ (_.cover [/.Nothing]
+ (and (exec
+ (is (-> /.Any /.Nothing)
+ (function (_ _)
+ (undefined)))
+ true)
+ (exec
+ (is (-> /.Any /.Int)
+ (function (_ _)
+ (is /.Int (undefined))))
+ true)))
+ (_.for [/.__adjusted_quantified_type__]
+ (all _.and
+ (_.cover [/.All]
+ (let [identity (is (/.All (_ a) (-> a a))
+ (|>>))]
+ (and (exec
+ (is Nat
+ (identity left))
+ true)
+ (exec
+ (is Text
+ (identity right))
+ true))))
+ (_.cover [/.Ex]
+ (let [hide (is (/.Ex (_ a) (-> Nat a))
+ (|>>))]
+ (exec
+ (is /.Any
+ (hide left))
+ true)))))
+ (_.cover [/.same?]
+ (let [not_left (atom.atom left)
+ left (atom.atom left)]
+ (and (/.same? left left)
+ (/.same? not_left not_left)
+ (not (/.same? left not_left)))))
+ (_.cover [/.Rec]
+ (let [list (is (/.Rec NList
+ (Maybe [Nat NList]))
+ {.#Some [item/0
+ {.#Some [item/1
+ {.#Some [item/2
+ {.#None}]}]}]})]
+ (case list
+ {.#Some [actual/0 {.#Some [actual/1 {.#Some [actual/2 {.#None}]}]}]}
+ (and (same? item/0 actual/0)
+ (same? item/1 actual/1)
+ (same? item/2 actual/2))
+
+ _
+ false)))
+ )))
(type: (Pair l r)
(Record
@@ -979,75 +979,75 @@
(in +1.25))
expected_text (random.either (in "+0.5")
(in "+1.25"))]
- ($_ _.and
- (_.cover [/.case]
- (and (/.case expected_nat
- 0 true
- _ false)
- (/.case expected_int
- +0 true
- _ false)
- (/.case expected_rev
- .5 true
- .25 true
- _ false)
- (/.case expected_frac
- +0.5 true
- +1.25 true
- _ false)
- (/.case expected_text
- "+0.5" true
- "+1.25" true
- _ false)
- (/.case [expected_nat expected_int]
- [0 +0] true
- _ false)
- (/.case [..#left expected_nat ..#right expected_int]
- [..#left 0 ..#right +0] true
- _ false)
- (/.case (is (Either Nat Int) {.#Left expected_nat})
- {.#Left 0} true
- _ false)
- (/.case (is (Either Nat Int) {.#Right expected_int})
- {.#Right +0} true
- _ false)
- ))
- (_.cover [/.pattern]
- (/.case [..#left expected_nat ..#right expected_int]
- (/.pattern (!pair 0 +0)) true
- _ false))
- (_.cover [/.let]
- (and (/.let [actual_nat expected_nat]
- (/.same? expected_nat actual_nat))
- (/.let [[actual_left actual_right] [..#left expected_nat ..#right expected_int]]
- (and (/.same? expected_nat actual_left)
- (/.same? expected_int actual_right)))))
- )))
+ (all _.and
+ (_.cover [/.case]
+ (and (/.case expected_nat
+ 0 true
+ _ false)
+ (/.case expected_int
+ +0 true
+ _ false)
+ (/.case expected_rev
+ .5 true
+ .25 true
+ _ false)
+ (/.case expected_frac
+ +0.5 true
+ +1.25 true
+ _ false)
+ (/.case expected_text
+ "+0.5" true
+ "+1.25" true
+ _ false)
+ (/.case [expected_nat expected_int]
+ [0 +0] true
+ _ false)
+ (/.case [..#left expected_nat ..#right expected_int]
+ [..#left 0 ..#right +0] true
+ _ false)
+ (/.case (is (Either Nat Int) {.#Left expected_nat})
+ {.#Left 0} true
+ _ false)
+ (/.case (is (Either Nat Int) {.#Right expected_int})
+ {.#Right +0} true
+ _ false)
+ ))
+ (_.cover [/.pattern]
+ (/.case [..#left expected_nat ..#right expected_int]
+ (/.pattern (!pair 0 +0)) true
+ _ false))
+ (_.cover [/.let]
+ (and (/.let [actual_nat expected_nat]
+ (/.same? expected_nat actual_nat))
+ (/.let [[actual_left actual_right] [..#left expected_nat ..#right expected_int]]
+ (and (/.same? expected_nat actual_left)
+ (/.same? expected_int actual_right)))))
+ )))
(def: for_control_flow
Test
- ($_ _.and
- (do random.monad
- [factor (random#each (|>> (n.% 10) (n.max 1)) random.nat)
- iterations (random#each (n.% 10) random.nat)
- .let [expected (n.* factor iterations)]]
- (_.cover [/.loop]
- (n.= expected
- (/.loop (again [counter 0
- value 0])
- (if (n.< iterations counter)
- (again (++ counter) (n.+ factor value))
- value)))))
- (do random.monad
- [pre random.nat
- post (random.only (|>> (n.= pre) not) random.nat)
- .let [box (atom.atom pre)]]
- (_.cover [/.exec]
- (and (same? pre (io.run! (atom.read! box)))
- (/.exec
- (io.run! (atom.write! post box))
- (same? post (io.run! (atom.read! box)))))))
- ))
+ (all _.and
+ (do random.monad
+ [factor (random#each (|>> (n.% 10) (n.max 1)) random.nat)
+ iterations (random#each (n.% 10) random.nat)
+ .let [expected (n.* factor iterations)]]
+ (_.cover [/.loop]
+ (n.= expected
+ (/.loop (again [counter 0
+ value 0])
+ (if (n.< iterations counter)
+ (again (++ counter) (n.+ factor value))
+ value)))))
+ (do random.monad
+ [pre random.nat
+ post (random.only (|>> (n.= pre) not) random.nat)
+ .let [box (atom.atom pre)]]
+ (_.cover [/.exec]
+ (and (same? pre (io.run! (atom.read! box)))
+ (/.exec
+ (io.run! (atom.write! post box))
+ (same? post (io.run! (atom.read! box)))))))
+ ))
(def: identity/constant
(All (_ a) (-> a a))
@@ -1099,22 +1099,22 @@
(def: for_meta
Test
- ($_ _.and
- (_.cover [/.Mode /.Info]
- (for_meta|Info))
- (_.cover [/.Module_State]
- (for_meta|Module_State))
- ))
+ (all _.and
+ (_.cover [/.Mode /.Info]
+ (for_meta|Info))
+ (_.cover [/.Module_State]
+ (for_meta|Module_State))
+ ))
(def: for_export
Test
- ($_ _.and
- (_.cover [/.public /.private]
- (and /.public (not /.private)))
- (_.cover [/.global /.local]
- (and (bit#= /.public /.global)
- (bit#= /.private /.local)))
- ))
+ (all _.and
+ (_.cover [/.public /.private]
+ (and /.public (not /.private)))
+ (_.cover [/.global /.local]
+ (and (bit#= /.public /.global)
+ (bit#= /.private /.local)))
+ ))
(for @.old (these)
(these (syntax: (for_bindings|test [fn/0 <code>.local
@@ -1198,32 +1198,32 @@
(def: test|lux
Test
- (`` (`` ($_ _.and
- ..for_bit
- ..for_try
- ..for_list
- ..for_interface
- ..for_module
- ..for_pipe
- ..for_code
- ..for_macro
- ..for_type
- ..for_i64
- ..for_function
- ..for_template
- ..for_static
- ..for_slot
- ..for_associative
- ..for_expansion
- ..for_value
- ..for_case
- ..for_control_flow
- ..for_def:
- ..for_meta
- ..for_export
- (~~ (for @.old (~~ (these))
- (~~ (these ..for_bindings))))
- ))))
+ (`` (`` (all _.and
+ ..for_bit
+ ..for_try
+ ..for_list
+ ..for_interface
+ ..for_module
+ ..for_pipe
+ ..for_code
+ ..for_macro
+ ..for_type
+ ..for_i64
+ ..for_function
+ ..for_template
+ ..for_static
+ ..for_slot
+ ..for_associative
+ ..for_expansion
+ ..for_value
+ ..for_case
+ ..for_control_flow
+ ..for_def:
+ ..for_meta
+ ..for_export
+ (~~ (for @.old (~~ (these))
+ (~~ (these ..for_bindings))))
+ ))))
(def: test
Test