diff options
Diffstat (limited to '')
298 files changed, 16371 insertions, 16371 deletions
diff --git a/stdlib/source/documentation/lux/test.lux b/stdlib/source/documentation/lux/test.lux index 295003e1d..ade8f549f 100644 --- a/stdlib/source/documentation/lux/test.lux +++ b/stdlib/source/documentation/lux/test.lux @@ -41,9 +41,9 @@ "Check that a condition is #1, and fail with the given message otherwise." [(assertion message condition)]) -(documentation: /.test +(documentation: /.property "Check that a condition is #1, and fail with the given message otherwise." - [(test message condition)]) + [(property message condition)]) (documentation: /.lifted "" @@ -68,19 +68,19 @@ \n "WARNING: This procedure is only meant to be used in (program: ...) forms.") [(run! test)]) -(documentation: /.cover' +(documentation: /.coverage' (format "Specifies a test as covering one or more definitions." \n "Adds to the test tally information to track which definitions have been tested.") - [(cover' [definition/0 definition/1 ,,, definition/N] - (is Bit - (some "computation")))]) + [(coverage' [definition/0 definition/1 ,,, definition/N] + (is Bit + (some "computation")))]) -(documentation: /.cover +(documentation: /.coverage (format "Specifies a test as covering one or more definitions." \n "Adds to the test tally information to track which definitions have been tested.") - [(cover [definition/0 definition/1 ,,, definition/N] - (is Bit - (some "computation")))]) + [(coverage [definition/0 definition/1 ,,, definition/N] + (is Bit + (some "computation")))]) (documentation: /.for (format "Specifies a context for tests as covering one or more definitions." @@ -112,14 +112,14 @@ ..context ..failure ..assertion - ..test + ..property ..lifted ..Seed ..seed ..times ..run! - ..cover' - ..cover + ..coverage' + ..coverage ..for ..covering ..in_parallel diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux index 9a42e0735..ac03309eb 100644 --- a/stdlib/source/library/lux/test.lux +++ b/stdlib/source/library/lux/test.lux @@ -133,7 +133,7 @@ [..success_tally (format ..success_prefix message)] [..failure_tally (format ..failure_prefix message)]))) -(def: .public (test message condition) +(def: .public (property message condition) (-> Text Bit Test) (random#in (..assertion (%.text message) condition))) @@ -272,7 +272,7 @@ (%.Format Symbol) (|>> %.symbol (format ..clean_up_marker))) -(def: (|cover'| coverage condition) +(def: (|coverage'| coverage condition) (-> (List Symbol) Bit Assertion) (let [message (|> coverage (list#each ..coverage_format) @@ -283,9 +283,9 @@ [(revised #actual_coverage (set.union coverage) tally) documentation]))))) -(def: (|cover| coverage condition) +(def: (|coverage| coverage condition) (-> (List Symbol) Bit Test) - (|> (..|cover'| coverage condition) + (|> (..|coverage'| coverage condition) random#in)) (def: (|for| coverage test) @@ -321,7 +321,7 @@ _ (format aggregate ..coverage_separator short))) "")) -(def: (coverage module encoding) +(def: (coverage_definitions module encoding) (-> Text Text (Set Symbol)) (loop (again [remaining encoding output (set.of_list symbol.hash (list))]) @@ -343,8 +343,8 @@ (.list (~+ coverage))) (~ condition)))))))] - [cover' ..|cover'|] - [cover ..|cover|] + [coverage' ..|coverage'|] + [coverage ..|coverage|] ) (syntax: .public (for [coverage (<code>.tuple (<>.many <code>.any)) @@ -359,7 +359,7 @@ (def: (covering' module coverage test) (-> Text Text Test Test) - (let [coverage (..coverage module coverage)] + (let [coverage (..coverage_definitions module coverage)] (|> (..context' module test) (random#each (async#each (function (_ [tally documentation]) [(revised #expected_coverage (set.union coverage) tally) diff --git a/stdlib/source/specification/aedifex/repository.lux b/stdlib/source/specification/aedifex/repository.lux index 3d4fdd69e..699a6cc52 100644 --- a/stdlib/source/specification/aedifex/repository.lux +++ b/stdlib/source/specification/aedifex/repository.lux @@ -36,22 +36,22 @@ .let [bad_uri (/remote.uri (the //artifact.#version invalid_artifact) invalid_artifact //artifact/extension.lux_library)] bad_upload! (# subject upload bad_uri expected) bad_download! (# subject download bad_uri)] - (_.cover' [/.Repository] - (let [successfull_flow! - (case [good_upload! good_download!] - [{try.#Success _} {try.#Success actual}] - (# binary.equivalence = expected actual) + (_.coverage' [/.Repository] + (let [successfull_flow! + (case [good_upload! good_download!] + [{try.#Success _} {try.#Success actual}] + (# binary.equivalence = expected actual) - _ - false) + _ + false) - failed_flow! - (case [bad_upload! bad_download!] - [{try.#Failure _} {try.#Failure _}] - true + failed_flow! + (case [bad_upload! bad_download!] + [{try.#Failure _} {try.#Failure _}] + true - _ - false)] - (and successfull_flow! - failed_flow!)))) + _ + false)] + (and successfull_flow! + failed_flow!)))) )))) diff --git a/stdlib/source/specification/compositor/analysis/type.lux b/stdlib/source/specification/compositor/analysis/type.lux index 5f2820ba2..2cbc93cea 100644 --- a/stdlib/source/specification/compositor/analysis/type.lux +++ b/stdlib/source/specification/compositor/analysis/type.lux @@ -57,8 +57,8 @@ [[typeC exprT exprC] ..check [other_typeC other_exprT other_exprC] ..check] (all _.and - (_.test "lux check" - (check_success+ expander state "lux check" (list typeC exprC) exprT)) - (_.test "lux coerce" - (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT)) + (_.property "lux check" + (check_success+ expander state "lux check" (list typeC exprC) exprT)) + (_.property "lux coerce" + (check_success+ expander state "lux coerce" (list typeC other_exprC) exprT)) ))) diff --git a/stdlib/source/specification/compositor/generation/case.lux b/stdlib/source/specification/compositor/generation/case.lux index 12fa81a14..1e5502e17 100644 --- a/stdlib/source/specification/compositor/generation/case.lux +++ b/stdlib/source/specification/compositor/generation/case.lux @@ -101,12 +101,12 @@ (-> Runner Test) (do r.monad [value r.safe_frac] - (_.test (%.symbol (symbol synthesis.branch/let)) - (|> (synthesis.branch/let [(synthesis.f64 value) - 0 - (synthesis.variable/local 0)]) - (run "let_spec") - (verify value))))) + (_.property (%.symbol (symbol synthesis.branch/let)) + (|> (synthesis.branch/let [(synthesis.f64 value) + 0 + (synthesis.variable/local 0)]) + (run "let_spec") + (verify value))))) (def: (if_spec run) (-> Runner Test) @@ -114,12 +114,12 @@ [on_true r.safe_frac on_false (|> r.safe_frac (r.only (|>> (f.= on_true) not))) verdict r.bit] - (_.test (%.symbol (symbol synthesis.branch/if)) - (|> (synthesis.branch/if [(synthesis.bit verdict) - (synthesis.f64 on_true) - (synthesis.f64 on_false)]) - (run "if_spec") - (verify (if verdict on_true on_false)))))) + (_.property (%.symbol (symbol synthesis.branch/if)) + (|> (synthesis.branch/if [(synthesis.bit verdict) + (synthesis.f64 on_true) + (synthesis.f64 on_false)]) + (run "if_spec") + (verify (if verdict on_true on_false)))))) (def: (case_spec run) (-> Runner Test) @@ -127,16 +127,16 @@ [[inputS pathS] ..case on_success r.safe_frac on_failure (|> r.safe_frac (r.only (|>> (f.= on_success) not)))] - (_.test (%.symbol (symbol synthesis.branch/case)) - (|> (synthesis.branch/case - [inputS - (all synthesis.path/alt - (all synthesis.path/seq - pathS - (synthesis.path/then (synthesis.f64 on_success))) - (synthesis.path/then (synthesis.f64 on_failure)))]) - (run "case_spec") - (verify on_success))))) + (_.property (%.symbol (symbol synthesis.branch/case)) + (|> (synthesis.branch/case + [inputS + (all synthesis.path/alt + (all synthesis.path/seq + pathS + (synthesis.path/then (synthesis.f64 on_success))) + (synthesis.path/then (synthesis.f64 on_failure)))]) + (run "case_spec") + (verify on_success))))) (def: special_input Synthesis @@ -243,39 +243,39 @@ (def: (special_spec run) (-> Runner Test) (all _.and - (_.test "===" - (and (text#= (synthesis.%path special_path) - (synthesis.%path special_pattern_path)) - (# synthesis.path_equivalence = special_path special_pattern_path))) - (_.test "CODE" - (|> special_input - (run "special_input") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 0" - (|> (synthesis.branch/case [special_input - special_path]) - (run "special_path") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) - (_.test "PATTERN_MATCHING 1" - (|> (synthesis.branch/case [special_input - special_pattern_path]) - (run "special_pattern_path") - (pipe.case - {try.#Success output} - true - - {try.#Failure _} - false))) + (_.property "===" + (and (text#= (synthesis.%path special_path) + (synthesis.%path special_pattern_path)) + (# synthesis.path_equivalence = special_path special_pattern_path))) + (_.property "CODE" + (|> special_input + (run "special_input") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.property "PATTERN_MATCHING 0" + (|> (synthesis.branch/case [special_input + special_path]) + (run "special_path") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) + (_.property "PATTERN_MATCHING 1" + (|> (synthesis.branch/case [special_input + special_pattern_path]) + (run "special_pattern_path") + (pipe.case + {try.#Success output} + true + + {try.#Failure _} + false))) )) (def: .public (spec run) diff --git a/stdlib/source/specification/compositor/generation/common.lux b/stdlib/source/specification/compositor/generation/common.lux index 77854d953..e93a46c29 100644 --- a/stdlib/source/specification/compositor/generation/common.lux +++ b/stdlib/source/specification/compositor/generation/common.lux @@ -40,17 +40,17 @@ [param r.i64 subject r.i64] (with_expansions [<binary> (template [<extension> <reference> <param_expr>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe <extension>)) - (pipe.case - {try.#Success valueT} - (n.= (<reference> param subject) (as Nat valueT)) - - {try.#Failure _} - false) - (let [param <param_expr>])))] + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list (synthesis.i64 param) + (synthesis.i64 subject))} + (run (..safe <extension>)) + (pipe.case + {try.#Success valueT} + (n.= (<reference> param subject) (as Nat valueT)) + + {try.#Failure _} + false) + (let [param <param_expr>])))] ["lux i64 and" i64.and param] ["lux i64 or" i64.or param] @@ -60,20 +60,20 @@ )] (all _.and <binary> - (_.test "lux i64 arithmetic-right-shift" - (|> {synthesis.#Extension "lux i64 arithmetic-right-shift" - (list (synthesis.i64 subject) - (synthesis.i64 param))} - (run (..safe "lux i64 arithmetic-right-shift")) - (pipe.case - {try.#Success valueT} - ("lux i64 =" - (i64.arithmetic_right_shifted param subject) - (as I64 valueT)) - - {try.#Failure _} - false) - (let [param (n.% 64 param)]))) + (_.property "lux i64 arithmetic-right-shift" + (|> {synthesis.#Extension "lux i64 arithmetic-right-shift" + (list (synthesis.i64 subject) + (synthesis.i64 param))} + (run (..safe "lux i64 arithmetic-right-shift")) + (pipe.case + {try.#Success valueT} + ("lux i64 =" + (i64.arithmetic_right_shifted param subject) + (as I64 valueT)) + + {try.#Failure _} + false) + (let [param (n.% 64 param)]))) )))) (def: (i64 run) @@ -83,16 +83,16 @@ subject r.i64] (`` (all _.and (~~ (template [<extension> <type> <prepare> <comp> <subject_expr>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))} - (run (..safe <extension>)) - (pipe.case - {try.#Success valueT} - (<comp> (<prepare> subject) (as <type> valueT)) + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list (synthesis.i64 subject))} + (run (..safe <extension>)) + (pipe.case + {try.#Success valueT} + (<comp> (<prepare> subject) (as <type> valueT)) - {try.#Failure _} - false) - (let [subject <subject_expr>])))] + {try.#Failure _} + false) + (let [subject <subject_expr>])))] ["lux i64 f64" Frac i.frac f.= subject] ["lux i64 char" Text (|>> (as Nat) text.from_code) text#= (|> subject @@ -101,16 +101,16 @@ (as Int))] )) (~~ (template [<extension> <reference> <outputT> <comp>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list (synthesis.i64 param) - (synthesis.i64 subject))} - (run (..safe <extension>)) - (pipe.case - {try.#Success valueT} - (<comp> (<reference> param subject) (as <outputT> valueT)) + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list (synthesis.i64 param) + (synthesis.i64 subject))} + (run (..safe <extension>)) + (pipe.case + {try.#Success valueT} + (<comp> (<reference> param subject) (as <outputT> valueT)) - {try.#Failure _} - false)))] + {try.#Failure _} + false)))] ["lux i64 +" i.+ Int i.=] ["lux i64 -" i.- Int i.=] @@ -133,11 +133,11 @@ subject ..simple_frac] (`` (all _.and (~~ (template [<extension> <reference> <comp>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe <extension>)) - (//case.verify (<reference> param subject))))] + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list (synthesis.f64 param) + (synthesis.f64 subject))} + (run (..safe <extension>)) + (//case.verify (<reference> param subject))))] ["lux f64 +" f.+ f.=] ["lux f64 -" f.- f.=] @@ -146,37 +146,37 @@ ["lux f64 %" f.% f.=] )) (~~ (template [<extension> <text>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list (synthesis.f64 param) - (synthesis.f64 subject))} - (run (..safe <extension>)) - (pipe.case - {try.#Success valueV} - (bit#= (<text> param subject) - (as Bit valueV)) - - _ - false)))] + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list (synthesis.f64 param) + (synthesis.f64 subject))} + (run (..safe <extension>)) + (pipe.case + {try.#Success valueV} + (bit#= (<text> param subject) + (as Bit valueV)) + + _ + false)))] ["lux f64 =" f.=] ["lux f64 <" f.<] )) (~~ (template [<extension> <reference>] - [(_.test <extension> - (|> {synthesis.#Extension <extension> (list)} - (run (..safe <extension>)) - (//case.verify <reference>)))] + [(_.property <extension> + (|> {synthesis.#Extension <extension> (list)} + (run (..safe <extension>)) + (//case.verify <reference>)))] ["lux f64 min" ("lux f64 min")] ["lux f64 max" ("lux f64 max")] ["lux f64 smallest" ("lux f64 smallest")] )) - (_.test "'lux f64 i64 && 'lux i64 f64'" - (|> (run (..safe "lux f64 i64") - (|> subject synthesis.f64 - (list) {synthesis.#Extension "lux f64 i64"} - (list) {synthesis.#Extension "lux i64 f64"})) - (//case.verify subject))) + (_.property "'lux f64 i64 && 'lux i64 f64'" + (|> (run (..safe "lux f64 i64") + (|> subject synthesis.f64 + (list) {synthesis.#Extension "lux f64 i64"} + (list) {synthesis.#Extension "lux i64 f64"})) + (//case.verify subject))) )))) (def: (text run) @@ -197,75 +197,75 @@ pre_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_upper)) post_rep_all (|> sample_lower (list.repeated sample_size) (text.interposed sample_alpha))]] (all _.and - (_.test "Can compare texts for equality." - (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)} - (run (..safe "lux text =")) - (pipe.case - {try.#Success valueV} - (as Bit valueV) - - _ - false)) - (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} - (run (..safe "lux text =")) - (pipe.case - {try.#Success valueV} - (not (as Bit valueV)) - - _ - false)))) - (_.test "Can compare texts for order." - (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} - (run (..safe "lux text <")) - (pipe.case - {try.#Success valueV} - (as Bit valueV) - - {try.#Failure _} - false))) - (_.test "Can get length of text." - (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} - (run (..safe "lux text size")) - (pipe.case - {try.#Success valueV} - (n.= sample_size (as Nat valueV)) - - _ - false))) - (_.test "Can concatenate text." - (|> {synthesis.#Extension "lux text size" (list concatenatedS)} - (run (..safe "lux text size")) - (pipe.case - {try.#Success valueV} - (n.= (n.* 2 sample_size) (as Nat valueV)) - - _ - false))) - (_.test "Can find index of sub-text." - (and (|> {synthesis.#Extension "lux text index" - (list concatenatedS sample_lowerS - (synthesis.i64 +0))} - (run (..safe "lux text index")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= 0 valueV) - - _ - false)) - (|> {synthesis.#Extension "lux text index" - (list concatenatedS sample_upperS - (synthesis.i64 +0))} - (run (..safe "lux text index")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Nat) valueV) - {.#Some valueV}]) - (n.= sample_size valueV) - - _ - false)))) + (_.property "Can compare texts for equality." + (and (|> {synthesis.#Extension "lux text =" (list sample_lowerS sample_lowerS)} + (run (..safe "lux text =")) + (pipe.case + {try.#Success valueV} + (as Bit valueV) + + _ + false)) + (|> {synthesis.#Extension "lux text =" (list sample_upperS sample_lowerS)} + (run (..safe "lux text =")) + (pipe.case + {try.#Success valueV} + (not (as Bit valueV)) + + _ + false)))) + (_.property "Can compare texts for order." + (|> {synthesis.#Extension "lux text <" (list sample_lowerS sample_upperS)} + (run (..safe "lux text <")) + (pipe.case + {try.#Success valueV} + (as Bit valueV) + + {try.#Failure _} + false))) + (_.property "Can get length of text." + (|> {synthesis.#Extension "lux text size" (list sample_lowerS)} + (run (..safe "lux text size")) + (pipe.case + {try.#Success valueV} + (n.= sample_size (as Nat valueV)) + + _ + false))) + (_.property "Can concatenate text." + (|> {synthesis.#Extension "lux text size" (list concatenatedS)} + (run (..safe "lux text size")) + (pipe.case + {try.#Success valueV} + (n.= (n.* 2 sample_size) (as Nat valueV)) + + _ + false))) + (_.property "Can find index of sub-text." + (and (|> {synthesis.#Extension "lux text index" + (list concatenatedS sample_lowerS + (synthesis.i64 +0))} + (run (..safe "lux text index")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= 0 valueV) + + _ + false)) + (|> {synthesis.#Extension "lux text index" + (list concatenatedS sample_upperS + (synthesis.i64 +0))} + (run (..safe "lux text index")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Nat) valueV) + {.#Some valueV}]) + (n.= sample_size valueV) + + _ + false)))) (let [test_clip (is (-> (I64 Any) (I64 Any) Text Bit) (function (_ offset length expected) (|> {synthesis.#Extension "lux text clip" @@ -281,23 +281,23 @@ _ false))))] - (_.test "Can clip text to extract sub-text." - (and (test_clip 0 sample_size sample_lower) - (test_clip sample_size sample_size sample_upper)))) - (_.test "Can extract individual characters from text." - (|> {synthesis.#Extension "lux text char" - (list sample_lowerS - (synthesis.i64 char_idx))} - (run (..safe "lux text char")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Maybe Int) valueV) - {.#Some valueV}]) - (text.contains? ("lux i64 char" valueV) - sample_lower) - - _ - false))) + (_.property "Can clip text to extract sub-text." + (and (test_clip 0 sample_size sample_lower) + (test_clip sample_size sample_size sample_upper)))) + (_.property "Can extract individual characters from text." + (|> {synthesis.#Extension "lux text char" + (list sample_lowerS + (synthesis.i64 char_idx))} + (run (..safe "lux text char")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Maybe Int) valueV) + {.#Some valueV}]) + (text.contains? ("lux i64 char" valueV) + sample_lower) + + _ + false))) ))) (def: (io run) @@ -305,57 +305,57 @@ (do r.monad [message (r.alphabetic 5)] (all _.and - (_.test "Can log messages." - (|> {synthesis.#Extension "lux io log" - (list (synthesis.text (format "LOG: " message)))} - (run (..safe "lux io log")) - (pipe.case - {try.#Success valueV} - true - - {try.#Failure _} - false))) - (_.test "Can throw runtime errors." - (and (|> {synthesis.#Extension "lux try" - (list (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity 1 - synthesis.#body {synthesis.#Extension "lux io error" - (list (synthesis.text message))}]))} - (run (..safe "lux try")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Try Text) valueV) - {try.#Failure error}]) - (text.contains? message error) - - _ - false)) - (|> {synthesis.#Extension "lux try" - (list (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity 1 - synthesis.#body (synthesis.text message)]))} - (run (..safe "lux try")) - (pipe.case - (^.multi {try.#Success valueV} - [(as (Try Text) valueV) - {try.#Success valueV}]) - (text#= message valueV) - - _ - false)))) - (_.test "Can obtain current time in milli-seconds." - (|> (synthesis.tuple (list {synthesis.#Extension "lux io current-time" (list)} - {synthesis.#Extension "lux io current-time" (list)})) - (run (..safe "lux io current-time")) - (pipe.case - {try.#Success valueV} - (let [[pre post] (as [Nat Nat] valueV)] - (n.>= pre post)) - - {try.#Failure _} - false))) + (_.property "Can log messages." + (|> {synthesis.#Extension "lux io log" + (list (synthesis.text (format "LOG: " message)))} + (run (..safe "lux io log")) + (pipe.case + {try.#Success valueV} + true + + {try.#Failure _} + false))) + (_.property "Can throw runtime errors." + (and (|> {synthesis.#Extension "lux try" + (list (synthesis.function/abstraction + [synthesis.#environment (list) + synthesis.#arity 1 + synthesis.#body {synthesis.#Extension "lux io error" + (list (synthesis.text message))}]))} + (run (..safe "lux try")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Try Text) valueV) + {try.#Failure error}]) + (text.contains? message error) + + _ + false)) + (|> {synthesis.#Extension "lux try" + (list (synthesis.function/abstraction + [synthesis.#environment (list) + synthesis.#arity 1 + synthesis.#body (synthesis.text message)]))} + (run (..safe "lux try")) + (pipe.case + (^.multi {try.#Success valueV} + [(as (Try Text) valueV) + {try.#Success valueV}]) + (text#= message valueV) + + _ + false)))) + (_.property "Can obtain current time in milli-seconds." + (|> (synthesis.tuple (list {synthesis.#Extension "lux io current-time" (list)} + {synthesis.#Extension "lux io current-time" (list)})) + (run (..safe "lux io current-time")) + (pipe.case + {try.#Success valueV} + (let [[pre post] (as [Nat Nat] valueV)] + (n.>= pre post)) + + {try.#Failure _} + false))) ))) (def: .public (spec runner) diff --git a/stdlib/source/specification/compositor/generation/function.lux b/stdlib/source/specification/compositor/generation/function.lux index 6cc0d14b5..33db49436 100644 --- a/stdlib/source/specification/compositor/generation/function.lux +++ b/stdlib/source/specification/compositor/generation/function.lux @@ -55,40 +55,40 @@ .let [expectation (maybe.trusted (list.item (-- local) inputs)) inputsS (list#each (|>> synthesis.f64) inputs)]] (all _.and - (_.test "Can read arguments." - (|> (synthesis.function/apply [synthesis.#function functionS + (_.property "Can read arguments." + (|> (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments inputsS]) + (run "with_local") + (//case.verify expectation))) + (_.property "Can partially apply functions." + (or (n.= 1 arity) + (let [preS (list.first partial_arity inputsS) + postS (list.after partial_arity inputsS) + partialS (synthesis.function/apply [synthesis.#function functionS + synthesis.#arguments preS])] + (|> (synthesis.function/apply [synthesis.#function partialS + synthesis.#arguments postS]) + (run "partial_application") + (//case.verify expectation))))) + (_.property "Can read environment." + (or (n.= 1 arity) + (let [environment (|> partial_arity + (enum.range n.enum 1) + (list#each (|>> {reference.#Local}))) + variableS (if (n.<= partial_arity local) + (synthesis.variable/foreign (-- local)) + (synthesis.variable/local (|> local (n.- partial_arity)))) + inner_arity (n.- partial_arity arity) + innerS (synthesis.function/abstraction + [synthesis.#environment environment + synthesis.#arity inner_arity + synthesis.#body variableS]) + outerS (synthesis.function/abstraction + [synthesis.#environment (list) + synthesis.#arity partial_arity + synthesis.#body innerS])] + (|> (synthesis.function/apply [synthesis.#function outerS synthesis.#arguments inputsS]) - (run "with_local") - (//case.verify expectation))) - (_.test "Can partially apply functions." - (or (n.= 1 arity) - (let [preS (list.first partial_arity inputsS) - postS (list.after partial_arity inputsS) - partialS (synthesis.function/apply [synthesis.#function functionS - synthesis.#arguments preS])] - (|> (synthesis.function/apply [synthesis.#function partialS - synthesis.#arguments postS]) - (run "partial_application") - (//case.verify expectation))))) - (_.test "Can read environment." - (or (n.= 1 arity) - (let [environment (|> partial_arity - (enum.range n.enum 1) - (list#each (|>> {reference.#Local}))) - variableS (if (n.<= partial_arity local) - (synthesis.variable/foreign (-- local)) - (synthesis.variable/local (|> local (n.- partial_arity)))) - inner_arity (n.- partial_arity arity) - innerS (synthesis.function/abstraction - [synthesis.#environment environment - synthesis.#arity inner_arity - synthesis.#body variableS]) - outerS (synthesis.function/abstraction - [synthesis.#environment (list) - synthesis.#arity partial_arity - synthesis.#body innerS])] - (|> (synthesis.function/apply [synthesis.#function outerS - synthesis.#arguments inputsS]) - (run "with_foreign") - (//case.verify expectation))))) + (run "with_foreign") + (//case.verify expectation))))) ))) diff --git a/stdlib/source/specification/compositor/generation/primitive.lux b/stdlib/source/specification/compositor/generation/primitive.lux index 46ba10d00..d79b226c3 100644 --- a/stdlib/source/specification/compositor/generation/primitive.lux +++ b/stdlib/source/specification/compositor/generation/primitive.lux @@ -32,14 +32,14 @@ (~~ (template [<evaluation_name> <synthesis> <gen> <test>] [(do r.monad [expected <gen>] - (_.test (%.symbol (symbol <synthesis>)) - (|> (run <evaluation_name> (<synthesis> expected)) - (pipe.case - {try.#Success actual} - (<test> expected (as_expected actual)) + (_.property (%.symbol (symbol <synthesis>)) + (|> (run <evaluation_name> (<synthesis> expected)) + (pipe.case + {try.#Success actual} + (<test> expected (as_expected actual)) - {try.#Failure _} - false))))] + {try.#Failure _} + false))))] ["bit" synthesis.bit r.bit bit#=] ["i64" synthesis.i64 r.i64 "lux i64 ="] diff --git a/stdlib/source/specification/compositor/generation/reference.lux b/stdlib/source/specification/compositor/generation/reference.lux index df9482058..f0893573f 100644 --- a/stdlib/source/specification/compositor/generation/reference.lux +++ b/stdlib/source/specification/compositor/generation/reference.lux @@ -29,31 +29,31 @@ (do r.monad [name ..symbol expected r.safe_frac] - (_.test "Definitions." - (|> (define name (synthesis.f64 expected)) - (pipe.case - {try.#Success actual} - (f.= expected (as Frac actual)) + (_.property "Definitions." + (|> (define name (synthesis.f64 expected)) + (pipe.case + {try.#Success actual} + (f.= expected (as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (variable run) (-> Runner Test) (do [! r.monad] [register (|> r.nat (# ! each (n.% 100))) expected r.safe_frac] - (_.test "Local variables." - (|> (synthesis.branch/let [(synthesis.f64 expected) - register - (synthesis.variable/local register)]) - (run "variable") - (pipe.case - {try.#Success actual} - (f.= expected (as Frac actual)) + (_.property "Local variables." + (|> (synthesis.branch/let [(synthesis.f64 expected) + register + (synthesis.variable/local register)]) + (run "variable") + (pipe.case + {try.#Success actual} + (f.= expected (as Frac actual)) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner definer) (-> Runner Definer Test) diff --git a/stdlib/source/specification/compositor/generation/structure.lux b/stdlib/source/specification/compositor/generation/structure.lux index 4423a85bf..3080f6abd 100644 --- a/stdlib/source/specification/compositor/generation/structure.lux +++ b/stdlib/source/specification/compositor/generation/structure.lux @@ -35,53 +35,53 @@ tag_in (|> r.nat (# ! each (n.% num_tags))) .let [last?_in (|> num_tags -- (n.= tag_in))] value_in r.i64] - (_.test (%.symbol (symbol synthesis.variant)) - (|> (synthesis.variant [analysis.#lefts (if last?_in - (-- tag_in) - tag_in) - analysis.#right? last?_in - analysis.#value (synthesis.i64 value_in)]) - (run "variant") - (pipe.case - {try.#Success valueT} - (let [valueT (as (Array Any) valueT)] - (and (n.= 3 (array.size valueT)) - (let [tag_out (as java/lang/Integer (maybe.trusted (array.read! 0 valueT))) - last?_out (array.read! 1 valueT) - value_out (as Any (maybe.trusted (array.read! 2 valueT))) - same_tag? (|> tag_out ffi.int_to_long (as Nat) (n.= tag_in)) - same_flag? (case last?_out - {.#Some last?_out'} - (and last?_in (text#= "" (as Text last?_out'))) + (_.property (%.symbol (symbol synthesis.variant)) + (|> (synthesis.variant [analysis.#lefts (if last?_in + (-- tag_in) + tag_in) + analysis.#right? last?_in + analysis.#value (synthesis.i64 value_in)]) + (run "variant") + (pipe.case + {try.#Success valueT} + (let [valueT (as (Array Any) valueT)] + (and (n.= 3 (array.size valueT)) + (let [tag_out (as java/lang/Integer (maybe.trusted (array.read! 0 valueT))) + last?_out (array.read! 1 valueT) + value_out (as Any (maybe.trusted (array.read! 2 valueT))) + same_tag? (|> tag_out ffi.int_to_long (as Nat) (n.= tag_in)) + same_flag? (case last?_out + {.#Some last?_out'} + (and last?_in (text#= "" (as Text last?_out'))) - {.#None} - (not last?_in)) - same_value? (|> value_out (as Int) (i.= value_in))] - (and same_tag? - same_flag? - same_value?)))) + {.#None} + (not last?_in)) + same_value? (|> value_out (as Int) (i.= value_in))] + (and same_tag? + same_flag? + same_value?)))) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: (tuple run) (-> Runner Test) (do [! r.monad] [size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) tuple_in (r.list size r.i64)] - (_.test (%.symbol (symbol synthesis.tuple)) - (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) - (run "tuple") - (pipe.case - {try.#Success tuple_out} - (let [tuple_out (as (Array Any) tuple_out)] - (and (n.= size (array.size tuple_out)) - (list.every? (function (_ [left right]) - (i.= left (as Int right))) - (list.zipped_2 tuple_in (array.list tuple_out))))) + (_.property (%.symbol (symbol synthesis.tuple)) + (|> (synthesis.tuple (list#each (|>> synthesis.i64) tuple_in)) + (run "tuple") + (pipe.case + {try.#Success tuple_out} + (let [tuple_out (as (Array Any) tuple_out)] + (and (n.= size (array.size tuple_out)) + (list.every? (function (_ [left right]) + (i.= left (as Int right))) + (list.zipped_2 tuple_in (array.list tuple_out))))) - {try.#Failure _} - false))))) + {try.#Failure _} + false))))) (def: .public (spec runner) (-> Runner Test) diff --git a/stdlib/source/specification/lux/abstract/apply.lux b/stdlib/source/specification/lux/abstract/apply.lux index 461f304c3..3266925ce 100644 --- a/stdlib/source/specification/lux/abstract/apply.lux +++ b/stdlib/source/specification/lux/abstract/apply.lux @@ -20,31 +20,31 @@ (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample (# ! each injection random.nat)] - (_.test "Identity." - ((comparison n.=) - (/#on sample (injection function.identity)) - sample)))) + (_.property "Identity." + ((comparison n.=) + (/#on sample (injection function.identity)) + sample)))) (def: (homomorphism injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat increase (# ! each n.+ random.nat)] - (_.test "Homomorphism." - ((comparison n.=) - (/#on (injection sample) (injection increase)) - (injection (increase sample)))))) + (_.property "Homomorphism." + ((comparison n.=) + (/#on (injection sample) (injection increase)) + (injection (increase sample)))))) (def: (interchange injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) (do [! random.monad] [sample random.nat increase (# ! each n.+ random.nat)] - (_.test "Interchange." - ((comparison n.=) - (/#on (injection sample) (injection increase)) - (/#on (injection increase) (injection (is (-> (-> Nat Nat) Nat) - (function (_ f) (f sample))))))))) + (_.property "Interchange." + ((comparison n.=) + (/#on (injection sample) (injection increase)) + (/#on (injection increase) (injection (is (-> (-> Nat Nat) Nat) + (function (_ f) (f sample))))))))) (def: (composition injection comparison (open "/#[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) @@ -55,16 +55,16 @@ (# ! each n.+ random.nat)) decrease (is (Random :$/1:) (# ! each n.- random.nat))] - (_.test "Composition." - ((comparison n.=) - (|> (injection (is (-> :$/1: :$/1: :$/1:) - function.composite)) - (/#on (injection increase)) - (/#on (injection decrease)) - (/#on (injection sample))) - (/#on (/#on (injection sample) - (injection increase)) - (injection decrease))))))) + (_.property "Composition." + ((comparison n.=) + (|> (injection (is (-> :$/1: :$/1: :$/1:) + function.composite)) + (/#on (injection increase)) + (/#on (injection decrease)) + (/#on (injection sample))) + (/#on (/#on (injection sample) + (injection increase)) + (injection decrease))))))) (def: .public (spec injection comparison apply) (All (_ f) (-> (Injection f) (Comparison f) (Apply f) Test)) diff --git a/stdlib/source/specification/lux/abstract/codec.lux b/stdlib/source/specification/lux/abstract/codec.lux index 9a39f4b1c..af4a3b157 100644 --- a/stdlib/source/specification/lux/abstract/codec.lux +++ b/stdlib/source/specification/lux/abstract/codec.lux @@ -18,10 +18,10 @@ (do random.monad [expected generator] (_.for [/.Codec] - (_.test "Isomorphism." - (case (|> expected @//encoded @//decoded) - {try.#Success actual} - (@//= expected actual) - - {try.#Failure _} - false))))) + (_.property "Isomorphism." + (case (|> expected @//encoded @//decoded) + {try.#Success actual} + (@//= expected actual) + + {try.#Failure _} + false))))) diff --git a/stdlib/source/specification/lux/abstract/comonad.lux b/stdlib/source/specification/lux/abstract/comonad.lux index dca713ac2..4ef7f6b22 100644 --- a/stdlib/source/specification/lux/abstract/comonad.lux +++ b/stdlib/source/specification/lux/abstract/comonad.lux @@ -21,9 +21,9 @@ (|>> _//out (n.+ diff))) random.nat) .let [start (injection sample)]] - (_.test "Left identity." - (n.= (morphism start) - (|> start _//disjoint (_//each morphism) _//out))))) + (_.property "Left identity." + (n.= (morphism start) + (|> start _//disjoint (_//each morphism) _//out))))) (def: (right_identity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) @@ -31,9 +31,9 @@ [sample random.nat .let [start (injection sample) == (comparison n.=)]] - (_.test "Right identity." - (== start - (|> start _//disjoint (_//each _//out)))))) + (_.property "Right identity." + (== start + (|> start _//disjoint (_//each _//out)))))) (def: (associativity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) @@ -47,9 +47,9 @@ random.nat) .let [start (injection sample) == (comparison n.=)]] - (_.test "Associativity." - (== (|> start _//disjoint (_//each (|>> _//disjoint (_//each increase) decrease))) - (|> start _//disjoint (_//each increase) _//disjoint (_//each decrease)))))) + (_.property "Associativity." + (== (|> start _//disjoint (_//each (|>> _//disjoint (_//each increase) decrease))) + (|> start _//disjoint (_//each increase) _//disjoint (_//each decrease)))))) (def: .public (spec injection comparison subject) (All (_ f) (-> (Injection f) (Comparison f) (CoMonad f) Test)) diff --git a/stdlib/source/specification/lux/abstract/enum.lux b/stdlib/source/specification/lux/abstract/enum.lux index bff39db70..572550645 100644 --- a/stdlib/source/specification/lux/abstract/enum.lux +++ b/stdlib/source/specification/lux/abstract/enum.lux @@ -15,13 +15,13 @@ [sample gen_sample] (<| (_.for [/.Enum]) (all _.and - (_.test "Successor and predecessor are inverse functions." - (and (_#= (|> sample _#succ _#pred) - sample) - (_#= (|> sample _#pred _#succ) - sample) - (not (_#= (_#succ sample) - sample)) - (not (_#= (_#pred sample) - sample)))) + (_.property "Successor and predecessor are inverse functions." + (and (_#= (|> sample _#succ _#pred) + sample) + (_#= (|> sample _#pred _#succ) + sample) + (not (_#= (_#succ sample) + sample)) + (not (_#= (_#pred sample) + sample)))) )))) diff --git a/stdlib/source/specification/lux/abstract/equivalence.lux b/stdlib/source/specification/lux/abstract/equivalence.lux index 892d77524..21b425f3d 100644 --- a/stdlib/source/specification/lux/abstract/equivalence.lux +++ b/stdlib/source/specification/lux/abstract/equivalence.lux @@ -18,7 +18,7 @@ right random] (<| (_.for [/.Equivalence]) (all _.and - (_.test "Reflexivity" - (/#= left left)) - (_.test "Symmetry" - (bit#= (/#= left right) (/#= right left))))))) + (_.property "Reflexivity" + (/#= left left)) + (_.property "Symmetry" + (bit#= (/#= left right) (/#= right left))))))) diff --git a/stdlib/source/specification/lux/abstract/functor.lux b/stdlib/source/specification/lux/abstract/functor.lux index f5b3a6205..9e2110a97 100644 --- a/stdlib/source/specification/lux/abstract/functor.lux +++ b/stdlib/source/specification/lux/abstract/functor.lux @@ -26,20 +26,20 @@ (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample (# ! each injection random.nat)] - (_.test "Identity." - ((comparison n.=) - (@//each function.identity sample) - sample)))) + (_.property "Identity." + ((comparison n.=) + (@//each function.identity sample) + sample)))) (def: (homomorphism injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) (do [! random.monad] [sample random.nat increase (# ! each n.+ random.nat)] - (_.test "Homomorphism." - ((comparison n.=) - (@//each increase (injection sample)) - (injection (increase sample)))))) + (_.property "Homomorphism." + ((comparison n.=) + (@//each increase (injection sample)) + (injection (increase sample)))))) (def: (composition injection comparison (open "@//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) @@ -47,10 +47,10 @@ [sample (# ! each injection random.nat) increase (# ! each n.+ random.nat) decrease (# ! each n.- random.nat)] - (_.test "Composition." - ((comparison n.=) - (|> sample (@//each increase) (@//each decrease)) - (|> sample (@//each (|>> increase decrease))))))) + (_.property "Composition." + ((comparison n.=) + (|> sample (@//each increase) (@//each decrease)) + (|> sample (@//each (|>> increase decrease))))))) (def: .public (spec injection comparison functor) (All (_ f) (-> (Injection f) (Comparison f) (Functor f) Test)) diff --git a/stdlib/source/specification/lux/abstract/functor/contravariant.lux b/stdlib/source/specification/lux/abstract/functor/contravariant.lux index 0fca98448..291476eb4 100644 --- a/stdlib/source/specification/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/specification/lux/abstract/functor/contravariant.lux @@ -16,10 +16,10 @@ (def: (identity equivalence value (open "@//[0]")) (All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test)) - (_.test "Law of identity." - (equivalence - (@//each function.identity value) - value))) + (_.property "Law of identity." + (equivalence + (@//each function.identity value) + value))) (def: .public (spec equivalence value functor) (All (_ f a) (-> (Equivalence (f a)) (f a) (Functor f) Test)) diff --git a/stdlib/source/specification/lux/abstract/hash.lux b/stdlib/source/specification/lux/abstract/hash.lux index 935dc6a2d..29b5a2a2f 100644 --- a/stdlib/source/specification/lux/abstract/hash.lux +++ b/stdlib/source/specification/lux/abstract/hash.lux @@ -16,7 +16,7 @@ (do random.monad [parameter random subject random] - (_.cover [/.Hash] - (if (_#= parameter subject) - (n.= (_#hash parameter) (_#hash subject)) - true)))) + (_.coverage [/.Hash] + (if (_#= parameter subject) + (n.= (_#hash parameter) (_#hash subject)) + true)))) diff --git a/stdlib/source/specification/lux/abstract/interval.lux b/stdlib/source/specification/lux/abstract/interval.lux index 4ea7ca50e..10e18cd81 100644 --- a/stdlib/source/specification/lux/abstract/interval.lux +++ b/stdlib/source/specification/lux/abstract/interval.lux @@ -16,8 +16,8 @@ (do random.monad [sample gen_sample] (all _.and - (_.test "No value is bigger than the top." - (@//< @//top sample)) - (_.test "No value is smaller than the bottom." - (order.> @//order @//bottom sample)) + (_.property "No value is bigger than the top." + (@//< @//top sample)) + (_.property "No value is smaller than the bottom." + (order.> @//order @//bottom sample)) )))) diff --git a/stdlib/source/specification/lux/abstract/mix.lux b/stdlib/source/specification/lux/abstract/mix.lux index 8ea932916..57b900a03 100644 --- a/stdlib/source/specification/lux/abstract/mix.lux +++ b/stdlib/source/specification/lux/abstract/mix.lux @@ -18,6 +18,6 @@ (do random.monad [subject random.nat parameter random.nat] - (_.cover [/.Mix] - (n.= (@//mix n.+ parameter (injection subject)) - (n.+ parameter subject))))) + (_.coverage [/.Mix] + (n.= (@//mix n.+ parameter (injection subject)) + (n.+ parameter subject))))) diff --git a/stdlib/source/specification/lux/abstract/monad.lux b/stdlib/source/specification/lux/abstract/monad.lux index e42b0dbdf..4344e5236 100644 --- a/stdlib/source/specification/lux/abstract/monad.lux +++ b/stdlib/source/specification/lux/abstract/monad.lux @@ -18,19 +18,19 @@ morphism (# ! each (function (_ diff) (|>> (n.+ diff) _//in)) random.nat)] - (_.test "Left identity." - ((comparison n.=) - (|> (injection sample) (_//each morphism) _//conjoint) - (morphism sample))))) + (_.property "Left identity." + ((comparison n.=) + (|> (injection sample) (_//each morphism) _//conjoint) + (morphism sample))))) (def: (right_identity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) (do random.monad [sample random.nat] - (_.test "Right identity." - ((comparison n.=) - (|> (injection sample) (_//each _//in) _//conjoint) - (injection sample))))) + (_.property "Right identity." + ((comparison n.=) + (|> (injection sample) (_//each _//in) _//conjoint) + (injection sample))))) (def: (associativity injection comparison (open "_//[0]")) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) @@ -42,10 +42,10 @@ decrease (# ! each (function (_ diff) (|>> (n.- diff) _//in)) random.nat)] - (_.test "Associativity." - ((comparison n.=) - (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint) - (|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint))))) + (_.property "Associativity." + ((comparison n.=) + (|> (injection sample) (_//each increase) _//conjoint (_//each decrease) _//conjoint) + (|> (injection sample) (_//each (|>> increase (_//each decrease) _//conjoint)) _//conjoint))))) (def: .public (spec injection comparison monad) (All (_ f) (-> (Injection f) (Comparison f) (/.Monad f) Test)) diff --git a/stdlib/source/specification/lux/abstract/monoid.lux b/stdlib/source/specification/lux/abstract/monoid.lux index f6daaa867..815cf8c4d 100644 --- a/stdlib/source/specification/lux/abstract/monoid.lux +++ b/stdlib/source/specification/lux/abstract/monoid.lux @@ -20,13 +20,13 @@ right gen_sample] (<| (_.for [/.Monoid]) (all _.and - (_.test "Left identity." - (_#= sample - (_#composite _#identity sample))) - (_.test "Right identity." - (_#= sample - (_#composite sample _#identity))) - (_.test "Associativity." - (_#= (_#composite left (_#composite mid right)) - (_#composite (_#composite left mid) right))) + (_.property "Left identity." + (_#= sample + (_#composite _#identity sample))) + (_.property "Right identity." + (_#= sample + (_#composite sample _#identity))) + (_.property "Associativity." + (_#= (_#composite left (_#composite mid right)) + (_#composite (_#composite left mid) right))) )))) diff --git a/stdlib/source/specification/lux/abstract/order.lux b/stdlib/source/specification/lux/abstract/order.lux index e6e85a1e8..18d6b845f 100644 --- a/stdlib/source/specification/lux/abstract/order.lux +++ b/stdlib/source/specification/lux/abstract/order.lux @@ -16,16 +16,16 @@ (do random.monad [parameter generator subject generator] - (_.test "Values are either ordered, or they are equal. All options(_ are mutually exclusive." - (cond (@//< parameter subject) - (not (or (@//< subject parameter) - (@//= parameter subject))) + (_.property "Values are either ordered, or they are equal. All options(_ are mutually exclusive." + (cond (@//< parameter subject) + (not (or (@//< subject parameter) + (@//= parameter subject))) - (@//< subject parameter) - (not (@//= parameter subject)) + (@//< subject parameter) + (not (@//= parameter subject)) - ... else - (@//= parameter subject)))) + ... else + (@//= parameter subject)))) (do random.monad [parameter generator subject (random.only (|>> (@//= parameter) not) @@ -34,25 +34,25 @@ (not (or (@//= parameter value) (@//= subject value)))) generator)] - (_.test "Transitive property." - (if (@//< parameter subject) - (let [greater? (and (@//< subject extra) - (@//< parameter extra)) - lesser? (and (@//< extra parameter) - (@//< extra subject)) - in_between? (and (@//< parameter extra) - (@//< extra subject))] - (or greater? - lesser? - in_between?)) - ... (@//< subject parameter) - (let [greater? (and (@//< extra subject) - (@//< extra parameter)) - lesser? (and (@//< parameter extra) - (@//< subject extra)) - in_between? (and (@//< subject extra) - (@//< extra parameter))] - (or greater? - lesser? - in_between?))))) + (_.property "Transitive property." + (if (@//< parameter subject) + (let [greater? (and (@//< subject extra) + (@//< parameter extra)) + lesser? (and (@//< extra parameter) + (@//< extra subject)) + in_between? (and (@//< parameter extra) + (@//< extra subject))] + (or greater? + lesser? + in_between?)) + ... (@//< subject parameter) + (let [greater? (and (@//< extra subject) + (@//< extra parameter)) + lesser? (and (@//< parameter extra) + (@//< subject extra)) + in_between? (and (@//< subject extra) + (@//< extra parameter))] + (or greater? + lesser? + in_between?))))) ))) diff --git a/stdlib/source/specification/lux/world/console.lux b/stdlib/source/specification/lux/world/console.lux index e9faf9834..38bb5ed8b 100644 --- a/stdlib/source/specification/lux/world/console.lux +++ b/stdlib/source/specification/lux/world/console.lux @@ -52,7 +52,7 @@ _ false)]] - (_.cover' [/.Console] - (and can_write! - can_read! - can_close!)))))) + (_.coverage' [/.Console] + (and can_write! + can_read! + can_close!)))))) diff --git a/stdlib/source/specification/lux/world/file.lux b/stdlib/source/specification/lux/world/file.lux index 75bf2a571..da20b8d30 100644 --- a/stdlib/source/specification/lux/world/file.lux +++ b/stdlib/source/specification/lux/world/file.lux @@ -40,19 +40,19 @@ (do async.monad [fs (async.future fs)] (all _.and' - (_.cover' [/.rooted] - (let [path (/.rooted fs parent child)] - (and (text.starts_with? parent path) - (text.ends_with? child path)))) - (_.cover' [/.parent] - (|> (/.rooted fs parent child) - (/.parent fs) - (maybe#each (text#= parent)) - (maybe.else false))) - (_.cover' [/.name] - (|> (/.rooted fs parent child) - (/.name fs) - (text#= child))) + (_.coverage' [/.rooted] + (let [path (/.rooted fs parent child)] + (and (text.starts_with? parent path) + (text.ends_with? child path)))) + (_.coverage' [/.parent] + (|> (/.rooted fs parent child) + (/.parent fs) + (maybe#each (text#= parent)) + (maybe.else false))) + (_.coverage' [/.name] + (|> (/.rooted fs parent child) + (/.name fs) + (text#= child))) )))) (def: (directory?&make_directory fs parent) @@ -196,14 +196,14 @@ move&delete (..move&delete fs parent child alternate_child)]) - (_.cover' [/.System] - (and directory?&make_directory - file?&write - file_size&read&append - modified?&last_modified - can_execute? - directory_files&sub_directories - move&delete)))) + (_.coverage' [/.System] + (and directory?&make_directory + file?&write + file_size&read&append + modified?&last_modified + can_execute? + directory_files&sub_directories + move&delete)))) (def: (make_directories&cannot_make_directory fs) (-> (IO (/.System Async)) Test) @@ -227,29 +227,29 @@ cannot_make_directory!/0 (/.make_directories ! fs "") cannot_make_directory!/1 (/.make_directories ! fs (# fs separator))]) (all _.and' - (_.cover' [/.make_directories] - (and (not pre_dir/0) - (not pre_dir/1) - (not pre_dir/2) - (case made? - {try.#Success _} true - {try.#Failure _} false) - post_dir/0 - post_dir/1 - post_dir/2)) - (_.cover' [/.cannot_make_directory] - (and (case cannot_make_directory!/0 - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_directory error)) - (case cannot_make_directory!/1 - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_directory error)))) + (_.coverage' [/.make_directories] + (and (not pre_dir/0) + (not pre_dir/1) + (not pre_dir/2) + (case made? + {try.#Success _} true + {try.#Failure _} false) + post_dir/0 + post_dir/1 + post_dir/2)) + (_.coverage' [/.cannot_make_directory] + (and (case cannot_make_directory!/0 + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_directory error)) + (case cannot_make_directory!/1 + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_directory error)))) ))) (def: (make_file&cannot_make_file fs) @@ -262,17 +262,17 @@ make_file!/0 (/.make_file ! fs (utf8#encoded file/0) file/0) make_file!/1 (/.make_file ! fs (utf8#encoded file/0) file/0)]) (all _.and' - (_.cover' [/.make_file] - (case make_file!/0 - {try.#Success _} true - {try.#Failure error} false)) - (_.cover' [/.cannot_make_file] - (case make_file!/1 - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_make_file error))) + (_.coverage' [/.make_file] + (case make_file!/0 + {try.#Success _} true + {try.#Failure error} false)) + (_.coverage' [/.cannot_make_file] + (case make_file!/1 + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_make_file error))) ))) (def: (for_utilities fs) @@ -304,23 +304,23 @@ post_file/1 (/.exists? ! fs file) post_dir/0 (# fs directory? dir) post_dir/1 (/.exists? ! fs dir)]) - (_.cover' [/.exists?] - (and (not pre_file/0) - (not pre_file/1) - (not pre_dir/0) - (not pre_dir/1) + (_.coverage' [/.exists?] + (and (not pre_file/0) + (not pre_file/1) + (not pre_dir/0) + (not pre_dir/1) - (case made_file? - {try.#Success _} true - {try.#Failure _} false) - (case made_dir? - {try.#Success _} true - {try.#Failure _} false) + (case made_file? + {try.#Success _} true + {try.#Failure _} false) + (case made_dir? + {try.#Success _} true + {try.#Failure _} false) - post_file/0 - post_file/1 - post_dir/0 - post_dir/1)))) + post_file/0 + post_file/1 + post_dir/0 + post_dir/1)))) (def: .public (spec fs) (-> (IO (/.System Async)) Test) diff --git a/stdlib/source/specification/lux/world/program.lux b/stdlib/source/specification/lux/world/program.lux index b7c742164..08392541c 100644 --- a/stdlib/source/specification/lux/world/program.lux +++ b/stdlib/source/specification/lux/world/program.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try] - [concurrency - ["[0]" async {"+" Async}]]] - [data - ["[0]" text] - [collection - ["[0]" dictionary] - ["[0]" list]]] - [math - ["[0]" random]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try] + [concurrency + ["[0]" async {"+" Async}]]] + [data + ["[0]" text] + [collection + ["[0]" dictionary] + ["[0]" list]]] + [math + ["[0]" random]]]] + [\\library + ["[0]" /]]) (def: .public (spec subject) (-> (/.Program Async) Test) @@ -24,9 +24,9 @@ [exit random.int] (in (do [! async.monad] [environment (/.environment ! subject)] - (_.cover' [/.Program] - (and (not (dictionary.empty? environment)) - (list.every? (|>> text.empty? not) - (dictionary.keys environment)) - (not (text.empty? (# subject home))) - (not (text.empty? (# subject directory))))))))) + (_.coverage' [/.Program] + (and (not (dictionary.empty? environment)) + (list.every? (|>> text.empty? not) + (dictionary.keys environment)) + (not (text.empty? (# subject home))) + (not (text.empty? (# subject directory))))))))) diff --git a/stdlib/source/specification/lux/world/shell.lux b/stdlib/source/specification/lux/world/shell.lux index 3b367bdd1..7d136b7e1 100644 --- a/stdlib/source/specification/lux/world/shell.lux +++ b/stdlib/source/specification/lux/world/shell.lux @@ -38,7 +38,7 @@ (|> (# process await []) (async#each (|>> (try#each (i.= /.normal)) (try.else false) - (_.cover' [/.Exit /.normal]))) + (_.coverage' [/.Exit /.normal]))) async#conjoint)) (def: (can_read! expected process) @@ -81,12 +81,12 @@ [can_read! (..can_read! message echo) can_destroy! (..can_destroy! sleep)] (all _.and' - (_.cover' <shell_coverage> - (and can_read! - can_destroy!)) + (_.coverage' <shell_coverage> + (and can_read! + can_destroy!)) (..can_wait! echo) )) _ - (_.cover' <shell_coverage> - false)))))))) + (_.coverage' <shell_coverage> + false)))))))) diff --git a/stdlib/source/test/aedifex/artifact.lux b/stdlib/source/test/aedifex/artifact.lux index e3a533036..150724ade 100644 --- a/stdlib/source/test/aedifex/artifact.lux +++ b/stdlib/source/test/aedifex/artifact.lux @@ -49,9 +49,9 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.format /.identity] - (and (text.ends_with? (/.identity sample) (/.format sample)) - (not (text#= (/.identity sample) (/.format sample))))) + (_.coverage [/.format /.identity] + (and (text.ends_with? (/.identity sample) (/.format sample)) + (not (text#= (/.identity sample) (/.format sample))))) /extension.test /snapshot.test diff --git a/stdlib/source/test/aedifex/artifact/extension.lux b/stdlib/source/test/aedifex/artifact/extension.lux index b71b0c001..ab6bc4949 100644 --- a/stdlib/source/test/aedifex/artifact/extension.lux +++ b/stdlib/source/test/aedifex/artifact/extension.lux @@ -23,21 +23,21 @@ (<| (_.covering /._) (_.for [/.Extension] (all _.and - (_.cover [/.lux_library /.jvm_library /.pom - /.sha-1 /.md5] - (let [options (list /.lux_library /.jvm_library /.pom /.sha-1 /.md5) - uniques (set.of_list text.hash options)] - (n.= (list.size options) - (set.size uniques)))) - (_.cover [/.extension /.type] - (`` (and (~~ (template [<type> <extension>] - [(and (text#= <extension> - (/.extension <type>)) - (text#= <type> - (/.type (/.extension <type>))))] + (_.coverage [/.lux_library /.jvm_library /.pom + /.sha-1 /.md5] + (let [options (list /.lux_library /.jvm_library /.pom /.sha-1 /.md5) + uniques (set.of_list text.hash options)] + (n.= (list.size options) + (set.size uniques)))) + (_.coverage [/.extension /.type] + (`` (and (~~ (template [<type> <extension>] + [(and (text#= <extension> + (/.extension <type>)) + (text#= <type> + (/.type (/.extension <type>))))] - [//.lux_library /.lux_library] - [//.jvm_library /.jvm_library] - [//.pom /.pom] - ))))) + [//.lux_library /.lux_library] + [//.jvm_library /.jvm_library] + [//.pom /.pom] + ))))) )))) diff --git a/stdlib/source/test/aedifex/artifact/snapshot.lux b/stdlib/source/test/aedifex/artifact/snapshot.lux index cea873a6e..e44ba514c 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot.lux @@ -35,13 +35,13 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) $/build.test $/stamp.test diff --git a/stdlib/source/test/aedifex/artifact/snapshot/build.lux b/stdlib/source/test/aedifex/artifact/snapshot/build.lux index b03fe7f10..36267e060 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/build.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/build.lux @@ -29,11 +29,11 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) )))) diff --git a/stdlib/source/test/aedifex/artifact/snapshot/stamp.lux b/stdlib/source/test/aedifex/artifact/snapshot/stamp.lux index 181e39523..25134c0cb 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/stamp.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/stamp.lux @@ -37,10 +37,10 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) ))) diff --git a/stdlib/source/test/aedifex/artifact/snapshot/time.lux b/stdlib/source/test/aedifex/artifact/snapshot/time.lux index 4e8a63fe5..cde73c729 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/time.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/time.lux @@ -32,11 +32,11 @@ (do random.monad [expected ..random] (all _.and - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) )) ))) diff --git a/stdlib/source/test/aedifex/artifact/snapshot/version.lux b/stdlib/source/test/aedifex/artifact/snapshot/version.lux index 47c276dc8..53e45aa9e 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/version.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/version.lux @@ -38,13 +38,13 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) /value.test ))) diff --git a/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux b/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux index 2b32260c5..81df110ce 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux @@ -60,7 +60,7 @@ remote_format) (text.ends_with? (%.nat (the ///stamp.#build stamp)) remote_format))] - (_.cover [/.snapshot /.format] - (and local! - remote!)))) + (_.coverage [/.snapshot /.format] + (and local! + remote!)))) ))) diff --git a/stdlib/source/test/aedifex/artifact/time.lux b/stdlib/source/test/aedifex/artifact/time.lux index d8f67e45a..521b07e9e 100644 --- a/stdlib/source/test/aedifex/artifact/time.lux +++ b/stdlib/source/test/aedifex/artifact/time.lux @@ -39,22 +39,22 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) (do random.monad [expected ..random] - (_.cover [/.instant /.of_instant] - (|> expected - /.instant - /.of_instant - (try#each (# /.equivalence = expected)) - (try.else false)))) - (_.cover [/.epoch] - (instant#= instant.epoch (/.instant /.epoch))) + (_.coverage [/.instant /.of_instant] + (|> expected + /.instant + /.of_instant + (try#each (# /.equivalence = expected)) + (try.else false)))) + (_.coverage [/.epoch] + (instant#= instant.epoch (/.instant /.epoch))) /date.test /time.test diff --git a/stdlib/source/test/aedifex/artifact/time/date.lux b/stdlib/source/test/aedifex/artifact/time/date.lux index 9f5169d78..48e4188a4 100644 --- a/stdlib/source/test/aedifex/artifact/time/date.lux +++ b/stdlib/source/test/aedifex/artifact/time/date.lux @@ -45,25 +45,25 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.value /.date] - (|> expected - /.value - /.date - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.year_is_out_of_range] - (case (/.date candidate) - {try.#Success date} - (same? candidate (/.value date)) - - {try.#Failure error} - (exception.match? /.year_is_out_of_range error))) - (_.cover [/.epoch] - (date#= date.epoch (/.value /.epoch))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.value /.date] + (|> expected + /.value + /.date + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.year_is_out_of_range] + (case (/.date candidate) + {try.#Success date} + (same? candidate (/.value date)) + + {try.#Failure error} + (exception.match? /.year_is_out_of_range error))) + (_.coverage [/.epoch] + (date#= date.epoch (/.value /.epoch))) )))) diff --git a/stdlib/source/test/aedifex/artifact/time/time.lux b/stdlib/source/test/aedifex/artifact/time/time.lux index da0589d93..70fc9dddf 100644 --- a/stdlib/source/test/aedifex/artifact/time/time.lux +++ b/stdlib/source/test/aedifex/artifact/time/time.lux @@ -31,10 +31,10 @@ (all _.and (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# time.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# time.equivalence = expected)) + (try.else false)))) ))) diff --git a/stdlib/source/test/aedifex/artifact/type.lux b/stdlib/source/test/aedifex/artifact/type.lux index a5592e3ef..4166828f8 100644 --- a/stdlib/source/test/aedifex/artifact/type.lux +++ b/stdlib/source/test/aedifex/artifact/type.lux @@ -33,11 +33,11 @@ (<| (_.covering /._) (_.for [/.Type] (all _.and - (_.cover [/.lux_library /.jvm_library /.js_library - /.pom /.md5 /.sha-1] - (let [options (list /.lux_library /.jvm_library /.js_library - /.pom /.md5 /.sha-1) - uniques (set.of_list text.hash options)] - (n.= (list.size options) - (set.size uniques)))) + (_.coverage [/.lux_library /.jvm_library /.js_library + /.pom /.md5 /.sha-1] + (let [options (list /.lux_library /.jvm_library /.js_library + /.pom /.md5 /.sha-1) + uniques (set.of_list text.hash options)] + (n.= (list.size options) + (set.size uniques)))) )))) diff --git a/stdlib/source/test/aedifex/artifact/versioning.lux b/stdlib/source/test/aedifex/artifact/versioning.lux index bc029a46a..683468bcf 100644 --- a/stdlib/source/test/aedifex/artifact/versioning.lux +++ b/stdlib/source/test/aedifex/artifact/versioning.lux @@ -37,18 +37,18 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) - (_.cover [/.init] - (|> /.init - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = /.init)) - (try.else false))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) + (_.coverage [/.init] + (|> /.init + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = /.init)) + (try.else false))) ))) diff --git a/stdlib/source/test/aedifex/cache.lux b/stdlib/source/test/aedifex/cache.lux index a641ee369..690ff01ff 100644 --- a/stdlib/source/test/aedifex/cache.lux +++ b/stdlib/source/test/aedifex/cache.lux @@ -110,14 +110,14 @@ (in (do async.monad [wrote! (/.write_one program fs dependency expected_package) read! (/.read_one program fs dependency)] - (_.cover' [/.write_one /.read_one] - (<| (try.else false) - (do try.monad - [_ wrote! - actual_package read!] - (in (# //package.equivalence = - (has //package.#origin {//repository/origin.#Local ""} expected_package) - actual_package))))))))) + (_.coverage' [/.write_one /.read_one] + (<| (try.else false) + (do try.monad + [_ wrote! + actual_package read!] + (in (# //package.equivalence = + (has //package.#origin {//repository/origin.#Local ""} expected_package) + actual_package))))))))) (def: plural Test @@ -131,16 +131,16 @@ (in (do async.monad [wrote! (/.write_all program fs expected) read! (/.read_all program fs (dictionary.keys expected) //dependency/resolution.empty)] - (_.cover' [/.write_all /.read_all] - (<| (try.else false) - (do try.monad - [_ wrote! - actual read!] - (in (# //dependency/resolution.equivalence = - (# dictionary.functor each - (has //package.#origin {//repository/origin.#Local ""}) - expected) - actual))))))))) + (_.coverage' [/.write_all /.read_all] + (<| (try.else false) + (do try.monad + [_ wrote! + actual read!] + (in (# //dependency/resolution.equivalence = + (# dictionary.functor each + (has //package.#origin {//repository/origin.#Local ""}) + expected) + actual))))))))) (def: .public test Test diff --git a/stdlib/source/test/aedifex/cli.lux b/stdlib/source/test/aedifex/cli.lux index c02ae8c4f..4f4de026a 100644 --- a/stdlib/source/test/aedifex/cli.lux +++ b/stdlib/source/test/aedifex/cli.lux @@ -72,35 +72,35 @@ Test (do random.monad [expected ..command] - (_.test "Without profile." - (|> expected - ..format - (cli.result /.command) - (pipe.case - {try.#Success [names actual]} - (and (# (list.equivalence text.equivalence) = (list //.default) names) - (# /.equivalence = expected actual)) - - {try.#Failure error} - false))))) + (_.property "Without profile." + (|> expected + ..format + (cli.result /.command) + (pipe.case + {try.#Success [names actual]} + (and (# (list.equivalence text.equivalence) = (list //.default) names) + (# /.equivalence = expected actual)) + + {try.#Failure error} + false))))) (def: with_profile Test (do random.monad [expected_profile (random.alphabetic 1) expected_command ..command] - (_.test "With profile." - (|> expected_command - ..format - (partial_list "with" expected_profile) - (cli.result /.command) - (pipe.case - {try.#Success [actual_profile actual_command]} - (and (# (list.equivalence text.equivalence) = (list expected_profile //.default) actual_profile) - (# /.equivalence = expected_command actual_command)) - - {try.#Failure error} - false))))) + (_.property "With profile." + (|> expected_command + ..format + (partial_list "with" expected_profile) + (cli.result /.command) + (pipe.case + {try.#Success [actual_profile actual_command]} + (and (# (list.equivalence text.equivalence) = (list expected_profile //.default) actual_profile) + (# /.equivalence = expected_command actual_command)) + + {try.#Failure error} + false))))) (def: .public test Test diff --git a/stdlib/source/test/aedifex/command/auto.lux b/stdlib/source/test/aedifex/command/auto.lux index 4bc2dec70..7a1e7dc35 100644 --- a/stdlib/source/test/aedifex/command/auto.lux +++ b/stdlib/source/test/aedifex/command/auto.lux @@ -91,8 +91,8 @@ dummy_path (# ! each (|>> (format source /)) (random.alphabetic 5)) [compiler resolution] $build.resolution] (all _.and - (_.cover [/.delay] - (n.> 0 /.delay)) + (_.coverage [/.delay] + (n.> 0 /.delay)) (in (do async.monad [verdict (do ///action.monad [_ (# fs make_directory source) @@ -120,6 +120,6 @@ (# ! each (n.= expected_runs)))] (in {try.#Success (and correct_number_of_runs! no_dangling_process!)})))] - (_.cover' [/.do!] - (try.else false verdict)))) + (_.coverage' [/.do!] + (try.else false verdict)))) )))) diff --git a/stdlib/source/test/aedifex/command/build.lux b/stdlib/source/test/aedifex/command/build.lux index 008908479..4d813a8ad 100644 --- a/stdlib/source/test/aedifex/command/build.lux +++ b/stdlib/source/test/aedifex/command/build.lux @@ -162,22 +162,22 @@ (in (do async.monad [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty (with_target empty_profile))] - (_.cover' [/.no_specified_program] - (case outcome - {try.#Success _} - false + (_.coverage' [/.no_specified_program] + (case outcome + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.no_specified_program error))))) + {try.#Failure error} + (exception.match? /.no_specified_program error))))) (in (do async.monad [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty profile)] - (_.cover' [/.Lux /.no_available_lux] - (case outcome - {try.#Success _} - false + (_.coverage' [/.Lux /.no_available_lux] + (case outcome + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.no_available_lux error))))) + {try.#Failure error} + (exception.match? /.no_available_lux error))))) (do ! [.let [console (@version.echo "")] [compiler resolution] ..resolution] @@ -190,16 +190,16 @@ end (# console read_line [])] (in (and (text#= /.start start) (text#= /.success end))))] - (_.cover' [/.do! - /.lux_group - /.jvm_lux_name - /.js_lux_name - /.python_lux_name - /.lua_lux_name - /.ruby_lux_name - /.start - /.success] - (try.else false verdict))))) + (_.coverage' [/.do! + /.lux_group + /.jvm_lux_name + /.js_lux_name + /.python_lux_name + /.lua_lux_name + /.ruby_lux_name + /.start + /.success] + (try.else false verdict))))) (do ! [.let [console (@version.echo "")] [compiler resolution] ..resolution] @@ -212,8 +212,8 @@ end (# console read_line [])] (in (and (text#= /.start start) (text#= /.failure end))))] - (_.cover' [/.failure] - (try.else false verdict))))) + (_.coverage' [/.failure] + (try.else false verdict))))) (do ! [expected/0 (random.alphabetic 5) expected/1 (random.alphabetic 5) @@ -243,8 +243,8 @@ (text#= expected/1 actual/1) (text#= expected/2 actual/2) end!)))] - (_.cover' [<log!>] - (try.else false verdict)))))] + (_.coverage' [<log!>] + (try.else false verdict)))))] [#0 /.log_output!] [#1 /.log_error!] diff --git a/stdlib/source/test/aedifex/command/clean.lux b/stdlib/source/test/aedifex/command/clean.lux index c64a5e1b7..90dd9c8b9 100644 --- a/stdlib/source/test/aedifex/command/clean.lux +++ b/stdlib/source/test/aedifex/command/clean.lux @@ -115,5 +115,5 @@ (and sub_exists!/pre (not sub_exists!/post)) (text#= (/.success target_path) logging))))] - (_.cover' [/.do! /.success] - (try.else false verdict))))))) + (_.coverage' [/.do! /.success] + (try.else false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/deploy.lux b/stdlib/source/test/aedifex/command/deploy.lux index f414f5d2b..67e1bf702 100644 --- a/stdlib/source/test/aedifex/command/deploy.lux +++ b/stdlib/source/test/aedifex/command/deploy.lux @@ -130,5 +130,5 @@ deployed_pom! deployed_sha-1! deployed_md5!)))] - (_.cover' [/.do! /.success] - (try.else false verdict))))))) + (_.coverage' [/.do! /.success] + (try.else false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/deps.lux b/stdlib/source/test/aedifex/command/deps.lux index 101eaa542..aeffb80f5 100644 --- a/stdlib/source/test/aedifex/command/deps.lux +++ b/stdlib/source/test/aedifex/command/deps.lux @@ -126,5 +126,5 @@ had_dependee_after! had_depender_after!)))] - (_.cover' [/.do!] - (try.else false verdict))))))) + (_.coverage' [/.do!] + (try.else false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/install.lux b/stdlib/source/test/aedifex/command/install.lux index d89a7a7a6..e0392fd56 100644 --- a/stdlib/source/test/aedifex/command/install.lux +++ b/stdlib/source/test/aedifex/command/install.lux @@ -92,14 +92,14 @@ (in (and succeeded! library_exists! pom_exists!)))] - (_.cover' [/.do! /.success] - (try.else false verdict)))) + (_.coverage' [/.do! /.success] + (try.else false verdict)))) (in (do [! async.monad] [.let [fs (file.mock /) program (program.async (program.mock environment.empty home working_directory))] logging (..execute! program fs (has ///.#identity {.#None} sample))] - (_.cover' [/.failure] - (|> logging - (try#each (text#= /.failure)) - (try.else false))))) + (_.coverage' [/.failure] + (|> logging + (try#each (text#= /.failure)) + (try.else false))))) )))) diff --git a/stdlib/source/test/aedifex/command/pom.lux b/stdlib/source/test/aedifex/command/pom.lux index 464189af0..54312e388 100644 --- a/stdlib/source/test/aedifex/command/pom.lux +++ b/stdlib/source/test/aedifex/command/pom.lux @@ -57,14 +57,14 @@ (binary#= expected actual)]] (in (and logging! expected_content!)))] - (_.cover' [/.do! /.success] - (try.else false verdict))) + (_.coverage' [/.do! /.success] + (try.else false verdict))) {try.#Failure error} - (_.cover' [/.do!] - (case (the ///.#identity sample) - {.#Some _} - false + (_.coverage' [/.do!] + (case (the ///.#identity sample) + {.#Some _} + false - {.#None} - true)))))))) + {.#None} + true)))))))) diff --git a/stdlib/source/test/aedifex/command/test.lux b/stdlib/source/test/aedifex/command/test.lux index 862597b79..eec957702 100644 --- a/stdlib/source/test/aedifex/command/test.lux +++ b/stdlib/source/test/aedifex/command/test.lux @@ -74,9 +74,9 @@ (text#= //build.success build_end)) (and (text#= /.start test_start) (text#= /.success test_end)))))] - (_.cover' [/.do! - /.start /.success] - (try.else false verdict))))) + (_.coverage' [/.do! + /.start /.success] + (try.else false verdict))))) (let [fs (file.mock (# file.default separator)) console (@version.echo "")] (in (do async.monad @@ -110,6 +110,6 @@ (text#= //build.success build_end)) (and (text#= /.start test_start) (text#= /.failure test_end)))))] - (_.cover' [/.failure] - (try.else false verdict))))) + (_.coverage' [/.failure] + (try.else false verdict))))) )))) diff --git a/stdlib/source/test/aedifex/command/version.lux b/stdlib/source/test/aedifex/command/version.lux index fff234d52..5a0fbf681 100644 --- a/stdlib/source/test/aedifex/command/version.lux +++ b/stdlib/source/test/aedifex/command/version.lux @@ -74,5 +74,5 @@ logging (# console read_line [])] (in (text#= (version.format lux_version.latest) logging)))] - (_.cover' [/.do!] - (try.else false verdict))))))) + (_.coverage' [/.do!] + (try.else false verdict))))))) diff --git a/stdlib/source/test/aedifex/dependency/deployment.lux b/stdlib/source/test/aedifex/dependency/deployment.lux index 12b175534..f9f5e6763 100644 --- a/stdlib/source/test/aedifex/dependency/deployment.lux +++ b/stdlib/source/test/aedifex/dependency/deployment.lux @@ -159,10 +159,10 @@ (in (do async.monad [?outcome (/.one repository dependency package) cache (async.future (atom.read! cache))] - (_.cover' [/.one] - (|> ?outcome - (try#each (verify_one 1 address package cache expected_artifact)) - (try.else false)))))) + (_.coverage' [/.one] + (|> ?outcome + (try#each (verify_one 1 address package cache expected_artifact)) + (try.else false)))))) (do [! random.monad] [.let [hash (is (Hash [Dependency Artifact Package]) (# hash.functor each (|>> product.right product.left product.left) @@ -182,23 +182,23 @@ (in (do async.monad [?outcome (/.all repository resolution) cache (async.future (atom.read! cache))] - (_.cover' [/.all] - (|> ?outcome - (try#each (function (_ actual_artifacts) - (let [expected_deployments! - (n.= num_bundles (set.size actual_artifacts)) + (_.coverage' [/.all] + (|> ?outcome + (try#each (function (_ actual_artifacts) + (let [expected_deployments! + (n.= num_bundles (set.size actual_artifacts)) - every_deployment_was_correct! - (list.every? (function (_ [dependency expected_artifact package]) - (let [deployed! - (set.member? actual_artifacts expected_artifact) + every_deployment_was_correct! + (list.every? (function (_ [dependency expected_artifact package]) + (let [deployed! + (set.member? actual_artifacts expected_artifact) - deployed_correctly! - (verify_one num_bundles address package cache expected_artifact expected_artifact)] - (and deployed! - deployed_correctly!))) - bundles)] - (and expected_deployments! - every_deployment_was_correct!)))) - (try.else false)))))) + deployed_correctly! + (verify_one num_bundles address package cache expected_artifact expected_artifact)] + (and deployed! + deployed_correctly!))) + bundles)] + (and expected_deployments! + every_deployment_was_correct!)))) + (try.else false)))))) )))) diff --git a/stdlib/source/test/aedifex/dependency/resolution.lux b/stdlib/source/test/aedifex/dependency/resolution.lux index 1233cd1cb..e5db7fe3c 100644 --- a/stdlib/source/test/aedifex/dependency/resolution.lux +++ b/stdlib/source/test/aedifex/dependency/resolution.lux @@ -262,27 +262,27 @@ [actual_package (/.one (///repository.mock good []) [///dependency.#artifact expected_artifact ///dependency.#type ///artifact/type.lux_library])] - (_.cover' [/.one] - (case actual_package - {try.#Success actual_package} - (# ///package.equivalence = - (has ///package.#origin {///repository/origin.#Remote ""} expected_package) - actual_package) - - {try.#Failure _} - false)))) + (_.coverage' [/.one] + (case actual_package + {try.#Success actual_package} + (# ///package.equivalence = + (has ///package.#origin {///repository/origin.#Remote ""} expected_package) + actual_package) + + {try.#Failure _} + false)))) (~~ (template [<exception> <bad>] [(in (do async.monad [actual_package (/.one (///repository.mock <bad> []) [///dependency.#artifact expected_artifact ///dependency.#type ///artifact/type.lux_library])] - (_.cover' [<exception>] - (case actual_package - {try.#Failure error} - (exception.match? <exception> error) + (_.coverage' [<exception>] + (case actual_package + {try.#Failure error} + (exception.match? <exception> error) - {try.#Success _} - false))))] + {try.#Success _} + false))))] [/.sha-1_does_not_match bad_sha-1] [/.md5_does_not_match bad_md5] @@ -311,15 +311,15 @@ (///repository.mock good [])) [///dependency.#artifact expected_artifact ///dependency.#type ///artifact/type.lux_library])] - (_.cover' [/.any] - (case actual_package - {try.#Success actual_package} - (# ///package.equivalence = - (has ///package.#origin {///repository/origin.#Remote ""} expected_package) - actual_package) - - {try.#Failure _} - false)))) + (_.coverage' [/.any] + (case actual_package + {try.#Success actual_package} + (# ///package.equivalence = + (has ///package.#origin {///repository/origin.#Remote ""} expected_package) + actual_package) + + {try.#Failure _} + false)))) (in (do async.monad [.let [console ($///version.echo "")] actual_package (/.any console @@ -327,13 +327,13 @@ (///repository.mock bad_md5 [])) [///dependency.#artifact expected_artifact ///dependency.#type ///artifact/type.lux_library])] - (_.cover' [/.cannot_resolve] - (case actual_package - {try.#Failure error} - (exception.match? /.cannot_resolve error) + (_.coverage' [/.cannot_resolve] + (case actual_package + {try.#Failure error} + (exception.match? /.cannot_resolve error) - {try.#Success _} - false)))) + {try.#Success _} + false)))) ))) (def: artifacts @@ -416,15 +416,15 @@ (///repository.mock ..nope [])) (list depender) /.empty)] - (_.cover' [/.all] - (and (dictionary.key? resolution depender) - (list.any? (///dependency#= depender) successes) - - (dictionary.key? resolution dependee) - (list.any? (///dependency#= dependee) successes) - - (list.empty? failures) - (not (dictionary.key? resolution ignored)))))) + (_.coverage' [/.all] + (and (dictionary.key? resolution depender) + (list.any? (///dependency#= depender) successes) + + (dictionary.key? resolution dependee) + (list.any? (///dependency#= dependee) successes) + + (list.empty? failures) + (not (dictionary.key? resolution ignored)))))) ))) (def: .public test @@ -435,8 +435,8 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.empty] - (dictionary.empty? /.empty)) + (_.coverage [/.empty] + (dictionary.empty? /.empty)) ..one ..any diff --git a/stdlib/source/test/aedifex/dependency/status.lux b/stdlib/source/test/aedifex/dependency/status.lux index 948de489f..5f221b4e4 100644 --- a/stdlib/source/test/aedifex/dependency/status.lux +++ b/stdlib/source/test/aedifex/dependency/status.lux @@ -38,11 +38,11 @@ (do random.monad [payload (binaryT.random 1)] - (_.cover [/.verified] - (case (/.verified payload) - {/.#Verified sha1 md5} - true + (_.coverage [/.verified] + (case (/.verified payload) + {/.#Verified sha1 md5} + true - _ - false))) + _ + false))) )))) diff --git a/stdlib/source/test/aedifex/hash.lux b/stdlib/source/test/aedifex/hash.lux index 804708085..339c7c3b4 100644 --- a/stdlib/source/test/aedifex/hash.lux +++ b/stdlib/source/test/aedifex/hash.lux @@ -48,21 +48,21 @@ (~~ (template [<hash> <constructor> <exception>] [(do random.monad [expected (..random <hash>)] - (_.cover [<hash> <constructor> <exception>] - (and (case (<constructor> (/.data expected)) - {try.#Success actual} - (# /.equivalence = expected actual) + (_.coverage [<hash> <constructor> <exception>] + (and (case (<constructor> (/.data expected)) + {try.#Success actual} + (# /.equivalence = expected actual) - {try.#Failure error} - false) - (case (<constructor> (# binary.monoid composite - (/.data expected) - (/.data expected))) - {try.#Success actual} - false + {try.#Failure error} + false) + (case (<constructor> (# binary.monoid composite + (/.data expected) + (/.data expected))) + {try.#Success actual} + false - {try.#Failure error} - (exception.match? <exception> error)))))] + {try.#Failure error} + (exception.match? <exception> error)))))] [/.sha-1 /.as_sha-1 /.not_a_sha-1] [/.md5 /.as_md5 /.not_a_md5] @@ -79,15 +79,15 @@ (~~ (template [<codec> <hash>] [(do random.monad [expected (..random <hash>)] - (_.cover [<codec>] - (case (# <codec> decoded - (format (# <codec> encoded expected) - "AABBCC")) - {try.#Success actual} - false + (_.coverage [<codec>] + (case (# <codec> decoded + (format (# <codec> encoded expected) + "AABBCC")) + {try.#Success actual} + false - {try.#Failure error} - (exception.match? /.not_a_hash error))))] + {try.#Failure error} + (exception.match? /.not_a_hash error))))] [/.sha-1_codec /.sha-1] [/.md5_codec /.md5] diff --git a/stdlib/source/test/aedifex/input.lux b/stdlib/source/test/aedifex/input.lux index bb4d7aa87..5cc687a7b 100644 --- a/stdlib/source/test/aedifex/input.lux +++ b/stdlib/source/test/aedifex/input.lux @@ -63,5 +63,5 @@ (revised //.#sources ..with_default_source) (revised //.#repositories ..with_default_repository)) actual)))] - (_.cover' [/.read] - (try.else false verdict))))))) + (_.coverage' [/.read] + (try.else false verdict))))))) diff --git a/stdlib/source/test/aedifex/local.lux b/stdlib/source/test/aedifex/local.lux index c46a1679d..58f1c019e 100644 --- a/stdlib/source/test/aedifex/local.lux +++ b/stdlib/source/test/aedifex/local.lux @@ -21,7 +21,7 @@ (do [! random.monad] [sample @artifact.random] (all _.and - (_.cover [/.repository /.uri] - (text.starts_with? /.repository - (/.uri (the //artifact.#version sample) sample))) + (_.coverage [/.repository /.uri] + (text.starts_with? /.repository + (/.uri (the //artifact.#version sample) sample))) )))) diff --git a/stdlib/source/test/aedifex/metadata.lux b/stdlib/source/test/aedifex/metadata.lux index 5ff5988ee..20c67f929 100644 --- a/stdlib/source/test/aedifex/metadata.lux +++ b/stdlib/source/test/aedifex/metadata.lux @@ -23,27 +23,27 @@ (do random.monad [sample $artifact.random] (all _.and - (_.cover [/.remote_artifact_uri /.remote_project_uri] - (not (text#= (/.remote_artifact_uri sample) - (/.remote_project_uri sample)))) - (_.cover [/.local_uri] - (let [remote_artifact_uri (/.remote_artifact_uri sample) - remote_project_uri (/.remote_project_uri sample)] - (and (not (text#= remote_artifact_uri (/.local_uri remote_artifact_uri))) - (not (text#= remote_project_uri (/.local_uri remote_project_uri)))))) - (_.cover [/.remote_uri] - (let [remote_artifact_uri (/.remote_artifact_uri sample) - remote_project_uri (/.remote_project_uri sample)] - (and (text#= remote_artifact_uri (/.remote_uri remote_artifact_uri)) - (text#= remote_project_uri (/.remote_uri remote_project_uri)) - (|> remote_artifact_uri - /.local_uri - /.remote_uri - (text#= remote_artifact_uri)) - (|> remote_project_uri - /.local_uri - /.remote_uri - (text#= remote_project_uri))))) + (_.coverage [/.remote_artifact_uri /.remote_project_uri] + (not (text#= (/.remote_artifact_uri sample) + (/.remote_project_uri sample)))) + (_.coverage [/.local_uri] + (let [remote_artifact_uri (/.remote_artifact_uri sample) + remote_project_uri (/.remote_project_uri sample)] + (and (not (text#= remote_artifact_uri (/.local_uri remote_artifact_uri))) + (not (text#= remote_project_uri (/.local_uri remote_project_uri)))))) + (_.coverage [/.remote_uri] + (let [remote_artifact_uri (/.remote_artifact_uri sample) + remote_project_uri (/.remote_project_uri sample)] + (and (text#= remote_artifact_uri (/.remote_uri remote_artifact_uri)) + (text#= remote_project_uri (/.remote_uri remote_project_uri)) + (|> remote_artifact_uri + /.local_uri + /.remote_uri + (text#= remote_artifact_uri)) + (|> remote_project_uri + /.local_uri + /.remote_uri + (text#= remote_project_uri))))) )) /artifact.test diff --git a/stdlib/source/test/aedifex/metadata/artifact.lux b/stdlib/source/test/aedifex/metadata/artifact.lux index 4a0294d61..02f1a6611 100644 --- a/stdlib/source/test/aedifex/metadata/artifact.lux +++ b/stdlib/source/test/aedifex/metadata/artifact.lux @@ -84,16 +84,16 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) - (_.cover [/.uri] - (text#= (//.remote_project_uri artifact) - (/.uri artifact))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) + (_.coverage [/.uri] + (text#= (//.remote_project_uri artifact) + (/.uri artifact))) (do random.monad [home (random.lower_case 5) working_directory (random.lower_case 5) @@ -103,14 +103,14 @@ (in (do async.monad [wrote? (/.write repository artifact expected) actual (/.read repository artifact)] - (_.cover' [/.write /.read] - (and (case wrote? - {try.#Success _} true - {try.#Failure _} false) - (case actual - {try.#Success actual} - (# /.equivalence = expected actual) - - {try.#Failure _} - false)))))) + (_.coverage' [/.write /.read] + (and (case wrote? + {try.#Success _} true + {try.#Failure _} false) + (case actual + {try.#Success actual} + (# /.equivalence = expected actual) + + {try.#Failure _} + false)))))) )))) diff --git a/stdlib/source/test/aedifex/metadata/snapshot.lux b/stdlib/source/test/aedifex/metadata/snapshot.lux index 00cdb05b6..27cffb1f0 100644 --- a/stdlib/source/test/aedifex/metadata/snapshot.lux +++ b/stdlib/source/test/aedifex/metadata/snapshot.lux @@ -96,16 +96,16 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.format /.parser] - (|> expected - /.format - list - (<xml>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.uri] - (text#= (//.remote_artifact_uri artifact) - (/.uri artifact))) + (_.coverage [/.format /.parser] + (|> expected + /.format + list + (<xml>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.uri] + (text#= (//.remote_artifact_uri artifact) + (/.uri artifact))) (do random.monad [home (random.lower_case 5) working_directory (random.lower_case 5) @@ -115,14 +115,14 @@ (in (do async.monad [wrote? (/.write repository artifact expected) actual (/.read repository artifact)] - (_.cover' [/.write /.read] - (and (case wrote? - {try.#Success _} true - {try.#Failure _} false) - (case actual - {try.#Success actual} - (# /.equivalence = expected actual) - - {try.#Failure _} - false)))))) + (_.coverage' [/.write /.read] + (and (case wrote? + {try.#Success _} true + {try.#Failure _} false) + (case actual + {try.#Success actual} + (# /.equivalence = expected actual) + + {try.#Failure _} + false)))))) )))) diff --git a/stdlib/source/test/aedifex/package.lux b/stdlib/source/test/aedifex/package.lux index 28d763e4c..4b95cd250 100644 --- a/stdlib/source/test/aedifex/package.lux +++ b/stdlib/source/test/aedifex/package.lux @@ -63,60 +63,60 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence (# ! each product.right ..random))) - (_.cover [/.local?] - (/.local? (has /.#origin {//origin.#Local "~/yolo"} package))) - (_.cover [/.remote?] - (/.remote? (has /.#origin {//origin.#Remote "https://example.com"} package))) - (_.cover [/.local] - (let [expected_pom (|> package (the /.#pom) product.left) - expected_library (|> package (the /.#library) product.left) + (_.coverage [/.local?] + (/.local? (has /.#origin {//origin.#Local "~/yolo"} package))) + (_.coverage [/.remote?] + (/.remote? (has /.#origin {//origin.#Remote "https://example.com"} package))) + (_.coverage [/.local] + (let [expected_pom (|> package (the /.#pom) product.left) + expected_library (|> package (the /.#library) product.left) - local (/.local expected_pom expected_library) + local (/.local expected_pom expected_library) - [actual_pom binary_pom pom_status] (the /.#pom local) - [actual_library library_status] (the /.#library local)] - (and (case (the /.#origin local) - {//origin.#Local ""} true - _ false) - (let [expected_sha1 (//hash.sha-1 expected_library) - expected_md5 (//hash.md5 expected_library)] - (and (same? expected_library actual_library) - (case library_status - {//status.#Verified actual_sha1 expected_md5} - (and (//hash#= expected_sha1 actual_sha1) - (//hash#= expected_md5 expected_md5)) - - _ - false))) - (let [expected_sha1 (//hash.sha-1 binary_pom) - expected_md5 (//hash.md5 binary_pom)] - (and (same? expected_pom actual_pom) - (|> (do try.monad - [xml_pom (# utf8.codec decoded binary_pom) - decoded_pom (# xml.codec decoded xml_pom)] - (in (# xml.equivalence = actual_pom decoded_pom))) - (try.else false)) - (case pom_status - {//status.#Verified actual_sha1 expected_md5} - (and (//hash#= expected_sha1 actual_sha1) - (//hash#= expected_md5 expected_md5)) - - _ - false)))))) - (_.cover [/.dependencies] - (let [expected (the //.#dependencies profile)] - (case (/.dependencies package) - {try.#Success actual} - (# set.equivalence = expected actual) - - {try.#Failure error} - false))) - (_.cover [/.repositories] - (let [expected (the //.#repositories profile)] - (case (/.repositories package) - {try.#Success actual} - (# set.equivalence = expected actual) - - {try.#Failure error} - false))) + [actual_pom binary_pom pom_status] (the /.#pom local) + [actual_library library_status] (the /.#library local)] + (and (case (the /.#origin local) + {//origin.#Local ""} true + _ false) + (let [expected_sha1 (//hash.sha-1 expected_library) + expected_md5 (//hash.md5 expected_library)] + (and (same? expected_library actual_library) + (case library_status + {//status.#Verified actual_sha1 expected_md5} + (and (//hash#= expected_sha1 actual_sha1) + (//hash#= expected_md5 expected_md5)) + + _ + false))) + (let [expected_sha1 (//hash.sha-1 binary_pom) + expected_md5 (//hash.md5 binary_pom)] + (and (same? expected_pom actual_pom) + (|> (do try.monad + [xml_pom (# utf8.codec decoded binary_pom) + decoded_pom (# xml.codec decoded xml_pom)] + (in (# xml.equivalence = actual_pom decoded_pom))) + (try.else false)) + (case pom_status + {//status.#Verified actual_sha1 expected_md5} + (and (//hash#= expected_sha1 actual_sha1) + (//hash#= expected_md5 expected_md5)) + + _ + false)))))) + (_.coverage [/.dependencies] + (let [expected (the //.#dependencies profile)] + (case (/.dependencies package) + {try.#Success actual} + (# set.equivalence = expected actual) + + {try.#Failure error} + false))) + (_.coverage [/.repositories] + (let [expected (the //.#repositories profile)] + (case (/.repositories package) + {try.#Success actual} + (# set.equivalence = expected actual) + + {try.#Failure error} + false))) )))) diff --git a/stdlib/source/test/aedifex/parser.lux b/stdlib/source/test/aedifex/parser.lux index a87131927..c63d1701c 100644 --- a/stdlib/source/test/aedifex/parser.lux +++ b/stdlib/source/test/aedifex/parser.lux @@ -78,23 +78,23 @@ (_.covering //format._) (do random.monad [expected ..random] - (_.cover [/.project - //format.Format //format.project] - (|> expected - //format.project - list - (<code>.result /.project) - (pipe.case - {try.#Success actual} - (|> expected - ..with_empty_profile - dictionary.entries - (list#each (function (_ [name profile]) - [name (|> profile - ..with_default_sources - ..with_default_repository)])) - (dictionary.of_list text.hash) - (# //project.equivalence = actual)) - - {try.#Failure error} - false)))))) + (_.coverage [/.project + //format.Format //format.project] + (|> expected + //format.project + list + (<code>.result /.project) + (pipe.case + {try.#Success actual} + (|> expected + ..with_empty_profile + dictionary.entries + (list#each (function (_ [name profile]) + [name (|> profile + ..with_default_sources + ..with_default_repository)])) + (dictionary.of_list text.hash) + (# //project.equivalence = actual)) + + {try.#Failure error} + false)))))) diff --git a/stdlib/source/test/aedifex/pom.lux b/stdlib/source/test/aedifex/pom.lux index bf29cfeb5..ac8869c54 100644 --- a/stdlib/source/test/aedifex/pom.lux +++ b/stdlib/source/test/aedifex/pom.lux @@ -26,32 +26,32 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.file] - (|> /.file - (text#= "") - not)) + (_.coverage [/.file] + (|> /.file + (text#= "") + not)) (do random.monad [expected @profile.random] - (_.cover [/.write /.parser] - (case [(/.write expected) - (the //.#identity expected)] - [{try.#Success pom} - {.#Some _}] - (case (<xml>.result /.parser (list pom)) - {try.#Success actual} - (# //.equivalence = - (|> (# //.monoid identity) - (has //.#dependencies (the //.#dependencies expected)) - (has //.#repositories (the //.#repositories expected))) - actual) + (_.coverage [/.write /.parser] + (case [(/.write expected) + (the //.#identity expected)] + [{try.#Success pom} + {.#Some _}] + (case (<xml>.result /.parser (list pom)) + {try.#Success actual} + (# //.equivalence = + (|> (# //.monoid identity) + (has //.#dependencies (the //.#dependencies expected)) + (has //.#repositories (the //.#repositories expected))) + actual) - {try.#Failure error} - false) + {try.#Failure error} + false) - [{try.#Failure error} - {.#None}] - (exception.match? //.no_identity error) + [{try.#Failure error} + {.#None}] + (exception.match? //.no_identity error) - _ - false))) + _ + false))) ))) diff --git a/stdlib/source/test/aedifex/profile.lux b/stdlib/source/test/aedifex/profile.lux index dd5b296d8..8bccf4459 100644 --- a/stdlib/source/test/aedifex/profile.lux +++ b/stdlib/source/test/aedifex/profile.lux @@ -159,14 +159,14 @@ (_.for [/.monoid] ($monoid.spec /.equivalence /.monoid ..random)) - (_.cover [/.default] - (text#= "" /.default)) - (_.cover [/.default_lux] - (|> (# /.monoid identity) - (the /.#lux) - (same? /.default_lux))) - (_.cover [/.default_target] - (|> (# /.monoid identity) - (the /.#target) - (same? /.default_target))) + (_.coverage [/.default] + (text#= "" /.default)) + (_.coverage [/.default_lux] + (|> (# /.monoid identity) + (the /.#lux) + (same? /.default_lux))) + (_.coverage [/.default_target] + (|> (# /.monoid identity) + (the /.#target) + (same? /.default_target))) ))))) diff --git a/stdlib/source/test/aedifex/project.lux b/stdlib/source/test/aedifex/project.lux index c191a5f83..748ea922d 100644 --- a/stdlib/source/test/aedifex/project.lux +++ b/stdlib/source/test/aedifex/project.lux @@ -46,10 +46,10 @@ (_.for [/.monoid] ($monoid.spec /.equivalence /.monoid ..random)) - (_.cover [/.file] - (|> /.file - (text#= "") - not)) + (_.coverage [/.file] + (|> /.file + (text#= "") + not)) (do random.monad [[super_name super_profile] ..profile [dummy_name dummy_profile] (random.only (|>> product.left (text#= super_name) not) @@ -72,29 +72,29 @@ (/.project dummy_name dummy_profile) (/.project sub_name (has //.#parents (list super_name) sub_profile)))]] (all _.and - (_.cover [/.profile] - (and (|> (/.profile project super_name) - (try#each (# //.equivalence = super_profile)) - (try.else false)) - (|> (/.profile project dummy_name) - (try#each (# //.equivalence = dummy_profile)) - (try.else false)) - (|> (/.profile project sub_name) - (try#each (# //.equivalence = (# //.monoid composite sub_profile super_profile))) - (try.else false)))) - (_.cover [/.unknown_profile] - (case (/.profile project fake_name) - {try.#Success _} - false + (_.coverage [/.profile] + (and (|> (/.profile project super_name) + (try#each (# //.equivalence = super_profile)) + (try.else false)) + (|> (/.profile project dummy_name) + (try#each (# //.equivalence = dummy_profile)) + (try.else false)) + (|> (/.profile project sub_name) + (try#each (# //.equivalence = (# //.monoid composite sub_profile super_profile))) + (try.else false)))) + (_.coverage [/.unknown_profile] + (case (/.profile project fake_name) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.unknown_profile error))) - (_.cover [/.circular_dependency] - (case (/.profile circular sub_name) - {try.#Success _} - false + {try.#Failure error} + (exception.match? /.unknown_profile error))) + (_.coverage [/.circular_dependency] + (case (/.profile circular sub_name) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.circular_dependency error))) + {try.#Failure error} + (exception.match? /.circular_dependency error))) )) )))) diff --git a/stdlib/source/test/aedifex/repository/local.lux b/stdlib/source/test/aedifex/repository/local.lux index 92826c8ff..9c9703d55 100644 --- a/stdlib/source/test/aedifex/repository/local.lux +++ b/stdlib/source/test/aedifex/repository/local.lux @@ -42,11 +42,11 @@ [before_upload (# repo download uri) _ (# repo upload uri expected) actual (# repo download uri)] - (_.cover' [/.repository] - (and (case before_upload - {try.#Success _} false - {try.#Failure _} true) - (|> actual - (try#each (binary#= expected)) - (try.else false)))))) + (_.coverage' [/.repository] + (and (case before_upload + {try.#Success _} false + {try.#Failure _} true) + (|> actual + (try#each (binary#= expected)) + (try.else false)))))) )))) diff --git a/stdlib/source/test/aedifex/repository/remote.lux b/stdlib/source/test/aedifex/repository/remote.lux index 05cd293c3..c20722d4c 100644 --- a/stdlib/source/test/aedifex/repository/remote.lux +++ b/stdlib/source/test/aedifex/repository/remote.lux @@ -93,39 +93,39 @@ content (# ! each (# utf8.codec encoded) (random.lower_case 10))] (all _.and - (_.cover [/.repository /.user_agent /.Address] - (let [repo (/.repository (..good_http user password) - {.#Some [//identity.#user user - //identity.#password password]} - address)] - (and (|> (# repo download uri) - io.run! - (try#each (# utf8.codec decoded)) - try#conjoint - (try#each (text#= (format address uri))) - (try.else false)) - (|> (# repo upload uri content) - io.run! - (try#each (function.constant true)) - (try.else false))))) - (_.cover [/.upload_failure] - (let [repo (/.repository (..good_http user password) - {.#None} - address)] - (case (io.run! (# repo upload uri content)) - {try.#Failure error} - (exception.match? /.upload_failure error) - - {try.#Success _} - false))) - (_.cover [/.download_failure] - (let [repo (/.repository ..bad_http - {.#None} - address)] - (case (io.run! (# repo download uri)) - {try.#Failure error} - (exception.match? /.download_failure error) - - {try.#Success _} - false))) + (_.coverage [/.repository /.user_agent /.Address] + (let [repo (/.repository (..good_http user password) + {.#Some [//identity.#user user + //identity.#password password]} + address)] + (and (|> (# repo download uri) + io.run! + (try#each (# utf8.codec decoded)) + try#conjoint + (try#each (text#= (format address uri))) + (try.else false)) + (|> (# repo upload uri content) + io.run! + (try#each (function.constant true)) + (try.else false))))) + (_.coverage [/.upload_failure] + (let [repo (/.repository (..good_http user password) + {.#None} + address)] + (case (io.run! (# repo upload uri content)) + {try.#Failure error} + (exception.match? /.upload_failure error) + + {try.#Success _} + false))) + (_.coverage [/.download_failure] + (let [repo (/.repository ..bad_http + {.#None} + address)] + (case (io.run! (# repo download uri)) + {try.#Failure error} + (exception.match? /.download_failure error) + + {try.#Success _} + false))) )))) diff --git a/stdlib/source/test/aedifex/runtime.lux b/stdlib/source/test/aedifex/runtime.lux index c982c455a..690657d70 100644 --- a/stdlib/source/test/aedifex/runtime.lux +++ b/stdlib/source/test/aedifex/runtime.lux @@ -42,12 +42,12 @@ ($equivalence.spec /.equivalence ..random)) (~~ (template [<command>] - [(_.cover [/.default_java /.default_js /.default_python /.default_lua /.default_ruby] - (let [listing (|> (list /.default_java /.default_js /.default_python /.default_lua /.default_ruby) - (list#each (the /.#program))) - unique (set.of_list text.hash listing)] - (n.= (list.size listing) - (set.size unique))))] + [(_.coverage [/.default_java /.default_js /.default_python /.default_lua /.default_ruby] + (let [listing (|> (list /.default_java /.default_js /.default_python /.default_lua /.default_ruby) + (list#each (the /.#program))) + unique (set.of_list text.hash listing)] + (n.= (list.size listing) + (set.size unique))))] [/.default_java] [/.default_js] @@ -55,13 +55,13 @@ [/.default_lua] [/.default_ruby] )) - (_.cover [/.for] - (let [runtime' (/.for runtime path)] - (and (text#= (the /.#program runtime) - (the /.#program runtime')) - (|> runtime' - (the /.#parameters) - list.last - (maybe#each (text#= path)) - (maybe.else false))))) + (_.coverage [/.for] + (let [runtime' (/.for runtime path)] + (and (text#= (the /.#program runtime) + (the /.#program runtime')) + (|> runtime' + (the /.#parameters) + list.last + (maybe#each (text#= path)) + (maybe.else false))))) ))))) diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 7d529f04e..fde45451b 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -78,60 +78,60 @@ dummy random.nat] (_.for [/.Bit /.if] (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)))) + (_.coverage [/.false] + (n.= expected + (/.if /.false + dummy + expected))) + (_.coverage [/.true] + (n.= expected + (/.if /.true + expected + dummy))) + (_.coverage [/.or] + (and (not (/.or /.false /.false)) + (/.or /.false /.true) + (/.or /.true /.false) + (/.or /.true /.true))) + (_.coverage [/.and] + (and (not (/.and /.false /.false)) + (not (/.and /.false /.true)) + (not (/.and /.true /.false)) + (/.and /.true /.true))) + (_.coverage [/.not] + (and (bit#= /.true (/.not /.false)) + (bit#= /.false (/.not /.true)))) + (_.coverage [/.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 @@ -140,27 +140,27 @@ [expected_error (random.lower_case 5) expected random.nat] (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)) + (_.coverage [/.try] + (case (/.try expected) + {.#Left _} + false + + {.#Right actual} + (n.= expected actual))) + (_.coverage [/.undefined] + (case (/.try (/.undefined)) + {.#Left _} + true + + {.#Right _} + false)) + (_.coverage [/.panic!] + (case (/.try (/.panic! expected_error)) + {.#Left actual_error} + (text.contains? expected_error actual_error) + + {.#Right _} + false)) ))) (def: for_list @@ -171,24 +171,24 @@ e/2 random.nat e/3 random.nat] (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)) + (_.coverage [/.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)) + (_.coverage [/.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) @@ -216,30 +216,30 @@ expected)))]] (_.for [/.Interface] (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 []))) + (_.coverage [/.implementation:] + (n.= expected (# (global_returner expected) return []))) + (_.coverage [/.implementation] + (n.= expected (# local_returner return []))) + (_.coverage [/.open:] + (n.= static_return (global#return []))) + (_.coverage [/.open] + (let [(/.open "local#[0]") local_returner] + (n.= expected (local#return [])))) + (_.coverage [/.#] + (n.= expected (/.# local_returner return []))) )))) (def: for_module Test (all _.and (let [[module short] (/.symbol .example)] - (_.cover [/.symbol /.prelude_module] - (and (text#= /.prelude_module module) - (text#= short "example")))) + (_.coverage [/.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))))) + (_.coverage [/.module_separator] + (and (text.contains? /.module_separator module) + (not (text.contains? /.module_separator short))))) )) (def: for_pipe @@ -249,18 +249,18 @@ factor random.nat .let [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))) + (_.coverage [/.|>] + (n.= expected + (/.|> start ++ (n.* factor)))) + (_.coverage [/.|>>] + (n.= expected + ((/.|>> ++ (n.* factor)) start))) + (_.coverage [/.<|] + (n.= expected + (/.<| (n.* factor) ++ start))) + (_.coverage [/.<<|] + (n.= expected + ((/.<<| (n.* factor) ++) start))) ))) (def: example_symbol "YOLO") @@ -275,89 +275,89 @@ Test (do random.monad [example_nat random.nat] - (_.cover [/.'] - (and (code#= (code.nat 0) (/.' 0)) - (code#= (code.int -1) (/.' -1)) - (code#= (code.rev .2) (/.' .2)) - (code#= (code.frac +3.4) (/.' +3.4)) - (code#= (code.text "5") (/.' "5")) - (code#= (code.symbol ["" "example_symbol"]) - (/.' example_symbol)) - (code#= (code.symbol [/.prelude_module "example_symbol"]) - (/.' .example_symbol)) - (code#= (code.symbol [..current_module "example_symbol"]) - (/.' ..example_symbol)) - (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) - (/.' (6 +7 .8))) - (code#= (code.variant (list (code.frac +9.0) - (code.text "9") - (code.symbol ["" "i8"]))) - (/.' {+9.0 "9" i8})) - (code#= (code.tuple (list (code.frac +9.0) - (code.text "9") - (code.symbol ["" "i8"]))) - (/.' [+9.0 "9" i8])) - (not (code#= (code.nat example_nat) - (/.' (~ (code.nat example_nat))))) - )))) + (_.coverage [/.'] + (and (code#= (code.nat 0) (/.' 0)) + (code#= (code.int -1) (/.' -1)) + (code#= (code.rev .2) (/.' .2)) + (code#= (code.frac +3.4) (/.' +3.4)) + (code#= (code.text "5") (/.' "5")) + (code#= (code.symbol ["" "example_symbol"]) + (/.' example_symbol)) + (code#= (code.symbol [/.prelude_module "example_symbol"]) + (/.' .example_symbol)) + (code#= (code.symbol [..current_module "example_symbol"]) + (/.' ..example_symbol)) + (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) + (/.' (6 +7 .8))) + (code#= (code.variant (list (code.frac +9.0) + (code.text "9") + (code.symbol ["" "i8"]))) + (/.' {+9.0 "9" i8})) + (code#= (code.tuple (list (code.frac +9.0) + (code.text "9") + (code.symbol ["" "i8"]))) + (/.' [+9.0 "9" i8])) + (not (code#= (code.nat example_nat) + (/.' (~ (code.nat example_nat))))) + )))) (def: for_code/` Test (do random.monad [example_nat random.nat] - (_.cover [/.`] - (and (code#= (code.nat 0) (/.` 0)) - (code#= (code.int -1) (/.` -1)) - (code#= (code.rev .2) (/.` .2)) - (code#= (code.frac +3.4) (/.` +3.4)) - (code#= (code.text "5") (/.` "5")) - (code#= (code.symbol [..current_module "example_symbol"]) - (/.` example_symbol)) - (code#= (code.symbol [/.prelude_module "example_symbol"]) - (/.` .example_symbol)) - (code#= (code.symbol [..current_module "example_symbol"]) - (/.` ..example_symbol)) - (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) - (/.` (6 +7 .8))) - (code#= (code.variant (list (code.frac +9.0) - (code.text "9") - (code.symbol [..current_module "i8"]))) - (/.` {+9.0 "9" i8})) - (code#= (code.tuple (list (code.frac +9.0) - (code.text "9") - (code.symbol [..current_module "i8"]))) - (/.` [+9.0 "9" i8])) - (code#= (code.nat example_nat) - (/.` (~ (code.nat example_nat)))))))) + (_.coverage [/.`] + (and (code#= (code.nat 0) (/.` 0)) + (code#= (code.int -1) (/.` -1)) + (code#= (code.rev .2) (/.` .2)) + (code#= (code.frac +3.4) (/.` +3.4)) + (code#= (code.text "5") (/.` "5")) + (code#= (code.symbol [..current_module "example_symbol"]) + (/.` example_symbol)) + (code#= (code.symbol [/.prelude_module "example_symbol"]) + (/.` .example_symbol)) + (code#= (code.symbol [..current_module "example_symbol"]) + (/.` ..example_symbol)) + (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) + (/.` (6 +7 .8))) + (code#= (code.variant (list (code.frac +9.0) + (code.text "9") + (code.symbol [..current_module "i8"]))) + (/.` {+9.0 "9" i8})) + (code#= (code.tuple (list (code.frac +9.0) + (code.text "9") + (code.symbol [..current_module "i8"]))) + (/.` [+9.0 "9" i8])) + (code#= (code.nat example_nat) + (/.` (~ (code.nat example_nat)))))))) (def: for_code/`' Test (do random.monad [example_nat random.nat] - (_.cover [/.`'] - (and (code#= (code.nat 0) (/.`' 0)) - (code#= (code.int -1) (/.`' -1)) - (code#= (code.rev .2) (/.`' .2)) - (code#= (code.frac +3.4) (/.`' +3.4)) - (code#= (code.text "5") (/.`' "5")) - (code#= (code.symbol ["" "example_symbol"]) - (/.`' example_symbol)) - (code#= (code.symbol [/.prelude_module "example_symbol"]) - (/.`' .example_symbol)) - (code#= (code.symbol [..current_module "example_symbol"]) - (/.`' ..example_symbol)) - (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) - (/.`' (6 +7 .8))) - (code#= (code.variant (list (code.frac +9.0) - (code.text "9") - (code.symbol ["" "i8"]))) - (/.`' {+9.0 "9" i8})) - (code#= (code.tuple (list (code.frac +9.0) - (code.text "9") - (code.symbol ["" "i8"]))) - (/.`' [+9.0 "9" i8])) - (code#= (code.nat example_nat) - (/.`' (~ (code.nat example_nat)))))))) + (_.coverage [/.`'] + (and (code#= (code.nat 0) (/.`' 0)) + (code#= (code.int -1) (/.`' -1)) + (code#= (code.rev .2) (/.`' .2)) + (code#= (code.frac +3.4) (/.`' +3.4)) + (code#= (code.text "5") (/.`' "5")) + (code#= (code.symbol ["" "example_symbol"]) + (/.`' example_symbol)) + (code#= (code.symbol [/.prelude_module "example_symbol"]) + (/.`' .example_symbol)) + (code#= (code.symbol [..current_module "example_symbol"]) + (/.`' ..example_symbol)) + (code#= (code.form (list (code.nat 6) (code.int +7) (code.rev .8))) + (/.`' (6 +7 .8))) + (code#= (code.variant (list (code.frac +9.0) + (code.text "9") + (code.symbol ["" "i8"]))) + (/.`' {+9.0 "9" i8})) + (code#= (code.tuple (list (code.frac +9.0) + (code.text "9") + (code.symbol ["" "i8"]))) + (/.`' [+9.0 "9" i8])) + (code#= (code.nat example_nat) + (/.`' (~ (code.nat example_nat)))))))) (def: for_code Test @@ -370,10 +370,10 @@ ..for_code/` ..for_code/`' )) - (_.cover [/.Ann] - (|> example - (the /.#meta) - (location#= location.dummy))) + (_.coverage [/.Ann] + (|> example + (the /.#meta) + (location#= location.dummy))) ))) (/.macro: (identity_macro tokens) @@ -410,130 +410,130 @@ (do random.monad [expected random.nat] (`` (`` (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))) + (_.coverage [/.Macro'] + (|> macro + (is /.Macro') + (same? macro))) + (_.coverage [/.Macro] + (|> macro + "lux macro" + (is /.Macro) + (is Any) + (same? (is Any macro)))) + (_.coverage [/.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.lower_case 1)) - <definition> (static.random code.local (random.lower_case 1)) - <module/0> (static.random code.text (random.lower_case 2)) - <module/0>' (template.symbol [<module/0>]) - <module/1> (static.random code.text (random.lower_case 3)) - <module/1>' (template.symbol [<module/1>]) - <module/2> (static.random code.text (random.lower_case 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>))]] - )))))) + (_.coverage [/.Source] + (..found_crosshair?)))) + (_.coverage [/.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)))) + (_.coverage [/.using] + (`` (with_expansions [<referral> ("lux in-module" "library/lux" library/lux.refer) + <alias> (static.random code.text (random.lower_case 1)) + <definition> (static.random code.local (random.lower_case 1)) + <module/0> (static.random code.text (random.lower_case 2)) + <module/0>' (template.symbol [<module/0>]) + <module/1> (static.random code.text (random.lower_case 3)) + <module/1>' (template.symbol [<module/1>]) + <module/2> (static.random code.text (random.lower_case 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 @@ -563,77 +563,77 @@ expected/1 existential_type] (<| (_.for [/.Type]) (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)) + (_.coverage [/.is] + (|> expected + (/.is Any) + (same? (/.is Any expected)))) + (_.coverage [/.as] + (|> expected + (/.is Any) + (/.as /.Nat) + (same? expected))) + (_.coverage [/.as_expected] + (|> expected + (/.is Any) + /.as_expected + (/.is /.Nat) + (same? expected))) + (_.coverage [/.type_of] + (same? /.Nat (/.type_of expected))) + (_.coverage [/.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)) + (_.coverage [/.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))) + (_.coverage [/.type:] + (exec + (is /.Type ..for_type/variant) + (is /.Type ..for_type/record) + (is /.Type ..for_type/all) + true)) + (_.coverage [/.Variant] + (exec + (is for_type/variant + {#Case/1 expected_left}) + true)) + (_.coverage [/.Record] + (exec + (is for_type/record + [#slot/0 (n.= expected_left expected_right) + #slot/1 (.rev expected_right)]) + true)) )))) (def: for_i64 @@ -641,24 +641,24 @@ (do random.monad [expected random.i64] (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))) + (_.coverage [/.i64] + (same? (is Any expected) + (is Any (/.i64 expected)))) + (_.coverage [/.nat] + (same? (is Any expected) + (is Any (/.nat expected)))) + (_.coverage [/.int] + (same? (is Any expected) + (is Any (/.int expected)))) + (_.coverage [/.rev] + (same? (is Any expected) + (is Any (/.rev expected)))) + (_.coverage [/.++] + (n.= 1 (n.- expected + (/.++ expected)))) + (_.coverage [/.--] + (n.= 1 (n.- (/.-- expected) + expected))) ))) (def: for_function @@ -666,17 +666,17 @@ (do random.monad [expected_left random.nat expected_right random.nat] - (_.cover [/.-> /.function] - (and (let [actual (is (/.-> Nat Nat Nat) - (/.function (_ actual_left actual_right) - (n.* (++ actual_left) (-- actual_right))))] - (n.= (n.* (++ expected_left) (-- expected_right)) - (actual expected_left expected_right))) - (let [actual (is (/.-> [Nat Nat] Nat) - (/.function (_ [actual_left actual_right]) - (n.* (++ actual_left) (-- actual_right))))] - (n.= (n.* (++ expected_left) (-- expected_right)) - (actual [expected_left expected_right]))))))) + (_.coverage [/.-> /.function] + (and (let [actual (is (/.-> Nat Nat Nat) + (/.function (_ actual_left actual_right) + (n.* (++ actual_left) (-- actual_right))))] + (n.= (n.* (++ expected_left) (-- expected_right)) + (actual expected_left expected_right))) + (let [actual (is (/.-> [Nat Nat] Nat) + (/.function (_ [actual_left actual_right]) + (n.* (++ actual_left) (-- actual_right))))] + (n.= (n.* (++ expected_left) (-- expected_right)) + (actual [expected_left expected_right]))))))) (/.template: (!n/+ <left> <right>) [(n.+ <left> <right>)]) @@ -684,20 +684,20 @@ (def: for_template Test (`` (all _.and - (_.cover [/.template] - (let [bits (list (~~ (/.template [_] - [true] - - [0] [1] [2] - )))] - (and (n.= 3 (list.size bits)) - (list.every? (bit#= true) bits)))) + (_.coverage [/.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)))) + (_.coverage [/.template:] + (n.= (n.+ left right) + (!n/+ left right)))) ))) (def: option/0 "0") @@ -710,15 +710,15 @@ [sample (random.either (in option/0) (in option/1))] (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))) + (_.coverage [/.static] + (case sample + (pattern (/.static option/0)) true + (pattern (/.static option/1)) true + _ false)) + (_.coverage [/.char] + (|> (`` (/.char (~~ (/.static static_char)))) + text.of_char + (text#= static_char))) ))) (type: Small @@ -746,73 +746,73 @@ #big_right [#small_left start/s #small_right text]]]] (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))))) + (_.coverage [/.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))))) + (_.coverage [/.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))))) + (_.coverage [/.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 @@ -822,19 +822,19 @@ mid (random.lower_case 1) right (random.lower_case 1) .let [expected (text.interposed "" (list 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>) - (' <right_association>)))))))) + (_.coverage [/.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>) + (' <right_association>)))))))) (def: for_expansion Test @@ -844,37 +844,37 @@ dummy random.nat .let [expected (n.+ left right)]] (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)))) + (_.coverage [/.these] + (`` (and (~~ (these true + true + true))))) + (_.coverage [/.with_expansions] + (/.with_expansions [<operands> (these left right)] + (n.= expected + (n.+ <operands>)))) + (_.coverage [/.comment] + (/.with_expansions [<dummy> (/.comment dummy) + <operands> (these left right)] + (n.= expected + (all n.+ <operands> <dummy>)))) + (_.coverage [/.``] + (n.= expected + (/.`` (all n.+ + (~~ (these left right)) + (~~ (/.comment dummy)))))) + (_.coverage [/.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 @@ -887,76 +887,76 @@ item/1 random.nat item/2 random.nat] (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))) + (_.coverage [/.Either] + (and (exec + (is (/.Either Nat Text) + {.#Left left}) + true) + (exec + (is (/.Either Nat Text) + {.#Right right}) + true))) + (_.coverage [/.Any] + (and (exec + (is /.Any + left) + true) + (exec + (is /.Any + right) + true))) + (_.coverage [/.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))) + (_.coverage [/.All] + (let [identity (is (/.All (_ a) (-> a a)) + (|>>))] + (and (exec + (is Nat + (identity left)) + true) + (exec + (is Text + (identity right)) + true)))) + (_.coverage [/.Ex] + (let [hide (is (/.Ex (_ a) (-> Nat a)) + (|>>))] + (exec + (is /.Any + (hide left)) + true))))) + (_.coverage [/.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))))) + (_.coverage [/.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) @@ -980,48 +980,48 @@ expected_text (random.either (in "+0.5") (in "+1.25"))] (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))))) + (_.coverage [/.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) + )) + (_.coverage [/.pattern] + (/.case [..#left expected_nat ..#right expected_int] + (/.pattern (!pair 0 +0)) true + _ false)) + (_.coverage [/.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 @@ -1031,22 +1031,22 @@ [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))))) + (_.coverage [/.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))))))) + (_.coverage [/.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 @@ -1062,9 +1062,9 @@ Test (do random.monad [expected random.nat] - (_.cover [/.def:] - (and (same? expected (identity/constant expected)) - (same? expected (identity/function expected)))))) + (_.coverage [/.def:] + (and (same? expected (identity/constant expected)) + (same? expected (identity/function expected)))))) (def: possible_targets (Set @.Target) @@ -1100,20 +1100,20 @@ (def: for_meta Test (all _.and - (_.cover [/.Mode /.Info] - (for_meta|Info)) - (_.cover [/.Module_State] - (for_meta|Module_State)) + (_.coverage [/.Mode /.Info] + (for_meta|Info)) + (_.coverage [/.Module_State] + (for_meta|Module_State)) )) (def: for_export Test (all _.and - (_.cover [/.public /.private] - (and /.public (not /.private))) - (_.cover [/.global /.local] - (and (bit#= /.public /.global) - (bit#= /.private /.local))) + (_.coverage [/.public /.private] + (and /.public (not /.private))) + (_.coverage [/.global /.local] + (and (bit#= /.public /.global) + (bit#= /.private /.local))) )) (for @.old (these) @@ -1192,8 +1192,8 @@ fn/1 var/1 let/1 fn/2 var/2 let/2 let/3)] - (_.cover [/.Bindings /.Ref] - verdict))) + (_.coverage [/.Bindings /.Ref] + verdict))) 0 1 2)))) (def: test|lux diff --git a/stdlib/source/test/lux/abstract/apply.lux b/stdlib/source/test/lux/abstract/apply.lux index a11786fd8..04c0a1e7f 100644 --- a/stdlib/source/test/lux/abstract/apply.lux +++ b/stdlib/source/test/lux/abstract/apply.lux @@ -23,14 +23,14 @@ right random.nat] (<| (_.covering /._) (all _.and - (_.cover [/.composite] - (let [expected (n.+ left right)] - (case (# (/.composite maybe.monad maybe.apply list.apply) on - {.#Some (list right)} - {.#Some (list (n.+ left))}) - (pattern {.#Some (list actual)}) - (n.= expected actual) + (_.coverage [/.composite] + (let [expected (n.+ left right)] + (case (# (/.composite maybe.monad maybe.apply list.apply) on + {.#Some (list right)} + {.#Some (list (n.+ left))}) + (pattern {.#Some (list actual)}) + (n.= expected actual) - _ - false))) + _ + false))) )))) diff --git a/stdlib/source/test/lux/abstract/codec.lux b/stdlib/source/test/lux/abstract/codec.lux index c29a007e7..ecc1c7ca3 100644 --- a/stdlib/source/test/lux/abstract/codec.lux +++ b/stdlib/source/test/lux/abstract/codec.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [format - ["[0]" json {"+" JSON}]]] - [math - ["[0]" random {"+" Random}]]]] - [\\library - ["[0]" / {"+" Codec} - [// - [equivalence {"+" Equivalence}]]]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [format + ["[0]" json {"+" JSON}]]] + [math + ["[0]" random {"+" Random}]]]] + [\\library + ["[0]" / {"+" Codec} + [// + [equivalence {"+" Equivalence}]]]]) (def: json (Codec JSON Bit) @@ -38,10 +38,10 @@ (do random.monad [expected random.bit] (<| (_.covering /._) - (_.cover [/.composite] - (case (|> expected (# ..codec encoded) (# ..codec decoded)) - {try.#Success actual} - (bit#= expected actual) - - {try.#Failure error} - false))))) + (_.coverage [/.composite] + (case (|> expected (# ..codec encoded) (# ..codec decoded)) + {try.#Success actual} + (bit#= expected actual) + + {try.#Failure error} + false))))) diff --git a/stdlib/source/test/lux/abstract/comonad.lux b/stdlib/source/test/lux/abstract/comonad.lux index 349988e4c..fce193ce1 100644 --- a/stdlib/source/test/lux/abstract/comonad.lux +++ b/stdlib/source/test/lux/abstract/comonad.lux @@ -19,10 +19,10 @@ [sample random.nat] (<| (_.covering /._) (all _.and - (_.cover [/.be] - (n.= (++ sample) - (is (Identity Nat) - (/.be identity.comonad - [value (out sample)] - (out (++ value)))))) + (_.coverage [/.be] + (n.= (++ sample) + (is (Identity Nat) + (/.be identity.comonad + [value (out sample)] + (out (++ value)))))) )))) diff --git a/stdlib/source/test/lux/abstract/enum.lux b/stdlib/source/test/lux/abstract/enum.lux index 31b90aacb..24992013b 100644 --- a/stdlib/source/test/lux/abstract/enum.lux +++ b/stdlib/source/test/lux/abstract/enum.lux @@ -30,28 +30,28 @@ range (/.range n.enum start end)]] (<| (_.covering /._) (all _.and - (_.cover [/.range] - (let [expected_size (|> end (n.- start) ++) - expected_start? (|> range list.head (maybe#each (n.= start)) (maybe.else false)) - expected_end? (|> range list.last (maybe#each (n.= end)) (maybe.else false)) - can_be_backwards? (# (list.equivalence n.equivalence) = - (/.range n.enum start end) - (list.reversed (/.range n.enum end start))) - every_element_is_a_successor? (case range - {.#Item head tail} - (|> (list#mix (function (_ next [verdict prev]) - [(and verdict - (n.= next (# n.enum succ prev))) - next]) - [true head] - tail) - product.left) - - {.#End} - false)] - (and (n.= expected_size (list.size range)) - expected_start? - expected_end? - can_be_backwards? - every_element_is_a_successor?))) + (_.coverage [/.range] + (let [expected_size (|> end (n.- start) ++) + expected_start? (|> range list.head (maybe#each (n.= start)) (maybe.else false)) + expected_end? (|> range list.last (maybe#each (n.= end)) (maybe.else false)) + can_be_backwards? (# (list.equivalence n.equivalence) = + (/.range n.enum start end) + (list.reversed (/.range n.enum end start))) + every_element_is_a_successor? (case range + {.#Item head tail} + (|> (list#mix (function (_ next [verdict prev]) + [(and verdict + (n.= next (# n.enum succ prev))) + next]) + [true head] + tail) + product.left) + + {.#End} + false)] + (and (n.= expected_size (list.size range)) + expected_start? + expected_end? + can_be_backwards? + every_element_is_a_successor?))) ))))) diff --git a/stdlib/source/test/lux/abstract/equivalence.lux b/stdlib/source/test/lux/abstract/equivalence.lux index 501791b08..0168babc8 100644 --- a/stdlib/source/test/lux/abstract/equivalence.lux +++ b/stdlib/source/test/lux/abstract/equivalence.lux @@ -39,22 +39,22 @@ (all _.and (_.for [/.functor] ($contravariant.spec equivalence n.equivalence /.functor)) - (_.cover [/.rec] - (let [equivalence (is (Equivalence (List Nat)) - (/.rec (function (_ equivalence) - (implementation - (def: (= left right) - (case [left right] - [{.#End} {.#End}] - true + (_.coverage [/.rec] + (let [equivalence (is (Equivalence (List Nat)) + (/.rec (function (_ equivalence) + (implementation + (def: (= left right) + (case [left right] + [{.#End} {.#End}] + true - [{.#Item leftH lefT} {.#Item rightH rightT}] - (and (n.= leftH rightH) - (# equivalence = lefT rightT)) + [{.#Item leftH lefT} {.#Item rightH rightT}] + (and (n.= leftH rightH) + (# equivalence = lefT rightT)) - _ - false))))))] - (and (# equivalence = (list sample sample) (list sample sample)) - (not (# equivalence = (list sample sample) (list sample))) - (not (# equivalence = (list sample sample) (list different different)))))) + _ + false))))))] + (and (# equivalence = (list sample sample) (list sample sample)) + (not (# equivalence = (list sample sample) (list sample))) + (not (# equivalence = (list sample sample) (list different different)))))) )))) diff --git a/stdlib/source/test/lux/abstract/functor.lux b/stdlib/source/test/lux/abstract/functor.lux index 3e4a62db0..ac42df1ba 100644 --- a/stdlib/source/test/lux/abstract/functor.lux +++ b/stdlib/source/test/lux/abstract/functor.lux @@ -24,40 +24,40 @@ shift random.nat] (<| (_.covering /._) (all _.and - (_.cover [/.Or /.sum] - (and (case (# (/.sum maybe.functor list.functor) each - (n.+ shift) - {.#Left {.#Some left}}) - {.#Left {.#Some actual}} - (n.= (n.+ shift left) actual) + (_.coverage [/.Or /.sum] + (and (case (# (/.sum maybe.functor list.functor) each + (n.+ shift) + {.#Left {.#Some left}}) + {.#Left {.#Some actual}} + (n.= (n.+ shift left) actual) - _ - false) - (case (# (/.sum maybe.functor list.functor) each - (n.+ shift) - {.#Right (list right)}) - (pattern {.#Right (list actual)}) - (n.= (n.+ shift right) actual) + _ + false) + (case (# (/.sum maybe.functor list.functor) each + (n.+ shift) + {.#Right (list right)}) + (pattern {.#Right (list actual)}) + (n.= (n.+ shift right) actual) - _ - false))) - (_.cover [/.And /.product] - (case (# (/.product maybe.functor list.functor) each - (n.+ shift) - [{.#Some left} (list right)]) - (pattern [{.#Some actualL} (list actualR)]) - (and (n.= (n.+ shift left) actualL) - (n.= (n.+ shift right) actualR)) + _ + false))) + (_.coverage [/.And /.product] + (case (# (/.product maybe.functor list.functor) each + (n.+ shift) + [{.#Some left} (list right)]) + (pattern [{.#Some actualL} (list actualR)]) + (and (n.= (n.+ shift left) actualL) + (n.= (n.+ shift right) actualR)) - _ - false)) - (_.cover [/.Then /.composite] - (case (# (/.composite maybe.functor list.functor) each - (n.+ shift) - {.#Some (list left)}) - (pattern {.#Some (list actual)}) - (n.= (n.+ shift left) actual) + _ + false)) + (_.coverage [/.Then /.composite] + (case (# (/.composite maybe.functor list.functor) each + (n.+ shift) + {.#Some (list left)}) + (pattern {.#Some (list actual)}) + (n.= (n.+ shift left) actual) - _ - false)) + _ + false)) )))) diff --git a/stdlib/source/test/lux/abstract/interval.lux b/stdlib/source/test/lux/abstract/interval.lux index 9e475fe11..8ad90d781 100644 --- a/stdlib/source/test/lux/abstract/interval.lux +++ b/stdlib/source/test/lux/abstract/interval.lux @@ -55,12 +55,12 @@ outer ..outer singleton ..singleton] (all _.and - (_.cover [/.inner?] - (/.inner? inner)) - (_.cover [/.outer?] - (/.outer? outer)) - (_.cover [/.singleton /.singleton?] - (/.singleton? singleton)) + (_.coverage [/.inner?] + (/.inner? inner)) + (_.coverage [/.outer?] + (/.outer? outer)) + (_.coverage [/.singleton /.singleton?] + (/.singleton? singleton)) ))) (def: boundaries @@ -70,16 +70,16 @@ top random.nat .let [interval (/.between n.enum bottom top)]] (all _.and - (_.cover [/.between /.within?] - (and (/.within? interval bottom) - (/.within? interval top))) - (_.cover [/.starts_with?] - (/.starts_with? bottom interval)) - (_.cover [/.ends_with?] - (/.ends_with? top interval)) - (_.cover [/.borders?] - (and (/.borders? interval bottom) - (/.borders? interval top))) + (_.coverage [/.between /.within?] + (and (/.within? interval bottom) + (/.within? interval top))) + (_.coverage [/.starts_with?] + (/.starts_with? bottom interval)) + (_.coverage [/.ends_with?] + (/.ends_with? top interval)) + (_.coverage [/.borders?] + (and (/.borders? interval bottom) + (/.borders? interval top))) ))) (def: union @@ -93,14 +93,14 @@ left_outer ..outer right_outer ..outer] (all _.and - (_.test "The union of an interval to itself yields the same interval." - (#= some_interval (/.union some_interval some_interval))) - (_.test "The union of 2 inner intervals is another inner interval." - (/.inner? (/.union left_inner right_inner))) - (_.test "The union of 2 outer intervals yields an inner interval when their complements don't overlap, and an outer when they do." - (if (/.overlaps? (/.complement left_outer) (/.complement right_outer)) - (/.outer? (/.union left_outer right_outer)) - (/.inner? (/.union left_outer right_outer)))) + (_.property "The union of an interval to itself yields the same interval." + (#= some_interval (/.union some_interval some_interval))) + (_.property "The union of 2 inner intervals is another inner interval." + (/.inner? (/.union left_inner right_inner))) + (_.property "The union of 2 outer intervals yields an inner interval when their complements don't overlap, and an outer when they do." + (if (/.overlaps? (/.complement left_outer) (/.complement right_outer)) + (/.outer? (/.union left_outer right_outer)) + (/.inner? (/.union left_outer right_outer)))) ))) (def: intersection @@ -114,14 +114,14 @@ left_outer ..outer right_outer ..outer] (all _.and - (_.test "The intersection of an interval to itself yields the same interval." - (#= some_interval (/.intersection some_interval some_interval))) - (_.test "The intersection of 2 inner intervals yields an inner interval when they overlap, and an outer when they don't." - (if (/.overlaps? left_inner right_inner) - (/.inner? (/.intersection left_inner right_inner)) - (/.outer? (/.intersection left_inner right_inner)))) - (_.test "The intersection of 2 outer intervals is another outer interval." - (/.outer? (/.intersection left_outer right_outer))) + (_.property "The intersection of an interval to itself yields the same interval." + (#= some_interval (/.intersection some_interval some_interval))) + (_.property "The intersection of 2 inner intervals yields an inner interval when they overlap, and an outer when they don't." + (if (/.overlaps? left_inner right_inner) + (/.inner? (/.intersection left_inner right_inner)) + (/.outer? (/.intersection left_inner right_inner)))) + (_.property "The intersection of 2 outer intervals is another outer interval." + (/.outer? (/.intersection left_outer right_outer))) ))) (def: complement @@ -129,10 +129,10 @@ (do random.monad [some_interval ..interval] (all _.and - (_.test "The complement of a complement is the same as the original." - (#= some_interval (|> some_interval /.complement /.complement))) - (_.test "The complement of an interval does not overlap it." - (not (/.overlaps? some_interval (/.complement some_interval)))) + (_.property "The complement of a complement is the same as the original." + (#= some_interval (|> some_interval /.complement /.complement))) + (_.property "The complement of an interval does not overlap it." + (not (/.overlaps? some_interval (/.complement some_interval)))) ))) (def: location @@ -150,12 +150,12 @@ .let [left (/.singleton n.enum l) right (/.singleton n.enum r)]] (all _.and - (_.cover [/.precedes? /.succeeds?] - (and (/.precedes? right left) - (/.succeeds? left right))) - (_.cover [/.before? /.after?] - (and (/.before? m left) - (/.after? m right))) + (_.coverage [/.precedes? /.succeeds?] + (and (/.precedes? right left) + (/.succeeds? left right))) + (_.coverage [/.before? /.after?] + (and (/.before? m left) + (/.after? m right))) ))) (def: touch @@ -173,16 +173,16 @@ .let [int_left (/.between n.enum t1 t2) int_right (/.between n.enum b t1)]] (all _.and - (_.cover [/.meets?] - (/.meets? int_left int_right)) - (_.cover [/.touches?] - (/.touches? int_left int_right)) - (_.cover [/.starts?] - (/.starts? (/.between n.enum b t2) - (/.between n.enum b t1))) - (_.cover [/.finishes?] - (/.finishes? (/.between n.enum b t2) - (/.between n.enum t1 t2))) + (_.coverage [/.meets?] + (/.meets? int_left int_right)) + (_.coverage [/.touches?] + (/.touches? int_left int_right)) + (_.coverage [/.starts?] + (/.starts? (/.between n.enum b t2) + (/.between n.enum b t1))) + (_.coverage [/.finishes?] + (/.finishes? (/.between n.enum b t2) + (/.between n.enum t1 t2))) ))) (def: nested @@ -199,24 +199,24 @@ _ (undefined)))))] (all _.and - (_.test "Every interval is nested into itself." - (/.nested? some_interval some_interval)) + (_.property "Every interval is nested into itself." + (/.nested? some_interval some_interval)) (let [small_inner (/.between n.enum x1 x2) large_inner (/.between n.enum x0 x3)] - (_.test "Inner intervals can be nested inside one another." - (and (/.nested? large_inner small_inner) - (not (/.nested? small_inner large_inner))))) + (_.property "Inner intervals can be nested inside one another." + (and (/.nested? large_inner small_inner) + (not (/.nested? small_inner large_inner))))) (let [small_outer (/.between n.enum x2 x1) large_outer (/.between n.enum x3 x0)] - (_.test "Outer intervals can be nested inside one another." - (and (/.nested? small_outer large_outer) - (not (/.nested? large_outer small_outer))))) + (_.property "Outer intervals can be nested inside one another." + (and (/.nested? small_outer large_outer) + (not (/.nested? large_outer small_outer))))) (let [left_inner (/.between n.enum x0 x1) right_inner (/.between n.enum x2 x3) outer (/.between n.enum x0 x3)] - (_.test "Inners can be nested inside outers." - (and (/.nested? outer left_inner) - (/.nested? outer right_inner)))) + (_.property "Inners can be nested inside outers." + (and (/.nested? outer left_inner) + (/.nested? outer right_inner)))) ))) (def: overlap @@ -233,19 +233,19 @@ _ (undefined)))))] (all _.and - (_.test "No interval overlaps with itself." - (not (/.overlaps? some_interval some_interval))) + (_.property "No interval overlaps with itself." + (not (/.overlaps? some_interval some_interval))) (let [left_inner (/.between n.enum x0 x2) right_inner (/.between n.enum x1 x3)] - (_.test "Inner intervals can overlap one another." - (and (/.overlaps? left_inner right_inner) - (/.overlaps? right_inner left_inner)))) + (_.property "Inner intervals can overlap one another." + (and (/.overlaps? left_inner right_inner) + (/.overlaps? right_inner left_inner)))) (let [left_inner (/.between n.enum x0 x2) right_inner (/.between n.enum x1 x3) outer (/.between n.enum x1 x2)] - (_.test "Inners can overlap outers." - (and (/.overlaps? outer left_inner) - (/.overlaps? outer right_inner)))) + (_.property "Inners can overlap outers." + (and (/.overlaps? outer left_inner) + (/.overlaps? outer right_inner)))) ))) (def: .public test diff --git a/stdlib/source/test/lux/abstract/mix.lux b/stdlib/source/test/lux/abstract/mix.lux index c07fc0036..96a870aa3 100644 --- a/stdlib/source/test/lux/abstract/mix.lux +++ b/stdlib/source/test/lux/abstract/mix.lux @@ -20,7 +20,7 @@ [samples (random.list 10 random.nat)] (<| (_.covering /._) (all _.and - (_.cover [/.with_monoid] - (n.= (# list.mix mix (# n.addition composite) (# n.addition identity) samples) - (/.with_monoid n.addition list.mix samples))) + (_.coverage [/.with_monoid] + (n.= (# list.mix mix (# n.addition composite) (# n.addition identity) samples) + (/.with_monoid n.addition list.mix samples))) )))) diff --git a/stdlib/source/test/lux/abstract/monad.lux b/stdlib/source/test/lux/abstract/monad.lux index dbd7cf10e..91cdf402f 100644 --- a/stdlib/source/test/lux/abstract/monad.lux +++ b/stdlib/source/test/lux/abstract/monad.lux @@ -20,45 +20,45 @@ poly (random.list 10 random.nat)] (<| (_.covering /._) (all _.and - (_.cover [/.do] - (n.= (++ mono) - (is (Identity Nat) - (/.do identity.monad - [sample (in mono)] - (in (++ sample)))))) - (_.cover [/.then] - (n.= (++ mono) - (is (Identity Nat) - (/.then identity.monad - (|>> ++ (# identity.monad in)) - (# identity.monad in mono))))) - (_.cover [/.all] - (# (list.equivalence n.equivalence) = - (list#each ++ poly) - (|> poly - (list#each (|>> ++ (# identity.monad in))) - (is (List (Identity Nat))) - (/.all identity.monad) - (is (Identity (List Nat)))))) - (_.cover [/.each] - (# (list.equivalence n.equivalence) = - (list#each ++ poly) - (|> poly - (/.each identity.monad (|>> ++ (# identity.monad in))) - (is (Identity (List Nat)))))) - (_.cover [/.only] - (# (list.equivalence n.equivalence) = - (list.only n.even? poly) - (|> poly - (/.only identity.monad (|>> n.even? (# identity.monad in))) - (is (Identity (List Nat)))))) - (_.cover [/.mix] - (n.= (list#mix n.+ 0 poly) - (|> poly - (/.mix identity.monad - (function (_ part whole) - (# identity.monad in - (n.+ part whole))) - 0) - (is (Identity Nat))))) + (_.coverage [/.do] + (n.= (++ mono) + (is (Identity Nat) + (/.do identity.monad + [sample (in mono)] + (in (++ sample)))))) + (_.coverage [/.then] + (n.= (++ mono) + (is (Identity Nat) + (/.then identity.monad + (|>> ++ (# identity.monad in)) + (# identity.monad in mono))))) + (_.coverage [/.all] + (# (list.equivalence n.equivalence) = + (list#each ++ poly) + (|> poly + (list#each (|>> ++ (# identity.monad in))) + (is (List (Identity Nat))) + (/.all identity.monad) + (is (Identity (List Nat)))))) + (_.coverage [/.each] + (# (list.equivalence n.equivalence) = + (list#each ++ poly) + (|> poly + (/.each identity.monad (|>> ++ (# identity.monad in))) + (is (Identity (List Nat)))))) + (_.coverage [/.only] + (# (list.equivalence n.equivalence) = + (list.only n.even? poly) + (|> poly + (/.only identity.monad (|>> n.even? (# identity.monad in))) + (is (Identity (List Nat)))))) + (_.coverage [/.mix] + (n.= (list#mix n.+ 0 poly) + (|> poly + (/.mix identity.monad + (function (_ part whole) + (# identity.monad in + (n.+ part whole))) + 0) + (is (Identity Nat))))) )))) diff --git a/stdlib/source/test/lux/abstract/monoid.lux b/stdlib/source/test/lux/abstract/monoid.lux index 4f48cd643..c52ebcc36 100644 --- a/stdlib/source/test/lux/abstract/monoid.lux +++ b/stdlib/source/test/lux/abstract/monoid.lux @@ -23,11 +23,11 @@ intR random.int] (<| (_.covering /._) (all _.and - (_.cover [/.and] - (let [[natLR intLR] (# (/.and nat.addition int.multiplication) composite - [natL intL] [natR intR])] - (and (nat.= (# nat.addition composite natL natR) - natLR) - (int.= (# int.multiplication composite intL intR) - intLR)))) + (_.coverage [/.and] + (let [[natLR intLR] (# (/.and nat.addition int.multiplication) composite + [natL intL] [natR intR])] + (and (nat.= (# nat.addition composite natL natR) + natLR) + (int.= (# int.multiplication composite intL intR) + intLR)))) )))) diff --git a/stdlib/source/test/lux/abstract/order.lux b/stdlib/source/test/lux/abstract/order.lux index a4a500370..e6d30b8f9 100644 --- a/stdlib/source/test/lux/abstract/order.lux +++ b/stdlib/source/test/lux/abstract/order.lux @@ -36,20 +36,20 @@ (all _.and (_.for [/.functor] ($contravariant.spec equivalence n.order /.functor)) - (_.cover [/.Choice /.min /.max] - (n.< (/.max n.order left right) - (/.min n.order left right))) - (_.cover [/.Comparison /.>] - (not (bit#= (n.< left right) - (/.> n.order left right)))) - (_.cover [/.<=] - (and (/.<= n.order left left) - (/.<= n.order right right) - (bit#= (# n.order < left right) - (/.<= n.order left right)))) - (_.cover [/.>=] - (and (/.>= n.order left left) - (/.>= n.order right right) - (bit#= (/.> n.order left right) - (/.>= n.order left right)))) + (_.coverage [/.Choice /.min /.max] + (n.< (/.max n.order left right) + (/.min n.order left right))) + (_.coverage [/.Comparison /.>] + (not (bit#= (n.< left right) + (/.> n.order left right)))) + (_.coverage [/.<=] + (and (/.<= n.order left left) + (/.<= n.order right right) + (bit#= (# n.order < left right) + (/.<= n.order left right)))) + (_.coverage [/.>=] + (and (/.>= n.order left left) + (/.>= n.order right right) + (bit#= (/.> n.order left right) + (/.>= n.order left right)))) ))) diff --git a/stdlib/source/test/lux/abstract/predicate.lux b/stdlib/source/test/lux/abstract/predicate.lux index d918d5fe7..78e6167a8 100644 --- a/stdlib/source/test/lux/abstract/predicate.lux +++ b/stdlib/source/test/lux/abstract/predicate.lux @@ -53,39 +53,39 @@ (_.for [/.intersection] ($monoid.spec equivalence /.intersection generator)))) - (_.cover [/.none] - (bit#= false (/.none sample))) - (_.cover [/.all] - (bit#= true (/.all sample))) - (_.cover [/.or] - (bit#= (/.all sample) - ((/.or /.none /.all) sample))) - (_.cover [/.and] - (bit#= (/.none sample) - ((/.and /.none /.all) sample))) - (_.cover [/.complement] - (and (not (bit#= (/.none sample) - ((/.complement /.none) sample))) - (not (bit#= (/.all sample) - ((/.complement /.all) sample))))) - (_.cover [/.difference] - (let [/2? (multiple? 2) - /3? (multiple? 3)] - (bit#= (and (/2? sample) - (not (/3? sample))) - ((/.difference /3? /2?) sample)))) - (_.cover [/.rec] - (let [even? (multiple? 2) - any_even? (is (/.Predicate (List Nat)) - (/.rec (function (_ again) - (function (_ values) - (case values - {.#End} - false + (_.coverage [/.none] + (bit#= false (/.none sample))) + (_.coverage [/.all] + (bit#= true (/.all sample))) + (_.coverage [/.or] + (bit#= (/.all sample) + ((/.or /.none /.all) sample))) + (_.coverage [/.and] + (bit#= (/.none sample) + ((/.and /.none /.all) sample))) + (_.coverage [/.complement] + (and (not (bit#= (/.none sample) + ((/.complement /.none) sample))) + (not (bit#= (/.all sample) + ((/.complement /.all) sample))))) + (_.coverage [/.difference] + (let [/2? (multiple? 2) + /3? (multiple? 3)] + (bit#= (and (/2? sample) + (not (/3? sample))) + ((/.difference /3? /2?) sample)))) + (_.coverage [/.rec] + (let [even? (multiple? 2) + any_even? (is (/.Predicate (List Nat)) + (/.rec (function (_ again) + (function (_ values) + (case values + {.#End} + false - {.#Item head tail} - (or (even? head) - (again tail)))))))] - (bit#= (list.any? even? samples) - (any_even? samples)))) + {.#Item head tail} + (or (even? head) + (again tail)))))))] + (bit#= (list.any? even? samples) + (any_even? samples)))) ))) diff --git a/stdlib/source/test/lux/control/concatenative.lux b/stdlib/source/test/lux/control/concatenative.lux index 8484cd1b8..1edbeccf4 100644 --- a/stdlib/source/test/lux/control/concatenative.lux +++ b/stdlib/source/test/lux/control/concatenative.lux @@ -25,70 +25,70 @@ [sample random.nat dummy random.nat] (`` (all _.and - (_.cover [/.push] - (n.= sample - (||> (/.push sample)))) - (_.cover [/.drop] - (n.= sample - (||> (/.push sample) - (/.push dummy) - /.drop))) - (_.cover [/.nip] - (n.= sample - (||> (/.push dummy) - (/.push sample) - /.nip))) - (_.cover [/.dup] - (||> (/.push sample) - /.dup - /.n/=)) - (_.cover [/.swap] - (n.= sample - (||> (/.push sample) - (/.push dummy) - /.swap))) - (_.cover [/.rotL] - (n.= sample - (||> (/.push sample) - (/.push dummy) - (/.push dummy) - /.rotL))) - (_.cover [/.rotR] - (n.= sample - (||> (/.push dummy) - (/.push sample) - (/.push dummy) - /.rotR))) - (_.cover [/.&&] - (let [[left right] (||> (/.push sample) - (/.push dummy) - /.&&)] - (and (n.= sample left) - (n.= dummy right)))) + (_.coverage [/.push] + (n.= sample + (||> (/.push sample)))) + (_.coverage [/.drop] + (n.= sample + (||> (/.push sample) + (/.push dummy) + /.drop))) + (_.coverage [/.nip] + (n.= sample + (||> (/.push dummy) + (/.push sample) + /.nip))) + (_.coverage [/.dup] + (||> (/.push sample) + /.dup + /.n/=)) + (_.coverage [/.swap] + (n.= sample + (||> (/.push sample) + (/.push dummy) + /.swap))) + (_.coverage [/.rotL] + (n.= sample + (||> (/.push sample) + (/.push dummy) + (/.push dummy) + /.rotL))) + (_.coverage [/.rotR] + (n.= sample + (||> (/.push dummy) + (/.push sample) + (/.push dummy) + /.rotR))) + (_.coverage [/.&&] + (let [[left right] (||> (/.push sample) + (/.push dummy) + /.&&)] + (and (n.= sample left) + (n.= dummy right)))) (~~ (template [<function> <tag>] - [(_.cover [<function>] - ((sum.equivalence n.= n.=) - {<tag> sample} - (||> (/.push sample) - <function>)))] + [(_.coverage [<function>] + ((sum.equivalence n.= n.=) + {<tag> sample} + (||> (/.push sample) + <function>)))] [/.||L .#Left] [/.||R .#Right])) - (_.cover [/.dip] - (n.= (++ sample) - (||> (/.push sample) - (/.push dummy) - (/.push (/.apply_1 ++)) - /.dip - /.drop))) - (_.cover [/.dip_2] - (n.= (++ sample) - (||> (/.push sample) - (/.push dummy) - (/.push dummy) - (/.push (/.apply_1 ++)) - /.dip_2 - /.drop /.drop))) + (_.coverage [/.dip] + (n.= (++ sample) + (||> (/.push sample) + (/.push dummy) + (/.push (/.apply_1 ++)) + /.dip + /.drop))) + (_.coverage [/.dip_2] + (n.= (++ sample) + (||> (/.push sample) + (/.push dummy) + (/.push dummy) + (/.push (/.apply_1 ++)) + /.dip_2 + /.drop /.drop))) )))) (template: (!numerical <=> <generator> <only> <arithmetic> <order>) @@ -100,19 +100,19 @@ subject <generator>] (`` (all _.and (~~ (template [<concatenative> <functional>] - [(_.cover [<concatenative>] - (<=> (<functional> parameter subject) - (||> (/.push subject) - (/.push parameter) - <concatenative>)))] + [(_.coverage [<concatenative>] + (<=> (<functional> parameter subject) + (||> (/.push subject) + (/.push parameter) + <concatenative>)))] <arithmetic>')) (~~ (template [<concatenative> <functional>] - [(_.cover [<concatenative>] - (bit#= (<functional> parameter subject) - (||> (/.push subject) - (/.push parameter) - <concatenative>)))] + [(_.coverage [<concatenative>] + (bit#= (<functional> parameter subject) + (||> (/.push subject) + (/.push parameter) + <concatenative>)))] <order>')) )))))]) @@ -146,153 +146,153 @@ |test| (is (/.=> [Nat] [Bit]) (/.apply_1 (|>> (n.- start) (n.< distance))))]] (all _.and - (_.cover [/.call /.apply_1] - (n.= (++ sample) - (||> (/.push sample) - (/.push (/.apply_1 ++)) - /.call))) - (_.cover [/.apply_2] - (n.= (n.+ sample sample) - (||> (/.push sample) - (/.push sample) - (/.push (/.apply_2 n.+)) - /.call))) - (_.cover [/.apply_3] - (n.= (all n.+ sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_3 (function (_ i0 i1 i2) - (all n.+ i0 i1 i2)))) - /.call))) - (_.cover [/.apply_4] - (n.= (all n.+ sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_4 (function (_ i0 i1 i2 i3) - (all n.+ i0 i1 i2 i3)))) - /.call))) - (_.cover [/.apply_5] - (n.= (all n.+ sample sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_5 (function (_ i0 i1 i2 i3 i4) - (all n.+ i0 i1 i2 i3 i4)))) - /.call))) - (_.cover [/.apply_6] - (n.= (all n.+ sample sample sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_6 (function (_ i0 i1 i2 i3 i4 i5) - (all n.+ i0 i1 i2 i3 i4 i5)))) - /.call))) - (_.cover [/.apply_7] - (n.= (all n.+ sample sample sample sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_7 (function (_ i0 i1 i2 i3 i4 i5 i6) - (all n.+ i0 i1 i2 i3 i4 i5 i6)))) - /.call))) - (_.cover [/.apply_8] - (n.= (all n.+ sample sample sample sample sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push (/.apply_8 (function (_ i0 i1 i2 i3 i4 i5 i6 i7) - (all n.+ i0 i1 i2 i3 i4 i5 i6 i7)))) - /.call))) - (_.cover [/.apply] - (n.= (all n.+ sample sample sample sample sample sample sample sample sample) - (||> (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push sample) - (/.push ((/.apply 9) (function (_ i0 i1 i2 i3 i4 i5 i6 i7 i8) - (all n.+ i0 i1 i2 i3 i4 i5 i6 i7 i8)))) - /.call))) - (_.cover [/.if] - (n.= (if choice - (++ sample) - (-- sample)) - (||> (/.push sample) - (/.push choice) - (/.push (/.apply_1 ++)) - (/.push (/.apply_1 --)) - /.if))) - (_.cover [/.loop] - (n.= (n.+ distance start) - (||> (/.push start) - (/.push (is (/.=> [Nat] [Nat Bit]) - (|>> |++| /.dup |test|))) - /.loop))) - (_.cover [/.while] - (n.= (n.+ distance start) - (||> (/.push start) - (/.push (is (/.=> [Nat] [Nat Bit]) - (|>> /.dup |test|))) - (/.push |++|) - /.while))) - (_.cover [/.do] - (n.= (++ sample) - (||> (/.push sample) - (/.push (is (/.=> [] [Bit]) - (|>> (/.push false)))) - (/.push |++|) - /.do /.while))) - (_.cover [/.compose] - (n.= (++ (++ sample)) - (||> (/.push sample) - (/.push |++|) - (/.push |++|) - /.compose - /.call))) - (_.cover [/.partial] - (n.= (n.+ sample sample) - (||> (/.push sample) - (/.push sample) - (/.push (/.apply_2 n.+)) - /.partial - /.call))) - (_.cover [/.when] - (n.= (if choice - (++ sample) - sample) - (||> (/.push sample) - (/.push choice) - (/.push (/.apply_1 ++)) - /.when))) - (_.cover [/.?] - (n.= (if choice - (++ sample) - (-- sample)) - (||> (/.push choice) - (/.push (++ sample)) - (/.push (-- sample)) - /.?))) + (_.coverage [/.call /.apply_1] + (n.= (++ sample) + (||> (/.push sample) + (/.push (/.apply_1 ++)) + /.call))) + (_.coverage [/.apply_2] + (n.= (n.+ sample sample) + (||> (/.push sample) + (/.push sample) + (/.push (/.apply_2 n.+)) + /.call))) + (_.coverage [/.apply_3] + (n.= (all n.+ sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_3 (function (_ i0 i1 i2) + (all n.+ i0 i1 i2)))) + /.call))) + (_.coverage [/.apply_4] + (n.= (all n.+ sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_4 (function (_ i0 i1 i2 i3) + (all n.+ i0 i1 i2 i3)))) + /.call))) + (_.coverage [/.apply_5] + (n.= (all n.+ sample sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_5 (function (_ i0 i1 i2 i3 i4) + (all n.+ i0 i1 i2 i3 i4)))) + /.call))) + (_.coverage [/.apply_6] + (n.= (all n.+ sample sample sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_6 (function (_ i0 i1 i2 i3 i4 i5) + (all n.+ i0 i1 i2 i3 i4 i5)))) + /.call))) + (_.coverage [/.apply_7] + (n.= (all n.+ sample sample sample sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_7 (function (_ i0 i1 i2 i3 i4 i5 i6) + (all n.+ i0 i1 i2 i3 i4 i5 i6)))) + /.call))) + (_.coverage [/.apply_8] + (n.= (all n.+ sample sample sample sample sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push (/.apply_8 (function (_ i0 i1 i2 i3 i4 i5 i6 i7) + (all n.+ i0 i1 i2 i3 i4 i5 i6 i7)))) + /.call))) + (_.coverage [/.apply] + (n.= (all n.+ sample sample sample sample sample sample sample sample sample) + (||> (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push sample) + (/.push ((/.apply 9) (function (_ i0 i1 i2 i3 i4 i5 i6 i7 i8) + (all n.+ i0 i1 i2 i3 i4 i5 i6 i7 i8)))) + /.call))) + (_.coverage [/.if] + (n.= (if choice + (++ sample) + (-- sample)) + (||> (/.push sample) + (/.push choice) + (/.push (/.apply_1 ++)) + (/.push (/.apply_1 --)) + /.if))) + (_.coverage [/.loop] + (n.= (n.+ distance start) + (||> (/.push start) + (/.push (is (/.=> [Nat] [Nat Bit]) + (|>> |++| /.dup |test|))) + /.loop))) + (_.coverage [/.while] + (n.= (n.+ distance start) + (||> (/.push start) + (/.push (is (/.=> [Nat] [Nat Bit]) + (|>> /.dup |test|))) + (/.push |++|) + /.while))) + (_.coverage [/.do] + (n.= (++ sample) + (||> (/.push sample) + (/.push (is (/.=> [] [Bit]) + (|>> (/.push false)))) + (/.push |++|) + /.do /.while))) + (_.coverage [/.compose] + (n.= (++ (++ sample)) + (||> (/.push sample) + (/.push |++|) + (/.push |++|) + /.compose + /.call))) + (_.coverage [/.partial] + (n.= (n.+ sample sample) + (||> (/.push sample) + (/.push sample) + (/.push (/.apply_2 n.+)) + /.partial + /.call))) + (_.coverage [/.when] + (n.= (if choice + (++ sample) + sample) + (||> (/.push sample) + (/.push choice) + (/.push (/.apply_1 ++)) + /.when))) + (_.coverage [/.?] + (n.= (if choice + (++ sample) + (-- sample)) + (||> (/.push choice) + (/.push (++ sample)) + (/.push (-- sample)) + /.?))) ))) (word: square @@ -305,10 +305,10 @@ Test (do random.monad [sample random.nat] - (_.cover [/.word: /.=> /.||>] - (n.= (n.* sample sample) - (||> (/.push sample) - ..square))))) + (_.coverage [/.word: /.=> /.||>] + (n.= (n.* sample sample) + (||> (/.push sample) + ..square))))) (def: .public test Test diff --git a/stdlib/source/test/lux/control/concurrency/actor.lux b/stdlib/source/test/lux/control/concurrency/actor.lux index f76e6a41d..fd99d624d 100644 --- a/stdlib/source/test/lux/control/concurrency/actor.lux +++ b/stdlib/source/test/lux/control/concurrency/actor.lux @@ -58,29 +58,29 @@ (<| (_.covering /._) (_.for [/.Actor]) (all _.and - (_.cover [/.alive?] - (io.run! (do io.monad - [actor (/.spawn! /.default 0)] - (/.alive? actor)))) + (_.coverage [/.alive?] + (io.run! (do io.monad + [actor (/.spawn! /.default 0)] + (/.alive? actor)))) - (_.cover [/.poison!] - (let [poisoned_actors_die! - (io.run! (do io.monad - [actor (/.spawn! /.default 0) - poisoned? (/.poison! actor) - alive? (/.alive? actor)] - (in (and (..mailed? poisoned?) - (not alive?))))) - - cannot_poison_more_than_once! - (io.run! (do io.monad - [actor (/.spawn! /.default 0) - first_time? (/.poison! actor) - second_time? (/.poison! actor)] - (in (and (..mailed? first_time?) - (not (..mailed? second_time?))))))] - (and poisoned_actors_die! - cannot_poison_more_than_once!))) + (_.coverage [/.poison!] + (let [poisoned_actors_die! + (io.run! (do io.monad + [actor (/.spawn! /.default 0) + poisoned? (/.poison! actor) + alive? (/.alive? actor)] + (in (and (..mailed? poisoned?) + (not alive?))))) + + cannot_poison_more_than_once! + (io.run! (do io.monad + [actor (/.spawn! /.default 0) + first_time? (/.poison! actor) + second_time? (/.poison! actor)] + (in (and (..mailed? first_time?) + (not (..mailed? second_time?))))))] + (and poisoned_actors_die! + cannot_poison_more_than_once!))) (let [[read write] (is [(Async Text) (Resolver Text)] (async.async []))] @@ -103,35 +103,35 @@ (/.poison! actor))) _ (async.delay 100) result (async.future (async.value read))] - (_.cover' [/.poisoned] - (case result - {.#Some error} - (exception.match? /.poisoned error) + (_.coverage' [/.poisoned] + (case result + {.#Some error} + (exception.match? /.poisoned error) - {.#None} - false))))) + {.#None} + false))))) (in (do async.monad [sent? (async.future (do io.monad [actor (/.spawn! /.default 0) sent? (/.mail! ++! actor)] (in (..mailed? sent?))))] - (_.cover' [/.Behavior /.Mail - /.default /.spawn! /.mail!] - sent?))) + (_.coverage' [/.Behavior /.Mail + /.default /.spawn! /.mail!] + sent?))) (in (do async.monad [result (async.future (do io.monad [counter (/.spawn! /.default 0) _ (/.poison! counter)] (/.mail! ++! counter)))] - (_.cover' [/.dead] - (case result - {try.#Success outcome} - false + (_.coverage' [/.dead] + (case result + {try.#Success outcome} + false - {try.#Failure error} - (exception.match? /.dead error))))) + {try.#Failure error} + (exception.match? /.dead error))))) (let [die! (is (/.Mail Nat) (function (_ state actor) @@ -143,17 +143,17 @@ alive? (/.alive? actor) obituary (/.obituary' actor)] (in {try.#Success [actor sent? alive? obituary]})))] - (_.cover' [/.Obituary /.obituary'] - (case result - (pattern {try.#Success [actor sent? alive? {.#Some [error state (list single_pending_message)]}]}) - (and (..mailed? sent?) - (not alive?) - (exception.match? ..got_wrecked error) - (n.= initial_state state) - (same? die! single_pending_message)) - - _ - false))))) + (_.coverage' [/.Obituary /.obituary'] + (case result + (pattern {try.#Success [actor sent? alive? {.#Some [error state (list single_pending_message)]}]}) + (and (..mailed? sent?) + (not alive?) + (exception.match? ..got_wrecked error) + (n.= initial_state state) + (same? die! single_pending_message)) + + _ + false))))) (in (do async.monad [counter (async.future (/.spawn! ..counter 0)) @@ -164,13 +164,13 @@ (in (and (n.= 1 output_1) (n.= 2 output_2) (n.= 3 output_3))))] - (_.cover' [/.Message /.actor: /.message: /.tell!] - (case result - {try.#Success outcome} - outcome + (_.coverage' [/.Message /.actor: /.message: /.tell!] + (case result + {try.#Success outcome} + outcome - {try.#Failure error} - false)))) + {try.#Failure error} + false)))) (in (do async.monad [verdict (async.future @@ -194,8 +194,8 @@ _ false)))))] - (_.cover' [/.actor] - verdict))) + (_.coverage' [/.actor] + verdict))) (do ! [num_events (# ! each (|>> (n.% 10) ++) random.nat) @@ -223,6 +223,6 @@ (in agent))) _ (/.obituary agent) actual (async.future (atom.read! sink))] - (_.cover' [/.Stop /.observe! /.obituary] - (# (list.equivalence n.equivalence) = expected (sequence.list actual)))))) + (_.coverage' [/.Stop /.observe! /.obituary] + (# (list.equivalence n.equivalence) = expected (sequence.list actual)))))) )))) diff --git a/stdlib/source/test/lux/control/concurrency/async.lux b/stdlib/source/test/lux/control/concurrency/async.lux index e43619f2c..0e59faf3d 100644 --- a/stdlib/source/test/lux/control/concurrency/async.lux +++ b/stdlib/source/test/lux/control/concurrency/async.lux @@ -71,97 +71,97 @@ (/.async []))] resolved? (/.future (resolver expected)) actual async] - (_.cover' [/.Async /.Resolver /.async] - (and resolved? - (n.= expected actual))))) + (_.coverage' [/.Async /.Resolver /.async] + (and resolved? + (n.= expected actual))))) (in (do /.monad [actual (/.resolved expected)] - (_.cover' [/.resolved] - (n.= expected actual)))) + (_.coverage' [/.resolved] + (n.= expected actual)))) (in (do /.monad [actual (/.future (io.io expected))] - (_.cover' [/.future] - (n.= expected actual)))) + (_.coverage' [/.future] + (n.= expected actual)))) (in (do /.monad [pre (/.future instant.now) actual (/.schedule! waiting_time (io.io expected)) post (/.future instant.now)] - (_.cover' [/.schedule!] - (and (n.= expected actual) - (i.>= (.int waiting_time) - (duration.millis (instant.span pre post))))))) + (_.coverage' [/.schedule!] + (and (n.= expected actual) + (i.>= (.int waiting_time) + (duration.millis (instant.span pre post))))))) (in (do /.monad [pre (/.future instant.now) _ (/.delay waiting_time) post (/.future instant.now)] - (_.cover' [/.delay] - (i.>= (.int waiting_time) - (duration.millis (instant.span pre post)))))) + (_.coverage' [/.delay] + (i.>= (.int waiting_time) + (duration.millis (instant.span pre post)))))) (in (do /.monad [[leftA rightA] (/.and (/.future (io.io leftE)) (/.future (io.io rightE)))] - (_.cover' [/.and] - (n.= (n.+ leftE rightE) - (n.+ leftA rightA))))) + (_.coverage' [/.and] + (n.= (n.+ leftE rightE) + (n.+ leftA rightA))))) (in (do /.monad [pre (/.future instant.now) actual (/.after waiting_time expected) post (/.future instant.now)] - (_.cover' [/.after] - (and (n.= expected actual) - (i.>= (.int waiting_time) - (duration.millis (instant.span pre post))))))) + (_.coverage' [/.after] + (and (n.= expected actual) + (i.>= (.int waiting_time) + (duration.millis (instant.span pre post))))))) (in (do /.monad [?left (/.or (in leftE) (/.after waiting_time dummy)) ?right (/.or (/.after waiting_time dummy) (in rightE))] - (_.cover' [/.or] - (case [?left ?right] - [{.#Left leftA} {.#Right rightA}] - (n.= (n.+ leftE rightE) - (n.+ leftA rightA)) + (_.coverage' [/.or] + (case [?left ?right] + [{.#Left leftA} {.#Right rightA}] + (n.= (n.+ leftE rightE) + (n.+ leftA rightA)) - _ - false)))) + _ + false)))) (in (do /.monad [leftA (/.either (in leftE) (/.after waiting_time dummy)) rightA (/.either (/.after waiting_time dummy) (in rightE))] - (_.cover' [/.either] - (n.= (n.+ leftE rightE) - (n.+ leftA rightA))))) + (_.coverage' [/.either] + (n.= (n.+ leftE rightE) + (n.+ leftA rightA))))) (in (do /.monad [?actual (/.future (/.value (/.resolved expected))) .let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)] (/.async []))] ?never (/.future (/.value async))] - (_.cover' [/.value] - (case [?actual ?never] - [{.#Some actual} {.#None}] - (n.= expected actual) + (_.coverage' [/.value] + (case [?actual ?never] + [{.#Some actual} {.#None}] + (n.= expected actual) - _ - false)))) + _ + false)))) (in (do /.monad [yep (/.future (/.resolved? (/.resolved expected))) .let [[async resolver] (is [(/.Async Nat) (/.Resolver Nat)] (/.async []))] nope (/.future (/.resolved? async))] - (_.cover' [/.resolved?] - (and yep - (not nope))))) + (_.coverage' [/.resolved?] + (and yep + (not nope))))) (in (do /.monad [?none (/.within 0 (/.after waiting_time dummy)) ?actual (/.within waiting_time (in expected))] - (_.cover' [/.within] - (case [?none ?actual] - [{.#None} {.#Some actual}] - (n.= expected actual) + (_.coverage' [/.within] + (case [?none ?actual] + [{.#None} {.#Some actual}] + (n.= expected actual) - _ - false)))) + _ + false)))) (in (do /.monad [.let [box (is (Atom Nat) (atom.atom dummy))] @@ -169,6 +169,6 @@ (atom.write! value box)) (/.resolved expected))) actual (/.future (atom.read! box))] - (_.cover' [/.upon!] - (n.= expected actual)))) + (_.coverage' [/.upon!] + (n.= expected actual)))) )))) diff --git a/stdlib/source/test/lux/control/concurrency/atom.lux b/stdlib/source/test/lux/control/concurrency/atom.lux index cda6a0737..04b80f7ca 100644 --- a/stdlib/source/test/lux/control/concurrency/atom.lux +++ b/stdlib/source/test/lux/control/concurrency/atom.lux @@ -20,45 +20,45 @@ (do random.monad [expected random.nat .let [box (/.atom expected)]] - (_.cover [/.Atom /.atom /.read!] - (io.run! - (do io.monad - [actual (/.read! box)] - (in (same? expected actual)))))) + (_.coverage [/.Atom /.atom /.read!] + (io.run! + (do io.monad + [actual (/.read! box)] + (in (same? expected actual)))))) (do random.monad [target random.nat unknown (random.only (|>> (same? target) not) random.nat) expected random.nat .let [box (/.atom target)]] - (_.cover [/.compare_and_swap!] - (io.run! - (do io.monad - [swapped_unknown? (/.compare_and_swap! unknown expected box) - swapped_target? (/.compare_and_swap! target expected box) - actual (/.read! box)] - (in (and (not swapped_unknown?) - swapped_target? - (same? expected actual))))))) + (_.coverage [/.compare_and_swap!] + (io.run! + (do io.monad + [swapped_unknown? (/.compare_and_swap! unknown expected box) + swapped_target? (/.compare_and_swap! target expected box) + actual (/.read! box)] + (in (and (not swapped_unknown?) + swapped_target? + (same? expected actual))))))) (do random.monad [init random.nat shift random.nat .let [box (/.atom init)]] - (_.cover [/.update!] - (io.run! - (do io.monad - [[pre post] (/.update! (n.+ shift) box)] - (in (and (same? init pre) - (n.= (n.+ shift init) - post))))))) + (_.coverage [/.update!] + (io.run! + (do io.monad + [[pre post] (/.update! (n.+ shift) box)] + (in (and (same? init pre) + (n.= (n.+ shift init) + post))))))) (do random.monad [pre random.nat post random.nat .let [box (/.atom pre)]] - (_.cover [/.write!] - (io.run! - (do io.monad - [old (/.write! post box) - new (/.read! box)] - (in (and (same? pre old) - (same? post new))))))) + (_.coverage [/.write!] + (io.run! + (do io.monad + [old (/.write! post box) + new (/.read! box)] + (in (and (same? pre old) + (same? post new))))))) ))) diff --git a/stdlib/source/test/lux/control/concurrency/frp.lux b/stdlib/source/test/lux/control/concurrency/frp.lux index 67255c72d..c5c84f492 100644 --- a/stdlib/source/test/lux/control/concurrency/frp.lux +++ b/stdlib/source/test/lux/control/concurrency/frp.lux @@ -85,62 +85,62 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.Channel /.Sink /.channel] - (case (io.run! - (do (try.with io.monad) - [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] - (/.channel []))] - _ (# sink feed sample) - _ (# sink close)] - (in channel))) - {try.#Success channel} - (io.run! - (do io.monad - [?actual (async.value channel)] - (in (case ?actual - {.#Some {.#Some [actual _]}} - (n.= sample (variance.read actual)) - - _ - false)))) - - {try.#Failure error} - false)) - (_.cover [/.channel_is_already_closed] - (case (io.run! - (do (try.with io.monad) - [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] - (/.channel []))] - _ (# sink close)] - (# sink feed sample))) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.channel_is_already_closed error))) + (_.coverage [/.Channel /.Sink /.channel] + (case (io.run! + (do (try.with io.monad) + [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] + (/.channel []))] + _ (# sink feed sample) + _ (# sink close)] + (in channel))) + {try.#Success channel} + (io.run! + (do io.monad + [?actual (async.value channel)] + (in (case ?actual + {.#Some {.#Some [actual _]}} + (n.= sample (variance.read actual)) + + _ + false)))) + + {try.#Failure error} + false)) + (_.coverage [/.channel_is_already_closed] + (case (io.run! + (do (try.with io.monad) + [.let [[channel sink] (is [(/.Channel Nat) (/.Sink Nat)] + (/.channel []))] + _ (# sink close)] + (# sink feed sample))) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.channel_is_already_closed error))) (in (do async.monad [output (|> sample async.resolved /.of_async /.list)] - (_.cover' [/.of_async /.list] - (list#= (list sample) - output)))) + (_.coverage' [/.of_async /.list] + (list#= (list sample) + output)))) (in (do async.monad [output (|> inputs (/.sequential 0) /.list)] - (_.cover' [/.sequential] - (list#= inputs - output)))) + (_.coverage' [/.sequential] + (list#= inputs + output)))) (in (do async.monad [output (|> inputs (/.sequential 0) (/.only n.even?) /.list)] - (_.cover' [/.only] - (list#= (list.only n.even? inputs) - output)))) + (_.coverage' [/.only] + (list#= (list.only n.even? inputs) + output)))) (in (do [! async.monad] [.let [[?signal !signal] (is [(async.Async Any) (async.Resolver Any)] (async.async [])) @@ -162,16 +162,16 @@ atom.read! async.future (# ! each sequence.list))] - (_.cover' [/.Subscriber /.subscribe!] - (list#= inputs listened)))) + (_.coverage' [/.Subscriber /.subscribe!] + (list#= inputs listened)))) (in (do async.monad [actual (/.mix (function (_ input total) (async.resolved (n.+ input total))) 0 (/.sequential 0 inputs))] - (_.cover' [/.mix] - (n.= (list#mix n.+ 0 inputs) - actual)))) + (_.coverage' [/.mix] + (n.= (list#mix n.+ 0 inputs) + actual)))) (in (do async.monad [actual (|> inputs (/.sequential 0) @@ -179,9 +179,9 @@ (async.resolved (n.+ input total))) 0) /.list)] - (_.cover' [/.mixes] - (list#= (list.mixes n.+ 0 inputs) - actual)))) + (_.coverage' [/.mixes] + (list#= (list.mixes n.+ 0 inputs) + actual)))) (in (do async.monad [actual (|> (list distinct/0 distinct/0 distinct/0 distinct/1 @@ -189,9 +189,9 @@ (/.sequential 0) (/.distinct n.equivalence) /.list)] - (_.cover' [/.distinct] - (list#= (list distinct/0 distinct/1 distinct/2) - actual)))) + (_.coverage' [/.distinct] + (list#= (list distinct/0 distinct/1 distinct/2) + actual)))) (do ! [polling_delay (# ! each (|>> (n.% 10) ++) random.nat) amount_of_polls (# ! each (|>> (n.% 10) ++) random.nat)] @@ -203,13 +203,13 @@ enough_polls! (n.= amount_of_polls (list.size actual))]] - (_.cover' [/.poll] - (and correct_values! - enough_polls!)))) + (_.coverage' [/.poll] + (and correct_values! + enough_polls!)))) (in (do [! async.monad] [actual (..take_amount amount_of_polls (/.periodic polling_delay))] - (_.cover' [/.periodic] - (n.= amount_of_polls (list.size actual))))))) + (_.coverage' [/.periodic] + (n.= amount_of_polls (list.size actual))))))) (in (do async.monad [.let [max_iterations 10] actual (|> [0 sample] @@ -220,8 +220,8 @@ current]} {.#None})))) /.list)] - (_.cover' [/.iterations] - (and (n.= max_iterations (list.size actual)) - (list#= (list.mixes n.+ sample (list.repeated (-- max_iterations) shift)) - actual))))) + (_.coverage' [/.iterations] + (and (n.= max_iterations (list.size actual)) + (list#= (list.mixes n.+ sample (list.repeated (-- max_iterations) shift)) + actual))))) ))))) diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux index 252f557b9..275613ebd 100644 --- a/stdlib/source/test/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux @@ -42,26 +42,26 @@ .let [semaphore (/.semaphore initial_open_positions)]] (in (do async.monad [result (async.within ..delay (/.wait! semaphore))] - (_.cover' [/.semaphore] - (case result - {.#Some _} - true + (_.coverage' [/.semaphore] + (case result + {.#Some _} + true - {.#None} - false))))) + {.#None} + false))))) (do [! random.monad] [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1)))) .let [semaphore (/.semaphore initial_open_positions)]] (in (do [! async.monad] [_ (monad.each ! /.wait! (list.repeated initial_open_positions semaphore)) result (async.within ..delay (/.wait! semaphore))] - (_.cover' [/.wait!] - (case result - {.#Some _} - false + (_.coverage' [/.wait!] + (case result + {.#Some _} + false - {.#None} - true))))) + {.#None} + true))))) (do [! random.monad] [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1)))) .let [semaphore (/.semaphore initial_open_positions)]] @@ -71,25 +71,25 @@ result/0 (async.within ..delay block) open_positions (/.signal! semaphore) result/1 (async.within ..delay block)] - (_.cover' [/.signal!] - (case [result/0 result/1 open_positions] - [{.#None} {.#Some _} {try.#Success +0}] - true + (_.coverage' [/.signal!] + (case [result/0 result/1 open_positions] + [{.#None} {.#Some _} {try.#Success +0}] + true - _ - false))))) + _ + false))))) (do [! random.monad] [initial_open_positions (|> random.nat (# ! each (|>> (n.% 10) (n.max 1)))) .let [semaphore (/.semaphore initial_open_positions)]] (in (do async.monad [outcome (/.signal! semaphore)] - (_.cover' [/.semaphore_is_maxed_out] - (case outcome - {try.#Failure error} - (exception.match? /.semaphore_is_maxed_out error) + (_.coverage' [/.semaphore_is_maxed_out] + (case outcome + {try.#Failure error} + (exception.match? /.semaphore_is_maxed_out error) - _ - false))))) + _ + false))))) ))) (def: mutex @@ -122,11 +122,11 @@ [_ processA _ processB .let [outcome (io.run! (atom.read! resource))]] - (_.cover' [/.mutex /.synchronize!] - (or (text#= (format expected_As expected_Bs) - outcome) - (text#= (format expected_Bs expected_As) - outcome)))))) + (_.coverage' [/.mutex /.synchronize!] + (or (text#= (format expected_As expected_Bs) + outcome) + (text#= (format expected_Bs expected_As) + outcome)))))) ))) (def: (waiter resource barrier id) @@ -142,17 +142,17 @@ (all _.and (do random.monad [raw random.nat] - (_.cover [/.Limit /.limit] - (case [raw (/.limit raw)] - [0 {.#None}] - true - - [_ {.#Some limit}] - (and (n.> 0 raw) - (n.= raw (refinement.value limit))) + (_.coverage [/.Limit /.limit] + (case [raw (/.limit raw)] + [0 {.#None}] + true + + [_ {.#Some limit}] + (and (n.> 0 raw) + (n.= raw (refinement.value limit))) - _ - false))) + _ + false))) (do [! random.monad] [limit (# ! each (|>> (n.% 9) ++) random.nat) .let [barrier (/.barrier (maybe.trusted (/.limit limit))) @@ -170,11 +170,11 @@ (waiter resource barrier id)))) (monad.all !)) .let [outcome (io.run! (atom.read! resource))]] - (_.cover' [/.barrier /.block!] - (and (text.ends_with? expected_ending outcome) - (list.every? (function (_ id) - (text.contains? (%.nat id) outcome)) - expected_ids)))))) + (_.coverage' [/.barrier /.block!] + (and (text.ends_with? expected_ending outcome) + (list.every? (function (_ id) + (text.contains? (%.nat id) outcome)) + expected_ids)))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/control/concurrency/stm.lux b/stdlib/source/test/lux/control/concurrency/stm.lux index 2e1f9586f..6b0e64a57 100644 --- a/stdlib/source/test/lux/control/concurrency/stm.lux +++ b/stdlib/source/test/lux/control/concurrency/stm.lux @@ -52,12 +52,12 @@ (in (do async.monad [actual (/.commit! (# /.monad in expected))] - (_.cover' [/.commit!] - (n.= expected actual)))) + (_.coverage' [/.commit!] + (n.= expected actual)))) (in (do async.monad [actual (/.commit! (/.read (/.var expected)))] - (_.cover' [/.Var /.var /.read] - (n.= expected actual)))) + (_.coverage' [/.Var /.var /.read] + (n.= expected actual)))) (in (do async.monad [actual (let [box (/.var dummy)] (/.commit! (do /.monad @@ -68,17 +68,17 @@ [_ (/.write expected box) actual (/.read box)] (in (n.= expected actual)))))] - (_.cover' [/.write] - (and (n.= expected actual) - verdict)))) + (_.coverage' [/.write] + (and (n.= expected actual) + verdict)))) (in (do async.monad [.let [box (/.var dummy)] output (/.commit! (do /.monad [_ (/.update (n.+ expected) box)] (/.read box)))] - (_.cover' [/.update] - (n.= (n.+ expected dummy) - output)))) + (_.coverage' [/.update] + (n.= (n.+ expected dummy) + output)))) (in (do async.monad [.let [box (/.var dummy) [follower sink] (io.run! (/.changes box))] @@ -87,17 +87,17 @@ _ (async.future (# sink close)) _ (/.commit! (/.update (n.* 3) box)) changes (frp.list follower)] - (_.cover' [/.changes] - (# (list.equivalence n.equivalence) = - (list expected (n.* 2 expected)) - changes)))) + (_.coverage' [/.changes] + (# (list.equivalence n.equivalence) = + (list expected (n.* 2 expected)) + changes)))) (in (let [var (/.var 0)] (do [! async.monad] [_ (|> (list.repeated iterations_per_process []) (list#each (function (_ _) (/.commit! (/.update ++ var)))) (monad.all !)) cummulative (/.commit! (/.read var))] - (_.cover' [/.STM] - (n.= iterations_per_process - cummulative))))) + (_.coverage' [/.STM] + (n.= iterations_per_process + cummulative))))) )))) diff --git a/stdlib/source/test/lux/control/concurrency/thread.lux b/stdlib/source/test/lux/control/concurrency/thread.lux index 4b3e41c37..cebb90dd8 100644 --- a/stdlib/source/test/lux/control/concurrency/thread.lux +++ b/stdlib/source/test/lux/control/concurrency/thread.lux @@ -29,8 +29,8 @@ delay (# ! each (|>> (n.% 5) (n.+ 5)) random.nat)] (all _.and - (_.cover [/.parallelism] - (n.> 0 /.parallelism)) + (_.coverage [/.parallelism] + (n.> 0 /.parallelism)) (in (do async.monad [reference_time (async.future instant.now) .let [box (atom.atom [reference_time dummy])] @@ -40,13 +40,13 @@ (atom.write! [execution_time expected] box)))) _ (async.delay (n.* 2 delay)) [execution_time actual] (async.future (atom.read! box))] - (_.cover' [/.schedule!] - (let [expected_delay! - (i.>= (.int delay) - (duration.millis (instant.span reference_time execution_time))) + (_.coverage' [/.schedule!] + (let [expected_delay! + (i.>= (.int delay) + (duration.millis (instant.span reference_time execution_time))) - correct_value! - (n.= expected actual)] - (and expected_delay! - correct_value!))))) + correct_value! + (n.= expected actual)] + (and expected_delay! + correct_value!))))) )))) diff --git a/stdlib/source/test/lux/control/continuation.lux b/stdlib/source/test/lux/control/continuation.lux index 77dffb213..062142453 100644 --- a/stdlib/source/test/lux/control/continuation.lux +++ b/stdlib/source/test/lux/control/continuation.lux @@ -44,53 +44,53 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.result] - (n.= sample (/.result (_#in sample)))) - (_.cover [/.with_current] - (n.= (n.* 2 sample) - (/.result (do [! /.monad] - [value (/.with_current - (function (_ k) - (do ! - [temp (k sample)] - ... If this code where to run, - ... the output would be - ... (n.* 4 sample) - (k temp))))] - (in (n.* 2 value)))))) - (_.cover [/.portal] - (n.= (n.+ 100 sample) - (/.result (do /.monad - [[restart [output idx]] (/.portal [sample 0])] - (if (n.< 10 idx) - (restart [(n.+ 10 output) (++ idx)]) - (in output)))))) - (_.cover [/.shift /.reset] - (let [(open "_#[0]") /.monad - (open "list#[0]") (list.equivalence n.equivalence) - visit (is (-> (List Nat) - (/.Cont (List Nat) (List Nat))) - (function (visit xs) - (case xs - {.#End} - (_#in {.#End}) + (_.coverage [/.result] + (n.= sample (/.result (_#in sample)))) + (_.coverage [/.with_current] + (n.= (n.* 2 sample) + (/.result (do [! /.monad] + [value (/.with_current + (function (_ k) + (do ! + [temp (k sample)] + ... If this code where to run, + ... the output would be + ... (n.* 4 sample) + (k temp))))] + (in (n.* 2 value)))))) + (_.coverage [/.portal] + (n.= (n.+ 100 sample) + (/.result (do /.monad + [[restart [output idx]] (/.portal [sample 0])] + (if (n.< 10 idx) + (restart [(n.+ 10 output) (++ idx)]) + (in output)))))) + (_.coverage [/.shift /.reset] + (let [(open "_#[0]") /.monad + (open "list#[0]") (list.equivalence n.equivalence) + visit (is (-> (List Nat) + (/.Cont (List Nat) (List Nat))) + (function (visit xs) + (case xs + {.#End} + (_#in {.#End}) - {.#Item x xs'} - (do [! /.monad] - [output (/.shift (function (_ k) - (do ! - [tail (k xs')] - (in {.#Item x tail}))))] - (visit output)))))] - (list#= elems - (/.result (/.reset (visit elems)))))) - (_.cover [/.continued] - (/.continued (same? sample) - (is (/.Cont Nat Bit) - (function (_ next) - (next sample))))) - (_.cover [/.pending] - (/.continued (same? sample) - (is (/.Cont Nat Bit) - (/.pending sample)))) + {.#Item x xs'} + (do [! /.monad] + [output (/.shift (function (_ k) + (do ! + [tail (k xs')] + (in {.#Item x tail}))))] + (visit output)))))] + (list#= elems + (/.result (/.reset (visit elems)))))) + (_.coverage [/.continued] + (/.continued (same? sample) + (is (/.Cont Nat Bit) + (function (_ next) + (next sample))))) + (_.coverage [/.pending] + (/.continued (same? sample) + (is (/.Cont Nat Bit) + (/.pending sample)))) ))) diff --git a/stdlib/source/test/lux/control/exception.lux b/stdlib/source/test/lux/control/exception.lux index f003e854d..fb69ebee8 100644 --- a/stdlib/source/test/lux/control/exception.lux +++ b/stdlib/source/test/lux/control/exception.lux @@ -37,78 +37,78 @@ (<| (_.covering /._) (_.for [/.Exception]) (all _.and - (_.cover [/.except] - (case (/.except ..an_exception []) - {try.#Success _} false - {try.#Failure _} true)) - (_.cover [/.error] - (case (/.except ..an_exception []) - {try.#Success _} - false - - {try.#Failure message} - (text#= message (/.error ..an_exception [])))) - (_.cover [/.match?] - (/.match? ..an_exception - (/.error ..an_exception []))) - (_.cover [/.assertion] - (case (/.assertion ..an_exception [] assertion_succeeded?) - {try.#Success _} - assertion_succeeded? - - {try.#Failure message} - (and (not assertion_succeeded?) - (text#= message (/.error ..an_exception []))))) - (_.cover [/.when] - (and (n.= expected - (|> (/.except ..an_exception []) - (/.when ..an_exception (function (_ ex) expected)) - (/.otherwise (function (_ ex) wrong)))) - (n.= expected - (|> (/.except ..another_exception []) - (/.when ..an_exception (function (_ ex) wrong)) - (/.when ..another_exception (function (_ ex) expected)) - (/.otherwise (function (_ ex) wrong)))))) - (_.cover [/.otherwise] - (n.= expected - (|> (/.except ..another_exception []) - (/.when ..an_exception (function (_ ex) wrong)) - (/.otherwise (function (_ ex) expected))))) - (_.cover [/.report] - (let [report (/.report field0 value0 - field1 value1)] - (and (text.contains? field0 report) - (text.contains? value0 report) - (text.contains? field1 report) - (text.contains? value1 report)))) - (_.cover [/.listing] - (let [enumeration (/.listing %.text (list field0 value0 field1 value1))] - (and (text.contains? field0 enumeration) - (text.contains? value0 enumeration) - (text.contains? field1 enumeration) - (text.contains? value1 enumeration)))) - (_.cover [/.with] - (and (case (/.with ..an_exception [] {try.#Success expected}) - {try.#Success actual} (n.= expected actual) - {try.#Failure _} false) - (case (/.with ..an_exception [] {try.#Failure ""}) - {try.#Success _} false - {try.#Failure message} (text#= message (/.error ..an_exception []))) - (case (/.with ..an_exception [] - (is (Try Nat) - (/.except ..another_exception []))) - {try.#Success _} - false - - {try.#Failure message} - (and (text.contains? (/.error ..an_exception []) message) - (text.contains? (/.error ..another_exception []) message))))) - (_.cover [/.exception:] - (case (/.except ..custom_exception [expected]) - {try.#Success _} - false - - {try.#Failure message} - (and (text.contains? ..label message) - (text.contains? (%.nat expected) message)))) + (_.coverage [/.except] + (case (/.except ..an_exception []) + {try.#Success _} false + {try.#Failure _} true)) + (_.coverage [/.error] + (case (/.except ..an_exception []) + {try.#Success _} + false + + {try.#Failure message} + (text#= message (/.error ..an_exception [])))) + (_.coverage [/.match?] + (/.match? ..an_exception + (/.error ..an_exception []))) + (_.coverage [/.assertion] + (case (/.assertion ..an_exception [] assertion_succeeded?) + {try.#Success _} + assertion_succeeded? + + {try.#Failure message} + (and (not assertion_succeeded?) + (text#= message (/.error ..an_exception []))))) + (_.coverage [/.when] + (and (n.= expected + (|> (/.except ..an_exception []) + (/.when ..an_exception (function (_ ex) expected)) + (/.otherwise (function (_ ex) wrong)))) + (n.= expected + (|> (/.except ..another_exception []) + (/.when ..an_exception (function (_ ex) wrong)) + (/.when ..another_exception (function (_ ex) expected)) + (/.otherwise (function (_ ex) wrong)))))) + (_.coverage [/.otherwise] + (n.= expected + (|> (/.except ..another_exception []) + (/.when ..an_exception (function (_ ex) wrong)) + (/.otherwise (function (_ ex) expected))))) + (_.coverage [/.report] + (let [report (/.report field0 value0 + field1 value1)] + (and (text.contains? field0 report) + (text.contains? value0 report) + (text.contains? field1 report) + (text.contains? value1 report)))) + (_.coverage [/.listing] + (let [enumeration (/.listing %.text (list field0 value0 field1 value1))] + (and (text.contains? field0 enumeration) + (text.contains? value0 enumeration) + (text.contains? field1 enumeration) + (text.contains? value1 enumeration)))) + (_.coverage [/.with] + (and (case (/.with ..an_exception [] {try.#Success expected}) + {try.#Success actual} (n.= expected actual) + {try.#Failure _} false) + (case (/.with ..an_exception [] {try.#Failure ""}) + {try.#Success _} false + {try.#Failure message} (text#= message (/.error ..an_exception []))) + (case (/.with ..an_exception [] + (is (Try Nat) + (/.except ..another_exception []))) + {try.#Success _} + false + + {try.#Failure message} + (and (text.contains? (/.error ..an_exception []) message) + (text.contains? (/.error ..another_exception []) message))))) + (_.coverage [/.exception:] + (case (/.except ..custom_exception [expected]) + {try.#Success _} + false + + {try.#Failure message} + (and (text.contains? ..label message) + (text.contains? (%.nat expected) message)))) )))) diff --git a/stdlib/source/test/lux/control/function.lux b/stdlib/source/test/lux/control/function.lux index 0b9c4a3e7..e6a9eb5b4 100644 --- a/stdlib/source/test/lux/control/function.lux +++ b/stdlib/source/test/lux/control/function.lux @@ -40,24 +40,24 @@ (_.for [/.monoid] ($monoid.spec equivalence /.monoid generator))) - (_.cover [/.identity] - (n.= expected - (/.identity expected))) - (_.cover [/.composite] - (n.= (f0 (f1 expected)) - ((/.composite f0 f1) expected))) - (_.cover [/.constant] - (n.= expected - ((/.constant expected) dummy))) - (_.cover [/.flipped] - (let [outcome ((/.flipped n.-) expected extra)] - (and (n.= (n.- extra expected) - outcome) - (not (n.= (n.- expected extra) - outcome))))) - (_.cover [/.on] - (n.= (f0 extra) - (/.on extra f0))) + (_.coverage [/.identity] + (n.= expected + (/.identity expected))) + (_.coverage [/.composite] + (n.= (f0 (f1 expected)) + ((/.composite f0 f1) expected))) + (_.coverage [/.constant] + (n.= expected + ((/.constant expected) dummy))) + (_.coverage [/.flipped] + (let [outcome ((/.flipped n.-) expected extra)] + (and (n.= (n.- extra expected) + outcome) + (not (n.= (n.- expected extra) + outcome))))) + (_.coverage [/.on] + (n.= (f0 extra) + (/.on extra f0))) /contract.test /memo.test 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)))))) diff --git a/stdlib/source/test/lux/control/io.lux b/stdlib/source/test/lux/control/io.lux index 028684c05..52cdf2b8c 100644 --- a/stdlib/source/test/lux/control/io.lux +++ b/stdlib/source/test/lux/control/io.lux @@ -41,7 +41,7 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.run! /.io] - (n.= sample - (/.run! (/.io sample)))) + (_.coverage [/.run! /.io] + (n.= sample + (/.run! (/.io sample)))) )))) diff --git a/stdlib/source/test/lux/control/lazy.lux b/stdlib/source/test/lux/control/lazy.lux index c3a74c42c..0c00be310 100644 --- a/stdlib/source/test/lux/control/lazy.lux +++ b/stdlib/source/test/lux/control/lazy.lux @@ -52,16 +52,16 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.lazy] - (let [lazy (/.lazy <eager>) - (open "_#=") (product.equivalence n.equivalence n.equivalence)] - (_#= expected - (/.value lazy)))) + (_.coverage [/.lazy] + (let [lazy (/.lazy <eager>) + (open "_#=") (product.equivalence n.equivalence n.equivalence)] + (_#= expected + (/.value lazy)))) - (_.cover [/.value] - (let [lazy (/.lazy <eager>)] - (and (not (same? expected - (/.value lazy))) - (same? (/.value lazy) - (/.value lazy))))) + (_.coverage [/.value] + (let [lazy (/.lazy <eager>)] + (and (not (same? expected + (/.value lazy))) + (same? (/.value lazy) + (/.value lazy))))) )))))) diff --git a/stdlib/source/test/lux/control/maybe.lux b/stdlib/source/test/lux/control/maybe.lux index 471173834..e980121b7 100644 --- a/stdlib/source/test/lux/control/maybe.lux +++ b/stdlib/source/test/lux/control/maybe.lux @@ -50,41 +50,41 @@ right random.nat .let [expected (n.+ left right)]] (let [lifted (/.lifted io.monad)] - (_.cover [/.with /.lifted] - (|> (io.run! (do (/.with io.monad) - [a (lifted (io#in left)) - b (in right)] - (in (n.+ a b)))) - (pipe.case - {.#Some actual} - (n.= expected actual) + (_.coverage [/.with /.lifted] + (|> (io.run! (do (/.with io.monad) + [a (lifted (io#in left)) + b (in right)] + (in (n.+ a b)))) + (pipe.case + {.#Some actual} + (n.= expected actual) - _ - false))))) + _ + false))))) (do random.monad [default random.nat value random.nat] - (_.cover [/.else] - (and (same? default (/.else default - (is (Maybe Nat) - {.#None}))) + (_.coverage [/.else] + (and (same? default (/.else default + (is (Maybe Nat) + {.#None}))) - (same? value (/.else default - {.#Some value}))))) + (same? value (/.else default + {.#Some value}))))) (do random.monad [value random.nat] - (_.cover [/.trusted] - (same? value (/.trusted {.#Some value})))) + (_.coverage [/.trusted] + (same? value (/.trusted {.#Some value})))) (do random.monad [value random.nat] - (_.cover [/.list] - (# (list.equivalence n.equivalence) = - (list value) - (/.list {.#Some value})))) + (_.coverage [/.list] + (# (list.equivalence n.equivalence) = + (list value) + (/.list {.#Some value})))) (do random.monad [expected random.nat .let [(open "/#[0]") (/.equivalence n.equivalence)]] - (_.cover [/.when] - (and (/#= {.#Some expected} (/.when true {.#Some expected})) - (/#= {.#None} (/.when false {.#Some expected}))))) + (_.coverage [/.when] + (and (/#= {.#Some expected} (/.when true {.#Some expected})) + (/#= {.#None} (/.when false {.#Some expected}))))) ))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index 4694be281..fcb84271d 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -96,85 +96,85 @@ odd0 (random.only n.odd? random.nat) not0 random.bit] (all _.and - (_.cover [/.maybe] - (and (|> (list (code.nat expected0)) - (/.result (/.maybe <code>.nat)) - (match {.#Some actual} - (n.= expected0 actual))) - (|> (list (code.int (.int expected0))) - (/.result (/.maybe <code>.nat)) - (match {.#None} - #1)))) - (_.cover [/.some] - (and (|> (list#each code.nat expected+) - (/.result (/.some <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = expected+ actual))) - (|> (list#each (|>> .int code.int) expected+) - (/.result (/.some <code>.nat)) - (match {.#End} - #1)))) - (_.cover [/.many] - (and (|> (list#each code.nat expected+) - (/.result (/.many <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = expected+ actual))) - (|> (list (code.nat expected0)) - (/.result (/.many <code>.nat)) - (match (list actual) - (n.= expected0 actual))) - (|> (list#each (|>> .int code.int) expected+) - (/.result (/.many <code>.nat)) - fails?))) - (_.cover [/.only] - (and (|> (list (code.nat even0)) - (/.result (/.only n.even? <code>.nat)) - (match actual (n.= even0 actual))) - (|> (list (code.nat odd0)) - (/.result (/.only n.even? <code>.nat)) - fails?))) - (_.cover [/.and] - (let [even (/.only n.even? <code>.nat) - odd (/.only n.odd? <code>.nat)] - (and (|> (list (code.nat even0) (code.nat odd0)) - (/.result (/.and even odd)) - (match [left right] - (and (n.= even0 left) - (n.= odd0 right)))) - (|> (list (code.nat odd0) (code.nat even0)) - (/.result (/.and even odd)) - fails?)))) - (_.cover [/.or] - (let [even (/.only n.even? <code>.nat) - odd (/.only n.odd? <code>.nat)] - (and (|> (list (code.nat even0)) - (/.result (/.or even odd)) - (match {.#Left actual} (n.= even0 actual))) - (|> (list (code.nat odd0)) - (/.result (/.or even odd)) - (match {.#Right actual} (n.= odd0 actual))) - (|> (list (code.bit not0)) - (/.result (/.or even odd)) - fails?)))) - (_.cover [/.either] - (let [even (/.only n.even? <code>.nat) - odd (/.only n.odd? <code>.nat)] - (and (|> (list (code.nat even0)) - (/.result (/.either even odd)) - (match actual (n.= even0 actual))) - (|> (list (code.nat odd0)) - (/.result (/.either even odd)) - (match actual (n.= odd0 actual))) - (|> (list (code.bit not0)) - (/.result (/.either even odd)) - fails?)))) - (_.cover [/.not] - (and (|> (list (code.nat expected0)) - (/.result (/.not <code>.nat)) - fails?) - (|> (list (code.bit not0)) - (/.result (/.not <code>.nat)) - (match [] #1)))) + (_.coverage [/.maybe] + (and (|> (list (code.nat expected0)) + (/.result (/.maybe <code>.nat)) + (match {.#Some actual} + (n.= expected0 actual))) + (|> (list (code.int (.int expected0))) + (/.result (/.maybe <code>.nat)) + (match {.#None} + #1)))) + (_.coverage [/.some] + (and (|> (list#each code.nat expected+) + (/.result (/.some <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = expected+ actual))) + (|> (list#each (|>> .int code.int) expected+) + (/.result (/.some <code>.nat)) + (match {.#End} + #1)))) + (_.coverage [/.many] + (and (|> (list#each code.nat expected+) + (/.result (/.many <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = expected+ actual))) + (|> (list (code.nat expected0)) + (/.result (/.many <code>.nat)) + (match (list actual) + (n.= expected0 actual))) + (|> (list#each (|>> .int code.int) expected+) + (/.result (/.many <code>.nat)) + fails?))) + (_.coverage [/.only] + (and (|> (list (code.nat even0)) + (/.result (/.only n.even? <code>.nat)) + (match actual (n.= even0 actual))) + (|> (list (code.nat odd0)) + (/.result (/.only n.even? <code>.nat)) + fails?))) + (_.coverage [/.and] + (let [even (/.only n.even? <code>.nat) + odd (/.only n.odd? <code>.nat)] + (and (|> (list (code.nat even0) (code.nat odd0)) + (/.result (/.and even odd)) + (match [left right] + (and (n.= even0 left) + (n.= odd0 right)))) + (|> (list (code.nat odd0) (code.nat even0)) + (/.result (/.and even odd)) + fails?)))) + (_.coverage [/.or] + (let [even (/.only n.even? <code>.nat) + odd (/.only n.odd? <code>.nat)] + (and (|> (list (code.nat even0)) + (/.result (/.or even odd)) + (match {.#Left actual} (n.= even0 actual))) + (|> (list (code.nat odd0)) + (/.result (/.or even odd)) + (match {.#Right actual} (n.= odd0 actual))) + (|> (list (code.bit not0)) + (/.result (/.or even odd)) + fails?)))) + (_.coverage [/.either] + (let [even (/.only n.even? <code>.nat) + odd (/.only n.odd? <code>.nat)] + (and (|> (list (code.nat even0)) + (/.result (/.either even odd)) + (match actual (n.= even0 actual))) + (|> (list (code.nat odd0)) + (/.result (/.either even odd)) + (match actual (n.= odd0 actual))) + (|> (list (code.bit not0)) + (/.result (/.either even odd)) + fails?)))) + (_.coverage [/.not] + (and (|> (list (code.nat expected0)) + (/.result (/.not <code>.nat)) + fails?) + (|> (list (code.bit not0)) + (/.result (/.not <code>.nat)) + (match [] #1)))) ))) (def: combinators_1 @@ -187,73 +187,73 @@ expected+ (random.list variadic random.nat) separator (random.ascii 1)] (all _.and - (_.cover [/.exactly] - (and (|> (list#each code.nat expected+) - (/.result (/.exactly times <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - (list.first times expected+) - actual))) - (|> (list#each code.nat expected+) - (/.result (/.exactly (++ variadic) <code>.nat)) - fails?))) - (_.cover [/.at_least] - (and (|> (list#each code.nat expected+) - (/.result (/.at_least times <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - expected+ - actual))) - (|> (list#each code.nat expected+) - (/.result (/.at_least (++ variadic) <code>.nat)) - fails?))) - (_.cover [/.at_most] - (and (|> (list#each code.nat expected+) - (/.result (/.at_most times <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - (list.first times expected+) - actual))) - (|> (list#each code.nat expected+) - (/.result (/.at_most (++ variadic) <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - expected+ - actual))))) - (_.cover [/.between] - (and (|> (list#each code.nat expected+) - (/.result (/.between times (n.- times variadic) <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - expected+ - actual))) - (|> (list#each code.nat (list.first times expected+)) - (/.result (/.between times (n.- times variadic) <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - (list.first times expected+) - actual))))) - (_.cover [/.separated_by] - (|> (list.interposed (code.text separator) (list#each code.nat expected+)) - (/.result (/.separated_by (<code>.this (code.text separator)) <code>.nat)) - (match actual - (# (list.equivalence n.equivalence) = - expected+ - actual)))) - (_.cover [/.remaining] - (|> (list#each code.nat expected+) - (/.result /.remaining) - (match actual - (# (list.equivalence code.equivalence) = - (list#each code.nat expected+) - actual)))) - (_.cover [/.else] - (and (|> (/.result (/.else wrong (# /.monad in expected)) (list)) - (match actual (n.= expected actual))) - (|> (/.result (/.else expected (/.failure "yolo")) - (list)) - (match actual (n.= expected actual))) - )) + (_.coverage [/.exactly] + (and (|> (list#each code.nat expected+) + (/.result (/.exactly times <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + (list.first times expected+) + actual))) + (|> (list#each code.nat expected+) + (/.result (/.exactly (++ variadic) <code>.nat)) + fails?))) + (_.coverage [/.at_least] + (and (|> (list#each code.nat expected+) + (/.result (/.at_least times <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + expected+ + actual))) + (|> (list#each code.nat expected+) + (/.result (/.at_least (++ variadic) <code>.nat)) + fails?))) + (_.coverage [/.at_most] + (and (|> (list#each code.nat expected+) + (/.result (/.at_most times <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + (list.first times expected+) + actual))) + (|> (list#each code.nat expected+) + (/.result (/.at_most (++ variadic) <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + expected+ + actual))))) + (_.coverage [/.between] + (and (|> (list#each code.nat expected+) + (/.result (/.between times (n.- times variadic) <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + expected+ + actual))) + (|> (list#each code.nat (list.first times expected+)) + (/.result (/.between times (n.- times variadic) <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + (list.first times expected+) + actual))))) + (_.coverage [/.separated_by] + (|> (list.interposed (code.text separator) (list#each code.nat expected+)) + (/.result (/.separated_by (<code>.this (code.text separator)) <code>.nat)) + (match actual + (# (list.equivalence n.equivalence) = + expected+ + actual)))) + (_.coverage [/.remaining] + (|> (list#each code.nat expected+) + (/.result /.remaining) + (match actual + (# (list.equivalence code.equivalence) = + (list#each code.nat expected+) + actual)))) + (_.coverage [/.else] + (and (|> (/.result (/.else wrong (# /.monad in expected)) (list)) + (match actual (n.= expected actual))) + (|> (/.result (/.else expected (/.failure "yolo")) + (list)) + (match actual (n.= expected actual))) + )) ))) (def: combinators_2 @@ -266,68 +266,68 @@ even^ (/.only n.even? <code>.nat) odd^ (/.only n.odd? <code>.nat)]] (all _.and - (_.cover [/.rec] - (let [parser (/.rec (function (_ self) - (/.either <code>.nat - (<code>.tuple self)))) - level_0 (code.nat expected) - level_up (is (-> Code Code) - (|>> list code.tuple))] - (and (|> (list level_0) - (/.result parser) - (match actual (n.= expected actual))) - (|> (list (level_up level_0)) - (/.result parser) - (match actual (n.= expected actual))) - (|> (list (level_up (level_up level_0))) - (/.result parser) - (match actual (n.= expected actual)))))) - (_.cover [/.after] - (and (|> (/.result (/.after even^ <code>.nat) - (list (code.nat even) (code.nat expected))) - (match actual (n.= expected actual))) - (|> (/.result (/.after even^ <code>.nat) - (list (code.nat odd) (code.nat expected))) - fails?))) - (_.cover [/.before] - (and (|> (/.result (/.before even^ <code>.nat) - (list (code.nat expected) (code.nat even))) - (match actual (n.= expected actual))) - (|> (/.result (/.before even^ <code>.nat) - (list (code.nat expected) (code.nat odd))) - fails?))) - (_.cover [/.parses?] - (and (|> (/.result (/.parses? even^) - (list (code.nat even))) - (match verdict verdict)) - (|> (/.result (/.parses? even^) - (list (code.nat odd))) - (match verdict (not verdict))))) - (_.cover [/.parses] - (and (|> (/.result (/.parses even^) - (list (code.nat even))) - (match [] true)) - (|> (/.result (/.parses even^) - (list (code.nat odd))) - fails?))) - (_.cover [/.speculative] - (let [happy_path! - (|> (/.result (/.and (/.speculative even^) nat^) - (list (code.nat even))) - (match [speculation actual] - (and (n.= speculation actual) - (n.= even actual)))) + (_.coverage [/.rec] + (let [parser (/.rec (function (_ self) + (/.either <code>.nat + (<code>.tuple self)))) + level_0 (code.nat expected) + level_up (is (-> Code Code) + (|>> list code.tuple))] + (and (|> (list level_0) + (/.result parser) + (match actual (n.= expected actual))) + (|> (list (level_up level_0)) + (/.result parser) + (match actual (n.= expected actual))) + (|> (list (level_up (level_up level_0))) + (/.result parser) + (match actual (n.= expected actual)))))) + (_.coverage [/.after] + (and (|> (/.result (/.after even^ <code>.nat) + (list (code.nat even) (code.nat expected))) + (match actual (n.= expected actual))) + (|> (/.result (/.after even^ <code>.nat) + (list (code.nat odd) (code.nat expected))) + fails?))) + (_.coverage [/.before] + (and (|> (/.result (/.before even^ <code>.nat) + (list (code.nat expected) (code.nat even))) + (match actual (n.= expected actual))) + (|> (/.result (/.before even^ <code>.nat) + (list (code.nat expected) (code.nat odd))) + fails?))) + (_.coverage [/.parses?] + (and (|> (/.result (/.parses? even^) + (list (code.nat even))) + (match verdict verdict)) + (|> (/.result (/.parses? even^) + (list (code.nat odd))) + (match verdict (not verdict))))) + (_.coverage [/.parses] + (and (|> (/.result (/.parses even^) + (list (code.nat even))) + (match [] true)) + (|> (/.result (/.parses even^) + (list (code.nat odd))) + fails?))) + (_.coverage [/.speculative] + (let [happy_path! + (|> (/.result (/.and (/.speculative even^) nat^) + (list (code.nat even))) + (match [speculation actual] + (and (n.= speculation actual) + (n.= even actual)))) - sad_path! - (|> (/.result (/.and (/.speculative even^) nat^) - (list (code.nat odd))) - fails?)] - (and happy_path! - sad_path!))) - (_.cover [/.codec] - (|> (/.result (/.codec n.decimal <code>.text) - (list (code.text (%.nat expected)))) - (match actual (n.= expected actual)))) + sad_path! + (|> (/.result (/.and (/.speculative even^) nat^) + (list (code.nat odd))) + fails?)] + (and happy_path! + sad_path!))) + (_.coverage [/.codec] + (|> (/.result (/.codec n.decimal <code>.text) + (list (code.text (%.nat expected)))) + (match actual (n.= expected actual)))) ))) (def: injection @@ -360,27 +360,27 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.result] - (|> (/.result (# /.monad in expected) (list)) - (match actual (n.= expected actual)))) - (_.cover [/.failure] - (|> (list) - (/.result (/.failure failure)) - (should_fail failure))) - (_.cover [/.lifted] - (and (|> (list) - (/.result (/.lifted {try.#Success expected})) - (match actual (n.= expected actual))) - (|> (list) - (/.result (/.lifted {try.#Failure failure})) - (should_fail failure)))) - (_.cover [/.assertion] - (and (|> (list (code.bit #1) (code.int +123)) - (/.result (/.assertion assertion #1)) - (match [] true)) - (|> (list (code.bit #1) (code.int +123)) - (/.result (/.assertion assertion #0)) - fails?))) + (_.coverage [/.result] + (|> (/.result (# /.monad in expected) (list)) + (match actual (n.= expected actual)))) + (_.coverage [/.failure] + (|> (list) + (/.result (/.failure failure)) + (should_fail failure))) + (_.coverage [/.lifted] + (and (|> (list) + (/.result (/.lifted {try.#Success expected})) + (match actual (n.= expected actual))) + (|> (list) + (/.result (/.lifted {try.#Failure failure})) + (should_fail failure)))) + (_.coverage [/.assertion] + (and (|> (list (code.bit #1) (code.int +123)) + (/.result (/.assertion assertion #1)) + (match [] true)) + (|> (list (code.bit #1) (code.int +123)) + (/.result (/.assertion assertion #0)) + fails?))) ..combinators_0 ..combinators_1 ..combinators_2 diff --git a/stdlib/source/test/lux/control/parser/analysis.lux b/stdlib/source/test/lux/control/parser/analysis.lux index 365696b14..92be5bc35 100644 --- a/stdlib/source/test/lux/control/parser/analysis.lux +++ b/stdlib/source/test/lux/control/parser/analysis.lux @@ -55,33 +55,33 @@ (`` (all _.and (do [! random.monad] [expected (# ! each (|>> analysis.bit) random.bit)] - (_.cover [/.result /.any] - (|> (list expected) - (/.result /.any) - (pipe.case - {try.#Success actual} - (# analysis.equivalence = expected actual) + (_.coverage [/.result /.any] + (|> (list expected) + (/.result /.any) + (pipe.case + {try.#Success actual} + (# analysis.equivalence = expected actual) - {try.#Failure _} - false)))) + {try.#Failure _} + false)))) (~~ (template [<query> <check> <random> <analysis> <=>] [(do [! random.monad] [expected <random>] - (_.cover [<query>] - (|> (list (<analysis> expected)) - (/.result <query>) - (pipe.case - {try.#Success actual} - (<=> expected actual) + (_.coverage [<query>] + (|> (list (<analysis> expected)) + (/.result <query>) + (pipe.case + {try.#Success actual} + (<=> expected actual) - {try.#Failure _} - false)))) + {try.#Failure _} + false)))) (do [! random.monad] [expected <random>] - (_.cover [<check>] - (|> (list (<analysis> expected)) - (/.result (<check> expected)) - (!expect {try.#Success _}))))] + (_.coverage [<check>] + (|> (list (<analysis> expected)) + (/.result (<check> expected)) + (!expect {try.#Success _}))))] [/.bit /.this_bit random.bit analysis.bit bit#=] [/.nat /.this_nat random.nat analysis.nat n.=] @@ -95,61 +95,61 @@ )) (do [! random.monad] [expected random.bit] - (_.cover [/.tuple] - (|> (list (analysis.tuple (list (analysis.bit expected)))) - (/.result (/.tuple /.bit)) - (pipe.case - {try.#Success actual} - (bit#= expected actual) + (_.coverage [/.tuple] + (|> (list (analysis.tuple (list (analysis.bit expected)))) + (/.result (/.tuple /.bit)) + (pipe.case + {try.#Success actual} + (bit#= expected actual) - {try.#Failure _} - false)))) + {try.#Failure _} + false)))) (do [! random.monad] [dummy random.bit] - (_.cover [/.end?] - (and (|> (/.result /.end? (list)) - (!expect {try.#Success #1})) - (|> (/.result (do <>.monad - [verdict /.end? - _ /.bit] - (in verdict)) - (list (analysis.bit dummy))) - (!expect {try.#Success #0}))))) + (_.coverage [/.end?] + (and (|> (/.result /.end? (list)) + (!expect {try.#Success #1})) + (|> (/.result (do <>.monad + [verdict /.end? + _ /.bit] + (in verdict)) + (list (analysis.bit dummy))) + (!expect {try.#Success #0}))))) (do [! random.monad] [dummy random.bit] - (_.cover [/.end] - (and (|> (/.result /.end (list)) - (!expect {try.#Success _})) - (|> (/.result /.end (list (analysis.bit dummy))) - (!expect {try.#Failure _}))))) + (_.coverage [/.end] + (and (|> (/.result /.end (list)) + (!expect {try.#Success _})) + (|> (/.result /.end (list (analysis.bit dummy))) + (!expect {try.#Failure _}))))) (do [! random.monad] [expected random.bit] - (_.cover [/.cannot_parse] - (and (|> (list (analysis.bit expected)) - (/.result /.nat) - (pipe.case - {try.#Success _} - false + (_.coverage [/.cannot_parse] + (and (|> (list (analysis.bit expected)) + (/.result /.nat) + (pipe.case + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.cannot_parse error))) - (|> (list) - (/.result /.bit) - (pipe.case - {try.#Success _} - false + {try.#Failure error} + (exception.match? /.cannot_parse error))) + (|> (list) + (/.result /.bit) + (pipe.case + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.cannot_parse error)))))) + {try.#Failure error} + (exception.match? /.cannot_parse error)))))) (do [! random.monad] [expected random.bit] - (_.cover [/.unconsumed_input] - (|> (list (analysis.bit expected) (analysis.bit expected)) - (/.result /.bit) - (pipe.case - {try.#Success _} - false + (_.coverage [/.unconsumed_input] + (|> (list (analysis.bit expected) (analysis.bit expected)) + (/.result /.bit) + (pipe.case + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.unconsumed_input error))))) + {try.#Failure error} + (exception.match? /.unconsumed_input error))))) ))))) diff --git a/stdlib/source/test/lux/control/parser/binary.lux b/stdlib/source/test/lux/control/parser/binary.lux index 2a7284c1d..50f1bea42 100644 --- a/stdlib/source/test/lux/control/parser/binary.lux +++ b/stdlib/source/test/lux/control/parser/binary.lux @@ -130,12 +130,12 @@ [(do [! random.monad] [expected (# ! each (i64.and (i64.mask <size>)) random.nat)] - (_.cover [<size> <parser> <format>] - (|> (format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (n.= (.nat expected) - (.nat actual)))))))] + (_.coverage [<size> <parser> <format>] + (|> (format.result <format> expected) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (n.= (.nat expected) + (.nat actual)))))))] [/.size_8 /.bits_8 format.bits_8] [/.size_16 /.bits_16 format.bits_16] @@ -149,11 +149,11 @@ (~~ (template [<parser> <format>] [(do [! random.monad] [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [<parser> <format>] - (|> (format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (# binary.equivalence = expected actual))))))] + (_.coverage [<parser> <format>] + (|> (format.result <format> expected) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (# binary.equivalence = expected actual))))))] [/.binary_8 format.binary_8] [/.binary_16 format.binary_16] @@ -167,11 +167,11 @@ (~~ (template [<parser> <format>] [(do [! random.monad] [expected (random.ascii ..segment_size)] - (_.cover [<parser> <format>] - (|> (format.result <format> expected) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (# text.equivalence = expected actual))))))] + (_.coverage [<parser> <format>] + (|> (format.result <format> expected) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (# text.equivalence = expected actual))))))] [/.utf8_8 format.utf8_8] [/.utf8_16 format.utf8_16] @@ -186,12 +186,12 @@ (~~ (template [<parser> <format>] [(do [! random.monad] [expected (random.sequence ..segment_size random.nat)] - (_.cover [<parser> <format>] - (|> expected - (format.result (<format> format.nat)) - (/.result (<parser> /.nat)) - (!expect (^.multi {try.#Success actual} - (# (sequence.equivalence n.equivalence) = expected actual))))))] + (_.coverage [<parser> <format>] + (|> expected + (format.result (<format> format.nat)) + (/.result (<parser> /.nat)) + (!expect (^.multi {try.#Success actual} + (# (sequence.equivalence n.equivalence) = expected actual))))))] [/.sequence_8 format.sequence_8] [/.sequence_16 format.sequence_16] @@ -205,12 +205,12 @@ (~~ (template [<parser> <format> <random> <equivalence>] [(do [! random.monad] [expected <random>] - (_.cover [<parser> <format>] - (|> expected - (format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (_.coverage [<parser> <format>] + (|> expected + (format.result <format>) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.bit format.bit random.bit bit.equivalence] [/.nat format.nat random.nat n.equivalence] @@ -218,24 +218,24 @@ [/.rev format.rev random.rev rev.equivalence])) (do [! random.monad] [expected random.frac] - (_.cover [/.frac format.frac] - (|> expected - (format.result format.frac) - (/.result /.frac) - (!expect (^.multi {try.#Success actual} - (or (# frac.equivalence = expected actual) - (and (frac.not_a_number? expected) - (frac.not_a_number? actual)))))))) + (_.coverage [/.frac format.frac] + (|> expected + (format.result format.frac) + (/.result /.frac) + (!expect (^.multi {try.#Success actual} + (or (# frac.equivalence = expected actual) + (and (frac.not_a_number? expected) + (frac.not_a_number? actual)))))))) (do [! random.monad] [expected (# ! each (|>> (i64.and (i64.mask /.size_8)) (n.max 2)) random.nat)] - (_.cover [/.not_a_bit] - (|> expected - (format.result format.bits_8) - (/.result /.bit) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_a_bit error)))))) + (_.coverage [/.not_a_bit] + (|> expected + (format.result format.bits_8) + (/.result /.bit) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_a_bit error)))))) ))) (def: complex @@ -244,12 +244,12 @@ (~~ (template [<parser> <format> <random> <equivalence>] [(do [! random.monad] [expected <random>] - (_.cover [<parser> <format>] - (|> expected - (format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (_.coverage [<parser> <format>] + (|> expected + (format.result <format>) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.location format.location random_location location_equivalence] [/.code format.code random_code code.equivalence] @@ -258,12 +258,12 @@ (~~ (template [<parser_coverage> <parser> <coverage_format> <format> <random> <equivalence>] [(do [! random.monad] [expected <random>] - (_.cover [<parser_coverage> <coverage_format>] - (|> expected - (format.result <format>) - (/.result <parser>) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))))] + (_.coverage [<parser_coverage> <coverage_format>] + (|> expected + (format.result <format>) + (/.result <parser>) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))))] [/.maybe (/.maybe /.nat) format.maybe (format.maybe format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)] [/.list (/.list /.nat) format.list (format.list format.nat) (random.list ..segment_size random.nat) (list.equivalence n.equivalence)] @@ -271,51 +271,51 @@ [/.symbol /.symbol format.symbol format.symbol ..random_symbol symbol.equivalence])) (do [! random.monad] [expected (# ! each (list.repeated ..segment_size) random.nat)] - (_.cover [/.set_elements_are_not_unique] - (|> expected - (format.result (format.list format.nat)) - (/.result (/.set n.hash /.nat)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.set_elements_are_not_unique error)))))) + (_.coverage [/.set_elements_are_not_unique] + (|> expected + (format.result (format.list format.nat)) + (/.result (/.set n.hash /.nat)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.set_elements_are_not_unique error)))))) (do [! random.monad] [expected (random.or random.bit random.nat)] - (_.cover [/.or format.or] - (|> expected - (format.result (format.or format.bit format.nat)) - (/.result (is (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) - (!expect (^.multi {try.#Success actual} - (# (sum.equivalence bit.equivalence n.equivalence) = - expected - actual)))))) + (_.coverage [/.or format.or] + (|> expected + (format.result (format.or format.bit format.nat)) + (/.result (is (/.Parser (Either Bit Nat)) + (/.or /.bit /.nat))) + (!expect (^.multi {try.#Success actual} + (# (sum.equivalence bit.equivalence n.equivalence) = + expected + actual)))))) (do [! random.monad] [tag (# ! each (|>> (i64.and (i64.mask /.size_8)) (n.max 2)) random.nat) value random.bit] - (_.cover [/.invalid_tag] - (|> [tag value] - (format.result (format.and format.bits_8 format.bit)) - (/.result (is (/.Parser (Either Bit Nat)) - (/.or /.bit /.nat))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.invalid_tag error)))))) + (_.coverage [/.invalid_tag] + (|> [tag value] + (format.result (format.and format.bits_8 format.bit)) + (/.result (is (/.Parser (Either Bit Nat)) + (/.or /.bit /.nat))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.invalid_tag error)))))) (do [! random.monad] [expected (random.list ..segment_size random.nat)] - (_.cover [/.rec format.rec format.and format.any] - (|> expected - (format.result (format.rec (|>> (format.and format.nat) - (format.or format.any)))) - (/.result (is (/.Parser (List Nat)) - (/.rec - (function (_ again) - (/.or /.any - (<>.and /.nat - again)))))) - (!expect (^.multi {try.#Success actual} - (# (list.equivalence n.equivalence) = - expected - actual)))))) + (_.coverage [/.rec format.rec format.and format.any] + (|> expected + (format.result (format.rec (|>> (format.and format.nat) + (format.or format.any)))) + (/.result (is (/.Parser (List Nat)) + (/.rec + (function (_ again) + (/.or /.any + (<>.and /.nat + again)))))) + (!expect (^.multi {try.#Success actual} + (# (list.equivalence n.equivalence) = + expected + actual)))))) ))) (def: .public test @@ -323,66 +323,66 @@ (<| (_.covering /._) (_.for [/.Parser]) (`` (all _.and - (_.cover [/.result /.any - format.no_op format.instance] - (|> (format.instance format.no_op) - (/.result /.any) - (!expect {try.#Success _}))) + (_.coverage [/.result /.any + format.no_op format.instance] + (|> (format.instance format.no_op) + (/.result /.any) + (!expect {try.#Success _}))) (do [! random.monad] [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [/.binary_was_not_fully_read] - (|> data - (/.result /.any) - (!expect (^.multi {try.#Failure error} - (exception.match? /.binary_was_not_fully_read error)))))) + (_.coverage [/.binary_was_not_fully_read] + (|> data + (/.result /.any) + (!expect (^.multi {try.#Failure error} + (exception.match? /.binary_was_not_fully_read error)))))) (do [! random.monad] [expected (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [/.segment format.segment format.result] - (|> expected - (format.result (format.segment ..segment_size)) - (/.result (/.segment ..segment_size)) - (!expect (^.multi {try.#Success actual} - (# binary.equivalence = expected actual)))))) + (_.coverage [/.segment format.segment format.result] + (|> expected + (format.result (format.segment ..segment_size)) + (/.result (/.segment ..segment_size)) + (!expect (^.multi {try.#Success actual} + (# binary.equivalence = expected actual)))))) (do [! random.monad] [data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [/.end?] - (|> data - (/.result (do <>.monad - [pre /.end? - _ (/.segment ..segment_size) - post /.end?] - (in (and (not pre) - post)))) - (!expect {try.#Success #1})))) + (_.coverage [/.end?] + (|> data + (/.result (do <>.monad + [pre /.end? + _ (/.segment ..segment_size) + post /.end?] + (in (and (not pre) + post)))) + (!expect {try.#Success #1})))) (do [! random.monad] [to_read (# ! each (n.% (++ ..segment_size)) random.nat) data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [/.Offset /.offset] - (|> data - (/.result (do <>.monad - [start /.offset - _ (/.segment to_read) - offset /.offset - _ (/.segment (n.- to_read ..segment_size)) - nothing_left /.offset] - (in (and (n.= 0 start) - (n.= to_read offset) - (n.= ..segment_size nothing_left))))) - (!expect {try.#Success #1})))) + (_.coverage [/.Offset /.offset] + (|> data + (/.result (do <>.monad + [start /.offset + _ (/.segment to_read) + offset /.offset + _ (/.segment (n.- to_read ..segment_size)) + nothing_left /.offset] + (in (and (n.= 0 start) + (n.= to_read offset) + (n.= ..segment_size nothing_left))))) + (!expect {try.#Success #1})))) (do [! random.monad] [to_read (# ! each (n.% (++ ..segment_size)) random.nat) data (# ! each (# utf8.codec encoded) (random.ascii ..segment_size))] - (_.cover [/.remaining] - (|> data - (/.result (do <>.monad - [_ (/.segment to_read) - remaining /.remaining - _ (/.segment (n.- to_read ..segment_size)) - nothing_left /.remaining] - (in (and (n.= ..segment_size - (n.+ to_read remaining)) - (n.= 0 nothing_left))))) - (!expect {try.#Success #1})))) + (_.coverage [/.remaining] + (|> data + (/.result (do <>.monad + [_ (/.segment to_read) + remaining /.remaining + _ (/.segment (n.- to_read ..segment_size)) + nothing_left /.remaining] + (in (and (n.= ..segment_size + (n.+ to_read remaining)) + (n.= 0 nothing_left))))) + (!expect {try.#Success #1})))) ..size ..binary ..utf8 diff --git a/stdlib/source/test/lux/control/parser/cli.lux b/stdlib/source/test/lux/control/parser/cli.lux index 5dc368174..69d9a20e7 100644 --- a/stdlib/source/test/lux/control/parser/cli.lux +++ b/stdlib/source/test/lux/control/parser/cli.lux @@ -42,44 +42,44 @@ pre_ignore (random.list 5 random_dummy) post_ignore (random.list 5 random_dummy)] (all _.and - (_.cover [/.result /.any] - (|> (/.result /.any (list expected)) - (!expect (^.multi {try.#Success actual} - (text#= expected actual))))) - (_.cover [/.parse] - (|> (/.result (/.parse n#decoded) (list expected)) - (!expect (^.multi {try.#Success actual} - (text#= expected - (n#encoded actual)))))) - (_.cover [/.this] - (and (|> (/.result (/.this expected) (list expected)) - (!expect {try.#Success _})) - (|> (/.result (/.this expected) (list dummy)) - (!expect {try.#Failure _})))) - (_.cover [/.somewhere] - (|> (/.result (|> (/.somewhere (/.this expected)) - (<>.before (<>.some /.any))) - (list.together (list pre_ignore (list expected) post_ignore))) - (!expect {try.#Success _}))) - (_.cover [/.end] - (and (|> (/.result /.end (list)) - (!expect {try.#Success _})) - (|> (/.result (<>.not /.end) (list expected)) - (!expect {try.#Failure _})))) - (_.cover [/.named] - (|> (/.result (/.named dummy /.any) (list dummy expected)) - (!expect (^.multi {try.#Success actual} - (text#= expected actual))))) - (_.cover [/.parameter] - (and (|> (/.result (/.parameter [short long] /.any) - (list short expected)) - (!expect (^.multi {try.#Success actual} - (text#= expected actual)))) - (|> (/.result (/.parameter [short long] /.any) - (list long expected)) - (!expect (^.multi {try.#Success actual} - (text#= expected actual)))) - (|> (/.result (/.parameter [short long] /.any) - (list dummy expected)) - (!expect {try.#Failure _})))) + (_.coverage [/.result /.any] + (|> (/.result /.any (list expected)) + (!expect (^.multi {try.#Success actual} + (text#= expected actual))))) + (_.coverage [/.parse] + (|> (/.result (/.parse n#decoded) (list expected)) + (!expect (^.multi {try.#Success actual} + (text#= expected + (n#encoded actual)))))) + (_.coverage [/.this] + (and (|> (/.result (/.this expected) (list expected)) + (!expect {try.#Success _})) + (|> (/.result (/.this expected) (list dummy)) + (!expect {try.#Failure _})))) + (_.coverage [/.somewhere] + (|> (/.result (|> (/.somewhere (/.this expected)) + (<>.before (<>.some /.any))) + (list.together (list pre_ignore (list expected) post_ignore))) + (!expect {try.#Success _}))) + (_.coverage [/.end] + (and (|> (/.result /.end (list)) + (!expect {try.#Success _})) + (|> (/.result (<>.not /.end) (list expected)) + (!expect {try.#Failure _})))) + (_.coverage [/.named] + (|> (/.result (/.named dummy /.any) (list dummy expected)) + (!expect (^.multi {try.#Success actual} + (text#= expected actual))))) + (_.coverage [/.parameter] + (and (|> (/.result (/.parameter [short long] /.any) + (list short expected)) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))) + (|> (/.result (/.parameter [short long] /.any) + (list long expected)) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))) + (|> (/.result (/.parameter [short long] /.any) + (list dummy expected)) + (!expect {try.#Failure _})))) )))) diff --git a/stdlib/source/test/lux/control/parser/code.lux b/stdlib/source/test/lux/control/parser/code.lux index 988151880..c4e202aba 100644 --- a/stdlib/source/test/lux/control/parser/code.lux +++ b/stdlib/source/test/lux/control/parser/code.lux @@ -62,25 +62,25 @@ (`` (all _.and (do [! random.monad] [expected (# ! each code.bit random.bit)] - (_.cover [/.result] - (and (|> (/.result /.any (list expected)) - (!expect {try.#Success _})) - (|> (/.result /.any (list)) - (!expect {try.#Failure _}))))) + (_.coverage [/.result] + (and (|> (/.result /.any (list expected)) + (!expect {try.#Success _})) + (|> (/.result /.any (list)) + (!expect {try.#Failure _}))))) (~~ (template [<query> <check> <random> <code> <equivalence>] [(do [! random.monad] [expected <random> dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))] (all _.and - (_.cover [<query>] - (|> (/.result <query> (list (<code> expected))) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))) - (_.cover [<check>] - (and (|> (/.result (<check> expected) (list (<code> expected))) - (!expect {try.#Success []})) - (|> (/.result (<check> expected) (list (<code> dummy))) - (!expect {try.#Failure _})))) + (_.coverage [<query>] + (|> (/.result <query> (list (<code> expected))) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) + (_.coverage [<check>] + (and (|> (/.result (<check> expected) (list (<code> expected))) + (!expect {try.#Success []})) + (|> (/.result (<check> expected) (list (<code> dummy))) + (!expect {try.#Failure _})))) ))] [/.any /.this (# ! each code.bit random.bit) function.identity code.equivalence] @@ -98,13 +98,13 @@ [(do [! random.monad] [expected_left random.nat expected_right random.int] - (_.cover [<query>] - (|> (/.result (<query> (<>.and /.nat /.int)) - (list (<code> (list (code.nat expected_left) - (code.int expected_right))))) - (!expect (^.multi {try.#Success [actual_left actual_right]} - (and (# nat.equivalence = expected_left actual_left) - (# int.equivalence = expected_right actual_right)))))))] + (_.coverage [<query>] + (|> (/.result (<query> (<>.and /.nat /.int)) + (list (<code> (list (code.nat expected_left) + (code.int expected_right))))) + (!expect (^.multi {try.#Success [actual_left actual_right]} + (and (# nat.equivalence = expected_left actual_left) + (# int.equivalence = expected_right actual_right)))))))] [/.form code.form] [/.variant code.variant] @@ -113,48 +113,48 @@ (do [! random.monad] [expected_local random.nat expected_global random.int] - (_.cover [/.locally] - (|> (/.result (<>.and (/.locally (list (code.nat expected_local)) /.nat) - /.int) - (list (code.int expected_global))) - (!expect (^.multi {try.#Success [actual_local actual_global]} - (and (# nat.equivalence = expected_local actual_local) - (# int.equivalence = expected_global actual_global))))))) + (_.coverage [/.locally] + (|> (/.result (<>.and (/.locally (list (code.nat expected_local)) /.nat) + /.int) + (list (code.int expected_global))) + (!expect (^.multi {try.#Success [actual_local actual_global]} + (and (# nat.equivalence = expected_local actual_local) + (# int.equivalence = expected_global actual_global))))))) (do [! random.monad] [dummy (# ! each code.bit random.bit)] - (_.cover [/.end?] - (|> (/.result (do <>.monad - [pre /.end? - _ /.any - post /.end?] - (in (and (not pre) - post))) - (list dummy)) - (!expect (^.multi {try.#Success verdict} - verdict))))) + (_.coverage [/.end?] + (|> (/.result (do <>.monad + [pre /.end? + _ /.any + post /.end?] + (in (and (not pre) + post))) + (list dummy)) + (!expect (^.multi {try.#Success verdict} + verdict))))) (do [! random.monad] [dummy (# ! each code.bit random.bit)] - (_.cover [/.end] - (and (|> (/.result /.end (list)) - (!expect {try.#Success []})) - (|> (/.result /.end (list dummy)) - (!expect {try.#Failure _}))))) + (_.coverage [/.end] + (and (|> (/.result /.end (list)) + (!expect {try.#Success []})) + (|> (/.result /.end (list dummy)) + (!expect {try.#Failure _}))))) (do [! random.monad] [expected (# ! each code.bit random.bit)] - (_.cover [/.next] - (|> (/.result (do <>.monad - [pre /.next - post /.any] - (in (and (same? expected pre) - (same? pre post)))) - (list expected)) - (!expect {try.#Success _})))) + (_.coverage [/.next] + (|> (/.result (do <>.monad + [pre /.next + post /.any] + (in (and (same? expected pre) + (same? pre post)))) + (list expected)) + (!expect {try.#Success _})))) (do [! random.monad] [expected (# ! each code.bit random.bit)] - (_.cover [/.not] - (and (|> (/.result (/.not /.nat) (list expected)) - (!expect (^.multi {try.#Success actual} - (same? expected actual)))) - (|> (/.result (/.not /.bit) (list expected)) - (!expect {try.#Failure _}))))) + (_.coverage [/.not] + (and (|> (/.result (/.not /.nat) (list expected)) + (!expect (^.multi {try.#Success actual} + (same? expected actual)))) + (|> (/.result (/.not /.bit) (list expected)) + (!expect {try.#Failure _}))))) )))) diff --git a/stdlib/source/test/lux/control/parser/environment.lux b/stdlib/source/test/lux/control/parser/environment.lux index 4c9dafeab..3f1c4bd6d 100644 --- a/stdlib/source/test/lux/control/parser/environment.lux +++ b/stdlib/source/test/lux/control/parser/environment.lux @@ -24,30 +24,30 @@ (<| (_.covering /._) (_.for [/.Environment /.Parser]) (all _.and - (_.cover [/.empty] - (dictionary.empty? /.empty)) + (_.coverage [/.empty] + (dictionary.empty? /.empty)) (do random.monad [expected random.nat] - (_.cover [/.result] - (|> (/.result (//#in expected) /.empty) - (# try.functor each (n.= expected)) - (try.else false)))) + (_.coverage [/.result] + (|> (/.result (//#in expected) /.empty) + (# try.functor each (n.= expected)) + (try.else false)))) (do random.monad [property (random.alphabetic 1) expected (random.alphabetic 1)] - (_.cover [/.Property /.property] - (|> /.empty - (dictionary.has property expected) - (/.result (/.property property)) - (# try.functor each (text#= expected)) - (try.else false)))) + (_.coverage [/.Property /.property] + (|> /.empty + (dictionary.has property expected) + (/.result (/.property property)) + (# try.functor each (text#= expected)) + (try.else false)))) (do random.monad [property (random.alphabetic 1)] - (_.cover [/.unknown_property] - (case (/.result (/.property property) /.empty) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.unknown_property error)))) + (_.coverage [/.unknown_property] + (case (/.result (/.property property) /.empty) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.unknown_property error)))) ))) diff --git a/stdlib/source/test/lux/control/parser/json.lux b/stdlib/source/test/lux/control/parser/json.lux index 55387d165..40d48afab 100644 --- a/stdlib/source/test/lux/control/parser/json.lux +++ b/stdlib/source/test/lux/control/parser/json.lux @@ -49,32 +49,32 @@ (`` (all _.and (do [! random.monad] [expected (# ! each (|>> {json.#String}) (random.unicode 1))] - (_.cover [/.result /.any] - (|> (/.result /.any expected) - (!expect (^.multi {try.#Success actual} - (# json.equivalence = expected actual)))))) - (_.cover [/.null] - (|> (/.result /.null {json.#Null}) - (!expect {try.#Success _}))) + (_.coverage [/.result /.any] + (|> (/.result /.any expected) + (!expect (^.multi {try.#Success actual} + (# json.equivalence = expected actual)))))) + (_.coverage [/.null] + (|> (/.result /.null {json.#Null}) + (!expect {try.#Success _}))) (~~ (template [<query> <test> <check> <random> <json> <equivalence>] [(do [! random.monad] [expected <random> dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))] (all _.and - (_.cover [<query>] - (|> (/.result <query> {<json> expected}) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))) - (_.cover [<test>] - (and (|> (/.result (<test> expected) {<json> expected}) - (!expect {try.#Success #1})) - (|> (/.result (<test> expected) {<json> dummy}) - (!expect {try.#Success #0})))) - (_.cover [<check>] - (and (|> (/.result (<check> expected) {<json> expected}) - (!expect {try.#Success _})) - (|> (/.result (<check> expected) {<json> dummy}) - (!expect {try.#Failure _}))))))] + (_.coverage [<query>] + (|> (/.result <query> {<json> expected}) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) + (_.coverage [<test>] + (and (|> (/.result (<test> expected) {<json> expected}) + (!expect {try.#Success #1})) + (|> (/.result (<test> expected) {<json> dummy}) + (!expect {try.#Success #0})))) + (_.coverage [<check>] + (and (|> (/.result (<check> expected) {<json> expected}) + (!expect {try.#Success _})) + (|> (/.result (<check> expected) {<json> dummy}) + (!expect {try.#Failure _}))))))] [/.boolean /.boolean? /.this_boolean random.bit json.#Boolean bit.equivalence] [/.number /.number? /.this_number ..safe_frac json.#Number frac.equivalence] @@ -83,46 +83,46 @@ (do [! random.monad] [expected (random.unicode 1) dummy random.bit] - (_.cover [/.unexpected_value] - (|> (/.result /.string {json.#Boolean dummy}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unexpected_value error)))))) + (_.coverage [/.unexpected_value] + (|> (/.result /.string {json.#Boolean dummy}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unexpected_value error)))))) (do [! random.monad] [expected (random.unicode 1) dummy (|> (random.unicode 1) (random.only (|>> (# text.equivalence = expected) not)))] - (_.cover [/.value_mismatch] - (|> (/.result (/.this_string expected) {json.#String dummy}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.value_mismatch error)))))) + (_.coverage [/.value_mismatch] + (|> (/.result (/.this_string expected) {json.#String dummy}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.value_mismatch error)))))) (do [! random.monad] [expected (random.unicode 1)] - (_.cover [/.nullable] - (and (|> (/.result (/.nullable /.string) {json.#Null}) - (!expect (^.multi {try.#Success actual} - (# (maybe.equivalence text.equivalence) = {.#None} actual)))) - (|> (/.result (/.nullable /.string) {json.#String expected}) - (!expect (^.multi {try.#Success actual} - (# (maybe.equivalence text.equivalence) = {.#Some expected} actual))))))) + (_.coverage [/.nullable] + (and (|> (/.result (/.nullable /.string) {json.#Null}) + (!expect (^.multi {try.#Success actual} + (# (maybe.equivalence text.equivalence) = {.#None} actual)))) + (|> (/.result (/.nullable /.string) {json.#String expected}) + (!expect (^.multi {try.#Success actual} + (# (maybe.equivalence text.equivalence) = {.#Some expected} actual))))))) (do [! random.monad] [size (# ! each (n.% 10) random.nat) expected (|> (random.unicode 1) (random.list size) (# ! each sequence.of_list))] - (_.cover [/.array] - (|> (/.result (/.array (<>.some /.string)) - {json.#Array (sequence#each (|>> {json.#String}) expected)}) - (!expect (^.multi {try.#Success actual} - (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual))))))) + (_.coverage [/.array] + (|> (/.result (/.array (<>.some /.string)) + {json.#Array (sequence#each (|>> {json.#String}) expected)}) + (!expect (^.multi {try.#Success actual} + (# (sequence.equivalence text.equivalence) = expected (sequence.of_list actual))))))) (do [! random.monad] [expected (# ! each (|>> {json.#String}) (random.unicode 1))] - (_.cover [/.unconsumed_input] - (|> (/.result (/.array /.any) {json.#Array (sequence expected expected)}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) - (_.cover [/.empty_input] - (|> (/.result (/.array /.any) {json.#Array (sequence)}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.empty_input error))))) + (_.coverage [/.unconsumed_input] + (|> (/.result (/.array /.any) {json.#Array (sequence expected expected)}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) + (_.coverage [/.empty_input] + (|> (/.result (/.array /.any) {json.#Array (sequence)}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))) (do [! random.monad] [expected_boolean random.bit expected_number ..safe_frac @@ -135,32 +135,32 @@ _ (undefined)))))] - (_.cover [/.object /.field] - (|> (/.result (/.object (all <>.and - (/.field boolean_field /.boolean) - (/.field number_field /.number) - (/.field string_field /.string))) - {json.#Object - (dictionary.of_list text.hash - (list [boolean_field {json.#Boolean expected_boolean}] - [number_field {json.#Number expected_number}] - [string_field {json.#String expected_string}]))}) - (!expect (^.multi {try.#Success [actual_boolean actual_number actual_string]} - (and (# bit.equivalence = expected_boolean actual_boolean) - (# frac.equivalence = expected_number actual_number) - (# text.equivalence = expected_string actual_string))))))) + (_.coverage [/.object /.field] + (|> (/.result (/.object (all <>.and + (/.field boolean_field /.boolean) + (/.field number_field /.number) + (/.field string_field /.string))) + {json.#Object + (dictionary.of_list text.hash + (list [boolean_field {json.#Boolean expected_boolean}] + [number_field {json.#Number expected_number}] + [string_field {json.#String expected_string}]))}) + (!expect (^.multi {try.#Success [actual_boolean actual_number actual_string]} + (and (# bit.equivalence = expected_boolean actual_boolean) + (# frac.equivalence = expected_number actual_number) + (# text.equivalence = expected_string actual_string))))))) (do [! random.monad] [size (# ! each (n.% 10) random.nat) keys (random.list size (random.unicode 1)) values (random.list size (random.unicode 1)) .let [expected (dictionary.of_list text.hash (list.zipped_2 keys values))]] - (_.cover [/.dictionary] - (|> (/.result (/.dictionary /.string) - {json.#Object - (|> values - (list#each (|>> {json.#String})) - (list.zipped_2 keys) - (dictionary.of_list text.hash))}) - (!expect (^.multi {try.#Success actual} - (# (dictionary.equivalence text.equivalence) = expected actual)))))) + (_.coverage [/.dictionary] + (|> (/.result (/.dictionary /.string) + {json.#Object + (|> values + (list#each (|>> {json.#String})) + (list.zipped_2 keys) + (dictionary.of_list text.hash))}) + (!expect (^.multi {try.#Success actual} + (# (dictionary.equivalence text.equivalence) = expected actual)))))) )))) diff --git a/stdlib/source/test/lux/control/parser/synthesis.lux b/stdlib/source/test/lux/control/parser/synthesis.lux index addb7c149..4cf859a46 100644 --- a/stdlib/source/test/lux/control/parser/synthesis.lux +++ b/stdlib/source/test/lux/control/parser/synthesis.lux @@ -68,16 +68,16 @@ [expected <random> dummy (|> <random> (random.only (|>> (# <equivalence> = expected) not)))] (all _.and - (_.cover [<query>] - (|> (/.result <query> (list (<synthesis> expected))) - (!expect (^.multi {try.#Success actual} - (# <equivalence> = expected actual))))) - (_.cover [<check>] - (and (|> (/.result (<check> expected) (list (<synthesis> expected))) - (!expect {try.#Success _})) - (|> (/.result (<check> expected) (list (<synthesis> dummy))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error)))))) + (_.coverage [<query>] + (|> (/.result <query> (list (<synthesis> expected))) + (!expect (^.multi {try.#Success actual} + (# <equivalence> = expected actual))))) + (_.coverage [<check>] + (and (|> (/.result (<check> expected) (list (<synthesis> expected))) + (!expect {try.#Success _})) + (|> (/.result (<check> expected) (list (<synthesis> dummy))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error)))))) ))] [/.bit /.this_bit random.bit synthesis.bit bit.equivalence] @@ -98,66 +98,66 @@ expected_i64 random.i64 expected_f64 random.safe_frac expected_text (random.unicode 1)] - (_.cover [/.tuple] - (and (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) - (list (synthesis.tuple (list (synthesis.bit expected_bit) - (synthesis.i64 expected_i64) - (synthesis.f64 expected_f64) - (synthesis.text expected_text))))) - (!expect (^.multi {try.#Success [actual_bit actual_i64 actual_f64 actual_text]} - (and (# bit.equivalence = expected_bit actual_bit) - (# i64.equivalence = expected_i64 actual_i64) - (# frac.equivalence = expected_f64 actual_f64) - (# text.equivalence = expected_text actual_text))))) - (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) - (list (synthesis.text expected_text))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (_.coverage [/.tuple] + (and (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) + (list (synthesis.tuple (list (synthesis.bit expected_bit) + (synthesis.i64 expected_i64) + (synthesis.f64 expected_f64) + (synthesis.text expected_text))))) + (!expect (^.multi {try.#Success [actual_bit actual_i64 actual_f64 actual_text]} + (and (# bit.equivalence = expected_bit actual_bit) + (# i64.equivalence = expected_i64 actual_i64) + (# frac.equivalence = expected_f64 actual_f64) + (# text.equivalence = expected_text actual_text))))) + (|> (/.result (/.tuple (all <>.and /.bit /.i64 /.f64 /.text)) + (list (synthesis.text expected_text))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment expected_body (random.unicode 1)] - (_.cover [/.function] - (and (|> (/.result (/.function arity /.text) - (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) - (!expect (^.multi {try.#Success [actual_environment actual_body]} - (and (# (list.equivalence synthesis.equivalence) = - expected_environment - actual_environment) - (# text.equivalence = expected_body actual_body))))) - (|> (/.result (/.function arity /.text) - (list (synthesis.text expected_body))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (_.coverage [/.function] + (and (|> (/.result (/.function arity /.text) + (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) + (!expect (^.multi {try.#Success [actual_environment actual_body]} + (and (# (list.equivalence synthesis.equivalence) = + expected_environment + actual_environment) + (# text.equivalence = expected_body actual_body))))) + (|> (/.result (/.function arity /.text) + (list (synthesis.text expected_body))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [arity random.nat expected_environment ..random_environment expected_body (random.unicode 1)] - (_.cover [/.wrong_arity] - (|> (/.result (/.function (++ arity) /.text) - (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.wrong_arity error)))))) + (_.coverage [/.wrong_arity] + (|> (/.result (/.function (++ arity) /.text) + (list (synthesis.function/abstraction [expected_environment arity (synthesis.text expected_body)]))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.wrong_arity error)))))) (do [! random.monad] [arity (# ! each (|>> (n.% 10) ++) random.nat) expected_offset random.nat expected_inits (random.list arity random.bit) expected_body (random.unicode 1)] - (_.cover [/.loop] - (and (|> (/.result (/.loop (<>.many /.bit) /.text) - (list (synthesis.loop/scope [expected_offset - (list#each (|>> synthesis.bit) expected_inits) - (synthesis.text expected_body)]))) - (!expect (^.multi {try.#Success [actual_offset actual_inits actual_body]} - (and (# n.equivalence = expected_offset actual_offset) - (# (list.equivalence bit.equivalence) = - expected_inits - actual_inits) - (# text.equivalence = expected_body actual_body))))) - (|> (/.result (/.loop (<>.many /.bit) /.text) - (list (synthesis.text expected_body))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (_.coverage [/.loop] + (and (|> (/.result (/.loop (<>.many /.bit) /.text) + (list (synthesis.loop/scope [expected_offset + (list#each (|>> synthesis.bit) expected_inits) + (synthesis.text expected_body)]))) + (!expect (^.multi {try.#Success [actual_offset actual_inits actual_body]} + (and (# n.equivalence = expected_offset actual_offset) + (# (list.equivalence bit.equivalence) = + expected_inits + actual_inits) + (# text.equivalence = expected_body actual_body))))) + (|> (/.result (/.loop (<>.many /.bit) /.text) + (list (synthesis.text expected_body))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) )) (def: .public test @@ -167,35 +167,35 @@ (all _.and (do [! random.monad] [expected (# ! each (|>> synthesis.i64) random.i64)] - (_.cover [/.result /.any] - (|> (/.result /.any (list expected)) - (!expect (^.multi {try.#Success actual} - (# synthesis.equivalence = expected actual)))))) - (_.cover [/.empty_input] - (|> (/.result /.any (list)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.empty_input error))))) + (_.coverage [/.result /.any] + (|> (/.result /.any (list expected)) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual)))))) + (_.coverage [/.empty_input] + (|> (/.result /.any (list)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))) (do [! random.monad] [expected (# ! each (|>> synthesis.i64) random.i64)] - (_.cover [/.unconsumed_input] - (|> (/.result /.any (list expected expected)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (_.coverage [/.unconsumed_input] + (|> (/.result /.any (list expected expected)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) (do [! random.monad] [dummy (# ! each (|>> synthesis.i64) random.i64)] - (_.cover [/.end /.expected_empty_input] - (and (|> (/.result /.end (list)) - (!expect {try.#Success _})) - (|> (/.result /.end (list dummy)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.expected_empty_input error))))))) + (_.coverage [/.end /.expected_empty_input] + (and (|> (/.result /.end (list)) + (!expect {try.#Success _})) + (|> (/.result /.end (list dummy)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_empty_input error))))))) (do [! random.monad] [dummy (# ! each (|>> synthesis.i64) random.i64)] - (_.cover [/.end?] - (and (|> (/.result /.end? (list)) - (!expect {try.#Success #1})) - (|> (/.result (<>.before /.any /.end?) (list dummy)) - (!expect {try.#Success #0}))))) + (_.coverage [/.end?] + (and (|> (/.result /.end? (list)) + (!expect {try.#Success #1})) + (|> (/.result (<>.before /.any /.end?) (list dummy)) + (!expect {try.#Success #0}))))) (_.for [/.cannot_parse] (all _.and ..simple diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index eb09bad2a..94f067ef7 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -80,50 +80,50 @@ out_of_range (case offset 0 (# ! each (|>> (n.% 10) ++ (n.+ limit) text.of_char) random.nat) _ (# ! each (|>> (n.% offset) text.of_char) random.nat))] - (_.cover [/.range] - (and (..should_pass expected (/.range offset limit)) - (..should_fail out_of_range (/.range offset limit))))) + (_.coverage [/.range] + (and (..should_pass expected (/.range offset limit)) + (..should_fail out_of_range (/.range offset limit))))) (do [! random.monad] [expected (random.char unicode.upper_case) invalid (random.only (|>> (unicode/block.within? unicode/block.upper_case) not) (random.char unicode.character))] - (_.cover [/.upper] - (and (..should_pass (text.of_char expected) /.upper) - (..should_fail (text.of_char invalid) /.upper)))) + (_.coverage [/.upper] + (and (..should_pass (text.of_char expected) /.upper) + (..should_fail (text.of_char invalid) /.upper)))) (do [! random.monad] [expected (random.char unicode.lower_case) invalid (random.only (|>> (unicode/block.within? unicode/block.lower_case) not) (random.char unicode.character))] - (_.cover [/.lower] - (and (..should_pass (text.of_char expected) /.lower) - (..should_fail (text.of_char invalid) /.lower)))) + (_.coverage [/.lower] + (and (..should_pass (text.of_char expected) /.lower) + (..should_fail (text.of_char invalid) /.lower)))) (do [! random.monad] [expected (# ! each (n.% 10) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] - (_.cover [/.decimal] - (and (..should_pass (# n.decimal encoded expected) /.decimal) - (..should_fail (text.of_char invalid) /.decimal)))) + (_.coverage [/.decimal] + (and (..should_pass (# n.decimal encoded expected) /.decimal) + (..should_fail (text.of_char invalid) /.decimal)))) (do [! random.monad] [expected (# ! each (n.% 8) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] - (_.cover [/.octal] - (and (..should_pass (# n.octal encoded expected) /.octal) - (..should_fail (text.of_char invalid) /.octal)))) + (_.coverage [/.octal] + (and (..should_pass (# n.octal encoded expected) /.octal) + (..should_fail (text.of_char invalid) /.octal)))) (do [! random.monad] [expected (# ! each (n.% 16) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] - (_.cover [/.hexadecimal] - (and (..should_pass (# n.hex encoded expected) /.hexadecimal) - (..should_fail (text.of_char invalid) /.hexadecimal)))) + (_.coverage [/.hexadecimal] + (and (..should_pass (# n.hex encoded expected) /.hexadecimal) + (..should_fail (text.of_char invalid) /.hexadecimal)))) (do [! random.monad] [expected (random.char unicode.alphabetic) invalid (random.only (function (_ char) (not (or (unicode/block.within? unicode/block.upper_case char) (unicode/block.within? unicode/block.lower_case char)))) (random.char unicode.character))] - (_.cover [/.alpha] - (and (..should_pass (text.of_char expected) /.alpha) - (..should_fail (text.of_char invalid) /.alpha)))) + (_.coverage [/.alpha] + (and (..should_pass (text.of_char expected) /.alpha) + (..should_fail (text.of_char invalid) /.alpha)))) (do [! random.monad] [expected (random.char unicode.alpha_numeric) invalid (random.only (function (_ char) @@ -131,9 +131,9 @@ (unicode/block.within? unicode/block.lower_case char) (unicode/block.within? unicode/block.numeric char)))) (random.char unicode.character))] - (_.cover [/.alpha_num] - (and (..should_pass (text.of_char expected) /.alpha_num) - (..should_fail (text.of_char invalid) /.alpha_num)))) + (_.coverage [/.alpha_num] + (and (..should_pass (text.of_char expected) /.alpha_num) + (..should_fail (text.of_char invalid) /.alpha_num)))) (do [! random.monad] [expected (all random.either (in text.tab) @@ -149,9 +149,9 @@ (text#= text.new_line char) (text#= text.carriage_return char) (text#= text.form_feed char))))))] - (_.cover [/.space] - (and (..should_pass expected /.space) - (..should_fail invalid /.space)))) + (_.coverage [/.space] + (and (..should_pass expected /.space) + (..should_fail invalid /.space)))) (do [! random.monad] [.let [num_options 3] options (|> (random.char unicode.character) @@ -167,17 +167,17 @@ invalid (random.only (function (_ char) (not (text.contains? (text.of_char char) options))) (random.char unicode.character))] - (_.cover [/.one_of /.one_of! /.character_should_be] - (and (..should_pass (text.of_char expected) (/.one_of options)) - (..should_fail (text.of_char invalid) (/.one_of options)) - (..should_fail' (text.of_char invalid) (/.one_of options) - /.character_should_be) + (_.coverage [/.one_of /.one_of! /.character_should_be] + (and (..should_pass (text.of_char expected) (/.one_of options)) + (..should_fail (text.of_char invalid) (/.one_of options)) + (..should_fail' (text.of_char invalid) (/.one_of options) + /.character_should_be) - (..should_pass! (text.of_char expected) (/.one_of! options)) - (..should_fail (text.of_char invalid) (/.one_of! options)) - (..should_fail' (text.of_char invalid) (/.one_of! options) - /.character_should_be) - ))) + (..should_pass! (text.of_char expected) (/.one_of! options)) + (..should_fail (text.of_char invalid) (/.one_of! options)) + (..should_fail' (text.of_char invalid) (/.one_of! options) + /.character_should_be) + ))) (do [! random.monad] [.let [num_options 3] options (|> (random.char unicode.character) @@ -193,17 +193,17 @@ expected (random.only (function (_ char) (not (text.contains? (text.of_char char) options))) (random.char unicode.character))] - (_.cover [/.none_of /.none_of! /.character_should_not_be] - (and (..should_pass (text.of_char expected) (/.none_of options)) - (..should_fail (text.of_char invalid) (/.none_of options)) - (..should_fail' (text.of_char invalid) (/.none_of options) - /.character_should_not_be) + (_.coverage [/.none_of /.none_of! /.character_should_not_be] + (and (..should_pass (text.of_char expected) (/.none_of options)) + (..should_fail (text.of_char invalid) (/.none_of options)) + (..should_fail' (text.of_char invalid) (/.none_of options) + /.character_should_not_be) - (..should_pass! (text.of_char expected) (/.none_of! options)) - (..should_fail (text.of_char invalid) (/.none_of! options)) - (..should_fail' (text.of_char invalid) (/.none_of! options) - /.character_should_not_be) - ))) + (..should_pass! (text.of_char expected) (/.none_of! options)) + (..should_fail (text.of_char invalid) (/.none_of! options)) + (..should_fail' (text.of_char invalid) (/.none_of! options) + /.character_should_not_be) + ))) )) (def: runs @@ -218,11 +218,11 @@ (# ! each (n.% 16)) (random.only (n.>= 8)) (# ! each (# n.hex encoded)))] - (_.cover [/.many /.many!] - (and (..should_pass expected (/.many /.octal)) - (..should_fail invalid (/.many /.octal)) + (_.coverage [/.many /.many!] + (and (..should_pass expected (/.many /.octal)) + (..should_fail invalid (/.many /.octal)) - (..should_pass! expected (/.many! octal!))))) + (..should_pass! expected (/.many! octal!))))) (do [! random.monad] [left (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat) right (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat) @@ -231,65 +231,65 @@ (# ! each (n.% 16)) (random.only (n.>= 8)) (# ! each (# n.hex encoded)))] - (_.cover [/.some /.some!] - (and (..should_pass expected (/.some /.octal)) - (..should_pass "" (/.some /.octal)) - (..should_fail invalid (/.some /.octal)) + (_.coverage [/.some /.some!] + (and (..should_pass expected (/.some /.octal)) + (..should_pass "" (/.some /.octal)) + (..should_fail invalid (/.some /.octal)) - (..should_pass! expected (/.some! octal!)) - (..should_pass! "" (/.some! octal!))))) + (..should_pass! expected (/.some! octal!)) + (..should_pass! "" (/.some! octal!))))) (do [! random.monad] [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)] first octal second octal third octal] - (_.cover [/.exactly /.exactly!] - (and (..should_pass (format first second) (/.exactly 2 /.octal)) - (..should_fail (format first second third) (/.exactly 2 /.octal)) - (..should_fail (format first) (/.exactly 2 /.octal)) + (_.coverage [/.exactly /.exactly!] + (and (..should_pass (format first second) (/.exactly 2 /.octal)) + (..should_fail (format first second third) (/.exactly 2 /.octal)) + (..should_fail (format first) (/.exactly 2 /.octal)) - (..should_pass! (format first second) (/.exactly! 2 octal!)) - (..should_fail (format first second third) (/.exactly! 2 octal!)) - (..should_fail (format first) (/.exactly! 2 octal!))))) + (..should_pass! (format first second) (/.exactly! 2 octal!)) + (..should_fail (format first second third) (/.exactly! 2 octal!)) + (..should_fail (format first) (/.exactly! 2 octal!))))) (do [! random.monad] [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)] first octal second octal third octal] - (_.cover [/.at_most /.at_most!] - (and (..should_pass (format first second) (/.at_most 2 /.octal)) - (..should_pass (format first) (/.at_most 2 /.octal)) - (..should_fail (format first second third) (/.at_most 2 /.octal)) + (_.coverage [/.at_most /.at_most!] + (and (..should_pass (format first second) (/.at_most 2 /.octal)) + (..should_pass (format first) (/.at_most 2 /.octal)) + (..should_fail (format first second third) (/.at_most 2 /.octal)) - (..should_pass! (format first second) (/.at_most! 2 octal!)) - (..should_pass! (format first) (/.at_most! 2 octal!)) - (..should_fail (format first second third) (/.at_most! 2 octal!))))) + (..should_pass! (format first second) (/.at_most! 2 octal!)) + (..should_pass! (format first) (/.at_most! 2 octal!)) + (..should_fail (format first second third) (/.at_most! 2 octal!))))) (do [! random.monad] [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)] first octal second octal third octal] - (_.cover [/.at_least /.at_least!] - (and (..should_pass (format first second) (/.at_least 2 /.octal)) - (..should_pass (format first second third) (/.at_least 2 /.octal)) - (..should_fail (format first) (/.at_least 2 /.octal)) + (_.coverage [/.at_least /.at_least!] + (and (..should_pass (format first second) (/.at_least 2 /.octal)) + (..should_pass (format first second third) (/.at_least 2 /.octal)) + (..should_fail (format first) (/.at_least 2 /.octal)) - (..should_pass! (format first second) (/.at_least! 2 octal!)) - (..should_pass! (format first second third) (/.at_least! 2 octal!)) - (..should_fail (format first) (/.at_least! 2 octal!))))) + (..should_pass! (format first second) (/.at_least! 2 octal!)) + (..should_pass! (format first second third) (/.at_least! 2 octal!)) + (..should_fail (format first) (/.at_least! 2 octal!))))) (do [! random.monad] [.let [octal (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)] first octal second octal third octal] - (_.cover [/.between /.between!] - (and (..should_pass (format first second) (/.between 2 1 /.octal)) - (..should_pass (format first second third) (/.between 2 1 /.octal)) - (..should_fail (format first) (/.between 2 1 /.octal)) + (_.coverage [/.between /.between!] + (and (..should_pass (format first second) (/.between 2 1 /.octal)) + (..should_pass (format first second third) (/.between 2 1 /.octal)) + (..should_fail (format first) (/.between 2 1 /.octal)) - (..should_pass! (format first second) (/.between! 2 1 octal!)) - (..should_pass! (format first second third) (/.between! 2 1 octal!)) - (..should_fail (format first) (/.between! 2 1 octal!))))) + (..should_pass! (format first second) (/.between! 2 1 octal!)) + (..should_pass! (format first second third) (/.between! 2 1 octal!)) + (..should_fail (format first) (/.between! 2 1 octal!))))) ))) (def: .public test @@ -299,121 +299,121 @@ (all _.and (do [! random.monad] [sample (random.unicode 1)] - (_.cover [/.result /.end] - (and (|> (/.result /.end - "") - (!expect {try.#Success _})) - (|> (/.result /.end - sample) - (!expect {try.#Failure _}))))) + (_.coverage [/.result /.end] + (and (|> (/.result /.end + "") + (!expect {try.#Success _})) + (|> (/.result /.end + sample) + (!expect {try.#Failure _}))))) (do [! random.monad] [.let [size 10] expected (random.unicode size) dummy (|> (random.unicode size) (random.only (|>> (text#= expected) not)))] - (_.cover [/.this /.cannot_match] - (and (|> (/.result (/.this expected) - expected) - (!expect {try.#Success []})) - (|> (/.result (/.this expected) - dummy) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_match error))))))) - (_.cover [/.Slice /.slice /.cannot_slice] - (|> "" - (/.result (/.slice /.any!)) + (_.coverage [/.this /.cannot_match] + (and (|> (/.result (/.this expected) + expected) + (!expect {try.#Success []})) + (|> (/.result (/.this expected) + dummy) (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_slice error))))) + (exception.match? /.cannot_match error))))))) + (_.coverage [/.Slice /.slice /.cannot_slice] + (|> "" + (/.result (/.slice /.any!)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_slice error))))) (do [! random.monad] [expected (random.unicode 1)] - (_.cover [/.any /.any!] - (and (..should_pass expected /.any) - (..should_fail "" /.any) + (_.coverage [/.any /.any!] + (and (..should_pass expected /.any) + (..should_fail "" /.any) - (..should_pass! expected /.any!) - (..should_fail "" /.any!)))) + (..should_pass! expected /.any!) + (..should_fail "" /.any!)))) (do [! random.monad] [expected (random.unicode 1)] - (_.cover [/.next /.cannot_parse] - (and (..should_pass expected (<>.before /.any /.next)) - (|> "" - (/.result (<>.before /.any /.next)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_parse error))))))) + (_.coverage [/.next /.cannot_parse] + (and (..should_pass expected (<>.before /.any /.next)) + (|> "" + (/.result (<>.before /.any /.next)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_parse error))))))) (do [! random.monad] [dummy (random.unicode 1)] - (_.cover [/.unconsumed_input] - (|> (format dummy dummy) - (/.result /.any) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unconsumed_input error)))))) + (_.coverage [/.unconsumed_input] + (|> (format dummy dummy) + (/.result /.any) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error)))))) (do [! random.monad] [sample (random.unicode 1)] - (_.cover [/.Offset /.offset] - (|> sample - (/.result (do <>.monad - [pre /.offset - _ /.any - post /.offset] - (in [pre post]))) - (!expect {try.#Success [0 1]})))) + (_.coverage [/.Offset /.offset] + (|> sample + (/.result (do <>.monad + [pre /.offset + _ /.any + post /.offset] + (in [pre post]))) + (!expect {try.#Success [0 1]})))) (do [! random.monad] [left (random.unicode 1) right (random.unicode 1) .let [input (format left right)]] - (_.cover [/.remaining] - (|> input - (/.result (do <>.monad - [pre /.remaining - _ /.any - post /.remaining - _ /.any] - (in (and (text#= input pre) - (text#= right post))))) - (!expect {try.#Success #1})))) + (_.coverage [/.remaining] + (|> input + (/.result (do <>.monad + [pre /.remaining + _ /.any + post /.remaining + _ /.any] + (in (and (text#= input pre) + (text#= right post))))) + (!expect {try.#Success #1})))) (do [! random.monad] [left (random.unicode 1) right (random.unicode 1) expected (random.only (|>> (text#= right) not) (random.unicode 1))] - (_.cover [/.enclosed] - (|> (format left expected right) - (/.result (/.enclosed [left right] (/.this expected))) - (!expect {try.#Success _})))) + (_.coverage [/.enclosed] + (|> (format left expected right) + (/.result (/.enclosed [left right] (/.this expected))) + (!expect {try.#Success _})))) (do [! random.monad] [input (random.unicode 1) output (random.unicode 1)] - (_.cover [/.local] - (|> output - (/.result (do <>.monad - [_ (/.local input (/.this input))] - (/.this output))) - (!expect {try.#Success _})))) + (_.coverage [/.local] + (|> output + (/.result (do <>.monad + [_ (/.local input (/.this input))] + (/.this output))) + (!expect {try.#Success _})))) (do [! random.monad] [expected (# ! each (|>> (n.% 8) (# n.octal encoded)) random.nat)] - (_.cover [/.then] - (|> (list (code.text expected)) - (<c>.result (/.then /.octal <c>.text)) - (!expect (^.multi {try.#Success actual} - (text#= expected actual)))))) + (_.coverage [/.then] + (|> (list (code.text expected)) + (<c>.result (/.then /.octal <c>.text)) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))))) (do [! random.monad] [invalid (random.upper_case 1) expected (random.only (|>> (unicode/block.within? unicode/block.upper_case) not) (random.char unicode.character)) .let [upper! (/.one_of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")]] - (_.cover [/.not /.not! /.expected_to_fail] - (and (..should_pass (text.of_char expected) (/.not /.upper)) - (|> invalid - (/.result (/.not /.upper)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.expected_to_fail error)))) + (_.coverage [/.not /.not! /.expected_to_fail] + (and (..should_pass (text.of_char expected) (/.not /.upper)) + (|> invalid + (/.result (/.not /.upper)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_to_fail error)))) - (..should_pass! (text.of_char expected) (/.not! upper!)) - (|> invalid - (/.result (/.not! upper!)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.expected_to_fail error))))))) + (..should_pass! (text.of_char expected) (/.not! upper!)) + (|> invalid + (/.result (/.not! upper!)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.expected_to_fail error))))))) (do [! random.monad] [upper (random.upper_case 1) lower (random.lower_case 1) @@ -423,21 +423,21 @@ (random.char unicode.character)) .let [upper! (/.one_of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ") lower! (/.one_of! "abcdefghijklmnopqrstuvwxyz")]] - (_.cover [/.and /.and!] - (and (..should_pass (format upper lower) (/.and /.upper /.lower)) - (..should_fail (format (text.of_char invalid) lower) (/.and /.upper /.lower)) - (..should_fail (format upper (text.of_char invalid)) (/.and /.upper /.lower)) + (_.coverage [/.and /.and!] + (and (..should_pass (format upper lower) (/.and /.upper /.lower)) + (..should_fail (format (text.of_char invalid) lower) (/.and /.upper /.lower)) + (..should_fail (format upper (text.of_char invalid)) (/.and /.upper /.lower)) - (..should_pass! (format upper lower) (/.and! upper! lower!)) - (..should_fail (format (text.of_char invalid) lower) (/.and! upper! lower!)) - (..should_fail (format upper (text.of_char invalid)) (/.and! upper! lower!))))) + (..should_pass! (format upper lower) (/.and! upper! lower!)) + (..should_fail (format (text.of_char invalid) lower) (/.and! upper! lower!)) + (..should_fail (format upper (text.of_char invalid)) (/.and! upper! lower!))))) (do [! random.monad] [expected (random.unicode 1) invalid (random.unicode 1)] - (_.cover [/.satisfies /.character_does_not_satisfy_predicate] - (and (..should_pass expected (/.satisfies (function.constant true))) - (..should_fail' invalid (/.satisfies (function.constant false)) - /.character_does_not_satisfy_predicate)))) + (_.coverage [/.satisfies /.character_does_not_satisfy_predicate] + (and (..should_pass expected (/.satisfies (function.constant true))) + (..should_fail' invalid (/.satisfies (function.constant false)) + /.character_does_not_satisfy_predicate)))) ..character_classes ..runs ))) diff --git a/stdlib/source/test/lux/control/parser/tree.lux b/stdlib/source/test/lux/control/parser/tree.lux index 4d014f42d..391e90014 100644 --- a/stdlib/source/test/lux/control/parser/tree.lux +++ b/stdlib/source/test/lux/control/parser/tree.lux @@ -33,23 +33,23 @@ [(do [! random.monad] [dummy random.nat expected (|> random.nat (random.only (|>> (n.= dummy) not)))] - (_.cover <coverage> - (|> (/.result <parser> - <sample>) - (!expect (^.multi {try.#Success actual} - (n.= expected actual))))))]) + (_.coverage <coverage> + (|> (/.result <parser> + <sample>) + (!expect (^.multi {try.#Success actual} + (n.= expected actual))))))]) (template: (!cover/2 <coverage> <parser> <sample0> <sample1>) [(do [! random.monad] [dummy random.nat expected (|> random.nat (random.only (|>> (n.= dummy) not)))] - (_.cover <coverage> - (and (|> (/.result <parser> <sample0>) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))) - (|> (/.result <parser> <sample1>) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))))))]) + (_.coverage <coverage> + (and (|> (/.result <parser> <sample0>) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) + (|> (/.result <parser> <sample1>) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))))]) (def: .public test Test @@ -61,11 +61,11 @@ (tree.leaf expected)) (do [! random.monad] [expected random.nat] - (_.cover [/.result'] - (|> (/.result' /.value - (zipper.zipper (tree.leaf expected))) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))))) + (_.coverage [/.result'] + (|> (/.result' /.value + (zipper.zipper (tree.leaf expected))) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))) (!cover [/.down] (do //.monad [_ /.down] @@ -161,15 +161,15 @@ (tree.leaf dummy)))) (do [! random.monad] [dummy random.nat] - (_.cover [/.cannot_move_further] - (`` (and (~~ (template [<parser>] - [(|> (/.result <parser> - (tree.leaf dummy)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.cannot_move_further error))))] + (_.coverage [/.cannot_move_further] + (`` (and (~~ (template [<parser>] + [(|> (/.result <parser> + (tree.leaf dummy)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.cannot_move_further error))))] - [/.down] [/.up] - [/.right] [/.left] - [/.next] [/.previous] - )))))) + [/.down] [/.up] + [/.right] [/.left] + [/.next] [/.previous] + )))))) ))) diff --git a/stdlib/source/test/lux/control/parser/type.lux b/stdlib/source/test/lux/control/parser/type.lux index a64688a8d..66f5114db 100644 --- a/stdlib/source/test/lux/control/parser/type.lux +++ b/stdlib/source/test/lux/control/parser/type.lux @@ -47,32 +47,32 @@ dummy (random.only (|>> (type#= expected) not) ..primitive)]) (all _.and - (_.cover [/.exactly] - (and (|> (/.result (/.exactly expected) expected) - (!expect {try.#Success []})) - (|> (/.result (/.exactly expected) dummy) - (!expect (^.multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) - (_.cover [/.sub] - (and (|> (/.result (/.sub expected) expected) - (!expect {try.#Success []})) - (|> (/.result (/.sub Any) expected) - (!expect {try.#Success []})) - (|> (/.result (/.sub expected) Nothing) - (!expect {try.#Success []})) - (|> (/.result (/.sub expected) dummy) - (!expect (^.multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) - (_.cover [/.super] - (and (|> (/.result (/.super expected) expected) - (!expect {try.#Success []})) - (|> (/.result (/.super expected) Any) - (!expect {try.#Success []})) - (|> (/.result (/.super Nothing) expected) - (!expect {try.#Success []})) - (|> (/.result (/.super expected) dummy) - (!expect (^.multi {try.#Failure error} - (exception.match? /.types_do_not_match error)))))) + (_.coverage [/.exactly] + (and (|> (/.result (/.exactly expected) expected) + (!expect {try.#Success []})) + (|> (/.result (/.exactly expected) dummy) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) + (_.coverage [/.sub] + (and (|> (/.result (/.sub expected) expected) + (!expect {try.#Success []})) + (|> (/.result (/.sub Any) expected) + (!expect {try.#Success []})) + (|> (/.result (/.sub expected) Nothing) + (!expect {try.#Success []})) + (|> (/.result (/.sub expected) dummy) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) + (_.coverage [/.super] + (and (|> (/.result (/.super expected) expected) + (!expect {try.#Success []})) + (|> (/.result (/.super expected) Any) + (!expect {try.#Success []})) + (|> (/.result (/.super Nothing) expected) + (!expect {try.#Success []})) + (|> (/.result (/.super expected) dummy) + (!expect (^.multi {try.#Failure error} + (exception.match? /.types_do_not_match error)))))) ))) (def: test|aggregate @@ -83,44 +83,44 @@ expected_right ..primitive] (`` (all _.and (~~ (template [<parser> <exception> <good_constructor> <bad_constructor>] - [(_.cover [<parser> <exception>] - (and (|> (/.result (<parser> (all //.and /.any /.any /.any)) - (<good_constructor> (list expected_left expected_middle expected_right))) - (!expect (^.multi {try.#Success [actual_left actual_middle actual_right]} - (and (type#= expected_left actual_left) - (type#= expected_middle actual_middle) - (type#= expected_right actual_right))))) - (|> (/.result (<parser> (all //.and /.any /.any /.any)) - (<bad_constructor> (list expected_left expected_middle expected_right))) - (!expect (^.multi {try.#Failure error} - (exception.match? <exception> error))))))] - - [/.variant /.not_variant type.variant type.tuple] - [/.tuple /.not_tuple type.tuple type.variant] - )) - - (_.cover [/.function /.not_function] - (and (|> (/.result (/.function (all //.and /.any /.any) /.any) - (type.function (list expected_left expected_middle) expected_right)) - (!expect (^.multi {try.#Success [[actual_left actual_middle] actual_right]} - (and (type#= expected_left actual_left) - (type#= expected_middle actual_middle) - (type#= expected_right actual_right))))) - (|> (/.result (/.function (all //.and /.any /.any) /.any) - (type.variant (list expected_left expected_middle expected_right))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_function error)))))) - (_.cover [/.applied /.not_application] - (and (|> (/.result (/.applied (all //.and /.any /.any /.any)) - (type.application (list expected_middle expected_right) expected_left)) + [(_.coverage [<parser> <exception>] + (and (|> (/.result (<parser> (all //.and /.any /.any /.any)) + (<good_constructor> (list expected_left expected_middle expected_right))) (!expect (^.multi {try.#Success [actual_left actual_middle actual_right]} (and (type#= expected_left actual_left) (type#= expected_middle actual_middle) (type#= expected_right actual_right))))) - (|> (/.result (/.applied (all //.and /.any /.any /.any)) - (type.variant (list expected_left expected_middle expected_right))) + (|> (/.result (<parser> (all //.and /.any /.any /.any)) + (<bad_constructor> (list expected_left expected_middle expected_right))) (!expect (^.multi {try.#Failure error} - (exception.match? /.not_application error)))))) + (exception.match? <exception> error))))))] + + [/.variant /.not_variant type.variant type.tuple] + [/.tuple /.not_tuple type.tuple type.variant] + )) + + (_.coverage [/.function /.not_function] + (and (|> (/.result (/.function (all //.and /.any /.any) /.any) + (type.function (list expected_left expected_middle) expected_right)) + (!expect (^.multi {try.#Success [[actual_left actual_middle] actual_right]} + (and (type#= expected_left actual_left) + (type#= expected_middle actual_middle) + (type#= expected_right actual_right))))) + (|> (/.result (/.function (all //.and /.any /.any) /.any) + (type.variant (list expected_left expected_middle expected_right))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_function error)))))) + (_.coverage [/.applied /.not_application] + (and (|> (/.result (/.applied (all //.and /.any /.any /.any)) + (type.application (list expected_middle expected_right) expected_left)) + (!expect (^.multi {try.#Success [actual_left actual_middle actual_right]} + (and (type#= expected_left actual_left) + (type#= expected_middle actual_middle) + (type#= expected_right actual_right))))) + (|> (/.result (/.applied (all //.and /.any /.any /.any)) + (type.variant (list expected_left expected_middle expected_right))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_application error)))))) )))) (def: test|parameter @@ -131,57 +131,57 @@ not_parameter ..primitive parameter random.nat] (all _.and - (_.cover [/.not_parameter] - (|> (/.result /.parameter not_parameter) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_parameter error))))) - (_.cover [/.unknown_parameter] - (|> (/.result /.parameter {.#Parameter parameter}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unknown_parameter error))))) - (_.cover [/.with_extension] - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - /.any) - not_parameter) - (!expect (^.multi {try.#Success [quantification##binding argument##binding actual]} - (same? not_parameter actual))))) - (_.cover [/.parameter] - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - /.parameter) - {.#Parameter 0}) - (!expect {try.#Success [quantification##binding argument##binding _]}))) - (_.cover [/.argument] - (let [argument? (is (-> Nat Nat Bit) - (function (_ @ expected) - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - (/.with_extension quantification) - (/.with_extension argument) - (do //.monad - [env /.env - _ /.any] - (in (/.argument env @)))) - not_parameter) - (!expect (^.multi {try.#Success [_ _ _ _ actual]} - (n.= expected actual))))))] - (and (argument? 0 2) - (argument? 1 3) - (argument? 2 0)))) - (_.cover [/.wrong_parameter] - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - (/.this_parameter 1)) - {.#Parameter 0}) - (!expect (^.multi {try.#Failure error} - (exception.match? /.wrong_parameter error))))) - (_.cover [/.this_parameter] - (|> (/.result (<| (/.with_extension quantification) - (/.with_extension argument) - (/.this_parameter 0)) - {.#Parameter 0}) - (!expect {try.#Success [quantification##binding argument##binding _]}))) + (_.coverage [/.not_parameter] + (|> (/.result /.parameter not_parameter) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_parameter error))))) + (_.coverage [/.unknown_parameter] + (|> (/.result /.parameter {.#Parameter parameter}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unknown_parameter error))))) + (_.coverage [/.with_extension] + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + /.any) + not_parameter) + (!expect (^.multi {try.#Success [quantification##binding argument##binding actual]} + (same? not_parameter actual))))) + (_.coverage [/.parameter] + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + /.parameter) + {.#Parameter 0}) + (!expect {try.#Success [quantification##binding argument##binding _]}))) + (_.coverage [/.argument] + (let [argument? (is (-> Nat Nat Bit) + (function (_ @ expected) + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + (/.with_extension quantification) + (/.with_extension argument) + (do //.monad + [env /.env + _ /.any] + (in (/.argument env @)))) + not_parameter) + (!expect (^.multi {try.#Success [_ _ _ _ actual]} + (n.= expected actual))))))] + (and (argument? 0 2) + (argument? 1 3) + (argument? 2 0)))) + (_.coverage [/.wrong_parameter] + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + (/.this_parameter 1)) + {.#Parameter 0}) + (!expect (^.multi {try.#Failure error} + (exception.match? /.wrong_parameter error))))) + (_.coverage [/.this_parameter] + (|> (/.result (<| (/.with_extension quantification) + (/.with_extension argument) + (/.this_parameter 0)) + {.#Parameter 0}) + (!expect {try.#Success [quantification##binding argument##binding _]}))) ))) (def: test|polymorphic @@ -190,21 +190,21 @@ [not_polymorphic ..primitive expected_inputs (# ! each (|>> (n.% 10) ++) random.nat)] (all _.and - (_.cover [/.not_polymorphic] - (and (|> (/.result (/.polymorphic /.any) - not_polymorphic) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_polymorphic error)))) - (|> (/.result (/.polymorphic /.any) - (type.univ_q 0 not_polymorphic)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_polymorphic error)))))) - (_.cover [/.polymorphic] - (|> (/.result (/.polymorphic /.any) - (type.univ_q expected_inputs not_polymorphic)) - (!expect (^.multi {try.#Success [g!poly actual_inputs bodyT]} - (and (n.= expected_inputs (list.size actual_inputs)) - (same? not_polymorphic bodyT)))))) + (_.coverage [/.not_polymorphic] + (and (|> (/.result (/.polymorphic /.any) + not_polymorphic) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_polymorphic error)))) + (|> (/.result (/.polymorphic /.any) + (type.univ_q 0 not_polymorphic)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_polymorphic error)))))) + (_.coverage [/.polymorphic] + (|> (/.result (/.polymorphic /.any) + (type.univ_q expected_inputs not_polymorphic)) + (!expect (^.multi {try.#Success [g!poly actual_inputs bodyT]} + (and (n.= expected_inputs (list.size actual_inputs)) + (same? not_polymorphic bodyT)))))) ))) (def: test|recursive @@ -212,29 +212,29 @@ (do random.monad [expected ..primitive] (all _.and - (_.cover [/.recursive] - (|> (.type (Rec @ expected)) - (/.result (/.recursive /.any)) - (!expect (^.multi {try.#Success [@self actual]} - (type#= expected actual))))) - (_.cover [/.recursive_self] - (|> (.type (Rec @ @)) - (/.result (/.recursive /.recursive_self)) - (!expect (^.multi {try.#Success [@expected @actual]} - (same? @expected @actual))))) - (_.cover [/.recursive_call] - (|> (.type (All (self input) (self input))) - (/.result (/.polymorphic /.recursive_call)) - (!expect {try.#Success [@self inputs ???]}))) - (_.cover [/.not_recursive] - (and (|> expected - (/.result (/.recursive /.any)) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_recursive error)))) - (|> expected - (/.result /.recursive_self) - (!expect (^.multi {try.#Failure error} - (exception.match? /.not_recursive error)))))) + (_.coverage [/.recursive] + (|> (.type (Rec @ expected)) + (/.result (/.recursive /.any)) + (!expect (^.multi {try.#Success [@self actual]} + (type#= expected actual))))) + (_.coverage [/.recursive_self] + (|> (.type (Rec @ @)) + (/.result (/.recursive /.recursive_self)) + (!expect (^.multi {try.#Success [@expected @actual]} + (same? @expected @actual))))) + (_.coverage [/.recursive_call] + (|> (.type (All (self input) (self input))) + (/.result (/.polymorphic /.recursive_call)) + (!expect {try.#Success [@self inputs ???]}))) + (_.coverage [/.not_recursive] + (and (|> expected + (/.result (/.recursive /.any)) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_recursive error)))) + (|> expected + (/.result /.recursive_self) + (!expect (^.multi {try.#Failure error} + (exception.match? /.not_recursive error)))))) ))) (def: .public test @@ -244,76 +244,76 @@ (all _.and (do [! random.monad] [expected ..primitive] - (_.cover [/.result /.any] - (|> (/.result /.any expected) - (!expect (^.multi {try.#Success actual} - (type#= expected actual)))))) + (_.coverage [/.result /.any] + (|> (/.result /.any expected) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))))) (do [! random.monad] [expected ..primitive] - (_.cover [/.next /.unconsumed_input] - (and (|> (/.result (do //.monad - [actual /.next - _ /.any] - (in actual)) - expected) - (!expect (^.multi {try.#Success actual} - (type#= expected actual)))) - (|> (/.result /.next expected) - (!expect (^.multi {try.#Failure error} - (exception.match? /.unconsumed_input error))))))) + (_.coverage [/.next /.unconsumed_input] + (and (|> (/.result (do //.monad + [actual /.next + _ /.any] + (in actual)) + expected) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))) + (|> (/.result /.next expected) + (!expect (^.multi {try.#Failure error} + (exception.match? /.unconsumed_input error))))))) (do [! random.monad] [expected ..primitive] - (_.cover [/.empty_input] - (`` (and (~~ (template [<parser>] - [(|> (/.result (do //.monad - [_ /.any] - <parser>) - expected) - (!expect (^.multi {try.#Failure error} - (exception.match? /.empty_input error))))] + (_.coverage [/.empty_input] + (`` (and (~~ (template [<parser>] + [(|> (/.result (do //.monad + [_ /.any] + <parser>) + expected) + (!expect (^.multi {try.#Failure error} + (exception.match? /.empty_input error))))] - [/.any] - [/.next] - )))))) + [/.any] + [/.next] + )))))) (do [! random.monad] [expected ..primitive] - (_.cover [/.Env /.env /.fresh] - (|> (/.result (do //.monad - [env /.env - _ /.any] - (in env)) - expected) - (!expect (^.multi {try.#Success environment} - (same? /.fresh environment)))))) + (_.coverage [/.Env /.env /.fresh] + (|> (/.result (do //.monad + [env /.env + _ /.any] + (in env)) + expected) + (!expect (^.multi {try.#Success environment} + (same? /.fresh environment)))))) (do [! random.monad] [expected ..primitive dummy (random.only (|>> (type#= expected) not) ..primitive)] - (_.cover [/.local] - (|> (/.result (do //.monad - [_ /.any] - (/.local (list expected) - /.any)) - dummy) - (!expect (^.multi {try.#Success actual} - (type#= expected actual)))))) + (_.coverage [/.local] + (|> (/.result (do //.monad + [_ /.any] + (/.local (list expected) + /.any)) + dummy) + (!expect (^.multi {try.#Success actual} + (type#= expected actual)))))) (do [! random.monad] [expected random.nat] - (_.cover [/.existential /.not_existential] - (|> (/.result /.existential - {.#Ex expected}) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))))) + (_.coverage [/.existential /.not_existential] + (|> (/.result /.existential + {.#Ex expected}) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))))) (do [! random.monad] [expected_name (random.and (random.alpha_numeric 1) (random.alpha_numeric 1)) expected_type ..primitive] - (_.cover [/.named /.not_named] - (|> (/.result /.named - {.#Named expected_name expected_type}) - (!expect (^.multi {try.#Success [actual_name actual_type]} - (and (symbol#= expected_name actual_name) - (type#= expected_type actual_type))))))) + (_.coverage [/.named /.not_named] + (|> (/.result /.named + {.#Named expected_name expected_type}) + (!expect (^.multi {try.#Success [actual_name actual_type]} + (and (symbol#= expected_name actual_name) + (type#= expected_type actual_type))))))) ..test|aggregate ..test|matches ..test|parameter diff --git a/stdlib/source/test/lux/control/parser/xml.lux b/stdlib/source/test/lux/control/parser/xml.lux index 10f8acc14..f3e19d428 100644 --- a/stdlib/source/test/lux/control/parser/xml.lux +++ b/stdlib/source/test/lux/control/parser/xml.lux @@ -40,13 +40,13 @@ [(with_expansions [<<cases>> (template.spliced <cases>)] (do [! random.monad] [expected (random.alphabetic 1)] - (_.cover [<exception>] - (`` (and (~~ (template [<parser> <input>] - [(|> (/.result <parser> (list <input>)) - (!expect (^.multi {try.#Failure error} - (exception.match? <exception> error))))] + (_.coverage [<exception>] + (`` (and (~~ (template [<parser> <input>] + [(|> (/.result <parser> (list <input>)) + (!expect (^.multi {try.#Failure error} + (exception.match? <exception> error))))] - <<cases>>)))))))]) + <<cases>>)))))))]) (def: random_label (Random Symbol) @@ -63,34 +63,34 @@ (all _.and (do [! random.monad] [expected (random.alphabetic 1)] - (_.cover [/.result /.text] - (|> (/.result /.text (list {xml.#Text expected})) - (!expect (^.multi {try.#Success actual} - (text#= expected actual)))))) + (_.coverage [/.result /.text] + (|> (/.result /.text (list {xml.#Text expected})) + (!expect (^.multi {try.#Success actual} + (text#= expected actual)))))) (!failure /.unconsumed_inputs [[(//#in expected) {xml.#Text expected}]]) (do [! random.monad] [expected (# ! each (|>> {xml.#Text}) (random.alphabetic 1))] - (_.cover [/.any] - (|> (/.result /.any (list expected)) - (try#each (xml#= expected)) - (try.else false)))) + (_.coverage [/.any] + (|> (/.result /.any (list expected)) + (try#each (xml#= expected)) + (try.else false)))) (do [! random.monad] [expected ..random_tag] - (_.cover [/.tag] - (|> (/.result (do //.monad - [actual /.tag - _ /.any] - (in (symbol#= expected actual))) - (list {xml.#Node expected (dictionary.empty symbol.hash) (list)})) - (!expect {try.#Success #1})))) + (_.coverage [/.tag] + (|> (/.result (do //.monad + [actual /.tag + _ /.any] + (in (symbol#= expected actual))) + (list {xml.#Node expected (dictionary.empty symbol.hash) (list)})) + (!expect {try.#Success #1})))) (do [! random.monad] [expected ..random_tag] - (_.cover [/.node] - (|> (/.result (/.node expected (//#in [])) - (list {xml.#Node expected (dictionary.empty symbol.hash) (list)})) - (!expect {try.#Success []})))) + (_.coverage [/.node] + (|> (/.result (/.node expected (//#in [])) + (list {xml.#Node expected (dictionary.empty symbol.hash) (list)})) + (!expect {try.#Success []})))) (!failure /.wrong_tag [[(/.node ["" expected] (//#in [])) {xml.#Node [expected ""] (dictionary.empty symbol.hash) (list)}]]) @@ -98,15 +98,15 @@ [expected_tag ..random_tag expected_attribute ..random_attribute expected_value (random.alphabetic 1)] - (_.cover [/.attribute] - (|> (/.result (<| (/.node expected_tag) - (//.after (/.attribute expected_attribute)) - (//#in [])) - (list {xml.#Node expected_tag - (|> (dictionary.empty symbol.hash) - (dictionary.has expected_attribute expected_value)) - (list)})) - (!expect {try.#Success []})))) + (_.coverage [/.attribute] + (|> (/.result (<| (/.node expected_tag) + (//.after (/.attribute expected_attribute)) + (//#in [])) + (list {xml.#Node expected_tag + (|> (dictionary.empty symbol.hash) + (dictionary.has expected_attribute expected_value)) + (list)})) + (!expect {try.#Success []})))) (!failure /.unknown_attribute [[(/.attribute ["" expected]) {xml.#Node [expected expected] @@ -163,18 +163,18 @@ (in [])))] repetitions (# ! each (n.% 10) random.nat)] (all _.and - (_.cover [/.somewhere] - (|> (/.result parser - (list (node parent - (list.together (list (list.repeated repetitions (node wrong (list))) - (list (node right (list))) - (list.repeated repetitions (node wrong (list)))))))) - (!expect {try.#Success []}))) - (_.cover [/.nowhere] - (|> (/.result parser - (list (node parent - (list.repeated repetitions (node wrong (list)))))) - (!expect (^.multi {try.#Failure error} - (exception.match? /.nowhere error))))) + (_.coverage [/.somewhere] + (|> (/.result parser + (list (node parent + (list.together (list (list.repeated repetitions (node wrong (list))) + (list (node right (list))) + (list.repeated repetitions (node wrong (list)))))))) + (!expect {try.#Success []}))) + (_.coverage [/.nowhere] + (|> (/.result parser + (list (node parent + (list.repeated repetitions (node wrong (list)))))) + (!expect (^.multi {try.#Failure error} + (exception.match? /.nowhere error))))) )) ))) diff --git a/stdlib/source/test/lux/control/pipe.lux b/stdlib/source/test/lux/control/pipe.lux index 04c181a69..3c1c53232 100644 --- a/stdlib/source/test/lux/control/pipe.lux +++ b/stdlib/source/test/lux/control/pipe.lux @@ -24,89 +24,89 @@ (all _.and (do ! [another random.nat] - (_.cover [/.new] - (n.= (++ another) - (|> sample - (n.* 3) - (n.+ 4) - (/.new another [++]))))) - (_.cover [/.let] - (n.= (n.+ sample sample) - (|> sample - (/.let x [(n.+ x x)])))) - (_.cover [/.cond] - (text#= (cond (n.= 0 sample) "zero" - (n.even? sample) "even" - "odd") - (|> sample - (/.cond [(n.= 0)] [(/.new "zero" [])] - [n.even?] [(/.new "even" [])] - [(/.new "odd" [])])))) - (_.cover [/.if] - (text#= (if (n.even? sample) - "even" - "odd") - (|> sample - (/.if [n.even?] - [(/.new "even" [])] - [(/.new "odd" [])])))) - (_.cover [/.when] - (n.= (if (n.even? sample) - (n.* 2 sample) - sample) - (|> sample - (/.when [n.even?] - [(n.* 2)])))) - (_.cover [/.while] - (n.= (n.* 10 sample) - (|> sample - (/.while [(n.= (n.* 10 sample)) not] - [(n.+ sample)])))) - (_.cover [/.do] - (n.= (++ (n.+ 4 (n.* 3 sample))) - (|> sample - (/.do identity.monad - [(n.* 3)] - [(n.+ 4)] - [++])))) - (_.cover [/.exec] - (n.= (n.* 10 sample) - (|> sample - (/.exec [%.nat (format "sample = ") debug.log!]) - (n.* 10)))) - (_.cover [/.tuple] - (let [[left middle right] (|> sample - (/.tuple [++] - [--] - [%.nat]))] - (and (n.= (++ sample) left) - (n.= (-- sample) middle) - (text#= (%.nat sample) right)))) - (_.cover [/.case] - (text#= (case (n.% 10 sample) - 0 "zero" - 1 "one" - 2 "two" - 3 "three" - 4 "four" - 5 "five" - 6 "six" - 7 "seven" - 8 "eight" - 9 "nine" - _ "???") - (|> sample - (n.% 10) - (/.case - 0 "zero" - 1 "one" - 2 "two" - 3 "three" - 4 "four" - 5 "five" - 6 "six" - 7 "seven" - 8 "eight" - 9 "nine" - _ "???")))) + (_.coverage [/.new] + (n.= (++ another) + (|> sample + (n.* 3) + (n.+ 4) + (/.new another [++]))))) + (_.coverage [/.let] + (n.= (n.+ sample sample) + (|> sample + (/.let x [(n.+ x x)])))) + (_.coverage [/.cond] + (text#= (cond (n.= 0 sample) "zero" + (n.even? sample) "even" + "odd") + (|> sample + (/.cond [(n.= 0)] [(/.new "zero" [])] + [n.even?] [(/.new "even" [])] + [(/.new "odd" [])])))) + (_.coverage [/.if] + (text#= (if (n.even? sample) + "even" + "odd") + (|> sample + (/.if [n.even?] + [(/.new "even" [])] + [(/.new "odd" [])])))) + (_.coverage [/.when] + (n.= (if (n.even? sample) + (n.* 2 sample) + sample) + (|> sample + (/.when [n.even?] + [(n.* 2)])))) + (_.coverage [/.while] + (n.= (n.* 10 sample) + (|> sample + (/.while [(n.= (n.* 10 sample)) not] + [(n.+ sample)])))) + (_.coverage [/.do] + (n.= (++ (n.+ 4 (n.* 3 sample))) + (|> sample + (/.do identity.monad + [(n.* 3)] + [(n.+ 4)] + [++])))) + (_.coverage [/.exec] + (n.= (n.* 10 sample) + (|> sample + (/.exec [%.nat (format "sample = ") debug.log!]) + (n.* 10)))) + (_.coverage [/.tuple] + (let [[left middle right] (|> sample + (/.tuple [++] + [--] + [%.nat]))] + (and (n.= (++ sample) left) + (n.= (-- sample) middle) + (text#= (%.nat sample) right)))) + (_.coverage [/.case] + (text#= (case (n.% 10 sample) + 0 "zero" + 1 "one" + 2 "two" + 3 "three" + 4 "four" + 5 "five" + 6 "six" + 7 "seven" + 8 "eight" + 9 "nine" + _ "???") + (|> sample + (n.% 10) + (/.case + 0 "zero" + 1 "one" + 2 "two" + 3 "three" + 4 "four" + 5 "five" + 6 "six" + 7 "seven" + 8 "eight" + 9 "nine" + _ "???")))) )))) diff --git a/stdlib/source/test/lux/control/reader.lux b/stdlib/source/test/lux/control/reader.lux index 4df1e2cdd..fead04bfa 100644 --- a/stdlib/source/test/lux/control/reader.lux +++ b/stdlib/source/test/lux/control/reader.lux @@ -42,19 +42,19 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.result /.read] - (n.= sample - (/.result sample /.read))) - (_.cover [/.local] - (n.= (n.* factor sample) - (/.result sample (/.local (n.* factor) /.read)))) + (_.coverage [/.result /.read] + (n.= sample + (/.result sample /.read))) + (_.coverage [/.local] + (n.= (n.* factor sample) + (/.result sample (/.local (n.* factor) /.read)))) (let [(open "io#[0]") io.monad] - (_.cover [/.with /.lifted] - (|> (is (/.Reader Any (IO Nat)) - (do (/.with io.monad) - [a (/.lifted (io#in sample)) - b (in factor)] - (in (n.* b a)))) - (/.result []) - io.run! - (n.= (n.* factor sample))))))))) + (_.coverage [/.with /.lifted] + (|> (is (/.Reader Any (IO Nat)) + (do (/.with io.monad) + [a (/.lifted (io#in sample)) + b (in factor)] + (in (n.* b a)))) + (/.result []) + io.run! + (n.= (n.* factor sample))))))))) diff --git a/stdlib/source/test/lux/control/region.lux b/stdlib/source/test/lux/control/region.lux index eb5ccd30a..da40cde51 100644 --- a/stdlib/source/test/lux/control/region.lux +++ b/stdlib/source/test/lux/control/region.lux @@ -96,93 +96,93 @@ (Monad (Region r (thread.Thread !)))) (/.monad thread.monad)))) - (_.cover [/.run!] - (thread.result - (do [! thread.monad] - [clean_up_counter (thread.box 0) - .let [//@ ! - count_clean_up (function (_ value) - (do ! - [_ (thread.update! ++ clean_up_counter)] - (in {try.#Success []})))] - outcome (/.run! ! - (do [! (/.monad !)] - [_ (monad.each ! (/.acquire! //@ count_clean_up) - (enum.range n.enum 1 expected_clean_ups))] - (in []))) - actual_clean_ups (thread.read! clean_up_counter)] - (in (and (..success? outcome) - (n.= expected_clean_ups - actual_clean_ups)))))) - (_.cover [/.failure] - (thread.result - (do [! thread.monad] - [clean_up_counter (thread.box 0) - .let [//@ ! - count_clean_up (function (_ value) - (do ! - [_ (thread.update! ++ clean_up_counter)] - (in {try.#Success []})))] - outcome (/.run! ! - (do [! (/.monad !)] - [_ (monad.each ! (/.acquire! //@ count_clean_up) - (enum.range n.enum 1 expected_clean_ups)) - _ (/.failure //@ (exception.error ..oops []))] - (in []))) - actual_clean_ups (thread.read! clean_up_counter)] - (in (and (..throws? ..oops outcome) - (n.= expected_clean_ups - actual_clean_ups)))))) - (_.cover [/.except] - (thread.result - (do [! thread.monad] - [clean_up_counter (thread.box 0) - .let [//@ ! - count_clean_up (function (_ value) - (do ! - [_ (thread.update! ++ clean_up_counter)] - (in {try.#Success []})))] - outcome (/.run! ! - (do [! (/.monad !)] - [_ (monad.each ! (/.acquire! //@ count_clean_up) - (enum.range n.enum 1 expected_clean_ups)) - _ (/.except //@ ..oops [])] - (in []))) - actual_clean_ups (thread.read! clean_up_counter)] - (in (and (..throws? ..oops outcome) - (n.= expected_clean_ups - actual_clean_ups)))))) - (_.cover [/.acquire! /.clean_up_error] - (thread.result - (do [! thread.monad] - [clean_up_counter (thread.box 0) - .let [//@ ! - count_clean_up (function (_ value) - (do ! - [_ (thread.update! ++ clean_up_counter)] - (in (is (Try Any) - (exception.except ..oops [])))))] - outcome (/.run! ! - (do [! (/.monad !)] - [_ (monad.each ! (/.acquire! //@ count_clean_up) - (enum.range n.enum 1 expected_clean_ups))] - (in []))) - actual_clean_ups (thread.read! clean_up_counter)] - (in (and (or (n.= 0 expected_clean_ups) - (..throws? /.clean_up_error outcome)) - (n.= expected_clean_ups - actual_clean_ups)))))) - (_.cover [/.lifted] - (thread.result - (do [! thread.monad] - [clean_up_counter (thread.box 0) - .let [//@ !] - outcome (/.run! ! - (do (/.monad !) - [_ (/.lifted //@ (thread.write! expected_clean_ups clean_up_counter))] - (in []))) - actual_clean_ups (thread.read! clean_up_counter)] - (in (and (..success? outcome) - (n.= expected_clean_ups - actual_clean_ups)))))) + (_.coverage [/.run!] + (thread.result + (do [! thread.monad] + [clean_up_counter (thread.box 0) + .let [//@ ! + count_clean_up (function (_ value) + (do ! + [_ (thread.update! ++ clean_up_counter)] + (in {try.#Success []})))] + outcome (/.run! ! + (do [! (/.monad !)] + [_ (monad.each ! (/.acquire! //@ count_clean_up) + (enum.range n.enum 1 expected_clean_ups))] + (in []))) + actual_clean_ups (thread.read! clean_up_counter)] + (in (and (..success? outcome) + (n.= expected_clean_ups + actual_clean_ups)))))) + (_.coverage [/.failure] + (thread.result + (do [! thread.monad] + [clean_up_counter (thread.box 0) + .let [//@ ! + count_clean_up (function (_ value) + (do ! + [_ (thread.update! ++ clean_up_counter)] + (in {try.#Success []})))] + outcome (/.run! ! + (do [! (/.monad !)] + [_ (monad.each ! (/.acquire! //@ count_clean_up) + (enum.range n.enum 1 expected_clean_ups)) + _ (/.failure //@ (exception.error ..oops []))] + (in []))) + actual_clean_ups (thread.read! clean_up_counter)] + (in (and (..throws? ..oops outcome) + (n.= expected_clean_ups + actual_clean_ups)))))) + (_.coverage [/.except] + (thread.result + (do [! thread.monad] + [clean_up_counter (thread.box 0) + .let [//@ ! + count_clean_up (function (_ value) + (do ! + [_ (thread.update! ++ clean_up_counter)] + (in {try.#Success []})))] + outcome (/.run! ! + (do [! (/.monad !)] + [_ (monad.each ! (/.acquire! //@ count_clean_up) + (enum.range n.enum 1 expected_clean_ups)) + _ (/.except //@ ..oops [])] + (in []))) + actual_clean_ups (thread.read! clean_up_counter)] + (in (and (..throws? ..oops outcome) + (n.= expected_clean_ups + actual_clean_ups)))))) + (_.coverage [/.acquire! /.clean_up_error] + (thread.result + (do [! thread.monad] + [clean_up_counter (thread.box 0) + .let [//@ ! + count_clean_up (function (_ value) + (do ! + [_ (thread.update! ++ clean_up_counter)] + (in (is (Try Any) + (exception.except ..oops [])))))] + outcome (/.run! ! + (do [! (/.monad !)] + [_ (monad.each ! (/.acquire! //@ count_clean_up) + (enum.range n.enum 1 expected_clean_ups))] + (in []))) + actual_clean_ups (thread.read! clean_up_counter)] + (in (and (or (n.= 0 expected_clean_ups) + (..throws? /.clean_up_error outcome)) + (n.= expected_clean_ups + actual_clean_ups)))))) + (_.coverage [/.lifted] + (thread.result + (do [! thread.monad] + [clean_up_counter (thread.box 0) + .let [//@ !] + outcome (/.run! ! + (do (/.monad !) + [_ (/.lifted //@ (thread.write! expected_clean_ups clean_up_counter))] + (in []))) + actual_clean_ups (thread.read! clean_up_counter)] + (in (and (..success? outcome) + (n.= expected_clean_ups + actual_clean_ups)))))) )))) diff --git a/stdlib/source/test/lux/control/remember.lux b/stdlib/source/test/lux/control/remember.lux index ecc1f4116..575e99aac 100644 --- a/stdlib/source/test/lux/control/remember.lux +++ b/stdlib/source/test/lux/control/remember.lux @@ -113,15 +113,15 @@ message ..message focus ..focus] (all _.and - (_.cover [/.must_remember] - (and (test_failure deadline message {.#None} - (exception.error /.must_remember [deadline deadline message {.#None}])) - (test_failure deadline message {.#Some focus} - (exception.error /.must_remember [deadline deadline message {.#Some focus}])))) - (_.cover [/.remember] - (..test_macro /.remember "")) - (_.cover [/.to_do] - (..test_macro /.to_do "TODO")) - (_.cover [/.fix_me] - (..test_macro /.fix_me "FIXME")) + (_.coverage [/.must_remember] + (and (test_failure deadline message {.#None} + (exception.error /.must_remember [deadline deadline message {.#None}])) + (test_failure deadline message {.#Some focus} + (exception.error /.must_remember [deadline deadline message {.#Some focus}])))) + (_.coverage [/.remember] + (..test_macro /.remember "")) + (_.coverage [/.to_do] + (..test_macro /.to_do "TODO")) + (_.coverage [/.fix_me] + (..test_macro /.fix_me "FIXME")) )))) diff --git a/stdlib/source/test/lux/control/security/capability.lux b/stdlib/source/test/lux/control/security/capability.lux index 31e711954..aa25ebd6c 100644 --- a/stdlib/source/test/lux/control/security/capability.lux +++ b/stdlib/source/test/lux/control/security/capability.lux @@ -31,15 +31,15 @@ pass_through (random.ascii 1)] (_.for [/.Capability] (all _.and - (_.cover [/.capability: /.use] - (let [capability (..can_shift (function (_ [no_op raw]) - [no_op (n.+ shift raw)])) - [untouched actual] (/.use capability [pass_through base])] - (and (same? pass_through untouched) - (n.= expected actual)))) + (_.coverage [/.capability: /.use] + (let [capability (..can_shift (function (_ [no_op raw]) + [no_op (n.+ shift raw)])) + [untouched actual] (/.use capability [pass_through base])] + (and (same? pass_through untouched) + (n.= expected actual)))) (in (let [capability (..can_io (function (_ _) (io.io expected)))] (do async.monad [actual (/.use (/.async capability) [])] - (_.cover' [/.async] - (n.= expected actual))))) + (_.coverage' [/.async] + (n.= expected actual))))) ))))) diff --git a/stdlib/source/test/lux/control/security/policy.lux b/stdlib/source/test/lux/control/security/policy.lux index 7067b6f70..afa9b2bda 100644 --- a/stdlib/source/test/lux/control/security/policy.lux +++ b/stdlib/source/test/lux/control/security/policy.lux @@ -89,12 +89,12 @@ (_.for [/.monad] ($monad.spec (..injection (# policy_0 #can_upgrade)) (..comparison (# policy_0 #can_downgrade)) /.monad)))) - (_.cover [/.Privilege /.Context /.with_policy] - (and (# policy_0 = password password) - (n.= (# text.hash hash raw_password) - (# policy_0 hash password)))) + (_.coverage [/.Privilege /.Context /.with_policy] + (and (# policy_0 = password password) + (n.= (# text.hash hash raw_password) + (# policy_0 hash password)))) (let [policy_1 (policy []) delegate (/.delegation (# policy_0 #can_downgrade) (# policy_1 #can_upgrade))] - (_.cover [/.Delegation /.delegation] - (# policy_1 = (delegate password) (delegate password)))) + (_.coverage [/.Delegation /.delegation] + (# policy_1 = (delegate password) (delegate password)))) )))) diff --git a/stdlib/source/test/lux/control/state.lux b/stdlib/source/test/lux/control/state.lux index 053170ad6..d821f5e62 100644 --- a/stdlib/source/test/lux/control/state.lux +++ b/stdlib/source/test/lux/control/state.lux @@ -32,26 +32,26 @@ [state random.nat value random.nat] (all _.and - (_.cover [/.State /.get] - (with_conditions [state state] - /.get)) - (_.cover [/.put] - (with_conditions [state value] - (do /.monad - [_ (/.put value)] + (_.coverage [/.State /.get] + (with_conditions [state state] + /.get)) + (_.coverage [/.put] + (with_conditions [state value] + (do /.monad + [_ (/.put value)] + /.get))) + (_.coverage [/.update] + (with_conditions [state (n.* value state)] + (do /.monad + [_ (/.update (n.* value))] + /.get))) + (_.coverage [/.use] + (with_conditions [state (++ state)] + (/.use ++))) + (_.coverage [/.local] + (with_conditions [state (n.* value state)] + (/.local (n.* value) /.get))) - (_.cover [/.update] - (with_conditions [state (n.* value state)] - (do /.monad - [_ (/.update (n.* value))] - /.get))) - (_.cover [/.use] - (with_conditions [state (++ state)] - (/.use ++))) - (_.cover [/.local] - (with_conditions [state (n.* value state)] - (/.local (n.* value) - /.get))) ))) (def: (injection value) @@ -86,18 +86,18 @@ [state /.get] (in (n.< limit state)))]] (all _.and - (_.cover [/.while /.result] - (|> (/.while condition (/.update ++)) - (/.result 0) - (pipe.let [state' output'] - (n.= limit state')))) - (_.cover [/.do_while] - (|> (/.do_while condition (/.update ++)) - (/.result 0) - (pipe.let [state' output'] - (or (n.= limit state') - (and (n.= 0 limit) - (n.= 1 state')))))) + (_.coverage [/.while /.result] + (|> (/.while condition (/.update ++)) + (/.result 0) + (pipe.let [state' output'] + (n.= limit state')))) + (_.coverage [/.do_while] + (|> (/.do_while condition (/.update ++)) + (/.result 0) + (pipe.let [state' output'] + (or (n.= limit state') + (and (n.= 0 limit) + (n.= 1 state')))))) ))) (def: monad_transformer @@ -107,17 +107,17 @@ left random.nat right random.nat] (let [(open "io#[0]") io.monad] - (_.cover [/.+State /.with /.lifted /.result'] - (|> (is (/.+State io.IO Nat Nat) - (do (/.with io.monad) - [a (/.lifted io.monad (io#in left)) - b (in right)] - (in (n.+ a b)))) - (/.result' state) - io.run! - (pipe.let [state' output'] - (and (n.= state state') - (n.= (n.+ left right) output'))))) + (_.coverage [/.+State /.with /.lifted /.result'] + (|> (is (/.+State io.IO Nat Nat) + (do (/.with io.monad) + [a (/.lifted io.monad (io#in left)) + b (in right)] + (in (n.+ a b)))) + (/.result' state) + io.run! + (pipe.let [state' output'] + (and (n.= state state') + (n.= (n.+ left right) output'))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/control/thread.lux b/stdlib/source/test/lux/control/thread.lux index 411a0c386..ed83c132f 100644 --- a/stdlib/source/test/lux/control/thread.lux +++ b/stdlib/source/test/lux/control/thread.lux @@ -35,17 +35,17 @@ (all _.and (_.for [/.Thread] (all _.and - (_.cover [/.result] - (n.= sample - (|> sample - (# /.monad in) - /.result))) - (_.cover [/.io] - (n.= sample - (|> sample - (# /.monad in) - /.io - io.run!))) + (_.coverage [/.result] + (n.= sample + (|> sample + (# /.monad in) + /.result))) + (_.coverage [/.io] + (n.= sample + (|> sample + (# /.monad in) + /.io + io.run!))) (_.for [/.functor] ($functor.spec ..injection ..comparison /.functor)) @@ -57,26 +57,26 @@ (_.for [/.Box /.box] (all _.and - (_.cover [/.read!] - (n.= sample - (/.result (is (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample)] - (/.read! box)))))) + (_.coverage [/.read!] + (n.= sample + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample)] + (/.read! box)))))) - (_.cover [/.write!] - (n.= factor - (/.result (is (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample) - _ (/.write! factor box)] - (/.read! box)))))) + (_.coverage [/.write!] + (n.= factor + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample) + _ (/.write! factor box)] + (/.read! box)))))) - (_.cover [/.update!] - (n.= (n.* factor sample) - (/.result (is (All (_ !) (Thread ! Nat)) - (do /.monad - [box (/.box sample) - [old new] (/.update! (n.* factor) box)] - (in new)))))))) + (_.coverage [/.update!] + (n.= (n.* factor sample) + (/.result (is (All (_ !) (Thread ! Nat)) + (do /.monad + [box (/.box sample) + [old new] (/.update! (n.* factor) box)] + (in new)))))))) )))) diff --git a/stdlib/source/test/lux/control/try.lux b/stdlib/source/test/lux/control/try.lux index 2919e59f8..1c9af6336 100644 --- a/stdlib/source/test/lux/control/try.lux +++ b/stdlib/source/test/lux/control/try.lux @@ -55,42 +55,42 @@ (_.for [/.monad] ($monad.spec ..injection ..comparison /.monad)) - (_.cover [/.trusted] - (n.= expected - (/.trusted {/.#Success expected}))) - (_.cover [/.of_maybe] - (case [(/.of_maybe {.#Some expected}) - (/.of_maybe {.#None})] - [{/.#Success actual} {/.#Failure _}] - (n.= expected actual) + (_.coverage [/.trusted] + (n.= expected + (/.trusted {/.#Success expected}))) + (_.coverage [/.of_maybe] + (case [(/.of_maybe {.#Some expected}) + (/.of_maybe {.#None})] + [{/.#Success actual} {/.#Failure _}] + (n.= expected actual) - _ - false)) - (_.cover [/.maybe] - (case [(/.maybe {/.#Success expected}) - (/.maybe (is (/.Try Nat) {/.#Failure error}))] - [{.#Some actual} {.#None}] - (n.= expected actual) + _ + false)) + (_.coverage [/.maybe] + (case [(/.maybe {/.#Success expected}) + (/.maybe (is (/.Try Nat) {/.#Failure error}))] + [{.#Some actual} {.#None}] + (n.= expected actual) - _ - false)) - (_.cover [/.else] - (and (n.= expected - (/.else alternative {/.#Success expected})) - (n.= alternative - (/.else alternative (is (Try Nat) {/.#Failure error}))))) - (_.cover [/.with /.lifted] - (let [lifted (/.lifted io.monad)] - (|> (do (/.with io.monad) - [a (lifted (io#in expected)) - b (in alternative)] - (in (n.+ a b))) - io.run! - (pipe.case - {/.#Success result} - (n.= (n.+ expected alternative) - result) + _ + false)) + (_.coverage [/.else] + (and (n.= expected + (/.else alternative {/.#Success expected})) + (n.= alternative + (/.else alternative (is (Try Nat) {/.#Failure error}))))) + (_.coverage [/.with /.lifted] + (let [lifted (/.lifted io.monad)] + (|> (do (/.with io.monad) + [a (lifted (io#in expected)) + b (in alternative)] + (in (n.+ a b))) + io.run! + (pipe.case + {/.#Success result} + (n.= (n.+ expected alternative) + result) - _ - false)))) + _ + false)))) ))) diff --git a/stdlib/source/test/lux/control/writer.lux b/stdlib/source/test/lux/control/writer.lux index 9842de747..418024334 100644 --- a/stdlib/source/test/lux/control/writer.lux +++ b/stdlib/source/test/lux/control/writer.lux @@ -47,17 +47,17 @@ (_.for [/.monad] ($monad.spec (..injection text.monoid) ..comparison (/.monad text.monoid))) - (_.cover [/.write] - (text#= log - (product.left (/.write log)))) - (_.cover [/.with /.lifted] - (let [lifted (/.lifted text.monoid io.monad) - (open "io#[0]") io.monad] - (|> (do (/.with text.monoid io.monad) - [a (lifted (io#in left)) - b (in right)] - (in (n.+ a b))) - io.run! - product.right - (n.= (n.+ left right))))) + (_.coverage [/.write] + (text#= log + (product.left (/.write log)))) + (_.coverage [/.with /.lifted] + (let [lifted (/.lifted text.monoid io.monad) + (open "io#[0]") io.monad] + (|> (do (/.with text.monoid io.monad) + [a (lifted (io#in left)) + b (in right)] + (in (n.+ a b))) + io.run! + product.right + (n.= (n.+ left right))))) )))) diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index d46560ddc..9e4e8e6b6 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -96,51 +96,51 @@ ($equivalence.spec (function (_ left right) (!.= left right)) (..random size))) - (_.cover [!.empty] - (!.= (!.empty size) (!.empty size))) - (_.cover [!.size] - (|> (!.empty size) !.size (n.= size))) + (_.coverage [!.empty] + (!.= (!.empty size) (!.empty size))) + (_.coverage [!.size] + (|> (!.empty size) !.size (n.= size))) (~~ (template [<power> <bytes/?> <has/?>] - [(_.cover [<bytes/?> <has/?>] - (let [bytes (i64.left_shifted <power> 1) - binary (!.empty bytes) - cap (case bytes - 8 (-- 0) - _ (|> 1 (i64.left_shifted (n.* 8 bytes)) --)) - capped_value (i64.and cap value) - - pre (<bytes/?> 0 binary) - _ (<has/?> 0 value binary) - post (<bytes/?> 0 binary)] - (and (n.= 0 pre) - (n.= capped_value post))))] + [(_.coverage [<bytes/?> <has/?>] + (let [bytes (i64.left_shifted <power> 1) + binary (!.empty bytes) + cap (case bytes + 8 (-- 0) + _ (|> 1 (i64.left_shifted (n.* 8 bytes)) --)) + capped_value (i64.and cap value) + + pre (<bytes/?> 0 binary) + _ (<has/?> 0 value binary) + post (<bytes/?> 0 binary)] + (and (n.= 0 pre) + (n.= capped_value post))))] [0 !.bits_8 !.has_8!] [1 !.bits_16 !.has_16!] [2 !.bits_32 !.has_32!] [3 !.bits_64 !.has_64!])) - (_.cover [!.slice] - (let [random_slice (!.slice offset length sample) - idxs (is (List Nat) - (case length - 0 (list) - _ (enum.range n.enum 0 (-- length)))) - reader (function (_ binary idx) - (!.bits_8 idx binary))] - (and (n.= length (!.size random_slice)) - (# (list.equivalence n.equivalence) = - (list#each (|>> (n.+ offset) (reader sample)) idxs) - (list#each (reader random_slice) idxs))))) - (_.cover [!.copy!] - (and (let [it (!.copy! size 0 sample 0 (!.empty size))] - (and (not (same? sample it)) - (!.= sample it))) - (let [sample/0 (!.bits_8 0 sample) - copy (!.copy! 1 0 sample 0 (!.empty 2)) - copy/0 (!.bits_8 0 copy) - copy/1 (!.bits_8 1 copy)] - (and (n.= sample/0 copy/0) - (n.= 0 copy/1))))) + (_.coverage [!.slice] + (let [random_slice (!.slice offset length sample) + idxs (is (List Nat) + (case length + 0 (list) + _ (enum.range n.enum 0 (-- length)))) + reader (function (_ binary idx) + (!.bits_8 idx binary))] + (and (n.= length (!.size random_slice)) + (# (list.equivalence n.equivalence) = + (list#each (|>> (n.+ offset) (reader sample)) idxs) + (list#each (reader random_slice) idxs))))) + (_.coverage [!.copy!] + (and (let [it (!.copy! size 0 sample 0 (!.empty size))] + (and (not (same? sample it)) + (!.= sample it))) + (let [sample/0 (!.bits_8 0 sample) + copy (!.copy! 1 0 sample 0 (!.empty 2)) + copy/0 (!.bits_8 0 copy) + copy/1 (!.bits_8 1 copy)] + (and (n.= sample/0 copy/0) + (n.= 0 copy/1))))) ))))) (def: .public test @@ -160,84 +160,84 @@ ($equivalence.spec /.equivalence (..random size))) (_.for [/.monoid] ($monoid.spec /.equivalence /.monoid (..random size))) - (_.cover [/.mix] - (n.= (# list.mix mix n.+ 0 (..as_list sample)) - (/.mix n.+ 0 sample))) + (_.coverage [/.mix] + (n.= (# list.mix mix n.+ 0 (..as_list sample)) + (/.mix n.+ 0 sample))) - (_.cover [/.empty] - (# /.equivalence = - (/.empty size) - (/.empty size))) - (_.cover [/.size] - (|> (/.empty size) /.size (n.= size))) + (_.coverage [/.empty] + (# /.equivalence = + (/.empty size) + (/.empty size))) + (_.coverage [/.size] + (|> (/.empty size) /.size (n.= size))) (_.for [/.index_out_of_bounds] (all _.and - (_.cover [/.bits_8 /.has_8!] - (..binary_io 0 /.bits_8 /.has_8! value)) - (_.cover [/.bits_16 /.has_16!] - (..binary_io 1 /.bits_16 /.has_16! value)) - (_.cover [/.bits_32 /.has_32!] - (..binary_io 2 /.bits_32 /.has_32! value)) - (_.cover [/.bits_64 /.has_64!] - (..binary_io 3 /.bits_64 /.has_64! value)))) - (_.cover [/.slice] - (let [random_slice (try.trusted (/.slice offset length sample)) - idxs (is (List Nat) - (case length - 0 (list) - _ (enum.range n.enum 0 (-- length)))) - reader (function (_ binary idx) - (/.bits_8 idx binary))] - (and (n.= length (/.size random_slice)) - (case [(monad.each try.monad (|>> (n.+ offset) (reader sample)) idxs) - (monad.each try.monad (reader random_slice) idxs)] - [{try.#Success binary_vals} {try.#Success slice_vals}] - (# (list.equivalence n.equivalence) = binary_vals slice_vals) + (_.coverage [/.bits_8 /.has_8!] + (..binary_io 0 /.bits_8 /.has_8! value)) + (_.coverage [/.bits_16 /.has_16!] + (..binary_io 1 /.bits_16 /.has_16! value)) + (_.coverage [/.bits_32 /.has_32!] + (..binary_io 2 /.bits_32 /.has_32! value)) + (_.coverage [/.bits_64 /.has_64!] + (..binary_io 3 /.bits_64 /.has_64! value)))) + (_.coverage [/.slice] + (let [random_slice (try.trusted (/.slice offset length sample)) + idxs (is (List Nat) + (case length + 0 (list) + _ (enum.range n.enum 0 (-- length)))) + reader (function (_ binary idx) + (/.bits_8 idx binary))] + (and (n.= length (/.size random_slice)) + (case [(monad.each try.monad (|>> (n.+ offset) (reader sample)) idxs) + (monad.each try.monad (reader random_slice) idxs)] + [{try.#Success binary_vals} {try.#Success slice_vals}] + (# (list.equivalence n.equivalence) = binary_vals slice_vals) - _ - #0)))) - (_.cover [/.slice_out_of_bounds] - (and (throws? /.slice_out_of_bounds (/.slice size size sample)) - (let [verdict (throws? /.slice_out_of_bounds (/.slice offset size sample))] - (case offset - 0 (not verdict) - _ verdict)))) - (_.cover [/.after] - (and (# /.equivalence = sample (/.after 0 sample)) - (# /.equivalence = (/.empty 0) (/.after size sample)) - (n.= (n.- offset size) (/.size (/.after offset sample))) - (case (list.reversed (..as_list sample)) - {.#End} - false + _ + #0)))) + (_.coverage [/.slice_out_of_bounds] + (and (throws? /.slice_out_of_bounds (/.slice size size sample)) + (let [verdict (throws? /.slice_out_of_bounds (/.slice offset size sample))] + (case offset + 0 (not verdict) + _ verdict)))) + (_.coverage [/.after] + (and (# /.equivalence = sample (/.after 0 sample)) + (# /.equivalence = (/.empty 0) (/.after size sample)) + (n.= (n.- offset size) (/.size (/.after offset sample))) + (case (list.reversed (..as_list sample)) + {.#End} + false - {.#Item head tail} - (n.= (list.mix n.+ 0 tail) - (/.mix n.+ 0 (/.after 1 sample)))))) - (_.cover [/.copy!] - (and (case (/.copy! size 0 sample 0 (/.empty size)) - {try.#Success output} - (and (not (same? sample output)) - (# /.equivalence = sample output)) + {.#Item head tail} + (n.= (list.mix n.+ 0 tail) + (/.mix n.+ 0 (/.after 1 sample)))))) + (_.coverage [/.copy!] + (and (case (/.copy! size 0 sample 0 (/.empty size)) + {try.#Success output} + (and (not (same? sample output)) + (# /.equivalence = sample output)) - {try.#Failure _} - false) - (succeed - (do try.monad - [sample/0 (/.bits_8 0 sample) - copy (/.copy! 1 0 sample 0 (/.empty 2)) - copy/0 (/.bits_8 0 copy) - copy/1 (/.bits_8 1 copy)] - (in (and (n.= sample/0 copy/0) - (n.= 0 copy/1))))))) - (_.cover [/.cannot_copy] - (and (not (throws? /.cannot_copy - (/.copy! size 0 sample 0 (/.empty size)))) - (throws? /.cannot_copy - (/.copy! (n.+ offset size) 0 sample 0 (/.empty size))) - (throws? /.cannot_copy - (/.copy! size offset sample 0 (/.empty size))) - (throws? /.cannot_copy - (/.copy! size 0 sample offset (/.empty size))))) + {try.#Failure _} + false) + (succeed + (do try.monad + [sample/0 (/.bits_8 0 sample) + copy (/.copy! 1 0 sample 0 (/.empty 2)) + copy/0 (/.bits_8 0 copy) + copy/1 (/.bits_8 1 copy)] + (in (and (n.= sample/0 copy/0) + (n.= 0 copy/1))))))) + (_.coverage [/.cannot_copy] + (and (not (throws? /.cannot_copy + (/.copy! size 0 sample 0 (/.empty size)))) + (throws? /.cannot_copy + (/.copy! (n.+ offset size) 0 sample 0 (/.empty size))) + (throws? /.cannot_copy + (/.copy! size offset sample 0 (/.empty size))) + (throws? /.cannot_copy + (/.copy! size 0 sample offset (/.empty size))))) ..test|unsafe )))) diff --git a/stdlib/source/test/lux/data/bit.lux b/stdlib/source/test/lux/data/bit.lux index fed07f172..25e1c5c8e 100644 --- a/stdlib/source/test/lux/data/bit.lux +++ b/stdlib/source/test/lux/data/bit.lux @@ -33,13 +33,13 @@ (_.for [/.codec] ($codec.spec /.equivalence /.codec random.bit)) - (_.cover [/.no /.yes] - (and (# /.equivalence = false /.no) - (# /.equivalence = true /.yes))) - (_.cover [/.off /.on] - (and (# /.equivalence = false /.off) - (# /.equivalence = true /.on))) - (_.cover [/.complement] - (and (not (# /.equivalence = value ((/.complement function.identity) value))) - (# /.equivalence = value ((/.complement not) value)))) + (_.coverage [/.no /.yes] + (and (# /.equivalence = false /.no) + (# /.equivalence = true /.yes))) + (_.coverage [/.off /.on] + (and (# /.equivalence = false /.off) + (# /.equivalence = true /.on))) + (_.coverage [/.complement] + (and (not (# /.equivalence = value ((/.complement function.identity) value))) + (# /.equivalence = value ((/.complement not) value)))) )))) diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index bbb829d98..278394bd3 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -68,50 +68,50 @@ (if (n.even? value) {.#Some (# n.decimal encoded value)} {.#None})))] - (_.cover [/.one] - (case [(|> evens - (/#each (# n.decimal encoded)) - (/.item 0)) - (/.one choose evens)] - [{.#Some expected} {.#Some actual}] - (text#= expected actual) + (_.coverage [/.one] + (case [(|> evens + (/#each (# n.decimal encoded)) + (/.item 0)) + (/.one choose evens)] + [{.#Some expected} {.#Some actual}] + (text#= expected actual) - [{.#None} {.#None}] - true + [{.#None} {.#None}] + true - _ - false))) - (_.cover [/.example] - (# (maybe.equivalence n.equivalence) = - (/.example n.even? the_array) - (list.example n.even? (/.list {.#None} the_array)))) - (_.cover [/.example'] - (case [(/.example n.even? the_array) - (/.example' (function (_ idx member) - (n.even? member)) - the_array)] - [{.#Some expected} {.#Some [idx actual]}] - (case (/.item idx the_array) - {.#Some again} - (and (n.= expected actual) - (n.= actual again)) - - {.#None} - false) + _ + false))) + (_.coverage [/.example] + (# (maybe.equivalence n.equivalence) = + (/.example n.even? the_array) + (list.example n.even? (/.list {.#None} the_array)))) + (_.coverage [/.example'] + (case [(/.example n.even? the_array) + (/.example' (function (_ idx member) + (n.even? member)) + the_array)] + [{.#Some expected} {.#Some [idx actual]}] + (case (/.item idx the_array) + {.#Some again} + (and (n.= expected actual) + (n.= actual again)) + + {.#None} + false) - [{.#None} {.#None}] - true + [{.#None} {.#None}] + true - _ - false)) - (_.cover [/.every?] - (# bit.equivalence = - (list.every? n.even? (/.list {.#None} the_array)) - (/.every? n.even? the_array))) - (_.cover [/.any?] - (# bit.equivalence = - (list.any? n.even? (/.list {.#None} the_array)) - (/.any? n.even? the_array))) + _ + false)) + (_.coverage [/.every?] + (# bit.equivalence = + (list.every? n.even? (/.list {.#None} the_array)) + (/.every? n.even? the_array))) + (_.coverage [/.any?] + (# bit.equivalence = + (list.any? n.even? (/.list {.#None} the_array)) + (/.any? n.even? the_array))) ))) (def: test|unsafe @@ -151,76 +151,76 @@ init it))))) - (_.cover [!.empty !.size] - (n.= size (!.size (is (Array Nat) - (!.empty size))))) - (_.cover [!.type] - (case !.Array - (pattern (<| {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) - (same? !.type nominal_type) + (_.coverage [!.empty !.size] + (n.= size (!.size (is (Array Nat) + (!.empty size))))) + (_.coverage [!.type] + (case !.Array + (pattern (<| {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) + (same? !.type nominal_type) - _ - false)) - (_.cover [!.lacks?] - (let [the_array (|> (!.empty 2) - (is (Array Nat)) - (!.has! 0 expected))] - (and (not (!.lacks? 0 the_array)) - (!.lacks? 1 the_array)))) - (_.cover [!.item !.has!] - (|> (!.empty 2) - (is (Array Nat)) - (!.has! 0 expected) - (!.item 0) - (n.= expected))) - (_.cover [!.lacks!] - (|> (!.empty 1) - (is (Array Nat)) - (!.has! 0 expected) - (!.lacks! 0) - (!.lacks? 0))) - (_.cover [!.lacks?] - (let [the_array (|> (!.empty 2) - (is (Array Nat)) - (!.has! 0 expected))] - (and (not (!.lacks? 0 the_array)) - (!.lacks? 1 the_array)))) - (_.cover [!.has?] - (let [the_array (|> (!.empty 2) - (is (Array Nat)) - (!.has! 0 expected))] - (and (!.has? 0 the_array) - (not (!.has? 1 the_array))))) - (_.cover [!.revised!] - (|> (!.empty 1) - (is (Array Nat)) - (!.has! 0 base) - (!.revised! 0 (n.+ shift)) - (!.item 0) - (n.= expected))) - (_.cover [!.upsert!] - (let [the_array (|> (!.empty 2) - (is (Array Nat)) - (!.has! 0 base) - (!.upsert! 0 dummy (n.+ shift)) - (!.upsert! 1 base (n.+ shift)))] - (and (n.= expected (!.item 0 the_array)) - (n.= expected (!.item 1 the_array))))) + _ + false)) + (_.coverage [!.lacks?] + (let [the_array (|> (!.empty 2) + (is (Array Nat)) + (!.has! 0 expected))] + (and (not (!.lacks? 0 the_array)) + (!.lacks? 1 the_array)))) + (_.coverage [!.item !.has!] + (|> (!.empty 2) + (is (Array Nat)) + (!.has! 0 expected) + (!.item 0) + (n.= expected))) + (_.coverage [!.lacks!] + (|> (!.empty 1) + (is (Array Nat)) + (!.has! 0 expected) + (!.lacks! 0) + (!.lacks? 0))) + (_.coverage [!.lacks?] + (let [the_array (|> (!.empty 2) + (is (Array Nat)) + (!.has! 0 expected))] + (and (not (!.lacks? 0 the_array)) + (!.lacks? 1 the_array)))) + (_.coverage [!.has?] + (let [the_array (|> (!.empty 2) + (is (Array Nat)) + (!.has! 0 expected))] + (and (!.has? 0 the_array) + (not (!.has? 1 the_array))))) + (_.coverage [!.revised!] + (|> (!.empty 1) + (is (Array Nat)) + (!.has! 0 base) + (!.revised! 0 (n.+ shift)) + (!.item 0) + (n.= expected))) + (_.coverage [!.upsert!] + (let [the_array (|> (!.empty 2) + (is (Array Nat)) + (!.has! 0 base) + (!.upsert! 0 dummy (n.+ shift)) + (!.upsert! 1 base (n.+ shift)))] + (and (n.= expected (!.item 0 the_array)) + (n.= expected (!.item 1 the_array))))) (do ! [occupancy (# ! each (n.% (++ size)) random.nat)] - (_.cover [!.occupancy !.vacancy] - (let [the_array (loop (again [output (is (Array Nat) - (!.empty size)) - idx 0]) - (if (n.< occupancy idx) - (again (!.has! idx expected output) - (++ idx)) - output))] - (and (n.= occupancy (!.occupancy the_array)) - (n.= size (n.+ (!.occupancy the_array) - (!.vacancy the_array))))))) + (_.coverage [!.occupancy !.vacancy] + (let [the_array (loop (again [output (is (Array Nat) + (!.empty size)) + idx 0]) + (if (n.< occupancy idx) + (again (!.has! idx expected output) + (++ idx)) + output))] + (and (n.= occupancy (!.occupancy the_array)) + (n.= size (n.+ (!.occupancy the_array) + (!.vacancy the_array))))))) (do ! [the_list (random.list size random.nat) .let [the_array (!.clone the_array) @@ -229,79 +229,79 @@ (not (or (n.even? value) (set.member? members value)))) random.nat)] - (_.cover [!.of_list !.list] - (and (|> the_list !.of_list (!.list {.#None}) - (# (list.equivalence n.equivalence) = the_list)) - (|> the_array (!.list {.#None}) !.of_list - (!.= n.equivalence the_array)) - (exec - (!.only! n.even? the_array) - (list.every? (function (_ value) - (or (n.even? value) - (same? default value))) - (!.list {.#Some default} the_array)))))) + (_.coverage [!.of_list !.list] + (and (|> the_list !.of_list (!.list {.#None}) + (# (list.equivalence n.equivalence) = the_list)) + (|> the_array (!.list {.#None}) !.of_list + (!.= n.equivalence the_array)) + (exec + (!.only! n.even? the_array) + (list.every? (function (_ value) + (or (n.even? value) + (same? default value))) + (!.list {.#Some default} the_array)))))) (do ! [amount (# ! each (n.% (++ size)) random.nat)] - (_.cover [!.copy!] - (let [copy (is (Array Nat) - (!.empty size))] - (exec (!.copy! amount 0 the_array 0 copy) - (# (list.equivalence n.equivalence) = - (list.first amount (!.list {.#None} the_array)) - (!.list {.#None} copy)))))) - (_.cover [!.clone] - (let [clone (!.clone the_array)] - (and (not (same? the_array clone)) - (!.= n.equivalence the_array clone)))) + (_.coverage [!.copy!] + (let [copy (is (Array Nat) + (!.empty size))] + (exec (!.copy! amount 0 the_array 0 copy) + (# (list.equivalence n.equivalence) = + (list.first amount (!.list {.#None} the_array)) + (!.list {.#None} copy)))))) + (_.coverage [!.clone] + (let [clone (!.clone the_array)] + (and (not (same? the_array clone)) + (!.= n.equivalence the_array clone)))) (let [the_array (!.clone the_array) evens (|> the_array (!.list {.#None}) (list.only n.even?)) odds (|> the_array (!.list {.#None}) (list.only n.odd?))] - (_.cover [!.only!] - (exec (!.only! n.even? the_array) - (and (n.= (list.size evens) (!.occupancy the_array)) - (n.= (list.size odds) (!.vacancy the_array)) - (|> the_array - (!.list {.#None}) - (# (list.equivalence n.equivalence) = evens)))))) + (_.coverage [!.only!] + (exec (!.only! n.even? the_array) + (and (n.= (list.size evens) (!.occupancy the_array)) + (n.= (list.size odds) (!.vacancy the_array)) + (|> the_array + (!.list {.#None}) + (# (list.equivalence n.equivalence) = evens)))))) (let [choose (is (-> Nat (Maybe Text)) (function (_ value) (if (n.even? value) {.#Some (# n.decimal encoded value)} {.#None})))] - (_.cover [!.one] - (|> evens - (!.one choose) - (maybe#each (text#= (|> evens - (!.each (# n.decimal encoded)) - (!.item 0)))) - (maybe.else false)))) - (_.cover [!.example] - (# (maybe.equivalence n.equivalence) = - (!.example n.even? the_array) - (list.example n.even? (!.list {.#None} the_array)))) - (_.cover [!.example'] - (case [(!.example n.even? the_array) - (!.example' (function (_ idx member) - (n.even? member)) - the_array)] - [{.#Some expected} {.#Some [idx actual]}] - (and (not (!.lacks? idx the_array)) - (n.= expected actual) - (n.= actual (!.item idx the_array))) + (_.coverage [!.one] + (|> evens + (!.one choose) + (maybe#each (text#= (|> evens + (!.each (# n.decimal encoded)) + (!.item 0)))) + (maybe.else false)))) + (_.coverage [!.example] + (# (maybe.equivalence n.equivalence) = + (!.example n.even? the_array) + (list.example n.even? (!.list {.#None} the_array)))) + (_.coverage [!.example'] + (case [(!.example n.even? the_array) + (!.example' (function (_ idx member) + (n.even? member)) + the_array)] + [{.#Some expected} {.#Some [idx actual]}] + (and (not (!.lacks? idx the_array)) + (n.= expected actual) + (n.= actual (!.item idx the_array))) - [{.#None} {.#None}] - true + [{.#None} {.#None}] + true - _ - false)) - (_.cover [!.every?] - (# bit.equivalence = - (list.every? n.even? (!.list {.#None} the_array)) - (!.every? n.even? the_array))) - (_.cover [!.any?] - (# bit.equivalence = - (list.any? n.even? (!.list {.#None} the_array)) - (!.any? n.even? the_array))) + _ + false)) + (_.coverage [!.every?] + (# bit.equivalence = + (list.every? n.even? (!.list {.#None} the_array)) + (!.every? n.even? the_array))) + (_.coverage [!.any?] + (# bit.equivalence = + (list.any? n.even? (!.list {.#None} the_array)) + (!.any? n.even? the_array))) ))))) (def: .public test @@ -319,91 +319,91 @@ ..structures ..search - (_.cover [/.empty /.size] - (n.= size (/.size (is (Array Nat) - (/.empty size))))) - (_.cover [/.type_name] - (case /.Array - (pattern (<| {.#Named (symbol /.Array)} - {.#Named (symbol !.Array)} - {.#UnivQ (list)} - {.#Primitive nominal_type (list {.#Parameter 1})})) - (same? /.type_name nominal_type) + (_.coverage [/.empty /.size] + (n.= size (/.size (is (Array Nat) + (/.empty size))))) + (_.coverage [/.type_name] + (case /.Array + (pattern (<| {.#Named (symbol /.Array)} + {.#Named (symbol !.Array)} + {.#UnivQ (list)} + {.#Primitive nominal_type (list {.#Parameter 1})})) + (same? /.type_name nominal_type) - _ - false)) - (_.cover [/.item /.has!] - (let [the_array (|> (/.empty 2) - (is (Array Nat)) - (/.has! 0 expected))] - (case [(/.item 0 the_array) - (/.item 1 the_array)] - [{.#Some actual} {.#None}] - (n.= expected actual) + _ + false)) + (_.coverage [/.item /.has!] + (let [the_array (|> (/.empty 2) + (is (Array Nat)) + (/.has! 0 expected))] + (case [(/.item 0 the_array) + (/.item 1 the_array)] + [{.#Some actual} {.#None}] + (n.= expected actual) - _ - false))) - (_.cover [/.lacks!] - (let [the_array (|> (/.empty 1) - (is (Array Nat)) - (/.has! 0 expected))] - (case [(/.item 0 the_array) - (/.item 0 (/.lacks! 0 the_array))] - [{.#Some actual} {.#None}] - (n.= expected actual) + _ + false))) + (_.coverage [/.lacks!] + (let [the_array (|> (/.empty 1) + (is (Array Nat)) + (/.has! 0 expected))] + (case [(/.item 0 the_array) + (/.item 0 (/.lacks! 0 the_array))] + [{.#Some actual} {.#None}] + (n.= expected actual) - _ - false))) - (_.cover [/.lacks?] - (let [the_array (|> (/.empty 2) - (is (Array Nat)) - (/.has! 0 expected))] - (and (not (/.lacks? 0 the_array)) - (/.lacks? 1 the_array)))) - (_.cover [/.has?] - (let [the_array (|> (/.empty 2) - (is (Array Nat)) - (/.has! 0 expected))] - (and (/.has? 0 the_array) - (not (/.has? 1 the_array))))) - (_.cover [/.revised!] - (let [the_array (|> (/.empty 1) - (is (Array Nat)) - (/.has! 0 base) - (/.revised! 0 (n.+ shift)))] - (case (/.item 0 the_array) - {.#Some actual} - (n.= expected actual) + _ + false))) + (_.coverage [/.lacks?] + (let [the_array (|> (/.empty 2) + (is (Array Nat)) + (/.has! 0 expected))] + (and (not (/.lacks? 0 the_array)) + (/.lacks? 1 the_array)))) + (_.coverage [/.has?] + (let [the_array (|> (/.empty 2) + (is (Array Nat)) + (/.has! 0 expected))] + (and (/.has? 0 the_array) + (not (/.has? 1 the_array))))) + (_.coverage [/.revised!] + (let [the_array (|> (/.empty 1) + (is (Array Nat)) + (/.has! 0 base) + (/.revised! 0 (n.+ shift)))] + (case (/.item 0 the_array) + {.#Some actual} + (n.= expected actual) - _ - false))) - (_.cover [/.upsert!] - (let [the_array (|> (/.empty 2) - (is (Array Nat)) - (/.has! 0 base) - (/.upsert! 0 dummy (n.+ shift)) - (/.upsert! 1 base (n.+ shift)))] - (case [(/.item 0 the_array) - (/.item 1 the_array)] - [{.#Some actual/0} {.#Some actual/1}] - (and (n.= expected actual/0) - (n.= expected actual/1)) + _ + false))) + (_.coverage [/.upsert!] + (let [the_array (|> (/.empty 2) + (is (Array Nat)) + (/.has! 0 base) + (/.upsert! 0 dummy (n.+ shift)) + (/.upsert! 1 base (n.+ shift)))] + (case [(/.item 0 the_array) + (/.item 1 the_array)] + [{.#Some actual/0} {.#Some actual/1}] + (and (n.= expected actual/0) + (n.= expected actual/1)) - _ - false))) + _ + false))) (do ! [occupancy (# ! each (n.% (++ size)) random.nat)] - (_.cover [/.occupancy /.vacancy] - (let [the_array (loop (again [output (is (Array Nat) - (/.empty size)) - idx 0]) - (if (n.< occupancy idx) - (again (/.has! idx expected output) - (++ idx)) - output))] - (and (n.= occupancy (/.occupancy the_array)) - (n.= size (n.+ (/.occupancy the_array) - (/.vacancy the_array))))))) + (_.coverage [/.occupancy /.vacancy] + (let [the_array (loop (again [output (is (Array Nat) + (/.empty size)) + idx 0]) + (if (n.< occupancy idx) + (again (/.has! idx expected output) + (++ idx)) + output))] + (and (n.= occupancy (/.occupancy the_array)) + (n.= size (n.+ (/.occupancy the_array) + (/.vacancy the_array))))))) (do ! [the_list (random.list size random.nat) .let [the_array (/.clone the_array) @@ -412,38 +412,38 @@ (not (or (n.even? value) (set.member? members value)))) random.nat)] - (_.cover [/.of_list /.list] - (and (|> the_list /.of_list (/.list {.#None}) - (# (list.equivalence n.equivalence) = the_list)) - (|> the_array (/.list {.#None}) /.of_list - (# (/.equivalence n.equivalence) = the_array)) - (exec - (/.only! n.even? the_array) - (list.every? (function (_ value) - (or (n.even? value) - (same? default value))) - (/.list {.#Some default} the_array)))))) + (_.coverage [/.of_list /.list] + (and (|> the_list /.of_list (/.list {.#None}) + (# (list.equivalence n.equivalence) = the_list)) + (|> the_array (/.list {.#None}) /.of_list + (# (/.equivalence n.equivalence) = the_array)) + (exec + (/.only! n.even? the_array) + (list.every? (function (_ value) + (or (n.even? value) + (same? default value))) + (/.list {.#Some default} the_array)))))) (do ! [amount (# ! each (n.% (++ size)) random.nat)] - (_.cover [/.copy!] - (let [copy (is (Array Nat) - (/.empty size))] - (exec (/.copy! amount 0 the_array 0 copy) - (# (list.equivalence n.equivalence) = - (list.first amount (/.list {.#None} the_array)) - (/.list {.#None} copy)))))) - (_.cover [/.clone] - (let [clone (/.clone the_array)] - (and (not (same? the_array clone)) - (# (/.equivalence n.equivalence) = the_array clone)))) + (_.coverage [/.copy!] + (let [copy (is (Array Nat) + (/.empty size))] + (exec (/.copy! amount 0 the_array 0 copy) + (# (list.equivalence n.equivalence) = + (list.first amount (/.list {.#None} the_array)) + (/.list {.#None} copy)))))) + (_.coverage [/.clone] + (let [clone (/.clone the_array)] + (and (not (same? the_array clone)) + (# (/.equivalence n.equivalence) = the_array clone)))) (let [the_array (/.clone the_array) evens (|> the_array (/.list {.#None}) (list.only n.even?)) odds (|> the_array (/.list {.#None}) (list.only n.odd?))] - (_.cover [/.only!] - (exec (/.only! n.even? the_array) - (and (n.= (list.size evens) (/.occupancy the_array)) - (n.= (list.size odds) (/.vacancy the_array)) - (|> the_array (/.list {.#None}) (# (list.equivalence n.equivalence) = evens)))))) + (_.coverage [/.only!] + (exec (/.only! n.even? the_array) + (and (n.= (list.size evens) (/.occupancy the_array)) + (n.= (list.size odds) (/.vacancy the_array)) + (|> the_array (/.list {.#None}) (# (list.equivalence n.equivalence) = evens)))))) ..test|unsafe )))) diff --git a/stdlib/source/test/lux/data/collection/bits.lux b/stdlib/source/test/lux/data/collection/bits.lux index 8547bcf42..717ed5337 100644 --- a/stdlib/source/test/lux/data/collection/bits.lux +++ b/stdlib/source/test/lux/data/collection/bits.lux @@ -39,57 +39,57 @@ (do random.monad [sample ..random] - (_.cover [/.empty? /.size] - (if (/.empty? sample) - (n.= 0 (/.size sample)) - (n.> 0 (/.size sample))))) - (_.cover [/.empty] - (/.empty? /.empty)) + (_.coverage [/.empty? /.size] + (if (/.empty? sample) + (n.= 0 (/.size sample)) + (n.> 0 (/.size sample))))) + (_.coverage [/.empty] + (/.empty? /.empty)) (do [! random.monad] [size (# ! each (|>> (n.% 1,000) ++) random.nat) idx (# ! each (n.% size) random.nat) sample ..random] (all _.and - (_.cover [/.bit /.one] - (and (|> /.empty (/.bit idx) not) - (|> /.empty (/.one idx) (/.bit idx)))) - (_.cover [/.zero] - (|> /.empty (/.one idx) (/.zero idx) (/.bit idx) not)) - (_.cover [/.flipped] - (and (|> /.empty (/.flipped idx) (/.bit idx)) - (|> /.empty (/.flipped idx) (/.flipped idx) (/.bit idx) not))) - (_.cover [/.Chunk /.capacity /.chunk_size] - (and (n.= 0 (/.capacity /.empty)) - (|> /.empty (/.one idx) /.capacity - (n.- idx) - (predicate.or (n.>= 0) - (n.< /.chunk_size))) - (let [grown (/.flipped idx /.empty)] - (and (n.> 0 (/.capacity grown)) - (same? /.empty (/.flipped idx grown)))))) - (_.cover [/.intersects?] - (and (not (/.intersects? /.empty - /.empty)) - (/.intersects? (/.one idx /.empty) - (/.one idx /.empty)) - (not (/.intersects? (/.one (++ idx) /.empty) - (/.one idx /.empty))) - (not (/.intersects? sample (/.not sample))))) - (_.cover [/.not] - (and (same? /.empty (/.not /.empty)) - (or (same? /.empty sample) - (and (not (# /.equivalence = sample (/.not sample))) - (# /.equivalence = sample (/.not (/.not sample))))))) - (_.cover [/.xor] - (and (same? /.empty (/.xor sample sample)) - (n.= (/.size (/.xor sample (/.not sample))) - (/.capacity sample)))) - (_.cover [/.or] - (and (# /.equivalence = sample (/.or sample sample)) - (n.= (/.size (/.or sample (/.not sample))) - (/.capacity sample)))) - (_.cover [/.and] - (and (# /.equivalence = sample (/.and sample sample)) - (same? /.empty (/.and sample (/.not sample))))) + (_.coverage [/.bit /.one] + (and (|> /.empty (/.bit idx) not) + (|> /.empty (/.one idx) (/.bit idx)))) + (_.coverage [/.zero] + (|> /.empty (/.one idx) (/.zero idx) (/.bit idx) not)) + (_.coverage [/.flipped] + (and (|> /.empty (/.flipped idx) (/.bit idx)) + (|> /.empty (/.flipped idx) (/.flipped idx) (/.bit idx) not))) + (_.coverage [/.Chunk /.capacity /.chunk_size] + (and (n.= 0 (/.capacity /.empty)) + (|> /.empty (/.one idx) /.capacity + (n.- idx) + (predicate.or (n.>= 0) + (n.< /.chunk_size))) + (let [grown (/.flipped idx /.empty)] + (and (n.> 0 (/.capacity grown)) + (same? /.empty (/.flipped idx grown)))))) + (_.coverage [/.intersects?] + (and (not (/.intersects? /.empty + /.empty)) + (/.intersects? (/.one idx /.empty) + (/.one idx /.empty)) + (not (/.intersects? (/.one (++ idx) /.empty) + (/.one idx /.empty))) + (not (/.intersects? sample (/.not sample))))) + (_.coverage [/.not] + (and (same? /.empty (/.not /.empty)) + (or (same? /.empty sample) + (and (not (# /.equivalence = sample (/.not sample))) + (# /.equivalence = sample (/.not (/.not sample))))))) + (_.coverage [/.xor] + (and (same? /.empty (/.xor sample sample)) + (n.= (/.size (/.xor sample (/.not sample))) + (/.capacity sample)))) + (_.coverage [/.or] + (and (# /.equivalence = sample (/.or sample sample)) + (n.= (/.size (/.or sample (/.not sample))) + (/.capacity sample)))) + (_.coverage [/.and] + (and (# /.equivalence = sample (/.and sample sample)) + (same? /.empty (/.and sample (/.not sample))))) ))))) diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 9c1121143..b48338682 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -39,18 +39,18 @@ test_val (random.only (|>> (list.member? n.equivalence (/.values dict)) not) random.nat)] (all _.and - (_.cover [/.size] - (n.= size (/.size dict))) + (_.coverage [/.size] + (n.= size (/.size dict))) - (_.cover [/.empty?] - (case size - 0 (/.empty? dict) - _ (not (/.empty? dict)))) + (_.coverage [/.empty?] + (case size + 0 (/.empty? dict) + _ (not (/.empty? dict)))) - (_.cover [/.empty] - (let [sample (/.empty n.hash)] - (and (n.= 0 (/.size sample)) - (/.empty? sample)))) + (_.coverage [/.empty] + (let [sample (/.empty n.hash)] + (and (n.= 0 (/.size sample)) + (/.empty? sample)))) (do ! [constant random.nat @@ -59,75 +59,75 @@ (def: equivalence n.equivalence) (def: (hash _) constant)))]] - (_.cover [/.key_hash] - (same? hash (/.key_hash (/.empty hash))))) + (_.coverage [/.key_hash] + (same? hash (/.key_hash (/.empty hash))))) - (_.cover [/.entries] - (let [entries (/.entries dict) + (_.coverage [/.entries] + (let [entries (/.entries dict) - correct_size! - (n.= (/.size dict) - (list.size entries)) + correct_size! + (n.= (/.size dict) + (list.size entries)) - unique_keys! - (|> entries - (list#each product.left) - (set.of_list n.hash) - set.size - (n.= (/.size dict))) + unique_keys! + (|> entries + (list#each product.left) + (set.of_list n.hash) + set.size + (n.= (/.size dict))) - correct_pairing! - (list.every? (function (_ [key value]) - (|> dict - (/.value key) - (maybe#each (n.= value)) - (maybe.else false))) - entries)] - (and correct_size! - unique_keys! - correct_pairing!))) - (_.cover [/.keys] - (let [keys (/.keys dict) + correct_pairing! + (list.every? (function (_ [key value]) + (|> dict + (/.value key) + (maybe#each (n.= value)) + (maybe.else false))) + entries)] + (and correct_size! + unique_keys! + correct_pairing!))) + (_.coverage [/.keys] + (let [keys (/.keys dict) - correct_size! - (n.= (/.size dict) - (list.size keys)) + correct_size! + (n.= (/.size dict) + (list.size keys)) - unique_keys! - (|> keys - (set.of_list n.hash) - set.size - (n.= (/.size dict))) + unique_keys! + (|> keys + (set.of_list n.hash) + set.size + (n.= (/.size dict))) - recognized! - (list.every? (/.key? dict) keys)] - (and correct_size! - unique_keys! - recognized!))) - (_.cover [/.values] - (n.= (/.size dict) - (list.size (/.values dict)))) + recognized! + (list.every? (/.key? dict) keys)] + (and correct_size! + unique_keys! + recognized!))) + (_.coverage [/.values] + (n.= (/.size dict) + (list.size (/.values dict)))) - (_.cover [/.composite] - (let [merging_with_oneself (let [(open "[0]") (/.equivalence n.equivalence)] - (= dict (/.composite dict dict))) - overwritting_keys (let [dict' (|> dict /.entries - (list#each (function (_ [k v]) [k (++ v)])) - (/.of_list n.hash)) - (open "[0]") (/.equivalence n.equivalence)] - (= dict' (/.composite dict' dict)))] - (and merging_with_oneself - overwritting_keys))) + (_.coverage [/.composite] + (let [merging_with_oneself (let [(open "[0]") (/.equivalence n.equivalence)] + (= dict (/.composite dict dict))) + overwritting_keys (let [dict' (|> dict /.entries + (list#each (function (_ [k v]) [k (++ v)])) + (/.of_list n.hash)) + (open "[0]") (/.equivalence n.equivalence)] + (= dict' (/.composite dict' dict)))] + (and merging_with_oneself + overwritting_keys))) - (_.cover [/.composite_with] - (list.every? (function (_ [x x*2]) (n.= (n.* 2 x) x*2)) - (list.zipped_2 (/.values dict) - (/.values (/.composite_with n.+ dict dict))))) + (_.coverage [/.composite_with] + (list.every? (function (_ [x x*2]) (n.= (n.* 2 x) x*2)) + (list.zipped_2 (/.values dict) + (/.values (/.composite_with n.+ dict dict))))) - (_.cover [/.of_list] - (let [(open "[0]") (/.equivalence n.equivalence)] - (and (= dict dict) - (|> dict /.entries (/.of_list n.hash) (= dict))))) + (_.coverage [/.of_list] + (let [(open "[0]") (/.equivalence n.equivalence)] + (and (= dict dict) + (|> dict /.entries (/.of_list n.hash) (= dict))))) ))) (def: for_entries @@ -141,111 +141,111 @@ test_val (random.only (|>> (list.member? n.equivalence (/.values dict)) not) random.nat)] (all _.and - (_.cover [/.key?] - (list.every? (/.key? dict) - (/.keys dict))) + (_.coverage [/.key?] + (list.every? (/.key? dict) + (/.keys dict))) - (_.cover [/.value] - (and (list.every? (function (_ key) (case (/.value key dict) - {.#Some _} true - _ false)) - (/.keys dict)) - (case (/.value non_key dict) - {.#Some _} false - _ true))) + (_.coverage [/.value] + (and (list.every? (function (_ key) (case (/.value key dict) + {.#Some _} true + _ false)) + (/.keys dict)) + (case (/.value non_key dict) + {.#Some _} false + _ true))) - (_.cover [/.has] - (and (n.= (++ (/.size dict)) - (/.size (/.has non_key test_val dict))) - (case (/.value non_key (/.has non_key test_val dict)) - {.#Some v} (n.= test_val v) - _ true))) + (_.coverage [/.has] + (and (n.= (++ (/.size dict)) + (/.size (/.has non_key test_val dict))) + (case (/.value non_key (/.has non_key test_val dict)) + {.#Some v} (n.= test_val v) + _ true))) - (_.cover [/.has' /.key_already_exists] - (let [can_put_new_keys! - (case (/.has' non_key test_val dict) - {try.#Success dict} - (case (/.value non_key dict) - {.#Some v} (n.= test_val v) - _ true) + (_.coverage [/.has' /.key_already_exists] + (let [can_put_new_keys! + (case (/.has' non_key test_val dict) + {try.#Success dict} + (case (/.value non_key dict) + {.#Some v} (n.= test_val v) + _ true) - {try.#Failure _} - false) - - cannot_put_old_keys! - (or (n.= 0 size) - (let [first_key (|> dict /.keys list.head maybe.trusted)] - (case (/.has' first_key test_val dict) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.key_already_exists error))))] - (and can_put_new_keys! - cannot_put_old_keys!))) - - (_.cover [/.lacks] - (and (let [base (/.has non_key test_val dict)] - (and (/.key? base non_key) - (not (/.key? (/.lacks non_key base) non_key)))) - (case (list.head (/.keys dict)) - {.#None} - true + {try.#Failure _} + false) + + cannot_put_old_keys! + (or (n.= 0 size) + (let [first_key (|> dict /.keys list.head maybe.trusted)] + (case (/.has' first_key test_val dict) + {try.#Success _} + false - {.#Some known_key} - (n.= (-- (/.size dict)) - (/.size (/.lacks known_key dict)))))) + {try.#Failure error} + (exception.match? /.key_already_exists error))))] + (and can_put_new_keys! + cannot_put_old_keys!))) + + (_.coverage [/.lacks] + (and (let [base (/.has non_key test_val dict)] + (and (/.key? base non_key) + (not (/.key? (/.lacks non_key base) non_key)))) + (case (list.head (/.keys dict)) + {.#None} + true + + {.#Some known_key} + (n.= (-- (/.size dict)) + (/.size (/.lacks known_key dict)))))) - (_.cover [/.revised] - (let [base (/.has non_key test_val dict) - updt (/.revised non_key ++ base)] - (case [(/.value non_key base) (/.value non_key updt)] - [{.#Some x} {.#Some y}] - (n.= (++ x) y) + (_.coverage [/.revised] + (let [base (/.has non_key test_val dict) + updt (/.revised non_key ++ base)] + (case [(/.value non_key base) (/.value non_key updt)] + [{.#Some x} {.#Some y}] + (n.= (++ x) y) - _ - false))) + _ + false))) - (_.cover [/.revised'] - (let [can_upsert_new_key! - (case (/.value non_key (/.revised' non_key test_val ++ dict)) - {.#Some inserted} - (n.= (++ test_val) inserted) + (_.coverage [/.revised'] + (let [can_upsert_new_key! + (case (/.value non_key (/.revised' non_key test_val ++ dict)) + {.#Some inserted} + (n.= (++ test_val) inserted) - {.#None} - false) + {.#None} + false) - can_upsert_old_key! - (case (list.head (/.entries dict)) - {.#None} - true - - {.#Some [known_key known_value]} - (case (/.value known_key (/.revised' known_key test_val ++ dict)) - {.#Some updated} - (n.= (++ known_value) updated) + can_upsert_old_key! + (case (list.head (/.entries dict)) + {.#None} + true + + {.#Some [known_key known_value]} + (case (/.value known_key (/.revised' known_key test_val ++ dict)) + {.#Some updated} + (n.= (++ known_value) updated) - {.#None} - false))] - (and can_upsert_new_key! - can_upsert_old_key!))) + {.#None} + false))] + (and can_upsert_new_key! + can_upsert_old_key!))) - (_.cover [/.sub] - (|> dict - (/.has non_key test_val) - (/.sub (list non_key)) - /.size - (n.= 1))) + (_.coverage [/.sub] + (|> dict + (/.has non_key test_val) + (/.sub (list non_key)) + /.size + (n.= 1))) - (_.cover [/.re_bound] - (or (n.= 0 size) - (let [first_key (|> dict /.keys list.head maybe.trusted) - rebound (/.re_bound first_key non_key dict)] - (and (n.= (/.size dict) (/.size rebound)) - (/.key? rebound non_key) - (not (/.key? rebound first_key)) - (n.= (maybe.trusted (/.value first_key dict)) - (maybe.trusted (/.value non_key rebound))))))) + (_.coverage [/.re_bound] + (or (n.= 0 size) + (let [first_key (|> dict /.keys list.head maybe.trusted) + rebound (/.re_bound first_key non_key dict)] + (and (n.= (/.size dict) (/.size rebound)) + (/.key? rebound non_key) + (not (/.key? rebound first_key)) + (n.= (maybe.trusted (/.value first_key dict)) + (maybe.trusted (/.value non_key rebound))))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 6dd9ce772..6e3acefa2 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -66,72 +66,72 @@ (_.for [/.equivalence] ($equivalence.spec (/.equivalence n.equivalence) (..dictionary n.order random.nat random.nat size))) - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (n.= 0 (/.size sample)) - (/.empty? sample))) - (_.cover [/.empty] - (/.empty? (/.empty n.order))) - (_.cover [/.min] - (case [(/.min sample) (list.head sorted_values)] - [{.#None} {.#None}] - #1 + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (n.= 0 (/.size sample)) + (/.empty? sample))) + (_.coverage [/.empty] + (/.empty? (/.empty n.order))) + (_.coverage [/.min] + (case [(/.min sample) (list.head sorted_values)] + [{.#None} {.#None}] + #1 - [{.#Some reference} {.#Some sample}] - (n.= reference sample) + [{.#Some reference} {.#Some sample}] + (n.= reference sample) - _ - #0)) - (_.cover [/.max] - (case [(/.max sample) (list.last sorted_values)] - [{.#None} {.#None}] - #1 + _ + #0)) + (_.coverage [/.max] + (case [(/.max sample) (list.last sorted_values)] + [{.#None} {.#None}] + #1 - [{.#Some reference} {.#Some sample}] - (n.= reference sample) + [{.#Some reference} {.#Some sample}] + (n.= reference sample) - _ - #0)) - (_.cover [/.entries] - (list#= (/.entries sample) - sorted_pairs)) - (_.cover [/.keys /.values] - (list#= (/.entries sample) - (list.zipped_2 (/.keys sample) (/.values sample)))) - (_.cover [/.of_list] - (|> sample - /.entries (/.of_list n.order) - (/#= sample))) - (_.cover [/.key?] - (and (list.every? (/.key? sample) - (/.keys sample)) - (not (/.key? sample extra_key)))) - (_.cover [/.has] - (and (not (/.key? sample extra_key)) - (let [sample+ (/.has extra_key extra_value sample)] - (and (/.key? sample+ extra_key) - (n.= (++ (/.size sample)) - (/.size sample+)))))) - (_.cover [/.value] - (let [sample+ (/.has extra_key extra_value sample)] - (case [(/.value extra_key sample) - (/.value extra_key sample+)] - [{.#None} {.#Some actual}] - (n.= extra_value actual) - - _ - false))) - (_.cover [/.lacks] - (|> sample - (/.has extra_key extra_value) - (/.lacks extra_key) - (/#= sample))) - (_.cover [/.revised] - (|> sample - (/.has extra_key extra_value) - (/.revised extra_key (n.+ shift)) - (/.value extra_key) - (maybe#each (n.= (n.+ shift extra_value))) - (maybe.else false))) + _ + #0)) + (_.coverage [/.entries] + (list#= (/.entries sample) + sorted_pairs)) + (_.coverage [/.keys /.values] + (list#= (/.entries sample) + (list.zipped_2 (/.keys sample) (/.values sample)))) + (_.coverage [/.of_list] + (|> sample + /.entries (/.of_list n.order) + (/#= sample))) + (_.coverage [/.key?] + (and (list.every? (/.key? sample) + (/.keys sample)) + (not (/.key? sample extra_key)))) + (_.coverage [/.has] + (and (not (/.key? sample extra_key)) + (let [sample+ (/.has extra_key extra_value sample)] + (and (/.key? sample+ extra_key) + (n.= (++ (/.size sample)) + (/.size sample+)))))) + (_.coverage [/.value] + (let [sample+ (/.has extra_key extra_value sample)] + (case [(/.value extra_key sample) + (/.value extra_key sample+)] + [{.#None} {.#Some actual}] + (n.= extra_value actual) + + _ + false))) + (_.coverage [/.lacks] + (|> sample + (/.has extra_key extra_value) + (/.lacks extra_key) + (/#= sample))) + (_.coverage [/.revised] + (|> sample + (/.has extra_key extra_value) + (/.revised extra_key (n.+ shift)) + (/.value extra_key) + (maybe#each (n.= (n.+ shift extra_value))) + (maybe.else false))) )))) diff --git a/stdlib/source/test/lux/data/collection/dictionary/plist.lux b/stdlib/source/test/lux/data/collection/dictionary/plist.lux index 113b166f3..ecac86868 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/plist.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/plist.lux @@ -53,45 +53,45 @@ /.monoid (..random 10 (random.lower_case 1) random.nat))) - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (n.= 0 (/.size sample)) - (/.empty? sample))) - (_.cover [/.empty] - (/.empty? /.empty)) - (_.cover [/.keys /.values] - (# (/.equivalence n.equivalence) = - sample - (list.zipped_2 (/.keys sample) - (/.values sample)))) - (_.cover [/.contains?] - (and (list.every? (function (_ key) - (/.contains? key sample)) - (/.keys sample)) - (not (/.contains? extra_key sample)))) - (_.cover [/.has] - (let [sample+ (/.has extra_key extra_value sample)] - (and (not (/.contains? extra_key sample)) - (/.contains? extra_key sample+) - (n.= (++ (/.size sample)) - (/.size sample+))))) - (_.cover [/.value] - (|> sample - (/.has extra_key extra_value) - (/.value extra_key) - (maybe#each (n.= extra_value)) - (maybe.else false))) - (_.cover [/.revised] - (|> sample - (/.has extra_key extra_value) - (/.revised extra_key (n.+ shift)) - (/.value extra_key) - (maybe#each (n.= (n.+ shift extra_value))) - (maybe.else false))) - (_.cover [/.lacks] - (|> sample - (/.has extra_key extra_value) - (/.lacks extra_key) - (# (/.equivalence n.equivalence) = sample))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (n.= 0 (/.size sample)) + (/.empty? sample))) + (_.coverage [/.empty] + (/.empty? /.empty)) + (_.coverage [/.keys /.values] + (# (/.equivalence n.equivalence) = + sample + (list.zipped_2 (/.keys sample) + (/.values sample)))) + (_.coverage [/.contains?] + (and (list.every? (function (_ key) + (/.contains? key sample)) + (/.keys sample)) + (not (/.contains? extra_key sample)))) + (_.coverage [/.has] + (let [sample+ (/.has extra_key extra_value sample)] + (and (not (/.contains? extra_key sample)) + (/.contains? extra_key sample+) + (n.= (++ (/.size sample)) + (/.size sample+))))) + (_.coverage [/.value] + (|> sample + (/.has extra_key extra_value) + (/.value extra_key) + (maybe#each (n.= extra_value)) + (maybe.else false))) + (_.coverage [/.revised] + (|> sample + (/.has extra_key extra_value) + (/.revised extra_key (n.+ shift)) + (/.value extra_key) + (maybe#each (n.= (n.+ shift extra_value))) + (maybe.else false))) + (_.coverage [/.lacks] + (|> sample + (/.has extra_key extra_value) + (/.lacks extra_key) + (# (/.equivalence n.equivalence) = sample))) )))) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 379c31458..9351adb21 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -71,17 +71,17 @@ (let [lifted (/.lifted io.monad) (open "io#[0]") io.monad expected (n.+ parameter subject)] - (_.cover [/.with /.lifted] - (|> (io.run! (do (/.with io.monad) - [a (lifted (io#in parameter)) - b (in subject)] - (in (n.+ a b)))) - (pipe.case - (pattern (list actual)) - (n.= expected actual) - - _ - false))))) + (_.coverage [/.with /.lifted] + (|> (io.run! (do (/.with io.monad) + [a (lifted (io#in parameter)) + b (in subject)] + (in (n.+ a b)))) + (pipe.case + (pattern (list actual)) + (n.= expected actual) + + _ + false))))) )) (def: whole @@ -91,41 +91,41 @@ .let [(open "/#[0]") (/.equivalence n.equivalence)] sample (# ! each set.list (random.set n.hash size random.nat))] (all _.and - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (# bit.equivalence = - (/.empty? sample) - (n.= 0 (/.size sample)))) - (_.cover [/.repeated] - (n.= size (/.size (/.repeated size [])))) - (_.cover [/.reversed] - (or (n.< 2 (/.size sample)) - (let [not_same! - (not (/#= sample - (/.reversed sample))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (# bit.equivalence = + (/.empty? sample) + (n.= 0 (/.size sample)))) + (_.coverage [/.repeated] + (n.= size (/.size (/.repeated size [])))) + (_.coverage [/.reversed] + (or (n.< 2 (/.size sample)) + (let [not_same! + (not (/#= sample + (/.reversed sample))) - self_symmetry! - (/#= sample - (/.reversed (/.reversed sample)))] - (and not_same! - self_symmetry!)))) - (_.cover [/.every? /.any?] - (if (/.every? n.even? sample) - (not (/.any? (bit.complement n.even?) sample)) - (/.any? (bit.complement n.even?) sample))) - (_.cover [/.sorted] - (let [<<< n.< - - size_preservation! - (n.= (/.size sample) - (/.size (/.sorted <<< sample))) - - symmetry! - (/#= (/.sorted <<< sample) - (/.reversed (/.sorted (function.flipped <<<) sample)))] - (and size_preservation! - symmetry!))) + self_symmetry! + (/#= sample + (/.reversed (/.reversed sample)))] + (and not_same! + self_symmetry!)))) + (_.coverage [/.every? /.any?] + (if (/.every? n.even? sample) + (not (/.any? (bit.complement n.even?) sample)) + (/.any? (bit.complement n.even?) sample))) + (_.coverage [/.sorted] + (let [<<< n.< + + size_preservation! + (n.= (/.size sample) + (/.size (/.sorted <<< sample))) + + symmetry! + (/#= (/.sorted <<< sample) + (/.reversed (/.sorted (function.flipped <<<) sample)))] + (and size_preservation! + symmetry!))) ))) (def: indices @@ -136,56 +136,56 @@ [sample ..random .let [size (/.size sample)]] (all _.and - (_.cover [/.indices] - (let [indices (/.indices size) + (_.coverage [/.indices] + (let [indices (/.indices size) - expected_amount! - (n.= size (/.size indices)) + expected_amount! + (n.= size (/.size indices)) - already_sorted! - (/#= indices - (/.sorted n.< indices)) + already_sorted! + (/#= indices + (/.sorted n.< indices)) - expected_numbers! - (/.every? (n.= (-- size)) - (/.zipped_with_2 n.+ - indices - (/.sorted n.> indices)))] - (and expected_amount! - already_sorted! - expected_numbers!))) - (_.cover [/.enumeration] - (let [enumeration (/.enumeration sample) + expected_numbers! + (/.every? (n.= (-- size)) + (/.zipped_with_2 n.+ + indices + (/.sorted n.> indices)))] + (and expected_amount! + already_sorted! + expected_numbers!))) + (_.coverage [/.enumeration] + (let [enumeration (/.enumeration sample) - has_correct_indices! - (/#= (/.indices (/.size enumeration)) - (/#each product.left enumeration)) + has_correct_indices! + (/#= (/.indices (/.size enumeration)) + (/#each product.left enumeration)) - has_correct_values! - (/#= sample - (/#each product.right enumeration))] - (and has_correct_indices! - has_correct_values!))) - (_.cover [/.item] - (/.every? (function (_ [index expected]) - (case (/.item index sample) - {.#Some actual} - (n.= expected actual) - - {.#None} - false)) - (/.enumeration sample))) + has_correct_values! + (/#= sample + (/#each product.right enumeration))] + (and has_correct_indices! + has_correct_values!))) + (_.coverage [/.item] + (/.every? (function (_ [index expected]) + (case (/.item index sample) + {.#Some actual} + (n.= expected actual) + + {.#None} + false)) + (/.enumeration sample))) (do ! [index (case size 0 random.nat _ (# ! each (n.% size) random.nat)) .let [changed? (/#= sample (/.revised index ++ sample)) same? (/#= sample (/.revised size ++ sample))]] - (_.cover [/.revised] - (case size - 0 (and changed? - same?) - _ (not changed?)))) + (_.coverage [/.revised] + (case size + 0 (and changed? + same?) + _ (not changed?)))) )))) (def: slice @@ -199,42 +199,42 @@ idx (# ! each (n.% size) random.nat) sub_size (# ! each (|>> (n.% size) ++) random.nat)] (all _.and - (_.cover [/.only] - (let [positives (/.only n.even? sample) - negatives (/.only (bit.complement n.even?) sample)] - (and (/.every? n.even? positives) - (not (/.any? n.even? negatives)) + (_.coverage [/.only] + (let [positives (/.only n.even? sample) + negatives (/.only (bit.complement n.even?) sample)] + (and (/.every? n.even? positives) + (not (/.any? n.even? negatives)) - (n.= (/.size sample) - (n.+ (/.size positives) - (/.size negatives)))))) - (_.cover [/.partition] - (let [[positives negatives] (/.partition n.even? sample)] - (and (/#= (/.only n.even? sample) - positives) - (/#= (/.only (bit.complement n.even?) sample) - negatives)))) - (_.cover [/.split_at] - (let [[left right] (/.split_at idx sample)] - (/#= sample - (/#composite left right)))) - (_.cover [/.split_when] - (let [[left right] (/.split_when n.even? sample)] - (/#= sample - (/#composite left right)))) - (_.cover [/.first /.after] + (n.= (/.size sample) + (n.+ (/.size positives) + (/.size negatives)))))) + (_.coverage [/.partition] + (let [[positives negatives] (/.partition n.even? sample)] + (and (/#= (/.only n.even? sample) + positives) + (/#= (/.only (bit.complement n.even?) sample) + negatives)))) + (_.coverage [/.split_at] + (let [[left right] (/.split_at idx sample)] + (/#= sample + (/#composite left right)))) + (_.coverage [/.split_when] + (let [[left right] (/.split_when n.even? sample)] + (/#= sample + (/#composite left right)))) + (_.coverage [/.first /.after] + (/#= sample + (/#composite (/.first idx sample) + (/.after idx sample)))) + (_.coverage [/.while /.until] + (/#= sample + (/#composite (/.while n.even? sample) + (/.until n.even? sample)))) + (_.coverage [/.sub] + (let [subs (/.sub sub_size sample)] + (and (/.every? (|>> /.size (n.<= sub_size)) subs) (/#= sample - (/#composite (/.first idx sample) - (/.after idx sample)))) - (_.cover [/.while /.until] - (/#= sample - (/#composite (/.while n.even? sample) - (/.until n.even? sample)))) - (_.cover [/.sub] - (let [subs (/.sub sub_size sample)] - (and (/.every? (|>> /.size (n.<= sub_size)) subs) - (/#= sample - (/.together subs))))) + (/.together subs))))) )))) (def: member @@ -243,31 +243,31 @@ (do [! random.monad] [sample ..random] (`` (all _.and - (_.cover [/.member?] - (/.every? (/.member? n.equivalence sample) - sample)) + (_.coverage [/.member?] + (/.every? (/.member? n.equivalence sample) + sample)) (~~ (template [<head> <tail> <pre>] [(all _.and - (_.cover [<head>] - (case [(<pre> sample) (<head> sample)] - [{.#Item expected _} {.#Some actual}] - (n.= expected actual) + (_.coverage [<head>] + (case [(<pre> sample) (<head> sample)] + [{.#Item expected _} {.#Some actual}] + (n.= expected actual) - [{.#End} {.#None}] - true + [{.#End} {.#None}] + true - _ - false)) - (_.cover [<tail>] - (case [(<pre> sample) (<tail> sample)] - [{.#Item _ expected} {.#Some actual}] - (/#= (<pre> expected) actual) + _ + false)) + (_.coverage [<tail>] + (case [(<pre> sample) (<tail> sample)] + [{.#Item _ expected} {.#Some actual}] + (/#= (<pre> expected) actual) - [{.#End} {.#None}] - true + [{.#End} {.#None}] + true - _ - false)) + _ + false)) )] [/.head /.tail |>] @@ -292,82 +292,82 @@ sample/1 ..random sample/2 ..random] (all _.and - (_.cover [/.pairs] - (let [even_sized? (|> sample/0 - /.size - (n.% 2) - (n.= 0))] - (case (/.pairs sample/0) - {.#Some pairs/0} - (and even_sized? - (n.= (n./ 2 (/.size sample/0)) - (/.size pairs/0))) + (_.coverage [/.pairs] + (let [even_sized? (|> sample/0 + /.size + (n.% 2) + (n.= 0))] + (case (/.pairs sample/0) + {.#Some pairs/0} + (and even_sized? + (n.= (n./ 2 (/.size sample/0)) + (/.size pairs/0))) - {.#None} - (not even_sized?)))) - (_.cover [/.zipped_2] - (let [zipped (/.zipped_2 sample/0 sample/1) - zipped::size (/.size zipped) + {.#None} + (not even_sized?)))) + (_.coverage [/.zipped_2] + (let [zipped (/.zipped_2 sample/0 sample/1) + zipped::size (/.size zipped) - size_of_smaller_list! - (n.= zipped::size - (n.min (/.size sample/0) (/.size sample/1))) + size_of_smaller_list! + (n.= zipped::size + (n.min (/.size sample/0) (/.size sample/1))) - can_extract_values! - (and (/#= (/.first zipped::size sample/0) - (/#each product.left zipped)) - (/#= (/.first zipped::size sample/1) - (/#each product.right zipped)))] - (and size_of_smaller_list! - can_extract_values!))) - (_.cover [/.zipped_3] - (let [zipped (/.zipped_3 sample/0 sample/1 sample/2) - zipped::size (/.size zipped) - - size_of_smaller_list! - (n.= zipped::size - (all n.min - (/.size sample/0) - (/.size sample/1) - (/.size sample/2))) + can_extract_values! + (and (/#= (/.first zipped::size sample/0) + (/#each product.left zipped)) + (/#= (/.first zipped::size sample/1) + (/#each product.right zipped)))] + (and size_of_smaller_list! + can_extract_values!))) + (_.coverage [/.zipped_3] + (let [zipped (/.zipped_3 sample/0 sample/1 sample/2) + zipped::size (/.size zipped) + + size_of_smaller_list! + (n.= zipped::size + (all n.min + (/.size sample/0) + (/.size sample/1) + (/.size sample/2))) - can_extract_values! - (and (/#= (/.first zipped::size sample/0) - (/#each product.left zipped)) - (/#= (/.first zipped::size sample/1) - (/#each (|>> product.right product.left) zipped)) - (/#= (/.first zipped::size sample/2) - (/#each (|>> product.right product.right) zipped)))] - (and size_of_smaller_list! - can_extract_values!))) - (_.cover [/.zipped] - (and (# (/.equivalence (product.equivalence n.equivalence n.equivalence)) = - (/.zipped_2 sample/0 sample/1) - ((/.zipped 2) sample/0 sample/1)) - (# (/.equivalence (all product.equivalence n.equivalence n.equivalence n.equivalence)) = - (/.zipped_3 sample/0 sample/1 sample/2) - ((/.zipped 3) sample/0 sample/1 sample/2)))) + can_extract_values! + (and (/#= (/.first zipped::size sample/0) + (/#each product.left zipped)) + (/#= (/.first zipped::size sample/1) + (/#each (|>> product.right product.left) zipped)) + (/#= (/.first zipped::size sample/2) + (/#each (|>> product.right product.right) zipped)))] + (and size_of_smaller_list! + can_extract_values!))) + (_.coverage [/.zipped] + (and (# (/.equivalence (product.equivalence n.equivalence n.equivalence)) = + (/.zipped_2 sample/0 sample/1) + ((/.zipped 2) sample/0 sample/1)) + (# (/.equivalence (all product.equivalence n.equivalence n.equivalence n.equivalence)) = + (/.zipped_3 sample/0 sample/1 sample/2) + ((/.zipped 3) sample/0 sample/1 sample/2)))) - (_.cover [/.zipped_with_2] - (/#= (/#each (function (_ [left right]) - (+/2 left right)) - (/.zipped_2 sample/0 sample/1)) - (/.zipped_with_2 +/2 sample/0 sample/1))) - (_.cover [/.zipped_with_3] - (/#= (/#each (function (_ [left mid right]) - (+/3 left mid right)) - (/.zipped_3 sample/0 sample/1 sample/2)) - (/.zipped_with_3 +/3 sample/0 sample/1 sample/2))) - (_.cover [/.zipped_with] - (and (/#= (/.zipped_with_2 +/2 sample/0 sample/1) - ((/.zipped_with 2) +/2 sample/0 sample/1)) - (/#= (/.zipped_with_3 +/3 sample/0 sample/1 sample/2) - ((/.zipped_with 3) +/3 sample/0 sample/1 sample/2)))) - (_.cover [/.together] - (and (/#= (/#composite sample/0 sample/1) - (/.together (list sample/0 sample/1))) - (/#= (all /#composite sample/0 sample/1 sample/2) - (/.together (list sample/0 sample/1 sample/2))))) + (_.coverage [/.zipped_with_2] + (/#= (/#each (function (_ [left right]) + (+/2 left right)) + (/.zipped_2 sample/0 sample/1)) + (/.zipped_with_2 +/2 sample/0 sample/1))) + (_.coverage [/.zipped_with_3] + (/#= (/#each (function (_ [left mid right]) + (+/3 left mid right)) + (/.zipped_3 sample/0 sample/1 sample/2)) + (/.zipped_with_3 +/3 sample/0 sample/1 sample/2))) + (_.coverage [/.zipped_with] + (and (/#= (/.zipped_with_2 +/2 sample/0 sample/1) + ((/.zipped_with 2) +/2 sample/0 sample/1)) + (/#= (/.zipped_with_3 +/3 sample/0 sample/1 sample/2) + ((/.zipped_with 3) +/3 sample/0 sample/1 sample/2)))) + (_.coverage [/.together] + (and (/#= (/#composite sample/0 sample/1) + (/.together (list sample/0 sample/1))) + (/#= (all /#composite sample/0 sample/1 sample/2) + (/.together (list sample/0 sample/1 sample/2))))) )))) (def: search @@ -382,33 +382,33 @@ (do [! random.monad] [sample ..random] (all _.and - (_.cover [/.one] - (case [(|> sample - (/.only n.even?) - (/#each (# n.decimal encoded)) - /.head) - (/.one choice sample)] - [{.#Some expected} {.#Some actual}] - (text#= expected actual) + (_.coverage [/.one] + (case [(|> sample + (/.only n.even?) + (/#each (# n.decimal encoded)) + /.head) + (/.one choice sample)] + [{.#Some expected} {.#Some actual}] + (text#= expected actual) - [{.#None} {.#None}] - true + [{.#None} {.#None}] + true - _ - false)) - (_.cover [/.all] - (# (/.equivalence text.equivalence) = - (|> sample - (/.only n.even?) - (/#each (# n.decimal encoded))) - (/.all choice sample))) - (_.cover [/.example] - (case (/.example n.even? sample) - {.#Some found} - (n.even? found) + _ + false)) + (_.coverage [/.all] + (# (/.equivalence text.equivalence) = + (|> sample + (/.only n.even?) + (/#each (# n.decimal encoded))) + (/.all choice sample))) + (_.coverage [/.example] + (case (/.example n.even? sample) + {.#Some found} + (n.even? found) - {.#None} - (not (/.any? n.even? sample)))) + {.#None} + (not (/.any? n.even? sample)))) )))) (def: .public test @@ -429,33 +429,33 @@ ..grouping ..search - (_.cover [/.interposed] - (or (/.empty? sample) - (let [sample+ (/.interposed separator sample)] - (and (n.= (|> (/.size sample) (n.* 2) --) - (/.size sample+)) - (|> sample+ - /.pairs - (maybe.else (list)) - (/.every? (|>> product.right (n.= separator)))))))) - (_.cover [/.iterations] - (or (/.empty? sample) - (let [size (/.size sample)] - (/#= (/.indices size) - (/.iterations (function (_ index) - (if (n.< size index) - {.#Some (++ index)} - {.#None})) - 0))))) - (_.cover [/.mixes] - (/#= (/#each (function (_ index) - (# /.mix mix n.+ 0 (/.first index sample))) - (/.indices (++ (/.size sample)))) - (/.mixes n.+ 0 sample))) + (_.coverage [/.interposed] + (or (/.empty? sample) + (let [sample+ (/.interposed separator sample)] + (and (n.= (|> (/.size sample) (n.* 2) --) + (/.size sample+)) + (|> sample+ + /.pairs + (maybe.else (list)) + (/.every? (|>> product.right (n.= separator)))))))) + (_.coverage [/.iterations] + (or (/.empty? sample) + (let [size (/.size sample)] + (/#= (/.indices size) + (/.iterations (function (_ index) + (if (n.< size index) + {.#Some (++ index)} + {.#None})) + 0))))) + (_.coverage [/.mixes] + (/#= (/#each (function (_ index) + (# /.mix mix n.+ 0 (/.first index sample))) + (/.indices (++ (/.size sample)))) + (/.mixes n.+ 0 sample))) (do random.monad [expected random.nat .let [(open "/#[0]") (/.equivalence n.equivalence)]] - (_.cover [/.when] - (and (/#= (list expected) (/.when true (list expected))) - (/#= (list) (/.when false (list expected)))))) + (_.coverage [/.when] + (and (/#= (list expected) (/.when true (list expected))) + (/#= (list) (/.when false (list expected)))))) ))))) diff --git a/stdlib/source/test/lux/data/collection/queue.lux b/stdlib/source/test/lux/data/collection/queue.lux index aa6365a41..ef8575e81 100644 --- a/stdlib/source/test/lux/data/collection/queue.lux +++ b/stdlib/source/test/lux/data/collection/queue.lux @@ -40,80 +40,80 @@ (_.for [/.functor] ($functor.spec ..injection /.equivalence /.functor)) - (_.cover [/.of_list /.list] - (|> members /.of_list /.list - (# (list.equivalence n.equivalence) = members))) - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (n.= 0 size) (/.empty? sample))) - (_.cover [/.empty] - (let [empty_is_empty! - (/.empty? /.empty) + (_.coverage [/.of_list /.list] + (|> members /.of_list /.list + (# (list.equivalence n.equivalence) = members))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (n.= 0 size) (/.empty? sample))) + (_.coverage [/.empty] + (let [empty_is_empty! + (/.empty? /.empty) - all_empty_queues_look_the_same! - (bit#= (/.empty? sample) - (# (/.equivalence n.equivalence) = - sample - /.empty))] - (and empty_is_empty! - all_empty_queues_look_the_same!))) - (_.cover [/.front] - (case [members (/.front sample)] - [{.#Item head tail} {.#Some first}] - (n.= head first) - - [{.#End} {.#None}] - true + all_empty_queues_look_the_same! + (bit#= (/.empty? sample) + (# (/.equivalence n.equivalence) = + sample + /.empty))] + (and empty_is_empty! + all_empty_queues_look_the_same!))) + (_.coverage [/.front] + (case [members (/.front sample)] + [{.#Item head tail} {.#Some first}] + (n.= head first) + + [{.#End} {.#None}] + true - _ - false)) - (_.cover [/.member?] - (let [every_member_is_identified! - (list.every? (/.member? n.equivalence sample) - (/.list sample)) + _ + false)) + (_.coverage [/.member?] + (let [every_member_is_identified! + (list.every? (/.member? n.equivalence sample) + (/.list sample)) - non_member_is_not_identified! - (not (/.member? n.equivalence sample non_member))] - (and every_member_is_identified! - non_member_is_not_identified!))) - (_.cover [/.end] - (let [pushed (/.end non_member sample) + non_member_is_not_identified! + (not (/.member? n.equivalence sample non_member))] + (and every_member_is_identified! + non_member_is_not_identified!))) + (_.coverage [/.end] + (let [pushed (/.end non_member sample) - size_increases! - (n.= (++ (/.size sample)) (/.size pushed)) + size_increases! + (n.= (++ (/.size sample)) (/.size pushed)) - new_member_is_identified! - (/.member? n.equivalence pushed non_member) + new_member_is_identified! + (/.member? n.equivalence pushed non_member) - has_expected_order! - (# (list.equivalence n.equivalence) = - (list#composite (/.list sample) (list non_member)) - (/.list pushed))] - (and size_increases! - new_member_is_identified! - has_expected_order!))) - (_.cover [/.next] - (case members - {.#Item target expected} - (let [popped (/.next sample) + has_expected_order! + (# (list.equivalence n.equivalence) = + (list#composite (/.list sample) (list non_member)) + (/.list pushed))] + (and size_increases! + new_member_is_identified! + has_expected_order!))) + (_.coverage [/.next] + (case members + {.#Item target expected} + (let [popped (/.next sample) - size_decreases! - (n.= (-- (/.size sample)) - (/.size popped)) + size_decreases! + (n.= (-- (/.size sample)) + (/.size popped)) - popped_member_is_not_identified! - (not (/.member? n.equivalence popped target)) + popped_member_is_not_identified! + (not (/.member? n.equivalence popped target)) - has_expected_order! - (# (list.equivalence n.equivalence) = - expected - (/.list popped))] - (and size_decreases! - popped_member_is_not_identified! - has_expected_order!)) - - {.#End} - (and (/.empty? sample) - (/.empty? (/.next sample))))) + has_expected_order! + (# (list.equivalence n.equivalence) = + expected + (/.list popped))] + (and size_decreases! + popped_member_is_not_identified! + has_expected_order!)) + + {.#End} + (and (/.empty? sample) + (/.empty? (/.next sample))))) )))) diff --git a/stdlib/source/test/lux/data/collection/queue/priority.lux b/stdlib/source/test/lux/data/collection/queue/priority.lux index d0a8faf6c..c802d6368 100644 --- a/stdlib/source/test/lux/data/collection/queue/priority.lux +++ b/stdlib/source/test/lux/data/collection/queue/priority.lux @@ -40,55 +40,55 @@ max_member random.nat min_member random.nat] (all _.and - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (n.= 0 (/.size sample)) - (/.empty? sample))) - (_.cover [/.empty] - (/.empty? /.empty)) - (_.cover [/.front] - (case (/.front sample) - {.#Some first} - (n.> 0 (/.size sample)) - - {.#None} - (/.empty? sample))) - (_.cover [/.member?] - (case (/.front sample) - {.#Some first} - (/.member? n.equivalence sample first) - - {.#None} - (/.empty? sample))) - (_.cover [/.end] - (let [sample+ (/.end non_member_priority non_member sample)] - (and (not (/.member? n.equivalence sample non_member)) - (n.= (++ (/.size sample)) - (/.size sample+)) - (/.member? n.equivalence sample+ non_member)))) - (_.cover [/.next] - (let [sample- (/.next sample)] - (or (and (/.empty? sample) - (/.empty? sample-)) - (n.= (-- (/.size sample)) - (/.size sample-))))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (n.= 0 (/.size sample)) + (/.empty? sample))) + (_.coverage [/.empty] + (/.empty? /.empty)) + (_.coverage [/.front] + (case (/.front sample) + {.#Some first} + (n.> 0 (/.size sample)) + + {.#None} + (/.empty? sample))) + (_.coverage [/.member?] + (case (/.front sample) + {.#Some first} + (/.member? n.equivalence sample first) + + {.#None} + (/.empty? sample))) + (_.coverage [/.end] + (let [sample+ (/.end non_member_priority non_member sample)] + (and (not (/.member? n.equivalence sample non_member)) + (n.= (++ (/.size sample)) + (/.size sample+)) + (/.member? n.equivalence sample+ non_member)))) + (_.coverage [/.next] + (let [sample- (/.next sample)] + (or (and (/.empty? sample) + (/.empty? sample-)) + (n.= (-- (/.size sample)) + (/.size sample-))))) (_.for [/.Priority] (all _.and - (_.cover [/.max] - (|> /.empty - (/.end /.min min_member) - (/.end /.max max_member) - /.front - (maybe#each (n.= max_member)) - (maybe.else false))) - (_.cover [/.min] - (|> /.empty - (/.end /.max max_member) - (/.end /.min min_member) - /.next - /.front - (maybe#each (n.= min_member)) - (maybe.else false))) + (_.coverage [/.max] + (|> /.empty + (/.end /.min min_member) + (/.end /.max max_member) + /.front + (maybe#each (n.= max_member)) + (maybe.else false))) + (_.coverage [/.min] + (|> /.empty + (/.end /.max max_member) + (/.end /.min min_member) + /.next + /.front + (maybe#each (n.= min_member)) + (maybe.else false))) )) )))) diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux index a88a1f8de..f3c3bb0d0 100644 --- a/stdlib/source/test/lux/data/collection/sequence.lux +++ b/stdlib/source/test/lux/data/collection/sequence.lux @@ -54,29 +54,29 @@ .let [sample (|> sample set.list /.of_list)] .let [(open "/#[0]") (/.equivalence n.equivalence)]] (all _.and - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (/.empty? sample) (n.= 0 (/.size sample)))) - (_.cover [/.empty] - (/.empty? /.empty)) - (_.cover [/.list /.of_list] - (|> sample /.list /.of_list (/#= sample))) - (_.cover [/.reversed] - (or (n.< 2 (/.size sample)) - (let [not_same! - (not (/#= sample - (/.reversed sample))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (/.empty? sample) (n.= 0 (/.size sample)))) + (_.coverage [/.empty] + (/.empty? /.empty)) + (_.coverage [/.list /.of_list] + (|> sample /.list /.of_list (/#= sample))) + (_.coverage [/.reversed] + (or (n.< 2 (/.size sample)) + (let [not_same! + (not (/#= sample + (/.reversed sample))) - self_symmetry! - (/#= sample - (/.reversed (/.reversed sample)))] - (and not_same! - self_symmetry!)))) - (_.cover [/.every? /.any?] - (if (/.every? n.even? sample) - (not (/.any? (bit.complement n.even?) sample)) - (/.any? (bit.complement n.even?) sample))) + self_symmetry! + (/#= sample + (/.reversed (/.reversed sample)))] + (and not_same! + self_symmetry!)))) + (_.coverage [/.every? /.any?] + (if (/.every? n.even? sample) + (not (/.any? (bit.complement n.even?) sample)) + (/.any? (bit.complement n.even?) sample))) ))) (def: index_based @@ -92,41 +92,41 @@ random.nat) .let [sample (|> sample set.list /.of_list)]] (all _.and - (_.cover [/.item] - (case (/.item good_index sample) - {try.#Success member} - (/.member? n.equivalence sample member) - - {try.#Failure error} - false)) - (_.cover [/.has] - (<| (try.else false) - (do try.monad - [sample (/.has good_index non_member sample) - actual (/.item good_index sample)] - (in (same? non_member actual))))) - (_.cover [/.revised] - (<| (try.else false) - (do try.monad - [sample (/.has good_index non_member sample) - sample (/.revised good_index ++ sample) - actual (/.item good_index sample)] - (in (n.= (++ non_member) actual))))) - (_.cover [/.within_bounds?] - (and (/.within_bounds? sample good_index) - (not (/.within_bounds? sample bad_index)))) - (_.cover [/.index_out_of_bounds] - (let [fails! (is (All (_ a) (-> (Try a) Bit)) - (function (_ situation) - (case situation - {try.#Success member} - false - - {try.#Failure error} - (exception.match? /.index_out_of_bounds error))))] - (and (fails! (/.item bad_index sample)) - (fails! (/.has bad_index non_member sample)) - (fails! (/.revised bad_index ++ sample))))) + (_.coverage [/.item] + (case (/.item good_index sample) + {try.#Success member} + (/.member? n.equivalence sample member) + + {try.#Failure error} + false)) + (_.coverage [/.has] + (<| (try.else false) + (do try.monad + [sample (/.has good_index non_member sample) + actual (/.item good_index sample)] + (in (same? non_member actual))))) + (_.coverage [/.revised] + (<| (try.else false) + (do try.monad + [sample (/.has good_index non_member sample) + sample (/.revised good_index ++ sample) + actual (/.item good_index sample)] + (in (n.= (++ non_member) actual))))) + (_.coverage [/.within_bounds?] + (and (/.within_bounds? sample good_index) + (not (/.within_bounds? sample bad_index)))) + (_.coverage [/.index_out_of_bounds] + (let [fails! (is (All (_ a) (-> (Try a) Bit)) + (function (_ situation) + (case situation + {try.#Success member} + false + + {try.#Failure error} + (exception.match? /.index_out_of_bounds error))))] + (and (fails! (/.item bad_index sample)) + (fails! (/.has bad_index non_member sample)) + (fails! (/.revised bad_index ++ sample))))) )) ))) @@ -152,66 +152,66 @@ [value/0 random.nat value/1 random.nat value/2 random.nat] - (_.cover [/.sequence] - (/#= (/.of_list (list value/0 value/1 value/2)) - (/.sequence value/0 value/1 value/2)))) - (_.cover [/.member?] - (and (list.every? (/.member? n.equivalence sample) - (/.list sample)) - (not (/.member? n.equivalence sample non_member)))) - (_.cover [/.suffix] - (let [added (/.suffix non_member sample) + (_.coverage [/.sequence] + (/#= (/.of_list (list value/0 value/1 value/2)) + (/.sequence value/0 value/1 value/2)))) + (_.coverage [/.member?] + (and (list.every? (/.member? n.equivalence sample) + (/.list sample)) + (not (/.member? n.equivalence sample non_member)))) + (_.coverage [/.suffix] + (let [added (/.suffix non_member sample) - size_increases! - (n.= (++ (/.size sample)) - (/.size added)) + size_increases! + (n.= (++ (/.size sample)) + (/.size added)) - is_a_member! - (/.member? n.equivalence added non_member)] - (and size_increases! - is_a_member!))) - (_.cover [/.prefix] - (if (/.empty? sample) - (/.empty? (/.prefix sample)) - (let [expected_size! - (n.= (-- (/.size sample)) - (/.size (/.prefix sample))) + is_a_member! + (/.member? n.equivalence added non_member)] + (and size_increases! + is_a_member!))) + (_.coverage [/.prefix] + (if (/.empty? sample) + (/.empty? (/.prefix sample)) + (let [expected_size! + (n.= (-- (/.size sample)) + (/.size (/.prefix sample))) - symmetry! - (|> sample - (/.suffix non_member) - /.prefix - (/#= sample))] - (and expected_size! - symmetry!)))) - (_.cover [/.only] - (let [positives (/.only n.even? sample) - negatives (/.only (bit.complement n.even?) sample)] - (and (/.every? n.even? positives) - (not (/.any? n.even? negatives)) + symmetry! + (|> sample + (/.suffix non_member) + /.prefix + (/#= sample))] + (and expected_size! + symmetry!)))) + (_.coverage [/.only] + (let [positives (/.only n.even? sample) + negatives (/.only (bit.complement n.even?) sample)] + (and (/.every? n.even? positives) + (not (/.any? n.even? negatives)) - (n.= (/.size sample) - (n.+ (/.size positives) - (/.size negatives)))))) - (_.cover [/.one] - (let [(open "/#[0]") /.functor - choice (is (-> Nat (Maybe Text)) - (function (_ value) - (if (n.even? value) - {.#Some (# n.decimal encoded value)} - {.#None})))] - (case [(|> sample - (/.only n.even?) - (/#each (# n.decimal encoded)) - (/.item 0)) - (/.one choice sample)] - [{try.#Success expected} {.#Some actual}] - (text#= expected actual) + (n.= (/.size sample) + (n.+ (/.size positives) + (/.size negatives)))))) + (_.coverage [/.one] + (let [(open "/#[0]") /.functor + choice (is (-> Nat (Maybe Text)) + (function (_ value) + (if (n.even? value) + {.#Some (# n.decimal encoded value)} + {.#None})))] + (case [(|> sample + (/.only n.even?) + (/#each (# n.decimal encoded)) + (/.item 0)) + (/.one choice sample)] + [{try.#Success expected} {.#Some actual}] + (text#= expected actual) - [{try.#Failure _} {.#None}] - true + [{try.#Failure _} {.#None}] + true - _ - false))) + _ + false))) )) )))) diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux index c444f5419..e42a3e3a7 100644 --- a/stdlib/source/test/lux/data/collection/set.lux +++ b/stdlib/source/test/lux/data/collection/set.lux @@ -49,8 +49,8 @@ non_memberL (random.only (|>> (/.member? setL) not) random.nat)] (all _.and - (_.cover [/.empty] - (/.empty? (/.empty n.hash))) + (_.coverage [/.empty] + (/.empty? (/.empty n.hash))) (do ! [hash (# ! each (function (_ constant) (is (Hash Nat) @@ -60,74 +60,74 @@ (def: (hash _) constant)))) random.nat)] - (_.cover [/.member_hash] - (same? hash (/.member_hash (/.empty hash))))) - (_.cover [/.size] - (n.= sizeL (/.size setL))) - (_.cover [/.empty?] - (bit#= (/.empty? setL) - (n.= 0 (/.size setL)))) - (_.cover [/.list /.of_list] - (|> setL /.list (/.of_list n.hash) (#= setL))) - (_.cover [/.member?] - (and (list.every? (/.member? setL) (/.list setL)) - (not (/.member? setL non_memberL)))) - (_.cover [/.has] - (let [before_addition! - (not (/.member? setL non_memberL)) + (_.coverage [/.member_hash] + (same? hash (/.member_hash (/.empty hash))))) + (_.coverage [/.size] + (n.= sizeL (/.size setL))) + (_.coverage [/.empty?] + (bit#= (/.empty? setL) + (n.= 0 (/.size setL)))) + (_.coverage [/.list /.of_list] + (|> setL /.list (/.of_list n.hash) (#= setL))) + (_.coverage [/.member?] + (and (list.every? (/.member? setL) (/.list setL)) + (not (/.member? setL non_memberL)))) + (_.coverage [/.has] + (let [before_addition! + (not (/.member? setL non_memberL)) - after_addition! - (/.member? (/.has non_memberL setL) non_memberL) + after_addition! + (/.member? (/.has non_memberL setL) non_memberL) - size_increase! - (n.= (++ (/.size setL)) - (/.size (/.has non_memberL setL)))] - (and before_addition! - after_addition!))) - (_.cover [/.lacks] - (let [symmetry! - (|> setL - (/.has non_memberL) - (/.lacks non_memberL) - (#= setL)) + size_increase! + (n.= (++ (/.size setL)) + (/.size (/.has non_memberL setL)))] + (and before_addition! + after_addition!))) + (_.coverage [/.lacks] + (let [symmetry! + (|> setL + (/.has non_memberL) + (/.lacks non_memberL) + (#= setL)) - idempotency! - (|> setL - (/.lacks non_memberL) - (#= setL))] - (and symmetry! - idempotency!))) - (_.cover [/.union /.sub?] - (let [setLR (/.union setL setR) - - sets_are_subs_of_their_unions! - (and (/.sub? setLR setL) - (/.sub? setLR setR)) + idempotency! + (|> setL + (/.lacks non_memberL) + (#= setL))] + (and symmetry! + idempotency!))) + (_.coverage [/.union /.sub?] + (let [setLR (/.union setL setR) + + sets_are_subs_of_their_unions! + (and (/.sub? setLR setL) + (/.sub? setLR setR)) - union_with_empty_set! - (|> setL - (/.union (/.empty n.hash)) - (#= setL))] - (and sets_are_subs_of_their_unions! - union_with_empty_set!))) - (_.cover [/.intersection /.super?] - (let [setLR (/.intersection setL setR) - - sets_are_supers_of_their_intersections! - (and (/.super? setLR setL) - (/.super? setLR setR)) + union_with_empty_set! + (|> setL + (/.union (/.empty n.hash)) + (#= setL))] + (and sets_are_subs_of_their_unions! + union_with_empty_set!))) + (_.coverage [/.intersection /.super?] + (let [setLR (/.intersection setL setR) + + sets_are_supers_of_their_intersections! + (and (/.super? setLR setL) + (/.super? setLR setR)) - intersection_with_empty_set! - (|> setL - (/.intersection (/.empty n.hash)) - /.empty?)] - (and sets_are_supers_of_their_intersections! - intersection_with_empty_set!))) - (_.cover [/.difference] - (let [setL+R (/.union setR setL) - setL_R (/.difference setR setL+R)] - (and (list.every? (/.member? setL+R) (/.list setR)) - (not (list.any? (/.member? setL_R) (/.list setR)))))) - (_.cover [/.predicate] - (list.every? (/.predicate setL) (/.list setL))) + intersection_with_empty_set! + (|> setL + (/.intersection (/.empty n.hash)) + /.empty?)] + (and sets_are_supers_of_their_intersections! + intersection_with_empty_set!))) + (_.coverage [/.difference] + (let [setL+R (/.union setR setL) + setL_R (/.difference setR setL+R)] + (and (list.every? (/.member? setL+R) (/.list setR)) + (not (list.any? (/.member? setL_R) (/.list setR)))))) + (_.coverage [/.predicate] + (list.every? (/.predicate setL) (/.list setL))) )))))) diff --git a/stdlib/source/test/lux/data/collection/set/multi.lux b/stdlib/source/test/lux/data/collection/set/multi.lux index 9ace968fb..93f7ef7e6 100644 --- a/stdlib/source/test/lux/data/collection/set/multi.lux +++ b/stdlib/source/test/lux/data/collection/set/multi.lux @@ -58,54 +58,54 @@ another (..random diversity n.hash ..count random.nat)] (`` (all _.and (~~ (template [<name> <composition>] - [(_.cover [<name>] - (let [|sample| (/.support sample) - |another| (/.support another) - sample_only (set.difference |another| |sample|) - another_only (set.difference |sample| |another|) - common (set.intersection |sample| |another|) - composed (<name> sample another) - - no_left_changes! (list.every? (function (_ member) - (n.= (/.multiplicity sample member) - (/.multiplicity composed member))) - (set.list sample_only)) - no_right_changes! (list.every? (function (_ member) - (n.= (/.multiplicity another member) - (/.multiplicity composed member))) - (set.list another_only)) - common_changes! (list.every? (function (_ member) - (n.= (<composition> (/.multiplicity sample member) - (/.multiplicity another member)) - (/.multiplicity composed member))) - (set.list common))] - (and no_left_changes! - no_right_changes! - common_changes!)))] - - [/.sum n.+] - [/.union n.max] - )) - (_.cover [/.intersection] + [(_.coverage [<name>] (let [|sample| (/.support sample) |another| (/.support another) sample_only (set.difference |another| |sample|) another_only (set.difference |sample| |another|) common (set.intersection |sample| |another|) - composed (/.intersection sample another) + composed (<name> sample another) - left_removals! (list.every? (|>> (/.member? composed) not) - (set.list sample_only)) - right_removals! (list.every? (|>> (/.member? composed) not) - (set.list another_only)) + no_left_changes! (list.every? (function (_ member) + (n.= (/.multiplicity sample member) + (/.multiplicity composed member))) + (set.list sample_only)) + no_right_changes! (list.every? (function (_ member) + (n.= (/.multiplicity another member) + (/.multiplicity composed member))) + (set.list another_only)) common_changes! (list.every? (function (_ member) - (n.= (n.min (/.multiplicity sample member) - (/.multiplicity another member)) + (n.= (<composition> (/.multiplicity sample member) + (/.multiplicity another member)) (/.multiplicity composed member))) (set.list common))] - (and left_removals! - right_removals! - common_changes!))) + (and no_left_changes! + no_right_changes! + common_changes!)))] + + [/.sum n.+] + [/.union n.max] + )) + (_.coverage [/.intersection] + (let [|sample| (/.support sample) + |another| (/.support another) + sample_only (set.difference |another| |sample|) + another_only (set.difference |sample| |another|) + common (set.intersection |sample| |another|) + composed (/.intersection sample another) + + left_removals! (list.every? (|>> (/.member? composed) not) + (set.list sample_only)) + right_removals! (list.every? (|>> (/.member? composed) not) + (set.list another_only)) + common_changes! (list.every? (function (_ member) + (n.= (n.min (/.multiplicity sample member) + (/.multiplicity another member)) + (/.multiplicity composed member))) + (set.list common))] + (and left_removals! + right_removals! + common_changes!))) )))) (def: .public test @@ -121,119 +121,119 @@ partial_removal_count (# ! each (n.% addition_count) random.nat) another (..random diversity n.hash ..count random.nat)] (all _.and - (_.cover [/.list /.of_list] - (|> sample - /.list - (/.of_list n.hash) - (# /.equivalence = sample))) - (_.cover [/.size] - (n.= (list.size (/.list sample)) - (/.size sample))) - (_.cover [/.empty?] - (bit#= (/.empty? sample) - (n.= 0 (/.size sample)))) - (_.cover [/.empty] - (/.empty? (/.empty n.hash))) - (_.cover [/.support] - (list.every? (set.member? (/.support sample)) - (/.list sample))) - (_.cover [/.member?] - (let [non_member_is_not_identified! - (not (/.member? sample non_member)) + (_.coverage [/.list /.of_list] + (|> sample + /.list + (/.of_list n.hash) + (# /.equivalence = sample))) + (_.coverage [/.size] + (n.= (list.size (/.list sample)) + (/.size sample))) + (_.coverage [/.empty?] + (bit#= (/.empty? sample) + (n.= 0 (/.size sample)))) + (_.coverage [/.empty] + (/.empty? (/.empty n.hash))) + (_.coverage [/.support] + (list.every? (set.member? (/.support sample)) + (/.list sample))) + (_.coverage [/.member?] + (let [non_member_is_not_identified! + (not (/.member? sample non_member)) - all_members_are_identified! - (list.every? (/.member? sample) - (/.list sample))] - (and non_member_is_not_identified! - all_members_are_identified!))) - (_.cover [/.multiplicity] - (let [non_members_have_0_multiplicity! - (n.= 0 (/.multiplicity sample non_member)) + all_members_are_identified! + (list.every? (/.member? sample) + (/.list sample))] + (and non_member_is_not_identified! + all_members_are_identified!))) + (_.coverage [/.multiplicity] + (let [non_members_have_0_multiplicity! + (n.= 0 (/.multiplicity sample non_member)) - every_member_has_positive_multiplicity! - (list.every? (|>> (/.multiplicity sample) (n.> 0)) - (/.list sample))] - (and non_members_have_0_multiplicity! - every_member_has_positive_multiplicity!))) - (_.cover [/.has] - (let [null_scenario! - (|> sample - (/.has 0 non_member) - (# /.equivalence = sample)) + every_member_has_positive_multiplicity! + (list.every? (|>> (/.multiplicity sample) (n.> 0)) + (/.list sample))] + (and non_members_have_0_multiplicity! + every_member_has_positive_multiplicity!))) + (_.coverage [/.has] + (let [null_scenario! + (|> sample + (/.has 0 non_member) + (# /.equivalence = sample)) - normal_scenario! - (let [sample+ (/.has addition_count non_member sample)] - (and (not (/.member? sample non_member)) - (/.member? sample+ non_member) - (n.= addition_count (/.multiplicity sample+ non_member))))] - (and null_scenario! - normal_scenario!))) - (_.cover [/.lacks] - (let [null_scenario! - (# /.equivalence = - (|> sample - (/.has addition_count non_member)) - (|> sample - (/.has addition_count non_member) - (/.lacks 0 non_member))) + normal_scenario! + (let [sample+ (/.has addition_count non_member sample)] + (and (not (/.member? sample non_member)) + (/.member? sample+ non_member) + (n.= addition_count (/.multiplicity sample+ non_member))))] + (and null_scenario! + normal_scenario!))) + (_.coverage [/.lacks] + (let [null_scenario! + (# /.equivalence = + (|> sample + (/.has addition_count non_member)) + (|> sample + (/.has addition_count non_member) + (/.lacks 0 non_member))) - partial_scenario! - (let [sample* (|> sample - (/.has addition_count non_member) - (/.lacks partial_removal_count non_member))] - (and (/.member? sample* non_member) - (n.= (n.- partial_removal_count - addition_count) - (/.multiplicity sample* non_member)))) + partial_scenario! + (let [sample* (|> sample + (/.has addition_count non_member) + (/.lacks partial_removal_count non_member))] + (and (/.member? sample* non_member) + (n.= (n.- partial_removal_count + addition_count) + (/.multiplicity sample* non_member)))) - total_scenario! - (|> sample - (/.has addition_count non_member) - (/.lacks addition_count non_member) - (# /.equivalence = sample))] - (and null_scenario! - partial_scenario! - total_scenario!))) - (_.cover [/.of_set] - (let [unary (|> sample /.support /.of_set)] - (list.every? (|>> (/.multiplicity unary) (n.= 1)) - (/.list unary)))) - (_.cover [/.sub?] - (let [unary (|> sample /.support /.of_set)] - (and (/.sub? sample unary) - (or (not (/.sub? unary sample)) - (# /.equivalence = sample unary))))) - (_.cover [/.super?] - (let [unary (|> sample /.support /.of_set)] - (and (/.super? unary sample) - (or (not (/.super? sample unary)) - (# /.equivalence = sample unary))))) - (_.cover [/.difference] - (let [|sample| (/.support sample) - |another| (/.support another) - sample_only (set.difference |another| |sample|) - another_only (set.difference |sample| |another|) - common (set.intersection |sample| |another|) - composed (/.difference sample another) + total_scenario! + (|> sample + (/.has addition_count non_member) + (/.lacks addition_count non_member) + (# /.equivalence = sample))] + (and null_scenario! + partial_scenario! + total_scenario!))) + (_.coverage [/.of_set] + (let [unary (|> sample /.support /.of_set)] + (list.every? (|>> (/.multiplicity unary) (n.= 1)) + (/.list unary)))) + (_.coverage [/.sub?] + (let [unary (|> sample /.support /.of_set)] + (and (/.sub? sample unary) + (or (not (/.sub? unary sample)) + (# /.equivalence = sample unary))))) + (_.coverage [/.super?] + (let [unary (|> sample /.support /.of_set)] + (and (/.super? unary sample) + (or (not (/.super? sample unary)) + (# /.equivalence = sample unary))))) + (_.coverage [/.difference] + (let [|sample| (/.support sample) + |another| (/.support another) + sample_only (set.difference |another| |sample|) + another_only (set.difference |sample| |another|) + common (set.intersection |sample| |another|) + composed (/.difference sample another) - ommissions! (list.every? (|>> (/.member? composed) not) - (set.list sample_only)) - intact! (list.every? (function (_ member) - (n.= (/.multiplicity another member) - (/.multiplicity composed member))) - (set.list another_only)) - subtractions! (list.every? (function (_ member) - (let [sample_multiplicity (/.multiplicity sample member) - another_multiplicity (/.multiplicity another member)] - (n.= (if (n.> another_multiplicity sample_multiplicity) - 0 - (n.- sample_multiplicity - another_multiplicity)) - (/.multiplicity composed member)))) - (set.list common))] - (and ommissions! - intact! - subtractions!))) + ommissions! (list.every? (|>> (/.member? composed) not) + (set.list sample_only)) + intact! (list.every? (function (_ member) + (n.= (/.multiplicity another member) + (/.multiplicity composed member))) + (set.list another_only)) + subtractions! (list.every? (function (_ member) + (let [sample_multiplicity (/.multiplicity sample member) + another_multiplicity (/.multiplicity another member)] + (n.= (if (n.> another_multiplicity sample_multiplicity) + 0 + (n.- sample_multiplicity + another_multiplicity)) + (/.multiplicity composed member)))) + (set.list common))] + (and ommissions! + intact! + subtractions!))) ..signature ..composition diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux index 67f7bb483..429df3d21 100644 --- a/stdlib/source/test/lux/data/collection/set/ordered.lux +++ b/stdlib/source/test/lux/data/collection/set/ordered.lux @@ -56,122 +56,122 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence (..random sizeL n.order random.nat))) - (_.cover [/.size] - (n.= sizeL (/.size setL))) - (_.cover [/.empty?] - (bit#= (n.= 0 (/.size setL)) - (/.empty? setL))) - (_.cover [/.empty] - (/.empty? (/.empty n.order))) - (_.cover [/.list] - (# (list.equivalence n.equivalence) = - (/.list (/.of_list n.order listL)) - (list.sorted (# n.order <) listL))) - (_.cover [/.of_list] - (|> setL - /.list (/.of_list n.order) - (/#= setL))) + (_.coverage [/.size] + (n.= sizeL (/.size setL))) + (_.coverage [/.empty?] + (bit#= (n.= 0 (/.size setL)) + (/.empty? setL))) + (_.coverage [/.empty] + (/.empty? (/.empty n.order))) + (_.coverage [/.list] + (# (list.equivalence n.equivalence) = + (/.list (/.of_list n.order listL)) + (list.sorted (# n.order <) listL))) + (_.coverage [/.of_list] + (|> setL + /.list (/.of_list n.order) + (/#= setL))) (~~ (template [<coverage> <comparison>] - [(_.cover [<coverage>] - (case (<coverage> setL) - {.#Some value} - (|> setL /.list (list.every? (<comparison> value))) + [(_.coverage [<coverage>] + (case (<coverage> setL) + {.#Some value} + (|> setL /.list (list.every? (<comparison> value))) - {.#None} - (/.empty? setL)))] + {.#None} + (/.empty? setL)))] [/.min n.>=] [/.max n.<=] )) - (_.cover [/.member?] - (let [members_are_identified! - (list.every? (/.member? setL) (/.list setL)) - - non_members_are_not_identified! - (not (/.member? setL non_memberL))] - (and members_are_identified! - non_members_are_not_identified!))) - (_.cover [/.has] - (let [setL+ (/.has non_memberL setL)] - (and (not (/.member? setL non_memberL)) - (/.member? setL+ non_memberL) - (n.= (++ (/.size setL)) - (/.size setL+))))) - (_.cover [/.lacks] - (|> setL - (/.has non_memberL) - (/.lacks non_memberL) - (# /.equivalence = setL))) - (_.cover [/.sub?] + (_.coverage [/.member?] + (let [members_are_identified! + (list.every? (/.member? setL) (/.list setL)) + + non_members_are_not_identified! + (not (/.member? setL non_memberL))] + (and members_are_identified! + non_members_are_not_identified!))) + (_.coverage [/.has] + (let [setL+ (/.has non_memberL setL)] + (and (not (/.member? setL non_memberL)) + (/.member? setL+ non_memberL) + (n.= (++ (/.size setL)) + (/.size setL+))))) + (_.coverage [/.lacks] + (|> setL + (/.has non_memberL) + (/.lacks non_memberL) + (# /.equivalence = setL))) + (_.coverage [/.sub?] + (let [self! + (/.sub? setL setL) + + empty! + (/.sub? setL empty)] + (and self! + empty!))) + (_.coverage [/.super?] + (let [self! + (/.super? setL setL) + + empty! + (/.super? empty setL) + + symmetry! + (bit#= (/.super? setL setR) + (/.sub? setR setL))] + (and self! + empty! + symmetry!))) + (~~ (template [<coverage> <relation> <empty?>] + [(_.coverage [<coverage>] (let [self! - (/.sub? setL setL) + (# /.equivalence = + setL + (<coverage> setL setL)) - empty! - (/.sub? setL empty)] - (and self! - empty!))) - (_.cover [/.super?] - (let [self! - (/.super? setL setL) + super! + (and (<relation> (<coverage> setL setR) setL) + (<relation> (<coverage> setL setR) setR)) empty! - (/.super? empty setL) + (# /.equivalence = + (if <empty?> empty setL) + (<coverage> setL empty)) - symmetry! - (bit#= (/.super? setL setR) - (/.sub? setR setL))] + idempotence! + (# /.equivalence = + (<coverage> setL (<coverage> setL setR)) + (<coverage> setR (<coverage> setL setR)))] (and self! + super! empty! - symmetry!))) - (~~ (template [<coverage> <relation> <empty?>] - [(_.cover [<coverage>] - (let [self! - (# /.equivalence = - setL - (<coverage> setL setL)) - - super! - (and (<relation> (<coverage> setL setR) setL) - (<relation> (<coverage> setL setR) setR)) - - empty! - (# /.equivalence = - (if <empty?> empty setL) - (<coverage> setL empty)) - - idempotence! - (# /.equivalence = - (<coverage> setL (<coverage> setL setR)) - (<coverage> setR (<coverage> setL setR)))] - (and self! - super! - empty! - idempotence!)))] + idempotence!)))] [/.union /.sub? false] [/.intersection /.super? true] )) - (_.cover [/.difference] - (let [self! - (|> setL - (/.difference setL) - (# /.equivalence = empty)) - - empty! - (|> setL - (/.difference empty) - (# /.equivalence = setL)) - - difference! - (not (list.any? (/.member? (/.difference setL setR)) - (/.list setL))) - - idempotence! - (# /.equivalence = - (/.difference setL setR) - (/.difference setL (/.difference setL setR)))] - (and self! - empty! - difference! - idempotence!))) + (_.coverage [/.difference] + (let [self! + (|> setL + (/.difference setL) + (# /.equivalence = empty)) + + empty! + (|> setL + (/.difference empty) + (# /.equivalence = setL)) + + difference! + (not (list.any? (/.member? (/.difference setL setR)) + (/.list setL))) + + idempotence! + (# /.equivalence = + (/.difference setL setR) + (/.difference setL (/.difference setL setR)))] + (and self! + empty! + difference! + idempotence!))) ))))) diff --git a/stdlib/source/test/lux/data/collection/stack.lux b/stdlib/source/test/lux/data/collection/stack.lux index f23767283..62844c59d 100644 --- a/stdlib/source/test/lux/data/collection/stack.lux +++ b/stdlib/source/test/lux/data/collection/stack.lux @@ -36,35 +36,35 @@ (_.for [/.functor] ($functor.spec ..injection /.equivalence /.functor)) - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (bit#= (n.= 0 (/.size sample)) - (/.empty? sample))) - (_.cover [/.empty] - (/.empty? /.empty)) - (_.cover [/.value] - (case (/.value sample) - {.#None} - (/.empty? sample) - - {.#Some _} - (not (/.empty? sample)))) - (_.cover [/.next] - (case (/.next sample) - {.#None} - (/.empty? sample) - - {.#Some [top remaining]} - (# (/.equivalence n.equivalence) = - sample - (/.top top remaining)))) - (_.cover [/.top] - (case (/.next (/.top expected_top sample)) - {.#Some [actual_top actual_sample]} - (and (same? expected_top actual_top) - (same? sample actual_sample)) - - {.#None} - false)) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (bit#= (n.= 0 (/.size sample)) + (/.empty? sample))) + (_.coverage [/.empty] + (/.empty? /.empty)) + (_.coverage [/.value] + (case (/.value sample) + {.#None} + (/.empty? sample) + + {.#Some _} + (not (/.empty? sample)))) + (_.coverage [/.next] + (case (/.next sample) + {.#None} + (/.empty? sample) + + {.#Some [top remaining]} + (# (/.equivalence n.equivalence) = + sample + (/.top top remaining)))) + (_.coverage [/.top] + (case (/.next (/.top expected_top sample)) + {.#Some [actual_top actual_sample]} + (and (same? expected_top actual_top) + (same? sample actual_sample)) + + {.#None} + false)) )))) diff --git a/stdlib/source/test/lux/data/collection/stream.lux b/stdlib/source/test/lux/data/collection/stream.lux index f6ddd13d3..f06af6f9c 100644 --- a/stdlib/source/test/lux/data/collection/stream.lux +++ b/stdlib/source/test/lux/data/collection/stream.lux @@ -56,68 +56,68 @@ (_.for [/.comonad] ($comonad.spec /.repeated ..equivalence /.comonad)) - (_.cover [/.item] - (n.= (n.+ offset index) - (/.item index (..iterations ++ offset)))) - (_.cover [/.repeated] - (n.= repeated - (/.item index (/.repeated repeated)))) - (_.cover [/.first] - (list#= (enum.range n.enum offset (-- (n.+ size offset))) - (/.first size (..iterations ++ offset)))) - (_.cover [/.after] - (list#= (enum.range n.enum offset (-- (n.+ size offset))) - (/.first size (/.after offset (..iterations ++ 0))))) - (_.cover [/.split_at] - (let [[drops takes] (/.split_at size (..iterations ++ 0))] - (and (list#= (enum.range n.enum 0 (-- size)) - drops) - (list#= (enum.range n.enum size (-- (n.* 2 size))) - (/.first size takes))))) - (_.cover [/.while] - (list#= (enum.range n.enum 0 (-- size)) - (/.while (n.< size) (..iterations ++ 0)))) - (_.cover [/.until] - (list#= (enum.range n.enum offset (-- (n.+ size offset))) - (/.while (n.< (n.+ size offset)) - (/.until (n.< offset) (..iterations ++ 0))))) - (_.cover [/.split_when] - (let [[drops takes] (/.split_when (n.= size) (..iterations ++ 0))] - (and (list#= (enum.range n.enum 0 (-- size)) - drops) - (list#= (enum.range n.enum size (-- (n.* 2 size))) - (/.while (n.< (n.* 2 size)) takes))))) - (_.cover [/.head] - (n.= offset - (/.head (..iterations ++ offset)))) - (_.cover [/.tail] - (list#= (enum.range n.enum (++ offset) (n.+ size offset)) - (/.first size (/.tail (..iterations ++ offset))))) - (_.cover [/.only] - (list#= (list#each (n.* 2) (enum.range n.enum 0 (-- size))) - (/.first size (/.only n.even? (..iterations ++ 0))))) - (_.cover [/.partition] - (let [[evens odds] (/.partition n.even? (..iterations ++ 0))] - (and (n.= (n.* 2 offset) - (/.item offset evens)) - (n.= (++ (n.* 2 offset)) - (/.item offset odds))))) - (_.cover [/.iterations] - (let [(open "/#[0]") /.functor - (open "list#[0]") (list.equivalence text.equivalence)] - (list#= (/.first size - (/#each %.nat (..iterations ++ offset))) - (/.first size - (/.iterations (function (_ n) [(++ n) (%.nat n)]) - offset))))) - (_.cover [/.cycle] - (let [cycle (partial_list cycle_start cycle_next)] - (list#= (list.together (list.repeated size cycle)) - (/.first (n.* size (list.size cycle)) - (/.cycle [cycle_start cycle_next]))))) - (_.cover [/.pattern] - (let [(/.pattern first second third next) (..iterations ++ offset)] - (and (n.= offset first) - (n.= (n.+ 1 offset) second) - (n.= (n.+ 2 offset) third)))) + (_.coverage [/.item] + (n.= (n.+ offset index) + (/.item index (..iterations ++ offset)))) + (_.coverage [/.repeated] + (n.= repeated + (/.item index (/.repeated repeated)))) + (_.coverage [/.first] + (list#= (enum.range n.enum offset (-- (n.+ size offset))) + (/.first size (..iterations ++ offset)))) + (_.coverage [/.after] + (list#= (enum.range n.enum offset (-- (n.+ size offset))) + (/.first size (/.after offset (..iterations ++ 0))))) + (_.coverage [/.split_at] + (let [[drops takes] (/.split_at size (..iterations ++ 0))] + (and (list#= (enum.range n.enum 0 (-- size)) + drops) + (list#= (enum.range n.enum size (-- (n.* 2 size))) + (/.first size takes))))) + (_.coverage [/.while] + (list#= (enum.range n.enum 0 (-- size)) + (/.while (n.< size) (..iterations ++ 0)))) + (_.coverage [/.until] + (list#= (enum.range n.enum offset (-- (n.+ size offset))) + (/.while (n.< (n.+ size offset)) + (/.until (n.< offset) (..iterations ++ 0))))) + (_.coverage [/.split_when] + (let [[drops takes] (/.split_when (n.= size) (..iterations ++ 0))] + (and (list#= (enum.range n.enum 0 (-- size)) + drops) + (list#= (enum.range n.enum size (-- (n.* 2 size))) + (/.while (n.< (n.* 2 size)) takes))))) + (_.coverage [/.head] + (n.= offset + (/.head (..iterations ++ offset)))) + (_.coverage [/.tail] + (list#= (enum.range n.enum (++ offset) (n.+ size offset)) + (/.first size (/.tail (..iterations ++ offset))))) + (_.coverage [/.only] + (list#= (list#each (n.* 2) (enum.range n.enum 0 (-- size))) + (/.first size (/.only n.even? (..iterations ++ 0))))) + (_.coverage [/.partition] + (let [[evens odds] (/.partition n.even? (..iterations ++ 0))] + (and (n.= (n.* 2 offset) + (/.item offset evens)) + (n.= (++ (n.* 2 offset)) + (/.item offset odds))))) + (_.coverage [/.iterations] + (let [(open "/#[0]") /.functor + (open "list#[0]") (list.equivalence text.equivalence)] + (list#= (/.first size + (/#each %.nat (..iterations ++ offset))) + (/.first size + (/.iterations (function (_ n) [(++ n) (%.nat n)]) + offset))))) + (_.coverage [/.cycle] + (let [cycle (partial_list cycle_start cycle_next)] + (list#= (list.together (list.repeated size cycle)) + (/.first (n.* size (list.size cycle)) + (/.cycle [cycle_start cycle_next]))))) + (_.coverage [/.pattern] + (let [(/.pattern first second third next) (..iterations ++ offset)] + (and (n.= offset first) + (n.= (n.+ 1 offset) second) + (n.= (n.+ 2 offset) third)))) )))) diff --git a/stdlib/source/test/lux/data/collection/tree.lux b/stdlib/source/test/lux/data/collection/tree.lux index b5dbfa7c4..0adcb50ba 100644 --- a/stdlib/source/test/lux/data/collection/tree.lux +++ b/stdlib/source/test/lux/data/collection/tree.lux @@ -47,23 +47,23 @@ (do random.monad [[size sample] (..tree random.nat)] - (_.cover [/.flat] - (n.= size - (list.size (/.flat sample))))) + (_.coverage [/.flat] + (n.= size + (list.size (/.flat sample))))) (do random.monad [expected random.nat] - (_.cover [/.leaf] - (# (list.equivalence n.equivalence) = - (list expected) - (/.flat (/.leaf expected))))) + (_.coverage [/.leaf] + (# (list.equivalence n.equivalence) = + (list expected) + (/.flat (/.leaf expected))))) (do [! random.monad] [value random.nat num_children (# ! each (n.% 3) random.nat) children (random.list num_children random.nat)] - (_.cover [/.branch] - (# (list.equivalence n.equivalence) = - (partial_list value children) - (/.flat (/.branch value (list#each /.leaf children)))))) + (_.coverage [/.branch] + (# (list.equivalence n.equivalence) = + (partial_list value children) + (/.flat (/.branch value (list#each /.leaf children)))))) (do random.monad [expected/0 random.nat expected/1 random.nat @@ -71,21 +71,21 @@ expected/3 random.nat expected/4 random.nat expected/5 random.nat] - (_.cover [/.tree] - (and (# (list.equivalence n.equivalence) = - (list expected/0) - (/.flat (/.tree expected/0))) - (# (list.equivalence n.equivalence) = - (list expected/0 expected/1 expected/2) - (/.flat (/.tree expected/0 - {expected/1 {} - expected/2 {}}))) - (# (list.equivalence n.equivalence) = - (list expected/0 expected/1 expected/2 - expected/3 expected/4 expected/5) - (/.flat (/.tree expected/0 - {expected/1 {} - expected/2 {expected/3 {} - expected/4 {expected/5 {}}}}))) - ))) + (_.coverage [/.tree] + (and (# (list.equivalence n.equivalence) = + (list expected/0) + (/.flat (/.tree expected/0))) + (# (list.equivalence n.equivalence) = + (list expected/0 expected/1 expected/2) + (/.flat (/.tree expected/0 + {expected/1 {} + expected/2 {}}))) + (# (list.equivalence n.equivalence) = + (list expected/0 expected/1 expected/2 + expected/3 expected/4 expected/5) + (/.flat (/.tree expected/0 + {expected/1 {} + expected/2 {expected/3 {} + expected/4 {expected/5 {}}}}))) + ))) ))) diff --git a/stdlib/source/test/lux/data/collection/tree/finger.lux b/stdlib/source/test/lux/data/collection/tree/finger.lux index 0a193f702..3fc005e70 100644 --- a/stdlib/source/test/lux/data/collection/tree/finger.lux +++ b/stdlib/source/test/lux/data/collection/tree/finger.lux @@ -39,45 +39,45 @@ expected_left random.nat expected_right random.nat] (all _.and - (_.cover [/.Builder /.builder] - (exec (/.builder text.monoid) - true)) - (_.cover [/.tag] - (and (text#= tag_left - (/.tag (# ..builder leaf tag_left expected_left))) - (text#= (text#composite tag_left tag_right) - (/.tag (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right)))))) - (_.cover [/.root] - (and (case (/.root (# ..builder leaf tag_left expected_left)) - {.#Left actual} - (n.= expected_left actual) - - {.#Right _} - false) - (case (/.root (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right))) - {.#Left _} - false - - {.#Right [left right]} - (case [(/.root left) - (/.root right)] - [{.#Left actual_left} {.#Left actual_right}] - (and (n.= expected_left actual_left) - (n.= expected_right actual_right)) - - _ - false)))) - (_.cover [/.value] - (and (n.= expected_left - (/.value (# ..builder leaf tag_left expected_left))) - (n.= expected_left - (/.value (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right)))))) + (_.coverage [/.Builder /.builder] + (exec (/.builder text.monoid) + true)) + (_.coverage [/.tag] + (and (text#= tag_left + (/.tag (# ..builder leaf tag_left expected_left))) + (text#= (text#composite tag_left tag_right) + (/.tag (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right)))))) + (_.coverage [/.root] + (and (case (/.root (# ..builder leaf tag_left expected_left)) + {.#Left actual} + (n.= expected_left actual) + + {.#Right _} + false) + (case (/.root (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right))) + {.#Left _} + false + + {.#Right [left right]} + (case [(/.root left) + (/.root right)] + [{.#Left actual_left} {.#Left actual_right}] + (and (n.= expected_left actual_left) + (n.= expected_right actual_right)) + + _ + false)))) + (_.coverage [/.value] + (and (n.= expected_left + (/.value (# ..builder leaf tag_left expected_left))) + (n.= expected_left + (/.value (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right)))))) (do random.monad [.let [tags_equivalence (list.equivalence text.equivalence) values_equivalence (list.equivalence n.equivalence)] @@ -85,68 +85,68 @@ tags/T (random.list 5 (random.alpha_numeric 1)) values/H random.nat values/T (random.list 5 random.nat)] - (_.cover [/.tags /.values] - (let [tree (list#mix (function (_ [tag value] tree) - (# builder branch tree (# builder leaf tag value))) - (# builder leaf tags/H values/H) - (list.zipped_2 tags/T values/T))] - (and (# tags_equivalence = (partial_list tags/H tags/T) (/.tags tree)) - (# values_equivalence = (partial_list values/H values/T) (/.values tree)))))) - (_.cover [/.one] - (let [can_find_correct_one! - (|> (# ..builder leaf tag_left expected_left) - (/.one (text.contains? tag_left)) - (maybe#each (n.= expected_left)) - (maybe.else false)) + (_.coverage [/.tags /.values] + (let [tree (list#mix (function (_ [tag value] tree) + (# builder branch tree (# builder leaf tag value))) + (# builder leaf tags/H values/H) + (list.zipped_2 tags/T values/T))] + (and (# tags_equivalence = (partial_list tags/H tags/T) (/.tags tree)) + (# values_equivalence = (partial_list values/H values/T) (/.values tree)))))) + (_.coverage [/.one] + (let [can_find_correct_one! + (|> (# ..builder leaf tag_left expected_left) + (/.one (text.contains? tag_left)) + (maybe#each (n.= expected_left)) + (maybe.else false)) - cannot_find_incorrect_one! - (|> (# ..builder leaf tag_right expected_right) - (/.one (text.contains? tag_left)) - (maybe#each (n.= expected_left)) - (maybe.else false) - not) + cannot_find_incorrect_one! + (|> (# ..builder leaf tag_right expected_right) + (/.one (text.contains? tag_left)) + (maybe#each (n.= expected_left)) + (maybe.else false) + not) - can_find_left! - (|> (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right)) - (/.one (text.contains? tag_left)) - (maybe#each (n.= expected_left)) - (maybe.else false)) + can_find_left! + (|> (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right)) + (/.one (text.contains? tag_left)) + (maybe#each (n.= expected_left)) + (maybe.else false)) - can_find_right! - (|> (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right)) - (/.one (text.contains? tag_right)) - (maybe#each (n.= expected_right)) - (maybe.else false))] - (and can_find_correct_one! - cannot_find_incorrect_one! - can_find_left! - can_find_right!))) - (_.cover [/.exists?] - (let [can_find_correct_one! - (/.exists? (text.contains? tag_left) - (# ..builder leaf tag_left expected_left)) + can_find_right! + (|> (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right)) + (/.one (text.contains? tag_right)) + (maybe#each (n.= expected_right)) + (maybe.else false))] + (and can_find_correct_one! + cannot_find_incorrect_one! + can_find_left! + can_find_right!))) + (_.coverage [/.exists?] + (let [can_find_correct_one! + (/.exists? (text.contains? tag_left) + (# ..builder leaf tag_left expected_left)) - cannot_find_incorrect_one! - (not (/.exists? (text.contains? tag_left) - (# ..builder leaf tag_right expected_right))) + cannot_find_incorrect_one! + (not (/.exists? (text.contains? tag_left) + (# ..builder leaf tag_right expected_right))) - can_find_left! - (/.exists? (text.contains? tag_left) - (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right))) + can_find_left! + (/.exists? (text.contains? tag_left) + (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right))) - can_find_right! - (/.exists? (text.contains? tag_right) - (# ..builder branch - (# ..builder leaf tag_left expected_left) - (# ..builder leaf tag_right expected_right)))] - (and can_find_correct_one! - cannot_find_incorrect_one! - can_find_left! - can_find_right!))) + can_find_right! + (/.exists? (text.contains? tag_right) + (# ..builder branch + (# ..builder leaf tag_left expected_left) + (# ..builder leaf tag_right expected_right)))] + (and can_find_correct_one! + cannot_find_incorrect_one! + can_find_left! + can_find_right!))) )))) diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 3a74a5030..b6b9a965f 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -31,124 +31,124 @@ [expected random.nat dummy (random.only (|>> (n.= expected) not) random.nat)] (all _.and - (_.cover [/.down] - (|> (tree.branch dummy (list (tree.leaf expected))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.up] - (|> (tree.branch expected (list (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.up] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.right] - (|> (tree.branch dummy (list (tree.leaf dummy) (tree.leaf expected))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.right] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.rightmost] - (|> (tree.branch dummy - (list (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf expected))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.rightmost] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.left] - (|> (tree.branch dummy (list (tree.leaf expected) (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.right] - [/.left] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.leftmost] - (|> (tree.branch dummy - (list (tree.leaf expected) - (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.down] - [/.rightmost] - [/.leftmost] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.next] - (and (|> (tree.branch dummy - (list (tree.leaf expected) - (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.next] - [/.value (n.= expected) in]) - (maybe.else false)) - (|> (tree.branch dummy - (list (tree.leaf dummy) - (tree.leaf expected))) - /.zipper - (pipe.do maybe.monad - [/.next] - [/.next] - [/.value (n.= expected) in]) - (maybe.else false)))) - (_.cover [/.end] - (|> (tree.branch dummy - (list (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf expected))) - /.zipper - (pipe.do maybe.monad - [/.end] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.start] - (|> (tree.branch expected - (list (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf dummy) - (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.end] - [/.start] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.previous] - (and (|> (tree.branch expected - (list (tree.leaf dummy) - (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.next] - [/.previous] - [/.value (n.= expected) in]) - (maybe.else false)) - (|> (tree.branch dummy - (list (tree.leaf expected) - (tree.leaf dummy))) - /.zipper - (pipe.do maybe.monad - [/.next] - [/.next] - [/.previous] - [/.value (n.= expected) in]) - (maybe.else false)))) + (_.coverage [/.down] + (|> (tree.branch dummy (list (tree.leaf expected))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.up] + (|> (tree.branch expected (list (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.up] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.right] + (|> (tree.branch dummy (list (tree.leaf dummy) (tree.leaf expected))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.right] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.rightmost] + (|> (tree.branch dummy + (list (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf expected))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.rightmost] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.left] + (|> (tree.branch dummy (list (tree.leaf expected) (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.right] + [/.left] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.leftmost] + (|> (tree.branch dummy + (list (tree.leaf expected) + (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [/.rightmost] + [/.leftmost] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.next] + (and (|> (tree.branch dummy + (list (tree.leaf expected) + (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.next] + [/.value (n.= expected) in]) + (maybe.else false)) + (|> (tree.branch dummy + (list (tree.leaf dummy) + (tree.leaf expected))) + /.zipper + (pipe.do maybe.monad + [/.next] + [/.next] + [/.value (n.= expected) in]) + (maybe.else false)))) + (_.coverage [/.end] + (|> (tree.branch dummy + (list (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf expected))) + /.zipper + (pipe.do maybe.monad + [/.end] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.start] + (|> (tree.branch expected + (list (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf dummy) + (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.end] + [/.start] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.previous] + (and (|> (tree.branch expected + (list (tree.leaf dummy) + (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.next] + [/.previous] + [/.value (n.= expected) in]) + (maybe.else false)) + (|> (tree.branch dummy + (list (tree.leaf expected) + (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.next] + [/.next] + [/.previous] + [/.value (n.= expected) in]) + (maybe.else false)))) ))) (def: .public test @@ -169,93 +169,93 @@ (_.for [/.comonad] ($comonad.spec (|>> tree.leaf /.zipper) /.equivalence /.comonad)) - (_.cover [/.zipper /.tree] - (|> sample /.zipper /.tree (tree#= sample))) - (_.cover [/.start?] - (|> sample /.zipper /.start?)) - (_.cover [/.leaf?] - (/.leaf? (/.zipper (tree.leaf expected)))) - (_.cover [/.branch?] - (and (/.branch? (/.zipper (tree.branch expected (list (tree.leaf expected))))) - (not (/.branch? (/.zipper (tree.branch expected (list))))))) - (_.cover [/.value] - (and (n.= expected (/.value (/.zipper (tree.leaf expected)))) - (n.= expected (/.value (/.zipper (tree.branch expected (list (tree.leaf expected)))))))) - (_.cover [/.set] - (|> (/.zipper (tree.leaf dummy)) - (/.set expected) - /.value - (n.= expected))) - (_.cover [/.update] - (|> (/.zipper (tree.leaf expected)) - (/.update ++) - /.value - (n.= (++ expected)))) + (_.coverage [/.zipper /.tree] + (|> sample /.zipper /.tree (tree#= sample))) + (_.coverage [/.start?] + (|> sample /.zipper /.start?)) + (_.coverage [/.leaf?] + (/.leaf? (/.zipper (tree.leaf expected)))) + (_.coverage [/.branch?] + (and (/.branch? (/.zipper (tree.branch expected (list (tree.leaf expected))))) + (not (/.branch? (/.zipper (tree.branch expected (list))))))) + (_.coverage [/.value] + (and (n.= expected (/.value (/.zipper (tree.leaf expected)))) + (n.= expected (/.value (/.zipper (tree.branch expected (list (tree.leaf expected)))))))) + (_.coverage [/.set] + (|> (/.zipper (tree.leaf dummy)) + (/.set expected) + /.value + (n.= expected))) + (_.coverage [/.update] + (|> (/.zipper (tree.leaf expected)) + (/.update ++) + /.value + (n.= (++ expected)))) ..move - (_.cover [/.end?] - (or (/.end? (/.zipper sample)) - (|> sample - /.zipper - /.end - (maybe#each /.end?) - (maybe.else false)))) - (_.cover [/.interpose] - (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zipper - (/.interpose expected))] - (and (n.= dummy (/.value cursor)) - (|> cursor - (pipe.do maybe.monad - [/.down] - [/.value (n.= expected) in]) - (maybe.else false)) - (|> cursor - (pipe.do maybe.monad - [/.down] - [/.down] - [/.value (n.= dummy) in]) - (maybe.else false))))) - (_.cover [/.adopt] - (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zipper - (/.adopt expected))] - (and (n.= dummy (/.value cursor)) - (|> cursor - (pipe.do maybe.monad - [/.down] - [/.value (n.= expected) in]) - (maybe.else false)) - (|> cursor - (pipe.do maybe.monad - [/.down] - [/.right] - [/.value (n.= dummy) in]) - (maybe.else false))))) - (_.cover [/.insert_left] - (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zipper + (_.coverage [/.end?] + (or (/.end? (/.zipper sample)) + (|> sample + /.zipper + /.end + (maybe#each /.end?) + (maybe.else false)))) + (_.coverage [/.interpose] + (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) + /.zipper + (/.interpose expected))] + (and (n.= dummy (/.value cursor)) + (|> cursor (pipe.do maybe.monad [/.down] - [(/.insert_left expected)] - [/.left] [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.insert_right] - (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zipper + (maybe.else false)) + (|> cursor (pipe.do maybe.monad [/.down] - [(/.insert_right expected)] - [/.right] - [/.value (n.= expected) in]) - (maybe.else false))) - (_.cover [/.remove] - (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zipper + [/.down] + [/.value (n.= dummy) in]) + (maybe.else false))))) + (_.coverage [/.adopt] + (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) + /.zipper + (/.adopt expected))] + (and (n.= dummy (/.value cursor)) + (|> cursor (pipe.do maybe.monad [/.down] - [(/.insert_left expected)] - [/.remove] [/.value (n.= expected) in]) - (maybe.else false))) + (maybe.else false)) + (|> cursor + (pipe.do maybe.monad + [/.down] + [/.right] + [/.value (n.= dummy) in]) + (maybe.else false))))) + (_.coverage [/.insert_left] + (|> (tree.branch dummy (list (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [(/.insert_left expected)] + [/.left] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.insert_right] + (|> (tree.branch dummy (list (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [(/.insert_right expected)] + [/.right] + [/.value (n.= expected) in]) + (maybe.else false))) + (_.coverage [/.remove] + (|> (tree.branch dummy (list (tree.leaf dummy))) + /.zipper + (pipe.do maybe.monad + [/.down] + [(/.insert_left expected)] + [/.remove] + [/.value (n.= expected) in]) + (maybe.else false))) )))) diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux index 14c22b77c..de615faaf 100644 --- a/stdlib/source/test/lux/data/color.lux +++ b/stdlib/source/test/lux/data/color.lux @@ -69,21 +69,21 @@ (def: (encoding expected) (-> /.Color Test) (all _.and - (_.cover [/.RGB /.rgb /.of_rgb] - (|> expected /.rgb /.of_rgb - (# /.equivalence = expected))) - (_.cover [/.HSL /.hsl /.of_hsl] - (|> expected /.hsl /.of_hsl - (distance/3 expected) - (f.<= ..rgb_error_margin))) - (_.cover [/.HSB /.hsb /.of_hsb] - (|> expected /.hsb /.of_hsb - (distance/3 expected) - (f.<= ..rgb_error_margin))) - (_.cover [/.CMYK /.cmyk /.of_cmyk] - (|> expected /.cmyk /.of_cmyk - (distance/3 expected) - (f.<= ..rgb_error_margin))) + (_.coverage [/.RGB /.rgb /.of_rgb] + (|> expected /.rgb /.of_rgb + (# /.equivalence = expected))) + (_.coverage [/.HSL /.hsl /.of_hsl] + (|> expected /.hsl /.of_hsl + (distance/3 expected) + (f.<= ..rgb_error_margin))) + (_.coverage [/.HSB /.hsb /.of_hsb] + (|> expected /.hsb /.of_hsb + (distance/3 expected) + (f.<= ..rgb_error_margin))) + (_.coverage [/.CMYK /.cmyk /.of_cmyk] + (|> expected /.cmyk /.of_cmyk + (distance/3 expected) + (f.<= ..rgb_error_margin))) )) (def: transformation @@ -99,30 +99,30 @@ (f.<= +0.75 saturation))))))) ratio (|> random.safe_frac (random.only (f.>= +0.5)))] (all _.and - (_.cover [/.darker /.brighter] - (and (f.<= (distance/3 colorful /.black) - (distance/3 (/.darker ratio colorful) /.black)) - (f.<= (distance/3 colorful /.white) - (distance/3 (/.brighter ratio colorful) /.white)))) - (_.cover [/.interpolated] - (and (f.<= (distance/3 colorful /.black) - (distance/3 (/.interpolated ratio /.black colorful) /.black)) - (f.<= (distance/3 colorful /.white) - (distance/3 (/.interpolated ratio /.white colorful) /.white)))) - (_.cover [/.saturated] - (f.> (saturation mediocre) - (saturation (/.saturated ratio mediocre)))) - (_.cover [/.un_saturated] - (f.< (saturation mediocre) - (saturation (/.un_saturated ratio mediocre)))) - (_.cover [/.gray_scale] - (let [gray'ed (/.gray_scale mediocre)] - (and (f.= +0.0 - (saturation gray'ed)) - (|> (luminance gray'ed) - (f.- (luminance mediocre)) - f.abs - (f.<= ..rgb_error_margin))))) + (_.coverage [/.darker /.brighter] + (and (f.<= (distance/3 colorful /.black) + (distance/3 (/.darker ratio colorful) /.black)) + (f.<= (distance/3 colorful /.white) + (distance/3 (/.brighter ratio colorful) /.white)))) + (_.coverage [/.interpolated] + (and (f.<= (distance/3 colorful /.black) + (distance/3 (/.interpolated ratio /.black colorful) /.black)) + (f.<= (distance/3 colorful /.white) + (distance/3 (/.interpolated ratio /.white colorful) /.white)))) + (_.coverage [/.saturated] + (f.> (saturation mediocre) + (saturation (/.saturated ratio mediocre)))) + (_.coverage [/.un_saturated] + (f.< (saturation mediocre) + (saturation (/.un_saturated ratio mediocre)))) + (_.coverage [/.gray_scale] + (let [gray'ed (/.gray_scale mediocre)] + (and (f.= +0.0 + (saturation gray'ed)) + (|> (luminance gray'ed) + (f.- (luminance mediocre)) + f.abs + (f.<= ..rgb_error_margin))))) ))) (def: palette @@ -141,34 +141,34 @@ random.safe_frac)] (`` (all _.and (~~ (template [<brightness> <palette>] - [(_.cover [<palette>] - (let [eB <brightness> - expected (/.of_hsb [eH eS eB]) - palette (<palette> spread variations expected)] - (and (n.= variations (list.size palette)) - (not (list.any? (# /.equivalence = expected) palette)))))] + [(_.coverage [<palette>] + (let [eB <brightness> + expected (/.of_hsb [eH eS eB]) + palette (<palette> spread variations expected)] + (and (n.= variations (list.size palette)) + (not (list.any? (# /.equivalence = expected) palette)))))] [+1.0 /.analogous] [+0.5 /.monochromatic] )) (~~ (template [<palette>] - [(_.cover [<palette>] - (let [expected (/.of_hsb [eH eS +0.5]) - [c0 c1 c2] (<palette> expected)] - (and (# /.equivalence = expected c0) - (not (# /.equivalence = expected c1)) - (not (# /.equivalence = expected c2)))))] + [(_.coverage [<palette>] + (let [expected (/.of_hsb [eH eS +0.5]) + [c0 c1 c2] (<palette> expected)] + (and (# /.equivalence = expected c0) + (not (# /.equivalence = expected c1)) + (not (# /.equivalence = expected c2)))))] [/.triad] [/.clash] [/.split_complement])) (~~ (template [<palette>] - [(_.cover [<palette>] - (let [expected (/.of_hsb [eH eS +0.5]) - [c0 c1 c2 c3] (<palette> expected)] - (and (# /.equivalence = expected c0) - (not (# /.equivalence = expected c1)) - (not (# /.equivalence = expected c2)) - (not (# /.equivalence = expected c3)))))] + [(_.coverage [<palette>] + (let [expected (/.of_hsb [eH eS +0.5]) + [c0 c1 c2 c3] (<palette> expected)] + (and (# /.equivalence = expected c0) + (not (# /.equivalence = expected c1)) + (not (# /.equivalence = expected c2)) + (not (# /.equivalence = expected c3)))))] [/.square] [/.tetradic])) @@ -191,22 +191,22 @@ ($monoid.spec /.equivalence /.addition ..random)) (..encoding expected) - (_.cover [/.complement] - (let [~expected (/.complement expected) - (open "/#[0]") /.equivalence] - (and (not (/#= expected ~expected)) - (/#= expected (/.complement ~expected))))) - (_.cover [/.black /.white] - (and (# /.equivalence = /.white (/.complement /.black)) - (# /.equivalence = /.black (/.complement /.white)))) + (_.coverage [/.complement] + (let [~expected (/.complement expected) + (open "/#[0]") /.equivalence] + (and (not (/#= expected ~expected)) + (/#= expected (/.complement ~expected))))) + (_.coverage [/.black /.white] + (and (# /.equivalence = /.white (/.complement /.black)) + (# /.equivalence = /.black (/.complement /.white)))) ..transformation ..palette (_.for [/.Alpha /.Pigment] (all _.and - (_.cover [/.transparent /.opaque] - (and (r.= /.opaque (-- /.transparent)) - (r.= /.transparent (++ /.opaque)))) - (_.cover [/.translucent] - (r.= /.transparent (r.+ /.translucent /.translucent))) + (_.coverage [/.transparent /.opaque] + (and (r.= /.opaque (-- /.transparent)) + (r.= /.transparent (++ /.opaque)))) + (_.coverage [/.translucent] + (r.= /.transparent (r.+ /.translucent /.translucent))) )) )))) diff --git a/stdlib/source/test/lux/data/color/named.lux b/stdlib/source/test/lux/data/color/named.lux index ce4f22fc3..70663ba7c 100644 --- a/stdlib/source/test/lux/data/color/named.lux +++ b/stdlib/source/test/lux/data/color/named.lux @@ -219,8 +219,8 @@ (template [<definition> <by_letter>] [(def: <definition> Test - (_.cover <by_letter> - ..verdict))] + (_.coverage <by_letter> + ..verdict))] <colors>) @@ -232,9 +232,9 @@ [<definition>] <colors>)) - (_.cover [/.aqua] - (# //.equivalence = /.cyan /.aqua)) - (_.cover [/.fuchsia] - (# //.equivalence = /.magenta /.fuchsia)) + (_.coverage [/.aqua] + (# //.equivalence = /.cyan /.aqua)) + (_.coverage [/.fuchsia] + (# //.equivalence = /.magenta /.fuchsia)) )))) ) diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux index 84f31a550..63bbcab87 100644 --- a/stdlib/source/test/lux/data/format/json.lux +++ b/stdlib/source/test/lux/data/format/json.lux @@ -73,20 +73,20 @@ (do random.monad [sample ..random] - (_.cover [/.Null /.null?] - (# bit.equivalence = - (/.null? sample) - (case sample - {/.#Null} true - _ false)))) + (_.coverage [/.Null /.null?] + (# bit.equivalence = + (/.null? sample) + (case sample + {/.#Null} true + _ false)))) (do random.monad [expected ..random] - (_.cover [/.format] - (|> expected - /.format - (# /.codec decoded) - (try#each (#= expected)) - (try.else false)))) + (_.coverage [/.format] + (|> expected + /.format + (# /.codec decoded) + (try#each (#= expected)) + (try.else false)))) (do random.monad [keys (random.set text.hash 3 (random.alphabetic 1)) values (random.set frac.hash 3 random.safe_frac) @@ -94,55 +94,55 @@ (list#each (|>> {/.#Number}) (set.list values))) object (/.object expected)]] (all _.and - (_.cover [/.object /.fields] - (case (/.fields object) - {try.#Success actual} - (# (list.equivalence text.equivalence) = - (list#each product.left expected) - actual) - - {try.#Failure error} - false)) - (_.cover [/.field] - (list.every? (function (_ [key expected]) - (|> (/.field key object) - (try#each (#= expected)) - (try.else false))) - expected)) + (_.coverage [/.object /.fields] + (case (/.fields object) + {try.#Success actual} + (# (list.equivalence text.equivalence) = + (list#each product.left expected) + actual) + + {try.#Failure error} + false)) + (_.coverage [/.field] + (list.every? (function (_ [key expected]) + (|> (/.field key object) + (try#each (#= expected)) + (try.else false))) + expected)) )) (do random.monad [key (random.alphabetic 1) unknown (random.only (|>> (# text.equivalence = key) not) (random.alphabetic 1)) expected random.safe_frac] - (_.cover [/.has] - (<| (try.else false) - (do try.monad - [object (/.has key {/.#Number expected} (/.object (list))) - .let [can_find_known_key! - (|> object - (/.field key) - (try#each (#= {/.#Number expected})) - (try.else false)) + (_.coverage [/.has] + (<| (try.else false) + (do try.monad + [object (/.has key {/.#Number expected} (/.object (list))) + .let [can_find_known_key! + (|> object + (/.field key) + (try#each (#= {/.#Number expected})) + (try.else false)) - cannot_find_unknown_key! - (case (/.field unknown object) - {try.#Success _} - false + cannot_find_unknown_key! + (case (/.field unknown object) + {try.#Success _} + false - {try.#Failure error} - true)]] - (in (and can_find_known_key! - cannot_find_unknown_key!)))))) + {try.#Failure error} + true)]] + (in (and can_find_known_key! + cannot_find_unknown_key!)))))) (~~ (template [<type> <field> <tag> <random> <equivalence>] [(do random.monad [key (random.alphabetic 1) value <random>] - (_.cover [<type> <field>] - (|> (/.object (list [key {<tag> value}])) - (<field> key) - (try#each (# <equivalence> = value)) - (try.else false))))] + (_.coverage [<type> <field>] + (|> (/.object (list [key {<tag> value}])) + (<field> key) + (try#each (# <equivalence> = value)) + (try.else false))))] [/.Boolean /.boolean_field /.#Boolean random.bit bit.equivalence] [/.Number /.number_field /.#Number random.safe_frac frac.equivalence] @@ -164,36 +164,36 @@ <key4> (string) <key5> (string) <key6> (string)] - (_.cover [/.json] - (and (#= {/.#Null} (/.json ())) - (~~ (template [<tag> <value>] - [(#= {<tag> <value>} (/.json <value>))] - - [/.#Boolean <boolean>] - [/.#Number <number>] - [/.#String <string>] - )) - (#= {/.#Array <array_sequence>} (/.json [() <boolean> <number> <string>])) - (let [object (/.json {<key0> () - <key1> <boolean> - <key2> <number> - <key3> <string> - <key4> [() <boolean> <number> <string>] - <key5> {<key6> <number>}})] - (<| (try.else false) - (do try.monad - [value0 (/.field <key0> object) - value1 (/.field <key1> object) - value2 (/.field <key2> object) - value3 (/.field <key3> object) - value4 (/.field <key4> object) - value5 (/.field <key5> object) - value6 (/.field <key6> value5)] - (in (and (#= {/.#Null} value0) - (#= {/.#Boolean <boolean>} value1) - (#= {/.#Number <number>} value2) - (#= {/.#String <string>} value3) - (#= {/.#Array <array_sequence>} value4) - (#= {/.#Number <number>} value6)))))) - ))) + (_.coverage [/.json] + (and (#= {/.#Null} (/.json ())) + (~~ (template [<tag> <value>] + [(#= {<tag> <value>} (/.json <value>))] + + [/.#Boolean <boolean>] + [/.#Number <number>] + [/.#String <string>] + )) + (#= {/.#Array <array_sequence>} (/.json [() <boolean> <number> <string>])) + (let [object (/.json {<key0> () + <key1> <boolean> + <key2> <number> + <key3> <string> + <key4> [() <boolean> <number> <string>] + <key5> {<key6> <number>}})] + (<| (try.else false) + (do try.monad + [value0 (/.field <key0> object) + value1 (/.field <key1> object) + value2 (/.field <key2> object) + value3 (/.field <key3> object) + value4 (/.field <key4> object) + value5 (/.field <key5> object) + value6 (/.field <key6> value5)] + (in (and (#= {/.#Null} value0) + (#= {/.#Boolean <boolean>} value1) + (#= {/.#Number <number>} value2) + (#= {/.#String <string>} value3) + (#= {/.#Array <array_sequence>} value4) + (#= {/.#Number <number>} value6)))))) + ))) )))) diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux index a62ce9de4..b4c57411f 100644 --- a/stdlib/source/test/lux/data/format/tar.lux +++ b/stdlib/source/test/lux/data/format/tar.lux @@ -45,30 +45,30 @@ not_ascii (random.text (random.char (unicode.set [unicode/block.katakana (list)])) /.path_size)] (`` (all _.and - (_.cover [/.path /.from_path] - (case (/.path expected) - {try.#Success actual} - (text#= expected - (/.from_path actual)) - - {try.#Failure error} - false)) - (_.cover [/.no_path] - (text#= "" (/.from_path /.no_path))) - (_.cover [/.path_size /.path_is_too_long] - (case (/.path invalid) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.path_is_too_long error))) - (_.cover [/.not_ascii] - (case (/.path not_ascii) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.not_ascii error))) + (_.coverage [/.path /.from_path] + (case (/.path expected) + {try.#Success actual} + (text#= expected + (/.from_path actual)) + + {try.#Failure error} + false)) + (_.coverage [/.no_path] + (text#= "" (/.from_path /.no_path))) + (_.coverage [/.path_size /.path_is_too_long] + (case (/.path invalid) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.path_is_too_long error))) + (_.coverage [/.not_ascii] + (case (/.path not_ascii) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.not_ascii error))) ))))) (def: name @@ -80,28 +80,28 @@ not_ascii (random.text (random.char (unicode.set [unicode/block.katakana (list)])) /.name_size)] (`` (all _.and - (_.cover [/.name /.from_name] - (case (/.name expected) - {try.#Success actual} - (text#= expected - (/.from_name actual)) - - {try.#Failure error} - false)) - (_.cover [/.name_size /.name_is_too_long] - (case (/.name invalid) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.name_is_too_long error))) - (_.cover [/.not_ascii] - (case (/.name not_ascii) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.not_ascii error))) + (_.coverage [/.name /.from_name] + (case (/.name expected) + {try.#Success actual} + (text#= expected + (/.from_name actual)) + + {try.#Failure error} + false)) + (_.coverage [/.name_size /.name_is_too_long] + (case (/.name invalid) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.name_is_too_long error))) + (_.coverage [/.not_ascii] + (case (/.name not_ascii) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.not_ascii error))) ))))) (def: small @@ -111,21 +111,21 @@ [expected (|> random.nat (# ! each (n.% /.small_limit))) invalid (|> random.nat (# ! each (n.max /.small_limit)))] (`` (all _.and - (_.cover [/.small /.from_small] - (case (/.small expected) - {try.#Success actual} - (n.= expected - (/.from_small actual)) - - {try.#Failure error} - false)) - (_.cover [/.small_limit /.not_a_small_number] - (case (/.small invalid) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.not_a_small_number error))) + (_.coverage [/.small /.from_small] + (case (/.small expected) + {try.#Success actual} + (n.= expected + (/.from_small actual)) + + {try.#Failure error} + false)) + (_.coverage [/.small_limit /.not_a_small_number] + (case (/.small invalid) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.not_a_small_number error))) ))))) (def: big @@ -135,21 +135,21 @@ [expected (|> random.nat (# ! each (n.% /.big_limit))) invalid (|> random.nat (# ! each (n.max /.big_limit)))] (`` (all _.and - (_.cover [/.big /.from_big] - (case (/.big expected) - {try.#Success actual} - (n.= expected - (/.from_big actual)) - - {try.#Failure error} - false)) - (_.cover [/.big_limit /.not_a_big_number] - (case (/.big invalid) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.not_a_big_number error))) + (_.coverage [/.big /.from_big] + (case (/.big expected) + {try.#Success actual} + (n.= expected + (/.from_big actual)) + + {try.#Failure error} + false)) + (_.coverage [/.big_limit /.not_a_big_number] + (case (/.big invalid) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.not_a_big_number error))) ))))) (def: chunk_size 32) @@ -168,20 +168,20 @@ (# utf8.codec encoded))]] (`` (all _.and (~~ (template [<type> <tag>] - [(_.cover [<type>] - (|> (do try.monad - [expected_path (/.path expected_path) - tar (|> (sequence.sequence {<tag> expected_path}) - (format.result /.writer) - (<b>.result /.parser))] - (in (case (sequence.list tar) - (pattern (list {<tag> actual_path})) - (text#= (/.from_path expected_path) - (/.from_path actual_path)) - - _ - false))) - (try.else false)))] + [(_.coverage [<type>] + (|> (do try.monad + [expected_path (/.path expected_path) + tar (|> (sequence.sequence {<tag> expected_path}) + (format.result /.writer) + (<b>.result /.parser))] + (in (case (sequence.list tar) + (pattern (list {<tag> actual_path})) + (text#= (/.from_path expected_path) + (/.from_path actual_path)) + + _ + false))) + (try.else false)))] [/.Symbolic_Link /.#Symbolic_Link] [/.Directory /.#Directory] @@ -189,34 +189,34 @@ (_.for [/.File /.Content /.content /.data] (all _.and (~~ (template [<type> <tag>] - [(_.cover [<type>] - (|> (do try.monad - [expected_path (/.path expected_path) - expected_content (/.content content) - tar (|> (sequence.sequence {<tag> [expected_path - expected_moment - /.none - [/.#user [/.#name /.anonymous - /.#id /.no_id] - /.#group [/.#name /.anonymous - /.#id /.no_id]] - expected_content]}) - (format.result /.writer) - (<b>.result /.parser))] - (in (case (sequence.list tar) - (pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) - (let [seconds (is (-> Instant Int) - (|>> instant.relative (duration.ticks duration.second)))] - (and (text#= (/.from_path expected_path) - (/.from_path actual_path)) - (i.= (seconds expected_moment) - (seconds actual_moment)) - (binary#= (/.data expected_content) - (/.data actual_content)))) - - _ - false))) - (try.else false)))] + [(_.coverage [<type>] + (|> (do try.monad + [expected_path (/.path expected_path) + expected_content (/.content content) + tar (|> (sequence.sequence {<tag> [expected_path + expected_moment + /.none + [/.#user [/.#name /.anonymous + /.#id /.no_id] + /.#group [/.#name /.anonymous + /.#id /.no_id]] + expected_content]}) + (format.result /.writer) + (<b>.result /.parser))] + (in (case (sequence.list tar) + (pattern (list {<tag> [actual_path actual_moment actual_mode actual_ownership actual_content]})) + (let [seconds (is (-> Instant Int) + (|>> instant.relative (duration.ticks duration.second)))] + (and (text#= (/.from_path expected_path) + (/.from_path actual_path)) + (i.= (seconds expected_moment) + (seconds actual_moment)) + (binary#= (/.data expected_content) + (/.data actual_content)))) + + _ + false))) + (try.else false)))] [/.Normal /.#Normal] [/.Contiguous /.#Contiguous] @@ -247,13 +247,36 @@ modes (random.list 4 ..random_mode) .let [expected_mode (list#mix /.and /.none modes)]] (`` (all _.and - (_.cover [/.and] + (_.coverage [/.and] + (|> (do try.monad + [path (/.path path) + content (/.content (binary.empty 0)) + tar (|> (sequence.sequence {/.#Normal [path + (instant.of_millis +0) + expected_mode + [/.#user [/.#name /.anonymous + /.#id /.no_id] + /.#group [/.#name /.anonymous + /.#id /.no_id]] + content]}) + (format.result /.writer) + (<b>.result /.parser))] + (in (case (sequence.list tar) + (pattern (list {/.#Normal [_ _ actual_mode _ _]})) + (n.= (/.mode expected_mode) + (/.mode actual_mode)) + + _ + false))) + (try.else false))) + (~~ (template [<expected_mode>] + [(_.coverage [<expected_mode>] (|> (do try.monad [path (/.path path) content (/.content (binary.empty 0)) tar (|> (sequence.sequence {/.#Normal [path (instant.of_millis +0) - expected_mode + <expected_mode> [/.#user [/.#name /.anonymous /.#id /.no_id] /.#group [/.#name /.anonymous @@ -263,35 +286,12 @@ (<b>.result /.parser))] (in (case (sequence.list tar) (pattern (list {/.#Normal [_ _ actual_mode _ _]})) - (n.= (/.mode expected_mode) + (n.= (/.mode <expected_mode>) (/.mode actual_mode)) _ false))) - (try.else false))) - (~~ (template [<expected_mode>] - [(_.cover [<expected_mode>] - (|> (do try.monad - [path (/.path path) - content (/.content (binary.empty 0)) - tar (|> (sequence.sequence {/.#Normal [path - (instant.of_millis +0) - <expected_mode> - [/.#user [/.#name /.anonymous - /.#id /.no_id] - /.#group [/.#name /.anonymous - /.#id /.no_id]] - content]}) - (format.result /.writer) - (<b>.result /.parser))] - (in (case (sequence.list tar) - (pattern (list {/.#Normal [_ _ actual_mode _ _]})) - (n.= (/.mode <expected_mode>) - (/.mode actual_mode)) - - _ - false))) - (try.else false)))] + (try.else false)))] [/.none] @@ -322,73 +322,73 @@ /.name_size)] (_.for [/.Ownership /.Owner /.ID] (all _.and - (_.cover [/.name_size /.name_is_too_long] - (case (/.name invalid) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.name_is_too_long error))) - (_.cover [/.not_ascii] - (case (/.name not_ascii) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.not_ascii error))) - (_.cover [/.Name /.name /.from_name] - (|> (do try.monad - [path (/.path path) - content (/.content (binary.empty 0)) - expected (/.name expected) - tar (|> (sequence.sequence {/.#Normal [path - (instant.of_millis +0) - /.none - [/.#user [/.#name expected - /.#id /.no_id] - /.#group [/.#name /.anonymous - /.#id /.no_id]] - content]}) - (format.result /.writer) - (<b>.result /.parser))] - (in (case (sequence.list tar) - (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) - (and (text#= (/.from_name expected) - (/.from_name (the [/.#user /.#name] actual_ownership))) - (text#= (/.from_name /.anonymous) - (/.from_name (the [/.#group /.#name] actual_ownership)))) - - _ - false))) - (try.else false))) - (_.cover [/.anonymous /.no_id] - (|> (do try.monad - [path (/.path path) - content (/.content (binary.empty 0)) - tar (|> (sequence.sequence {/.#Normal [path - (instant.of_millis +0) - /.none - [/.#user [/.#name /.anonymous - /.#id /.no_id] - /.#group [/.#name /.anonymous - /.#id /.no_id]] - content]}) - (format.result /.writer) - (<b>.result /.parser))] - (in (case (sequence.list tar) - (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) - (and (text#= (/.from_name /.anonymous) - (/.from_name (the [/.#user /.#name] actual_ownership))) - (n.= (/.from_small /.no_id) - (/.from_small (the [/.#user /.#id] actual_ownership))) - (text#= (/.from_name /.anonymous) - (/.from_name (the [/.#group /.#name] actual_ownership))) - (n.= (/.from_small /.no_id) - (/.from_small (the [/.#group /.#id] actual_ownership)))) - - _ - false))) - (try.else false))) + (_.coverage [/.name_size /.name_is_too_long] + (case (/.name invalid) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.name_is_too_long error))) + (_.coverage [/.not_ascii] + (case (/.name not_ascii) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.not_ascii error))) + (_.coverage [/.Name /.name /.from_name] + (|> (do try.monad + [path (/.path path) + content (/.content (binary.empty 0)) + expected (/.name expected) + tar (|> (sequence.sequence {/.#Normal [path + (instant.of_millis +0) + /.none + [/.#user [/.#name expected + /.#id /.no_id] + /.#group [/.#name /.anonymous + /.#id /.no_id]] + content]}) + (format.result /.writer) + (<b>.result /.parser))] + (in (case (sequence.list tar) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) + (and (text#= (/.from_name expected) + (/.from_name (the [/.#user /.#name] actual_ownership))) + (text#= (/.from_name /.anonymous) + (/.from_name (the [/.#group /.#name] actual_ownership)))) + + _ + false))) + (try.else false))) + (_.coverage [/.anonymous /.no_id] + (|> (do try.monad + [path (/.path path) + content (/.content (binary.empty 0)) + tar (|> (sequence.sequence {/.#Normal [path + (instant.of_millis +0) + /.none + [/.#user [/.#name /.anonymous + /.#id /.no_id] + /.#group [/.#name /.anonymous + /.#id /.no_id]] + content]}) + (format.result /.writer) + (<b>.result /.parser))] + (in (case (sequence.list tar) + (pattern (list {/.#Normal [_ _ _ actual_ownership _]})) + (and (text#= (/.from_name /.anonymous) + (/.from_name (the [/.#user /.#name] actual_ownership))) + (n.= (/.from_small /.no_id) + (/.from_small (the [/.#user /.#id] actual_ownership))) + (text#= (/.from_name /.anonymous) + (/.from_name (the [/.#group /.#name] actual_ownership))) + (n.= (/.from_small /.no_id) + (/.from_small (the [/.#group /.#id] actual_ownership)))) + + _ + false))) + (try.else false))) )))) (def: .public test @@ -398,20 +398,20 @@ (do random.monad [_ (in [])] (all _.and - (_.cover [/.writer /.parser] - (|> sequence.empty - (format.result /.writer) - (<b>.result /.parser) - (# try.monad each sequence.empty?) - (try.else false))) - (_.cover [/.invalid_end_of_archive] - (let [dump (format.result /.writer sequence.empty)] - (case (<b>.result /.parser (binary#composite dump dump)) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.invalid_end_of_archive error)))) + (_.coverage [/.writer /.parser] + (|> sequence.empty + (format.result /.writer) + (<b>.result /.parser) + (# try.monad each sequence.empty?) + (try.else false))) + (_.coverage [/.invalid_end_of_archive] + (let [dump (format.result /.writer sequence.empty)] + (case (<b>.result /.parser (binary#composite dump dump)) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.invalid_end_of_archive error)))) ..path ..name diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux index b4c0e7276..0e45f5d72 100644 --- a/stdlib/source/test/lux/data/format/xml.lux +++ b/stdlib/source/test/lux/data/format/xml.lux @@ -82,16 +82,16 @@ [(^.let symbol [namespace name]) ..symbol] (`` (all _.and (~~ (template [<type> <format>] - [(_.cover [<type> <format>] - (and (text#= name (<format> ["" name])) - (let [symbol (<format> symbol)] - (and (text.starts_with? namespace symbol) - (text.ends_with? name symbol)))))] + [(_.coverage [<type> <format>] + (and (text#= name (<format> ["" name])) + (let [symbol (<format> symbol)] + (and (text.starts_with? namespace symbol) + (text.ends_with? name symbol)))))] [/.Tag /.tag] [/.Attribute /.attribute] )) - (_.cover [/.Attrs /.attributes] - (dictionary.empty? /.attributes)) + (_.coverage [/.Attrs /.attributes] + (dictionary.empty? /.attributes)) ))) ))) diff --git a/stdlib/source/test/lux/data/product.lux b/stdlib/source/test/lux/data/product.lux index a33f53a1d..9f7465057 100644 --- a/stdlib/source/test/lux/data/product.lux +++ b/stdlib/source/test/lux/data/product.lux @@ -30,17 +30,17 @@ (do random.monad [left random.int right random.nat] - (_.cover [/.hash] - (let [hash (/.hash i.hash n.hash)] - (n.= (n.+ (# i.hash hash left) - (# n.hash hash right)) - (# hash hash [left right]))))) + (_.coverage [/.hash] + (let [hash (/.hash i.hash n.hash)] + (n.= (n.+ (# i.hash hash left) + (# n.hash hash right)) + (# hash hash [left right]))))) - (<| (_.cover [/.left]) + (<| (_.coverage [/.left]) (n.= expected (/.left [expected dummy]))) - (<| (_.cover [/.right]) + (<| (_.coverage [/.right]) (n.= expected (/.right [dummy expected]))) - (<| (_.cover [/.forked]) + (<| (_.coverage [/.forked]) (let [[left right] ((/.forked (n.+ shift) (n.- shift)) expected)] (and (n.= (n.+ shift expected) left) @@ -50,19 +50,19 @@ [left random.nat right random.nat] (all _.and - (<| (_.cover [/.swapped]) + (<| (_.coverage [/.swapped]) (let [pair [left right]] (and (n.= (/.left pair) (/.right (/.swapped pair))) (n.= (/.right pair) (/.left (/.swapped pair)))))) - (<| (_.cover [/.uncurried]) + (<| (_.coverage [/.uncurried]) (n.= (n.+ left right) ((/.uncurried n.+) [left right]))) - (<| (_.cover [/.curried]) + (<| (_.coverage [/.curried]) (n.= (n.+ left right) ((/.curried (/.uncurried n.+)) left right))) - (<| (_.cover [/.then]) + (<| (_.coverage [/.then]) (let [[left' right'] (/.then (n.+ shift) (n.- shift) [left right])] (and (n.= (n.+ shift left) left') (n.= (n.- shift right) right')))))) diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux index ec9e7d67d..f1b132062 100644 --- a/stdlib/source/test/lux/data/sum.lux +++ b/stdlib/source/test/lux/data/sum.lux @@ -36,71 +36,71 @@ ($hash.spec (/.hash n.hash n.hash) (random.or random.nat random.nat))) - (_.cover [/.left] - (|> (/.left expected) - (is (Or Nat Nat)) - (pipe.case - {0 #0 actual} (n.= expected actual) - _ false))) - (_.cover [/.right] - (|> (/.right expected) - (is (Or Nat Nat)) - (pipe.case - {0 #1 actual} (n.= expected actual) - _ false))) - (_.cover [/.either] - (and (|> (/.left expected) - (is (Or Nat Nat)) - (/.either (n.+ shift) (n.- shift)) - (n.= (n.+ shift expected))) - (|> (/.right expected) - (is (Or Nat Nat)) - (/.either (n.+ shift) (n.- shift)) - (n.= (n.- shift expected))))) - (_.cover [/.then] - (and (|> (/.left expected) - (is (Or Nat Nat)) - (/.then (n.+ shift) (n.- shift)) - (pipe.case {0 #0 actual} (n.= (n.+ shift expected) actual) _ false)) - (|> (/.right expected) - (is (Or Nat Nat)) - (/.then (n.+ shift) (n.- shift)) - (pipe.case {0 #1 actual} (n.= (n.- shift expected) actual) _ false)))) + (_.coverage [/.left] + (|> (/.left expected) + (is (Or Nat Nat)) + (pipe.case + {0 #0 actual} (n.= expected actual) + _ false))) + (_.coverage [/.right] + (|> (/.right expected) + (is (Or Nat Nat)) + (pipe.case + {0 #1 actual} (n.= expected actual) + _ false))) + (_.coverage [/.either] + (and (|> (/.left expected) + (is (Or Nat Nat)) + (/.either (n.+ shift) (n.- shift)) + (n.= (n.+ shift expected))) + (|> (/.right expected) + (is (Or Nat Nat)) + (/.either (n.+ shift) (n.- shift)) + (n.= (n.- shift expected))))) + (_.coverage [/.then] + (and (|> (/.left expected) + (is (Or Nat Nat)) + (/.then (n.+ shift) (n.- shift)) + (pipe.case {0 #0 actual} (n.= (n.+ shift expected) actual) _ false)) + (|> (/.right expected) + (is (Or Nat Nat)) + (/.then (n.+ shift) (n.- shift)) + (pipe.case {0 #1 actual} (n.= (n.- shift expected) actual) _ false)))) (do ! [size (# ! each (n.% 5) random.nat) expected (random.list size random.nat)] (all _.and - (_.cover [/.lefts] - (let [actual (is (List (Or Nat Nat)) - (list#each /.left expected))] - (and (# (list.equivalence n.equivalence) = - expected - (/.lefts actual)) - (# (list.equivalence n.equivalence) = - (list) - (/.rights actual))))) - (_.cover [/.rights] - (let [actual (is (List (Or Nat Nat)) - (list#each /.right expected))] - (and (# (list.equivalence n.equivalence) = - expected - (/.rights actual)) - (# (list.equivalence n.equivalence) = - (list) - (/.lefts actual))))) - (_.cover [/.partition] - (let [[lefts rights] (|> expected - (list#each (function (_ value) - (if (n.even? value) - (/.left value) - (/.right value)))) - (is (List (Or Nat Nat))) - /.partition)] - (and (# (list.equivalence n.equivalence) = - (list.only n.even? expected) - lefts) - (# (list.equivalence n.equivalence) = - (list.only (|>> n.even? not) expected) - rights)))) + (_.coverage [/.lefts] + (let [actual (is (List (Or Nat Nat)) + (list#each /.left expected))] + (and (# (list.equivalence n.equivalence) = + expected + (/.lefts actual)) + (# (list.equivalence n.equivalence) = + (list) + (/.rights actual))))) + (_.coverage [/.rights] + (let [actual (is (List (Or Nat Nat)) + (list#each /.right expected))] + (and (# (list.equivalence n.equivalence) = + expected + (/.rights actual)) + (# (list.equivalence n.equivalence) = + (list) + (/.lefts actual))))) + (_.coverage [/.partition] + (let [[lefts rights] (|> expected + (list#each (function (_ value) + (if (n.even? value) + (/.left value) + (/.right value)))) + (is (List (Or Nat Nat))) + /.partition)] + (and (# (list.equivalence n.equivalence) = + (list.only n.even? expected) + lefts) + (# (list.equivalence n.equivalence) = + (list.only (|>> n.even? not) expected) + rights)))) )) )))) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index a4ecc3e09..76e6f4ccb 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -42,11 +42,11 @@ [size (# ! each (n.% 10) random.nat) sample (random.unicode size)] (all _.and - (_.cover [/.size] - (n.= size (/.size sample))) - (_.cover [/.empty?] - (or (/.empty? sample) - (not (n.= 0 size))))))) + (_.coverage [/.size] + (n.= size (/.size sample))) + (_.coverage [/.empty?] + (or (/.empty? sample) + (not (n.= 0 size))))))) (def: affix Test @@ -60,21 +60,21 @@ fake_index (-- 0)]] (`` (all _.and (~~ (template [<affix> <predicate>] - [(_.cover [<affix> <predicate>] - (<predicate> outer (<affix> outer inner)))] + [(_.coverage [<affix> <predicate>] + (<predicate> outer (<affix> outer inner)))] [/.prefix /.starts_with?] [/.suffix /.ends_with?] [/.enclosed' /.enclosed_by?] )) - (_.cover [/.enclosed] - (let [value (/.enclosed [left right] inner)] - (and (/.starts_with? left value) - (/.ends_with? right value)))) - (_.cover [/.format] - (let [sample (/.format inner)] - (and (/.enclosed_by? /.double_quote sample) - (/.contains? inner sample)))) + (_.coverage [/.enclosed] + (let [value (/.enclosed [left right] inner)] + (and (/.starts_with? left value) + (/.ends_with? right value)))) + (_.coverage [/.format] + (let [sample (/.format inner)] + (and (/.enclosed_by? /.double_quote sample) + (/.contains? inner sample)))) )))) (def: index @@ -85,43 +85,43 @@ (random.unicode 1)) .let [fake_index (-- 0)]] (all _.and - (_.cover [/.contains?] - (let [full (# /.monoid composite inner outer)] - (and (/.contains? inner full) - (/.contains? outer full)))) - (_.cover [/.index] - (and (|> (/.index inner (# /.monoid composite inner outer)) - (maybe.else fake_index) - (n.= 0)) - (|> (/.index outer (# /.monoid composite inner outer)) - (maybe.else fake_index) - (n.= 1)))) - (_.cover [/.index_since] - (let [full (# /.monoid composite inner outer)] - (and (|> (/.index_since 0 inner full) - (maybe.else fake_index) - (n.= 0)) - (|> (/.index_since 1 inner full) - (maybe.else fake_index) - (n.= fake_index)) - - (|> (/.index_since 0 outer full) - (maybe.else fake_index) - (n.= 1)) - (|> (/.index_since 1 outer full) - (maybe.else fake_index) - (n.= 1)) - (|> (/.index_since 2 outer full) - (maybe.else fake_index) - (n.= fake_index))))) - (_.cover [/.last_index] - (let [full (all (# /.monoid composite) outer inner outer)] - (and (|> (/.last_index inner full) - (maybe.else fake_index) - (n.= 1)) - (|> (/.last_index outer full) - (maybe.else fake_index) - (n.= 2))))) + (_.coverage [/.contains?] + (let [full (# /.monoid composite inner outer)] + (and (/.contains? inner full) + (/.contains? outer full)))) + (_.coverage [/.index] + (and (|> (/.index inner (# /.monoid composite inner outer)) + (maybe.else fake_index) + (n.= 0)) + (|> (/.index outer (# /.monoid composite inner outer)) + (maybe.else fake_index) + (n.= 1)))) + (_.coverage [/.index_since] + (let [full (# /.monoid composite inner outer)] + (and (|> (/.index_since 0 inner full) + (maybe.else fake_index) + (n.= 0)) + (|> (/.index_since 1 inner full) + (maybe.else fake_index) + (n.= fake_index)) + + (|> (/.index_since 0 outer full) + (maybe.else fake_index) + (n.= 1)) + (|> (/.index_since 1 outer full) + (maybe.else fake_index) + (n.= 1)) + (|> (/.index_since 2 outer full) + (maybe.else fake_index) + (n.= fake_index))))) + (_.coverage [/.last_index] + (let [full (all (# /.monoid composite) outer inner outer)] + (and (|> (/.last_index inner full) + (maybe.else fake_index) + (n.= 1)) + (|> (/.last_index outer full) + (maybe.else fake_index) + (n.= 2))))) ))) (def: char @@ -130,8 +130,8 @@ (_.for [/.Char /.of_char] (`` (all _.and (~~ (template [<short> <long>] - [(_.cover [<short> <long>] - (# /.equivalence = <short> <long>))] + [(_.coverage [<short> <long>] + (# /.equivalence = <short> <long>))] [/.\0 /.null] [/.\a /.alarm] @@ -142,37 +142,37 @@ [/.\f /.form_feed] [/.\r /.carriage_return] [/.\'' /.double_quote])) - (_.cover [/.line_feed] - (# /.equivalence = /.new_line /.line_feed)) + (_.coverage [/.line_feed] + (# /.equivalence = /.new_line /.line_feed)) ))) (do [! random.monad] [size (# ! each (|>> (n.% 10) ++) random.nat) characters (random.set /.hash size (random.alphabetic 1)) .let [sample (|> characters set.list /.together)] expected (# ! each (n.% size) random.nat)] - (_.cover [/.char] - (case (/.char expected sample) - {.#Some char} - (case (/.index (/.of_char char) sample) - {.#Some actual} - (n.= expected actual) + (_.coverage [/.char] + (case (/.char expected sample) + {.#Some char} + (case (/.index (/.of_char char) sample) + {.#Some actual} + (n.= expected actual) - _ - false) - - {.#None} - false))) - (_.cover [/.space /.space?] - (`` (and (~~ (template [<char>] - [(/.space? (`` (.char (~~ (static <char>)))))] - - [/.tab] - [/.vertical_tab] - [/.space] - [/.new_line] - [/.carriage_return] - [/.form_feed] - ))))) + _ + false) + + {.#None} + false))) + (_.coverage [/.space /.space?] + (`` (and (~~ (template [<char>] + [(/.space? (`` (.char (~~ (static <char>)))))] + + [/.tab] + [/.vertical_tab] + [/.space] + [/.new_line] + [/.carriage_return] + [/.form_feed] + ))))) )) (def: manipulation @@ -192,70 +192,70 @@ lower (random.lower_case 1) upper (random.upper_case 1)] (all _.and - (_.cover [/.together] - (n.= (set.size characters) - (/.size (/.together (set.list characters))))) - (_.cover [/.interposed /.all_split_by] - (and (|> (set.list characters) - (/.interposed separator) - (/.all_split_by separator) - (set.of_list /.hash) - (# set.equivalence = characters)) - (# /.equivalence = - (/.together (set.list characters)) - (/.interposed "" (set.list characters))))) - (_.cover [/.replaced_once] - (# /.equivalence = - (# /.monoid composite post static) - (/.replaced_once pre post (# /.monoid composite pre static)))) - (_.cover [/.split_by] - (case (/.split_by static (all (# /.monoid composite) pre static post)) - {.#Some [left right]} - (and (# /.equivalence = pre left) - (# /.equivalence = post right)) - - {.#None} - false)) - (_.cover [/.lower_cased] - (let [effectiveness! - (|> upper - /.lower_cased - (# /.equivalence = upper) - not) + (_.coverage [/.together] + (n.= (set.size characters) + (/.size (/.together (set.list characters))))) + (_.coverage [/.interposed /.all_split_by] + (and (|> (set.list characters) + (/.interposed separator) + (/.all_split_by separator) + (set.of_list /.hash) + (# set.equivalence = characters)) + (# /.equivalence = + (/.together (set.list characters)) + (/.interposed "" (set.list characters))))) + (_.coverage [/.replaced_once] + (# /.equivalence = + (# /.monoid composite post static) + (/.replaced_once pre post (# /.monoid composite pre static)))) + (_.coverage [/.split_by] + (case (/.split_by static (all (# /.monoid composite) pre static post)) + {.#Some [left right]} + (and (# /.equivalence = pre left) + (# /.equivalence = post right)) + + {.#None} + false)) + (_.coverage [/.lower_cased] + (let [effectiveness! + (|> upper + /.lower_cased + (# /.equivalence = upper) + not) - idempotence! - (|> lower - /.lower_cased - (# /.equivalence = lower)) - - inverse! - (|> lower - /.upper_cased - /.lower_cased - (# /.equivalence = lower))] - (and effectiveness! - idempotence! - inverse!))) - (_.cover [/.upper_cased] - (let [effectiveness! - (|> lower - /.upper_cased - (# /.equivalence = lower) - not) + idempotence! + (|> lower + /.lower_cased + (# /.equivalence = lower)) + + inverse! + (|> lower + /.upper_cased + /.lower_cased + (# /.equivalence = lower))] + (and effectiveness! + idempotence! + inverse!))) + (_.coverage [/.upper_cased] + (let [effectiveness! + (|> lower + /.upper_cased + (# /.equivalence = lower) + not) - idempotence! - (|> upper - /.upper_cased - (# /.equivalence = upper)) - - inverse! - (|> upper - /.lower_cased - /.upper_cased - (# /.equivalence = upper))] - (and effectiveness! - idempotence! - inverse!))) + idempotence! + (|> upper + /.upper_cased + (# /.equivalence = upper)) + + inverse! + (|> upper + /.lower_cased + /.upper_cased + (# /.equivalence = upper))] + (and effectiveness! + idempotence! + inverse!))) ))) (def: .public test @@ -287,30 +287,30 @@ .let [sample (/.together (list sampleL sampleR)) (open "/#[0]") /.equivalence]] (all _.and - (_.cover [/.split_at] - (|> (/.split_at sizeL sample) - (pipe.case - {.#Right [_l _r]} - (and (/#= sampleL _l) - (/#= sampleR _r) - (/#= sample (/.together (list _l _r)))) + (_.coverage [/.split_at] + (|> (/.split_at sizeL sample) + (pipe.case + {.#Right [_l _r]} + (and (/#= sampleL _l) + (/#= sampleR _r) + (/#= sample (/.together (list _l _r)))) - _ - #0))) - (_.cover [/.clip /.clip_since] - (|> [(/.clip 0 sizeL sample) - (/.clip sizeL (n.- sizeL (/.size sample)) sample) - (/.clip_since sizeL sample) - (/.clip_since 0 sample)] - (pipe.case - [{.#Right _l} {.#Right _r} {.#Right _r'} {.#Right _f}] - (and (/#= sampleL _l) - (/#= sampleR _r) - (/#= _r _r') - (/#= sample _f)) + _ + #0))) + (_.coverage [/.clip /.clip_since] + (|> [(/.clip 0 sizeL sample) + (/.clip sizeL (n.- sizeL (/.size sample)) sample) + (/.clip_since sizeL sample) + (/.clip_since 0 sample)] + (pipe.case + [{.#Right _l} {.#Right _r} {.#Right _r'} {.#Right _f}] + (and (/#= sampleL _l) + (/#= sampleR _r) + (/#= _r _r') + (/#= sample _f)) - _ - #0))) + _ + #0))) )) (do [! random.monad] [sizeP bounded_size @@ -327,9 +327,9 @@ .let [sample1 (/.together (list.interposed sep1 parts)) sample2 (/.together (list.interposed sep2 parts)) (open "/#[0]") /.equivalence]] - (_.cover [/.replaced] - (/#= sample2 - (/.replaced sep1 sep2 sample1)))) + (_.coverage [/.replaced] + (/#= sample2 + (/.replaced sep1 sep2 sample1)))) /buffer.test /encoding.test diff --git a/stdlib/source/test/lux/data/text/buffer.lux b/stdlib/source/test/lux/data/text/buffer.lux index fe1506d88..aefc51bf1 100644 --- a/stdlib/source/test/lux/data/text/buffer.lux +++ b/stdlib/source/test/lux/data/text/buffer.lux @@ -29,16 +29,16 @@ mid ..part right ..part] (all _.and - (_.cover [/.empty] - (n.= 0(/.size /.empty))) - (_.cover [/.size /.then] - (n.= (text.size left) - (/.size (/.then left /.empty)))) - (_.cover [/.text] - (text#= (format left mid right) - (|> /.empty - (/.then left) - (/.then mid) - (/.then right) - /.text))) + (_.coverage [/.empty] + (n.= 0(/.size /.empty))) + (_.coverage [/.size /.then] + (n.= (text.size left) + (/.size (/.then left /.empty)))) + (_.coverage [/.text] + (text#= (format left mid right) + (|> /.empty + (/.then left) + (/.then mid) + (/.then right) + /.text))) )))) diff --git a/stdlib/source/test/lux/data/text/encoding.lux b/stdlib/source/test/lux/data/text/encoding.lux index eaa9b6aba..b0a70422c 100644 --- a/stdlib/source/test/lux/data/text/encoding.lux +++ b/stdlib/source/test/lux/data/text/encoding.lux @@ -205,8 +205,8 @@ (template [<definition> <by_letter>] [(def: <definition> Test - (`` (_.cover [/.name (~~ (template.spliced <by_letter>))] - ..verdict)))] + (`` (_.coverage [/.name (~~ (template.spliced <by_letter>))] + ..verdict)))] <encodings>) diff --git a/stdlib/source/test/lux/data/text/escape.lux b/stdlib/source/test/lux/data/text/escape.lux index c7fb6d2fc..937fbf4c5 100644 --- a/stdlib/source/test/lux/data/text/escape.lux +++ b/stdlib/source/test/lux/data/text/escape.lux @@ -85,54 +85,54 @@ (all _.and (do random.monad [ascii ..ascii_range] - (_.cover [/.escapable?] - (`` (if (or (~~ (template [<char>] - [(n.= (debug.private <char>) ascii)] - - [/.\0] [/.\a] [/.\b] [/.\t] - [/.\n] [/.\v] [/.\f] [/.\r] - [/.\''] [/.\\]))) - (/.escapable? ascii) - (bit#= (/.escapable? ascii) - (or (n.< (debug.private /.ascii_bottom) ascii) - (n.> (debug.private /.ascii_top) ascii))))))) + (_.coverage [/.escapable?] + (`` (if (or (~~ (template [<char>] + [(n.= (debug.private <char>) ascii)] + + [/.\0] [/.\a] [/.\b] [/.\t] + [/.\n] [/.\v] [/.\f] [/.\r] + [/.\''] [/.\\]))) + (/.escapable? ascii) + (bit#= (/.escapable? ascii) + (or (n.< (debug.private /.ascii_bottom) ascii) + (n.> (debug.private /.ascii_top) ascii))))))) (do random.monad [left (random.char unicode.character) right (random.char unicode.character)] - (_.cover [/.escaped /.un_escaped] - (let [expected (format (text.of_char left) (text.of_char right))] - (if (or (/.escapable? left) - (/.escapable? right)) - (let [escaped (/.escaped expected)] - (case (/.un_escaped escaped) - {try.#Success un_escaped} - (and (not (text#= escaped expected)) - (text#= un_escaped expected)) - - {try.#Failure error} - false)) - (text#= expected (/.escaped expected)))))) + (_.coverage [/.escaped /.un_escaped] + (let [expected (format (text.of_char left) (text.of_char right))] + (if (or (/.escapable? left) + (/.escapable? right)) + (let [escaped (/.escaped expected)] + (case (/.un_escaped escaped) + {try.#Success un_escaped} + (and (not (text#= escaped expected)) + (text#= un_escaped expected)) + + {try.#Failure error} + false)) + (text#= expected (/.escaped expected)))))) (do [! random.monad] [dummy (|> (random.char unicode.character) (# ! each text.of_char))] - (_.cover [/.dangling_escape] - (case (/.un_escaped (format (/.escaped dummy) "\")) - {try.#Success _} - false + (_.coverage [/.dangling_escape] + (case (/.un_escaped (format (/.escaped dummy) "\")) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.dangling_escape error)))) + {try.#Failure error} + (exception.match? /.dangling_escape error)))) (do [! random.monad] [dummy (|> (random.char unicode.character) (random.only (|>> (set.member? ..valid_sigils) not)) (# ! each text.of_char))] - (_.cover [/.invalid_escape] - (case (/.un_escaped (format "\" dummy)) - {try.#Success _} - false + (_.coverage [/.invalid_escape] + (case (/.un_escaped (format "\" dummy)) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.invalid_escape error)))) + {try.#Failure error} + (exception.match? /.invalid_escape error)))) (do [! random.monad] [too_short (|> (random.char unicode.character) (# ! each (n.% (hex "1000")))) @@ -141,17 +141,17 @@ (case (# n.hex decoded code) {try.#Failure error} true {try.#Success _} false))))] - (_.cover [/.invalid_unicode_escape] - (template.let [(!invalid <code>) - [(case (/.un_escaped (format "\u" <code>)) - {try.#Success _} - false + (_.coverage [/.invalid_unicode_escape] + (template.let [(!invalid <code>) + [(case (/.un_escaped (format "\u" <code>)) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.invalid_unicode_escape error))]] - (and (!invalid (# n.hex encoded too_short)) - (!invalid code))))) - (_.cover [/.literal] - (with_expansions [<example> (..static_sample)] - (text#= <example> (`` (/.literal (~~ (..static_escaped <example>))))))) + {try.#Failure error} + (exception.match? /.invalid_unicode_escape error))]] + (and (!invalid (# n.hex encoded too_short)) + (!invalid code))))) + (_.coverage [/.literal] + (with_expansions [<example> (..static_sample)] + (text#= <example> (`` (/.literal (~~ (..static_escaped <example>))))))) ))) diff --git a/stdlib/source/test/lux/data/text/format.lux b/stdlib/source/test/lux/data/text/format.lux index 5ac493e4e..97a9005f8 100644 --- a/stdlib/source/test/lux/data/text/format.lux +++ b/stdlib/source/test/lux/data/text/format.lux @@ -76,9 +76,9 @@ (~~ (template [<format> <codec> <random>] [(do random.monad [sample <random>] - (_.cover [<format>] - (text#= (# <codec> encoded sample) - (<format> sample))))] + (_.coverage [<format>] + (text#= (# <codec> encoded sample) + (<format> sample))))] [/.bit bit.codec random.bit] [/.nat nat.decimal random.nat] @@ -135,16 +135,16 @@ [left (random.unicode 5) mid (random.unicode 5) right (random.unicode 5)] - (_.cover [/.format] - (text#= (/.format left mid right) - (all "lux text concat" left mid right)))) + (_.coverage [/.format] + (text#= (/.format left mid right) + (all "lux text concat" left mid right)))) ..codec (~~ (template [<format> <alias> <random>] [(do random.monad [sample <random>] - (_.cover [<format>] - (text#= (<alias> sample) - (<format> sample))))] + (_.coverage [<format>] + (text#= (<alias> sample) + (<format> sample))))] [/.text text.format (random.unicode 5)] [/.code code.format $///code.random] @@ -157,30 +157,30 @@ )) (do random.monad [members (random.list 5 random.nat)] - (_.cover [/.list] - (text#= (/.list /.nat members) - (|> members - (list#each /.nat) - (text.interposed " ") - list - (/.list (|>>)))))) + (_.coverage [/.list] + (text#= (/.list /.nat members) + (|> members + (list#each /.nat) + (text.interposed " ") + list + (/.list (|>>)))))) (do random.monad [sample (random.maybe random.nat)] - (_.cover [/.maybe] - (case sample - {.#None} - true - - {.#Some value} - (text.contains? (/.nat value) - (/.maybe /.nat sample))))) + (_.coverage [/.maybe] + (case sample + {.#None} + true + + {.#Some value} + (text.contains? (/.nat value) + (/.maybe /.nat sample))))) (do [! random.monad] [modulus (random.one (|>> modulus.modulus try.maybe) random.int) sample (# ! each (modular.modular modulus) random.int)] - (_.cover [/.mod] - (text#= (# (modular.codec modulus) encoded sample) - (/.mod sample)))) + (_.coverage [/.mod] + (text#= (# (modular.codec modulus) encoded sample) + (/.mod sample)))) )))) diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux index a9f5d8cc4..7488c1b83 100644 --- a/stdlib/source/test/lux/data/text/regex.lux +++ b/stdlib/source/test/lux/data/text/regex.lux @@ -70,210 +70,210 @@ (def: basics Test - (_.test "Can parse character literals." - (and (should_pass (/.regex "a") "a") - (should_fail (/.regex "a") ".") - (should_pass (/.regex "\.") ".") - (should_fail (/.regex "\.") "a")))) + (_.property "Can parse character literals." + (and (should_pass (/.regex "a") "a") + (should_fail (/.regex "a") ".") + (should_pass (/.regex "\.") ".") + (should_fail (/.regex "\.") "a")))) (def: system_character_classes Test (all _.and - (_.test "Can parse anything." - (should_pass (/.regex ".") "a")) + (_.property "Can parse anything." + (should_pass (/.regex ".") "a")) - (_.test "Can parse digits." - (and (should_pass (/.regex "\d") "0") - (should_fail (/.regex "\d") "m"))) + (_.property "Can parse digits." + (and (should_pass (/.regex "\d") "0") + (should_fail (/.regex "\d") "m"))) - (_.test "Can parse non digits." - (and (should_pass (/.regex "\D") "m") - (should_fail (/.regex "\D") "0"))) + (_.property "Can parse non digits." + (and (should_pass (/.regex "\D") "m") + (should_fail (/.regex "\D") "0"))) - (_.test "Can parse white-space." - (and (should_pass (/.regex "\s") " ") - (should_fail (/.regex "\s") "m"))) + (_.property "Can parse white-space." + (and (should_pass (/.regex "\s") " ") + (should_fail (/.regex "\s") "m"))) - (_.test "Can parse non white-space." - (and (should_pass (/.regex "\S") "m") - (should_fail (/.regex "\S") " "))) + (_.property "Can parse non white-space." + (and (should_pass (/.regex "\S") "m") + (should_fail (/.regex "\S") " "))) - (_.test "Can parse word characters." - (and (should_pass (/.regex "\w") "_") - (should_fail (/.regex "\w") "^"))) + (_.property "Can parse word characters." + (and (should_pass (/.regex "\w") "_") + (should_fail (/.regex "\w") "^"))) - (_.test "Can parse non word characters." - (and (should_pass (/.regex "\W") ".") - (should_fail (/.regex "\W") "a"))) + (_.property "Can parse non word characters." + (and (should_pass (/.regex "\W") ".") + (should_fail (/.regex "\W") "a"))) )) (def: special_system_character_classes Test (all _.and - (_.test "Lower-case." - (and (should_pass (/.regex "\p{Lower}") "m") - (should_fail (/.regex "\p{Lower}") "M"))) - (_.test "Upper-case." - (and (should_pass (/.regex "\p{Upper}") "M") - (should_fail (/.regex "\p{Upper}") "m"))) - (_.test "Alphabetic." - (and (should_pass (/.regex "\p{Alpha}") "M") - (should_fail (/.regex "\p{Alpha}") "0"))) - (_.test "Numeric digits." - (and (should_pass (/.regex "\p{Digit}") "1") - (should_fail (/.regex "\p{Digit}") "n"))) - (_.test "Alphanumeric." - (and (should_pass (/.regex "\p{Alnum}") "1") - (should_fail (/.regex "\p{Alnum}") "."))) - (_.test "Whitespace." - (and (should_pass (/.regex "\p{Space}") " ") - (should_fail (/.regex "\p{Space}") "."))) - (_.test "Hexadecimal." - (and (should_pass (/.regex "\p{HexDigit}") "a") - (should_fail (/.regex "\p{HexDigit}") "."))) - (_.test "Octal." - (and (should_pass (/.regex "\p{OctDigit}") "6") - (should_fail (/.regex "\p{OctDigit}") "."))) - (_.test "Blank." - (and (should_pass (/.regex "\p{Blank}") text.tab) - (should_fail (/.regex "\p{Blank}") "."))) - (_.test "ASCII." - (and (should_pass (/.regex "\p{ASCII}") text.tab) - (should_fail (/.regex "\p{ASCII}") (text.of_char (hex "1234"))))) - (_.test "Control characters." - (and (should_pass (/.regex "\p{Contrl}") (text.of_char (hex "12"))) - (should_fail (/.regex "\p{Contrl}") "a"))) - (_.test "Punctuation." - (and (should_pass (/.regex "\p{Punct}") "@") - (should_fail (/.regex "\p{Punct}") "a"))) - (_.test "Graph." - (and (should_pass (/.regex "\p{Graph}") "@") - (should_fail (/.regex "\p{Graph}") " "))) - (_.test "Print." - (and (should_pass (/.regex "\p{Print}") (text.of_char (hex "20"))) - (should_fail (/.regex "\p{Print}") (text.of_char (hex "1234"))))) + (_.property "Lower-case." + (and (should_pass (/.regex "\p{Lower}") "m") + (should_fail (/.regex "\p{Lower}") "M"))) + (_.property "Upper-case." + (and (should_pass (/.regex "\p{Upper}") "M") + (should_fail (/.regex "\p{Upper}") "m"))) + (_.property "Alphabetic." + (and (should_pass (/.regex "\p{Alpha}") "M") + (should_fail (/.regex "\p{Alpha}") "0"))) + (_.property "Numeric digits." + (and (should_pass (/.regex "\p{Digit}") "1") + (should_fail (/.regex "\p{Digit}") "n"))) + (_.property "Alphanumeric." + (and (should_pass (/.regex "\p{Alnum}") "1") + (should_fail (/.regex "\p{Alnum}") "."))) + (_.property "Whitespace." + (and (should_pass (/.regex "\p{Space}") " ") + (should_fail (/.regex "\p{Space}") "."))) + (_.property "Hexadecimal." + (and (should_pass (/.regex "\p{HexDigit}") "a") + (should_fail (/.regex "\p{HexDigit}") "."))) + (_.property "Octal." + (and (should_pass (/.regex "\p{OctDigit}") "6") + (should_fail (/.regex "\p{OctDigit}") "."))) + (_.property "Blank." + (and (should_pass (/.regex "\p{Blank}") text.tab) + (should_fail (/.regex "\p{Blank}") "."))) + (_.property "ASCII." + (and (should_pass (/.regex "\p{ASCII}") text.tab) + (should_fail (/.regex "\p{ASCII}") (text.of_char (hex "1234"))))) + (_.property "Control characters." + (and (should_pass (/.regex "\p{Contrl}") (text.of_char (hex "12"))) + (should_fail (/.regex "\p{Contrl}") "a"))) + (_.property "Punctuation." + (and (should_pass (/.regex "\p{Punct}") "@") + (should_fail (/.regex "\p{Punct}") "a"))) + (_.property "Graph." + (and (should_pass (/.regex "\p{Graph}") "@") + (should_fail (/.regex "\p{Graph}") " "))) + (_.property "Print." + (and (should_pass (/.regex "\p{Print}") (text.of_char (hex "20"))) + (should_fail (/.regex "\p{Print}") (text.of_char (hex "1234"))))) )) (def: custom_character_classes Test (all _.and - (_.test "Can parse using custom character classes." - (and (should_pass (/.regex "[abc]") "a") - (should_fail (/.regex "[abc]") "m"))) - (_.test "Can parse using character ranges." - (and (should_pass (/.regex "[a-z]") "a") - (should_pass (/.regex "[a-z]") "m") - (should_pass (/.regex "[a-z]") "z"))) - (_.test "Can combine character ranges." - (and (should_pass (/.regex "[a-zA-Z]") "a") - (should_pass (/.regex "[a-zA-Z]") "m") - (should_pass (/.regex "[a-zA-Z]") "z") - (should_pass (/.regex "[a-zA-Z]") "A") - (should_pass (/.regex "[a-zA-Z]") "M") - (should_pass (/.regex "[a-zA-Z]") "Z"))) - (_.test "Can negate custom character classes." - (and (should_fail (/.regex "[^abc]") "a") - (should_pass (/.regex "[^abc]") "m"))) - (_.test "Can negate character ranges.." - (and (should_fail (/.regex "[^a-z]") "a") - (should_pass (/.regex "[^a-z]") "0"))) - (_.test "Can parse negate combinations of character ranges." - (and (should_fail (/.regex "[^a-zA-Z]") "a") - (should_pass (/.regex "[^a-zA-Z]") "0"))) - (_.test "Can make custom character classes more specific." - (and (let [RE (/.regex "[a-z&&[def]]")] - (and (should_fail RE "a") - (should_pass RE "d"))) - (let [RE (/.regex "[a-z&&[^bc]]")] - (and (should_pass RE "a") - (should_fail RE "b"))) - (let [RE (/.regex "[a-z&&[^m-p]]")] - (and (should_pass RE "a") - (should_fail RE "m") - (should_fail RE "p"))))) + (_.property "Can parse using custom character classes." + (and (should_pass (/.regex "[abc]") "a") + (should_fail (/.regex "[abc]") "m"))) + (_.property "Can parse using character ranges." + (and (should_pass (/.regex "[a-z]") "a") + (should_pass (/.regex "[a-z]") "m") + (should_pass (/.regex "[a-z]") "z"))) + (_.property "Can combine character ranges." + (and (should_pass (/.regex "[a-zA-Z]") "a") + (should_pass (/.regex "[a-zA-Z]") "m") + (should_pass (/.regex "[a-zA-Z]") "z") + (should_pass (/.regex "[a-zA-Z]") "A") + (should_pass (/.regex "[a-zA-Z]") "M") + (should_pass (/.regex "[a-zA-Z]") "Z"))) + (_.property "Can negate custom character classes." + (and (should_fail (/.regex "[^abc]") "a") + (should_pass (/.regex "[^abc]") "m"))) + (_.property "Can negate character ranges.." + (and (should_fail (/.regex "[^a-z]") "a") + (should_pass (/.regex "[^a-z]") "0"))) + (_.property "Can parse negate combinations of character ranges." + (and (should_fail (/.regex "[^a-zA-Z]") "a") + (should_pass (/.regex "[^a-zA-Z]") "0"))) + (_.property "Can make custom character classes more specific." + (and (let [RE (/.regex "[a-z&&[def]]")] + (and (should_fail RE "a") + (should_pass RE "d"))) + (let [RE (/.regex "[a-z&&[^bc]]")] + (and (should_pass RE "a") + (should_fail RE "b"))) + (let [RE (/.regex "[a-z&&[^m-p]]")] + (and (should_pass RE "a") + (should_fail RE "m") + (should_fail RE "p"))))) )) (def: references Test (let [number (/.regex "\d+")] - (_.test "Can build complex regexs by combining simpler ones." - (should_check ["809-345-6789" "809" "345" "6789"] - (/.regex "(\@<number>)-(\@<number>)-(\@<number>)") - "809-345-6789")))) + (_.property "Can build complex regexs by combining simpler ones." + (should_check ["809-345-6789" "809" "345" "6789"] + (/.regex "(\@<number>)-(\@<number>)-(\@<number>)") + "809-345-6789")))) (def: fuzzy_quantifiers Test (all _.and - (_.test "Can sequentially combine patterns." - (text_should_pass "aa" (/.regex "aa") "aa")) + (_.property "Can sequentially combine patterns." + (text_should_pass "aa" (/.regex "aa") "aa")) - (_.test "Can match patterns optionally." - (and (text_should_pass "a" (/.regex "a?") "a") - (text_should_pass "" (/.regex "a?") ""))) + (_.property "Can match patterns optionally." + (and (text_should_pass "a" (/.regex "a?") "a") + (text_should_pass "" (/.regex "a?") ""))) - (_.test "Can match a pattern 0 or more times." - (and (text_should_pass "aaa" (/.regex "a*") "aaa") - (text_should_pass "" (/.regex "a*") ""))) + (_.property "Can match a pattern 0 or more times." + (and (text_should_pass "aaa" (/.regex "a*") "aaa") + (text_should_pass "" (/.regex "a*") ""))) - (_.test "Can match a pattern 1 or more times." - (and (text_should_pass "aaa" (/.regex "a+") "aaa") - (text_should_pass "a" (/.regex "a+") "a") - (should_fail (/.regex "a+") ""))) + (_.property "Can match a pattern 1 or more times." + (and (text_should_pass "aaa" (/.regex "a+") "aaa") + (text_should_pass "a" (/.regex "a+") "a") + (should_fail (/.regex "a+") ""))) )) (def: crisp_quantifiers Test (all _.and - (_.test "Can match a pattern N times." - (and (text_should_pass "aa" (/.regex "a{2}") "aa") - (text_should_pass "a" (/.regex "a{1}") "a") - (should_fail (/.regex "a{3}") "aa"))) - - (_.test "Can match a pattern at-least N times." - (and (text_should_pass "aa" (/.regex "a{1,}") "aa") - (text_should_pass "aa" (/.regex "a{2,}") "aa") - (should_fail (/.regex "a{3,}") "aa"))) - - (_.test "Can match a pattern at-most N times." - (and (text_should_pass "aa" (/.regex "a{,2}") "aa") - (text_should_pass "aa" (/.regex "a{,3}") "aa"))) - - (_.test "Can match a pattern between N and M times." - (and (text_should_pass "a" (/.regex "a{1,2}") "a") - (text_should_pass "aa" (/.regex "a{1,2}") "aa"))) + (_.property "Can match a pattern N times." + (and (text_should_pass "aa" (/.regex "a{2}") "aa") + (text_should_pass "a" (/.regex "a{1}") "a") + (should_fail (/.regex "a{3}") "aa"))) + + (_.property "Can match a pattern at-least N times." + (and (text_should_pass "aa" (/.regex "a{1,}") "aa") + (text_should_pass "aa" (/.regex "a{2,}") "aa") + (should_fail (/.regex "a{3,}") "aa"))) + + (_.property "Can match a pattern at-most N times." + (and (text_should_pass "aa" (/.regex "a{,2}") "aa") + (text_should_pass "aa" (/.regex "a{,3}") "aa"))) + + (_.property "Can match a pattern between N and M times." + (and (text_should_pass "a" (/.regex "a{1,2}") "a") + (text_should_pass "aa" (/.regex "a{1,2}") "aa"))) )) (def: groups Test (all _.and - (_.test "Can extract groups of sub-matches specified in a pattern." - (and (should_check ["abc" "b"] (/.regex "a(.)c") "abc") - (should_check ["abbbbbc" "bbbbb"] (/.regex "a(b+)c") "abbbbbc") - (should_check ["809-345-6789" "809" "345" "6789"] (/.regex "(\d{3})-(\d{3})-(\d{4})") "809-345-6789") - (should_check ["809-345-6789" "809" "6789"] (/.regex "(\d{3})-(?:\d{3})-(\d{4})") "809-345-6789") - (should_check ["809-809-6789" "809" "6789"] (/.regex "(\d{3})-\0-(\d{4})") "809-809-6789") - (should_check ["809-809-6789" "809" "6789"] (/.regex "(?<code>\d{3})-\k<code>-(\d{4})") "809-809-6789") - (should_check ["809-809-6789-6789" "809" "6789"] (/.regex "(?<code>\d{3})-\k<code>-(\d{4})-\0") "809-809-6789-6789"))) - - (_.test "Can specify groups within groups." - (should_check ["809-345-6789" "809" ["345-6789" "345" "6789"]] (/.regex "(\d{3})-((\d{3})-(\d{4}))") "809-345-6789")) + (_.property "Can extract groups of sub-matches specified in a pattern." + (and (should_check ["abc" "b"] (/.regex "a(.)c") "abc") + (should_check ["abbbbbc" "bbbbb"] (/.regex "a(b+)c") "abbbbbc") + (should_check ["809-345-6789" "809" "345" "6789"] (/.regex "(\d{3})-(\d{3})-(\d{4})") "809-345-6789") + (should_check ["809-345-6789" "809" "6789"] (/.regex "(\d{3})-(?:\d{3})-(\d{4})") "809-345-6789") + (should_check ["809-809-6789" "809" "6789"] (/.regex "(\d{3})-\0-(\d{4})") "809-809-6789") + (should_check ["809-809-6789" "809" "6789"] (/.regex "(?<code>\d{3})-\k<code>-(\d{4})") "809-809-6789") + (should_check ["809-809-6789-6789" "809" "6789"] (/.regex "(?<code>\d{3})-\k<code>-(\d{4})-\0") "809-809-6789-6789"))) + + (_.property "Can specify groups within groups." + (should_check ["809-345-6789" "809" ["345-6789" "345" "6789"]] (/.regex "(\d{3})-((\d{3})-(\d{4}))") "809-345-6789")) )) (def: alternation Test (all _.and - (_.test "Can specify alternative patterns." - (and (should_check ["a" {0 #0 []}] (/.regex "a|b") "a") - (should_check ["b" {0 #1 []}] (/.regex "a|b") "b") - (should_fail (/.regex "a|b") "c"))) - (_.test "Can have groups within alternations." - (and (should_check ["abc" {0 #0 ["b" "c"]}] (/.regex "a(.)(.)|b(.)(.)") "abc") - (should_check ["bcd" {0 #1 ["c" "d"]}] (/.regex "a(.)(.)|b(.)(.)") "bcd") - (should_fail (/.regex "a(.)(.)|b(.)(.)") "cde") - - (should_check ["123-456-7890" {0 #0 ["123" "456-7890" "456" "7890"]}] - (/.regex "(\d{3})-((\d{3})-(\d{4}))|b(.)d") - "123-456-7890"))) + (_.property "Can specify alternative patterns." + (and (should_check ["a" {0 #0 []}] (/.regex "a|b") "a") + (should_check ["b" {0 #1 []}] (/.regex "a|b") "b") + (should_fail (/.regex "a|b") "c"))) + (_.property "Can have groups within alternations." + (and (should_check ["abc" {0 #0 ["b" "c"]}] (/.regex "a(.)(.)|b(.)(.)") "abc") + (should_check ["bcd" {0 #1 ["c" "d"]}] (/.regex "a(.)(.)|b(.)(.)") "bcd") + (should_fail (/.regex "a(.)(.)|b(.)(.)") "cde") + + (should_check ["123-456-7890" {0 #0 ["123" "456-7890" "456" "7890"]}] + (/.regex "(\d{3})-((\d{3})-(\d{4}))|b(.)d") + "123-456-7890"))) )) (syntax: (expands? [form <code>.any]) @@ -305,17 +305,17 @@ [sample1 (random.unicode 3) sample2 (random.unicode 3) sample3 (random.unicode 4)] - (_.cover [/.pattern] - (case (format sample1 "-" sample2 "-" sample3) - (/.pattern "(.{3})-(.{3})-(.{4})" - [_ match1 match2 match3]) - (and (text#= sample1 match1) - (text#= sample2 match2) - (text#= sample3 match3)) - - _ - false))) - (_.cover [/.incorrect_quantification] - (and (expands? (/.regex "a{1,2}")) - (not (expands? (/.regex "a{2,1}"))))) + (_.coverage [/.pattern] + (case (format sample1 "-" sample2 "-" sample3) + (/.pattern "(.{3})-(.{3})-(.{4})" + [_ match1 match2 match3]) + (and (text#= sample1 match1) + (text#= sample2 match2) + (text#= sample3 match3)) + + _ + false))) + (_.coverage [/.incorrect_quantification] + (and (expands? (/.regex "a{1,2}")) + (not (expands? (/.regex "a{2,1}"))))) ))) diff --git a/stdlib/source/test/lux/data/text/unicode/block.lux b/stdlib/source/test/lux/data/text/unicode/block.lux index 4c4a35e69..b7c79e556 100644 --- a/stdlib/source/test/lux/data/text/unicode/block.lux +++ b/stdlib/source/test/lux/data/text/unicode/block.lux @@ -156,11 +156,11 @@ (template [<definition> <part>] [(def: <definition> Test - (`` (_.cover [(~~ (template.spliced <part>))] - (let [all (list.together (list <named>)) - unique (set.of_list /.hash all)] - (n.= (list.size all) - (set.size unique))))))] + (`` (_.coverage [(~~ (template.spliced <part>))] + (let [all (list.together (list <named>)) + unique (set.of_list /.hash all)] + (n.= (list.size all) + (set.size unique))))))] <blocks> ) @@ -192,19 +192,19 @@ (_.for [/.block] (all _.and - (_.cover [/.start] - (n.= start - (/.start sample))) - (_.cover [/.end] - (n.= end - (/.end sample))) - (_.cover [/.size] - (n.= (++ additional) - (/.size sample))) - (_.cover [/.within?] - (and (/.within? sample inside) - (not (/.within? sample (-- (/.start sample)))) - (not (/.within? sample (++ (/.end sample)))))) + (_.coverage [/.start] + (n.= start + (/.start sample))) + (_.coverage [/.end] + (n.= end + (/.end sample))) + (_.coverage [/.size] + (n.= (++ additional) + (/.size sample))) + (_.coverage [/.within?] + (and (/.within? sample inside) + (not (/.within? sample (-- (/.start sample)))) + (not (/.within? sample (++ (/.end sample)))))) (~~ (template [<definition> <part>] [<definition>] diff --git a/stdlib/source/test/lux/data/text/unicode/set.lux b/stdlib/source/test/lux/data/text/unicode/set.lux index 11c1faa88..66b35626a 100644 --- a/stdlib/source/test/lux/data/text/unicode/set.lux +++ b/stdlib/source/test/lux/data/text/unicode/set.lux @@ -48,40 +48,40 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.set] - (and (n.= (block.start left) - (/.start (/.set [left (list)]))) - (n.= (block.end left) - (/.end (/.set [left (list)]))))) - (_.cover [/.start] - (n.= (n.min (block.start left) + (_.coverage [/.set] + (and (n.= (block.start left) + (/.start (/.set [left (list)]))) + (n.= (block.end left) + (/.end (/.set [left (list)]))))) + (_.coverage [/.start] + (n.= (n.min (block.start left) + (block.start right)) + (/.start (/.set [left (list right)])))) + (_.coverage [/.end] + (n.= (n.max (block.end left) + (block.end right)) + (/.end (/.set [left (list right)])))) + (_.coverage [/.member?] + (bit#= (block.within? block inside) + (/.member? (/.set [block (list)]) inside))) + (_.coverage [/.composite] + (let [composed (/.composite (/.set [left (list)]) + (/.set [right (list)]))] + (and (n.= (n.min (block.start left) (block.start right)) - (/.start (/.set [left (list right)])))) - (_.cover [/.end] + (/.start composed)) (n.= (n.max (block.end left) (block.end right)) - (/.end (/.set [left (list right)])))) - (_.cover [/.member?] - (bit#= (block.within? block inside) - (/.member? (/.set [block (list)]) inside))) - (_.cover [/.composite] - (let [composed (/.composite (/.set [left (list)]) - (/.set [right (list)]))] - (and (n.= (n.min (block.start left) - (block.start right)) - (/.start composed)) - (n.= (n.max (block.end left) - (block.end right)) - (/.end composed))))) + (/.end composed))))) (~~ (template [<set>] [(do random.monad [char (random.char <set>) .let [start (/.start <set>) end (/.end <set>)]] - (_.cover [<set>] - (and (/.member? <set> char) - (not (/.member? <set> (-- start))) - (not (/.member? <set> (++ end))))))] + (_.coverage [<set>] + (and (/.member? <set> char) + (not (/.member? <set> (-- start))) + (not (/.member? <set> (++ end))))))] [/.ascii] [/.alphabetic] diff --git a/stdlib/source/test/lux/debug.lux b/stdlib/source/test/lux/debug.lux index 79bc194a8..3965359b5 100644 --- a/stdlib/source/test/lux/debug.lux +++ b/stdlib/source/test/lux/debug.lux @@ -162,34 +162,34 @@ can_represent_complex_types! ..can_represent_complex_types can_represent_time_types! ..can_represent_time_types] (all _.and - (_.cover [/.representation] - (`` (and can_represent_simple_types! - can_represent_structure_types! - can_represent_complex_types! - can_represent_time_types! - - (|> (/.representation .Any sample_frac) - (try#each (text#= "[]")) - (try.else false)) - (|> (/.representation (type (List Nat)) (is (List Nat) (list sample_nat))) - (try#each (text#= (%.list %.nat (list sample_nat)))) - (try.else false)) - (~~ (template [<sample>] - [(|> (/.representation (type (Maybe Nat)) (is (Maybe Nat) <sample>)) - (try#each (text#= (%.maybe %.nat <sample>))) - (try.else false))] - - [{.#Some sample_nat}] - [{.#None}] - )) - ))) - (_.cover [/.cannot_represent_value] - (case (/.representation (-> Nat Nat) (|>>)) - {try.#Success representation} - false + (_.coverage [/.representation] + (`` (and can_represent_simple_types! + can_represent_structure_types! + can_represent_complex_types! + can_represent_time_types! + + (|> (/.representation .Any sample_frac) + (try#each (text#= "[]")) + (try.else false)) + (|> (/.representation (type (List Nat)) (is (List Nat) (list sample_nat))) + (try#each (text#= (%.list %.nat (list sample_nat)))) + (try.else false)) + (~~ (template [<sample>] + [(|> (/.representation (type (Maybe Nat)) (is (Maybe Nat) <sample>)) + (try#each (text#= (%.maybe %.nat <sample>))) + (try.else false))] + + [{.#Some sample_nat}] + [{.#None}] + )) + ))) + (_.coverage [/.cannot_represent_value] + (case (/.representation (-> Nat Nat) (|>>)) + {try.#Success representation} + false - {try.#Failure error} - (exception.match? /.cannot_represent_value error))) + {try.#Failure error} + (exception.match? /.cannot_represent_value error))) ))) (def: inspection @@ -199,22 +199,22 @@ sample_int random.int sample_frac random.frac sample_text (random.upper_case 10)] - (_.cover [/.inspection] - (`` (and (~~ (template [<format> <sample>] - [(text#= (<format> <sample>) (/.inspection <sample>))] + (_.coverage [/.inspection] + (`` (and (~~ (template [<format> <sample>] + [(text#= (<format> <sample>) (/.inspection <sample>))] - [%.bit sample_bit] - [%.int sample_int] - [%.frac sample_frac] - [%.text sample_text] - )) - (text#= (|> (list sample_bit sample_int sample_frac sample_text) - (is (List Any)) - (list#each /.inspection) - (text.interposed " ") - (text.enclosed ["[" "]"])) - (/.inspection [sample_bit sample_int sample_frac sample_text])) - ))))) + [%.bit sample_bit] + [%.int sample_int] + [%.frac sample_frac] + [%.text sample_text] + )) + (text#= (|> (list sample_bit sample_int sample_frac sample_text) + (is (List Any)) + (list#each /.inspection) + (text.interposed " ") + (text.enclosed ["[" "]"])) + (/.inspection [sample_bit sample_int sample_frac sample_text])) + ))))) (syntax: (macro_error [macro <code>.any]) (function (_ compiler) @@ -236,33 +236,33 @@ (all _.and ..inspection ..representation - (_.cover [/.hole /.type_hole] - (let [error (is My_Text (..macro_error (/.hole)))] - (and (exception.match? /.type_hole error) - (text.contains? (%.type My_Text) error)))) + (_.coverage [/.hole /.type_hole] + (let [error (is My_Text (..macro_error (/.hole)))] + (and (exception.match? /.type_hole error) + (text.contains? (%.type My_Text) error)))) (do random.monad [foo (random.upper_case 10) bar random.nat baz random.bit] - (_.cover [/.here] - (with_expansions [<no_parameters> (for @.js (~~ (these)) - (~~ (these (/.here))))] - (`` (exec - <no_parameters> - (/.here foo - [bar %.nat]) - true))))) - (_.cover [/.unknown_local_binding] - (exception.match? /.unknown_local_binding - (..macro_error (/.here yolo)))) - (_.cover [/.private] - (exec - (is (/.private /.Inspector) - /.inspection) - true)) - (_.cover [/.log!] - (exec - (/.log! (format (%.symbol (symbol /.log!)) - " works: " (%.text message))) - true)) + (_.coverage [/.here] + (with_expansions [<no_parameters> (for @.js (~~ (these)) + (~~ (these (/.here))))] + (`` (exec + <no_parameters> + (/.here foo + [bar %.nat]) + true))))) + (_.coverage [/.unknown_local_binding] + (exception.match? /.unknown_local_binding + (..macro_error (/.here yolo)))) + (_.coverage [/.private] + (exec + (is (/.private /.Inspector) + /.inspection) + true)) + (_.coverage [/.log!] + (exec + (/.log! (format (%.symbol (symbol /.log!)) + " works: " (%.text message))) + true)) )))) diff --git a/stdlib/source/test/lux/documentation.lux b/stdlib/source/test/lux/documentation.lux index c5b8620e4..684556ecf 100644 --- a/stdlib/source/test/lux/documentation.lux +++ b/stdlib/source/test/lux/documentation.lux @@ -51,70 +51,70 @@ (all _.and (_.for [/.Definition] (all _.and - (_.cover [/.default] - (case (`` (/.default (~~ (template.symbol [.._] [g!default])))) - (pattern (list definition)) - (and (|> definition - (the /.#definition) - (text#= (template.text [g!default]))) - (|> definition - (the /.#documentation) - md.markdown - (text#= "") - not)) + (_.coverage [/.default] + (case (`` (/.default (~~ (template.symbol [.._] [g!default])))) + (pattern (list definition)) + (and (|> definition + (the /.#definition) + (text#= (template.text [g!default]))) + (|> definition + (the /.#documentation) + md.markdown + (text#= "") + not)) - _ - false)) - (_.cover [/.documentation:] - (case ..documentation: - (pattern (list documentation:)) - (and (|> documentation: - (the /.#definition) - (text#= (template.text [/.documentation:]))) - (|> documentation: - (the /.#documentation) - md.markdown - (text.contains? 'definition_description'))) + _ + false)) + (_.coverage [/.documentation:] + (case ..documentation: + (pattern (list documentation:)) + (and (|> documentation: + (the /.#definition) + (text#= (template.text [/.documentation:]))) + (|> documentation: + (the /.#documentation) + md.markdown + (text.contains? 'definition_description'))) - _ - false)) + _ + false)) )) (_.for [/.Module] (all _.and - (_.cover [/.module /.documentation] - (let [sub (`` (/.module /._ - (~~ (template.text ['sub_description'])) - [] - [])) - super (`` (/.module .._ - (~~ (template.text ['super_description'])) - [..documentation:] - [sub]))] - (and (text.contains? (template.text ['sub_description']) - (/.documentation sub)) - (text.contains? (/.documentation sub) - (/.documentation super)) - (text.contains? (template.text ['super_description']) - (/.documentation super)) - (case ..documentation: - (pattern (list documentation:)) - (text.contains? (md.markdown (the /.#documentation documentation:)) - (/.documentation super)) + (_.coverage [/.module /.documentation] + (let [sub (`` (/.module /._ + (~~ (template.text ['sub_description'])) + [] + [])) + super (`` (/.module .._ + (~~ (template.text ['super_description'])) + [..documentation:] + [sub]))] + (and (text.contains? (template.text ['sub_description']) + (/.documentation sub)) + (text.contains? (/.documentation sub) + (/.documentation super)) + (text.contains? (template.text ['super_description']) + (/.documentation super)) + (case ..documentation: + (pattern (list documentation:)) + (text.contains? (md.markdown (the /.#documentation documentation:)) + (/.documentation super)) - _ - false)))) + _ + false)))) )) - (_.cover [/.unqualified_symbol] - (`` (and (~~ (template [<example>] - [(macro_error <example>)] - - [(/.default g!default)] - [(/.documentation: g!default - (~~ (template.text ['definition_description'])))] - [(/.module g!default - "" - [..documentation:] - [sub])] - ))))) + (_.coverage [/.unqualified_symbol] + (`` (and (~~ (template [<example>] + [(macro_error <example>)] + + [(/.default g!default)] + [(/.documentation: g!default + (~~ (template.text ['definition_description'])))] + [(/.module g!default + "" + [..documentation:] + [sub])] + ))))) ))))) ) diff --git a/stdlib/source/test/lux/extension.lux b/stdlib/source/test/lux/extension.lux index 4233cd956..5eb545463 100644 --- a/stdlib/source/test/lux/extension.lux +++ b/stdlib/source/test/lux/extension.lux @@ -188,19 +188,19 @@ [expected random.nat] (`` (all _.and (~~ (template [<macro> <extension>] - [(_.cover [<macro>] - (for @.old false - (n.= expected - (`` ((~~ (static <extension>)) expected)))))] + [(_.coverage [<macro>] + (for @.old false + (n.= expected + (`` ((~~ (static <extension>)) expected)))))] [/.analysis: ..analysis] [/.synthesis: ..synthesis])) - (_.cover [/.generation:] - (for @.old false - (and (n.= expected - (`` ((~~ (static ..generation)) expected))) - (text#= ..dummy_generation - (`` ((~~ (static ..dummy_generation)))))))) - (_.cover [/.directive:] - true) + (_.coverage [/.generation:] + (for @.old false + (and (n.= expected + (`` ((~~ (static ..generation)) expected))) + (text#= ..dummy_generation + (`` ((~~ (static ..dummy_generation)))))))) + (_.coverage [/.directive:] + true) ))))) diff --git a/stdlib/source/test/lux/ffi.js.lux b/stdlib/source/test/lux/ffi.js.lux index d1ab5636a..e8fcd24f8 100644 --- a/stdlib/source/test/lux/ffi.js.lux +++ b/stdlib/source/test/lux/ffi.js.lux @@ -60,10 +60,10 @@ (<| (_.covering /._) (`` (all _.and (~~ (template [<type> <value>] - [(_.cover [<type>] - (exec - (is <type> <value>) - true))] + [(_.coverage [<type>] + (exec + (is <type> <value>) + true))] [/.Boolean boolean] [/.Number number] @@ -72,12 +72,12 @@ (_.for [/.Object] (all _.and (~~ (template [<type>] - [(_.cover [<type>] - (exec - (is (Ex (_ a) (/.Object a)) - (is <type> - (as_expected []))) - true))] + [(_.coverage [<type>] + (exec + (is (Ex (_ a) (/.Object a)) + (is <type> + (as_expected []))) + true))] [/.Function] [/.Symbol] @@ -85,64 +85,64 @@ [/.Undefined] )) )) - (_.cover [/.null] - (exec - (is Nat (/.null [])) - (is Text (/.null [])) - (is (All (_ a) (-> a a)) (/.null [])) - true)) - (_.cover [/.null?] - (and (/.null? (/.null [])) - (not (/.null? 0)) - (not (/.null? "0")) - (not (/.null? (|>>))))) - (_.cover [/.global] - (|> (/.global /.Function [parseFloat]) - "js object null?" - not)) - (_.cover [/.function] - (|> (/.function (_ [input/0 Nat]) - Int - (.int input/0)) - "js object null?" - not)) - (_.cover [/.on_browser? /.on_node_js? /.on_nashorn?] - (and (or /.on_nashorn? + (_.coverage [/.null] + (exec + (is Nat (/.null [])) + (is Text (/.null [])) + (is (All (_ a) (-> a a)) (/.null [])) + true)) + (_.coverage [/.null?] + (and (/.null? (/.null [])) + (not (/.null? 0)) + (not (/.null? "0")) + (not (/.null? (|>>))))) + (_.coverage [/.global] + (|> (/.global /.Function [parseFloat]) + "js object null?" + not)) + (_.coverage [/.function] + (|> (/.function (_ [input/0 Nat]) + Int + (.int input/0)) + "js object null?" + not)) + (_.coverage [/.on_browser? /.on_node_js? /.on_nashorn?] + (and (or /.on_nashorn? + /.on_node_js? + /.on_browser?) + (bit#= /.on_nashorn? + (not (or /.on_node_js? + /.on_browser?))) + (bit#= /.on_node_js? + (not (or /.on_nashorn? + /.on_browser?))) + (bit#= /.on_browser? + (not (or /.on_nashorn? + /.on_node_js?))))) + (_.coverage [/.type_of] + (and (text#= "boolean" (/.type_of boolean)) + (text#= "number" (/.type_of number)) + (text#= "string" (/.type_of string)) + (text#= "function" (/.type_of function)) + (text#= "object" (/.type_of object)))) + (_.coverage [/.import:] + (let [encoding "utf8"] + (text#= string + (cond /.on_nashorn? + (let [binary (java/lang/String::getBytes encoding (as java/lang/String string))] + (|> (java/lang/String::new binary encoding) + (as Text))) + /.on_node_js? - /.on_browser?) - (bit#= /.on_nashorn? - (not (or /.on_node_js? - /.on_browser?))) - (bit#= /.on_node_js? - (not (or /.on_nashorn? - /.on_browser?))) - (bit#= /.on_browser? - (not (or /.on_nashorn? - /.on_node_js?))))) - (_.cover [/.type_of] - (and (text#= "boolean" (/.type_of boolean)) - (text#= "number" (/.type_of number)) - (text#= "string" (/.type_of string)) - (text#= "function" (/.type_of function)) - (text#= "object" (/.type_of object)))) - (_.cover [/.import:] - (let [encoding "utf8"] - (text#= string - (cond /.on_nashorn? - (let [binary (java/lang/String::getBytes encoding (as java/lang/String string))] - (|> (java/lang/String::new binary encoding) - (as Text))) - - /.on_node_js? - (|> (Buffer::from string encoding) - (Buffer::toString encoding)) - - ... On the browser - (let [binary (|> (TextEncoder::new encoding) - (TextEncoder::encode string))] - (|> (TextDecoder::new encoding) - (TextDecoder::decode binary))) - )))) + (|> (Buffer::from string encoding) + (Buffer::toString encoding)) + + ... On the browser + (let [binary (|> (TextEncoder::new encoding) + (TextEncoder::encode string))] + (|> (TextDecoder::new encoding) + (TextDecoder::decode binary))) + )))) $/export.test ))))) diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux index 6f8490ef9..9b842641e 100644 --- a/stdlib/source/test/lux/ffi.jvm.lux +++ b/stdlib/source/test/lux/ffi.jvm.lux @@ -94,10 +94,10 @@ (# ! each (|>> /.as_float)))] (`` (all _.and (~~ (template [<sample> <=> <to> <from>] - [(_.cover [<to> <from>] - (or (|> <sample> <to> <from> (<=> <sample>)) - (let [capped (|> <sample> <to> <from>)] - (|> capped <to> <from> (<=> capped)))))] + [(_.coverage [<to> <from>] + (or (|> <sample> <to> <from> (<=> <sample>)) + (let [capped (|> <sample> <to> <from>)] + (|> capped <to> <from> (<=> capped)))))] [long long#= /.long_to_byte /.byte_to_long] [long long#= /.long_to_short /.short_to_long] @@ -124,24 +124,24 @@ idx (|> random.nat (# ! each (n.% size))) value (# ! each (|>> /.as_long) random.int)] (all _.and - (_.cover [/.array /.length] - (|> size - (/.array java/lang/Long) - /.length - (n.= size))) - (_.cover [/.write! /.read!] - (|> (/.array java/lang/Long size) - (/.write! idx value) - (/.read! idx) - /.of_long - (i.= (/.of_long value)))) - (_.cover [/.cannot_convert_to_jvm_type] - (let [array (as (Array Nothing) - (array.empty 1))] - (|> array - /.length - ..macro_error - (text.contains? (the exception.#label /.cannot_convert_to_jvm_type)))))))) + (_.coverage [/.array /.length] + (|> size + (/.array java/lang/Long) + /.length + (n.= size))) + (_.coverage [/.write! /.read!] + (|> (/.array java/lang/Long size) + (/.write! idx value) + (/.read! idx) + /.of_long + (i.= (/.of_long value)))) + (_.coverage [/.cannot_convert_to_jvm_type] + (let [array (as (Array Nothing) + (array.empty 1))] + (|> array + /.length + ..macro_error + (text.contains? (the exception.#label /.cannot_convert_to_jvm_type)))))))) (def: for_miscellaneous Test @@ -165,52 +165,52 @@ bit/0 random.bit] (all _.and - (_.cover [/.as] - (and (case (/.as java/lang/String sample) {.#Some _} true {.#None} false) - (case (/.as java/lang/Long sample) {.#Some _} false {.#None} true) - (case (/.as java/lang/Object sample) {.#Some _} true {.#None} false) - (case (/.as java/lang/Object (/.null)) {.#Some _} false {.#None} true))) - (_.cover [/.synchronized] - (/.synchronized sample #1)) - (_.cover [/.class_for] - (text#= "java.lang.Class" (/.of_string (java/lang/Class::getName (/.class_for java/lang/Class))))) - (_.cover [/.null /.null?] - (and (/.null? (/.null)) - (not (/.null? sample)))) - (_.cover [/.???] - (and (|> (/.??? (/.null)) - (is (Maybe java/lang/Object)) - (pipe.case - {.#None} #1 - {.#Some _} #0)) - (|> (/.??? sample) - (is (Maybe java/lang/Object)) - (pipe.case - {.#Some _} #1 - {.#None} #0)))) - (_.cover [/.!!!] - (and (|> (/.??? (/.null)) - /.!!! - /.null?) - (|> (/.??? sample) - /.!!! - /.null? - not))) + (_.coverage [/.as] + (and (case (/.as java/lang/String sample) {.#Some _} true {.#None} false) + (case (/.as java/lang/Long sample) {.#Some _} false {.#None} true) + (case (/.as java/lang/Object sample) {.#Some _} true {.#None} false) + (case (/.as java/lang/Object (/.null)) {.#Some _} false {.#None} true))) + (_.coverage [/.synchronized] + (/.synchronized sample #1)) + (_.coverage [/.class_for] + (text#= "java.lang.Class" (/.of_string (java/lang/Class::getName (/.class_for java/lang/Class))))) + (_.coverage [/.null /.null?] + (and (/.null? (/.null)) + (not (/.null? sample)))) + (_.coverage [/.???] + (and (|> (/.??? (/.null)) + (is (Maybe java/lang/Object)) + (pipe.case + {.#None} #1 + {.#Some _} #0)) + (|> (/.??? sample) + (is (Maybe java/lang/Object)) + (pipe.case + {.#Some _} #1 + {.#None} #0)))) + (_.coverage [/.!!!] + (and (|> (/.??? (/.null)) + /.!!! + /.null?) + (|> (/.??? sample) + /.!!! + /.null? + not))) (~~ (template [<object> <primitive> <jvm#value> <jvm#=> <lux#value> <as> <of> <lux#=>] - [(_.cover [<object> <primitive>] - (|> <jvm#value> - (is <object>) - "jvm object cast" - (is <primitive>) - "jvm object cast" - (is <object>) - (<jvm#=> <jvm#value>))) - (_.cover [<as> <of>] - (|> <lux#value> - <as> - <of> - (<lux#=> <lux#value>)))] + [(_.coverage [<object> <primitive>] + (|> <jvm#value> + (is <object>) + "jvm object cast" + (is <primitive>) + "jvm object cast" + (is <object>) + (<jvm#=> <jvm#value>))) + (_.coverage [<as> <of>] + (|> <lux#value> + <as> + <of> + (<lux#=> <lux#value>)))] [/.Boolean /.boolean boolean boolean#= bit/0 /.as_boolean /.of_boolean bit#=] @@ -229,36 +229,36 @@ [/.Character /.char character character#= (/.of_char character) /.as_char /.of_char i#=] )) - (_.cover [/.as_string /.of_string] - (let [it (/.of_string string)] - (|> it - /.as_string - /.of_string - (text#= it)))) - (_.cover [/.cannot_cast_to_non_object] - (text.contains? (the exception.#label /.cannot_cast_to_non_object) - (macro_error (/.is boolean (is /.Boolean boolean))))) - (_.cover [/.is] - (|> string - (/.is java/lang/Object) - (same? (as java/lang/Object string)))) - (_.cover [/.type] - (and (and (type#= /.Boolean (/.type java/lang/Boolean)) - (type#= /.Boolean (/.type boolean))) - (and (type#= /.Byte (/.type java/lang/Byte)) - (type#= /.Byte (/.type byte))) - (and (type#= /.Short (/.type java/lang/Short)) - (type#= /.Short (/.type short))) - (and (type#= /.Integer (/.type java/lang/Integer)) - (type#= /.Integer (/.type int))) - (and (type#= /.Long (/.type java/lang/Long)) - (type#= /.Long (/.type long))) - (and (type#= /.Float (/.type java/lang/Float)) - (type#= /.Float (/.type float))) - (and (type#= /.Double (/.type java/lang/Double)) - (type#= /.Double (/.type double))) - (and (type#= /.Character (/.type java/lang/Character)) - (type#= /.Character (/.type char))))) + (_.coverage [/.as_string /.of_string] + (let [it (/.of_string string)] + (|> it + /.as_string + /.of_string + (text#= it)))) + (_.coverage [/.cannot_cast_to_non_object] + (text.contains? (the exception.#label /.cannot_cast_to_non_object) + (macro_error (/.is boolean (is /.Boolean boolean))))) + (_.coverage [/.is] + (|> string + (/.is java/lang/Object) + (same? (as java/lang/Object string)))) + (_.coverage [/.type] + (and (and (type#= /.Boolean (/.type java/lang/Boolean)) + (type#= /.Boolean (/.type boolean))) + (and (type#= /.Byte (/.type java/lang/Byte)) + (type#= /.Byte (/.type byte))) + (and (type#= /.Short (/.type java/lang/Short)) + (type#= /.Short (/.type short))) + (and (type#= /.Integer (/.type java/lang/Integer)) + (type#= /.Integer (/.type int))) + (and (type#= /.Long (/.type java/lang/Long)) + (type#= /.Long (/.type long))) + (and (type#= /.Float (/.type java/lang/Float)) + (type#= /.Float (/.type float))) + (and (type#= /.Double (/.type java/lang/Double)) + (type#= /.Double (/.type double))) + (and (type#= /.Character (/.type java/lang/Character)) + (type#= /.Character (/.type char))))) )))) (/.interface: test/TestInterface0 @@ -368,12 +368,12 @@ (/.of_long actual_right)))))] (i.= expected (/.of_long (test/TestInterface4::actual4 left right object/4))))]] - (_.cover [/.interface: /.object] - (and example/0! - example/1! - example/2! - example/3! - example/4!)))) + (_.coverage [/.interface: /.object] + (and example/0! + example/1! + example/2! + example/3! + example/4!)))) (/.class: "final" test/TestClass0 [test/TestInterface0] ... Fields @@ -601,17 +601,17 @@ /.as_long (same? dummy/2))]] (all _.and - (_.cover [/.class: /.import:] - (and example/0! - example/1! - example/2! - example/3! - example/4! - example/5! - example/7! - example_8!)) - (_.cover [/.do_to] - example/9!) + (_.coverage [/.class: /.import:] + (and example/0! + example/1! + example/2! + example/3! + example/4! + example/5! + example/7! + example_8!)) + (_.coverage [/.do_to] + example/9!) ))) (syntax: (expands? [expression <code>.any]) @@ -636,34 +636,34 @@ var/1 (random.lower_case 2) var/2 (random.lower_case 3)] (all _.and - (_.cover [/.class_names_cannot_contain_periods] - (with_expansions [<class> (template.symbol ["java.lang.Float"])] - (not (expands? (/.import: <class>))))) - (_.cover [/.class_name_cannot_be_a_type_variable] - (and (not (expands? (/.import: (java/lang/Double a) - "[1]::[0]" - (invalid [] (a java/lang/String))))) - (not (expands? (/.import: java/lang/Double - "[1]::[0]" - ([a] invalid [] (a java/lang/String))))))) - (_.cover [/.unknown_type_variable] - (let [type_variable ((debug.private /.type_variable) (list (jvm.var var/0) (jvm.var var/1)))] - (and (|> (list (code.local var/0)) - (<code>.result type_variable) - (try#each (|>> (jvm#= (jvm.var var/0)))) - (try.else false)) - (|> (list (code.local var/1)) - (<code>.result type_variable) - (try#each (|>> (jvm#= (jvm.var var/1)))) - (try.else false)) - (|> (list (code.local var/2)) - (<code>.result type_variable) - (pipe.case - {try.#Failure error} - (exception.match? /.unknown_type_variable error) - - _ - false))))) + (_.coverage [/.class_names_cannot_contain_periods] + (with_expansions [<class> (template.symbol ["java.lang.Float"])] + (not (expands? (/.import: <class>))))) + (_.coverage [/.class_name_cannot_be_a_type_variable] + (and (not (expands? (/.import: (java/lang/Double a) + "[1]::[0]" + (invalid [] (a java/lang/String))))) + (not (expands? (/.import: java/lang/Double + "[1]::[0]" + ([a] invalid [] (a java/lang/String))))))) + (_.coverage [/.unknown_type_variable] + (let [type_variable ((debug.private /.type_variable) (list (jvm.var var/0) (jvm.var var/1)))] + (and (|> (list (code.local var/0)) + (<code>.result type_variable) + (try#each (|>> (jvm#= (jvm.var var/0)))) + (try.else false)) + (|> (list (code.local var/1)) + (<code>.result type_variable) + (try#each (|>> (jvm#= (jvm.var var/1)))) + (try.else false)) + (|> (list (code.local var/2)) + (<code>.result type_variable) + (pipe.case + {try.#Failure error} + (exception.match? /.unknown_type_variable error) + + _ + false))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/ffi.lua.lux b/stdlib/source/test/lux/ffi.lua.lux index 3e5894ff2..76ea6d2f3 100644 --- a/stdlib/source/test/lux/ffi.lua.lux +++ b/stdlib/source/test/lux/ffi.lua.lux @@ -25,10 +25,10 @@ (<| (_.covering /._) (`` (all _.and (~~ (template [<type> <sample>] - [(_.cover [<type>] - (exec - (is <type> <sample>) - true))] + [(_.coverage [<type>] + (exec + (is <type> <sample>) + true))] [/.Boolean boolean] [/.Integer integer] @@ -38,28 +38,28 @@ (_.for [/.Object] (all _.and (~~ (template [<type>] - [(_.cover [<type>] - (exec - (|> [] - (as <type>) - (is (Ex (_ a) (/.Object a)))) - true))] + [(_.coverage [<type>] + (exec + (|> [] + (as <type>) + (is (Ex (_ a) (/.Object a)))) + true))] [/.Nil] [/.Table] )))) - (_.cover [/.Function /.function] - (exec - (|> (/.function (_ [input/0 Nat]) - Int - (.int input/0)) - (is /.Function) - (is (Ex (_ a) (/.Object a)))) - true)) - (_.cover [/.import:] - (case (io.run! (..os/getenv string)) - {.#Some _} true - {.#None} true)) + (_.coverage [/.Function /.function] + (exec + (|> (/.function (_ [input/0 Nat]) + Int + (.int input/0)) + (is /.Function) + (is (Ex (_ a) (/.Object a)))) + true)) + (_.coverage [/.import:] + (case (io.run! (..os/getenv string)) + {.#Some _} true + {.#None} true)) $/export.test ))))) diff --git a/stdlib/source/test/lux/ffi.old.lux b/stdlib/source/test/lux/ffi.old.lux index 6b6bc0f34..3e397ad8c 100644 --- a/stdlib/source/test/lux/ffi.old.lux +++ b/stdlib/source/test/lux/ffi.old.lux @@ -101,10 +101,10 @@ (# ! each (|>> /.double_to_float)))] (`` (all _.and (~~ (template [<=> <sample> <to> <from>] - [(_.cover [<to> <from>] - (or (|> <sample> <to> <from> (<=> <sample>)) - (let [capped (|> <sample> <to> <from>)] - (|> capped <to> <from> (<=> capped)))))] + [(_.coverage [<to> <from>] + (or (|> <sample> <to> <from> (<=> <sample>)) + (let [capped (|> <sample> <to> <from>)] + (|> capped <to> <from> (<=> capped)))))] [i.= long /.long_to_byte /.byte_to_long] [i.= long /.long_to_short /.short_to_long] @@ -116,44 +116,44 @@ [f.= double /.double_to_int /.int_to_double] )) (~~ (template [<to> <from>] - [(_.cover [<to>] - (or (|> int <to> <from> (i.= (/.int_to_long int))) - (let [capped (|> int <to> <from>)] - (|> capped /.long_to_int <to> <from> (i.= capped)))))] + [(_.coverage [<to>] + (or (|> int <to> <from> (i.= (/.int_to_long int))) + (let [capped (|> int <to> <from>)] + (|> capped /.long_to_int <to> <from> (i.= capped)))))] [/.int_to_byte /.byte_to_long] [/.int_to_short /.short_to_long] [/.int_to_char /.char_to_long] )) (~~ (template [<sample> <to> <from>] - [(_.cover [<to> <from>] - (or (|> <sample> <to> <from> /.float_to_double (f.= (/.float_to_double <sample>))) - (let [capped (|> <sample> <to> <from>)] - (|> capped <to> <from> /.float_to_double (f.= (/.float_to_double capped))))))] + [(_.coverage [<to> <from>] + (or (|> <sample> <to> <from> /.float_to_double (f.= (/.float_to_double <sample>))) + (let [capped (|> <sample> <to> <from>)] + (|> capped <to> <from> /.float_to_double (f.= (/.float_to_double capped))))))] [float /.float_to_int /.int_to_float] )) (~~ (template [<to> <from>] - [(_.cover [<to>] - (or (|> char <to> <from> (i.= (|> char /.char_to_int /.int_to_long))) - (let [capped (|> char <to> <from>)] - (|> capped /.long_to_int /.int_to_char <to> <from> (i.= capped)))))] + [(_.coverage [<to>] + (or (|> char <to> <from> (i.= (|> char /.char_to_int /.int_to_long))) + (let [capped (|> char <to> <from>)] + (|> capped /.long_to_int /.int_to_char <to> <from> (i.= capped)))))] [/.char_to_byte /.byte_to_long] [/.char_to_short /.short_to_long] )) - (_.cover [/.char_to_long] - (with_expansions [<to> /.int_to_char - <from> /.char_to_long] - (`` (or (|> int <to> <from> (i.= (/.int_to_long int))) - (let [capped (|> int <to> <from>)] - (|> capped /.long_to_int <to> <from> (i.= capped))))))) - (_.cover [/.char_to_int] - (with_expansions [<to> /.int_to_char - <from> /.char_to_int] - (`` (or (|> int <to> <from> /.int_to_long (i.= (/.int_to_long int))) - (let [capped (|> int <to> <from>)] - (|> capped <to> <from> /.int_to_long (i.= (/.int_to_long capped)))))))) + (_.coverage [/.char_to_long] + (with_expansions [<to> /.int_to_char + <from> /.char_to_long] + (`` (or (|> int <to> <from> (i.= (/.int_to_long int))) + (let [capped (|> int <to> <from>)] + (|> capped /.long_to_int <to> <from> (i.= capped))))))) + (_.coverage [/.char_to_int] + (with_expansions [<to> /.int_to_char + <from> /.char_to_int] + (`` (or (|> int <to> <from> /.int_to_long (i.= (/.int_to_long int))) + (let [capped (|> int <to> <from>)] + (|> capped <to> <from> /.int_to_long (i.= (/.int_to_long capped)))))))) )))) (def: arrays @@ -163,13 +163,13 @@ idx (|> random.nat (# ! each (n.% size))) value random.int] (all _.and - (_.cover [/.array /.length] - (n.= size (/.length (/.array java/lang/Long size)))) - (_.cover [/.write! /.read!] - (|> (/.array java/lang/Long size) - (/.write! idx value) - (/.read! idx) - (i.= value))) + (_.coverage [/.array /.length] + (n.= size (/.length (/.array java/lang/Long size)))) + (_.coverage [/.write! /.read!] + (|> (/.array java/lang/Long size) + (/.write! idx value) + (/.read! idx) + (i.= value))) ))) (def: null @@ -177,21 +177,21 @@ (do random.monad [sample (random.ascii 1)] (all _.and - (_.cover [/.null /.null?] - (and (/.null? (/.null)) - (not (/.null? sample)))) - (_.cover [/.???] - (and (|> (is (Maybe java/lang/Object) (/.??? (/.null))) - (pipe.case - {.#None} #1 - _ #0)) - (|> (is (Maybe java/lang/Object) (/.??? sample)) - (pipe.case - {.#Some _} #1 - _ #0)))) - (_.cover [/.!!!] - (and (/.null? (/.!!! (/.??? (/.null)))) - (not (/.null? (/.!!! (/.??? sample)))))) + (_.coverage [/.null /.null?] + (and (/.null? (/.null)) + (not (/.null? sample)))) + (_.coverage [/.???] + (and (|> (is (Maybe java/lang/Object) (/.??? (/.null))) + (pipe.case + {.#None} #1 + _ #0)) + (|> (is (Maybe java/lang/Object) (/.??? sample)) + (pipe.case + {.#Some _} #1 + _ #0)))) + (_.coverage [/.!!!] + (and (/.null? (/.!!! (/.??? (/.null)))) + (not (/.null? (/.!!! (/.??? sample)))))) ))) (def: miscellaneous @@ -201,36 +201,36 @@ counter random.int increase random.int] (all _.and - (_.cover [/.as] - (and (case (/.as java/lang/String sample) {.#Some _} true {.#None} false) - (case (/.as java/lang/Long sample) {.#Some _} false {.#None} true) - (case (/.as java/lang/Object sample) {.#Some _} true {.#None} false) - (case (/.as java/lang/Object (/.null)) {.#Some _} false {.#None} true))) - (_.cover [/.synchronized] - (/.synchronized sample #1)) - (_.cover [/.class_for /.import:] - (|> (/.class_for java/lang/Class) - java/lang/Class::getName - (text#= "java.lang.Class"))) - (_.cover [/.class: /.do_to] - (|> (/.do_to (test/lux/ffi/TestClass::new increase counter) - (test/lux/ffi/TestClass::upC) - (test/lux/ffi/TestClass::upC) - (test/lux/ffi/TestClass::downC)) - test/lux/ffi/TestClass::currentC - (i.= (i.+ increase counter)))) - (_.cover [/.interface: /.object] - (|> (..test_object increase counter) - test/lux/ffi/TestInterface::up - test/lux/ffi/TestInterface::up - test/lux/ffi/TestInterface::down - test/lux/ffi/TestInterface::current - (i.= (i.+ increase counter)))) - (_.cover [/.type] - (and (type#= (Primitive "java.lang.Char") - (/.type java/lang/Char)) - (type#= (Primitive "java.util.List" [(Primitive "java.lang.Byte")]) - (/.type (java/util/List java/lang/Byte))))) + (_.coverage [/.as] + (and (case (/.as java/lang/String sample) {.#Some _} true {.#None} false) + (case (/.as java/lang/Long sample) {.#Some _} false {.#None} true) + (case (/.as java/lang/Object sample) {.#Some _} true {.#None} false) + (case (/.as java/lang/Object (/.null)) {.#Some _} false {.#None} true))) + (_.coverage [/.synchronized] + (/.synchronized sample #1)) + (_.coverage [/.class_for /.import:] + (|> (/.class_for java/lang/Class) + java/lang/Class::getName + (text#= "java.lang.Class"))) + (_.coverage [/.class: /.do_to] + (|> (/.do_to (test/lux/ffi/TestClass::new increase counter) + (test/lux/ffi/TestClass::upC) + (test/lux/ffi/TestClass::upC) + (test/lux/ffi/TestClass::downC)) + test/lux/ffi/TestClass::currentC + (i.= (i.+ increase counter)))) + (_.coverage [/.interface: /.object] + (|> (..test_object increase counter) + test/lux/ffi/TestInterface::up + test/lux/ffi/TestInterface::up + test/lux/ffi/TestInterface::down + test/lux/ffi/TestInterface::current + (i.= (i.+ increase counter)))) + (_.coverage [/.type] + (and (type#= (Primitive "java.lang.Char") + (/.type java/lang/Char)) + (type#= (Primitive "java.util.List" [(Primitive "java.lang.Byte")]) + (/.type (java/util/List java/lang/Byte))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/ffi.php.lux b/stdlib/source/test/lux/ffi.php.lux index 7205a4b3c..ae182a90e 100644 --- a/stdlib/source/test/lux/ffi.php.lux +++ b/stdlib/source/test/lux/ffi.php.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try]] - [data - ["[0]" text ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["[0]" nat] - ["[0]" frac]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try]] + [data + ["[0]" text ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["[0]" nat] + ["[0]" frac]]]]] + [\\library + ["[0]" /]]) (def: .public test Test (do [! random.monad] [] (<| (_.covering /._) - (_.test "TBD" - true)))) + (_.property "TBD" + true)))) diff --git a/stdlib/source/test/lux/ffi.py.lux b/stdlib/source/test/lux/ffi.py.lux index d28f19138..edef790f9 100644 --- a/stdlib/source/test/lux/ffi.py.lux +++ b/stdlib/source/test/lux/ffi.py.lux @@ -28,10 +28,10 @@ (<| (_.covering /._) (`` (all _.and (~~ (template [<type> <sample>] - [(_.cover [<type>] - (exec - (is <type> <sample>) - true))] + [(_.coverage [<type>] + (exec + (is <type> <sample>) + true))] [/.Boolean boolean] [/.Integer integer] @@ -41,27 +41,27 @@ (_.for [/.Object] (all _.and (~~ (template [<type>] - [(_.cover [<type>] - (exec - (|> [] - (as <type>) - (is (Ex (_ a) (/.Object a)))) - true))] + [(_.coverage [<type>] + (exec + (|> [] + (as <type>) + (is (Ex (_ a) (/.Object a)))) + true))] [/.None] [/.Dict] )))) - (_.cover [/.Function /.function] - (exec - (|> (/.function (_ [input/0 Nat]) - Int - (.int input/0)) - (is /.Function) - (is (Ex (_ a) (/.Object a)))) - true)) - (_.cover [/.import:] - (and (i.= (os::R_OK) (os::R_OK)) - (not (i.= (os::W_OK) (os::R_OK))))) + (_.coverage [/.Function /.function] + (exec + (|> (/.function (_ [input/0 Nat]) + Int + (.int input/0)) + (is /.Function) + (is (Ex (_ a) (/.Object a)))) + true)) + (_.coverage [/.import:] + (and (i.= (os::R_OK) (os::R_OK)) + (not (i.= (os::W_OK) (os::R_OK))))) $/export.test ))))) diff --git a/stdlib/source/test/lux/ffi.rb.lux b/stdlib/source/test/lux/ffi.rb.lux index 8e08fa744..c12690d67 100644 --- a/stdlib/source/test/lux/ffi.rb.lux +++ b/stdlib/source/test/lux/ffi.rb.lux @@ -25,10 +25,10 @@ (<| (_.covering /._) (`` (all _.and (~~ (template [<type> <sample>] - [(_.cover [<type>] - (exec - (is <type> <sample>) - true))] + [(_.coverage [<type>] + (exec + (is <type> <sample>) + true))] [/.Boolean boolean] [/.Integer integer] @@ -38,19 +38,19 @@ (_.for [/.Object] (all _.and (~~ (template [<type>] - [(_.cover [<type>] - (exec - (|> [] - (as <type>) - (is (Ex (_ a) (/.Object a)))) - true))] + [(_.coverage [<type>] + (exec + (|> [] + (as <type>) + (is (Ex (_ a) (/.Object a)))) + true))] [/.Nil] [/.Function] )))) - (_.cover [/.import:] - (same? (..File::SEPARATOR) - (..File::SEPARATOR))) + (_.coverage [/.import:] + (same? (..File::SEPARATOR) + (..File::SEPARATOR))) $/export.test ))))) diff --git a/stdlib/source/test/lux/ffi.scm.lux b/stdlib/source/test/lux/ffi.scm.lux index 7205a4b3c..ae182a90e 100644 --- a/stdlib/source/test/lux/ffi.scm.lux +++ b/stdlib/source/test/lux/ffi.scm.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}]] - [control - ["[0]" try]] - [data - ["[0]" text ("[1]#[0]" equivalence)]] - [math - ["[0]" random {"+" Random}] - [number - ["[0]" nat] - ["[0]" frac]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}]] + [control + ["[0]" try]] + [data + ["[0]" text ("[1]#[0]" equivalence)]] + [math + ["[0]" random {"+" Random}] + [number + ["[0]" nat] + ["[0]" frac]]]]] + [\\library + ["[0]" /]]) (def: .public test Test (do [! random.monad] [] (<| (_.covering /._) - (_.test "TBD" - true)))) + (_.property "TBD" + true)))) diff --git a/stdlib/source/test/lux/ffi/export.js.lux b/stdlib/source/test/lux/ffi/export.js.lux index 16eab39bb..20bd74c34 100644 --- a/stdlib/source/test/lux/ffi/export.js.lux +++ b/stdlib/source/test/lux/ffi/export.js.lux @@ -26,8 +26,8 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.export:] - (and (n.= <nat> ..constant) - (n.= (n.+ <nat> <nat>) (..shift <nat>)))) + (_.coverage [/.export:] + (and (n.= <nat> ..constant) + (n.= (n.+ <nat> <nat>) (..shift <nat>)))) ))) ) diff --git a/stdlib/source/test/lux/ffi/export.jvm.lux b/stdlib/source/test/lux/ffi/export.jvm.lux index c407a9c43..bb8d092ce 100644 --- a/stdlib/source/test/lux/ffi/export.jvm.lux +++ b/stdlib/source/test/lux/ffi/export.jvm.lux @@ -141,46 +141,46 @@ [string //.as_string (random.lower_case 1)] ))] (all _.and - (_.cover [/.export:] - (and (bit#= (//.of_boolean ..expected_boolean) (//.of_boolean (Primitives::actual_boolean))) - (int#= (//.of_byte ..expected_byte) (//.of_byte (Primitives::actual_byte))) - (int#= (//.of_short ..expected_short) (//.of_short (Primitives::actual_short))) - (int#= (//.of_int ..expected_int) (//.of_int (Primitives::actual_int))) - (int#= (//.of_long ..expected_long) (//.of_long (Primitives::actual_long))) - (int#= (//.of_char ..expected_char) (//.of_char (Primitives::actual_char))) - (frac#= (//.of_float ..expected_float) (//.of_float (Primitives::actual_float))) - (frac#= (//.of_double ..expected_double) (//.of_double (Primitives::actual_double))) - - (~~ (template [<=> <+> <type>] - [(with_expansions [<left> (template.symbol ["left_" <type>]) - <right> (template.symbol ["right_" <type>]) - <of> (template.symbol [//._] ["of_" <type>]) - <method> (template.symbol ["Primitives::" <type> "_method"])] - (<=> (<+> (<of> <left>) (<of> <right>)) - (<of> (<method> <left> <right>))))] - - [bit#= and boolean] - [int#= int.+ byte] - [int#= int.+ short] - [int#= int.+ int] - [int#= int.+ long] - [int#= int.+ char] - [frac#= frac.+ float] - [frac#= frac.+ double] - )) - - (text#= (//.of_string ..expected_string) (//.of_string (Objects::actual_string))) - - (text#= (%.format (//.of_string left_string) (//.of_string right_string)) - (//.of_string (Objects::string_method left_string right_string))) - - (text#= (//.of_string left_string) - (//.of_string (Objects::left left_string right_string))) - (text#= (//.of_string right_string) - (//.of_string (Objects::right left_string right_string))) - (int#= (//.of_long left_long) - (//.of_long (Objects::left left_long right_long))) - (int#= (//.of_long right_long) - (//.of_long (Objects::right left_long right_long))) - )) + (_.coverage [/.export:] + (and (bit#= (//.of_boolean ..expected_boolean) (//.of_boolean (Primitives::actual_boolean))) + (int#= (//.of_byte ..expected_byte) (//.of_byte (Primitives::actual_byte))) + (int#= (//.of_short ..expected_short) (//.of_short (Primitives::actual_short))) + (int#= (//.of_int ..expected_int) (//.of_int (Primitives::actual_int))) + (int#= (//.of_long ..expected_long) (//.of_long (Primitives::actual_long))) + (int#= (//.of_char ..expected_char) (//.of_char (Primitives::actual_char))) + (frac#= (//.of_float ..expected_float) (//.of_float (Primitives::actual_float))) + (frac#= (//.of_double ..expected_double) (//.of_double (Primitives::actual_double))) + + (~~ (template [<=> <+> <type>] + [(with_expansions [<left> (template.symbol ["left_" <type>]) + <right> (template.symbol ["right_" <type>]) + <of> (template.symbol [//._] ["of_" <type>]) + <method> (template.symbol ["Primitives::" <type> "_method"])] + (<=> (<+> (<of> <left>) (<of> <right>)) + (<of> (<method> <left> <right>))))] + + [bit#= and boolean] + [int#= int.+ byte] + [int#= int.+ short] + [int#= int.+ int] + [int#= int.+ long] + [int#= int.+ char] + [frac#= frac.+ float] + [frac#= frac.+ double] + )) + + (text#= (//.of_string ..expected_string) (//.of_string (Objects::actual_string))) + + (text#= (%.format (//.of_string left_string) (//.of_string right_string)) + (//.of_string (Objects::string_method left_string right_string))) + + (text#= (//.of_string left_string) + (//.of_string (Objects::left left_string right_string))) + (text#= (//.of_string right_string) + (//.of_string (Objects::right left_string right_string))) + (int#= (//.of_long left_long) + (//.of_long (Objects::left left_long right_long))) + (int#= (//.of_long right_long) + (//.of_long (Objects::right left_long right_long))) + )) )))))) diff --git a/stdlib/source/test/lux/ffi/export.lua.lux b/stdlib/source/test/lux/ffi/export.lua.lux index daaea870c..cfa2de19f 100644 --- a/stdlib/source/test/lux/ffi/export.lua.lux +++ b/stdlib/source/test/lux/ffi/export.lua.lux @@ -26,8 +26,8 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.export:] - (and (n.= <nat> (..constant)) - (n.= (n.+ <nat> <nat>) ((..shift) <nat>)))) + (_.coverage [/.export:] + (and (n.= <nat> (..constant)) + (n.= (n.+ <nat> <nat>) ((..shift) <nat>)))) ))) ) diff --git a/stdlib/source/test/lux/ffi/export.py.lux b/stdlib/source/test/lux/ffi/export.py.lux index 16eab39bb..20bd74c34 100644 --- a/stdlib/source/test/lux/ffi/export.py.lux +++ b/stdlib/source/test/lux/ffi/export.py.lux @@ -26,8 +26,8 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.export:] - (and (n.= <nat> ..constant) - (n.= (n.+ <nat> <nat>) (..shift <nat>)))) + (_.coverage [/.export:] + (and (n.= <nat> ..constant) + (n.= (n.+ <nat> <nat>) (..shift <nat>)))) ))) ) diff --git a/stdlib/source/test/lux/ffi/export.rb.lux b/stdlib/source/test/lux/ffi/export.rb.lux index 3ab6e3c93..6ee3b8832 100644 --- a/stdlib/source/test/lux/ffi/export.rb.lux +++ b/stdlib/source/test/lux/ffi/export.rb.lux @@ -34,10 +34,10 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.export:] - (and (n.= <nat> (..nullary [])) - (n.= (n.+ <nat> <nat>) (..unary <nat>)) - (n.= <nat> (..CONSTANT)) - (n.= (n.+ <nat> <nat>) ((..$global) <nat>)))) + (_.coverage [/.export:] + (and (n.= <nat> (..nullary [])) + (n.= (n.+ <nat> <nat>) (..unary <nat>)) + (n.= <nat> (..CONSTANT)) + (n.= (n.+ <nat> <nat>) ((..$global) <nat>)))) ))) ) diff --git a/stdlib/source/test/lux/locale.lux b/stdlib/source/test/lux/locale.lux index a4892aa3e..479cd3e45 100644 --- a/stdlib/source/test/lux/locale.lux +++ b/stdlib/source/test/lux/locale.lux @@ -88,10 +88,10 @@ (list lt_locale lte_locale)) encoding_check (list.every? (|>> /.code (text.ends_with? (encoding.name encoding))) (list le_locale lte_locale))]] - (_.cover [/.locale /.code] - (and language_check - territory_check - encoding_check))) + (_.coverage [/.locale /.code] + (and language_check + territory_check + encoding_check))) /language.test /territory.test diff --git a/stdlib/source/test/lux/locale/language.lux b/stdlib/source/test/lux/locale/language.lux index a95df8de0..f7eaa7840 100644 --- a/stdlib/source/test/lux/locale/language.lux +++ b/stdlib/source/test/lux/locale/language.lux @@ -41,8 +41,8 @@ #names (|> languages (list#each /.name) (set.of_list text.hash)) #codes (|> languages (list#each /.code) (set.of_list text.hash)) #languages (set.of_list /.hash languages) - #test (_.cover <languages> - true)]))] + #test (_.coverage <languages> + true)]))] [languages/a [/.afar /.abkhazian /.achinese /.acoli /.adangme /.adyghe /.afro_asiatic /.afrihili /.afrikaans /.ainu @@ -204,8 +204,8 @@ (`` (all _.and (~~ (template [<lens> <tag> <hash>] [(let [[amount set] (..aggregate (the <tag>) <hash> ..languages)] - (_.cover [<lens>] - (n.= amount (set.size set))))] + (_.coverage [<lens>] + (n.= amount (set.size set))))] [/.name #names text.hash] [/.code #codes text.hash] @@ -214,9 +214,9 @@ ))))) (template: (!aliases <reference> <aliases>) - [(_.cover <aliases> - (list.every? (# /.equivalence = <reference>) - (`` (list (~~ (template.spliced <aliases>))))))]) + [(_.coverage <aliases> + (list.every? (# /.equivalence = <reference>) + (`` (list (~~ (template.spliced <aliases>))))))]) (def: aliases_test/0 Test diff --git a/stdlib/source/test/lux/locale/territory.lux b/stdlib/source/test/lux/locale/territory.lux index b8d2b6e05..5548c3a6e 100644 --- a/stdlib/source/test/lux/locale/territory.lux +++ b/stdlib/source/test/lux/locale/territory.lux @@ -44,8 +44,8 @@ #longs (|> territories (list#each /.long_code) (set.of_list text.hash)) #numbers (|> territories (list#each /.numeric_code) (set.of_list n.hash)) #territories (|> territories (set.of_list /.hash)) - #test (_.cover <territories> - true)]))] + #test (_.coverage <territories> + true)]))] [territories/a [/.afghanistan /.aland_islands /.albania /.algeria /.american_samoa /.andorra /.angola /.anguilla /.antarctica /.antigua @@ -159,8 +159,8 @@ (`` (all _.and (~~ (template [<lens> <tag> <hash>] [(let [[amount set] (..aggregate (the <tag>) <hash> ..territories)] - (_.cover [<lens>] - (n.= amount (set.size set))))] + (_.coverage [<lens>] + (n.= amount (set.size set))))] [/.name #names text.hash] [/.short_code #shorts text.hash] @@ -171,9 +171,9 @@ ))))) (template: (!aliases <reference> <aliases>) - [(_.cover <aliases> - (list.every? (# /.equivalence = <reference>) - (`` (list (~~ (template.spliced <aliases>))))))]) + [(_.coverage <aliases> + (list.every? (# /.equivalence = <reference>) + (`` (list (~~ (template.spliced <aliases>))))))]) (def: aliases_test Test diff --git a/stdlib/source/test/lux/macro.lux b/stdlib/source/test/lux/macro.lux index 0ba513c1a..d10b10547 100644 --- a/stdlib/source/test/lux/macro.lux +++ b/stdlib/source/test/lux/macro.lux @@ -126,58 +126,58 @@ (n.* (~ pow/1) (~ pow/1))))]] (`` (all _.and (~~ (template [<expander> <logger> <expansion>] - [(_.cover [<expander>] - (|> (<expander> (` (..pow/4 (~ pow/1)))) - (meta.result lux) - (try#each (# (list.equivalence code.equivalence) = - (list <expansion>))) - (try.else false))) - - (_.cover [<logger>] - (and (|> (/.single_expansion (` (<logger> "omit" (..pow/4 (~ pow/1))))) - (meta.result lux) - (try#each (# (list.equivalence code.equivalence) = (list))) - (try.else false)) - (|> (/.single_expansion (` (<logger> (..pow/4 (~ pow/1))))) - (meta.result lux) - (try#each (# (list.equivalence code.equivalence) = (list <expansion>))) - (try.else false))))] + [(_.coverage [<expander>] + (|> (<expander> (` (..pow/4 (~ pow/1)))) + (meta.result lux) + (try#each (# (list.equivalence code.equivalence) = + (list <expansion>))) + (try.else false))) + + (_.coverage [<logger>] + (and (|> (/.single_expansion (` (<logger> "omit" (..pow/4 (~ pow/1))))) + (meta.result lux) + (try#each (# (list.equivalence code.equivalence) = (list))) + (try.else false)) + (|> (/.single_expansion (` (<logger> (..pow/4 (~ pow/1))))) + (meta.result lux) + (try#each (# (list.equivalence code.equivalence) = (list <expansion>))) + (try.else false))))] [/.single_expansion /.log_single_expansion! single_expansion] [/.expansion /.log_expansion! expansion] [/.full_expansion /.log_full_expansion! full_expansion] )) - (_.cover [/.one_expansion] - (bit#= (not (n.= 1 repetitions)) - (|> (/.one_expansion (` (..repeated (~ (code.nat repetitions)) (~ pow/1)))) - (meta.result lux) - (!expect {try.#Failure _})))) - (_.cover [/.final] - (with_expansions [<expected> (static.random_nat) - <cycles> (static.random code.nat - (random#each (|>> (n.% 5) ++) random.nat)) - <actual> (/.final (..iterated <cycles> <expected>))] - (case (' <actual>) - [_ {.#Nat actual}] - (n.= <expected> actual) - - _ - false))) - (_.cover [/.times] - (with_expansions [<expected> (static.random_nat) - <max> (static.random code.nat - (random#each (|>> (n.% 10) (n.+ 2)) random.nat)) - <cycles> (static.random code.nat - (random#each (|>> (n.% <max>) ++) random.nat)) - <actual> (/.times <cycles> (..iterated <max> <expected>))] - (let [expected_remaining (n.- <cycles> <max>)] - (case (` <actual>) - (^.` (..iterated (~ [_ {.#Nat actual_remaining}]) (~ [_ {.#Nat actual}]))) - (and (n.= expected_remaining actual_remaining) - (n.= <expected> actual)) - - _ - false)))) + (_.coverage [/.one_expansion] + (bit#= (not (n.= 1 repetitions)) + (|> (/.one_expansion (` (..repeated (~ (code.nat repetitions)) (~ pow/1)))) + (meta.result lux) + (!expect {try.#Failure _})))) + (_.coverage [/.final] + (with_expansions [<expected> (static.random_nat) + <cycles> (static.random code.nat + (random#each (|>> (n.% 5) ++) random.nat)) + <actual> (/.final (..iterated <cycles> <expected>))] + (case (' <actual>) + [_ {.#Nat actual}] + (n.= <expected> actual) + + _ + false))) + (_.coverage [/.times] + (with_expansions [<expected> (static.random_nat) + <max> (static.random code.nat + (random#each (|>> (n.% 10) (n.+ 2)) random.nat)) + <cycles> (static.random code.nat + (random#each (|>> (n.% <max>) ++) random.nat)) + <actual> (/.times <cycles> (..iterated <max> <expected>))] + (let [expected_remaining (n.- <cycles> <max>)] + (case (` <actual>) + (^.` (..iterated (~ [_ {.#Nat actual_remaining}]) (~ [_ {.#Nat actual}]))) + (and (n.= expected_remaining actual_remaining) + (n.= <expected> actual)) + + _ + false)))) )))) (def: .public test @@ -187,27 +187,27 @@ (do [! random.monad] [[seed symbol_prefix lux] ..random_lux] (all _.and - (_.cover [/.symbol] - (|> (/.symbol symbol_prefix) - (# meta.monad each %.code) - (meta.result lux) - (!expect (^.multi {try.#Success actual_symbol} - (and (text.contains? symbol_prefix actual_symbol) - (text.contains? (%.nat seed) actual_symbol)))))) - (_.cover [/.wrong_syntax_error] - (|> (/.single_expansion (` (/.log_single_expansion!))) - (meta.result lux) - (!expect (^.multi {try.#Failure error} - (text.contains? (/.wrong_syntax_error (symbol /.log_single_expansion!)) - error))))) - (_.cover [/.with_symbols] - (with_expansions [<expected> (fresh_symbol)] - (|> (/.with_symbols [<expected>] - (# meta.monad in <expected>)) - (meta.result lux) - (!expect (^.multi {try.#Success [_ {.#Symbol ["" actual]}]} - (text.contains? (template.text [<expected>]) - actual)))))) + (_.coverage [/.symbol] + (|> (/.symbol symbol_prefix) + (# meta.monad each %.code) + (meta.result lux) + (!expect (^.multi {try.#Success actual_symbol} + (and (text.contains? symbol_prefix actual_symbol) + (text.contains? (%.nat seed) actual_symbol)))))) + (_.coverage [/.wrong_syntax_error] + (|> (/.single_expansion (` (/.log_single_expansion!))) + (meta.result lux) + (!expect (^.multi {try.#Failure error} + (text.contains? (/.wrong_syntax_error (symbol /.log_single_expansion!)) + error))))) + (_.coverage [/.with_symbols] + (with_expansions [<expected> (fresh_symbol)] + (|> (/.with_symbols [<expected>] + (# meta.monad in <expected>)) + (meta.result lux) + (!expect (^.multi {try.#Success [_ {.#Symbol ["" actual]}]} + (text.contains? (template.text [<expected>]) + actual)))))) )) ..test|expansion diff --git a/stdlib/source/test/lux/macro/code.lux b/stdlib/source/test/lux/macro/code.lux index 63d6a7ccf..528ffdfe0 100644 --- a/stdlib/source/test/lux/macro/code.lux +++ b/stdlib/source/test/lux/macro/code.lux @@ -107,18 +107,18 @@ (~~ (template [<coverage> <random> <tag>] [(do [! random.monad] [expected <random>] - (_.cover [<coverage>] - (and (case (..read (/.format (<coverage> expected))) - {try.#Success actual} - (# /.equivalence = - actual - (<coverage> expected)) - - {try.#Failure error} - false) - (# /.equivalence = - [location.dummy {<tag> expected}] - (<coverage> expected)))))] + (_.coverage [<coverage>] + (and (case (..read (/.format (<coverage> expected))) + {try.#Success actual} + (# /.equivalence = + actual + (<coverage> expected)) + + {try.#Failure error} + false) + (# /.equivalence = + [location.dummy {<tag> expected}] + (<coverage> expected)))))] [/.bit random.bit .#Bit] [/.nat random.nat .#Nat] @@ -133,19 +133,19 @@ (~~ (template [<coverage> <random> <tag>] [(do [! random.monad] [expected <random>] - (_.cover [<coverage>] - (and (case (..read (/.format (<coverage> expected))) - {try.#Success actual} - (# /.equivalence = - actual - (<coverage> expected)) - - {try.#Failure error} - false) - (# /.equivalence = - [location.dummy {<tag> ["" expected]}] - (<coverage> expected))) - ))] + (_.coverage [<coverage>] + (and (case (..read (/.format (<coverage> expected))) + {try.#Success actual} + (# /.equivalence = + actual + (<coverage> expected)) + + {try.#Failure error} + false) + (# /.equivalence = + [location.dummy {<tag> ["" expected]}] + (<coverage> expected))) + ))] [/.local ..random_text .#Symbol] ))))) @@ -167,8 +167,8 @@ [sample expected] (random.only (function (_ [sample expected]) (not (# /.equivalence = sample expected))) (..replacement_simulation [original substitute]))] - (_.cover [/.replaced] - (# /.equivalence = - expected - (/.replaced original substitute sample)))) + (_.coverage [/.replaced] + (# /.equivalence = + expected + (/.replaced original substitute sample)))) ))) diff --git a/stdlib/source/test/lux/macro/local.lux b/stdlib/source/test/lux/macro/local.lux index 0f4d48263..4678fe067 100644 --- a/stdlib/source/test/lux/macro/local.lux +++ b/stdlib/source/test/lux/macro/local.lux @@ -70,22 +70,22 @@ (do [! random.monad] [expected random.nat] (all _.and - (_.cover [/.push] - (..with ["" "actual"] expected #0 - (n.= expected (..actual)))) - (_.cover [/.unknown_module] - (exception.match? /.unknown_module - (..macro_error - (..with ["123yolo456" "actual"] expected #0 - (n.= expected (..actual)))))) - (_.cover [/.cannot_shadow_definition] - (exception.match? /.cannot_shadow_definition - (..macro_error - (..with ["" "with"] expected #0 - (n.= expected (..actual)))))) - (_.cover [/.unknown_definition] - (exception.match? /.unknown_definition - (<| ..macro_error - (..with ["" "actual"] expected #1) - (n.= expected (..actual))))) + (_.coverage [/.push] + (..with ["" "actual"] expected #0 + (n.= expected (..actual)))) + (_.coverage [/.unknown_module] + (exception.match? /.unknown_module + (..macro_error + (..with ["123yolo456" "actual"] expected #0 + (n.= expected (..actual)))))) + (_.coverage [/.cannot_shadow_definition] + (exception.match? /.cannot_shadow_definition + (..macro_error + (..with ["" "with"] expected #0 + (n.= expected (..actual)))))) + (_.coverage [/.unknown_definition] + (exception.match? /.unknown_definition + (<| ..macro_error + (..with ["" "actual"] expected #1) + (n.= expected (..actual))))) )))) diff --git a/stdlib/source/test/lux/macro/pattern.lux b/stdlib/source/test/lux/macro/pattern.lux index ce57f48ea..c4819c59e 100644 --- a/stdlib/source/test/lux/macro/pattern.lux +++ b/stdlib/source/test/lux/macro/pattern.lux @@ -41,58 +41,58 @@ (all _.and (do [! random.monad] [sample (# ! each (n.% 5) random.nat)] - (_.cover [/.template] - (case sample - (/.template [<case>] - [<case> true]) - ([0] [1] [2] [3] [4]) + (_.coverage [/.template] + (case sample + (/.template [<case>] + [<case> true]) + ([0] [1] [2] [3] [4]) - _ - false))) - (_.cover [/.or] - (and (/.case expected_rev - (/.or .5 .25) true - _ false) - (/.case expected_frac - (/.or +0.5 +1.25) true - _ false) - (/.case expected_text - (/.or "+0.5" "+1.25") true - _ false))) - (_.cover [/.let] - (let [expected_pair (is (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] - (/.case expected_pair - (/.let actual_pair (/.pattern (!pair actual_left actual_right))) - (and (/.same? expected_pair actual_pair) - (/.same? expected_nat actual_left) - (/.same? expected_int actual_right))))) - (_.cover [/.multi] - (let [expected_pair (is (Pair Nat Int) - [..#left expected_nat ..#right expected_int])] - (and (/.case expected_pair - (/.multi (/.pattern (!pair 0 actual_right)) - [actual_right - +0]) - true + _ + false))) + (_.coverage [/.or] + (and (/.case expected_rev + (/.or .5 .25) true + _ false) + (/.case expected_frac + (/.or +0.5 +1.25) true + _ false) + (/.case expected_text + (/.or "+0.5" "+1.25") true + _ false))) + (_.coverage [/.let] + (let [expected_pair (is (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] + (/.case expected_pair + (/.let actual_pair (/.pattern (!pair actual_left actual_right))) + (and (/.same? expected_pair actual_pair) + (/.same? expected_nat actual_left) + (/.same? expected_int actual_right))))) + (_.coverage [/.multi] + (let [expected_pair (is (Pair Nat Int) + [..#left expected_nat ..#right expected_int])] + (and (/.case expected_pair + (/.multi (/.pattern (!pair 0 actual_right)) + [actual_right + +0]) + true - _ - false) - (/.case expected_pair - (/.multi (/.pattern (!pair 0 actual_right)) - (i.= +0 actual_right)) - true + _ + false) + (/.case expected_pair + (/.multi (/.pattern (!pair 0 actual_right)) + (i.= +0 actual_right)) + true - _ - false)))) - (_.cover [/.|>] - (case expected_frac - (/.|> actual_frac [(f.* +2.0) (f.* +2.0)]) - (f.= (f.* +4.0 expected_frac) - actual_frac))) - (_.cover [/.`] - (case (code.text expected_text) - (/.` "+0.5") true - (/.` "+1.25") true - _ false)) + _ + false)))) + (_.coverage [/.|>] + (case expected_frac + (/.|> actual_frac [(f.* +2.0) (f.* +2.0)]) + (f.= (f.* +4.0 expected_frac) + actual_frac))) + (_.coverage [/.`] + (case (code.text expected_text) + (/.` "+0.5") true + (/.` "+1.25") true + _ false)) )))) diff --git a/stdlib/source/test/lux/macro/syntax.lux b/stdlib/source/test/lux/macro/syntax.lux index 6cf8db75c..c70bdc504 100644 --- a/stdlib/source/test/lux/macro/syntax.lux +++ b/stdlib/source/test/lux/macro/syntax.lux @@ -35,9 +35,9 @@ [x random.nat y random.nat z random.nat] - (_.cover [/.syntax:] - (n.= (all n.+ x y z) - (+/3 x y z)))) + (_.coverage [/.syntax:] + (n.= (all n.+ x y z) + (+/3 x y z)))) /check.test /declaration.test diff --git a/stdlib/source/test/lux/macro/syntax/check.lux b/stdlib/source/test/lux/macro/syntax/check.lux index c8ba8394c..de933e033 100644 --- a/stdlib/source/test/lux/macro/syntax/check.lux +++ b/stdlib/source/test/lux/macro/syntax/check.lux @@ -36,13 +36,13 @@ (do random.monad [[type value] ..random] - (_.cover [/.format /.parser] - (case (<code>.result /.parser - (list (/.format [/.#type type - /.#value value]))) - {try.#Failure _} - false - - {try.#Success check} - (and (code#= type (the /.#type check)) - (code#= value (the /.#value check))))))))) + (_.coverage [/.format /.parser] + (case (<code>.result /.parser + (list (/.format [/.#type type + /.#value value]))) + {try.#Failure _} + false + + {try.#Success check} + (and (code#= type (the /.#type check)) + (code#= value (the /.#value check))))))))) diff --git a/stdlib/source/test/lux/macro/syntax/declaration.lux b/stdlib/source/test/lux/macro/syntax/declaration.lux index 9f136e7d8..ed89e605a 100644 --- a/stdlib/source/test/lux/macro/syntax/declaration.lux +++ b/stdlib/source/test/lux/macro/syntax/declaration.lux @@ -37,11 +37,11 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (case (<code>.result /.parser - (list (/.format expected))) - {try.#Failure _} - false - - {try.#Success actual} - (# /.equivalence = expected actual))))))) + (_.coverage [/.format /.parser] + (case (<code>.result /.parser + (list (/.format expected))) + {try.#Failure _} + false + + {try.#Success actual} + (# /.equivalence = expected actual))))))) diff --git a/stdlib/source/test/lux/macro/syntax/definition.lux b/stdlib/source/test/lux/macro/syntax/definition.lux index 24056ae07..2efc46208 100644 --- a/stdlib/source/test/lux/macro/syntax/definition.lux +++ b/stdlib/source/test/lux/macro/syntax/definition.lux @@ -67,31 +67,31 @@ type $///code.random untyped_value $///code.random] (all _.and - (_.cover [/.format /.parser] - (case (<code>.result (/.parser compiler) - (list (/.format expected))) - {try.#Failure error} - false - - {try.#Success actual} - (# /.equivalence = expected actual))) - (_.cover [/.typed] - (let [expected (has /.#value {.#Left [type untyped_value]} expected)] - (case (<code>.result (/.typed compiler) - (list (/.format expected))) - {try.#Failure error} - false - - {try.#Success actual} - (# /.equivalence = expected actual)))) - (_.cover [/.lacks_type] - (let [expected (has /.#value {.#Right untyped_value} expected)] - (case (<code>.result (/.typed compiler) - (list (/.format expected))) - {try.#Failure error} - (exception.match? /.lacks_type error) - - {try.#Success actual} - false))) + (_.coverage [/.format /.parser] + (case (<code>.result (/.parser compiler) + (list (/.format expected))) + {try.#Failure error} + false + + {try.#Success actual} + (# /.equivalence = expected actual))) + (_.coverage [/.typed] + (let [expected (has /.#value {.#Left [type untyped_value]} expected)] + (case (<code>.result (/.typed compiler) + (list (/.format expected))) + {try.#Failure error} + false + + {try.#Success actual} + (# /.equivalence = expected actual)))) + (_.coverage [/.lacks_type] + (let [expected (has /.#value {.#Right untyped_value} expected)] + (case (<code>.result (/.typed compiler) + (list (/.format expected))) + {try.#Failure error} + (exception.match? /.lacks_type error) + + {try.#Success actual} + false))) ))) )) diff --git a/stdlib/source/test/lux/macro/syntax/export.lux b/stdlib/source/test/lux/macro/syntax/export.lux index 973842471..e40f34e4b 100644 --- a/stdlib/source/test/lux/macro/syntax/export.lux +++ b/stdlib/source/test/lux/macro/syntax/export.lux @@ -31,17 +31,17 @@ (<| (_.covering /._) (do random.monad [[expected_export_policy expected_un_exported] ..export] - (_.cover [/.parser /.default_policy] - (|> (case expected_export_policy - {.#Some expected_export_policy} - (list expected_export_policy (code.nat expected_un_exported)) + (_.coverage [/.parser /.default_policy] + (|> (case expected_export_policy + {.#Some expected_export_policy} + (list expected_export_policy (code.nat expected_un_exported)) - {.#None} - (list (code.nat expected_un_exported))) - (<code>.result (/.parser <code>.nat)) - (try#each (function (_ [actual_export_policy actual_un_exported]) - (|> expected_export_policy - (maybe.else /.default_policy) - (code#= actual_export_policy) - (and (n.= expected_un_exported actual_un_exported))))) - (try.else false)))))) + {.#None} + (list (code.nat expected_un_exported))) + (<code>.result (/.parser <code>.nat)) + (try#each (function (_ [actual_export_policy actual_un_exported]) + (|> expected_export_policy + (maybe.else /.default_policy) + (code#= actual_export_policy) + (and (n.= expected_un_exported actual_un_exported))))) + (try.else false)))))) diff --git a/stdlib/source/test/lux/macro/syntax/input.lux b/stdlib/source/test/lux/macro/syntax/input.lux index 4e1008333..eb5f9b7b4 100644 --- a/stdlib/source/test/lux/macro/syntax/input.lux +++ b/stdlib/source/test/lux/macro/syntax/input.lux @@ -39,10 +39,10 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (case (<code>.result /.parser (list (/.format (list expected)))) - {try.#Failure _} - false - - {try.#Success actual} - (# (list.equivalence /.equivalence) = (list expected) actual))))))) + (_.coverage [/.format /.parser] + (case (<code>.result /.parser (list (/.format (list expected)))) + {try.#Failure _} + false + + {try.#Success actual} + (# (list.equivalence /.equivalence) = (list expected) actual))))))) diff --git a/stdlib/source/test/lux/macro/syntax/type/variable.lux b/stdlib/source/test/lux/macro/syntax/type/variable.lux index f5f8a490d..91b1a0587 100644 --- a/stdlib/source/test/lux/macro/syntax/type/variable.lux +++ b/stdlib/source/test/lux/macro/syntax/type/variable.lux @@ -29,9 +29,9 @@ (do random.monad [expected ..random] - (_.cover [/.format /.parser] - (|> (list (/.format expected)) - (<code>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.format /.parser] + (|> (list (/.format expected)) + (<code>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) ))) diff --git a/stdlib/source/test/lux/macro/template.lux b/stdlib/source/test/lux/macro/template.lux index 4d4424428..403266486 100644 --- a/stdlib/source/test/lux/macro/template.lux +++ b/stdlib/source/test/lux/macro/template.lux @@ -49,68 +49,68 @@ <short> (these ["a" b c #0 #1 2 +3 -4 .5]) <short>' "abc#0#12+3-4.5"] (all _.and - (_.cover [/.spliced] - (# (list.equivalence nat.equivalence) = - (list left mid right) - (`` (list (~~ (/.spliced [left mid right])))))) - (_.cover [/.amount] - (case (/.amount [left mid right]) - 3 true - _ false)) - (_.cover [/.text] - (case (/.text <short>) - <short>' true - _ false)) - (_.cover [/.symbol] - (and (case (`` (symbol (~~ (/.symbol <short>)))) - ["" <short>'] true - _ false) - (case (`` (symbol (~~ (/.symbol <module> <short>)))) - [<module>' <short>'] true - _ false) - )) - (_.cover [/.with_locals] - (/.with_locals [var0 var1] - (let [var0 left - var1 right] - (and (nat.= left var0) - (nat.= right var1))))) + (_.coverage [/.spliced] + (# (list.equivalence nat.equivalence) = + (list left mid right) + (`` (list (~~ (/.spliced [left mid right])))))) + (_.coverage [/.amount] + (case (/.amount [left mid right]) + 3 true + _ false)) + (_.coverage [/.text] + (case (/.text <short>) + <short>' true + _ false)) + (_.coverage [/.symbol] + (and (case (`` (symbol (~~ (/.symbol <short>)))) + ["" <short>'] true + _ false) + (case (`` (symbol (~~ (/.symbol <module> <short>)))) + [<module>' <short>'] true + _ false) + )) + (_.coverage [/.with_locals] + (/.with_locals [var0 var1] + (let [var0 left + var1 right] + (and (nat.= left var0) + (nat.= right var1))))) (do ! [scalar random.nat] - (_.cover [/.let] - (let [can_use_with_statements! - (nat.= (all nat.* scalar scalar) - (..pow/2 scalar))] - (and can_use_with_statements! - (/.let [(pow/3 <scalar>) - [(all nat.* <scalar> <scalar> <scalar>)] + (_.coverage [/.let] + (let [can_use_with_statements! + (nat.= (all nat.* scalar scalar) + (..pow/2 scalar))] + (and can_use_with_statements! + (/.let [(pow/3 <scalar>) + [(all nat.* <scalar> <scalar> <scalar>)] - (pow/9 <scalar>) - [(pow/3 (pow/3 <scalar>))]] - (let [can_use_with_expressions! - (nat.= (all nat.* scalar scalar scalar) - (pow/3 scalar)) + (pow/9 <scalar>) + [(pow/3 (pow/3 <scalar>))]] + (let [can_use_with_expressions! + (nat.= (all nat.* scalar scalar scalar) + (pow/3 scalar)) - can_refer! - (nat.= (all nat.* - scalar scalar scalar - scalar scalar scalar - scalar scalar scalar) - (pow/9 scalar)) + can_refer! + (nat.= (all nat.* + scalar scalar scalar + scalar scalar scalar + scalar scalar scalar) + (pow/9 scalar)) - can_shadow! - (let [pow/3 (function (_ scalar) - (all nat.+ scalar scalar scalar))] - (nat.= (all nat.+ scalar scalar scalar) - (pow/3 scalar)))] - (and can_use_with_expressions! - can_refer! - can_shadow!))) - )))) - (_.cover [/.irregular_arguments] - (/.let [(arity/3 <0> <1> <2>) - [""]] - (exception.match? /.irregular_arguments - (macro_error (arity/3 "a" "b"))))) + can_shadow! + (let [pow/3 (function (_ scalar) + (all nat.+ scalar scalar scalar))] + (nat.= (all nat.+ scalar scalar scalar) + (pow/3 scalar)))] + (and can_use_with_expressions! + can_refer! + can_shadow!))) + )))) + (_.coverage [/.irregular_arguments] + (/.let [(arity/3 <0> <1> <2>) + [""]] + (exception.match? /.irregular_arguments + (macro_error (arity/3 "a" "b"))))) ))) )) diff --git a/stdlib/source/test/lux/math.lux b/stdlib/source/test/lux/math.lux index 4aa96e6db..a59f42a6e 100644 --- a/stdlib/source/test/lux/math.lux +++ b/stdlib/source/test/lux/math.lux @@ -59,13 +59,13 @@ subjectC random.complex]) (`` (all _.and (~~ (template [</> <scenarios>'] - [(_.cover [</>] - (with_expansions [<scenarios> (template.spliced <scenarios>')] - (`` (and (~~ (template [<=> <//> <parameter> <subject>] - [(<=> (<//> <parameter> <subject>) - (</> <parameter> <subject>))] - - <scenarios>))))))] + [(_.coverage [</>] + (with_expansions [<scenarios> (template.spliced <scenarios>')] + (`` (and (~~ (template [<=> <//> <parameter> <subject>] + [(<=> (<//> <parameter> <subject>) + (</> <parameter> <subject>))] + + <scenarios>))))))] [/.+ [[n.= n.+ parameterN subjectN] [i.= i.+ parameterI subjectI] @@ -99,13 +99,13 @@ [complex.= complex.% parameterC subjectC]]] )) (~~ (template [</> <scenarios>'] - [(_.cover [</>] - (with_expansions [<scenarios> (template.spliced <scenarios>')] - (`` (and (~~ (template [<//> <parameter> <subject>] - [(bit#= (<//> <parameter> <subject>) - (</> <parameter> <subject>))] - - <scenarios>))))))] + [(_.coverage [</>] + (with_expansions [<scenarios> (template.spliced <scenarios>')] + (`` (and (~~ (template [<//> <parameter> <subject>] + [(bit#= (<//> <parameter> <subject>) + (</> <parameter> <subject>))] + + <scenarios>))))))] [/.= [[n.= parameterN subjectN] [i.= parameterI subjectI] diff --git a/stdlib/source/test/lux/math/infix.lux b/stdlib/source/test/lux/math/infix.lux index 709a24b0b..f8d3554cd 100644 --- a/stdlib/source/test/lux/math/infix.lux +++ b/stdlib/source/test/lux/math/infix.lux @@ -23,34 +23,34 @@ extra random.nat angle random.safe_frac factor random.nat] - (_.cover [/.infix] - (let [constant_values! - (n.= subject - (/.infix subject)) + (_.coverage [/.infix] + (let [constant_values! + (n.= subject + (/.infix subject)) - unary_functions! - (f.= (f.sin angle) - (/.infix [f.sin angle])) + unary_functions! + (f.= (f.sin angle) + (/.infix [f.sin angle])) - binary_functions! - (n.= (n.gcd parameter subject) - (/.infix [subject n.gcd parameter])) + binary_functions! + (n.= (n.gcd parameter subject) + (/.infix [subject n.gcd parameter])) - multiple_binary_functions! - (n.= (n.* factor (n.gcd parameter subject)) - (/.infix [subject n.gcd parameter n.* factor])) + multiple_binary_functions! + (n.= (n.* factor (n.gcd parameter subject)) + (/.infix [subject n.gcd parameter n.* factor])) - function_call! - (n.= (n.gcd extra (n.* parameter subject)) - (/.infix [(n.* parameter subject) n.gcd extra])) + function_call! + (n.= (n.gcd extra (n.* parameter subject)) + (/.infix [(n.* parameter subject) n.gcd extra])) - non_numeric! - (bit#= (and (n.< parameter subject) (n.< extra parameter)) - (/.infix [[subject n.< parameter] and [parameter n.< extra]]))] - (and constant_values! - unary_functions! - binary_functions! - multiple_binary_functions! - function_call! - non_numeric! - )))))) + non_numeric! + (bit#= (and (n.< parameter subject) (n.< extra parameter)) + (/.infix [[subject n.< parameter] and [parameter n.< extra]]))] + (and constant_values! + unary_functions! + binary_functions! + multiple_binary_functions! + function_call! + non_numeric! + )))))) diff --git a/stdlib/source/test/lux/math/logic/continuous.lux b/stdlib/source/test/lux/math/logic/continuous.lux index b4d9993d5..56386b590 100644 --- a/stdlib/source/test/lux/math/logic/continuous.lux +++ b/stdlib/source/test/lux/math/logic/continuous.lux @@ -29,87 +29,87 @@ [/.conjunction] )) - (_.cover [/.true /.false] - (let [true=max! - (r.= /.false (++ /.true)) + (_.coverage [/.true /.false] + (let [true=max! + (r.= /.false (++ /.true)) - false=min! - (r.= /.true (-- /.false))] - (and true=max! - false=min!))) - (_.cover [/.or] - (let [identity! - (r.= left (/.or /.false left)) + false=min! + (r.= /.true (-- /.false))] + (and true=max! + false=min!))) + (_.coverage [/.or] + (let [identity! + (r.= left (/.or /.false left)) - annihilation! - (r.= /.true (/.or /.true left)) - - idempotence! - (r.= left (/.or left left)) + annihilation! + (r.= /.true (/.or /.true left)) + + idempotence! + (r.= left (/.or left left)) - associativity! - (r.= (all /.or left mid right) - (.left /.or left mid right))] - (and identity! - annihilation! - idempotence! - associativity! - (let [l|r (/.or left right)] - (and (r.>= left l|r) - (r.>= right l|r)))))) - (_.cover [/.and] - (let [identity! - (r.= left (/.and /.true left)) + associativity! + (r.= (all /.or left mid right) + (.left /.or left mid right))] + (and identity! + annihilation! + idempotence! + associativity! + (let [l|r (/.or left right)] + (and (r.>= left l|r) + (r.>= right l|r)))))) + (_.coverage [/.and] + (let [identity! + (r.= left (/.and /.true left)) - annihilation! - (r.= /.false (/.and /.false left)) - - idempotence! - (r.= left (/.and left left)) + annihilation! + (r.= /.false (/.and /.false left)) + + idempotence! + (r.= left (/.and left left)) - associativity! - (r.= (all /.and left mid right) - (.left /.and left mid right))] - (and identity! - annihilation! - idempotence! - associativity! - (let [l&r (/.and left right)] - (and (r.<= left l&r) - (r.<= right l&r)))))) - (_.cover [/.not] - (let [inverses! - (and (r.= /.false (/.not /.true)) - (r.= /.true (/.not /.false))) + associativity! + (r.= (all /.and left mid right) + (.left /.and left mid right))] + (and identity! + annihilation! + idempotence! + associativity! + (let [l&r (/.and left right)] + (and (r.<= left l&r) + (r.<= right l&r)))))) + (_.coverage [/.not] + (let [inverses! + (and (r.= /.false (/.not /.true)) + (r.= /.true (/.not /.false))) - double_negation! - (r.= left (/.not (/.not left))) + double_negation! + (r.= left (/.not (/.not left))) - de_morgan! - (and (r.= (/.not (/.or left right)) - (/.and (/.not left) (/.not right))) - (r.= (/.not (/.and left right)) - (/.or (/.not left) (/.not right))))] - (and inverses! - double_negation! - de_morgan!))) - (_.cover [/.implies] - (let [modus_tollens! - (r.= (/.implies right left) - (/.implies (/.not left) (/.not right)))] - (and modus_tollens!))) - (_.cover [/.=] - (let [trivial! - (and (r.= /.true (/.= /.true /.true)) - (r.= /.true (/.= /.false /.false)) + de_morgan! + (and (r.= (/.not (/.or left right)) + (/.and (/.not left) (/.not right))) + (r.= (/.not (/.and left right)) + (/.or (/.not left) (/.not right))))] + (and inverses! + double_negation! + de_morgan!))) + (_.coverage [/.implies] + (let [modus_tollens! + (r.= (/.implies right left) + (/.implies (/.not left) (/.not right)))] + (and modus_tollens!))) + (_.coverage [/.=] + (let [trivial! + (and (r.= /.true (/.= /.true /.true)) + (r.= /.true (/.= /.false /.false)) - (r.= /.false (/.= /.true /.false))) + (r.= /.false (/.= /.true /.false))) - common! - (and (r.>= left - (/.= left left)) - (r.>= right - (/.= right right)))] - (and trivial! - common!))) + common! + (and (r.>= left + (/.= left left)) + (r.>= right + (/.= right right)))] + (and trivial! + common!))) ))))) diff --git a/stdlib/source/test/lux/math/logic/fuzzy.lux b/stdlib/source/test/lux/math/logic/fuzzy.lux index d954d22e7..dd030636a 100644 --- a/stdlib/source/test/lux/math/logic/fuzzy.lux +++ b/stdlib/source/test/lux/math/logic/fuzzy.lux @@ -28,10 +28,10 @@ (do random.monad [sample random.rev] (all _.and - (_.cover [/.empty] - (r.= //.false (/.empty sample))) - (_.cover [/.full] - (r.= //.true (/.full sample))) + (_.coverage [/.empty] + (r.= //.false (/.empty sample))) + (_.coverage [/.full] + (r.= //.true (/.full sample))) ))) (def: simple @@ -47,38 +47,38 @@ .let [bottom (r.min threshold_0 threshold_1) top (r.max threshold_0 threshold_1)]] (all _.and - (_.cover [/.gradient] - (let [ascending! - (let [set (/.gradient bottom top)] - (and (r.= //.false (set bottom)) - (r.= //.true (set top)) - (let [membership (set sample)] - (cond (r.<= bottom sample) - (r.= //.false membership) - - (r.>= top sample) - (r.= //.true membership) - - (r.> //.false membership))))) - - descending! - (let [set (/.gradient top bottom)] - (and (r.= //.true (set bottom)) - (r.= //.false (set top)) - (let [membership (set sample)] - (cond (r.<= bottom sample) - (r.= //.true membership) - - (r.>= top sample) - (r.= //.false membership) - - (r.> //.false membership)))))] - (and ascending! - descending!))) - (_.cover [/.membership] - (let [set (/.gradient bottom top)] - (r.= (set sample) - (/.membership set sample)))) + (_.coverage [/.gradient] + (let [ascending! + (let [set (/.gradient bottom top)] + (and (r.= //.false (set bottom)) + (r.= //.true (set top)) + (let [membership (set sample)] + (cond (r.<= bottom sample) + (r.= //.false membership) + + (r.>= top sample) + (r.= //.true membership) + + (r.> //.false membership))))) + + descending! + (let [set (/.gradient top bottom)] + (and (r.= //.true (set bottom)) + (r.= //.false (set top)) + (let [membership (set sample)] + (cond (r.<= bottom sample) + (r.= //.true membership) + + (r.>= top sample) + (r.= //.false membership) + + (r.> //.false membership)))))] + (and ascending! + descending!))) + (_.coverage [/.membership] + (let [set (/.gradient bottom top)] + (r.= (set sample) + (/.membership set sample)))) ))) (def: composition @@ -101,66 +101,66 @@ .let [bottom_set (/.gradient bottom middle_bottom) top_set (/.gradient middle_top top)]] (all _.and - (_.cover [/.union] - (let [set (/.gradient bottom top)] - (and (r.= (/.membership set sample) - (/.membership (/.union /.empty set) sample)) - (r.= (/.membership /.full sample) - (/.membership (/.union /.full set) sample)) - - (r.>= (/.membership bottom_set sample) - (/.membership (/.union bottom_set top_set) sample)) - (r.>= (/.membership top_set sample) - (/.membership (/.union bottom_set top_set) sample))))) - (_.cover [/.intersection] - (let [set (/.gradient bottom top)] - (and (r.= (/.membership /.empty sample) - (/.membership (/.intersection /.empty set) sample)) - (r.= (/.membership set sample) - (/.membership (/.intersection /.full set) sample)) - - (r.<= (/.membership bottom_set sample) - (/.membership (/.intersection bottom_set top_set) sample)) - (r.<= (/.membership top_set sample) - (/.membership (/.intersection bottom_set top_set) sample))))) - (_.cover [/.complement] - (let [set (/.gradient bottom top) - - trivial! - (and (r.= (/.membership /.full sample) - (/.membership (/.complement /.empty) sample)) - (r.= (/.membership /.empty sample) - (/.membership (/.complement /.full) sample))) - - common! - (and (r.>= (/.membership set sample) - (/.membership (/.union set (/.complement set)) sample)) - (r.<= (/.membership set sample) - (/.membership (/.intersection set (/.complement set)) sample))) - - de_morgan! - (and (r.= (/.membership (/.complement (/.union bottom_set top_set)) - sample) - (/.membership (/.intersection (/.complement bottom_set) (/.complement top_set)) - sample)) - (r.= (/.membership (/.complement (/.intersection bottom_set top_set)) - sample) - (/.membership (/.union (/.complement bottom_set) (/.complement top_set)) - sample)))] - (and trivial! - common! - de_morgan!))) - (_.cover [/.difference] - (let [set (/.gradient bottom top)] - (and (r.= (/.membership set sample) - (/.membership (/.difference /.empty set) sample)) - (r.= (/.membership /.empty sample) - (/.membership (/.difference /.full set) sample)) - - (r.<= (/.membership top_set sample) - (/.membership (/.difference bottom_set top_set) sample)) - (r.<= (/.membership bottom_set sample) - (/.membership (/.difference bottom_set top_set) sample))))) + (_.coverage [/.union] + (let [set (/.gradient bottom top)] + (and (r.= (/.membership set sample) + (/.membership (/.union /.empty set) sample)) + (r.= (/.membership /.full sample) + (/.membership (/.union /.full set) sample)) + + (r.>= (/.membership bottom_set sample) + (/.membership (/.union bottom_set top_set) sample)) + (r.>= (/.membership top_set sample) + (/.membership (/.union bottom_set top_set) sample))))) + (_.coverage [/.intersection] + (let [set (/.gradient bottom top)] + (and (r.= (/.membership /.empty sample) + (/.membership (/.intersection /.empty set) sample)) + (r.= (/.membership set sample) + (/.membership (/.intersection /.full set) sample)) + + (r.<= (/.membership bottom_set sample) + (/.membership (/.intersection bottom_set top_set) sample)) + (r.<= (/.membership top_set sample) + (/.membership (/.intersection bottom_set top_set) sample))))) + (_.coverage [/.complement] + (let [set (/.gradient bottom top) + + trivial! + (and (r.= (/.membership /.full sample) + (/.membership (/.complement /.empty) sample)) + (r.= (/.membership /.empty sample) + (/.membership (/.complement /.full) sample))) + + common! + (and (r.>= (/.membership set sample) + (/.membership (/.union set (/.complement set)) sample)) + (r.<= (/.membership set sample) + (/.membership (/.intersection set (/.complement set)) sample))) + + de_morgan! + (and (r.= (/.membership (/.complement (/.union bottom_set top_set)) + sample) + (/.membership (/.intersection (/.complement bottom_set) (/.complement top_set)) + sample)) + (r.= (/.membership (/.complement (/.intersection bottom_set top_set)) + sample) + (/.membership (/.union (/.complement bottom_set) (/.complement top_set)) + sample)))] + (and trivial! + common! + de_morgan!))) + (_.coverage [/.difference] + (let [set (/.gradient bottom top)] + (and (r.= (/.membership set sample) + (/.membership (/.difference /.empty set) sample)) + (r.= (/.membership /.empty sample) + (/.membership (/.difference /.full set) sample)) + + (r.<= (/.membership top_set sample) + (/.membership (/.difference bottom_set top_set) sample)) + (r.<= (/.membership bottom_set sample) + (/.membership (/.difference bottom_set top_set) sample))))) ))) (def: geometric @@ -182,109 +182,109 @@ _ {.#None}))))] (all _.and - (_.cover [/.triangle] - (let [reference (/.triangle bottom middle_bottom top) - - irrelevant_order! - (list.every? (function (_ set) - (r.= (/.membership reference sample) - (/.membership set sample))) - (list (/.triangle bottom top middle_bottom) - (/.triangle middle_bottom bottom top) - (/.triangle middle_bottom top bottom) - (/.triangle top bottom middle_bottom) - (/.triangle top middle_bottom bottom))) - - middle_maximum! - (r.= //.true (/.membership reference middle_bottom)) - - boundary_minima! - (and (r.= //.false (/.membership reference bottom)) - (r.= //.false (/.membership reference top))) - - inside_range! - (bit#= (r.> //.false (/.membership reference sample)) - (and (r.> bottom sample) - (r.< top sample))) - - outside_range! - (bit#= (r.= //.false (/.membership reference sample)) - (or (r.<= bottom sample) - (r.>= top sample)))] - (and irrelevant_order! - middle_maximum! - boundary_minima! - inside_range! - outside_range!))) - (_.cover [/.trapezoid] - (let [reference (/.trapezoid bottom middle_bottom middle_top top) - - irrelevant_order! - (list.every? (function (_ set) - (r.= (/.membership reference sample) - (/.membership set sample))) - (let [r0 bottom - r1 middle_bottom - r2 middle_top - r3 top] - (list (/.trapezoid r0 r1 r2 r3) - (/.trapezoid r0 r1 r3 r2) - (/.trapezoid r0 r2 r1 r3) - (/.trapezoid r0 r2 r3 r1) - (/.trapezoid r0 r3 r1 r2) - (/.trapezoid r0 r3 r2 r1) - - (/.trapezoid r1 r0 r2 r3) - (/.trapezoid r1 r0 r3 r2) - (/.trapezoid r1 r2 r0 r3) - (/.trapezoid r1 r2 r3 r0) - (/.trapezoid r1 r3 r0 r2) - (/.trapezoid r1 r3 r2 r0) - - (/.trapezoid r2 r0 r1 r3) - (/.trapezoid r2 r0 r3 r1) - (/.trapezoid r2 r1 r0 r3) - (/.trapezoid r2 r1 r3 r0) - (/.trapezoid r2 r3 r0 r1) - (/.trapezoid r2 r3 r1 r0) - - (/.trapezoid r3 r0 r1 r2) - (/.trapezoid r3 r0 r2 r1) - (/.trapezoid r3 r1 r0 r2) - (/.trapezoid r3 r1 r2 r0) - (/.trapezoid r3 r2 r0 r1) - (/.trapezoid r3 r2 r1 r0) - ))) - - middle_maxima! - (and (r.= //.true (/.membership reference middle_bottom)) - (r.= //.true (/.membership reference middle_top))) - - boundary_minima! - (and (r.= //.false (/.membership reference bottom)) - (r.= //.false (/.membership reference top))) - - inside_range! - (bit#= (r.> //.false (/.membership reference sample)) - (and (r.> bottom sample) - (r.< top sample))) - - outside_range! - (bit#= (r.= //.false (/.membership reference sample)) - (or (r.<= bottom sample) - (r.>= top sample))) - - - inside_inner_range! - (bit#= (r.= //.true (/.membership reference sample)) - (and (r.<= middle_top sample) - (r.>= middle_bottom sample)))] - (and irrelevant_order! - middle_maxima! - boundary_minima! - inside_range! - outside_range! - inside_inner_range!))) + (_.coverage [/.triangle] + (let [reference (/.triangle bottom middle_bottom top) + + irrelevant_order! + (list.every? (function (_ set) + (r.= (/.membership reference sample) + (/.membership set sample))) + (list (/.triangle bottom top middle_bottom) + (/.triangle middle_bottom bottom top) + (/.triangle middle_bottom top bottom) + (/.triangle top bottom middle_bottom) + (/.triangle top middle_bottom bottom))) + + middle_maximum! + (r.= //.true (/.membership reference middle_bottom)) + + boundary_minima! + (and (r.= //.false (/.membership reference bottom)) + (r.= //.false (/.membership reference top))) + + inside_range! + (bit#= (r.> //.false (/.membership reference sample)) + (and (r.> bottom sample) + (r.< top sample))) + + outside_range! + (bit#= (r.= //.false (/.membership reference sample)) + (or (r.<= bottom sample) + (r.>= top sample)))] + (and irrelevant_order! + middle_maximum! + boundary_minima! + inside_range! + outside_range!))) + (_.coverage [/.trapezoid] + (let [reference (/.trapezoid bottom middle_bottom middle_top top) + + irrelevant_order! + (list.every? (function (_ set) + (r.= (/.membership reference sample) + (/.membership set sample))) + (let [r0 bottom + r1 middle_bottom + r2 middle_top + r3 top] + (list (/.trapezoid r0 r1 r2 r3) + (/.trapezoid r0 r1 r3 r2) + (/.trapezoid r0 r2 r1 r3) + (/.trapezoid r0 r2 r3 r1) + (/.trapezoid r0 r3 r1 r2) + (/.trapezoid r0 r3 r2 r1) + + (/.trapezoid r1 r0 r2 r3) + (/.trapezoid r1 r0 r3 r2) + (/.trapezoid r1 r2 r0 r3) + (/.trapezoid r1 r2 r3 r0) + (/.trapezoid r1 r3 r0 r2) + (/.trapezoid r1 r3 r2 r0) + + (/.trapezoid r2 r0 r1 r3) + (/.trapezoid r2 r0 r3 r1) + (/.trapezoid r2 r1 r0 r3) + (/.trapezoid r2 r1 r3 r0) + (/.trapezoid r2 r3 r0 r1) + (/.trapezoid r2 r3 r1 r0) + + (/.trapezoid r3 r0 r1 r2) + (/.trapezoid r3 r0 r2 r1) + (/.trapezoid r3 r1 r0 r2) + (/.trapezoid r3 r1 r2 r0) + (/.trapezoid r3 r2 r0 r1) + (/.trapezoid r3 r2 r1 r0) + ))) + + middle_maxima! + (and (r.= //.true (/.membership reference middle_bottom)) + (r.= //.true (/.membership reference middle_top))) + + boundary_minima! + (and (r.= //.false (/.membership reference bottom)) + (r.= //.false (/.membership reference top))) + + inside_range! + (bit#= (r.> //.false (/.membership reference sample)) + (and (r.> bottom sample) + (r.< top sample))) + + outside_range! + (bit#= (r.= //.false (/.membership reference sample)) + (or (r.<= bottom sample) + (r.>= top sample))) + + + inside_inner_range! + (bit#= (r.= //.true (/.membership reference sample)) + (and (r.<= middle_top sample) + (r.>= middle_bottom sample)))] + (and irrelevant_order! + middle_maxima! + boundary_minima! + inside_range! + outside_range! + inside_inner_range!))) )))) (def: discrete @@ -295,13 +295,13 @@ set (set.of_list n.hash (list threshold))] sample random.nat] (all _.and - (_.cover [/.of_predicate] - (bit#= (r.= //.true (/.membership (/.of_predicate under?) sample)) - (under? sample))) - (_.cover [/.of_set] - (and (r.= //.true (/.membership (/.of_set set) threshold)) - (bit#= (r.= //.true (/.membership (/.of_set set) sample)) - (set.member? set sample)))) + (_.coverage [/.of_predicate] + (bit#= (r.= //.true (/.membership (/.of_predicate under?) sample)) + (under? sample))) + (_.coverage [/.of_set] + (and (r.= //.true (/.membership (/.of_set set) threshold)) + (bit#= (r.= //.true (/.membership (/.of_set set) sample)) + (set.member? set sample)))) ))) (def: gradient @@ -324,12 +324,12 @@ threshold random.rev sample random.rev] (all _.and - (_.cover [/.predicate] - (bit#= (not ((/.predicate threshold set) sample)) - (r.< threshold (/.membership set sample)))) - (_.cover [/.cut] - (bit#= (r.= //.false (/.membership (/.cut threshold set) sample)) - (r.< threshold (/.membership set sample)))) + (_.coverage [/.predicate] + (bit#= (not ((/.predicate threshold set) sample)) + (r.< threshold (/.membership set sample)))) + (_.coverage [/.cut] + (bit#= (r.= //.false (/.membership (/.cut threshold set) sample)) + (r.< threshold (/.membership set sample)))) ))) (def: .public test diff --git a/stdlib/source/test/lux/math/modular.lux b/stdlib/source/test/lux/math/modular.lux index 535ba1048..69c47f49f 100644 --- a/stdlib/source/test/lux/math/modular.lux +++ b/stdlib/source/test/lux/math/modular.lux @@ -62,63 +62,63 @@ (_.for [/.codec] ($codec.spec /.equivalence (/.codec subject##%) (..random subject##%))) - (_.cover [/.incorrect_modulus] - (case (|> param - (# (/.codec param##%) encoded) - (# (/.codec subject##%) decoded)) - {try.#Failure error} - (exception.match? /.incorrect_modulus error) - - {try.#Success _} - false)) - (_.cover [/.modulus] - (and (type#= (type_of (/.modulus subject)) - (type_of (/.modulus subject))) - (not (type#= (type_of (/.modulus subject)) - (type_of (/.modulus param)))))) - (_.cover [/.modular /.value] + (_.coverage [/.incorrect_modulus] + (case (|> param + (# (/.codec param##%) encoded) + (# (/.codec subject##%) decoded)) + {try.#Failure error} + (exception.match? /.incorrect_modulus error) + + {try.#Success _} + false)) + (_.coverage [/.modulus] + (and (type#= (type_of (/.modulus subject)) + (type_of (/.modulus subject))) + (not (type#= (type_of (/.modulus subject)) + (type_of (/.modulus param)))))) + (_.coverage [/.modular /.value] + (/.= subject + (/.modular (/.modulus subject) (/.value subject)))) + (_.coverage [/.>] + (bit#= (/.> another subject) + (/.< subject another))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= another subject) + (/.>= subject another))) + (_.coverage [/.-] + (let [zero (/.modular (/.modulus subject) +0)] + (and (/.= zero + (/.- subject subject)) (/.= subject - (/.modular (/.modulus subject) (/.value subject)))) - (_.cover [/.>] - (bit#= (/.> another subject) - (/.< subject another))) - (_.cover [/.<= /.>=] - (bit#= (/.<= another subject) - (/.>= subject another))) - (_.cover [/.-] - (let [zero (/.modular (/.modulus subject) +0)] - (and (/.= zero - (/.- subject subject)) - (/.= subject - (/.- zero subject))))) - (_.cover [/.inverse] - (let [one (/.modular (/.modulus subject) +1) - co_prime? (i.co_prime? (//.divisor (/.modulus subject)) - (/.value subject))] - (case (/.inverse subject) - {.#Some subject^-1} - (and co_prime? - (|> subject - (/.* subject^-1) - (/.= one))) - - {.#None} - (not co_prime?)))) - (_.cover [/.adapter] - (<| (try.else false) - (do try.monad - [copy##% (//.modulus (//.divisor subject##%)) - adapt (/.adapter subject##% copy##%)] - (in (|> subject - /.value - (/.modular copy##%) - adapt - (/.= subject)))))) - (_.cover [/.moduli_are_not_equal] - (case (/.adapter subject##% param##%) - {try.#Failure error} - (exception.match? /.moduli_are_not_equal error) - - {try.#Success _} - false)) + (/.- zero subject))))) + (_.coverage [/.inverse] + (let [one (/.modular (/.modulus subject) +1) + co_prime? (i.co_prime? (//.divisor (/.modulus subject)) + (/.value subject))] + (case (/.inverse subject) + {.#Some subject^-1} + (and co_prime? + (|> subject + (/.* subject^-1) + (/.= one))) + + {.#None} + (not co_prime?)))) + (_.coverage [/.adapter] + (<| (try.else false) + (do try.monad + [copy##% (//.modulus (//.divisor subject##%)) + adapt (/.adapter subject##% copy##%)] + (in (|> subject + /.value + (/.modular copy##%) + adapt + (/.= subject)))))) + (_.coverage [/.moduli_are_not_equal] + (case (/.adapter subject##% param##%) + {try.#Failure error} + (exception.match? /.moduli_are_not_equal error) + + {try.#Success _} + false)) ))))) diff --git a/stdlib/source/test/lux/math/modulus.lux b/stdlib/source/test/lux/math/modulus.lux index 71dd3b81b..df4d22c6d 100644 --- a/stdlib/source/test/lux/math/modulus.lux +++ b/stdlib/source/test/lux/math/modulus.lux @@ -40,29 +40,29 @@ modulus (..random +1,000,000) dividend random.int] (all _.and - (_.cover [/.modulus /.divisor] - (case (/.modulus divisor) - {try.#Success modulus} - (i.= divisor (/.divisor modulus)) - - {try.#Failure error} - (i.= +0 divisor))) - (_.cover [/.zero_cannot_be_a_modulus] - (case (/.modulus +0) - {try.#Failure error} - (exception.match? /.zero_cannot_be_a_modulus error) + (_.coverage [/.modulus /.divisor] + (case (/.modulus divisor) + {try.#Success modulus} + (i.= divisor (/.divisor modulus)) + + {try.#Failure error} + (i.= +0 divisor))) + (_.coverage [/.zero_cannot_be_a_modulus] + (case (/.modulus +0) + {try.#Failure error} + (exception.match? /.zero_cannot_be_a_modulus error) - {try.#Success modulus} - false)) - (_.cover [/.literal] - (with_expansions [<divisor> (|divisor|)] - (i.= <divisor> (/.divisor (/.literal <divisor>))))) - (_.cover [/.=] - (with_expansions [<divisor> (|divisor|)] - (/.= (/.literal <divisor>) - (/.literal <divisor>)))) - (_.cover [/.congruent?] - (and (/.congruent? modulus dividend dividend) - (or (not (/.congruent? modulus dividend (++ dividend))) - (i.= +1 (/.divisor modulus))))) + {try.#Success modulus} + false)) + (_.coverage [/.literal] + (with_expansions [<divisor> (|divisor|)] + (i.= <divisor> (/.divisor (/.literal <divisor>))))) + (_.coverage [/.=] + (with_expansions [<divisor> (|divisor|)] + (/.= (/.literal <divisor>) + (/.literal <divisor>)))) + (_.coverage [/.congruent?] + (and (/.congruent? modulus dividend dividend) + (or (not (/.congruent? modulus dividend (++ dividend))) + (i.= +1 (/.divisor modulus))))) )))) diff --git a/stdlib/source/test/lux/math/number.lux b/stdlib/source/test/lux/math/number.lux index 94df83848..d5a065984 100644 --- a/stdlib/source/test/lux/math/number.lux +++ b/stdlib/source/test/lux/math/number.lux @@ -32,63 +32,63 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.bin] - (`` (and (~~ (template [<=> <codec> <number>] - [(case (# <codec> decoded (..clean_commas <number>)) - {try.#Success actual} - (<=> (/.bin <number>) actual) + (_.coverage [/.bin] + (`` (and (~~ (template [<=> <codec> <number>] + [(case (# <codec> decoded (..clean_commas <number>)) + {try.#Success actual} + (<=> (/.bin <number>) actual) - {try.#Failure error} - false)] + {try.#Failure error} + false)] - [n.= n.binary "11,00,10,01"] + [n.= n.binary "11,00,10,01"] - [i.= i.binary "+11,00,10,01"] - [i.= i.binary "-11,00,10,01"] + [i.= i.binary "+11,00,10,01"] + [i.= i.binary "-11,00,10,01"] - [r.= r.binary ".11,00,10,01"] + [r.= r.binary ".11,00,10,01"] - [f.= f.binary "+11,00.10,01"] - [f.= f.binary "-11,00.10,01"] - ))))) - (_.cover [/.oct] - (`` (and (~~ (template [<=> <codec> <number>] - [(case (# <codec> decoded (..clean_commas <number>)) - {try.#Success actual} - (<=> (/.oct <number>) actual) + [f.= f.binary "+11,00.10,01"] + [f.= f.binary "-11,00.10,01"] + ))))) + (_.coverage [/.oct] + (`` (and (~~ (template [<=> <codec> <number>] + [(case (# <codec> decoded (..clean_commas <number>)) + {try.#Success actual} + (<=> (/.oct <number>) actual) - {try.#Failure error} - false)] + {try.#Failure error} + false)] - [n.= n.octal "615,243"] + [n.= n.octal "615,243"] - [i.= i.octal "+615,243"] - [i.= i.octal "-615,243"] + [i.= i.octal "+615,243"] + [i.= i.octal "-615,243"] - [r.= r.octal ".615,243"] + [r.= r.octal ".615,243"] - [f.= f.octal "+61,52.43"] - [f.= f.octal "-61,52.43"] - ))))) - (_.cover [/.hex] - (`` (and (~~ (template [<=> <codec> <number>] - [(case (# <codec> decoded (..clean_commas <number>)) - {try.#Success actual} - (<=> (/.hex <number>) actual) + [f.= f.octal "+61,52.43"] + [f.= f.octal "-61,52.43"] + ))))) + (_.coverage [/.hex] + (`` (and (~~ (template [<=> <codec> <number>] + [(case (# <codec> decoded (..clean_commas <number>)) + {try.#Success actual} + (<=> (/.hex <number>) actual) - {try.#Failure error} - false)] + {try.#Failure error} + false)] - [n.= n.hex "dead,BEEF"] + [n.= n.hex "dead,BEEF"] - [i.= i.hex "+dead,BEEF"] - [i.= i.hex "-dead,BEEF"] + [i.= i.hex "+dead,BEEF"] + [i.= i.hex "-dead,BEEF"] - [r.= r.hex ".dead,BEEF"] + [r.= r.hex ".dead,BEEF"] - [f.= f.hex "+dead,BE.EF"] - [f.= f.hex "-dead,BE.EF"] - ))))) + [f.= f.hex "+dead,BE.EF"] + [f.= f.hex "-dead,BE.EF"] + ))))) /i8.test /i16.test diff --git a/stdlib/source/test/lux/math/number/complex.lux b/stdlib/source/test/lux/math/number/complex.lux index a705bbb0e..d2e2d152a 100644 --- a/stdlib/source/test/lux/math/number/complex.lux +++ b/stdlib/source/test/lux/math/number/complex.lux @@ -50,20 +50,20 @@ [real ..dimension imaginary ..dimension] (all _.and - (_.cover [/.complex] - (and (let [r+i (/.complex real imaginary)] - (and (f.= real (the /.#real r+i)) - (f.= imaginary (the /.#imaginary r+i)))) - (let [r+i (/.complex real)] - (and (f.= real (the /.#real r+i)) - (f.= +0.0 (the /.#imaginary r+i)))))) - (_.cover [/.approximately?] - (/.approximately? ..margin_of_error - (/.complex real imaginary) - (/.complex real imaginary))) - (_.cover [/.not_a_number?] - (and (/.not_a_number? (/.complex f.not_a_number imaginary)) - (/.not_a_number? (/.complex real f.not_a_number)))) + (_.coverage [/.complex] + (and (let [r+i (/.complex real imaginary)] + (and (f.= real (the /.#real r+i)) + (f.= imaginary (the /.#imaginary r+i)))) + (let [r+i (/.complex real)] + (and (f.= real (the /.#real r+i)) + (f.= +0.0 (the /.#imaginary r+i)))))) + (_.coverage [/.approximately?] + (/.approximately? ..margin_of_error + (/.complex real imaginary) + (/.complex real imaginary))) + (_.coverage [/.not_a_number?] + (and (/.not_a_number? (/.complex f.not_a_number imaginary)) + (/.not_a_number? (/.complex real f.not_a_number)))) ))) (def: constant @@ -72,20 +72,20 @@ [sample ..random dimension ..dimension] (all _.and - (_.cover [/.zero] - (/.= /.zero (/.* /.zero sample))) - (_.cover [/.+one] - (/.= sample (/.* /.+one sample))) - (_.cover [/.-one] - (and (/.= /.zero - (/.+ sample - (/.* /.-one sample))) - (/.= sample (/.* /.-one (/.* /.-one sample))))) - (_.cover [/.i] - (and (/.= (/.complex +0.0 dimension) - (/.* /.i (/.complex dimension))) - (/.= (/.* /.-one sample) - (/.* /.i (/.* /.i sample))))) + (_.coverage [/.zero] + (/.= /.zero (/.* /.zero sample))) + (_.coverage [/.+one] + (/.= sample (/.* /.+one sample))) + (_.coverage [/.-one] + (and (/.= /.zero + (/.+ sample + (/.* /.-one sample))) + (/.= sample (/.* /.-one (/.* /.-one sample))))) + (_.coverage [/.i] + (and (/.= (/.complex +0.0 dimension) + (/.* /.i (/.complex dimension))) + (/.= (/.* /.-one sample) + (/.* /.i (/.* /.i sample))))) ))) (def: absolute_value&argument @@ -94,32 +94,32 @@ [real ..dimension imaginary ..dimension] (all _.and - (_.cover [/.abs] - (let [normal! - (let [r+i (/.complex real imaginary)] - (and (f.>= (f.abs real) (/.abs r+i)) - (f.>= (f.abs imaginary) (/.abs r+i)))) + (_.coverage [/.abs] + (let [normal! + (let [r+i (/.complex real imaginary)] + (and (f.>= (f.abs real) (/.abs r+i)) + (f.>= (f.abs imaginary) (/.abs r+i)))) - not_a_number! - (and (f.not_a_number? (/.abs (/.complex f.not_a_number imaginary))) - (f.not_a_number? (/.abs (/.complex real f.not_a_number)))) + not_a_number! + (and (f.not_a_number? (/.abs (/.complex f.not_a_number imaginary))) + (f.not_a_number? (/.abs (/.complex real f.not_a_number)))) - infinity! - (and (f.= f.positive_infinity (/.abs (/.complex f.positive_infinity imaginary))) - (f.= f.positive_infinity (/.abs (/.complex real f.positive_infinity))) - (f.= f.positive_infinity (/.abs (/.complex f.negative_infinity imaginary))) - (f.= f.positive_infinity (/.abs (/.complex real f.negative_infinity))))] - (and normal! - not_a_number! - infinity!))) + infinity! + (and (f.= f.positive_infinity (/.abs (/.complex f.positive_infinity imaginary))) + (f.= f.positive_infinity (/.abs (/.complex real f.positive_infinity))) + (f.= f.positive_infinity (/.abs (/.complex f.negative_infinity imaginary))) + (f.= f.positive_infinity (/.abs (/.complex real f.negative_infinity))))] + (and normal! + not_a_number! + infinity!))) ... https://en.wikipedia.org/wiki/Argument_(complex_analysis)#Identities - (_.cover [/.argument] - (let [sample (/.complex real imaginary)] - (or (/.= /.zero sample) - (/.approximately? ..margin_of_error - sample - (/.*' (/.abs sample) - (/.exp (/.* /.i (/.complex (/.argument sample))))))))) + (_.coverage [/.argument] + (let [sample (/.complex real imaginary)] + (or (/.= /.zero sample) + (/.approximately? ..margin_of_error + sample + (/.*' (/.abs sample) + (/.exp (/.* /.i (/.complex (/.argument sample))))))))) ))) (def: number @@ -129,40 +129,40 @@ y ..random factor ..dimension] (all _.and - (_.cover [/.+] - (let [z (/.+ y x)] - (and (/.= z - (/.complex (f.+ (the /.#real y) - (the /.#real x)) - (f.+ (the /.#imaginary y) - (the /.#imaginary x))))))) - (_.cover [/.-] - (let [normal! - (let [z (/.- y x)] - (and (/.= z - (/.complex (f.- (the /.#real y) - (the /.#real x)) - (f.- (the /.#imaginary y) - (the /.#imaginary x)))))) + (_.coverage [/.+] + (let [z (/.+ y x)] + (and (/.= z + (/.complex (f.+ (the /.#real y) + (the /.#real x)) + (f.+ (the /.#imaginary y) + (the /.#imaginary x))))))) + (_.coverage [/.-] + (let [normal! + (let [z (/.- y x)] + (and (/.= z + (/.complex (f.- (the /.#real y) + (the /.#real x)) + (f.- (the /.#imaginary y) + (the /.#imaginary x)))))) - inverse! - (and (|> x (/.+ y) (/.- y) (/.approximately? ..margin_of_error x)) - (|> x (/.- y) (/.+ y) (/.approximately? ..margin_of_error x)))] - (and normal! - inverse!))) - (_.cover [/.* /./] - (|> x (/.* y) (/./ y) (/.approximately? ..margin_of_error x))) - (_.cover [/.*' /./'] - (|> x (/.*' factor) (/./' factor) (/.approximately? ..margin_of_error x))) - (_.cover [/.%] - (let [rem (/.% y x) - quotient (|> x (/.- rem) (/./ y)) - floored (|> quotient - (revised /.#real f.floor) - (revised /.#imaginary f.floor))] - (/.approximately? +0.000000000001 - x - (|> quotient (/.* y) (/.+ rem))))) + inverse! + (and (|> x (/.+ y) (/.- y) (/.approximately? ..margin_of_error x)) + (|> x (/.- y) (/.+ y) (/.approximately? ..margin_of_error x)))] + (and normal! + inverse!))) + (_.coverage [/.* /./] + (|> x (/.* y) (/./ y) (/.approximately? ..margin_of_error x))) + (_.coverage [/.*' /./'] + (|> x (/.*' factor) (/./' factor) (/.approximately? ..margin_of_error x))) + (_.coverage [/.%] + (let [rem (/.% y x) + quotient (|> x (/.- rem) (/./ y)) + floored (|> quotient + (revised /.#real f.floor) + (revised /.#imaginary f.floor))] + (/.approximately? +0.000000000001 + x + (|> quotient (/.* y) (/.+ rem))))) ))) (def: conjugate&reciprocal&signum&negation @@ -170,38 +170,38 @@ (do random.monad [x ..random] (all _.and - (_.cover [/.conjugate] - (let [cx (/.conjugate x)] - (and (f.= (the /.#real x) - (the /.#real cx)) - (f.= (f.opposite (the /.#imaginary x)) - (the /.#imaginary cx))))) - (_.cover [/.reciprocal] - (let [reciprocal! - (|> x (/.* (/.reciprocal x)) (/.approximately? ..margin_of_error /.+one)) - - own_inverse! - (|> x /.reciprocal /.reciprocal (/.approximately? ..margin_of_error x))] - (and reciprocal! - own_inverse!))) - (_.cover [/.signum] - ... Absolute value of signum is always root_2(2), 1 or 0. - (let [signum_abs (|> x /.signum /.abs)] - (or (f.= +0.0 signum_abs) - (f.= +1.0 signum_abs) - (f.= (f.pow +0.5 +2.0) signum_abs)))) - (_.cover [/.opposite] - (let [own_inverse! - (let [there (/.opposite x) - back_again (/.opposite there)] - (and (not (/.= there x)) - (/.= back_again x))) + (_.coverage [/.conjugate] + (let [cx (/.conjugate x)] + (and (f.= (the /.#real x) + (the /.#real cx)) + (f.= (f.opposite (the /.#imaginary x)) + (the /.#imaginary cx))))) + (_.coverage [/.reciprocal] + (let [reciprocal! + (|> x (/.* (/.reciprocal x)) (/.approximately? ..margin_of_error /.+one)) + + own_inverse! + (|> x /.reciprocal /.reciprocal (/.approximately? ..margin_of_error x))] + (and reciprocal! + own_inverse!))) + (_.coverage [/.signum] + ... Absolute value of signum is always root_2(2), 1 or 0. + (let [signum_abs (|> x /.signum /.abs)] + (or (f.= +0.0 signum_abs) + (f.= +1.0 signum_abs) + (f.= (f.pow +0.5 +2.0) signum_abs)))) + (_.coverage [/.opposite] + (let [own_inverse! + (let [there (/.opposite x) + back_again (/.opposite there)] + (and (not (/.= there x)) + (/.= back_again x))) - absolute! - (f.= (/.abs x) - (/.abs (/.opposite x)))] - (and own_inverse! - absolute!))) + absolute! + (f.= (/.abs x) + (/.abs (/.opposite x)))] + (and own_inverse! + absolute!))) ))) (def: (trigonometric_symmetry forward backward angle) @@ -214,30 +214,30 @@ (do [! random.monad] [angle ..angle] (all _.and - (_.cover [/.sin /.asin] - (trigonometric_symmetry /.sin /.asin angle)) - (_.cover [/.cos /.acos] - (trigonometric_symmetry /.cos /.acos angle)) - (_.cover [/.tan /.atan] - (trigonometric_symmetry /.tan /.atan angle))))) + (_.coverage [/.sin /.asin] + (trigonometric_symmetry /.sin /.asin angle)) + (_.coverage [/.cos /.acos] + (trigonometric_symmetry /.cos /.acos angle)) + (_.coverage [/.tan /.atan] + (trigonometric_symmetry /.tan /.atan angle))))) (def: hyperbolic Test (do [! random.monad] [angle ..angle] (all _.and - (_.cover [/.sinh] - (/.approximately? ..margin_of_error - (|> angle (/.* /.i) /.sin (/.* /.i) (/.* /.-one)) - (/.sinh angle))) - (_.cover [/.cosh] - (/.approximately? ..margin_of_error - (|> angle (/.* /.i) /.cos) - (/.cosh angle))) - (_.cover [/.tanh] - (/.approximately? ..margin_of_error - (|> angle (/.* /.i) /.tan (/.* /.i) (/.* /.-one)) - (/.tanh angle))) + (_.coverage [/.sinh] + (/.approximately? ..margin_of_error + (|> angle (/.* /.i) /.sin (/.* /.i) (/.* /.-one)) + (/.sinh angle))) + (_.coverage [/.cosh] + (/.approximately? ..margin_of_error + (|> angle (/.* /.i) /.cos) + (/.cosh angle))) + (_.coverage [/.tanh] + (/.approximately? ..margin_of_error + (|> angle (/.* /.i) /.tan (/.* /.i) (/.* /.-one)) + (/.tanh angle))) ))) (def: exponentiation&logarithm @@ -245,12 +245,12 @@ (do random.monad [x ..random] (all _.and - (_.cover [/.pow /.root_2] - (|> x (/.pow (/.complex +2.0)) /.root_2 (/.approximately? ..margin_of_error x))) - (_.cover [/.pow'] - (|> x (/.pow' +2.0) (/.pow' +0.5) (/.approximately? ..margin_of_error x))) - (_.cover [/.log /.exp] - (|> x /.log /.exp (/.approximately? ..margin_of_error x))) + (_.coverage [/.pow /.root_2] + (|> x (/.pow (/.complex +2.0)) /.root_2 (/.approximately? ..margin_of_error x))) + (_.coverage [/.pow'] + (|> x (/.pow' +2.0) (/.pow' +0.5) (/.approximately? ..margin_of_error x))) + (_.coverage [/.log /.exp] + (|> x /.log /.exp (/.approximately? ..margin_of_error x))) ))) (def: root @@ -258,11 +258,11 @@ (do [! random.monad] [sample ..random degree (|> random.nat (# ! each (|>> (n.max 1) (n.% 5))))] - (_.cover [/.roots] - (|> sample - (/.roots degree) - (list#each (/.pow' (|> degree .int int.frac))) - (list.every? (/.approximately? ..margin_of_error sample)))))) + (_.coverage [/.roots] + (|> sample + (/.roots degree) + (list#each (/.pow' (|> degree .int int.frac))) + (list.every? (/.approximately? ..margin_of_error sample)))))) (def: .public test Test diff --git a/stdlib/source/test/lux/math/number/frac.lux b/stdlib/source/test/lux/math/number/frac.lux index 66334e80c..9009727f5 100644 --- a/stdlib/source/test/lux/math/number/frac.lux +++ b/stdlib/source/test/lux/math/number/frac.lux @@ -35,19 +35,19 @@ (do random.monad [sample random.safe_frac] (all _.and - (_.cover [/.biggest] - (/.<= /.biggest sample)) - (_.cover [/.positive_infinity] - (/.< /.positive_infinity sample)) - (_.cover [/.smallest] - (bit#= (/.positive? sample) - (/.>= /.smallest sample))) - (_.cover [/.negative_infinity] - (/.> /.negative_infinity sample)) - (_.cover [/.not_a_number /.not_a_number?] - (and (/.not_a_number? /.not_a_number) - (not (or (/.= /.not_a_number sample) - (/.not_a_number? sample))))) + (_.coverage [/.biggest] + (/.<= /.biggest sample)) + (_.coverage [/.positive_infinity] + (/.< /.positive_infinity sample)) + (_.coverage [/.smallest] + (bit#= (/.positive? sample) + (/.>= /.smallest sample))) + (_.coverage [/.negative_infinity] + (/.> /.negative_infinity sample)) + (_.coverage [/.not_a_number /.not_a_number?] + (and (/.not_a_number? /.not_a_number) + (not (or (/.= /.not_a_number sample) + (/.not_a_number? sample))))) ))) (def: predicate @@ -56,23 +56,23 @@ [sample ..random shift (# ! each /.abs ..random)] (all _.and - (_.cover [/.negative?] - (bit#= (/.negative? sample) - (/.< +0.0 sample))) - (_.cover [/.positive?] - (bit#= (/.positive? sample) - (/.> +0.0 sample))) - (_.cover [/.zero?] - (bit#= (/.zero? sample) - (/.= +0.0 sample))) - (_.cover [/.approximately?] - (and (/.approximately? /.smallest sample sample) - (/.approximately? (/.+ +1.0 shift) sample (/.+ shift sample)))) - (_.cover [/.number?] - (and (not (/.number? /.not_a_number)) - (not (/.number? /.positive_infinity)) - (not (/.number? /.negative_infinity)) - (/.number? sample))) + (_.coverage [/.negative?] + (bit#= (/.negative? sample) + (/.< +0.0 sample))) + (_.coverage [/.positive?] + (bit#= (/.positive? sample) + (/.> +0.0 sample))) + (_.coverage [/.zero?] + (bit#= (/.zero? sample) + (/.= +0.0 sample))) + (_.coverage [/.approximately?] + (and (/.approximately? /.smallest sample sample) + (/.approximately? (/.+ +1.0 shift) sample (/.+ shift sample)))) + (_.coverage [/.number?] + (and (not (/.number? /.not_a_number)) + (not (/.number? /.positive_infinity)) + (not (/.number? /.negative_infinity)) + (/.number? sample))) ))) (def: conversion @@ -80,17 +80,17 @@ (all _.and (do [! random.monad] [expected (# ! each (n.% 1,000,000) random.nat)] - (_.cover [/.nat] - (|> expected n.frac /.nat (n.= expected)))) + (_.coverage [/.nat] + (|> expected n.frac /.nat (n.= expected)))) (do [! random.monad] [expected (# ! each (i.% +1,000,000) random.int)] - (_.cover [/.int] - (|> expected i.frac /.int (i.= expected)))) + (_.coverage [/.int] + (|> expected i.frac /.int (i.= expected)))) (do [! random.monad] [expected (# ! each (|>> (i64.left_shifted 52) .rev) random.nat)] - (_.cover [/.rev] - (|> expected r.frac /.rev (r.= expected)))) + (_.coverage [/.rev] + (|> expected r.frac /.rev (r.= expected)))) )) (def: signature @@ -143,71 +143,71 @@ [.let [~= (/.approximately? ..margin_of_error)] angle (|> random.safe_frac (# ! each (/.* /.tau)))] (all _.and - (_.cover [/.sin /.asin] - (trigonometric_symmetry /.sin /.asin angle)) - (_.cover [/.cos /.acos] - (trigonometric_symmetry /.cos /.acos angle)) - (_.cover [/.tan /.atan] - (trigonometric_symmetry /.tan /.atan angle)) - (_.cover [/.tau] - (and (and (~= +0.0 (/.sin /.tau)) - (~= +1.0 (/.cos /.tau))) - (and (~= +0.0 (/.sin (/./ +2.0 /.tau))) - (~= -1.0 (/.cos (/./ +2.0 /.tau)))) - (and (~= +1.0 (/.sin (/./ +4.0 /.tau))) - (~= +0.0 (/.cos (/./ +4.0 /.tau)))) - (and (~= -1.0 (/.sin (/.* +3.0 (/./ +4.0 /.tau)))) - (~= +0.0 (/.cos (/.* +3.0 (/./ +4.0 /.tau))))) - (let [x2+y2 (/.+ (/.pow +2.0 (/.sin angle)) - (/.pow +2.0 (/.cos angle)))] - (~= +1.0 x2+y2)))) - (_.cover [/.pi] - (~= (/./ +2.0 /.tau) /.pi)) + (_.coverage [/.sin /.asin] + (trigonometric_symmetry /.sin /.asin angle)) + (_.coverage [/.cos /.acos] + (trigonometric_symmetry /.cos /.acos angle)) + (_.coverage [/.tan /.atan] + (trigonometric_symmetry /.tan /.atan angle)) + (_.coverage [/.tau] + (and (and (~= +0.0 (/.sin /.tau)) + (~= +1.0 (/.cos /.tau))) + (and (~= +0.0 (/.sin (/./ +2.0 /.tau))) + (~= -1.0 (/.cos (/./ +2.0 /.tau)))) + (and (~= +1.0 (/.sin (/./ +4.0 /.tau))) + (~= +0.0 (/.cos (/./ +4.0 /.tau)))) + (and (~= -1.0 (/.sin (/.* +3.0 (/./ +4.0 /.tau)))) + (~= +0.0 (/.cos (/.* +3.0 (/./ +4.0 /.tau))))) + (let [x2+y2 (/.+ (/.pow +2.0 (/.sin angle)) + (/.pow +2.0 (/.cos angle)))] + (~= +1.0 x2+y2)))) + (_.coverage [/.pi] + (~= (/./ +2.0 /.tau) /.pi)) )) (do [! random.monad] [sample (|> random.safe_frac (# ! each (/.* +1000.0)))] (all _.and - (_.cover [/.ceil] - (let [ceil'd (/.ceil sample)] - (and (|> ceil'd /.int i.frac (/.= ceil'd)) - (/.>= sample ceil'd) - (/.<= +1.0 (/.- sample ceil'd))))) - (_.cover [/.floor] - (let [floor'd (/.floor sample)] - (and (|> floor'd /.int i.frac (/.= floor'd)) - (/.<= sample floor'd) - (/.<= +1.0 (/.- floor'd sample))))) - (_.cover [/.round] - (let [round'd (/.round sample)] - (and (|> round'd /.int i.frac (/.= round'd)) - (/.<= +1.0 (/.abs (/.- sample round'd)))))) - (_.cover [/.root_2] - (let [sample (/.abs sample)] - (|> sample - /.root_2 - (/.pow +2.0) - (/.approximately? ..margin_of_error sample)))) - (_.cover [/.root_3] - (|> sample - /.root_3 - (/.pow +3.0) - (/.approximately? ..margin_of_error sample))) + (_.coverage [/.ceil] + (let [ceil'd (/.ceil sample)] + (and (|> ceil'd /.int i.frac (/.= ceil'd)) + (/.>= sample ceil'd) + (/.<= +1.0 (/.- sample ceil'd))))) + (_.coverage [/.floor] + (let [floor'd (/.floor sample)] + (and (|> floor'd /.int i.frac (/.= floor'd)) + (/.<= sample floor'd) + (/.<= +1.0 (/.- floor'd sample))))) + (_.coverage [/.round] + (let [round'd (/.round sample)] + (and (|> round'd /.int i.frac (/.= round'd)) + (/.<= +1.0 (/.abs (/.- sample round'd)))))) + (_.coverage [/.root_2] + (let [sample (/.abs sample)] + (|> sample + /.root_2 + (/.pow +2.0) + (/.approximately? ..margin_of_error sample)))) + (_.coverage [/.root_3] + (|> sample + /.root_3 + (/.pow +3.0) + (/.approximately? ..margin_of_error sample))) )) (do [! random.monad] [.let [~= (/.approximately? ..margin_of_error)] sample (# ! each (/.* +10.0) random.safe_frac) power (# ! each (|>> (n.% 10) ++ n.frac) random.nat)] (all _.and - (_.cover [/.exp /.log] - (|> sample /.exp /.log (/.approximately? +0.000000000000001 sample))) - (_.cover [/.e] - (~= +1.0 (/.log /.e))) - (_.cover [/.pow /.log_by] - (let [sample (/.abs sample)] - (|> sample - (/.pow power) - (/.log_by sample) - (~= power)))) + (_.coverage [/.exp /.log] + (|> sample /.exp /.log (/.approximately? +0.000000000000001 sample))) + (_.coverage [/.e] + (~= +1.0 (/.log /.e))) + (_.coverage [/.pow /.log_by] + (let [sample (/.abs sample)] + (|> sample + (/.pow power) + (/.log_by sample) + (~= power)))) )) (do [! random.monad] [.let [~= (/.approximately? ..margin_of_error)] @@ -215,19 +215,19 @@ sample (# ! each /.abs random.safe_frac) big (# ! each (/.* +1,000,000,000.00) random.safe_frac)] (template.let [(odd! <function>) - [(_.cover [<function>] - (~= (/.opposite (<function> angle)) - (<function> (/.opposite angle))))] + [(_.coverage [<function>] + (~= (/.opposite (<function> angle)) + (<function> (/.opposite angle))))] (even! <function>) - [(_.cover [<function>] - (~= (<function> angle) - (<function> (/.opposite angle))))] + [(_.coverage [<function>] + (~= (<function> angle) + (<function> (/.opposite angle))))] (inverse! <left> <right> <input>) - [(_.cover [<left> <right>] - (~= (<right> <input>) - (<left> (/./ <input> +1.0))))]] + [(_.coverage [<left> <right>] + (~= (<right> <input>) + (<left> (/./ <input> +1.0))))]] (all _.and (odd! /.sinh) (even! /.cosh) @@ -243,31 +243,31 @@ (do [! random.monad] [x (# ! each (|>> (/.* +10.0) /.abs) random.safe_frac) y (# ! each (|>> (/.* +10.0) /.abs) random.safe_frac)] - (_.cover [/.hypotenuse] - (let [h (/.hypotenuse x y)] - (and (/.>= x h) - (/.>= y h))))) + (_.coverage [/.hypotenuse] + (let [h (/.hypotenuse x y)] + (and (/.>= x h) + (/.>= y h))))) (do [! random.monad] [.let [~= (/.approximately? ..margin_of_error) tau/4 (/./ +4.0 /.tau)] x (# ! each (/.* tau/4) random.safe_frac) y (# ! each (/.* tau/4) random.safe_frac)] - (_.cover [/.atan_2] - (let [expected (/.atan_2 x y) - actual (if (/.> +0.0 x) - (/.atan (/./ x y)) - (if (/.< +0.0 y) - (/.- /.pi (/.atan (/./ x y))) - (/.+ /.pi (/.atan (/./ x y)))))] - (and (~= expected actual) - (~= tau/4 (/.atan_2 +0.0 (/.abs y))) - (~= (/.opposite tau/4) (/.atan_2 +0.0 (/.opposite (/.abs y)))) - (/.not_a_number? (/.atan_2 +0.0 +0.0)))))) + (_.coverage [/.atan_2] + (let [expected (/.atan_2 x y) + actual (if (/.> +0.0 x) + (/.atan (/./ x y)) + (if (/.< +0.0 y) + (/.- /.pi (/.atan (/./ x y))) + (/.+ /.pi (/.atan (/./ x y)))))] + (and (~= expected actual) + (~= tau/4 (/.atan_2 +0.0 (/.abs y))) + (~= (/.opposite tau/4) (/.atan_2 +0.0 (/.opposite (/.abs y)))) + (/.not_a_number? (/.atan_2 +0.0 +0.0)))))) (do [! random.monad] [of (# ! each (|>> (n.% 10) ++) random.nat)] - (_.cover [/.factorial] - (and (n.= 1 (/.factorial 0)) - (|> (/.factorial of) (n.% of) (n.= 0))))) + (_.coverage [/.factorial] + (and (n.= 1 (/.factorial 0)) + (|> (/.factorial of) (n.% of) (n.= 0))))) )) (def: .public test @@ -279,57 +279,57 @@ [left random.safe_frac right random.safe_frac] (all _.and - (_.cover [/.>] - (bit#= (/.> left right) - (/.< right left))) - (_.cover [/.<= /.>=] - (bit#= (/.<= left right) - (/.>= right left))) + (_.coverage [/.>] + (bit#= (/.> left right) + (/.< right left))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= left right) + (/.>= right left))) )) (do random.monad [sample random.safe_frac] (all _.and - (_.cover [/.-] - (and (/.= +0.0 (/.- sample sample)) - (/.= sample (/.- +0.0 sample)) - (/.= (/.opposite sample) - (/.- sample +0.0)))) - (_.cover [/./] - (and (/.= +1.0 (/./ sample sample)) - (/.= sample (/./ +1.0 sample)))) - (_.cover [/.abs] - (bit#= (/.> sample (/.abs sample)) - (/.negative? sample))) - (_.cover [/.signum] - (/.= (/.abs sample) - (/.* (/.signum sample) sample))) + (_.coverage [/.-] + (and (/.= +0.0 (/.- sample sample)) + (/.= sample (/.- +0.0 sample)) + (/.= (/.opposite sample) + (/.- sample +0.0)))) + (_.coverage [/./] + (and (/.= +1.0 (/./ sample sample)) + (/.= sample (/./ +1.0 sample)))) + (_.coverage [/.abs] + (bit#= (/.> sample (/.abs sample)) + (/.negative? sample))) + (_.coverage [/.signum] + (/.= (/.abs sample) + (/.* (/.signum sample) sample))) )) (do random.monad [left (random.only (|>> (/.= +0.0) not) ..random) right ..random] (all _.and - (_.cover [/.%] - (let [rem (/.% left right) - div (|> right (/.- rem) (/./ left))] - (/.= right - (|> div (/.* left) (/.+ rem))))) - (_.cover [/./%] - (let [[div rem] (/./% left right)] - (and (/.= div (/./ left right)) - (/.= rem (/.% left right))))) - (_.cover [/.mod] - (or (and (/.= +0.0 (/.% left right)) - (/.= +0.0 (/.mod left right))) - (and (/.= (/.signum left) - (/.signum (/.mod left right))) - (/.= (/.signum right) - (/.signum (/.% left right))) - (if (/.= (/.signum left) (/.signum right)) - (/.= (/.% left right) - (/.mod left right)) - (/.= (/.+ left (/.% left right)) - (/.mod left right)))))) + (_.coverage [/.%] + (let [rem (/.% left right) + div (|> right (/.- rem) (/./ left))] + (/.= right + (|> div (/.* left) (/.+ rem))))) + (_.coverage [/./%] + (let [[div rem] (/./% left right)] + (and (/.= div (/./ left right)) + (/.= rem (/.% left right))))) + (_.coverage [/.mod] + (or (and (/.= +0.0 (/.% left right)) + (/.= +0.0 (/.mod left right))) + (and (/.= (/.signum left) + (/.signum (/.mod left right))) + (/.= (/.signum right) + (/.signum (/.% left right))) + (if (/.= (/.signum left) (/.signum right)) + (/.= (/.% left right) + (/.mod left right)) + (/.= (/.+ left (/.% left right)) + (/.mod left right)))))) )) (with_expansions [<jvm> (all _.and (let [test (is (-> Frac Bit) @@ -338,21 +338,21 @@ (/.bits value))))] (do random.monad [sample random.frac] - (_.cover [/.bits] - (and (test sample) - (test /.biggest) - (test /.smallest) - (test /.not_a_number) - (test /.positive_infinity) - (test /.negative_infinity))))) + (_.coverage [/.bits] + (and (test sample) + (test /.biggest) + (test /.smallest) + (test /.not_a_number) + (test /.positive_infinity) + (test /.negative_infinity))))) (do random.monad [sample random.i64] - (_.cover [/.of_bits] - (let [expected (ffi.of_double (java/lang/Double::longBitsToDouble (ffi.as_long sample))) - actual (/.of_bits sample)] - (or (/.= expected actual) - (and (/.not_a_number? expected) - (/.not_a_number? actual)))))) + (_.coverage [/.of_bits] + (let [expected (ffi.of_double (java/lang/Double::longBitsToDouble (ffi.as_long sample))) + actual (/.of_bits sample)] + (or (/.= expected actual) + (and (/.not_a_number? expected) + (/.not_a_number? actual)))))) )] (for @.old <jvm> @.jvm <jvm> @@ -364,23 +364,23 @@ (/.not_a_number? actual))))))] (do random.monad [sample random.frac] - (_.cover [/.bits /.of_bits] - (and (test sample) - (test /.biggest) - (test /.smallest) - (test /.not_a_number) - (test /.positive_infinity) - (test /.negative_infinity))))))) + (_.coverage [/.bits /.of_bits] + (and (test sample) + (test /.biggest) + (test /.smallest) + (test /.not_a_number) + (test /.positive_infinity) + (test /.negative_infinity))))))) (do random.monad [expected random.safe_frac] - (_.cover [/.opposite] - (let [subtraction! - (/.= +0.0 (/.+ (/.opposite expected) expected)) + (_.coverage [/.opposite] + (let [subtraction! + (/.= +0.0 (/.+ (/.opposite expected) expected)) - inverse! - (|> expected /.opposite /.opposite (/.= expected))] - (and subtraction! - inverse!)))) + inverse! + (|> expected /.opposite /.opposite (/.= expected))] + (and subtraction! + inverse!)))) ..constant ..predicate diff --git a/stdlib/source/test/lux/math/number/i16.lux b/stdlib/source/test/lux/math/number/i16.lux index 8321376d8..6a20bd218 100644 --- a/stdlib/source/test/lux/math/number/i16.lux +++ b/stdlib/source/test/lux/math/number/i16.lux @@ -32,7 +32,7 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.i16 /.i64 /.width] - (let [actual (|> expected .i64 /.i16 /.i64)] - (# //i64.equivalence = expected actual))) + (_.coverage [/.i16 /.i64 /.width] + (let [actual (|> expected .i64 /.i16 /.i64)] + (# //i64.equivalence = expected actual))) )))) diff --git a/stdlib/source/test/lux/math/number/i32.lux b/stdlib/source/test/lux/math/number/i32.lux index ed7e88201..9a77acb81 100644 --- a/stdlib/source/test/lux/math/number/i32.lux +++ b/stdlib/source/test/lux/math/number/i32.lux @@ -32,7 +32,7 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.i32 /.i64 /.width] - (let [actual (|> expected .i64 /.i32 /.i64)] - (# //i64.equivalence = expected actual))) + (_.coverage [/.i32 /.i64 /.width] + (let [actual (|> expected .i64 /.i32 /.i64)] + (# //i64.equivalence = expected actual))) )))) diff --git a/stdlib/source/test/lux/math/number/i64.lux b/stdlib/source/test/lux/math/number/i64.lux index 805c212b1..c7c7b9445 100644 --- a/stdlib/source/test/lux/math/number/i64.lux +++ b/stdlib/source/test/lux/math/number/i64.lux @@ -24,22 +24,22 @@ [pattern random.nat idx (# ! each (n.% /.width) random.nat)] (all _.and - (_.cover [/.one? /.one] - (if (/.one? idx pattern) - (#= pattern (/.one idx pattern)) - (not (#= pattern (/.one idx pattern))))) - (_.cover [/.zero? /.zero] - (if (/.zero? idx pattern) - (#= pattern (/.zero idx pattern)) - (not (#= pattern (/.zero idx pattern))))) - (_.cover [/.flipped] - (#= (/.flipped idx pattern) - (if (/.one? idx pattern) - (/.zero idx pattern) - (/.one idx pattern)))) - (_.cover [/.bit] - (bit#= (/.zero? idx pattern) - (#= /.false (/.and (/.bit idx) pattern)))) + (_.coverage [/.one? /.one] + (if (/.one? idx pattern) + (#= pattern (/.one idx pattern)) + (not (#= pattern (/.one idx pattern))))) + (_.coverage [/.zero? /.zero] + (if (/.zero? idx pattern) + (#= pattern (/.zero idx pattern)) + (not (#= pattern (/.zero idx pattern))))) + (_.coverage [/.flipped] + (#= (/.flipped idx pattern) + (if (/.one? idx pattern) + (/.zero idx pattern) + (/.one idx pattern)))) + (_.coverage [/.bit] + (bit#= (/.zero? idx pattern) + (#= /.false (/.and (/.bit idx) pattern)))) ))) (def: shift @@ -49,24 +49,24 @@ (all _.and (do ! [idx (# ! each (|>> (n.% (-- /.width)) ++) random.nat)] - (_.cover [/.left_shifted /.right_shifted] - (let [nullity! - (and (#= pattern (/.left_shifted 0 pattern)) - (#= pattern (/.right_shifted 0 pattern))) + (_.coverage [/.left_shifted /.right_shifted] + (let [nullity! + (and (#= pattern (/.left_shifted 0 pattern)) + (#= pattern (/.right_shifted 0 pattern))) - idempotency! - (and (#= pattern (/.left_shifted /.width pattern)) - (#= pattern (/.right_shifted /.width pattern))) + idempotency! + (and (#= pattern (/.left_shifted /.width pattern)) + (#= pattern (/.right_shifted /.width pattern))) - movement! - (let [shift (n.- idx /.width)] - (#= (/.and (/.mask idx) pattern) - (|> pattern - (/.left_shifted shift) - (/.right_shifted shift))))] - (and nullity! - idempotency! - movement!)))) + movement! + (let [shift (n.- idx /.width)] + (#= (/.and (/.mask idx) pattern) + (|> pattern + (/.left_shifted shift) + (/.right_shifted shift))))] + (and nullity! + idempotency! + movement!)))) ))) (def: mask @@ -77,45 +77,45 @@ idx (# ! each (n.% /.width) random.nat) signed random.int] (all _.and - (_.cover [/.sign] - (bit#= (#= (.i64 0) (/.and /.sign signed)) - (i.positive? signed))) - (_.cover [/.mask] - (let [mask (/.mask idx) - idempotency! (#= (/.and mask pattern) - (/.and mask (/.and mask pattern))) + (_.coverage [/.sign] + (bit#= (#= (.i64 0) (/.and /.sign signed)) + (i.positive? signed))) + (_.coverage [/.mask] + (let [mask (/.mask idx) + idempotency! (#= (/.and mask pattern) + (/.and mask (/.and mask pattern))) - limit (++ (.nat mask)) - limit! (if (n.< limit pattern) - (#= pattern (/.and mask pattern)) - (n.< limit (/.and mask pattern))) + limit (++ (.nat mask)) + limit! (if (n.< limit pattern) + (#= pattern (/.and mask pattern)) + (n.< limit (/.and mask pattern))) - empty! (#= /.false (/.mask 0)) - full! (#= /.true (/.mask /.width))] - (and idempotency! - limit! + empty! (#= /.false (/.mask 0)) + full! (#= /.true (/.mask /.width))] + (and idempotency! + limit! - empty! - full!))) + empty! + full!))) (do ! [size (# ! each (n.% /.width) random.nat) .let [spare (n.- size /.width)] offset (# ! each (n.% spare) random.nat)] - (_.cover [/.region] - (case size - 0 (#= /.false (/.region offset size)) - _ (#= (|> pattern - ... NNNNYYYYNNNN - (/.right_shifted offset) - ... ____NNNNYYYY - (/.left_shifted spare) - ... YYYY________ - (/.right_shifted spare) - ... ________YYYY - (/.left_shifted offset) - ... ____YYYY____ - ) - (/.and (/.region offset size) pattern))))) + (_.coverage [/.region] + (case size + 0 (#= /.false (/.region offset size)) + _ (#= (|> pattern + ... NNNNYYYYNNNN + (/.right_shifted offset) + ... ____NNNNYYYY + (/.left_shifted spare) + ... YYYY________ + (/.right_shifted spare) + ... ________YYYY + (/.left_shifted offset) + ... ____YYYY____ + ) + (/.and (/.region offset size) pattern))))) )))) (def: sub @@ -125,8 +125,8 @@ [size (# ! each (n.% /.width) random.nat)] (case (/.sub size) {.#None} - (_.cover [/.sub] - (n.= 0 size)) + (_.coverage [/.sub] + (n.= 0 size)) {.#Some sub} (do [! random.monad] @@ -141,9 +141,9 @@ (# random.functor each narrow random.i64)))]] (all _.and ($equivalence.spec (# sub sub_equivalence) (random (# sub narrow))) - (_.cover [/.sub] - (let [actual (|> expected .i64 (# sub narrow) (# sub wide))] - (#= expected actual))) + (_.coverage [/.sub] + (let [actual (|> expected .i64 (# sub narrow) (# sub wide))] + (#= expected actual))) )))))) (def: signature @@ -167,95 +167,95 @@ [pattern random.nat idx (# ! each (n.% /.width) random.nat)] (all _.and - (_.cover [/.width /.bits_per_byte /.bytes_per_i64] - (and (n.= /.bytes_per_i64 - (n./ /.bits_per_byte /.width)) - (n.= /.bits_per_byte - (n./ /.bytes_per_i64 /.width)))) - (_.cover [/.false] - (n.= 0 (/.ones /.false))) - (_.cover [/.or] - (and (#= /.true (/.or /.true pattern)) - (#= pattern (/.or /.false pattern)))) - (_.cover [/.true] - (n.= /.width (/.ones /.true))) - (_.cover [/.and] - (and (#= pattern (/.and /.true pattern)) - (#= /.false (/.and /.false pattern)))) - (_.cover [/.not] - (and (#= /.false - (/.and pattern - (/.not pattern))) - (#= /.true - (/.or pattern - (/.not pattern))))) - (_.cover [/.xor] - (and (#= /.true - (/.xor pattern - (/.not pattern))) - (#= /.false - (/.xor pattern - pattern)))) - (_.cover [/.ones] - (let [zero&one! - (if (/.one? idx pattern) - (n.= (-- (/.ones pattern)) (/.ones (/.zero idx pattern))) - (n.= (++ (/.ones pattern)) (/.ones (/.one idx pattern)))) + (_.coverage [/.width /.bits_per_byte /.bytes_per_i64] + (and (n.= /.bytes_per_i64 + (n./ /.bits_per_byte /.width)) + (n.= /.bits_per_byte + (n./ /.bytes_per_i64 /.width)))) + (_.coverage [/.false] + (n.= 0 (/.ones /.false))) + (_.coverage [/.or] + (and (#= /.true (/.or /.true pattern)) + (#= pattern (/.or /.false pattern)))) + (_.coverage [/.true] + (n.= /.width (/.ones /.true))) + (_.coverage [/.and] + (and (#= pattern (/.and /.true pattern)) + (#= /.false (/.and /.false pattern)))) + (_.coverage [/.not] + (and (#= /.false + (/.and pattern + (/.not pattern))) + (#= /.true + (/.or pattern + (/.not pattern))))) + (_.coverage [/.xor] + (and (#= /.true + (/.xor pattern + (/.not pattern))) + (#= /.false + (/.xor pattern + pattern)))) + (_.coverage [/.ones] + (let [zero&one! + (if (/.one? idx pattern) + (n.= (-- (/.ones pattern)) (/.ones (/.zero idx pattern))) + (n.= (++ (/.ones pattern)) (/.ones (/.one idx pattern)))) - complementarity! - (n.= /.width - (n.+ (/.ones pattern) - (/.ones (/.not pattern))))] - (and zero&one! - complementarity!))) - (_.cover [/.left_rotated /.right_rotated] - (let [false! - (and (#= /.false (/.left_rotated idx /.false)) - (#= /.false (/.right_rotated idx /.false))) + complementarity! + (n.= /.width + (n.+ (/.ones pattern) + (/.ones (/.not pattern))))] + (and zero&one! + complementarity!))) + (_.coverage [/.left_rotated /.right_rotated] + (let [false! + (and (#= /.false (/.left_rotated idx /.false)) + (#= /.false (/.right_rotated idx /.false))) - true! - (and (#= /.true (/.left_rotated idx /.true)) - (#= /.true (/.right_rotated idx /.true))) + true! + (and (#= /.true (/.left_rotated idx /.true)) + (#= /.true (/.right_rotated idx /.true))) - inverse! - (and (|> pattern - (/.left_rotated idx) - (/.right_rotated idx) - (#= pattern)) - (|> pattern - (/.right_rotated idx) - (/.left_rotated idx) - (#= pattern))) + inverse! + (and (|> pattern + (/.left_rotated idx) + (/.right_rotated idx) + (#= pattern)) + (|> pattern + (/.right_rotated idx) + (/.left_rotated idx) + (#= pattern))) - nullity! - (and (|> pattern - (/.left_rotated 0) - (#= pattern)) - (|> pattern - (/.right_rotated 0) - (#= pattern))) + nullity! + (and (|> pattern + (/.left_rotated 0) + (#= pattern)) + (|> pattern + (/.right_rotated 0) + (#= pattern))) - futility! - (and (|> pattern - (/.left_rotated /.width) - (#= pattern)) - (|> pattern - (/.right_rotated /.width) - (#= pattern)))] - (and false! - true! - inverse! - nullity! - futility!))) - (_.cover [/.reversed] - (and (|> pattern /.reversed /.reversed (#= pattern)) - (or (|> pattern /.reversed (#= pattern) not) - (let [high (/.and (hex "FFFFFFFF00000000") - pattern) - low (/.and (hex "00000000FFFFFFFF") - pattern)] - (#= (/.reversed high) - low))))) + futility! + (and (|> pattern + (/.left_rotated /.width) + (#= pattern)) + (|> pattern + (/.right_rotated /.width) + (#= pattern)))] + (and false! + true! + inverse! + nullity! + futility!))) + (_.coverage [/.reversed] + (and (|> pattern /.reversed /.reversed (#= pattern)) + (or (|> pattern /.reversed (#= pattern) not) + (let [high (/.and (hex "FFFFFFFF00000000") + pattern) + low (/.and (hex "00000000FFFFFFFF") + pattern)] + (#= (/.reversed high) + low))))) ..bit ..shift diff --git a/stdlib/source/test/lux/math/number/i8.lux b/stdlib/source/test/lux/math/number/i8.lux index 3994b5433..23f91eca3 100644 --- a/stdlib/source/test/lux/math/number/i8.lux +++ b/stdlib/source/test/lux/math/number/i8.lux @@ -32,7 +32,7 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.i8 /.i64 /.width] - (let [actual (|> expected .i64 /.i8 /.i64)] - (# //i64.equivalence = expected actual))) + (_.coverage [/.i8 /.i64 /.width] + (let [actual (|> expected .i64 /.i8 /.i64)] + (# //i64.equivalence = expected actual))) )))) diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux index 9265507e7..02a8fe497 100644 --- a/stdlib/source/test/lux/math/number/int.lux +++ b/stdlib/source/test/lux/math/number/int.lux @@ -59,18 +59,18 @@ (do [! random.monad] [sample random.int] (all _.and - (_.cover [/.negative?] - (bit#= (/.negative? sample) - (/.< +0 sample))) - (_.cover [/.positive?] - (bit#= (/.positive? sample) - (/.> +0 sample))) - (_.cover [/.zero?] - (bit#= (/.zero? sample) - (/.= +0 sample))) - (_.cover [/.even? /.odd?] - (bit#= (/.even? sample) - (not (/.odd? sample)))) + (_.coverage [/.negative?] + (bit#= (/.negative? sample) + (/.< +0 sample))) + (_.coverage [/.positive?] + (bit#= (/.positive? sample) + (/.> +0 sample))) + (_.coverage [/.zero?] + (bit#= (/.zero? sample) + (/.= +0 sample))) + (_.coverage [/.even? /.odd?] + (bit#= (/.even? sample) + (not (/.odd? sample)))) ))) (def: .public test @@ -84,86 +84,86 @@ left random.int right random.int] (all _.and - (_.cover [/.+] - (and (/.= (/.+ left right) - (/.+ right left)) - (/.= sample (/.+ +0 sample)))) - (_.cover [/.-] - (and (/.= +0 (/.- sample sample)) - (/.= sample (/.- +0 sample)) - (/.= (/.opposite sample) - (/.- sample +0)) - (/.= /#bottom - (/.- /#bottom +0)))) - (_.cover [/.*] - (and (/.= (/.* left right) - (/.* right left)) - (/.= sample (/.* +1 sample)) - (/.= /#bottom - (/.* -1 /#bottom)))) - (_.cover [/./] - (and (/.= +1 (/./ sample sample)) - (/.= sample (/./ +1 sample)) - (/.= /#bottom - (/./ -1 /#bottom)))) - (_.cover [/.abs] - (bit#= (/.> sample (/.abs sample)) - (/.negative? sample))) - (_.cover [/.signum] - (/.= (/.abs sample) - (/.* (/.signum sample) sample))) - (_.cover [/.min] - (and (/.= (/.min left right) - (/.min right left)) - (/.= sample - (/.min /#top sample)) - (/.= /#bottom - (/.min /#bottom sample)))) - (_.cover [/.max] - (and (/.= (/.max left right) - (/.max right left)) - (/.= /#top - (/.max /#top sample)) - (/.= sample - (/.max /#bottom sample)))) + (_.coverage [/.+] + (and (/.= (/.+ left right) + (/.+ right left)) + (/.= sample (/.+ +0 sample)))) + (_.coverage [/.-] + (and (/.= +0 (/.- sample sample)) + (/.= sample (/.- +0 sample)) + (/.= (/.opposite sample) + (/.- sample +0)) + (/.= /#bottom + (/.- /#bottom +0)))) + (_.coverage [/.*] + (and (/.= (/.* left right) + (/.* right left)) + (/.= sample (/.* +1 sample)) + (/.= /#bottom + (/.* -1 /#bottom)))) + (_.coverage [/./] + (and (/.= +1 (/./ sample sample)) + (/.= sample (/./ +1 sample)) + (/.= /#bottom + (/./ -1 /#bottom)))) + (_.coverage [/.abs] + (bit#= (/.> sample (/.abs sample)) + (/.negative? sample))) + (_.coverage [/.signum] + (/.= (/.abs sample) + (/.* (/.signum sample) sample))) + (_.coverage [/.min] + (and (/.= (/.min left right) + (/.min right left)) + (/.= sample + (/.min /#top sample)) + (/.= /#bottom + (/.min /#bottom sample)))) + (_.coverage [/.max] + (and (/.= (/.max left right) + (/.max right left)) + (/.= /#top + (/.max /#top sample)) + (/.= sample + (/.max /#bottom sample)))) )) (do random.monad [left random.int right random.int] (all _.and - (_.cover [/.>] - (bit#= (/.> left right) - (/.< right left))) - (_.cover [/.<= /.>=] - (bit#= (/.<= left right) - (/.>= right left))) + (_.coverage [/.>] + (bit#= (/.> left right) + (/.< right left))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= left right) + (/.>= right left))) )) (do random.monad [left (random.only (|>> (/.= +0) not) random.int) right random.int] (all _.and - (_.cover [/.%] - (let [rem (/.% left right) - div (|> right (/.- rem) (/./ left))] - (/.= right - (|> div (/.* left) (/.+ rem))))) - (_.cover [/./%] - (let [[div rem] (/./% left right)] - (and (/.= div (/./ left right)) - (/.= rem (/.% left right))))) - (_.cover [/.mod] - (and (/.= (/.signum left) - (/.signum (/.mod left right))) - (/.= (/.signum right) - (/.signum (/.% left right))) - (if (/.= (/.signum left) (/.signum right)) - (/.= (/.% left right) - (/.mod left right)) - (or (and (/.= +0 (/.% left right)) - (/.= +0 (/.mod left right))) - (/.= (/.+ left (/.% left right)) - (/.mod left right)))))) + (_.coverage [/.%] + (let [rem (/.% left right) + div (|> right (/.- rem) (/./ left))] + (/.= right + (|> div (/.* left) (/.+ rem))))) + (_.coverage [/./%] + (let [[div rem] (/./% left right)] + (and (/.= div (/./ left right)) + (/.= rem (/.% left right))))) + (_.coverage [/.mod] + (and (/.= (/.signum left) + (/.signum (/.mod left right))) + (/.= (/.signum right) + (/.signum (/.% left right))) + (if (/.= (/.signum left) (/.signum right)) + (/.= (/.% left right) + (/.mod left right)) + (or (and (/.= +0 (/.% left right)) + (/.= +0 (/.mod left right))) + (/.= (/.+ left (/.% left right)) + (/.mod left right)))))) )) (do [! random.monad] [.let [random (|> random.int @@ -172,82 +172,82 @@ left random right random] (all _.and - (_.cover [/.gcd] - (let [gcd (/.gcd left right)] - (and (/.= +0 (/.% gcd left)) - (/.= +0 (/.% gcd right))))) - (_.cover [/.extended_gcd] - (let [[[left_k right_k] gcd] (/.extended_gcd left right) + (_.coverage [/.gcd] + (let [gcd (/.gcd left right)] + (and (/.= +0 (/.% gcd left)) + (/.= +0 (/.% gcd right))))) + (_.coverage [/.extended_gcd] + (let [[[left_k right_k] gcd] (/.extended_gcd left right) - same_gcd! - (/.= gcd - (/.gcd left right)) - - bezout_identity! - (/.= gcd - (/.+ (/.* left_k left) - (/.* right_k right)))] - (and same_gcd! - bezout_identity!))) - (_.cover [/.co_prime?] - (bit#= (/.= +1 (/.gcd left right)) - (/.co_prime? left right))) - (_.cover [/.lcm] - (let [lcm (/.lcm left right)] - (and (/.= +0 (/.% left lcm)) - (/.= +0 (/.% right lcm))))) + same_gcd! + (/.= gcd + (/.gcd left right)) + + bezout_identity! + (/.= gcd + (/.+ (/.* left_k left) + (/.* right_k right)))] + (and same_gcd! + bezout_identity!))) + (_.coverage [/.co_prime?] + (bit#= (/.= +1 (/.gcd left right)) + (/.co_prime? left right))) + (_.coverage [/.lcm] + (let [lcm (/.lcm left right)] + (and (/.= +0 (/.% left lcm)) + (/.= +0 (/.% right lcm))))) )) (do random.monad [expected random.int] - (_.cover [/.opposite] - (let [subtraction! - (/.= +0 (/.+ (/.opposite expected) expected)) + (_.coverage [/.opposite] + (let [subtraction! + (/.= +0 (/.+ (/.opposite expected) expected)) - inverse! - (|> expected /.opposite /.opposite (/.= expected))] - (and subtraction! - inverse!)))) + inverse! + (|> expected /.opposite /.opposite (/.= expected))] + (and subtraction! + inverse!)))) (do [! random.monad] [expected (# ! each (/.% +1,000,000) random.int) sample random.int] - (_.cover [/.frac] - (and (|> expected /.frac f.int (/.= expected)) - (f.number? (/.frac sample))))) + (_.coverage [/.frac] + (and (|> expected /.frac f.int (/.= expected)) + (f.number? (/.frac sample))))) (do [! random.monad] [pattern random.int idx (# ! each (n.% i64.width) random.nat)] - (_.cover [/.right_shifted] - (let [nullity! - (/.= pattern (/.right_shifted 0 pattern)) + (_.coverage [/.right_shifted] + (let [nullity! + (/.= pattern (/.right_shifted 0 pattern)) - idempotency! - (/.= pattern (/.right_shifted i64.width pattern)) + idempotency! + (/.= pattern (/.right_shifted i64.width pattern)) - sign_mask (i64.left_shifted (-- i64.width) 1) - mantissa_mask (-- (i64.left_shifted (n.- idx i64.width) 1)) - co_mantissa_mask (i64.not mantissa_mask) + sign_mask (i64.left_shifted (-- i64.width) 1) + mantissa_mask (-- (i64.left_shifted (n.- idx i64.width) 1)) + co_mantissa_mask (i64.not mantissa_mask) - sign_preservation! - (/.= (i64.and sign_mask pattern) - (i64.and sign_mask (/.right_shifted idx pattern))) + sign_preservation! + (/.= (i64.and sign_mask pattern) + (i64.and sign_mask (/.right_shifted idx pattern))) - mantissa_parity! - (/.= (i64.and mantissa_mask (i64.right_shifted idx pattern)) - (i64.and mantissa_mask (/.right_shifted idx pattern))) + mantissa_parity! + (/.= (i64.and mantissa_mask (i64.right_shifted idx pattern)) + (i64.and mantissa_mask (/.right_shifted idx pattern))) - co_mantissa_disparity! - (or (n.= 0 idx) - (and (/.= +0 (i64.and co_mantissa_mask (i64.right_shifted idx pattern))) - (/.= (if (/.< +0 pattern) - (.int co_mantissa_mask) - +0) - (i64.and co_mantissa_mask (/.right_shifted idx pattern)))))] - (and nullity! - idempotency! - sign_preservation! - mantissa_parity! - co_mantissa_disparity! - )))) + co_mantissa_disparity! + (or (n.= 0 idx) + (and (/.= +0 (i64.and co_mantissa_mask (i64.right_shifted idx pattern))) + (/.= (if (/.< +0 pattern) + (.int co_mantissa_mask) + +0) + (i64.and co_mantissa_mask (/.right_shifted idx pattern)))))] + (and nullity! + idempotency! + sign_preservation! + mantissa_parity! + co_mantissa_disparity! + )))) ..predicate ..signature diff --git a/stdlib/source/test/lux/math/number/nat.lux b/stdlib/source/test/lux/math/number/nat.lux index 05c248337..9dfc823c9 100644 --- a/stdlib/source/test/lux/math/number/nat.lux +++ b/stdlib/source/test/lux/math/number/nat.lux @@ -57,9 +57,9 @@ (do [! random.monad] [sample random.nat] (all _.and - (_.cover [/.even? /.odd?] - (bit#= (/.even? sample) - (not (/.odd? sample)))) + (_.coverage [/.even? /.odd?] + (bit#= (/.even? sample) + (not (/.odd? sample)))) ))) (def: .public test @@ -70,62 +70,62 @@ (do random.monad [sample random.nat] (all _.and - (_.cover [/.-] - (and (/.= 0 (/.- sample sample)) - (/.= sample (/.- 0 sample)))) - (_.cover [/./] - (and (/.= 1 (/./ sample sample)) - (/.= sample (/./ 1 sample)))) + (_.coverage [/.-] + (and (/.= 0 (/.- sample sample)) + (/.= sample (/.- 0 sample)))) + (_.coverage [/./] + (and (/.= 1 (/./ sample sample)) + (/.= sample (/./ 1 sample)))) )) (do random.monad [left random.nat right random.nat] (all _.and - (_.cover [/.>] - (bit#= (/.> left right) - (/.< right left))) - (_.cover [/.<= /.>=] - (bit#= (/.<= left right) - (/.>= right left))) + (_.coverage [/.>] + (bit#= (/.> left right) + (/.< right left))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= left right) + (/.>= right left))) )) (do random.monad [left (random.only (|>> (/.= 0) not) random.nat) right random.nat] (all _.and - (_.cover [/.%] - (let [rem (/.% left right) - div (|> right (/.- rem) (/./ left))] - (/.= right - (|> div (/.* left) (/.+ rem))))) - (_.cover [/./%] - (let [[div rem] (/./% left right)] - (and (/.= div (/./ left right)) - (/.= rem (/.% left right))))) + (_.coverage [/.%] + (let [rem (/.% left right) + div (|> right (/.- rem) (/./ left))] + (/.= right + (|> div (/.* left) (/.+ rem))))) + (_.coverage [/./%] + (let [[div rem] (/./% left right)] + (and (/.= div (/./ left right)) + (/.= rem (/.% left right))))) )) (do [! random.monad] [.let [random (# ! each (|>> (/.% 1,000) ++) random.nat)] left random right random] (all _.and - (_.cover [/.gcd] - (let [gcd (/.gcd left right)] - (and (/.= 0 (/.% gcd left)) - (/.= 0 (/.% gcd right))))) - (_.cover [/.co_prime?] - (bit#= (/.= 1 (/.gcd left right)) - (/.co_prime? left right))) - (_.cover [/.lcm] - (let [lcm (/.lcm left right)] - (and (/.= 0 (/.% left lcm)) - (/.= 0 (/.% right lcm))))) + (_.coverage [/.gcd] + (let [gcd (/.gcd left right)] + (and (/.= 0 (/.% gcd left)) + (/.= 0 (/.% gcd right))))) + (_.coverage [/.co_prime?] + (bit#= (/.= 1 (/.gcd left right)) + (/.co_prime? left right))) + (_.coverage [/.lcm] + (let [lcm (/.lcm left right)] + (and (/.= 0 (/.% left lcm)) + (/.= 0 (/.% right lcm))))) )) (do [! random.monad] [expected (# ! each (/.% 1,000,000) random.nat) sample random.nat] - (_.cover [/.frac] - (and (|> expected /.frac f.nat (/.= expected)) - (f.number? (/.frac sample))))) + (_.coverage [/.frac] + (and (|> expected /.frac f.nat (/.= expected)) + (f.number? (/.frac sample))))) ..predicate ..signature diff --git a/stdlib/source/test/lux/math/number/ratio.lux b/stdlib/source/test/lux/math/number/ratio.lux index a5af79e0b..de4afac08 100644 --- a/stdlib/source/test/lux/math/number/ratio.lux +++ b/stdlib/source/test/lux/math/number/ratio.lux @@ -57,71 +57,71 @@ [.let [(open "#[0]") /.equivalence] denom/0 ..part denom/1 ..part] - (_.cover [/.ratio] - (#= (/.ratio 0 denom/0) - (/.ratio 0 denom/1)))) + (_.coverage [/.ratio] + (#= (/.ratio 0 denom/0) + (/.ratio 0 denom/1)))) (do random.monad [numerator ..part denominator (random.only (|>> (n#= 1) not) ..part)] - (_.cover [/.nat] - (let [only_numerator! - (|> (/.ratio numerator) - /.nat - (maybe#each (n#= numerator)) - (maybe.else false)) + (_.coverage [/.nat] + (let [only_numerator! + (|> (/.ratio numerator) + /.nat + (maybe#each (n#= numerator)) + (maybe.else false)) - denominator_1! - (|> (/.ratio numerator 1) - /.nat - (maybe#each (n#= numerator)) - (maybe.else false)) + denominator_1! + (|> (/.ratio numerator 1) + /.nat + (maybe#each (n#= numerator)) + (maybe.else false)) - with_denominator! - (case (/.nat (/.ratio numerator denominator)) - {.#Some factor} - (and (n.= 0 (n.% denominator numerator)) - (n.= numerator (n.* factor denominator))) - - {.#None} - (not (n.= 0 (n.% denominator numerator))))] - (and only_numerator! - denominator_1! - with_denominator!)))) + with_denominator! + (case (/.nat (/.ratio numerator denominator)) + {.#Some factor} + (and (n.= 0 (n.% denominator numerator)) + (n.= numerator (n.* factor denominator))) + + {.#None} + (not (n.= 0 (n.% denominator numerator))))] + (and only_numerator! + denominator_1! + with_denominator!)))) (do random.monad [sample ..random] (all _.and - (_.cover [/.-] - (and (/.= (/.ratio 0) (/.- sample sample)) - (/.= sample (/.- (/.ratio 0) sample)))) - (_.cover [/./] - (and (/.= (/.ratio 1) (/./ sample sample)) - (/.= sample (/./ (/.ratio 1) sample)))) - (_.cover [/.reciprocal] - (/.= (/.ratio 1) - (/.* sample (/.reciprocal sample)))) + (_.coverage [/.-] + (and (/.= (/.ratio 0) (/.- sample sample)) + (/.= sample (/.- (/.ratio 0) sample)))) + (_.coverage [/./] + (and (/.= (/.ratio 1) (/./ sample sample)) + (/.= sample (/./ (/.ratio 1) sample)))) + (_.coverage [/.reciprocal] + (/.= (/.ratio 1) + (/.* sample (/.reciprocal sample)))) )) (do random.monad [left (random.only (|>> (/.= (/.ratio 0)) not) ..random) right ..random] - (_.cover [/.%] - (let [rem (/.% left right) - div (|> right (/.- rem) (/./ left))] - (and (/.= right - (|> div (/.* left) (/.+ rem))) - (case (/.nat div) - {.#Some _} true - {.#None} false))))) + (_.coverage [/.%] + (let [rem (/.% left right) + div (|> right (/.- rem) (/./ left))] + (and (/.= right + (|> div (/.* left) (/.+ rem))) + (case (/.nat div) + {.#Some _} true + {.#None} false))))) (do random.monad [left ..random right ..random] (all _.and - (_.cover [/.>] - (bit#= (/.> left right) - (/.< right left))) - (_.cover [/.<= /.>=] - (bit#= (/.<= left right) - (/.>= right left))) + (_.coverage [/.>] + (bit#= (/.> left right) + (/.< right left))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= left right) + (/.>= right left))) )) )))) diff --git a/stdlib/source/test/lux/math/number/rev.lux b/stdlib/source/test/lux/math/number/rev.lux index 7fe3c86dd..db2657d98 100644 --- a/stdlib/source/test/lux/math/number/rev.lux +++ b/stdlib/source/test/lux/math/number/rev.lux @@ -59,9 +59,9 @@ (_.for [.Rev]) (`` (all _.and (~~ (template [<half> <whole>] - [(_.cover [<half>] - (/.= <whole> - (/.+ <half> <half>)))] + [(_.coverage [<half>] + (/.= <whole> + (/.+ <half> <half>)))] [/./1 (-- /./1)] [/./2 .0] @@ -79,15 +79,15 @@ )) (do random.monad [sample random.rev] - (_.cover [/.-] - (and (/.= .0 (/.- sample sample)) - (/.= sample (/.- .0 sample))))) + (_.coverage [/.-] + (and (/.= .0 (/.- sample sample)) + (/.= sample (/.- .0 sample))))) (do [! random.monad] [left random.rev right random.rev] - (_.cover [/.*] - (and (/.< left (/.* left right)) - (/.< right (/.* left right))))) + (_.coverage [/.*] + (and (/.< left (/.* left right)) + (/.< right (/.* left right))))) (do [! random.monad] [.let [dividend (# ! each (i64.and (hex "FFFF")) random.rev) @@ -103,65 +103,65 @@ scale (# ! each (|>> (n.% 10) ++) random.nat)] (all _.and - (_.cover [/./] - (bit#= (/.< divisor/0 divisor/1) - (/.> (/./ divisor/0 dividend) (/./ divisor/1 dividend)))) - (_.cover [/.%] - (# i64.equivalence = - (.i64 (n.% (.nat divisor/0) (.nat dividend))) - (.i64 (/.% divisor/0 dividend)))) - (_.cover [/.up /.down] - (let [symmetry! - (|> dividend - (/.up scale) - (/.down scale) - (/.= dividend)) + (_.coverage [/./] + (bit#= (/.< divisor/0 divisor/1) + (/.> (/./ divisor/0 dividend) (/./ divisor/1 dividend)))) + (_.coverage [/.%] + (# i64.equivalence = + (.i64 (n.% (.nat divisor/0) (.nat dividend))) + (.i64 (/.% divisor/0 dividend)))) + (_.coverage [/.up /.down] + (let [symmetry! + (|> dividend + (/.up scale) + (/.down scale) + (/.= dividend)) - discrete_division! - (/.= (/.% (.rev scale) dividend) - (/.- (|> dividend - (/.down scale) - (/.up scale)) - dividend))] - (and symmetry! - discrete_division!))) - (_.cover [/.ratio] - (|> dividend - (/.up scale) - (/.ratio dividend) - (n.= scale))) + discrete_division! + (/.= (/.% (.rev scale) dividend) + (/.- (|> dividend + (/.down scale) + (/.up scale)) + dividend))] + (and symmetry! + discrete_division!))) + (_.coverage [/.ratio] + (|> dividend + (/.up scale) + (/.ratio dividend) + (n.= scale))) )) (do [! random.monad] [dividend random.rev divisor (random.only (|>> (/.= .0) not) random.rev)] - (_.cover [/./%] - (let [[quotient remainder] (/./% divisor dividend)] - (and (/.= (/./ divisor dividend) quotient) - (/.= (/.% divisor dividend) remainder))))) + (_.coverage [/./%] + (let [[quotient remainder] (/./% divisor dividend)] + (and (/.= (/./ divisor dividend) quotient) + (/.= (/.% divisor dividend) remainder))))) (do random.monad [left random.rev right random.rev] (all _.and - (_.cover [/.>] - (bit#= (/.> left right) - (/.< right left))) - (_.cover [/.<= /.>=] - (bit#= (/.<= left right) - (/.>= right left))) + (_.coverage [/.>] + (bit#= (/.> left right) + (/.< right left))) + (_.coverage [/.<= /.>=] + (bit#= (/.<= left right) + (/.>= right left))) )) (do random.monad [sample random.nat] - (_.cover [/.reciprocal] - (/.= (/.reciprocal sample) - (|> sample /.reciprocal .nat /.reciprocal .nat /.reciprocal)))) + (_.coverage [/.reciprocal] + (/.= (/.reciprocal sample) + (|> sample /.reciprocal .nat /.reciprocal .nat /.reciprocal)))) (do [! random.monad] [expected (# ! each (|>> f.abs (f.% +1.0)) random.safe_frac) sample random.rev] - (_.cover [/.frac] - (and (|> expected f.rev /.frac (f.= expected)) - (f.number? (/.frac sample))))) + (_.coverage [/.frac] + (and (|> expected f.rev /.frac (f.= expected)) + (f.number? (/.frac sample))))) ..signature )))) diff --git a/stdlib/source/test/lux/meta.lux b/stdlib/source/test/lux/meta.lux index 03c6c9b2e..5919d32af 100644 --- a/stdlib/source/test/lux/meta.lux +++ b/stdlib/source/test/lux/meta.lux @@ -76,32 +76,32 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] (all _.and - (_.cover [/.result] - (|> (# /.monad in expected) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual} - (n.= expected actual))))) - (_.cover [/.result'] - (|> (# /.monad in expected) - (/.result' expected_lux) - (!expect (^.multi {try.#Success [actual_lux actual]} - (and (same? expected_lux actual_lux) - (n.= expected actual)))))) - (_.cover [/.compiler_state] - (|> /.compiler_state - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_lux} - (same? expected_lux actual_lux))))) - (_.cover [/.version] - (|> /.version - (/.result expected_lux) - (!expect (^.multi {try.#Success it} - (same? version it))))) - (_.cover [/.configuration] - (|> /.configuration - (/.result expected_lux) - (!expect (^.multi {try.#Success it} - (same? configuration it))))) + (_.coverage [/.result] + (|> (# /.monad in expected) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual} + (n.= expected actual))))) + (_.coverage [/.result'] + (|> (# /.monad in expected) + (/.result' expected_lux) + (!expect (^.multi {try.#Success [actual_lux actual]} + (and (same? expected_lux actual_lux) + (n.= expected actual)))))) + (_.coverage [/.compiler_state] + (|> /.compiler_state + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_lux} + (same? expected_lux actual_lux))))) + (_.coverage [/.version] + (|> /.version + (/.result expected_lux) + (!expect (^.multi {try.#Success it} + (same? version it))))) + (_.coverage [/.configuration] + (|> /.configuration + (/.result expected_lux) + (!expect (^.multi {try.#Success it} + (same? configuration it))))) ))) (def: error_handling @@ -135,59 +135,59 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] (all _.and - (_.cover [/.failure] - (|> (/.failure expected_error) - (is (Meta Any)) - (/.result expected_lux) - (!expect (^.multi {try.#Failure actual_error} - (text#= (location.with location.dummy expected_error) - actual_error))))) - (_.cover [/.assertion] - (and (|> (/.assertion expected_error true) - (is (Meta Any)) - (/.result expected_lux) - (!expect {try.#Success []})) - (|> (/.assertion expected_error false) - (/.result expected_lux) - (!expect (^.multi {try.#Failure actual_error} - (text#= expected_error actual_error)))))) - (_.cover [/.either] - (and (|> (/.either (# /.monad in expected) - (is (Meta Nat) - (/.failure expected_error))) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))) - (|> (/.either (is (Meta Nat) - (/.failure expected_error)) - (# /.monad in expected)) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))) - (|> (/.either (is (Meta Nat) - (/.failure expected_error)) - (is (Meta Nat) - (/.failure expected_error))) - (/.result expected_lux) - (!expect (^.multi {try.#Failure actual_error} - (text#= (location.with location.dummy expected_error) - actual_error)))) - (|> (/.either (# /.monad in expected) - (# /.monad in dummy)) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual} - (n.= expected actual)))) - )) - (_.cover [/.try] - (and (|> (/.try (/.failure expected_error)) - (/.result expected_lux) - (!expect (^.multi {try.#Success {try.#Failure actual_error}} - (text#= (location.with location.dummy expected_error) - actual_error)))) - (|> (/.try (# /.monad in expected)) - (/.result expected_lux) - (!expect (^.multi {try.#Success {try.#Success actual}} - (same? expected actual)))))) + (_.coverage [/.failure] + (|> (/.failure expected_error) + (is (Meta Any)) + (/.result expected_lux) + (!expect (^.multi {try.#Failure actual_error} + (text#= (location.with location.dummy expected_error) + actual_error))))) + (_.coverage [/.assertion] + (and (|> (/.assertion expected_error true) + (is (Meta Any)) + (/.result expected_lux) + (!expect {try.#Success []})) + (|> (/.assertion expected_error false) + (/.result expected_lux) + (!expect (^.multi {try.#Failure actual_error} + (text#= expected_error actual_error)))))) + (_.coverage [/.either] + (and (|> (/.either (# /.monad in expected) + (is (Meta Nat) + (/.failure expected_error))) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) + (|> (/.either (is (Meta Nat) + (/.failure expected_error)) + (# /.monad in expected)) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) + (|> (/.either (is (Meta Nat) + (/.failure expected_error)) + (is (Meta Nat) + (/.failure expected_error))) + (/.result expected_lux) + (!expect (^.multi {try.#Failure actual_error} + (text#= (location.with location.dummy expected_error) + actual_error)))) + (|> (/.either (# /.monad in expected) + (# /.monad in dummy)) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual} + (n.= expected actual)))) + )) + (_.coverage [/.try] + (and (|> (/.try (/.failure expected_error)) + (/.result expected_lux) + (!expect (^.multi {try.#Success {try.#Failure actual_error}} + (text#= (location.with location.dummy expected_error) + actual_error)))) + (|> (/.try (# /.monad in expected)) + (/.result expected_lux) + (!expect (^.multi {try.#Success {try.#Success actual}} + (same? expected actual)))))) ))) (def: module_related @@ -242,63 +242,63 @@ .#host []]]] (<| (_.for [.Module]) (all _.and - (_.cover [/.current_module_name] - (|> /.current_module_name - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_current_module} - (text#= expected_current_module actual_current_module))))) - (_.cover [/.current_module] - (|> /.current_module - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_module} - (same? expected_module actual_module))))) - (_.cover [/.module] - (|> (/.module expected_current_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_module} - (same? expected_module actual_module))))) - (_.cover [/.module_exists?] - (and (|> (/.module_exists? expected_current_module) - (/.result expected_lux) - (!expect {try.#Success #1})) - (|> (/.module_exists? dummy_module) - (/.result expected_lux) - (!expect {try.#Success #0})))) - (_.cover [/.modules] - (|> /.modules - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_modules} - (same? expected_modules actual_modules))))) - (_.cover [/.imported_modules] - (and (|> (/.imported_modules expected_current_module) - (/.result expected_lux) - (try#each (# (list.equivalence text.equivalence) = - (list imported_module_name))) - (try.else false)) - (|> (/.imported_modules imported_module_name) - (/.result expected_lux) - (try#each (# (list.equivalence text.equivalence) = - (list))) - (try.else false)))) - (_.cover [/.imported_by?] - (|> (/.imported_by? imported_module_name expected_current_module) - (/.result expected_lux) - (try.else false))) - (_.cover [/.imported?] - (|> (/.imported? imported_module_name) - (/.result expected_lux) - (try.else false))) - (_.cover [/.normal] - (and (|> (/.normal ["" expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success [actual_module actual_short]} - (and (text#= expected_current_module actual_module) - (same? expected_short actual_short))))) - (|> (/.normal [dummy_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success [actual_module actual_short]} - (and (text#= dummy_module actual_module) - (same? expected_short actual_short))))))) + (_.coverage [/.current_module_name] + (|> /.current_module_name + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_current_module} + (text#= expected_current_module actual_current_module))))) + (_.coverage [/.current_module] + (|> /.current_module + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_module} + (same? expected_module actual_module))))) + (_.coverage [/.module] + (|> (/.module expected_current_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_module} + (same? expected_module actual_module))))) + (_.coverage [/.module_exists?] + (and (|> (/.module_exists? expected_current_module) + (/.result expected_lux) + (!expect {try.#Success #1})) + (|> (/.module_exists? dummy_module) + (/.result expected_lux) + (!expect {try.#Success #0})))) + (_.coverage [/.modules] + (|> /.modules + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_modules} + (same? expected_modules actual_modules))))) + (_.coverage [/.imported_modules] + (and (|> (/.imported_modules expected_current_module) + (/.result expected_lux) + (try#each (# (list.equivalence text.equivalence) = + (list imported_module_name))) + (try.else false)) + (|> (/.imported_modules imported_module_name) + (/.result expected_lux) + (try#each (# (list.equivalence text.equivalence) = + (list))) + (try.else false)))) + (_.coverage [/.imported_by?] + (|> (/.imported_by? imported_module_name expected_current_module) + (/.result expected_lux) + (try.else false))) + (_.coverage [/.imported?] + (|> (/.imported? imported_module_name) + (/.result expected_lux) + (try.else false))) + (_.coverage [/.normal] + (and (|> (/.normal ["" expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success [actual_module actual_short]} + (and (text#= expected_current_module actual_module) + (same? expected_short actual_short))))) + (|> (/.normal [dummy_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success [actual_module actual_short]} + (and (text#= dummy_module actual_module) + (same? expected_short actual_short))))))) )))) (def: random_location @@ -341,35 +341,35 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []]]] (all _.and - (_.cover [/.target] - (|> /.target - (/.result expected_lux) - (try#each (same? target)) - (try.else false))) - (_.cover [/.seed] - (|> (do /.monad - [pre /.seed - post /.seed] - (in [pre post])) - (/.result expected_lux) - (!expect (^.multi {try.#Success [actual_pre actual_post]} - (and (n.= expected_seed actual_pre) - (n.= (++ expected_seed) actual_post)))))) - (_.cover [/.location] - (|> /.location - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_location} - (same? expected_location actual_location))))) - (_.cover [/.expected_type] - (|> /.expected_type - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_type} - (same? expected_type actual_type))))) - (_.cover [.Type_Context /.type_context] - (|> /.type_context - (/.result expected_lux) - (try#each (same? type_context)) - (try.else false))) + (_.coverage [/.target] + (|> /.target + (/.result expected_lux) + (try#each (same? target)) + (try.else false))) + (_.coverage [/.seed] + (|> (do /.monad + [pre /.seed + post /.seed] + (in [pre post])) + (/.result expected_lux) + (!expect (^.multi {try.#Success [actual_pre actual_post]} + (and (n.= expected_seed actual_pre) + (n.= (++ expected_seed) actual_post)))))) + (_.coverage [/.location] + (|> /.location + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_location} + (same? expected_location actual_location))))) + (_.coverage [/.expected_type] + (|> /.expected_type + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type))))) + (_.coverage [.Type_Context /.type_context] + (|> /.type_context + (/.result expected_lux) + (try#each (same? type_context)) + (try.else false))) ))) (def: definition_related @@ -433,58 +433,58 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []]])))]] (all _.and - (_.cover [.Global .Alias /.globals] - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro}) - - current_globals! - (|> (/.globals expected_current_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_globals} - (same? current_globals actual_globals)))) - - macro_globals! - (|> (/.globals expected_macro_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_globals} - (same? macro_globals actual_globals))))] - (and current_globals! - macro_globals!))) - (_.cover [.Definition /.definitions] - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro})] - (and (|> (/.definitions expected_current_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) - (|> (/.definitions expected_macro_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 1 (list.size actual_definitions))))) - ))) - (_.cover [/.exports] - (and (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro})] - (and (|> (/.exports expected_current_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) - (|> (/.exports expected_macro_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 1 (list.size actual_definitions))))) - )) - (let [[current_globals macro_globals expected_lux] - (expected_lux false {.#Some .Macro})] - (and (|> (/.exports expected_current_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) - (|> (/.exports expected_macro_module) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_definitions} - (n.= 0 (list.size actual_definitions))))) - )))) + (_.coverage [.Global .Alias /.globals] + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro}) + + current_globals! + (|> (/.globals expected_current_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_globals} + (same? current_globals actual_globals)))) + + macro_globals! + (|> (/.globals expected_macro_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_globals} + (same? macro_globals actual_globals))))] + (and current_globals! + macro_globals!))) + (_.coverage [.Definition /.definitions] + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro})] + (and (|> (/.definitions expected_current_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) + (|> (/.definitions expected_macro_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 1 (list.size actual_definitions))))) + ))) + (_.coverage [/.exports] + (and (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro})] + (and (|> (/.exports expected_current_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) + (|> (/.exports expected_macro_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 1 (list.size actual_definitions))))) + )) + (let [[current_globals macro_globals expected_lux] + (expected_lux false {.#Some .Macro})] + (and (|> (/.exports expected_current_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) + (|> (/.exports expected_macro_module) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_definitions} + (n.= 0 (list.size actual_definitions))))) + )))) ))) (def: search_related @@ -549,116 +549,116 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []]])))]] (all _.and - (_.cover [/.export] - (and (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some expected_type})] - (|> (/.export [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect {try.#Success _}))) - (let [[current_globals macro_globals expected_lux] - (expected_lux false {.#Some expected_type})] - (|> (/.export [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect {try.#Failure _}))))) - (_.cover [/.macro] - (let [same_module! - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro})] - (|> (/.macro [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success {.#Some actual_value}} - (same? expected_value actual_value))))) - - not_macro! - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some expected_type})] - (|> (/.macro [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect {try.#Success {.#None}}))) - - not_found! - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#None})] - (|> (/.macro [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect {try.#Success {.#None}}))) - - aliasing! - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro})] - (|> (/.macro [expected_current_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success {.#Some actual_value}} - (same? expected_value actual_value)))))] - (and same_module! - not_macro! - not_found! - aliasing!))) - (_.cover [/.de_aliased] - (let [[current_globals macro_globals expected_lux] - (expected_lux true {.#Some .Macro})] - (and (|> (/.de_aliased [expected_macro_module expected_short]) - (/.result expected_lux) - (try#each (symbol#= [expected_macro_module expected_short])) - (try.else false)) - (|> (/.de_aliased [expected_current_module expected_short]) - (/.result expected_lux) - (try#each (symbol#= [expected_macro_module expected_short])) - (try.else false))))) - (_.cover [/.definition] - (let [[current_globals macro_globals expected_lux] - (expected_lux expected_exported? {.#Some expected_type}) - - definition! - (|> (/.definition [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success {.#Definition [actual_exported? actual_type actual_value]}} - (and (bit#= expected_exported? actual_exported?) - (same? expected_type actual_type) - (same? (as Any expected_value) actual_value))))) - - alias! - (|> (/.definition [expected_current_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success {.#Alias [actual_module actual_short]}} - (and (same? expected_macro_module actual_module) - (same? expected_short actual_short)))))] - (and definition! - alias!))) - (_.cover [/.definition_type] - (let [[current_globals macro_globals expected_lux] - (expected_lux expected_exported? {.#Some expected_type}) - - definition! - (|> (/.definition_type [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_type} - (same? expected_type actual_type)))) - - alias! - (|> (/.definition_type [expected_current_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_type} - (same? expected_type actual_type))))] - (and definition! - alias!))) - (_.cover [/.type_definition] - (let [[current_globals macro_globals expected_lux] - (expected_lux expected_exported? {.#Some .Type}) - - definition! - (|> (/.type_definition [expected_macro_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_value} - (same? (as .Type expected_value) actual_value)))) - - alias! - (|> (/.type_definition [expected_current_module expected_short]) - (/.result expected_lux) - (!expect (^.multi {try.#Success actual_value} - (same? (as .Type expected_value) actual_value))))] - (and definition! - alias!))) + (_.coverage [/.export] + (and (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some expected_type})] + (|> (/.export [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect {try.#Success _}))) + (let [[current_globals macro_globals expected_lux] + (expected_lux false {.#Some expected_type})] + (|> (/.export [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect {try.#Failure _}))))) + (_.coverage [/.macro] + (let [same_module! + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro})] + (|> (/.macro [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success {.#Some actual_value}} + (same? expected_value actual_value))))) + + not_macro! + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some expected_type})] + (|> (/.macro [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect {try.#Success {.#None}}))) + + not_found! + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#None})] + (|> (/.macro [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect {try.#Success {.#None}}))) + + aliasing! + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro})] + (|> (/.macro [expected_current_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success {.#Some actual_value}} + (same? expected_value actual_value)))))] + (and same_module! + not_macro! + not_found! + aliasing!))) + (_.coverage [/.de_aliased] + (let [[current_globals macro_globals expected_lux] + (expected_lux true {.#Some .Macro})] + (and (|> (/.de_aliased [expected_macro_module expected_short]) + (/.result expected_lux) + (try#each (symbol#= [expected_macro_module expected_short])) + (try.else false)) + (|> (/.de_aliased [expected_current_module expected_short]) + (/.result expected_lux) + (try#each (symbol#= [expected_macro_module expected_short])) + (try.else false))))) + (_.coverage [/.definition] + (let [[current_globals macro_globals expected_lux] + (expected_lux expected_exported? {.#Some expected_type}) + + definition! + (|> (/.definition [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success {.#Definition [actual_exported? actual_type actual_value]}} + (and (bit#= expected_exported? actual_exported?) + (same? expected_type actual_type) + (same? (as Any expected_value) actual_value))))) + + alias! + (|> (/.definition [expected_current_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success {.#Alias [actual_module actual_short]}} + (and (same? expected_macro_module actual_module) + (same? expected_short actual_short)))))] + (and definition! + alias!))) + (_.coverage [/.definition_type] + (let [[current_globals macro_globals expected_lux] + (expected_lux expected_exported? {.#Some expected_type}) + + definition! + (|> (/.definition_type [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type)))) + + alias! + (|> (/.definition_type [expected_current_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_type} + (same? expected_type actual_type))))] + (and definition! + alias!))) + (_.coverage [/.type_definition] + (let [[current_globals macro_globals expected_lux] + (expected_lux expected_exported? {.#Some .Type}) + + definition! + (|> (/.type_definition [expected_macro_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_value} + (same? (as .Type expected_value) actual_value)))) + + alias! + (|> (/.type_definition [expected_current_module expected_short]) + (/.result expected_lux) + (!expect (^.multi {try.#Success actual_value} + (same? (as .Type expected_value) actual_value))))] + (and definition! + alias!))) ))) (def: label_related @@ -733,71 +733,71 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []])]] (all _.and - (_.cover [/.tag_lists] - (let [equivalence (list.equivalence - (product.equivalence - (list.equivalence symbol.equivalence) - type.equivalence))] - (|> (/.tag_lists label_module) - (/.result expected_lux) - (try#each (# equivalence = (list [(list#each (|>> [label_module]) {.#Item tags_0}) - type_0] - [(list#each (|>> [label_module]) {.#Item tags_1}) - type_1]))) - (try.else false)))) - (_.cover [/.tags_of] - (|> (/.tags_of [label_module name_1]) - (/.result expected_lux) - (try#each (# (maybe.equivalence (list.equivalence symbol.equivalence)) = {.#Some (list#each (|>> [label_module]) {.#Item tags_1})})) - (try.else false))) - (_.cover [/.tag] - (|> {.#Item tags_0} - list.enumeration - (list.every? (function (_ [expected_index label]) - (|> [label_module label] - /.tag - (/.result expected_lux) - (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} - (let [correct_index! - (n.= expected_index - actual_index) - - correct_tags! - (# (list.equivalence symbol.equivalence) = - (list#each (|>> [label_module]) {.#Item tags_0}) - actual_tags) - - correct_type! - (type#= type_0 - actual_type)] - (and correct_index! - correct_tags! - correct_type!)))) - ))))) - (_.cover [/.slot] - (|> {.#Item tags_1} - list.enumeration - (list.every? (function (_ [expected_index label]) - (|> [label_module label] - /.slot - (/.result expected_lux) - (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} - (let [correct_index! - (n.= expected_index - actual_index) - - correct_tags! - (# (list.equivalence symbol.equivalence) = - (list#each (|>> [label_module]) {.#Item tags_1}) - actual_tags) - - correct_type! - (type#= type_1 - actual_type)] - (and correct_index! - correct_tags! - correct_type!)))) - ))))) + (_.coverage [/.tag_lists] + (let [equivalence (list.equivalence + (product.equivalence + (list.equivalence symbol.equivalence) + type.equivalence))] + (|> (/.tag_lists label_module) + (/.result expected_lux) + (try#each (# equivalence = (list [(list#each (|>> [label_module]) {.#Item tags_0}) + type_0] + [(list#each (|>> [label_module]) {.#Item tags_1}) + type_1]))) + (try.else false)))) + (_.coverage [/.tags_of] + (|> (/.tags_of [label_module name_1]) + (/.result expected_lux) + (try#each (# (maybe.equivalence (list.equivalence symbol.equivalence)) = {.#Some (list#each (|>> [label_module]) {.#Item tags_1})})) + (try.else false))) + (_.coverage [/.tag] + (|> {.#Item tags_0} + list.enumeration + (list.every? (function (_ [expected_index label]) + (|> [label_module label] + /.tag + (/.result expected_lux) + (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} + (let [correct_index! + (n.= expected_index + actual_index) + + correct_tags! + (# (list.equivalence symbol.equivalence) = + (list#each (|>> [label_module]) {.#Item tags_0}) + actual_tags) + + correct_type! + (type#= type_0 + actual_type)] + (and correct_index! + correct_tags! + correct_type!)))) + ))))) + (_.coverage [/.slot] + (|> {.#Item tags_1} + list.enumeration + (list.every? (function (_ [expected_index label]) + (|> [label_module label] + /.slot + (/.result expected_lux) + (!expect (^.multi {try.#Success [actual_index actual_tags actual_type]} + (let [correct_index! + (n.= expected_index + actual_index) + + correct_tags! + (# (list.equivalence symbol.equivalence) = + (list#each (|>> [label_module]) {.#Item tags_1}) + actual_tags) + + correct_type! + (type#= type_1 + actual_type)] + (and correct_index! + correct_tags! + correct_type!)))) + ))))) ))) (def: locals_related @@ -869,61 +869,61 @@ .#eval (as (-> Type Code (Meta Any)) []) .#host []])]] (all _.and - (_.cover [.Scope /.locals] - (let [equivalence (is (Equivalence (List (List [Text Type]))) - (list.equivalence - (list.equivalence - (product.equivalence - text.equivalence - type.equivalence))))] - (|> /.locals - (/.result expected_lux) - (try#each (# equivalence = (list (list [name_3 type_3]) - (list [name_1 type_1] - [name_2 type_2])))) - (try.else false)))) - (_.cover [/.var_type] - (and (|> (/.var_type name_0) - (/.result expected_lux) - (try#each (# type.equivalence = type_0)) - (try.else false)) - (|> (/.var_type name_1) - (/.result expected_lux) - (try#each (# type.equivalence = type_1)) - (try.else false)) - (|> (/.var_type name_2) - (/.result expected_lux) - (try#each (# type.equivalence = type_2)) - (try.else false)) - (|> (/.var_type name_3) - (/.result expected_lux) - (try#each (# type.equivalence = type_3)) - (try.else false)))) - (_.cover [/.type] - (and (|> (/.type ["" name_0]) - (/.result expected_lux) - (try#each (# type.equivalence = type_0)) - (try.else false)) - (|> (/.type ["" name_1]) - (/.result expected_lux) - (try#each (# type.equivalence = type_1)) - (try.else false)) - (|> (/.type ["" name_2]) - (/.result expected_lux) - (try#each (# type.equivalence = type_2)) - (try.else false)) - (|> (/.type ["" name_3]) - (/.result expected_lux) - (try#each (# type.equivalence = type_3)) - (try.else false)) - (|> (/.type [current_module name_4]) - (/.result expected_lux) - (try#each (# type.equivalence = type_4)) - (try.else false)) - (|> (/.type ["" name_4]) - (/.result expected_lux) - (try#each (# type.equivalence = type_4)) - (try.else false)))) + (_.coverage [.Scope /.locals] + (let [equivalence (is (Equivalence (List (List [Text Type]))) + (list.equivalence + (list.equivalence + (product.equivalence + text.equivalence + type.equivalence))))] + (|> /.locals + (/.result expected_lux) + (try#each (# equivalence = (list (list [name_3 type_3]) + (list [name_1 type_1] + [name_2 type_2])))) + (try.else false)))) + (_.coverage [/.var_type] + (and (|> (/.var_type name_0) + (/.result expected_lux) + (try#each (# type.equivalence = type_0)) + (try.else false)) + (|> (/.var_type name_1) + (/.result expected_lux) + (try#each (# type.equivalence = type_1)) + (try.else false)) + (|> (/.var_type name_2) + (/.result expected_lux) + (try#each (# type.equivalence = type_2)) + (try.else false)) + (|> (/.var_type name_3) + (/.result expected_lux) + (try#each (# type.equivalence = type_3)) + (try.else false)))) + (_.coverage [/.type] + (and (|> (/.type ["" name_0]) + (/.result expected_lux) + (try#each (# type.equivalence = type_0)) + (try.else false)) + (|> (/.type ["" name_1]) + (/.result expected_lux) + (try#each (# type.equivalence = type_1)) + (try.else false)) + (|> (/.type ["" name_2]) + (/.result expected_lux) + (try#each (# type.equivalence = type_2)) + (try.else false)) + (|> (/.type ["" name_3]) + (/.result expected_lux) + (try#each (# type.equivalence = type_3)) + (try.else false)) + (|> (/.type [current_module name_4]) + (/.result expected_lux) + (try#each (# type.equivalence = type_4)) + (try.else false)) + (|> (/.type ["" name_4]) + (/.result expected_lux) + (try#each (# type.equivalence = type_4)) + (try.else false)))) ))) (def: injection @@ -987,22 +987,22 @@ (do random.monad [expected_value random.nat expected_error (random.upper_case 1)] - (_.cover [/.lifted] - (and (|> expected_error - {try.#Failure} - (is (Try Nat)) - /.lifted - (/.result expected_lux) - (!expect (^.multi {try.#Failure actual} - (text#= (location.with expected_location expected_error) - actual)))) - (|> expected_value - {try.#Success} - (is (Try Nat)) - /.lifted - (/.result expected_lux) - (!expect (^.multi {try.#Success actual} - (same? expected_value actual))))))) + (_.coverage [/.lifted] + (and (|> expected_error + {try.#Failure} + (is (Try Nat)) + /.lifted + (/.result expected_lux) + (!expect (^.multi {try.#Failure actual} + (text#= (location.with expected_location expected_error) + actual)))) + (|> expected_value + {try.#Success} + (is (Try Nat)) + /.lifted + (/.result expected_lux) + (!expect (^.multi {try.#Success actual} + (same? expected_value actual))))))) ..compiler_related ..error_handling diff --git a/stdlib/source/test/lux/meta/configuration.lux b/stdlib/source/test/lux/meta/configuration.lux index 17d91168b..2bcb18f7e 100644 --- a/stdlib/source/test/lux/meta/configuration.lux +++ b/stdlib/source/test/lux/meta/configuration.lux @@ -57,41 +57,41 @@ (_.for [/.monoid] ($monoid.spec /.equivalence /.monoid (..random 5))) - (_.cover [/.empty] - (list.empty? /.empty)) - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.for] - (and (and (/.for ["left" "<<<" - "right" ">>>"] - true - ... else - false) - (/.for ["left" "<<<"] - true - ... else - false) - (/.for ["right" ">>>"] - true - ... else - false)) - (and (/.for ["yolo" ""] - false - ... else - true) - (/.for ["left" "yolo"] - false - ... else - true)))) - (_.cover [/.invalid] - (and (text.contains? (the exception.#label /.invalid) - (..failure (/.for))) - (text.contains? (the exception.#label /.invalid) - (..failure (/.for ["left" "yolo"] - ... else - false))))) + (_.coverage [/.empty] + (list.empty? /.empty)) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.for] + (and (and (/.for ["left" "<<<" + "right" ">>>"] + true + ... else + false) + (/.for ["left" "<<<"] + true + ... else + false) + (/.for ["right" ">>>"] + true + ... else + false)) + (and (/.for ["yolo" ""] + false + ... else + true) + (/.for ["left" "yolo"] + false + ... else + true)))) + (_.coverage [/.invalid] + (and (text.contains? (the exception.#label /.invalid) + (..failure (/.for))) + (text.contains? (the exception.#label /.invalid) + (..failure (/.for ["left" "yolo"] + ... else + false))))) )))) diff --git a/stdlib/source/test/lux/meta/location.lux b/stdlib/source/test/lux/meta/location.lux index 93f24f460..d76b386be 100644 --- a/stdlib/source/test/lux/meta/location.lux +++ b/stdlib/source/test/lux/meta/location.lux @@ -32,19 +32,19 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.here] - (not (# /.equivalence = (/.here) (/.here)))) + (_.coverage [/.here] + (not (# /.equivalence = (/.here) (/.here)))) (do random.monad [location ..random error (random.alphabetic 10)] - (_.cover [/.format /.with] - (let [located_error (/.with location error)] - (and (text.contains? (/.format location) - located_error) - (text.contains? error - located_error))))) + (_.coverage [/.format /.with] + (let [located_error (/.with location error)] + (and (text.contains? (/.format location) + located_error) + (text.contains? error + located_error))))) (do random.monad [[location _] $///code.random] - (_.cover [/.dummy] - (# /.equivalence = /.dummy location))) + (_.coverage [/.dummy] + (# /.equivalence = /.dummy location))) ))) diff --git a/stdlib/source/test/lux/meta/symbol.lux b/stdlib/source/test/lux/meta/symbol.lux index b372e93bd..e7b7df738 100644 --- a/stdlib/source/test/lux/meta/symbol.lux +++ b/stdlib/source/test/lux/meta/symbol.lux @@ -49,25 +49,25 @@ ($order.spec /.order (..random sizeM1 sizeS1))) (_.for [/.codec] (_.and ($codec.spec /.equivalence /.codec (..random sizeM1 sizeS1)) - (_.test "Encoding a symbol without a module component results in text equal to the short of the symbol." - (if (text.empty? module1) - (same? short1 (# /.codec encoded symbol1)) - #1)))) + (_.property "Encoding a symbol without a module component results in text equal to the short of the symbol." + (if (text.empty? module1) + (same? short1 (# /.codec encoded symbol1)) + #1)))) - (_.cover [/.separator] - (let [it (# /.codec encoded symbol1)] - (if (text.empty? module1) - (same? short1 it) - (text.contains? /.separator it)))) - (_.cover [/.module /.short] - (and (same? module1 (/.module symbol1)) - (same? short1 (/.short symbol1)))) + (_.coverage [/.separator] + (let [it (# /.codec encoded symbol1)] + (if (text.empty? module1) + (same? short1 it) + (text.contains? /.separator it)))) + (_.coverage [/.module /.short] + (and (same? module1 (/.module symbol1)) + (same? short1 (/.short symbol1)))) (_.for [.symbol] (let [(open "/#[0]") /.equivalence] (all _.and - (_.test "Can obtain Symbol from a symbol." - (and (/#= [.prelude_module "yolo"] (.symbol .yolo)) - (/#= ["test/lux/meta/symbol" "yolo"] (.symbol ..yolo)) - (/#= ["" "yolo"] (.symbol yolo)) - (/#= ["library/lux/test" "yolo"] (.symbol library/lux/test.yolo))))))) + (_.property "Can obtain Symbol from a symbol." + (and (/#= [.prelude_module "yolo"] (.symbol .yolo)) + (/#= ["test/lux/meta/symbol" "yolo"] (.symbol ..yolo)) + (/#= ["" "yolo"] (.symbol yolo)) + (/#= ["library/lux/test" "yolo"] (.symbol library/lux/test.yolo))))))) ))))) diff --git a/stdlib/source/test/lux/meta/version.lux b/stdlib/source/test/lux/meta/version.lux index 58e8296c9..4f0f769f9 100644 --- a/stdlib/source/test/lux/meta/version.lux +++ b/stdlib/source/test/lux/meta/version.lux @@ -38,18 +38,18 @@ (with_expansions [<current> (/.current) <fake> (static.random code.text (random.lower_case 1))]) (all _.and - (_.cover [/.latest] - (n.> 0 /.latest)) - (_.cover [/.current] - (not (text.empty? (/.current)))) - (_.cover [/.for] - (and (/.for <current> true - false) - (/.for <fake> false - true))) - (_.cover [/.invalid] - (and (text.contains? (the exception.#label /.invalid) - (..failure (/.for))) - (text.contains? (the exception.#label /.invalid) - (..failure (/.for <fake> false))))) + (_.coverage [/.latest] + (n.> 0 /.latest)) + (_.coverage [/.current] + (not (text.empty? (/.current)))) + (_.coverage [/.for] + (and (/.for <current> true + false) + (/.for <fake> false + true))) + (_.coverage [/.invalid] + (and (text.contains? (the exception.#label /.invalid) + (..failure (/.for))) + (text.contains? (the exception.#label /.invalid) + (..failure (/.for <fake> false))))) ))) diff --git a/stdlib/source/test/lux/program.lux b/stdlib/source/test/lux/program.lux index 2279a4526..f600adb53 100644 --- a/stdlib/source/test/lux/program.lux +++ b/stdlib/source/test/lux/program.lux @@ -31,43 +31,43 @@ (<| (_.covering /._) (do random.monad [inputs (random.list 5 (random.upper_case 5))] - (_.cover [/.program:] - (let [(open "list#[0]") (list.equivalence text.equivalence)] - (and (with_expansions [<program> (/.program: all_arguments - (io.io all_arguments))] - (let [outcome ((is (-> (List Text) (io.IO Any)) - (..actual_program <program>)) - inputs)] - (same? (is Any inputs) - (io.run! outcome)))) - (with_expansions [<program> (/.program: [arg/0 <cli>.any - arg/1 <cli>.any - arg/2 <cli>.any - arg/3 <cli>.any - arg/4 <cli>.any] - (io.io (list arg/4 arg/3 arg/2 arg/1 arg/0)))] - (let [outcome ((is (-> (List Text) (io.IO Any)) - (..actual_program <program>)) - inputs)] - (list#= (list.reversed inputs) - (as (List Text) (io.run! outcome))))) - (with_expansions [<program> (/.program: [all_arguments (<>.many <cli>.any)] - (io.io all_arguments))] - (let [outcome ((is (-> (List Text) (io.IO Any)) - (..actual_program <program>)) - inputs)] - (list#= inputs - (as (List Text) (io.run! outcome))))) - (with_expansions [<program> (/.program: [arg/0 <cli>.any - arg/1 <cli>.any - arg/2 <cli>.any - arg/3 <cli>.any] - (io.io []))] - (case (try ((is (-> (List Text) (io.IO Any)) - (..actual_program <program>)) - inputs)) - {try.#Success _} - false - - {try.#Failure _} - true)))))))) + (_.coverage [/.program:] + (let [(open "list#[0]") (list.equivalence text.equivalence)] + (and (with_expansions [<program> (/.program: all_arguments + (io.io all_arguments))] + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) + inputs)] + (same? (is Any inputs) + (io.run! outcome)))) + (with_expansions [<program> (/.program: [arg/0 <cli>.any + arg/1 <cli>.any + arg/2 <cli>.any + arg/3 <cli>.any + arg/4 <cli>.any] + (io.io (list arg/4 arg/3 arg/2 arg/1 arg/0)))] + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) + inputs)] + (list#= (list.reversed inputs) + (as (List Text) (io.run! outcome))))) + (with_expansions [<program> (/.program: [all_arguments (<>.many <cli>.any)] + (io.io all_arguments))] + (let [outcome ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) + inputs)] + (list#= inputs + (as (List Text) (io.run! outcome))))) + (with_expansions [<program> (/.program: [arg/0 <cli>.any + arg/1 <cli>.any + arg/2 <cli>.any + arg/3 <cli>.any] + (io.io []))] + (case (try ((is (-> (List Text) (io.IO Any)) + (..actual_program <program>)) + inputs)) + {try.#Success _} + false + + {try.#Failure _} + true)))))))) diff --git a/stdlib/source/test/lux/static.lux b/stdlib/source/test/lux/static.lux index 6fdf9b5dd..ff411b83a 100644 --- a/stdlib/source/test/lux/static.lux +++ b/stdlib/source/test/lux/static.lux @@ -24,71 +24,71 @@ (def: .public test Test (<| (_.covering /._) - (for @.old (_.test "PLACEHOLDER" true)) + (for @.old (_.property "PLACEHOLDER" true)) (_.for [meta.eval]) (`` (all _.and (~~ (template [<static> <random> <=> <+> <tag>] - [(_.cover [<static> <random>] - (with_expansions [<left> (<random>) - <right> (<random>) - <l+r> (<static> (<+> <left> <right>))] - (case (' <l+r>) - [_ {<tag> l+r}] - (<=> l+r (<+> <left> <right>)) + [(_.coverage [<static> <random>] + (with_expansions [<left> (<random>) + <right> (<random>) + <l+r> (<static> (<+> <left> <right>))] + (case (' <l+r>) + [_ {<tag> l+r}] + (<=> l+r (<+> <left> <right>)) - _ - false)))] + _ + false)))] [/.nat /.random_nat n.= n.+ .#Nat] [/.int /.random_int i.= i.+ .#Int] [/.rev /.random_rev r.= r.+ .#Rev] )) - (_.cover [/.frac /.random_frac] - (with_expansions [<left> (/.random_frac) - <right> (/.random_frac) - <l+r> (/.frac (f.+ <left> <right>))] - (case (' <l+r>) - [_ {.#Frac l+r}] - (or (f.= l+r (f.+ <left> <right>)) - (and (f.not_a_number? l+r) - (f.not_a_number? (f.+ <left> <right>)) - (or (f.not_a_number? <left>) - (f.not_a_number? <right>)))) + (_.coverage [/.frac /.random_frac] + (with_expansions [<left> (/.random_frac) + <right> (/.random_frac) + <l+r> (/.frac (f.+ <left> <right>))] + (case (' <l+r>) + [_ {.#Frac l+r}] + (or (f.= l+r (f.+ <left> <right>)) + (and (f.not_a_number? l+r) + (f.not_a_number? (f.+ <left> <right>)) + (or (f.not_a_number? <left>) + (f.not_a_number? <right>)))) - _ - false))) - (_.cover [/.text /.random] - (with_expansions [<left> (/.random code.text (random.alpha_numeric 1)) - <right> (/.random code.text (random.alpha_numeric 1)) - <l+r> (/.text (format <left> <right>))] - (case (' <l+r>) - [_ {.#Text l+r}] - (text#= l+r (format <left> <right>)) + _ + false))) + (_.coverage [/.text /.random] + (with_expansions [<left> (/.random code.text (random.alpha_numeric 1)) + <right> (/.random code.text (random.alpha_numeric 1)) + <l+r> (/.text (format <left> <right>))] + (case (' <l+r>) + [_ {.#Text l+r}] + (text#= l+r (format <left> <right>)) - _ - false))) - (_.cover [/.randoms] - (with_expansions [<amount> (/.random code.nat - (random#each (|>> (n.% 10) ++) random.nat)) - l/* (/.randoms code.nat (random.list <amount> random.nat))] - (and (n.= <amount> (list.size (list l/*))) - (n.= (list#mix n.+ 0 (list l/*)) - (all n.+ l/*))))) - (_.cover [/.literal] - (with_expansions [<left> (/.random code.text (random.alpha_numeric 1)) - <right> (/.random code.text (random.alpha_numeric 1)) - <l+r> (/.literal code.text (format <left> <right>))] - (case (' <l+r>) - [_ {.#Text l+r}] - (text#= l+r (format <left> <right>)) + _ + false))) + (_.coverage [/.randoms] + (with_expansions [<amount> (/.random code.nat + (random#each (|>> (n.% 10) ++) random.nat)) + l/* (/.randoms code.nat (random.list <amount> random.nat))] + (and (n.= <amount> (list.size (list l/*))) + (n.= (list#mix n.+ 0 (list l/*)) + (all n.+ l/*))))) + (_.coverage [/.literal] + (with_expansions [<left> (/.random code.text (random.alpha_numeric 1)) + <right> (/.random code.text (random.alpha_numeric 1)) + <l+r> (/.literal code.text (format <left> <right>))] + (case (' <l+r>) + [_ {.#Text l+r}] + (text#= l+r (format <left> <right>)) - _ - false))) - (_.cover [/.literals] - (with_expansions [l/0 (/.random_nat) - l/1 (/.random_nat) - l/2 (/.random_nat) - l/* (/.literals code.nat (list l/0 l/1 l/2))] - (n.= (all n.+ l/0 l/1 l/2) - (all n.+ l/*)))) + _ + false))) + (_.coverage [/.literals] + (with_expansions [l/0 (/.random_nat) + l/1 (/.random_nat) + l/2 (/.random_nat) + l/* (/.literals code.nat (list l/0 l/1 l/2))] + (n.= (all n.+ l/0 l/1 l/2) + (all n.+ l/*)))) )))) diff --git a/stdlib/source/test/lux/target.lux b/stdlib/source/test/lux/target.lux index 1f66a4f59..6c7436400 100644 --- a/stdlib/source/test/lux/target.lux +++ b/stdlib/source/test/lux/target.lux @@ -40,7 +40,7 @@ (<| (_.covering /._) (_.for [/.Target]) (.all _.and - (_.cover [<targets>] - ..verdict) + (_.coverage [<targets>] + ..verdict) ))) ) diff --git a/stdlib/source/test/lux/target/js.lux b/stdlib/source/test/lux/target/js.lux index 81587cd20..bfdbf32fb 100644 --- a/stdlib/source/test/lux/target/js.lux +++ b/stdlib/source/test/lux/target/js.lux @@ -74,26 +74,26 @@ int ..int_32 string (random.upper_case 5)] (all _.and - (_.cover [/.null] - (|> /.null - ..eval - (try#each (function (_ it) - (case it - {.#None} true - {.#Some _} false))) - (try.else false))) - (_.cover [/.boolean] - (expression (|>> (as Bit) (bit#= boolean)) - (/.boolean boolean))) - (_.cover [/.number] - (expression (|>> (as Frac) (f.= number)) - (/.number number))) - (_.cover [/.int] - (expression (|>> (as Frac) f.int (i.= int)) - (/.int int))) - (_.cover [/.string] - (expression (|>> (as Text) (text#= string)) - (/.string string))) + (_.coverage [/.null] + (|> /.null + ..eval + (try#each (function (_ it) + (case it + {.#None} true + {.#Some _} false))) + (try.else false))) + (_.coverage [/.boolean] + (expression (|>> (as Bit) (bit#= boolean)) + (/.boolean boolean))) + (_.coverage [/.number] + (expression (|>> (as Frac) (f.= number)) + (/.number number))) + (_.coverage [/.int] + (expression (|>> (as Frac) f.int (i.= int)) + (/.int int))) + (_.coverage [/.string] + (expression (|>> (as Text) (text#= string)) + (/.string string))) ))) (def: test|boolean @@ -103,17 +103,17 @@ right random.bit] (`` (all _.and (~~ (template [<js> <lux>] - [(_.cover [<js>] - (let [expected (<lux> left right)] - (expression (|>> (as Bit) (bit#= expected)) - (<js> (/.boolean left) (/.boolean right)))))] + [(_.coverage [<js>] + (let [expected (<lux> left right)] + (expression (|>> (as Bit) (bit#= expected)) + (<js> (/.boolean left) (/.boolean right)))))] [/.or .or] [/.and .and] )) - (_.cover [/.not] - (expression (|>> (as Bit) (bit#= (not left))) - (/.not (/.boolean left)))) + (_.coverage [/.not] + (expression (|>> (as Bit) (bit#= (not left))) + (/.not (/.boolean left)))) )))) (def: test|number @@ -124,10 +124,10 @@ subject random.safe_frac] (`` (all _.and (~~ (template [<js> <lux>] - [(_.cover [<js>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Frac) (f.= expected)) - (<js> (/.number parameter) (/.number subject)))))] + [(_.coverage [<js>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Frac) (f.= expected)) + (<js> (/.number parameter) (/.number subject)))))] [/.+ f.+] [/.- f.-] @@ -136,10 +136,10 @@ [/.% f.%] )) (~~ (template [<js> <lux>] - [(_.cover [<js>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Bit) (bit#= expected)) - (<js> (/.number parameter) (/.number subject)))))] + [(_.coverage [<js>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Bit) (bit#= expected)) + (<js> (/.number parameter) (/.number subject)))))] [/.< f.<] [/.<= f.<=] @@ -160,46 +160,46 @@ shift (# ! each (n.% 16) random.nat)] (`` (all _.and (~~ (template [<js> <lux>] - [(_.cover [<js>] - (let [expected (<lux> left right)] - (expression (|>> (as Frac) f.int (i.= expected)) - (<js> (/.int left) (/.int right)))))] + [(_.coverage [<js>] + (let [expected (<lux> left right)] + (expression (|>> (as Frac) f.int (i.= expected)) + (<js> (/.int left) (/.int right)))))] [/.bit_or i64.or] [/.bit_xor i64.xor] [/.bit_and i64.and] )) - (_.cover [/.opposite] - (expression (|>> (as Frac) f.int (i.= (i.* -1 i32))) - (/.opposite (/.i32 i32)))) - - (_.cover [/.i32] - (expression (|>> (as Frac) f.int (i.= i32)) - (/.i32 i32))) - (_.cover [/.to_i32] - (expression (|>> (as Frac) f.int (i.= i32)) - (/.to_i32 (/.int i32)))) - (_.cover [/.left_shift] - (let [expected (i64.left_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.left_shift (/.int (.int shift)) + (_.coverage [/.opposite] + (expression (|>> (as Frac) f.int (i.= (i.* -1 i32))) + (/.opposite (/.i32 i32)))) + + (_.coverage [/.i32] + (expression (|>> (as Frac) f.int (i.= i32)) + (/.i32 i32))) + (_.coverage [/.to_i32] + (expression (|>> (as Frac) f.int (i.= i32)) + (/.to_i32 (/.int i32)))) + (_.coverage [/.left_shift] + (let [expected (i64.left_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.left_shift (/.int (.int shift)) + (/.i32 i16))))) + (_.coverage [/.logic_right_shift] + (let [expected (i64.right_shifted shift (as_int_32 i16))] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.logic_right_shift (/.int (.int shift)) (/.i32 i16))))) - (_.cover [/.logic_right_shift] - (let [expected (i64.right_shifted shift (as_int_32 i16))] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.logic_right_shift (/.int (.int shift)) - (/.i32 i16))))) - (_.cover [/.arithmetic_right_shift] - (let [expected (i.right_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.arithmetic_right_shift (/.int (.int shift)) - (/.i32 i16))))) - (_.cover [/.bit_not] - (let [expected (if (i.< +0 i32) - (as_int_32 (i64.not i32)) - (i64.not (as_int_32 i32)))] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_not (/.i32 i32))))) + (_.coverage [/.arithmetic_right_shift] + (let [expected (i.right_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.arithmetic_right_shift (/.int (.int shift)) + (/.i32 i16))))) + (_.coverage [/.bit_not] + (let [expected (if (i.< +0 i32) + (as_int_32 (i64.not i32)) + (i64.not (as_int_32 i32)))] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_not (/.i32 i32))))) )))) (def: test|array @@ -212,14 +212,14 @@ (list.item index) (maybe.else f.not_a_number))]] (all _.and - (_.cover [/.array /.at] - (and (expression (|>> (as Frac) (f.= expected)) - (/.at (/.int (.int index)) - (/.array (list#each /.number items)))) - (expression (|>> (as Bit)) - (|> (/.array (list#each /.number items)) - (/.at (/.int (.int size))) - (/.= /.undefined))))) + (_.coverage [/.array /.at] + (and (expression (|>> (as Frac) (f.= expected)) + (/.at (/.int (.int index)) + (/.array (list#each /.number items)))) + (expression (|>> (as Bit)) + (|> (/.array (list#each /.number items)) + (/.at (/.int (.int size))) + (/.= /.undefined))))) ))) (def: test|object @@ -234,21 +234,21 @@ index (# ! each (n.% size) random.nat) items (random.list size random.safe_frac)] (all _.and - (_.cover [/.object /.the] - (expression (|>> (as Frac) (f.= expected)) - (/.the field (/.object (list [field (/.number expected)]))))) + (_.coverage [/.object /.the] + (expression (|>> (as Frac) (f.= expected)) + (/.the field (/.object (list [field (/.number expected)]))))) (let [expected (|> items (list.item index) (maybe.else f.not_a_number))] - (_.cover [/.do] - (expression (|>> (as Frac) f.int (i.= (.int index))) - (|> (/.array (list#each /.number items)) - (/.do "lastIndexOf" (list (/.number expected))))))) - (_.cover [/.undefined] - (expression (|>> (as Bit)) - (|> (/.object (list [field (/.number expected)])) - (/.the dummy) - (/.= /.undefined)))) + (_.coverage [/.do] + (expression (|>> (as Frac) f.int (i.= (.int index))) + (|> (/.array (list#each /.number items)) + (/.do "lastIndexOf" (list (/.number expected))))))) + (_.coverage [/.undefined] + (expression (|>> (as Bit)) + (|> (/.object (list [field (/.number expected)])) + (/.the dummy) + (/.= /.undefined)))) ))) (def: test|computation @@ -269,38 +269,38 @@ ..test|i32 ..test|array ..test|object - (_.cover [/.?] - (let [expected (if test then else)] - (expression (|>> (as Frac) (f.= expected)) - (/.? (/.boolean test) - (/.number then) - (/.number else))))) - (_.cover [/.not_a_number?] - (and (expression (|>> (as Bit)) - (/.not_a_number? (/.number f.not_a_number))) - (expression (|>> (as Bit) not) - (/.not_a_number? (/.number then))))) - (_.cover [/.type_of] - (and (expression (|>> (as Text) (text#= "boolean")) - (/.type_of (/.boolean boolean))) - (expression (|>> (as Text) (text#= "number")) - (/.type_of (/.number number))) - (expression (|>> (as Text) (text#= "string")) - (/.type_of (/.string string))) - (expression (|>> (as Text) (text#= "object")) - (/.type_of /.null)) - (expression (|>> (as Text) (text#= "object")) - (/.type_of (/.object (list [string (/.number number)])))) - (expression (|>> (as Text) (text#= "object")) - (/.type_of (/.array (list (/.boolean boolean) - (/.number number) - (/.string string))))) - (expression (|>> (as Text) (text#= "undefined")) - (/.type_of /.undefined)))) - (_.cover [/.comment] - (expression (|>> (as Frac) (f.= then)) - (/.comment comment - (/.number then)))) + (_.coverage [/.?] + (let [expected (if test then else)] + (expression (|>> (as Frac) (f.= expected)) + (/.? (/.boolean test) + (/.number then) + (/.number else))))) + (_.coverage [/.not_a_number?] + (and (expression (|>> (as Bit)) + (/.not_a_number? (/.number f.not_a_number))) + (expression (|>> (as Bit) not) + (/.not_a_number? (/.number then))))) + (_.coverage [/.type_of] + (and (expression (|>> (as Text) (text#= "boolean")) + (/.type_of (/.boolean boolean))) + (expression (|>> (as Text) (text#= "number")) + (/.type_of (/.number number))) + (expression (|>> (as Text) (text#= "string")) + (/.type_of (/.string string))) + (expression (|>> (as Text) (text#= "object")) + (/.type_of /.null)) + (expression (|>> (as Text) (text#= "object")) + (/.type_of (/.object (list [string (/.number number)])))) + (expression (|>> (as Text) (text#= "object")) + (/.type_of (/.array (list (/.boolean boolean) + (/.number number) + (/.string string))))) + (expression (|>> (as Text) (text#= "undefined")) + (/.type_of /.undefined)))) + (_.coverage [/.comment] + (expression (|>> (as Frac) (f.= then)) + (/.comment comment + (/.number then)))) ))) (def: test|expression @@ -313,9 +313,9 @@ ..test|literal) (_.for [/.Computation] ..test|computation) - (_.cover [/.,] - (expression (|>> (as Frac) (f.= expected)) - (/., (/.number dummy) (/.number expected)))) + (_.coverage [/.,] + (expression (|>> (as Frac) (f.= expected)) + (/., (/.number dummy) (/.number expected)))) )))) (def: test/var @@ -330,25 +330,25 @@ .let [$foreign (/.var foreign) $local (/.var local)]] (all _.and - (_.cover [/.var] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_* (/.closure (list $foreign) (/.return $foreign)) - (list (/.number number/0))))) - (_.cover [/.define] - (expression (|>> (as Frac) (f.= number/1)) - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.define $local (/.number number/1)) - (/.return $local))) - (list (/.number number/0))))) - (_.cover [/.declare] - (expression (|>> (as Frac) (f.= number/1)) - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.declare $local) - (/.set $local (/.number number/1)) - (/.return $local))) - (list (/.number number/0))))) + (_.coverage [/.var] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_* (/.closure (list $foreign) (/.return $foreign)) + (list (/.number number/0))))) + (_.coverage [/.define] + (expression (|>> (as Frac) (f.= number/1)) + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.define $local (/.number number/1)) + (/.return $local))) + (list (/.number number/0))))) + (_.coverage [/.declare] + (expression (|>> (as Frac) (f.= number/1)) + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.declare $local) + (/.set $local (/.number number/1)) + (/.return $local))) + (list (/.number number/0))))) ))) (def: test/location @@ -359,85 +359,85 @@ $foreign (# ! each /.var (random.lower_case 10)) field (random.upper_case 10)] (all _.and - (_.cover [/.set] - (and (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.+ $foreign $foreign)) - (/.return $foreign))) - (list (/.number number/0)))) - (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) - (let [@ (/.at (/.int +0) $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.array (list $foreign))) - (/.set @ (/.+ @ @)) - (/.return @))) - (list (/.number number/0))))) - (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) - (let [@ (/.the field $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.object (list [field $foreign]))) - (/.set @ (/.+ @ @)) - (/.return @))) - (list (/.number number/0))))))) - (_.cover [/.delete] - (and (and (expression (|>> (as Bit)) - (/.apply_* (/.closure (list) - (all /.then - (/.set $foreign (/.number number/0)) - (/.return (/.delete $foreign)))) - (list))) - (expression (|>> (as Bit) not) - (/.apply_* (/.closure (list $foreign) - (/.return (/.delete $foreign))) - (list (/.number number/0))))) - (expression (|>> (as Bit)) - (let [@ (/.at (/.int +0) $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.array (list $foreign))) - (/.return (|> (/.= (/.boolean true) (/.delete @)) - (/.and (/.= /.undefined @)))))) - (list (/.number number/0))))) - (expression (|>> (as Bit)) - (let [@ (/.the field $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.object (list [field $foreign]))) - (/.return (|> (/.= (/.boolean true) (/.delete @)) - (/.and (/.= /.undefined @)))))) - (list (/.number number/0))))) - )) - (_.cover [/.Access] - (`` (and (~~ (template [<js> <lux>] - [(expression (|>> (as Frac) f.int (i.= (<lux> int/0))) - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.statement (<js> $foreign)) - (/.return $foreign))) - (list (/.int int/0)))) - (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) - (let [@ (/.at (/.int +0) $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.array (list $foreign))) - (/.statement (<js> @)) - (/.return @))) - (list (/.int int/0))))) - (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) - (let [@ (/.the field $foreign)] - (/.apply_* (/.closure (list $foreign) - (all /.then - (/.set $foreign (/.object (list [field $foreign]))) - (/.statement (<js> @)) - (/.return @))) - (list (/.int int/0)))))] - - [/.++ .++] - [/.-- .--] - ))))) + (_.coverage [/.set] + (and (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.+ $foreign $foreign)) + (/.return $foreign))) + (list (/.number number/0)))) + (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) + (let [@ (/.at (/.int +0) $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.array (list $foreign))) + (/.set @ (/.+ @ @)) + (/.return @))) + (list (/.number number/0))))) + (expression (|>> (as Frac) (f.= (f.+ number/0 number/0))) + (let [@ (/.the field $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.object (list [field $foreign]))) + (/.set @ (/.+ @ @)) + (/.return @))) + (list (/.number number/0))))))) + (_.coverage [/.delete] + (and (and (expression (|>> (as Bit)) + (/.apply_* (/.closure (list) + (all /.then + (/.set $foreign (/.number number/0)) + (/.return (/.delete $foreign)))) + (list))) + (expression (|>> (as Bit) not) + (/.apply_* (/.closure (list $foreign) + (/.return (/.delete $foreign))) + (list (/.number number/0))))) + (expression (|>> (as Bit)) + (let [@ (/.at (/.int +0) $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.array (list $foreign))) + (/.return (|> (/.= (/.boolean true) (/.delete @)) + (/.and (/.= /.undefined @)))))) + (list (/.number number/0))))) + (expression (|>> (as Bit)) + (let [@ (/.the field $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.object (list [field $foreign]))) + (/.return (|> (/.= (/.boolean true) (/.delete @)) + (/.and (/.= /.undefined @)))))) + (list (/.number number/0))))) + )) + (_.coverage [/.Access] + (`` (and (~~ (template [<js> <lux>] + [(expression (|>> (as Frac) f.int (i.= (<lux> int/0))) + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.statement (<js> $foreign)) + (/.return $foreign))) + (list (/.int int/0)))) + (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) + (let [@ (/.at (/.int +0) $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.array (list $foreign))) + (/.statement (<js> @)) + (/.return @))) + (list (/.int int/0))))) + (expression (|>> (as Frac) f.int (i.= (<lux> int/0))) + (let [@ (/.the field $foreign)] + (/.apply_* (/.closure (list $foreign) + (all /.then + (/.set $foreign (/.object (list [field $foreign]))) + (/.statement (<js> @)) + (/.return @))) + (list (/.int int/0)))))] + + [/.++ .++] + [/.-- .--] + ))))) (_.for [/.Var] ..test/var) ))) @@ -459,93 +459,93 @@ $inner_index (/.var "inner_index") $outer_index (/.var "outer_index")]] (all _.and - (_.cover [/.break] - (let [expected (i.* (.int expected_inner_iterations) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $inner_index (/.int +0)) - (/.define $output (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) - /.break) - (/.set $output (/.+ $input $output)) - (/.set $inner_index (/.+ (/.int +1) $inner_index)) - )) - (/.return $output))) - (list (/.int input)))))) - (_.cover [/.continue] - (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $inner_index (/.int +0)) - (/.define $output (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.set $inner_index (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.continue) - (/.set $output (/.+ $input $output)) - )) - (/.return $output))) - (list (/.int input)))))) + (_.coverage [/.break] + (let [expected (i.* (.int expected_inner_iterations) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $inner_index (/.int +0)) + (/.define $output (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) + /.break) + (/.set $output (/.+ $input $output)) + (/.set $inner_index (/.+ (/.int +1) $inner_index)) + )) + (/.return $output))) + (list (/.int input)))))) + (_.coverage [/.continue] + (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $inner_index (/.int +0)) + (/.define $output (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set $inner_index (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.continue) + (/.set $output (/.+ $input $output)) + )) + (/.return $output))) + (list (/.int input)))))) (_.for [/.label /.with_label] (all _.and - (_.cover [/.break_at] - (let [expected (i.* (.int (n.* expected_outer_iterations - expected_inner_iterations)) - input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $output (/.int +0)) - (/.define $outer_index (/.int +0)) - (/.with_label @outer - (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index) - (all /.then - (/.define $inner_index (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.when (/.= (/.int (.int expected_outer_iterations)) $outer_index) - (/.break_at @outer)) - (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) - /.break) - (/.set $output (/.+ $input $output)) - (/.set $inner_index (/.+ (/.int +1) $inner_index)) - )) - (/.set $outer_index (/.+ (/.int +1) $outer_index)) - ))) - (/.return $output))) - (list (/.int input)))))) - (_.cover [/.continue_at] - (let [expected (i.* (.int (n.* (n.- expected_outer_iterations full_outer_iterations) - (n.- expected_inner_iterations full_inner_iterations))) - input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $output (/.int +0)) - (/.define $outer_index (/.int +0)) - (/.with_label @outer - (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index) - (all /.then - (/.set $outer_index (/.+ (/.int +1) $outer_index)) - (/.define $inner_index (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.set $inner_index (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_outer_iterations)) $outer_index) - (/.continue_at @outer)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.continue) - (/.set $output (/.+ $input $output)) - )) - ) - )) - (/.return $output))) - (list (/.int input)))))) + (_.coverage [/.break_at] + (let [expected (i.* (.int (n.* expected_outer_iterations + expected_inner_iterations)) + input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $output (/.int +0)) + (/.define $outer_index (/.int +0)) + (/.with_label @outer + (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index) + (all /.then + (/.define $inner_index (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.when (/.= (/.int (.int expected_outer_iterations)) $outer_index) + (/.break_at @outer)) + (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) + /.break) + (/.set $output (/.+ $input $output)) + (/.set $inner_index (/.+ (/.int +1) $inner_index)) + )) + (/.set $outer_index (/.+ (/.int +1) $outer_index)) + ))) + (/.return $output))) + (list (/.int input)))))) + (_.coverage [/.continue_at] + (let [expected (i.* (.int (n.* (n.- expected_outer_iterations full_outer_iterations) + (n.- expected_inner_iterations full_inner_iterations))) + input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $output (/.int +0)) + (/.define $outer_index (/.int +0)) + (/.with_label @outer + (/.while (/.< (/.int (.int full_outer_iterations)) $outer_index) + (all /.then + (/.set $outer_index (/.+ (/.int +1) $outer_index)) + (/.define $inner_index (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set $inner_index (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_outer_iterations)) $outer_index) + (/.continue_at @outer)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.continue) + (/.set $output (/.+ $input $output)) + )) + ) + )) + (/.return $output))) + (list (/.int input)))))) )) ))) @@ -560,43 +560,43 @@ expected|while (i.* (.int iterations) input) expected|do_while (i.* (.int (n.max 1 iterations)) input)]] (all _.and - (_.cover [/.while] - (expression (|>> (as Frac) f.int (i.= expected|while)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $index (/.int +0)) - (/.define $output (/.int +0)) - (/.while (/.< (/.int (.int iterations)) $index) - (all /.then - (/.set $output (/.+ $input $output)) - (/.set $index (/.+ (/.int +1) $index)) - )) - (/.return $output))) - (list (/.int input))))) - (_.cover [/.do_while] - (expression (|>> (as Frac) f.int (i.= expected|do_while)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $index (/.int +0)) - (/.define $output (/.int +0)) - (/.do_while (/.< (/.int (.int iterations)) $index) - (all /.then - (/.set $output (/.+ $input $output)) - (/.set $index (/.+ (/.int +1) $index)) - )) - (/.return $output))) - (list (/.int input))))) - (_.cover [/.for] - (expression (|>> (as Frac) f.int (i.= expected|while)) - (/.apply_* (/.closure (list $input) - (all /.then - (/.define $output (/.int +0)) - (/.for $index (/.int +0) - (/.< (/.int (.int iterations)) $index) - (/.++ $index) - (/.set $output (/.+ $input $output))) - (/.return $output))) - (list (/.int input))))) + (_.coverage [/.while] + (expression (|>> (as Frac) f.int (i.= expected|while)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $index (/.int +0)) + (/.define $output (/.int +0)) + (/.while (/.< (/.int (.int iterations)) $index) + (all /.then + (/.set $output (/.+ $input $output)) + (/.set $index (/.+ (/.int +1) $index)) + )) + (/.return $output))) + (list (/.int input))))) + (_.coverage [/.do_while] + (expression (|>> (as Frac) f.int (i.= expected|do_while)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $index (/.int +0)) + (/.define $output (/.int +0)) + (/.do_while (/.< (/.int (.int iterations)) $index) + (all /.then + (/.set $output (/.+ $input $output)) + (/.set $index (/.+ (/.int +1) $index)) + )) + (/.return $output))) + (list (/.int input))))) + (_.coverage [/.for] + (expression (|>> (as Frac) f.int (i.= expected|while)) + (/.apply_* (/.closure (list $input) + (all /.then + (/.define $output (/.int +0)) + (/.for $index (/.int +0) + (/.< (/.int (.int iterations)) $index) + (/.++ $index) + (/.set $output (/.+ $input $output))) + (/.return $output))) + (list (/.int input))))) (_.for [/.Label] ..test|label) ))) @@ -609,20 +609,20 @@ random.safe_frac) $ex (# ! each /.var (random.lower_case 10))] (all _.and - (_.cover [/.try] - (expression (|>> (as Frac) (f.= expected)) - (/.apply_* (/.closure (list) - (/.try (/.return (/.number expected)) - [$ex (/.return (/.number dummy))])) - (list)))) - (_.cover [/.throw] - (expression (|>> (as Frac) (f.= expected)) - (/.apply_* (/.closure (list) - (/.try (all /.then - (/.throw (/.number expected)) - (/.return (/.number dummy))) - [$ex (/.return $ex)])) - (list)))) + (_.coverage [/.try] + (expression (|>> (as Frac) (f.= expected)) + (/.apply_* (/.closure (list) + (/.try (/.return (/.number expected)) + [$ex (/.return (/.number dummy))])) + (list)))) + (_.coverage [/.throw] + (expression (|>> (as Frac) (f.= expected)) + (/.apply_* (/.closure (list) + (/.try (all /.then + (/.throw (/.number expected)) + (/.return (/.number dummy))) + [$ex (/.return $ex)])) + (list)))) ))) (def: test|apply @@ -635,27 +635,27 @@ $arg/1 (# ! each /.var (random.lower_case 11)) $arg/2 (# ! each /.var (random.lower_case 12))] (`` (all _.and - (_.cover [/.apply_1] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_1 (/.closure (list $arg/0) (/.return $arg/0)) - (/.number number/0)))) - (_.cover [/.apply_2] - (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1))) - (/.apply_2 (/.closure (list $arg/0 $arg/1) (/.return (all /.+ $arg/0 $arg/1))) - (/.number number/0) - (/.number number/1)))) - (_.cover [/.apply_3] - (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1 number/2))) - (/.apply_3 (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2))) - (/.number number/0) - (/.number number/1) - (/.number number/2)))) - (_.cover [/.apply_*] - (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1 number/2))) - (/.apply_* (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2))) - (list (/.number number/0) - (/.number number/1) - (/.number number/2))))) + (_.coverage [/.apply_1] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_1 (/.closure (list $arg/0) (/.return $arg/0)) + (/.number number/0)))) + (_.coverage [/.apply_2] + (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1))) + (/.apply_2 (/.closure (list $arg/0 $arg/1) (/.return (all /.+ $arg/0 $arg/1))) + (/.number number/0) + (/.number number/1)))) + (_.coverage [/.apply_3] + (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1 number/2))) + (/.apply_3 (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2))) + (/.number number/0) + (/.number number/1) + (/.number number/2)))) + (_.coverage [/.apply_*] + (expression (|>> (as Frac) (f.= (all f.+ number/0 number/1 number/2))) + (/.apply_* (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2))) + (list (/.number number/0) + (/.number number/1) + (/.number number/2))))) )))) (def: test|function @@ -668,36 +668,36 @@ field (random.lower_case 3) $class (# ! each /.var (random.upper_case 4))] (all _.and - (_.cover [/.closure /.return] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_* (/.closure (list) (/.return (/.number number/0))) - (list)))) - (_.cover [/.function] - (expression (|>> (as Frac) f.nat (n.= iterations)) - (/.apply_1 (/.function $self (list $arg/0) - (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply_1 $self (/.+ (/.int +1) $arg/0)) - $arg/0))) - (/.int +0)))) - (_.cover [/.function_definition] - (expression (|>> (as Frac) f.nat (n.= iterations)) - (/.apply_* (/.closure (list) - (all /.then - (/.function_definition $self (list $arg/0) - (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply_1 $self (/.+ (/.int +1) $arg/0)) - $arg/0))) - (/.return (/.apply_1 $self (/.int +0))))) - (list)))) - (_.cover [/.new] - (let [$this (/.var "this")] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_1 (/.closure (list $arg/0) - (all /.then - (/.function_definition $class (list) - (/.set (/.the field $this) $arg/0)) - (/.return (/.the field (/.new $class (list)))))) - (/.number number/0))))) + (_.coverage [/.closure /.return] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_* (/.closure (list) (/.return (/.number number/0))) + (list)))) + (_.coverage [/.function] + (expression (|>> (as Frac) f.nat (n.= iterations)) + (/.apply_1 (/.function $self (list $arg/0) + (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply_1 $self (/.+ (/.int +1) $arg/0)) + $arg/0))) + (/.int +0)))) + (_.coverage [/.function_definition] + (expression (|>> (as Frac) f.nat (n.= iterations)) + (/.apply_* (/.closure (list) + (all /.then + (/.function_definition $self (list $arg/0) + (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply_1 $self (/.+ (/.int +1) $arg/0)) + $arg/0))) + (/.return (/.apply_1 $self (/.int +0))))) + (list)))) + (_.coverage [/.new] + (let [$this (/.var "this")] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_1 (/.closure (list $arg/0) + (all /.then + (/.function_definition $class (list) + (/.set (/.the field $this) $arg/0)) + (/.return (/.the field (/.new $class (list)))))) + (/.number number/0))))) ..test|apply ))) @@ -719,47 +719,47 @@ ??? random.bit int ..int_16] (all _.and - (_.cover [/.if] - (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) + (_.coverage [/.if] + (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) + (/.apply_* (/.closure (list) + (/.if (/.boolean ???) + (/.return (/.number number/0)) + (/.return (/.number number/1)))) + (list)))) + (_.coverage [/.when] + (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) + (/.apply_* (/.closure (list) + (all /.then + (/.when (/.boolean ???) + (/.return (/.number number/0))) + (/.return (/.number number/1)))) + (list)))) + (_.coverage [/.switch] + (let [number/0' (%.frac number/0) + number/1' (%.frac number/1) + number/2' (%.frac number/2)] + (and (expression (|>> (as Text) (text#= number/0')) (/.apply_* (/.closure (list) - (/.if (/.boolean ???) - (/.return (/.number number/0)) - (/.return (/.number number/1)))) - (list)))) - (_.cover [/.when] - (expression (|>> (as Frac) (f.= (if ??? number/0 number/1))) + (/.switch (/.number number/0) + (list [(list (/.number number/0)) (/.return (/.string number/0'))] + [(list (/.number number/1)) (/.return (/.string number/1'))]) + {.#None})) + (list))) + (expression (|>> (as Text) (text#= number/1')) (/.apply_* (/.closure (list) - (all /.then - (/.when (/.boolean ???) - (/.return (/.number number/0))) - (/.return (/.number number/1)))) - (list)))) - (_.cover [/.switch] - (let [number/0' (%.frac number/0) - number/1' (%.frac number/1) - number/2' (%.frac number/2)] - (and (expression (|>> (as Text) (text#= number/0')) - (/.apply_* (/.closure (list) - (/.switch (/.number number/0) - (list [(list (/.number number/0)) (/.return (/.string number/0'))] - [(list (/.number number/1)) (/.return (/.string number/1'))]) - {.#None})) - (list))) - (expression (|>> (as Text) (text#= number/1')) - (/.apply_* (/.closure (list) - (/.switch (/.number number/1) - (list [(list (/.number number/0)) (/.return (/.string number/0'))] - [(list (/.number number/1)) (/.return (/.string number/1'))]) - {.#Some (/.return (/.string number/2'))})) - (list))) - (expression (|>> (as Text) (text#= number/2')) - (/.apply_* (/.closure (list) - (/.switch (/.number number/2) - (list [(list (/.number number/0)) (/.return (/.string number/0'))] - [(list (/.number number/1)) (/.return (/.string number/1'))]) - {.#Some (/.return (/.string number/2'))})) - (list))) - ))) + (/.switch (/.number number/1) + (list [(list (/.number number/0)) (/.return (/.string number/0'))] + [(list (/.number number/1)) (/.return (/.string number/1'))]) + {.#Some (/.return (/.string number/2'))})) + (list))) + (expression (|>> (as Text) (text#= number/2')) + (/.apply_* (/.closure (list) + (/.switch (/.number number/2) + (list [(list (/.number number/0)) (/.return (/.string number/0'))] + [(list (/.number number/1)) (/.return (/.string number/1'))]) + {.#Some (/.return (/.string number/2'))})) + (list))) + ))) ))) (def: test|statement @@ -774,55 +774,55 @@ ??? random.bit int ..int_16] (`` (all _.and - (_.cover [/.statement] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_1 (/.closure (list $arg/0) - (all /.then - (/.statement (/.+ $arg/0 $arg/0)) - (/.return $arg/0))) - (/.number number/0)))) + (_.coverage [/.statement] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_1 (/.closure (list $arg/0) + (all /.then + (/.statement (/.+ $arg/0 $arg/0)) + (/.return $arg/0))) + (/.number number/0)))) (~~ (template [<js> <lux>] - [(_.cover [<js>] - (expression (|>> (as Frac) f.int (i.= (<lux> int))) - (/.apply_1 (/.closure (list $arg/0) - (/.return (/., (<js> $arg/0) - $arg/0))) - (/.int int))))] + [(_.coverage [<js>] + (expression (|>> (as Frac) f.int (i.= (<lux> int))) + (/.apply_1 (/.closure (list $arg/0) + (/.return (/., (<js> $arg/0) + $arg/0))) + (/.int int))))] [/.++ .++] [/.-- .--] )) - (_.cover [/.then] - (expression (|>> (as Frac) (f.= number/0)) - (/.apply_2 (/.closure (list $arg/0 $arg/1) - (all /.then - (/.return $arg/0) - (/.return $arg/1))) - (/.number number/0) - (/.number number/1)))) - (_.cover [/.use_strict] - (and (expression (|>> (as Frac) (f.= number/0)) - (/.apply_* (/.closure (list) - (all /.then - /.use_strict - (/.declare $arg/0) - (/.set $arg/0 (/.number number/0)) - (/.return $arg/0))) - (list))) - (|> (/.apply_* (/.closure (list) - (all /.then - /.use_strict - ... (/.declare $arg/0) - (/.set $arg/0 (/.number number/0)) - (/.return $arg/0))) - (list)) - ..eval - (pipe.case - {try.#Success it} - false - - {try.#Failure error} - true)))) + (_.coverage [/.then] + (expression (|>> (as Frac) (f.= number/0)) + (/.apply_2 (/.closure (list $arg/0 $arg/1) + (all /.then + (/.return $arg/0) + (/.return $arg/1))) + (/.number number/0) + (/.number number/1)))) + (_.coverage [/.use_strict] + (and (expression (|>> (as Frac) (f.= number/0)) + (/.apply_* (/.closure (list) + (all /.then + /.use_strict + (/.declare $arg/0) + (/.set $arg/0 (/.number number/0)) + (/.return $arg/0))) + (list))) + (|> (/.apply_* (/.closure (list) + (all /.then + /.use_strict + ... (/.declare $arg/0) + (/.set $arg/0 (/.number number/0)) + (/.return $arg/0))) + (list)) + ..eval + (pipe.case + {try.#Success it} + false + + {try.#Failure error} + true)))) ..test|exception ..test|function ..test|branching diff --git a/stdlib/source/test/lux/target/jvm.lux b/stdlib/source/test/lux/target/jvm.lux index efbb44c8f..2121dfc19 100644 --- a/stdlib/source/test/lux/target/jvm.lux +++ b/stdlib/source/test/lux/target/jvm.lux @@ -909,18 +909,18 @@ try.trusted (format.result /class.writer)) loader (/loader.memory (/loader.new_library []))]] - (_.test "PUTSTATIC & PUTFIELD & GETFIELD & GETSTATIC" - (case (do try.monad - [_ (/loader.define class_name bytecode loader) - class (io.run! (/loader.load class_name loader)) - method (try (get_method static_method class)) - output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] - (in (as Int output))) - {try.#Success actual} - (i.= (as Int expected) (as Int actual)) - - {try.#Failure error} - false)))) + (_.property "PUTSTATIC & PUTFIELD & GETFIELD & GETSTATIC" + (case (do try.monad + [_ (/loader.define class_name bytecode loader) + class (io.run! (/loader.load class_name loader)) + method (try (get_method static_method class)) + output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] + (in (as Int output))) + {try.#Success actual} + (i.= (as Int expected) (as Int actual)) + + {try.#Failure error} + false)))) (def: array Test @@ -1728,20 +1728,20 @@ try.trusted (format.result /class.writer)) loader (/loader.memory (/loader.new_library []))]] - (_.test "Class & interface inheritance" - (case (do try.monad - [_ (/loader.define abstract_class abstract_bytecode loader) - _ (/loader.define interface_class interface_bytecode loader) - _ (/loader.define concrete_class concrete_bytecode loader) - class (io.run! (/loader.load concrete_class loader)) - method (try (get_method static_method class)) - output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] - (in (as Int output))) - {try.#Success actual} - (i.= (as Int expected) (as Int actual)) - - {try.#Failure error} - false)))) + (_.property "Class & interface inheritance" + (case (do try.monad + [_ (/loader.define abstract_class abstract_bytecode loader) + _ (/loader.define interface_class interface_bytecode loader) + _ (/loader.define concrete_class concrete_bytecode loader) + class (io.run! (/loader.load concrete_class loader)) + method (try (get_method static_method class)) + output (java/lang/reflect/Method::invoke (ffi.null) (ffi.array java/lang/Object 0) method)] + (in (as Int output))) + {try.#Success actual} + (i.= (as Int expected) (as Int actual)) + + {try.#Failure error} + false)))) (def: .public test Test diff --git a/stdlib/source/test/lux/target/lua.lux b/stdlib/source/test/lux/target/lua.lux index 7d81b41f5..631b754f5 100644 --- a/stdlib/source/test/lux/target/lua.lux +++ b/stdlib/source/test/lux/target/lua.lux @@ -52,25 +52,25 @@ float random.frac string (random.upper_case 5)] (all _.and - (_.cover [/.nil] - (|> /.nil - /.code - ..load - (pipe.case - {.#None} true - {.#Some _} false))) - (_.cover [/.boolean] - (expression (|>> (as Bit) (bit#= boolean)) - (/.boolean boolean))) - (_.cover [/.int] - (expression (|>> (as Int) (i.= int)) - (/.int int))) - (_.cover [/.float] - (expression (|>> (as Frac) (f.= float)) - (/.float float))) - (_.cover [/.string] - (expression (|>> (as Text) (text#= string)) - (/.string string))) + (_.coverage [/.nil] + (|> /.nil + /.code + ..load + (pipe.case + {.#None} true + {.#Some _} false))) + (_.coverage [/.boolean] + (expression (|>> (as Bit) (bit#= boolean)) + (/.boolean boolean))) + (_.coverage [/.int] + (expression (|>> (as Int) (i.= int)) + (/.int int))) + (_.coverage [/.float] + (expression (|>> (as Frac) (f.= float)) + (/.float float))) + (_.coverage [/.string] + (expression (|>> (as Text) (text#= string)) + (/.string string))) ))) (def: test|boolean @@ -80,17 +80,17 @@ right random.bit] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.boolean left) (/.boolean right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.boolean left) (/.boolean right)))))] [/.or .or] [/.and .and] )) - (_.cover [/.not] - (expression (|>> (as Bit) (bit#= (not left))) - (/.not (/.boolean left)))) + (_.coverage [/.not] + (expression (|>> (as Bit) (bit#= (not left))) + (/.not (/.boolean left)))) )))) (template [<bits>] @@ -115,35 +115,35 @@ subject random.int] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Int) (i.= expected)) - (</> (/.int left) (/.int right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Int) (i.= expected)) + (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] [/.bit_xor i64.xor] [/.bit_and i64.and] )) - (_.cover [/.opposite] - (expression (|>> (as Int) (i.= (i.- left +0))) - (/.opposite (/.int left)))) - (_.cover [/.bit_shl] - (let [expected (i64.left_shifted shift left)] - (expression (|>> (as Int) (i.= expected)) - (/.bit_shl (/.int (.int shift)) - (/.int left))))) - (_.cover [/.bit_shr] - (let [expected (i64.right_shifted shift left)] - (expression (|>> (as Int) (i.= expected)) - (/.bit_shr (/.int (.int shift)) - (/.int left))))) - (_.cover [/.//] - (let [expected (if (or (i.= (i.signum parameter) (i.signum subject)) - (i.= +0 (i.% parameter subject))) - (i./ parameter subject) - (-- (i./ parameter subject)))] - (expression (|>> (as Int) (i.= expected)) - (/.// (/.int parameter) (/.int subject))))) + (_.coverage [/.opposite] + (expression (|>> (as Int) (i.= (i.- left +0))) + (/.opposite (/.int left)))) + (_.coverage [/.bit_shl] + (let [expected (i64.left_shifted shift left)] + (expression (|>> (as Int) (i.= expected)) + (/.bit_shl (/.int (.int shift)) + (/.int left))))) + (_.coverage [/.bit_shr] + (let [expected (i64.right_shifted shift left)] + (expression (|>> (as Int) (i.= expected)) + (/.bit_shr (/.int (.int shift)) + (/.int left))))) + (_.coverage [/.//] + (let [expected (if (or (i.= (i.signum parameter) (i.signum subject)) + (i.= +0 (i.% parameter subject))) + (i./ parameter subject) + (-- (i./ parameter subject)))] + (expression (|>> (as Int) (i.= expected)) + (/.// (/.int parameter) (/.int subject))))) )))) (def: test|float @@ -154,10 +154,10 @@ subject random.safe_frac] (`` (all _.and (~~ (template [</> <lux> <pre>] - [(_.cover [</>] - (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (as Frac) (f.= expected)) - (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] + [(_.coverage [</>] + (let [expected (<lux> (<pre> parameter) (<pre> subject))] + (expression (|>> (as Frac) (f.= expected)) + (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] [/.- f.- |>] @@ -167,10 +167,10 @@ [/.^ f.pow f.abs] )) (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.float parameter) (/.float subject)))))] + [(_.coverage [</>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.float parameter) (/.float subject)))))] [/.< f.<] [/.<= f.<=] @@ -187,10 +187,10 @@ right (random.lower_case 8) .let [expected (format left right)]] (all _.and - (_.cover [/.concat] - (expression (|>> (as Text) (text#= expected)) - (|> (/.string left) - (/.concat (/.string right))))) + (_.coverage [/.concat] + (expression (|>> (as Text) (text#= expected)) + (|> (/.string left) + (/.concat (/.string right))))) ))) (def: test|array @@ -203,17 +203,17 @@ (list.item index) maybe.trusted)]] (all _.and - (_.cover [/.array /.item] - (and (expression (|>> (as Frac) (f.= expected)) - (/.item (/.int (.int (++ index))) - (/.array (list#each /.float items)))) - (expression (|>> (as Bit)) - (|> (/.array (list#each /.float items)) - (/.item (/.int (.int (++ size)))) - (/.= /.nil))))) - (_.cover [/.length] - (expression (|>> (as Int) (i.= (.int size))) - (/.length (/.array (list#each /.float items))))) + (_.coverage [/.array /.item] + (and (expression (|>> (as Frac) (f.= expected)) + (/.item (/.int (.int (++ index))) + (/.array (list#each /.float items)))) + (expression (|>> (as Bit)) + (|> (/.array (list#each /.float items)) + (/.item (/.int (.int (++ size)))) + (/.= /.nil))))) + (_.coverage [/.length] + (expression (|>> (as Int) (i.= (.int size))) + (/.length (/.array (list#each /.float items))))) ))) (def: test|table @@ -235,24 +235,24 @@ (random.upper_case 5)) method (random.upper_case 6)] (all _.and - (_.cover [/.table /.the] - (and (expression (|>> (as Frac) (f.= expected)) - (/.the field (/.table (list [field (/.float expected)])))) - (expression (|>> (as Bit)) - (|> (/.table (list [field (/.float expected)])) - (/.the non_field) - (/.= /.nil))))) - (_.cover [/.do /.function] - (expression (|>> (as Frac) (f.= expected)) - (|> (all /.then - (/.local/1 $table (/.table (list [field (/.float expected)]))) - (/.function (/.the method $table) (list $self $arg) - (/.if (/.= (/.float dummy) $arg) - (/.return (/.the field $self)) - (/.return $arg))) - (/.return (/.do method (list (/.float dummy)) $table))) - (/.closure (list)) - (/.apply (list))))) + (_.coverage [/.table /.the] + (and (expression (|>> (as Frac) (f.= expected)) + (/.the field (/.table (list [field (/.float expected)])))) + (expression (|>> (as Bit)) + (|> (/.table (list [field (/.float expected)])) + (/.the non_field) + (/.= /.nil))))) + (_.coverage [/.do /.function] + (expression (|>> (as Frac) (f.= expected)) + (|> (all /.then + (/.local/1 $table (/.table (list [field (/.float expected)]))) + (/.function (/.the method $table) (list $self $arg) + (/.if (/.= (/.float dummy) $arg) + (/.return (/.the field $self)) + (/.return $arg))) + (/.return (/.do method (list (/.float dummy)) $table))) + (/.closure (list)) + (/.apply (list))))) ))) (def: test|computation @@ -275,33 +275,33 @@ ..test|string ..test|array ..test|table - (_.cover [/.type/1] - (and (expression (|>> (as Text) (text#= "boolean")) - (/.type/1 (/.boolean boolean))) - (expression (|>> (as Text) (text#= "number")) - (/.type/1 (/.int int))) - (expression (|>> (as Text) (text#= "number")) - (/.type/1 (/.float float))) - (expression (|>> (as Text) (text#= "string")) - (/.type/1 (/.string string))) - (expression (|>> (as Text) (text#= "nil")) - (/.type/1 /.nil)) - (expression (|>> (as Text) (text#= "table")) - (/.type/1 (/.table (list [string (/.float float)])))) - (expression (|>> (as Text) (text#= "table")) - (/.type/1 (/.array (list (/.boolean boolean) - (/.float float) - (/.string string))))) - )) - (_.cover [/.require/1] - (expression (|>> (as Int) (i.= (i.abs int))) - (|> (/.require/1 (/.string "math")) - (/.the "abs") - (/.apply (list (/.int int)))))) - (_.cover [/.comment] - (expression (|>> (as Frac) (f.= then)) - (/.comment comment - (/.float then)))) + (_.coverage [/.type/1] + (and (expression (|>> (as Text) (text#= "boolean")) + (/.type/1 (/.boolean boolean))) + (expression (|>> (as Text) (text#= "number")) + (/.type/1 (/.int int))) + (expression (|>> (as Text) (text#= "number")) + (/.type/1 (/.float float))) + (expression (|>> (as Text) (text#= "string")) + (/.type/1 (/.string string))) + (expression (|>> (as Text) (text#= "nil")) + (/.type/1 /.nil)) + (expression (|>> (as Text) (text#= "table")) + (/.type/1 (/.table (list [string (/.float float)])))) + (expression (|>> (as Text) (text#= "table")) + (/.type/1 (/.array (list (/.boolean boolean) + (/.float float) + (/.string string))))) + )) + (_.coverage [/.require/1] + (expression (|>> (as Int) (i.= (i.abs int))) + (|> (/.require/1 (/.string "math")) + (/.the "abs") + (/.apply (list (/.int int)))))) + (_.coverage [/.comment] + (expression (|>> (as Frac) (f.= then)) + (/.comment comment + (/.float then)))) ))) (def: test|expression @@ -325,33 +325,33 @@ .let [$foreign (/.var foreign) $local (/.var local)]] (all _.and - (_.cover [/.var] - (expression (|>> (as Frac) (f.= float/0)) - (|> (/.return $foreign) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))) - (_.cover [/.let] - (expression (|>> (as Frac) (f.= float/1)) - (|> (all /.then - (/.let (list $local) (/.float float/1)) - (/.return $local)) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))) - (_.cover [/.local/1] - (expression (|>> (as Frac) (f.= float/1)) - (|> (all /.then - (/.local/1 $local (/.float float/1)) - (/.return $local)) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))) - (_.cover [/.local] - (expression (|>> (as Frac) (f.= float/1)) - (|> (all /.then - (/.local (list $local)) - (/.set (list $local) (/.float float/1)) - (/.return $local)) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))) + (_.coverage [/.var] + (expression (|>> (as Frac) (f.= float/0)) + (|> (/.return $foreign) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))) + (_.coverage [/.let] + (expression (|>> (as Frac) (f.= float/1)) + (|> (all /.then + (/.let (list $local) (/.float float/1)) + (/.return $local)) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))) + (_.coverage [/.local/1] + (expression (|>> (as Frac) (f.= float/1)) + (|> (all /.then + (/.local/1 $local (/.float float/1)) + (/.return $local)) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))) + (_.coverage [/.local] + (expression (|>> (as Frac) (f.= float/1)) + (|> (all /.then + (/.local (list $local)) + (/.set (list $local) (/.float float/1)) + (/.return $local)) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))) ))) (def: test/location @@ -365,43 +365,43 @@ $arg/1 (# ! each /.var (random.lower_case 12)) field (random.upper_case 10)] (all _.and - (_.cover [/.set] - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (_.coverage [/.set] + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (|> (all /.then + (/.set (list $foreign) (/.+ $foreign $foreign)) + (/.return $foreign)) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))) + (_.coverage [/.multi] + (and (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) + (/.return $arg/0)) + (/.closure (list)) + (/.apply (list)))) + (expression (|>> (as Frac) (f.= float/1)) + (|> (all /.then + (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) + (/.return $arg/1)) + (/.closure (list)) + (/.apply (list)))))) + (_.coverage [/.Access] + (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.item (/.int +1) $foreign)] (|> (all /.then - (/.set (list $foreign) (/.+ $foreign $foreign)) - (/.return $foreign)) + (/.set (list $foreign) (/.array (list $foreign))) + (/.set (list @) (/.+ @ @)) + (/.return @)) (/.closure (list $foreign)) (/.apply (list (/.float float/0)))))) - (_.cover [/.multi] - (and (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) - (/.return $arg/0)) - (/.closure (list)) - (/.apply (list)))) - (expression (|>> (as Frac) (f.= float/1)) - (|> (all /.then - (/.set (list $arg/0 $arg/1) (/.multi (list (/.float float/0) (/.float float/1)))) - (/.return $arg/1)) - (/.closure (list)) - (/.apply (list)))))) - (_.cover [/.Access] - (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.item (/.int +1) $foreign)] - (|> (all /.then - (/.set (list $foreign) (/.array (list $foreign))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))) - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.the field $foreign)] - (|> (all /.then - (/.set (list $foreign) (/.table (list [field $foreign]))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - (/.closure (list $foreign)) - (/.apply (list (/.float float/0)))))))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.the field $foreign)] + (|> (all /.then + (/.set (list $foreign) (/.table (list [field $foreign]))) + (/.set (list @) (/.+ @ @)) + (/.return @)) + (/.closure (list $foreign)) + (/.apply (list (/.float float/0)))))))) (_.for [/.Var] ..test/var) ))) @@ -423,77 +423,77 @@ .let [expected (i.* expected_iterations input) expected_iterations (/.int expected_iterations)]] (all _.and - (_.cover [/.break] - (let [=for_in (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $output (/.int +0)) - (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated full_iterations $input))) - (all /.then - (/.when (/.> expected_iterations $index) - /.break) - (/.set (list $output) (/.+ $input $output)))) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input))))) - - full_iterations (/.int (.int full_iterations)) - =while (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $index (/.int +0)) - (/.local/1 $output (/.int +0)) - (/.while (/.< full_iterations $index) - (all /.then - (/.when (/.= expected_iterations $index) - /.break) - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input))))) - =repeat (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $index (/.int +0)) - (/.local/1 $output (/.int +0)) - (/.repeat (/.= full_iterations $index) - (all /.then - (/.when (/.= expected_iterations $index) - /.break) - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input))))) - =for_step (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $output (/.int +0)) - (/.for_step $index (/.int +0) full_iterations (/.int +1) - (all /.then - (/.when (/.= expected_iterations $index) - /.break) - (/.set (list $output) (/.+ $input $output)))) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input)))))] - (and =while - =repeat - =for_step - =for_in))) - (_.cover [/.label /.set_label /.go_to] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $index (/.int +0)) - (/.local/1 $output (/.int +0)) - (/.set_label @loop) - (/.if (/.< expected_iterations $index) - (all /.then - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - (/.go_to @loop)) - (/.return $output))) - (/.closure (list $input)) - (/.apply (list (/.int input)))))) + (_.coverage [/.break] + (let [=for_in (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $output (/.int +0)) + (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated full_iterations $input))) + (all /.then + (/.when (/.> expected_iterations $index) + /.break) + (/.set (list $output) (/.+ $input $output)))) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input))))) + + full_iterations (/.int (.int full_iterations)) + =while (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $index (/.int +0)) + (/.local/1 $output (/.int +0)) + (/.while (/.< full_iterations $index) + (all /.then + (/.when (/.= expected_iterations $index) + /.break) + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input))))) + =repeat (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $index (/.int +0)) + (/.local/1 $output (/.int +0)) + (/.repeat (/.= full_iterations $index) + (all /.then + (/.when (/.= expected_iterations $index) + /.break) + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input))))) + =for_step (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $output (/.int +0)) + (/.for_step $index (/.int +0) full_iterations (/.int +1) + (all /.then + (/.when (/.= expected_iterations $index) + /.break) + (/.set (list $output) (/.+ $input $output)))) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input)))))] + (and =while + =repeat + =for_step + =for_in))) + (_.coverage [/.label /.set_label /.go_to] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $index (/.int +0)) + (/.local/1 $output (/.int +0)) + (/.set_label @loop) + (/.if (/.< expected_iterations $index) + (all /.then + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + (/.go_to @loop)) + (/.return $output))) + (/.closure (list $input)) + (/.apply (list (/.int input)))))) ))) (def: test|loop @@ -506,50 +506,50 @@ $index (/.var "index") expected (i.* (.int iterations) input)]] (all _.and - (_.cover [/.while] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $index (/.int +0)) - (/.local/1 $output (/.int +0)) - (/.while (/.< (/.int (.int iterations)) $index) - (all /.then - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input)))))) - (_.cover [/.repeat] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $index (/.int +0)) - (/.local/1 $output (/.int +0)) - (/.repeat (/.= (/.int (.int iterations)) $index) - (all /.then - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input)))))) - (_.cover [/.for_step] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $output (/.int +0)) - (/.for_step $index (/.int +0) (/.int (.int (-- iterations))) (/.int +1) - (/.set (list $output) (/.+ $input $output))) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input)))))) - (_.cover [/.for_in /.ipairs/1] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.local/1 $output (/.int +0)) - (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated iterations $input))) - (/.set (list $output) (/.+ $input $output))) - (/.return $output)) - (/.closure (list $input)) - (/.apply (list (/.int input)))))) + (_.coverage [/.while] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $index (/.int +0)) + (/.local/1 $output (/.int +0)) + (/.while (/.< (/.int (.int iterations)) $index) + (all /.then + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input)))))) + (_.coverage [/.repeat] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $index (/.int +0)) + (/.local/1 $output (/.int +0)) + (/.repeat (/.= (/.int (.int iterations)) $index) + (all /.then + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input)))))) + (_.coverage [/.for_step] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $output (/.int +0)) + (/.for_step $index (/.int +0) (/.int (.int (-- iterations))) (/.int +1) + (/.set (list $output) (/.+ $input $output))) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input)))))) + (_.coverage [/.for_in /.ipairs/1] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.local/1 $output (/.int +0)) + (/.for_in (list $index $input) (/.ipairs/1 (/.array (list.repeated iterations $input))) + (/.set (list $output) (/.+ $input $output))) + (/.return $output)) + (/.closure (list $input)) + (/.apply (list (/.int input)))))) (_.for [/.Label] ..test|label) ))) @@ -563,40 +563,40 @@ $verdict (# ! each /.var (random.lower_case 10)) $outcome (# ! each /.var (random.lower_case 11))] (all _.and - (_.cover [/.pcall/1] - (expression (|>> (as Frac) (f.= expected)) - (|> (all /.then - (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) - (/.return (/.float expected))))) - (/.if $verdict - (/.return $outcome) - (/.return (/.float dummy)))) - (/.closure (list)) - (/.apply (list))))) - (_.cover [/.error/1] - (expression (|>> (as Frac) (f.= expected)) - (|> (all /.then - (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) - (all /.then - (/.statement (/.error/1 (/.float expected))) - (/.return (/.float dummy)))))) - (/.if $verdict - (/.return (/.float dummy)) - (/.return $outcome))) - (/.closure (list)) - (/.apply (list))))) - (_.cover [/.error/2] - (expression (|>> (as Frac) (f.= expected)) - (|> (all /.then - (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) - (all /.then - (/.statement (/.error/2 (/.float expected) (/.int +2))) - (/.return (/.float dummy)))))) - (/.if $verdict - (/.return (/.float dummy)) - (/.return $outcome))) - (/.closure (list)) - (/.apply (list))))) + (_.coverage [/.pcall/1] + (expression (|>> (as Frac) (f.= expected)) + (|> (all /.then + (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) + (/.return (/.float expected))))) + (/.if $verdict + (/.return $outcome) + (/.return (/.float dummy)))) + (/.closure (list)) + (/.apply (list))))) + (_.coverage [/.error/1] + (expression (|>> (as Frac) (f.= expected)) + (|> (all /.then + (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) + (all /.then + (/.statement (/.error/1 (/.float expected))) + (/.return (/.float dummy)))))) + (/.if $verdict + (/.return (/.float dummy)) + (/.return $outcome))) + (/.closure (list)) + (/.apply (list))))) + (_.coverage [/.error/2] + (expression (|>> (as Frac) (f.= expected)) + (|> (all /.then + (/.let (list $verdict $outcome) (/.pcall/1 (/.closure (list) + (all /.then + (/.statement (/.error/2 (/.float expected) (/.int +2))) + (/.return (/.float dummy)))))) + (/.if $verdict + (/.return (/.float dummy)) + (/.return $outcome))) + (/.closure (list)) + (/.apply (list))))) ))) (def: test|function @@ -609,20 +609,20 @@ field (random.lower_case 3) $class (# ! each /.var (random.upper_case 4))] (all _.and - (_.cover [/.closure /.return] - (expression (|>> (as Frac) (f.= float/0)) - (/.apply (list) - (/.closure (list) (/.return (/.float float/0)))))) - (_.cover [/.local_function] - (expression (|>> (as Int) .nat (n.= iterations)) - (|> (all /.then - (/.local_function $self (list $arg/0) - (/.if (/.< (/.int (.int iterations)) $arg/0) - (/.return (/.apply (list (/.+ (/.int +1) $arg/0)) $self)) - (/.return $arg/0))) - (/.return (/.apply (list (/.int +0)) $self))) - (/.closure (list)) - (/.apply (list))))) + (_.coverage [/.closure /.return] + (expression (|>> (as Frac) (f.= float/0)) + (/.apply (list) + (/.closure (list) (/.return (/.float float/0)))))) + (_.coverage [/.local_function] + (expression (|>> (as Int) .nat (n.= iterations)) + (|> (all /.then + (/.local_function $self (list $arg/0) + (/.if (/.< (/.int (.int iterations)) $arg/0) + (/.return (/.apply (list (/.+ (/.int +1) $arg/0)) $self)) + (/.return $arg/0))) + (/.return (/.apply (list (/.int +0)) $self))) + (/.closure (list)) + (/.apply (list))))) (do [! random.monad] [float/0 random.safe_frac float/1 random.safe_frac @@ -631,12 +631,12 @@ $arg/1 (# ! each /.var (random.lower_case 11)) $arg/2 (# ! each /.var (random.lower_case 12))] (`` (all _.and - (_.cover [/.apply] - (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) - (/.apply (list (/.float float/0) - (/.float float/1) - (/.float float/2)) - (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2)))))) + (_.coverage [/.apply] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (/.apply (list (/.float float/0) + (/.float float/1) + (/.float float/2)) + (/.closure (list $arg/0 $arg/1 $arg/2) (/.return (all /.+ $arg/0 $arg/1 $arg/2)))))) ))) ))) @@ -647,21 +647,21 @@ float/1 random.safe_frac ??? random.bit] (all _.and - (_.cover [/.if] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> (/.if (/.boolean ???) - (/.return (/.float float/0)) - (/.return (/.float float/1))) - (/.closure (list)) - (/.apply (list))))) - (_.cover [/.when] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> (all /.then - (/.when (/.boolean ???) - (/.return (/.float float/0))) - (/.return (/.float float/1))) - (/.closure (list)) - (/.apply (list))))) + (_.coverage [/.if] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (/.if (/.boolean ???) + (/.return (/.float float/0)) + (/.return (/.float float/1))) + (/.closure (list)) + (/.apply (list))))) + (_.coverage [/.when] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (all /.then + (/.when (/.boolean ???) + (/.return (/.float float/0))) + (/.return (/.float float/1))) + (/.closure (list)) + (/.apply (list))))) ))) (def: test|binding @@ -688,13 +688,13 @@ $arg/0 (# ! each /.var (random.lower_case 10)) $arg/1 (# ! each /.var (random.lower_case 11))] (`` (all _.and - (_.cover [/.statement /.then /.print/1] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.statement (/.print/1 $arg/0)) - (/.return $arg/0)) - (/.closure (list $arg/0)) - (/.apply (list (/.float float/0)))))) + (_.coverage [/.statement /.then /.print/1] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.statement (/.print/1 $arg/0)) + (/.return $arg/0)) + (/.closure (list $arg/0)) + (/.apply (list (/.float float/0)))))) ..test|binding ..test|control )))) @@ -712,9 +712,9 @@ (_.for [/.hash] ($hash.spec /.hash random)) - (_.cover [/.manual] - (expression (|>> (as Int) (i.= expected)) - (/.manual (/.code (/.int expected))))) + (_.coverage [/.manual] + (expression (|>> (as Int) (i.= expected)) + (/.manual (/.code (/.int expected))))) (_.for [/.Expression] ..test|expression) (_.for [/.Statement] diff --git a/stdlib/source/test/lux/target/python.lux b/stdlib/source/test/lux/target/python.lux index 60fb46d9d..e9ce7cdda 100644 --- a/stdlib/source/test/lux/target/python.lux +++ b/stdlib/source/test/lux/target/python.lux @@ -51,33 +51,33 @@ int random.int string (random.upper_case 1)] (all _.and - (_.cover [/.none] - (|> /.none - /.code - ..eval - (try#each (function (_ it) - (case it - {.#None} true - {.#Some _} false))) - (try.else false))) - (_.cover [/.bool] - (expression (|>> (as Bit) (bit#= bool)) - (/.bool bool))) - (_.cover [/.int] - (expression (|>> (as Int) (i.= int)) - (/.int int))) - ... (_.cover [/.long] + (_.coverage [/.none] + (|> /.none + /.code + ..eval + (try#each (function (_ it) + (case it + {.#None} true + {.#Some _} false))) + (try.else false))) + (_.coverage [/.bool] + (expression (|>> (as Bit) (bit#= bool)) + (/.bool bool))) + (_.coverage [/.int] + (expression (|>> (as Int) (i.= int)) + (/.int int))) + ... (_.coverage [/.long] ... (expression (|>> (as Int) (i.= int)) ... (/.long int))) - (_.cover [/.float] - (expression (|>> (as Frac) (f.= float)) - (/.float float))) - (_.cover [/.string] - (expression (|>> (as Text) (text#= string)) - (/.string string))) - (_.cover [/.unicode] - (expression (|>> (as Text) (text#= string)) - (/.unicode string))) + (_.coverage [/.float] + (expression (|>> (as Frac) (f.= float)) + (/.float float))) + (_.coverage [/.string] + (expression (|>> (as Text) (text#= string)) + (/.string string))) + (_.coverage [/.unicode] + (expression (|>> (as Text) (text#= string)) + (/.unicode string))) ))) (def: test|bool @@ -87,17 +87,17 @@ right random.bit] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.bool left) (/.bool right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.bool left) (/.bool right)))))] [/.or .or] [/.and .and] )) - (_.cover [/.not] - (expression (|>> (as Bit) (bit#= (not left))) - (/.not (/.bool left)))) + (_.coverage [/.not] + (expression (|>> (as Bit) (bit#= (not left))) + (/.not (/.bool left)))) )))) (def: test|float @@ -108,10 +108,10 @@ subject random.safe_frac] (`` (all _.and (~~ (template [</> <lux> <pre>] - [(_.cover [</>] - (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (as Frac) (f.= expected)) - (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] + [(_.coverage [</>] + (let [expected (<lux> (<pre> parameter) (<pre> subject))] + (expression (|>> (as Frac) (f.= expected)) + (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] [/.- f.- |>] @@ -121,10 +121,10 @@ [/.** f.pow f.abs] )) (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.float parameter) (/.float subject)))))] + [(_.coverage [</>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.float parameter) (/.float subject)))))] [/.< f.<] [/.<= f.<=] @@ -132,12 +132,12 @@ [/.>= f.>=] [/.= f.=] )) - (_.cover [/.float/1] - (expression (|>> (as Frac) (f.= subject)) - (/.float/1 (/.string (%.frac subject))))) - (_.cover [/.repr/1] - (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.frac subject)))) - (/.repr/1 (/.float subject)))) + (_.coverage [/.float/1] + (expression (|>> (as Frac) (f.= subject)) + (/.float/1 (/.string (%.frac subject))))) + (_.coverage [/.repr/1] + (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.frac subject)))) + (/.repr/1 (/.float subject)))) )))) (def: python_3? @@ -161,49 +161,49 @@ shift (# ! each (n.% 16) random.nat)] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Frac) f.int (i.= expected)) - (</> (/.int left) (/.int right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Frac) f.int (i.= expected)) + (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] [/.bit_xor i64.xor] [/.bit_and i64.and] )) (~~ (template [</> <lux>] - [(_.cover [</>] - (let [left (.int shift) - right (i.* (.int shift) i16) - expected (<lux> left right)] - (expression (|>> (as Int) (i.= expected)) - (</> (/.int left) (/.int right)))))] + [(_.coverage [</>] + (let [left (.int shift) + right (i.* (.int shift) i16) + expected (<lux> left right)] + (expression (|>> (as Int) (i.= expected)) + (</> (/.int left) (/.int right)))))] [/.// i./] )) - (_.cover [/.opposite] - (expression (|>> (as Int) (i.= (i.* -1 left))) - (/.opposite (/.int left)))) - (_.cover [/.bit_shl] - (let [expected (i64.left_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shl (/.int (.int shift)) - (/.int i16))))) - (_.cover [/.bit_shr] - (let [expected (i.right_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shr (/.int (.int shift)) - (/.int i16))))) - (_.cover [/.int/1] - (expression (|>> (as Int) (i.= left)) - (/.int/1 (/.string (%.int left))))) - (_.cover [/.str/1] - (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.int left)))) - (/.str/1 (/.int left)))) - (_.cover [/.long] - (or (expression (|>> (as Bit)) - ..python_3?) - (expression (|>> (as Int) (i.= left)) - (/.long left)))) + (_.coverage [/.opposite] + (expression (|>> (as Int) (i.= (i.* -1 left))) + (/.opposite (/.int left)))) + (_.coverage [/.bit_shl] + (let [expected (i64.left_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shl (/.int (.int shift)) + (/.int i16))))) + (_.coverage [/.bit_shr] + (let [expected (i.right_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shr (/.int (.int shift)) + (/.int i16))))) + (_.coverage [/.int/1] + (expression (|>> (as Int) (i.= left)) + (/.int/1 (/.string (%.int left))))) + (_.coverage [/.str/1] + (expression (|>> (as Text) (text#= (text.replaced "+" "" (%.int left)))) + (/.str/1 (/.int left)))) + (_.coverage [/.long] + (or (expression (|>> (as Bit)) + ..python_3?) + (expression (|>> (as Int) (i.= left)) + (/.long left)))) )))) (def: test|text @@ -212,16 +212,16 @@ [expected_code (# ! each (n.% 128) random.nat) .let [expected_char (text.of_char expected_code)]] (all _.and - (_.cover [/.chr/1 /.ord/1 - /.unichr/1 /.unicode/1] - (and (expression (|>> (as Int) .nat (n.= expected_code)) - (/.? python_3? - (/.ord/1 (/.chr/1 (/.int (.int expected_code)))) - (/.unicode/1 (/.unichr/1 (/.int (.int expected_code)))))) - (expression (|>> (as Text) (text#= expected_char)) - (/.? python_3? - (/.chr/1 (/.ord/1 (/.string expected_char))) - (/.unichr/1 (/.unicode/1 (/.string expected_char))))))) + (_.coverage [/.chr/1 /.ord/1 + /.unichr/1 /.unicode/1] + (and (expression (|>> (as Int) .nat (n.= expected_code)) + (/.? python_3? + (/.ord/1 (/.chr/1 (/.int (.int expected_code)))) + (/.unicode/1 (/.unichr/1 (/.int (.int expected_code)))))) + (expression (|>> (as Text) (text#= expected_char)) + (/.? python_3? + (/.chr/1 (/.ord/1 (/.string expected_char))) + (/.unichr/1 (/.unicode/1 (/.string expected_char))))))) ))) (def: test|array @@ -241,24 +241,24 @@ (all _.and (_.for [/.item] (all _.and - (_.cover [/.list] - (expression (|>> (as Frac) (f.= expected)) - (/.item (/.int (.int index)) - (/.list (list#each /.float items))))) - (_.cover [/.tuple] - (expression (|>> (as Frac) (f.= expected)) - (/.item (/.int (.int index)) - (/.tuple (list#each /.float items))))))) - (_.cover [/.slice /.len/1] - (expression (|>> (as Int) (i.= (.int plus))) - (|> (/.list (list#each /.float items)) - (/.slice from to) - /.len/1))) - (_.cover [/.slice_from] - (expression (|>> (as Int) (i.= (.int slice_from|size))) - (|> (/.list (list#each /.float items)) - (/.slice_from from) - /.len/1))) + (_.coverage [/.list] + (expression (|>> (as Frac) (f.= expected)) + (/.item (/.int (.int index)) + (/.list (list#each /.float items))))) + (_.coverage [/.tuple] + (expression (|>> (as Frac) (f.= expected)) + (/.item (/.int (.int index)) + (/.tuple (list#each /.float items))))))) + (_.coverage [/.slice /.len/1] + (expression (|>> (as Int) (i.= (.int plus))) + (|> (/.list (list#each /.float items)) + (/.slice from to) + /.len/1))) + (_.coverage [/.slice_from] + (expression (|>> (as Int) (i.= (.int slice_from|size))) + (|> (/.list (list#each /.float items)) + (/.slice_from from) + /.len/1))) ))) (def: test|dict @@ -271,14 +271,14 @@ .let [field (/.string field) dummy (/.string dummy)]] (all _.and - (_.cover [/.dict] - (expression (|>> (as Frac) (f.= expected)) - (/.item field (/.dict (list [field (/.float expected)]))))) - (_.cover [/.in?] - (and (expression (|>> (as Bit) not) - (/.in? (/.dict (list)) field)) - (expression (|>> (as Bit)) - (/.in? (/.dict (list [field (/.float expected)])) field)))) + (_.coverage [/.dict] + (expression (|>> (as Frac) (f.= expected)) + (/.item field (/.dict (list [field (/.float expected)]))))) + (_.coverage [/.in?] + (and (expression (|>> (as Bit) not) + (/.in? (/.dict (list)) field)) + (expression (|>> (as Bit)) + (/.in? (/.dict (list [field (/.float expected)])) field)))) ))) (def: test|computation @@ -302,33 +302,33 @@ ..test|text ..test|array ..test|dict - (_.cover [/.?] - (let [expected (if test then else)] - (expression (|>> (as Frac) (f.= expected)) - (/.? (/.bool test) - (/.float then) - (/.float else))))) - (_.cover [/.comment] - (expression (|>> (as Frac) (f.= then)) - (/.comment comment - (/.float then)))) - (_.cover [/.__import__/1] - (expression (function.constant true) - (/.__import__/1 (/.string "math")))) - (_.cover [/.do] - (expression (|>> (as Frac) (f.= (f.ceil float))) - (|> (/.__import__/1 (/.string "math")) - (/.do "ceil" (list (/.float float)))))) - (_.cover [/.is] - (and (expression (|>> (as Bit)) - (/.apply/* (list (/.string (format string string))) - (/.lambda (list $arg/0) - (/.is $arg/0 $arg/0)))) - (expression (|>> (as Bit) not) - (/.apply/* (list (/.string (format string string)) - (/.string string)) - (/.lambda (list $arg/0 $arg/1) - (/.is $arg/0 (/.+ $arg/1 $arg/1))))))) + (_.coverage [/.?] + (let [expected (if test then else)] + (expression (|>> (as Frac) (f.= expected)) + (/.? (/.bool test) + (/.float then) + (/.float else))))) + (_.coverage [/.comment] + (expression (|>> (as Frac) (f.= then)) + (/.comment comment + (/.float then)))) + (_.coverage [/.__import__/1] + (expression (function.constant true) + (/.__import__/1 (/.string "math")))) + (_.coverage [/.do] + (expression (|>> (as Frac) (f.= (f.ceil float))) + (|> (/.__import__/1 (/.string "math")) + (/.do "ceil" (list (/.float float)))))) + (_.coverage [/.is] + (and (expression (|>> (as Bit)) + (/.apply/* (list (/.string (format string string))) + (/.lambda (list $arg/0) + (/.is $arg/0 $arg/0)))) + (expression (|>> (as Bit) not) + (/.apply/* (list (/.string (format string string)) + (/.string string)) + (/.lambda (list $arg/0 $arg/1) + (/.is $arg/0 (/.+ $arg/1 $arg/1))))))) ))) (def: test|function @@ -341,16 +341,16 @@ $arg/1 (# ! each /.var (random.lower_case 11)) $arg/2 (# ! each /.var (random.lower_case 12))] (all _.and - (_.cover [/.lambda] - (expression (|>> (as Frac) (f.= float/0)) - (/.apply/* (list) - (/.lambda (list) - (/.float float/0))))) - (_.cover [/.apply/*] - (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) - (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) - (/.lambda (list $arg/0 $arg/1 $arg/2) - (all /.+ $arg/0 $arg/1 $arg/2))))) + (_.coverage [/.lambda] + (expression (|>> (as Frac) (f.= float/0)) + (/.apply/* (list) + (/.lambda (list) + (/.float float/0))))) + (_.coverage [/.apply/*] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) + (/.lambda (list $arg/0 $arg/1 $arg/2) + (all /.+ $arg/0 $arg/1 $arg/2))))) ))) (def: test|var @@ -369,46 +369,46 @@ $var (# ! each (|>> %.nat (format "v") /.var) random.nat) $choice (# ! each (|>> %.nat (format "c") /.var) random.nat)] (all _.and - (_.cover [/.Single /.SVar /.var] - (expression (|>> (as Frac) (f.= expected/0)) - (/.apply/* (list (/.float expected/0)) - (/.lambda (list $var) $var)))) + (_.coverage [/.Single /.SVar /.var] + (expression (|>> (as Frac) (f.= expected/0)) + (/.apply/* (list (/.float expected/0)) + (/.lambda (list $var) $var)))) (_.for [/.Poly /.PVar] (all _.and - (_.cover [/.poly] - (expression (|>> (as Frac) (f.= expected/?)) - (/.apply/* (list (/.int (.int poly_choice)) - (/.float expected/0) - (/.float expected/1)) - (/.lambda (list $choice (/.poly $var)) - (/.item $choice $var))))) - (_.cover [/.splat_poly] - (expression (|>> (as Frac) (f.= expected/?)) - (/.apply/* (list (/.int (.int poly_choice)) - (/.splat_poly - (/.list (list (/.float expected/0) - (/.float expected/1))))) - (/.lambda (list $choice (/.poly $var)) - (/.item $choice $var))))) + (_.coverage [/.poly] + (expression (|>> (as Frac) (f.= expected/?)) + (/.apply/* (list (/.int (.int poly_choice)) + (/.float expected/0) + (/.float expected/1)) + (/.lambda (list $choice (/.poly $var)) + (/.item $choice $var))))) + (_.coverage [/.splat_poly] + (expression (|>> (as Frac) (f.= expected/?)) + (/.apply/* (list (/.int (.int poly_choice)) + (/.splat_poly + (/.list (list (/.float expected/0) + (/.float expected/1))))) + (/.lambda (list $choice (/.poly $var)) + (/.item $choice $var))))) )) (_.for [/.Keyword /.KVar] (all _.and - (_.cover [/.keyword] - (expression (|>> (as Nat) (n.= 2)) - (/.apply/* (list keyword_choice - (/.splat_keyword - (/.dict (list [keyword/0 (/.float expected/0)] - [keyword/1 (/.float expected/1)])))) - (/.lambda (list $choice (/.keyword $var)) - (/.len/1 $var))))) - (_.cover [/.splat_keyword] - (expression (|>> (as Frac) (f.= expected/?)) - (/.apply/* (list keyword_choice - (/.splat_keyword - (/.dict (list [keyword/0 (/.float expected/0)] - [keyword/1 (/.float expected/1)])))) - (/.lambda (list $choice (/.keyword $var)) - (/.item $choice $var))))) + (_.coverage [/.keyword] + (expression (|>> (as Nat) (n.= 2)) + (/.apply/* (list keyword_choice + (/.splat_keyword + (/.dict (list [keyword/0 (/.float expected/0)] + [keyword/1 (/.float expected/1)])))) + (/.lambda (list $choice (/.keyword $var)) + (/.len/1 $var))))) + (_.coverage [/.splat_keyword] + (expression (|>> (as Frac) (f.= expected/?)) + (/.apply/* (list keyword_choice + (/.splat_keyword + (/.dict (list [keyword/0 (/.float expected/0)] + [keyword/1 (/.float expected/1)])))) + (/.lambda (list $choice (/.keyword $var)) + (/.item $choice $var))))) )) ))) @@ -450,34 +450,34 @@ dummy/0 random.safe_frac field (# ! each /.string (random.upper_case 1))] (all _.and - (_.cover [/.item] - (`` (and (~~ (template [<seq>] - [(expression (|>> (as Frac) (f.= expected/0)) - (/.item (/.int +0) - (<seq> (list (/.float expected/0)))))] - - [/.list] - [/.tuple] - )) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.list (list (/.float dummy/0)))) - (/.set (list (/.item (/.int +0) $var/0)) (/.float expected/0)) - (/.set (list $output) (/.item (/.int +0) $var/0))))) - (as Frac) - (f.= expected/0)) - - (expression (|>> (as Frac) (f.= expected/0)) - (/.item field (/.dict (list [field (/.float expected/0)])))) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.dict (list [field (/.float dummy/0)]))) - (/.set (list (/.item field $var/0)) (/.float expected/0)) - (/.set (list $output) (/.item field $var/0))))) - (as Frac) - (f.= expected/0))))) + (_.coverage [/.item] + (`` (and (~~ (template [<seq>] + [(expression (|>> (as Frac) (f.= expected/0)) + (/.item (/.int +0) + (<seq> (list (/.float expected/0)))))] + + [/.list] + [/.tuple] + )) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.list (list (/.float dummy/0)))) + (/.set (list (/.item (/.int +0) $var/0)) (/.float expected/0)) + (/.set (list $output) (/.item (/.int +0) $var/0))))) + (as Frac) + (f.= expected/0)) + + (expression (|>> (as Frac) (f.= expected/0)) + (/.item field (/.dict (list [field (/.float expected/0)])))) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.dict (list [field (/.float dummy/0)]))) + (/.set (list (/.item field $var/0)) (/.float expected/0)) + (/.set (list $output) (/.item field $var/0))))) + (as Frac) + (f.= expected/0))))) ))) (def: test|location @@ -491,102 +491,102 @@ dummy/0 random.safe_frac field/0 (# ! each /.string (random.upper_case 1))] (all _.and - (_.cover [/.set] - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.float expected/0)) - (/.set (list $output) $var/0)))) - (as Frac) - (f.= expected/0))) - (_.cover [/.multi] - (`` (and (~~ (template [<var> <value>] - [(|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0 $var/1) (/.multi (list (/.float expected/0) (/.float expected/1)))) - (/.set (list $output) <var>)))) - (as Frac) - (f.= <value>))] - - [$var/0 expected/0] - [$var/1 expected/1] - ))))) - (_.cover [/.delete] - (and (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) - (/.delete (/.item (/.int +0) $var/0)) - (/.set (list $output) (/.item (/.int +0) $var/0))))) - (as Frac) - (f.= expected/0)) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) - (/.delete (/.slice (/.int +0) (/.int +1) $var/0)) - (/.set (list $output) (/.item (/.int +0) $var/0))))) - (as Frac) - (f.= expected/0)) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float dummy/0)))) - (/.delete (/.slice_from (/.int +0) $var/0)) - (/.statement (/.do "append" (list (/.float expected/0)) $var/0)) - (/.set (list $output) (/.item (/.int +0) $var/0))))) - (as Frac) - (f.= expected/0)) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.dict (list [field/0 (/.float dummy/0)]))) - (/.delete (/.item field/0 $var/0)) - (/.set (list $output) (/.in? $var/0 field/0))))) - (as Bit) - not) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $var/0) (/.float dummy/0)) - (/.delete $var/0) - (/.set (list $output) (/.or (/.in? /.locals/0 (/.string (/.code $var/0))) - (/.in? /.globals/0 (/.string (/.code $var/0)))))))) - (as Bit) - not) - )) - (_.cover [/.globals/0] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list $var/0) - (/.return (/.in? /.globals/0 (/.string (/.code $var/0))))) - (/.set (list $output) (/.and (/.not (/.in? /.globals/0 (/.string (/.code $var/0)))) - (/.not (/.apply/* (list (/.float dummy/0)) $def)))) - (/.set (list $var/0) (/.float dummy/0)) - (/.set (list $output) (/.and $output - (/.in? /.globals/0 (/.string (/.code $var/0)))))))) - (as Bit))) - (_.cover [/.locals/0] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list $var/0) - (/.return (/.in? /.locals/0 (/.string (/.code $var/0))))) - (/.set (list $output) (/.and (/.not (/.in? /.locals/0 (/.string (/.code $var/0)))) - (/.apply/* (list (/.float dummy/0)) $def))) - (/.set (list $var/0) (/.float dummy/0)) - (/.set (list $output) (/.and $output - (/.in? /.locals/0 (/.string (/.code $var/0)))))))) - (as Bit))) - (_.cover [/.import] - (|> (..statement - (function (_ $output) - (all /.then - (/.import "math") - (/.set (list $output) (/.in? /.globals/0 (/.string "math")))))) - (as Bit))) + (_.coverage [/.set] + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.float expected/0)) + (/.set (list $output) $var/0)))) + (as Frac) + (f.= expected/0))) + (_.coverage [/.multi] + (`` (and (~~ (template [<var> <value>] + [(|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0 $var/1) (/.multi (list (/.float expected/0) (/.float expected/1)))) + (/.set (list $output) <var>)))) + (as Frac) + (f.= <value>))] + + [$var/0 expected/0] + [$var/1 expected/1] + ))))) + (_.coverage [/.delete] + (and (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) + (/.delete (/.item (/.int +0) $var/0)) + (/.set (list $output) (/.item (/.int +0) $var/0))))) + (as Frac) + (f.= expected/0)) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float expected/0)))) + (/.delete (/.slice (/.int +0) (/.int +1) $var/0)) + (/.set (list $output) (/.item (/.int +0) $var/0))))) + (as Frac) + (f.= expected/0)) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.list (list (/.float dummy/0) (/.float dummy/0)))) + (/.delete (/.slice_from (/.int +0) $var/0)) + (/.statement (/.do "append" (list (/.float expected/0)) $var/0)) + (/.set (list $output) (/.item (/.int +0) $var/0))))) + (as Frac) + (f.= expected/0)) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.dict (list [field/0 (/.float dummy/0)]))) + (/.delete (/.item field/0 $var/0)) + (/.set (list $output) (/.in? $var/0 field/0))))) + (as Bit) + not) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $var/0) (/.float dummy/0)) + (/.delete $var/0) + (/.set (list $output) (/.or (/.in? /.locals/0 (/.string (/.code $var/0))) + (/.in? /.globals/0 (/.string (/.code $var/0)))))))) + (as Bit) + not) + )) + (_.coverage [/.globals/0] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list $var/0) + (/.return (/.in? /.globals/0 (/.string (/.code $var/0))))) + (/.set (list $output) (/.and (/.not (/.in? /.globals/0 (/.string (/.code $var/0)))) + (/.not (/.apply/* (list (/.float dummy/0)) $def)))) + (/.set (list $var/0) (/.float dummy/0)) + (/.set (list $output) (/.and $output + (/.in? /.globals/0 (/.string (/.code $var/0)))))))) + (as Bit))) + (_.coverage [/.locals/0] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list $var/0) + (/.return (/.in? /.locals/0 (/.string (/.code $var/0))))) + (/.set (list $output) (/.and (/.not (/.in? /.locals/0 (/.string (/.code $var/0)))) + (/.apply/* (list (/.float dummy/0)) $def))) + (/.set (list $var/0) (/.float dummy/0)) + (/.set (list $output) (/.and $output + (/.in? /.locals/0 (/.string (/.code $var/0)))))))) + (as Bit))) + (_.coverage [/.import] + (|> (..statement + (function (_ $output) + (all /.then + (/.import "math") + (/.set (list $output) (/.in? /.globals/0 (/.string "math")))))) + (as Bit))) (_.for [/.Access] ..test|access) ))) @@ -600,41 +600,41 @@ random.safe_frac) $ex (# ! each (|>> %.nat (format "ex_") /.var) random.nat)] (all _.and - (_.cover [/.raise /.Exception/1] - (case (try (..statement - (function (_ $output) - (all /.then - (/.raise (/.Exception/1 (/.string expected_error))) - (/.set (list $output) (/.float dummy)))))) - {try.#Failure actual_error} - (text#= expected_error actual_error) - - {try.#Success _} - false)) - (_.cover [/.try /.Except] - (and (|> (..statement + (_.coverage [/.raise /.Exception/1] + (case (try (..statement + (function (_ $output) + (all /.then + (/.raise (/.Exception/1 (/.string expected_error))) + (/.set (list $output) (/.float dummy)))))) + {try.#Failure actual_error} + (text#= expected_error actual_error) + + {try.#Success _} + false)) + (_.coverage [/.try /.Except] + (and (|> (..statement + (function (_ $output) + (/.try (all /.then + (/.raise (/.Exception/1 (/.string expected_error))) + (/.set (list $output) (/.float dummy))) + (list [/.#classes (list "Exception") + /.#exception $ex + /.#handler (/.set (list $output) (/.float expected))])))) + (as Frac) + (f.= expected)) + (case (try (..statement (function (_ $output) (/.try (all /.then (/.raise (/.Exception/1 (/.string expected_error))) (/.set (list $output) (/.float dummy))) - (list [/.#classes (list "Exception") + (list [/.#classes (list) /.#exception $ex - /.#handler (/.set (list $output) (/.float expected))])))) - (as Frac) - (f.= expected)) - (case (try (..statement - (function (_ $output) - (/.try (all /.then - (/.raise (/.Exception/1 (/.string expected_error))) - (/.set (list $output) (/.float dummy))) - (list [/.#classes (list) - /.#exception $ex - /.#handler (/.set (list $output) (/.float expected))]))))) - {try.#Failure actual_error} - (text#= expected_error actual_error) - - {try.#Success actual} - false))) + /.#handler (/.set (list $output) (/.float expected))]))))) + {try.#Failure actual_error} + (text#= expected_error actual_error) + + {try.#Success actual} + false))) ))) (def: test|loop @@ -647,99 +647,99 @@ $iteration (# ! each (|>> %.nat (format "iteration_") /.var) random.nat) $temp (# ! each (|>> %.nat (format "temp_") /.var) random.nat)] (all _.and - (_.cover [/.while] - (and (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $output) (/.int +0)) - (/.set (list $iteration) (/.int +0)) - (/.while (/.< (/.int (.int factor)) $iteration) - (all /.then - (/.set (list $output) (/.+ (/.int (.int base)) - $output)) - (/.set (list $iteration) (/.+ (/.int +1) - $iteration)) - ) - {.#None})))) - (as Nat) - (n.= expected)) - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $temp) (/.int +0)) - (/.set (list $iteration) (/.int +0)) - (/.while (/.< (/.int (.int factor)) $iteration) - (all /.then - (/.set (list $temp) (/.+ (/.int (.int base)) - $temp)) - (/.set (list $iteration) (/.+ (/.int +1) - $iteration)) - ) - {.#Some (/.set (list $output) $temp)})))) - (as Nat) - (n.= expected)))) - (_.cover [/.for_in] - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $output) (/.int +0)) - (/.for_in $iteration - (/.list (list.repeated factor (/.int (.int base)))) - (/.set (list $output) (/.+ $iteration - $output)))))) - (as Nat) - (n.= expected))) - (_.cover [/.pass] - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $output) (/.int +0)) - (/.set (list $iteration) (/.int +0)) - (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) - (all /.then - (/.set (list $iteration) (/.+ (/.int +1) - $iteration)) - (/.if (/.> (/.int (.int extra)) $iteration) - (/.set (list $output) (/.+ (/.int (.int base)) - $output)) - /.pass)) - {.#None})))) - (as Nat) - (n.= expected))) - (_.cover [/.continue] - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $output) (/.int +0)) - (/.set (list $iteration) (/.int +0)) - (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) - (all /.then - (/.set (list $iteration) (/.+ (/.int +1) - $iteration)) - (/.if (/.> (/.int (.int extra)) $iteration) - (/.set (list $output) (/.+ (/.int (.int base)) - $output)) - /.continue)) - {.#None})))) - (as Nat) - (n.= expected))) - (_.cover [/.break] - (|> (..statement - (function (_ $output) - (all /.then - (/.set (list $output) (/.int +0)) - (/.set (list $iteration) (/.int +0)) - (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) - (all /.then - (/.set (list $iteration) (/.+ (/.int +1) - $iteration)) - (/.if (/.> (/.int (.int factor)) $iteration) - /.break - (/.set (list $output) (/.+ (/.int (.int base)) - $output)))) - {.#None})))) - (as Nat) - (n.= expected))) + (_.coverage [/.while] + (and (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $output) (/.int +0)) + (/.set (list $iteration) (/.int +0)) + (/.while (/.< (/.int (.int factor)) $iteration) + (all /.then + (/.set (list $output) (/.+ (/.int (.int base)) + $output)) + (/.set (list $iteration) (/.+ (/.int +1) + $iteration)) + ) + {.#None})))) + (as Nat) + (n.= expected)) + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $temp) (/.int +0)) + (/.set (list $iteration) (/.int +0)) + (/.while (/.< (/.int (.int factor)) $iteration) + (all /.then + (/.set (list $temp) (/.+ (/.int (.int base)) + $temp)) + (/.set (list $iteration) (/.+ (/.int +1) + $iteration)) + ) + {.#Some (/.set (list $output) $temp)})))) + (as Nat) + (n.= expected)))) + (_.coverage [/.for_in] + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $output) (/.int +0)) + (/.for_in $iteration + (/.list (list.repeated factor (/.int (.int base)))) + (/.set (list $output) (/.+ $iteration + $output)))))) + (as Nat) + (n.= expected))) + (_.coverage [/.pass] + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $output) (/.int +0)) + (/.set (list $iteration) (/.int +0)) + (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) + (all /.then + (/.set (list $iteration) (/.+ (/.int +1) + $iteration)) + (/.if (/.> (/.int (.int extra)) $iteration) + (/.set (list $output) (/.+ (/.int (.int base)) + $output)) + /.pass)) + {.#None})))) + (as Nat) + (n.= expected))) + (_.coverage [/.continue] + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $output) (/.int +0)) + (/.set (list $iteration) (/.int +0)) + (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) + (all /.then + (/.set (list $iteration) (/.+ (/.int +1) + $iteration)) + (/.if (/.> (/.int (.int extra)) $iteration) + (/.set (list $output) (/.+ (/.int (.int base)) + $output)) + /.continue)) + {.#None})))) + (as Nat) + (n.= expected))) + (_.coverage [/.break] + (|> (..statement + (function (_ $output) + (all /.then + (/.set (list $output) (/.int +0)) + (/.set (list $iteration) (/.int +0)) + (/.while (/.< (/.int (.int (n.+ extra factor))) $iteration) + (all /.then + (/.set (list $iteration) (/.+ (/.int +1) + $iteration)) + (/.if (/.> (/.int (.int factor)) $iteration) + /.break + (/.set (list $output) (/.+ (/.int (.int base)) + $output)))) + {.#None})))) + (as Nat) + (n.= expected))) ))) (def: test|statement @@ -753,56 +753,56 @@ else random.safe_frac .let [expected/? (if test then else)]] (all _.and - (_.cover [/.def /.return] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list $input/0) - (/.return $input/0)) - (/.set (list $output) (/.apply/* (list (/.float expected/0)) $def))))) - (as Frac) - (f.= expected/0))) - (_.cover [/.if] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list) - (/.if (/.bool test) - (/.return (/.float then)) - (/.return (/.float else)))) - (/.set (list $output) (/.apply/* (list) $def))))) - (as Frac) - (f.= expected/?))) - (_.cover [/.when /.then] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list) - (all /.then - (/.when (/.bool test) - (/.return (/.float then))) - (/.return (/.float else)))) - (/.set (list $output) (/.apply/* (list) $def))))) - (as Frac) - (f.= expected/?))) - (_.cover [/.statement] - (|> (..statement - (function (_ $output) - (all /.then - (/.def $def (list) - (all /.then - (/.statement (/.+ (/.float expected/0) (/.float expected/0))) - (/.return (/.float expected/0)))) - (/.set (list $output) (/.apply/* (list) $def))))) - (as Frac) - (f.= expected/0))) - (_.cover [/.exec] - (|> (..statement - (function (_ $output) - (/.exec {.#Some /.globals/0} - (/.string (/.code (/.set (list $output) (/.float expected/0))))))) - (as Frac) - (f.= expected/0))) + (_.coverage [/.def /.return] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list $input/0) + (/.return $input/0)) + (/.set (list $output) (/.apply/* (list (/.float expected/0)) $def))))) + (as Frac) + (f.= expected/0))) + (_.coverage [/.if] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list) + (/.if (/.bool test) + (/.return (/.float then)) + (/.return (/.float else)))) + (/.set (list $output) (/.apply/* (list) $def))))) + (as Frac) + (f.= expected/?))) + (_.coverage [/.when /.then] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list) + (all /.then + (/.when (/.bool test) + (/.return (/.float then))) + (/.return (/.float else)))) + (/.set (list $output) (/.apply/* (list) $def))))) + (as Frac) + (f.= expected/?))) + (_.coverage [/.statement] + (|> (..statement + (function (_ $output) + (all /.then + (/.def $def (list) + (all /.then + (/.statement (/.+ (/.float expected/0) (/.float expected/0))) + (/.return (/.float expected/0)))) + (/.set (list $output) (/.apply/* (list) $def))))) + (as Frac) + (f.= expected/0))) + (_.coverage [/.exec] + (|> (..statement + (function (_ $output) + (/.exec {.#Some /.globals/0} + (/.string (/.code (/.set (list $output) (/.float expected/0))))))) + (as Frac) + (f.= expected/0))) ..test|exception (_.for [/.Location] ..test|location) @@ -831,10 +831,10 @@ (_.for [/.hash] ($hash.spec /.hash ..random_expression)) - (_.cover [/.code /.manual] - (|> (/.manual (/.code expected)) - (is /.Expression) - (/#= expected))) + (_.coverage [/.code /.manual] + (|> (/.manual (/.code expected)) + (is /.Expression) + (/#= expected))) (_.for [/.Expression] ..test|expression) (_.for [/.Statement] diff --git a/stdlib/source/test/lux/target/ruby.lux b/stdlib/source/test/lux/target/ruby.lux index 2774aa58a..ccbb01bd1 100644 --- a/stdlib/source/test/lux/target/ruby.lux +++ b/stdlib/source/test/lux/target/ruby.lux @@ -65,23 +65,23 @@ int random.int string (random.upper_case 5)] (all _.and - (_.cover [/.nil] - (..nil /.nil)) - (_.cover [/.bool] - (expression (|>> (as Bit) (bit#= bool)) - (/.bool bool))) - (_.cover [/.int] - (expression (|>> (as Int) (i.= int)) - (/.int int))) - (_.cover [/.float] - (expression (|>> (as Frac) (f.= float)) - (/.float float))) - (_.cover [/.string] - (expression (|>> (as Text) (text#= string)) - (/.string string))) - (_.cover [/.symbol] - (expression (|>> (as Text) (text#= string)) - (/.do "id2name" (list) {.#None} (/.symbol string)))) + (_.coverage [/.nil] + (..nil /.nil)) + (_.coverage [/.bool] + (expression (|>> (as Bit) (bit#= bool)) + (/.bool bool))) + (_.coverage [/.int] + (expression (|>> (as Int) (i.= int)) + (/.int int))) + (_.coverage [/.float] + (expression (|>> (as Frac) (f.= float)) + (/.float float))) + (_.coverage [/.string] + (expression (|>> (as Text) (text#= string)) + (/.string string))) + (_.coverage [/.symbol] + (expression (|>> (as Text) (text#= string)) + (/.do "id2name" (list) {.#None} (/.symbol string)))) ))) (def: test|bool @@ -91,17 +91,17 @@ right random.bit] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.bool left) (/.bool right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.bool left) (/.bool right)))))] [/.or .or] [/.and .and] )) - (_.cover [/.not] - (expression (|>> (as Bit) (bit#= (not left))) - (/.not (/.bool left)))) + (_.coverage [/.not] + (expression (|>> (as Bit) (bit#= (not left))) + (/.not (/.bool left)))) )))) (def: test|float @@ -112,10 +112,10 @@ subject random.safe_frac] (`` (all _.and (~~ (template [</> <lux> <pre>] - [(_.cover [</>] - (let [expected (<lux> (<pre> parameter) (<pre> subject))] - (expression (|>> (as Frac) (f.= expected)) - (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] + [(_.coverage [</>] + (let [expected (<lux> (<pre> parameter) (<pre> subject))] + (expression (|>> (as Frac) (f.= expected)) + (</> (/.float (<pre> parameter)) (/.float (<pre> subject))))))] [/.+ f.+ |>] [/.- f.- |>] @@ -125,10 +125,10 @@ [/.pow f.pow f.abs] )) (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> parameter subject)] - (expression (|>> (as Bit) (bit#= expected)) - (</> (/.float parameter) (/.float subject)))))] + [(_.coverage [</>] + (let [expected (<lux> parameter subject)] + (expression (|>> (as Bit) (bit#= expected)) + (</> (/.float parameter) (/.float subject)))))] [/.< f.<] [/.<= f.<=] @@ -152,31 +152,31 @@ shift (# ! each (n.% 16) random.nat)] (`` (all _.and (~~ (template [</> <lux>] - [(_.cover [</>] - (let [expected (<lux> left right)] - (expression (|>> (as Frac) f.int (i.= expected)) - (</> (/.int left) (/.int right)))))] + [(_.coverage [</>] + (let [expected (<lux> left right)] + (expression (|>> (as Frac) f.int (i.= expected)) + (</> (/.int left) (/.int right)))))] [/.bit_or i64.or] [/.bit_xor i64.xor] [/.bit_and i64.and] )) - (_.cover [/.bit_not] - (expression (|>> (as Int) (i.= (i64.not left))) - (/.bit_not (/.int left)))) - (_.cover [/.opposite] - (expression (|>> (as Int) (i.= (i.* -1 left))) - (/.opposite (/.int left)))) - (_.cover [/.bit_shl] - (let [expected (i64.left_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shl (/.int (.int shift)) - (/.int i16))))) - (_.cover [/.bit_shr] - (let [expected (i.right_shifted shift i16)] - (expression (|>> (as Frac) f.int (i.= expected)) - (/.bit_shr (/.int (.int shift)) - (/.int i16))))) + (_.coverage [/.bit_not] + (expression (|>> (as Int) (i.= (i64.not left))) + (/.bit_not (/.int left)))) + (_.coverage [/.opposite] + (expression (|>> (as Int) (i.= (i.* -1 left))) + (/.opposite (/.int left)))) + (_.coverage [/.bit_shl] + (let [expected (i64.left_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shl (/.int (.int shift)) + (/.int i16))))) + (_.coverage [/.bit_shr] + (let [expected (i.right_shifted shift i16)] + (expression (|>> (as Frac) f.int (i.= expected)) + (/.bit_shr (/.int (.int shift)) + (/.int i16))))) )))) (def: test|array @@ -193,19 +193,19 @@ .let [to (/.int (.int (n.+ plus from))) from (/.int (.int from))]] (all _.and - (_.cover [/.array /.item] - (and (expression (|>> (as Frac) (f.= expected)) - (/.item (/.int (.int index)) - (/.array (list#each /.float items)))) - (expression (|>> (as Bit)) - (|> (/.array (list#each /.float items)) - (/.item (/.int (.int size))) - (/.= /.nil))))) - (_.cover [/.array_range] - (expression (|>> (as Int) (i.= (.int (++ plus)))) - (|> (/.array (list#each /.float items)) - (/.array_range from to) - (/.the "length")))) + (_.coverage [/.array /.item] + (and (expression (|>> (as Frac) (f.= expected)) + (/.item (/.int (.int index)) + (/.array (list#each /.float items)))) + (expression (|>> (as Bit)) + (|> (/.array (list#each /.float items)) + (/.item (/.int (.int size))) + (/.= /.nil))))) + (_.coverage [/.array_range] + (expression (|>> (as Int) (i.= (.int (++ plus)))) + (|> (/.array (list#each /.float items)) + (/.array_range from to) + (/.the "length")))) ))) (def: test|hash @@ -218,13 +218,13 @@ .let [field (/.string field) dummy (/.string dummy)]] (all _.and - (_.cover [/.hash] - (and (expression (|>> (as Frac) (f.= expected)) - (/.item field (/.hash (list [field (/.float expected)])))) - (expression (|>> (as Bit)) - (|> (/.hash (list [field (/.float expected)])) - (/.item dummy) - (/.= /.nil))))) + (_.coverage [/.hash] + (and (expression (|>> (as Frac) (f.= expected)) + (/.item field (/.hash (list [field (/.float expected)])))) + (expression (|>> (as Bit)) + (|> (/.hash (list [field (/.float expected)])) + (/.item dummy) + (/.= /.nil))))) ))) (def: test|object @@ -250,80 +250,80 @@ .let [double (/.function $method/0 (list $arg/0) (/.return (/.+ $arg/0 $arg/0)))]] (all _.and - (_.cover [/.the] - (expression (|>> (as Int) (i.= (.int size))) - (|> (/.array (list#each /.float items)) - (/.the "length")))) - (_.cover [/.do] - (expression (let [expected (|> items - (list.item index) - (maybe.else f.not_a_number))] - (|>> (as Frac) (f.= expected))) - (|> (/.array (list#each /.float items)) - (/.do "at" (list (/.int (.int index))) {.#None})))) - (_.cover [/.class] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body double])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.new /.initialize] - (expression (|>> (as Frac) (f.= single)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (all /.then - (/.function /.initialize (list $arg/0) - (/.set (list $state) $arg/0)) - (/.function $method/0 (list) - (/.return $state)) - )])) - (/.return (|> $class - (/.new (list (/.float single)) {.#None}) - (/.do (/.code $method/0) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.alias_method/2] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (all /.then - double - (/.statement (/.alias_method/2 (/.string (/.code $method/1)) - (/.string (/.code $method/0)))))])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method/1) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.the] + (expression (|>> (as Int) (i.= (.int size))) + (|> (/.array (list#each /.float items)) + (/.the "length")))) + (_.coverage [/.do] + (expression (let [expected (|> items + (list.item index) + (maybe.else f.not_a_number))] + (|>> (as Frac) (f.= expected))) + (|> (/.array (list#each /.float items)) + (/.do "at" (list (/.int (.int index))) {.#None})))) + (_.coverage [/.class] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body double])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.new /.initialize] + (expression (|>> (as Frac) (f.= single)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.function /.initialize (list $arg/0) + (/.set (list $state) $arg/0)) + (/.function $method/0 (list) + (/.return $state)) + )])) + (/.return (|> $class + (/.new (list (/.float single)) {.#None}) + (/.do (/.code $method/0) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.alias_method/2] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + double + (/.statement (/.alias_method/2 (/.string (/.code $method/1)) + (/.string (/.code $method/0)))))])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method/1) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) (_.for [/.module] (all _.and - (_.cover [/.include/1] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> (all /.then - (/.set (list $class) (/.module [/.#parameters (list) - /.#body double])) - (/.set (list $sub_class) (/.class [/.#parameters (list) - /.#body (/.statement (/.include/1 $class))])) - (/.return (|> $sub_class - (/.new (list) {.#None}) - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.extend/1] - (expression (|>> (as Frac) (f.= (f.+ single single))) - (|> (all /.then - (/.set (list $class) (/.module [/.#parameters (list) - /.#body double])) - (/.set (list $sub_class) (/.class [/.#parameters (list) - /.#body (/.statement (/.extend/1 $class))])) - (/.return (|> $sub_class - (/.do (/.code $method/0) (list (/.float single)) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.include/1] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.module [/.#parameters (list) + /.#body double])) + (/.set (list $sub_class) (/.class [/.#parameters (list) + /.#body (/.statement (/.include/1 $class))])) + (/.return (|> $sub_class + (/.new (list) {.#None}) + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.extend/1] + (expression (|>> (as Frac) (f.= (f.+ single single))) + (|> (all /.then + (/.set (list $class) (/.module [/.#parameters (list) + /.#body double])) + (/.set (list $sub_class) (/.class [/.#parameters (list) + /.#body (/.statement (/.extend/1 $class))])) + (/.return (|> $sub_class + (/.do (/.code $method/0) (list (/.float single)) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) )) ))) @@ -339,61 +339,61 @@ (all _.and (_.for [/.stdout] (all _.and - (_.cover [/.print/1] - (expression (|>> (as Text) (text#= expected)) - (|> (all /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdout) - (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) - (/.set (list /.stdout) $new) - (/.statement (/.print/1 (/.string left))) - (/.statement (/.print/1 (/.string right))) - (/.set (list /.stdout) $old) - (/.return (/.the "string" $new))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.print/2] - (expression (|>> (as Text) (text#= expected)) - (|> (all /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdout) - (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) - (/.set (list /.stdout) $new) - (/.statement (/.print/2 (/.string left) (/.string right))) - (/.set (list /.stdout) $old) - (/.return (/.the "string" $new))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.print/1] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdout) + (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) + (/.set (list /.stdout) $new) + (/.statement (/.print/1 (/.string left))) + (/.statement (/.print/1 (/.string right))) + (/.set (list /.stdout) $old) + (/.return (/.the "string" $new))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.print/2] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdout) + (/.set (list $new) (/.new (list) {.#None} (/.manual "StringIO"))) + (/.set (list /.stdout) $new) + (/.statement (/.print/2 (/.string left) (/.string right))) + (/.set (list /.stdout) $old) + (/.return (/.the "string" $new))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) )) (_.for [/.stdin] (all _.and - (_.cover [/.gets/0] - (expression (|>> (as Text) (text#= (format left text.\n))) - (|> (all /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdin) - (/.set (list /.stdin) (/.new (list (/.string (format left text.\n))) {.#None} - (/.manual "StringIO"))) - (/.set (list $it) /.gets/0) - (/.set (list /.stdin) $old) - (/.return $it)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_string_read] - (expression (|>> (as Text) (text#= (format right text.\n))) - (|> (all /.then - (/.statement (/.require/1 (/.string "stringio"))) - (/.set (list $old) /.stdin) - (/.set (list /.stdin) (/.new (list (/.string (format right text.\n))) {.#None} - (/.manual "StringIO"))) - (/.set (list $it) /.gets/0) - (/.set (list /.stdin) $old) - (/.return /.last_string_read)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_line_number_read] - (expression (|>> (as Nat) (n.= 2)) - /.last_line_number_read)) + (_.coverage [/.gets/0] + (expression (|>> (as Text) (text#= (format left text.\n))) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdin) + (/.set (list /.stdin) (/.new (list (/.string (format left text.\n))) {.#None} + (/.manual "StringIO"))) + (/.set (list $it) /.gets/0) + (/.set (list /.stdin) $old) + (/.return $it)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.last_string_read] + (expression (|>> (as Text) (text#= (format right text.\n))) + (|> (all /.then + (/.statement (/.require/1 (/.string "stringio"))) + (/.set (list $old) /.stdin) + (/.set (list /.stdin) (/.new (list (/.string (format right text.\n))) {.#None} + (/.manual "StringIO"))) + (/.set (list $it) /.gets/0) + (/.set (list /.stdin) $old) + (/.return /.last_string_read)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.last_line_number_read] + (expression (|>> (as Nat) (n.= 2)) + /.last_line_number_read)) )) ))) @@ -417,16 +417,16 @@ ..test|hash ..test|object ..test|io - (_.cover [/.?] - (let [expected (if test then else)] - (expression (|>> (as Frac) (f.= expected)) - (/.? (/.bool test) - (/.float then) - (/.float else))))) - (_.cover [/.comment] - (expression (|>> (as Frac) (f.= then)) - (/.comment comment - (/.float then)))) + (_.coverage [/.?] + (let [expected (if test then else)] + (expression (|>> (as Frac) (f.= expected)) + (/.? (/.bool test) + (/.float then) + (/.float else))))) + (_.coverage [/.comment] + (expression (|>> (as Frac) (f.= then)) + (/.comment comment + (/.float then)))) ))) (def: test|global @@ -436,51 +436,51 @@ $global (# ! each /.global (random.lower_case 10)) pattern (# ! each /.string (random.lower_case 11))] (all _.and - (_.cover [/.global] - (expression (|>> (as Text) (text#= "global-variable")) - (|> (all /.then - (/.set (list $global) (/.float float/0)) - (/.return (/.defined?/1 $global))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.script_name] - (expression (let [file (format (# file.default separator) packager.main_file)] - (|>> (as Text) - (text.ends_with? file))) - /.script_name)) - (_.cover [/.input_record_separator] - (expression (|>> (as Text) - (text#= text.\n)) - /.input_record_separator)) - (_.cover [/.output_record_separator] - (..nil /.output_record_separator)) - (_.cover [/.process_id] - (expression (|>> (as Nat) (n.= 0) not) - /.process_id)) - (_.cover [/.case_insensitivity_flag] - (expression (|>> (as Bit) (bit#= false)) - /.case_insensitivity_flag)) - (_.cover [/.command_line_arguments] - (expression (|>> (as Int) (i.= +0)) - (/.the "length" /.command_line_arguments))) - (_.cover [/.last_string_matched] - (expression (|>> (as Bit)) - (|> (all /.then - (/.statement - (|> (/.manual "Regexp") - (/.new (list pattern) {.#None}) - (/.do "match" (list pattern) {.#None}))) - (/.return (/.= pattern /.last_string_matched))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.last_regexp_match] - (expression (|>> (as Bit)) - (|> (/.return (|> (/.manual "Regexp") - (/.new (list pattern) {.#None}) - (/.do "match" (list pattern) {.#None}) - (/.= /.last_regexp_match))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.global] + (expression (|>> (as Text) (text#= "global-variable")) + (|> (all /.then + (/.set (list $global) (/.float float/0)) + (/.return (/.defined?/1 $global))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.script_name] + (expression (let [file (format (# file.default separator) packager.main_file)] + (|>> (as Text) + (text.ends_with? file))) + /.script_name)) + (_.coverage [/.input_record_separator] + (expression (|>> (as Text) + (text#= text.\n)) + /.input_record_separator)) + (_.coverage [/.output_record_separator] + (..nil /.output_record_separator)) + (_.coverage [/.process_id] + (expression (|>> (as Nat) (n.= 0) not) + /.process_id)) + (_.coverage [/.case_insensitivity_flag] + (expression (|>> (as Bit) (bit#= false)) + /.case_insensitivity_flag)) + (_.coverage [/.command_line_arguments] + (expression (|>> (as Int) (i.= +0)) + (/.the "length" /.command_line_arguments))) + (_.coverage [/.last_string_matched] + (expression (|>> (as Bit)) + (|> (all /.then + (/.statement + (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}))) + (/.return (/.= pattern /.last_string_matched))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.last_regexp_match] + (expression (|>> (as Bit)) + (|> (/.return (|> (/.manual "Regexp") + (/.new (list pattern) {.#None}) + (/.do "match" (list pattern) {.#None}) + (/.= /.last_regexp_match))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|local_var @@ -489,18 +489,18 @@ [float/0 random.safe_frac $foreign (# ! each /.local (random.lower_case 10))] (all _.and - (_.cover [/.local] - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (|> (/.return (/.+ $foreign $foreign)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (_.cover [/.set] - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (|> (all /.then - (/.set (list $foreign) (/.float float/0)) - (/.return (/.+ $foreign $foreign))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.local] + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (|> (/.return (/.+ $foreign $foreign)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (_.coverage [/.set] + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (|> (all /.then + (/.set (list $foreign) (/.float float/0)) + (/.return (/.+ $foreign $foreign))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|instance_var @@ -517,62 +517,62 @@ $object (# ! each (|>> %.nat (format "object_") /.local) random.nat)] (all _.and - (_.cover [/.instance] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (all /.then - (/.function /.initialize (list) - (/.set (list $instance) (/.float float/0))) - (/.function $method (list) - (/.return $instance)) - )])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.do (/.code $method) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_reader/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (all /.then - (/.attr_reader/* (list instance)) - (/.function /.initialize (list) - (/.set (list $instance) (/.float float/0))) - )])) - (/.return (|> $class - (/.new (list) {.#None}) - (/.the instance)))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_writer/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (all /.then - (/.attr_writer/* (list instance)) - (/.function $method (list) - (/.return $instance)) - )])) - (/.set (list $object) (|> $class - (/.new (list) {.#None}))) - (/.set (list (/.the instance $object)) (/.float float/0)) - (/.return (|> $object - (/.do (/.code $method) (list) {.#None})))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.attr_accessor/*] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (/.attr_accessor/* (list instance))])) - (/.set (list $object) (|> $class - (/.new (list) {.#None}))) - (/.set (list (/.the instance $object)) (/.float float/0)) - (/.return (/.the instance $object))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.instance] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.function /.initialize (list) + (/.set (list $instance) (/.float float/0))) + (/.function $method (list) + (/.return $instance)) + )])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.do (/.code $method) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.attr_reader/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.attr_reader/* (list instance)) + (/.function /.initialize (list) + (/.set (list $instance) (/.float float/0))) + )])) + (/.return (|> $class + (/.new (list) {.#None}) + (/.the instance)))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.attr_writer/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (all /.then + (/.attr_writer/* (list instance)) + (/.function $method (list) + (/.return $instance)) + )])) + (/.set (list $object) (|> $class + (/.new (list) {.#None}))) + (/.set (list (/.the instance $object)) (/.float float/0)) + (/.return (|> $object + (/.do (/.code $method) (list) {.#None})))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.attr_accessor/*] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (/.attr_accessor/* (list instance))])) + (/.set (list $object) (|> $class + (/.new (list) {.#None}))) + (/.set (list (/.the instance $object)) (/.float float/0)) + (/.return (/.the instance $object))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|static_var @@ -589,16 +589,16 @@ $class (# ! each (|>> %.nat (format "class_") /.local) random.nat)] (all _.and - (_.cover [/.static /.class_variable_set /.class_variable_get] - (expression (|>> (as Int) (i.= int/0)) - (|> (all /.then - (/.set (list $class) (/.class [/.#parameters (list) - /.#body (/.function $method (list) - (/.return (/.int +0)))])) - (/.statement (/.class_variable_set $static (/.int int/0) $class)) - (/.return (/.class_variable_get $static $class))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.static /.class_variable_set /.class_variable_get] + (expression (|>> (as Int) (i.= int/0)) + (|> (all /.then + (/.set (list $class) (/.class [/.#parameters (list) + /.#body (/.function $method (list) + (/.return (/.int +0)))])) + (/.statement (/.class_variable_set $static (/.int int/0) $class)) + (/.return (/.class_variable_get $static $class))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|variadic @@ -615,22 +615,22 @@ (all _.and (<| (_.for [/.LVar*]) (all _.and - (_.cover [/.variadic] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" $inputs)) - [(list (/.variadic $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* vals)))) - (_.cover [/.splat] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" (/.array (list (/.splat $inputs))))) - [(list (/.variadic $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* vals)))))) + (_.coverage [/.variadic] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" $inputs)) + [(list (/.variadic $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* vals)))) + (_.coverage [/.splat] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" (/.array (list (/.splat $inputs))))) + [(list (/.variadic $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* vals)))))) (<| (_.for [/.LVar**]) - (_.cover [/.variadic_kv /.double_splat] - (expression (|>> (as Int) .nat (n.= arity)) - (|> (/.return (/.the "length" $inputs)) - [(list (/.variadic_kv $inputs))] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.double_splat (/.hash (list.zipped_2 keys vals))))))))) + (_.coverage [/.variadic_kv /.double_splat] + (expression (|>> (as Int) .nat (n.= arity)) + (|> (/.return (/.the "length" $inputs)) + [(list (/.variadic_kv $inputs))] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.double_splat (/.hash (list.zipped_2 keys vals))))))))) ))) (def: test|var @@ -641,24 +641,24 @@ $constant (# ! each /.constant (random.lower_case 10))] (all _.and - (_.cover [/.defined?/1] - (and (expression (|>> (as Bit)) - (|> (/.defined?/1 $foreign) - (/.= /.nil))) - (expression (|>> (as Text) (text#= "local-variable")) - (|> (all /.then - (/.set (list $foreign) (/.float float/0)) - (/.return (/.defined?/1 $foreign))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) + (_.coverage [/.defined?/1] + (and (expression (|>> (as Bit)) + (|> (/.defined?/1 $foreign) + (/.= /.nil))) + (expression (|>> (as Text) (text#= "local-variable")) + (|> (all /.then + (/.set (list $foreign) (/.float float/0)) + (/.return (/.defined?/1 $foreign))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) (_.for [/.CVar] - (_.cover [/.constant] - (expression (|>> (as Text) (text#= "constant")) - (|> (all /.then - (/.set (list $constant) (/.float float/0)) - (/.return (/.defined?/1 $constant))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) + (_.coverage [/.constant] + (expression (|>> (as Text) (text#= "constant")) + (|> (all /.then + (/.set (list $constant) (/.float float/0)) + (/.return (/.defined?/1 $constant))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) (_.for [/.GVar] ..test|global) (_.for [/.LVar] @@ -679,24 +679,24 @@ (all _.and (<| (_.for [/.Var]) ..test|var) - (_.cover [/.Access] - (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.item (/.int +0) $foreign)] - (|> (all /.then - (/.set (list $foreign) (/.array (list $foreign))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) - (let [@ (/.item field $foreign)] - (|> (all /.then - (/.set (list $foreign) (/.hash (list [field $foreign]))) - (/.set (list @) (/.+ @ @)) - (/.return @)) - [(list $foreign)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - )) + (_.coverage [/.Access] + (and (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.item (/.int +0) $foreign)] + (|> (all /.then + (/.set (list $foreign) (/.array (list $foreign))) + (/.set (list @) (/.+ @ @)) + (/.return @)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (expression (|>> (as Frac) (f.= (f.+ float/0 float/0))) + (let [@ (/.item field $foreign)] + (|> (all /.then + (/.set (list $foreign) (/.hash (list [field $foreign]))) + (/.set (list @) (/.+ @ @)) + (/.return @)) + [(list $foreign)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + )) ))) (def: test|expression @@ -729,54 +729,54 @@ $inner_index (/.local "inner_index") $outer_index (/.local "outer_index")]] (all _.and - (_.cover [/.break] - (let [expected (i.* (.int expected_inner_iterations) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> (all /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) - /.break) - (/.set (list $output) (/.+ $input $output)) - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) - (_.cover [/.next] - (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> (all /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.next) - (/.set (list $output) (/.+ $input $output)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) - (_.cover [/.redo] - (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] - (expression (|>> (as Frac) f.int (i.= expected)) - (|> (all /.then - (/.set (list $inner_index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) - (all /.then - (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) - (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) - /.redo) - (/.set (list $output) (/.+ $input $output)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input))))))) + (_.coverage [/.break] + (let [expected (i.* (.int expected_inner_iterations) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.when (/.= (/.int (.int expected_inner_iterations)) $inner_index) + /.break) + (/.set (list $output) (/.+ $input $output)) + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) + (_.coverage [/.next] + (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.next) + (/.set (list $output) (/.+ $input $output)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) + (_.coverage [/.redo] + (let [expected (i.* (.int (n.- expected_inner_iterations full_inner_iterations)) input)] + (expression (|>> (as Frac) f.int (i.= expected)) + (|> (all /.then + (/.set (list $inner_index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int full_inner_iterations)) $inner_index) + (all /.then + (/.set (list $inner_index) (/.+ (/.int +1) $inner_index)) + (/.when (/.<= (/.int (.int expected_inner_iterations)) $inner_index) + /.redo) + (/.set (list $output) (/.+ $input $output)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input))))))) ))) (def: test|loop @@ -789,28 +789,28 @@ $index (/.local "index") expected (i.* (.int iterations) input)]] (all _.and - (_.cover [/.while] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.set (list $index) (/.int +0)) - (/.set (list $output) (/.int +0)) - (/.while (/.< (/.int (.int iterations)) $index) - (all /.then - (/.set (list $output) (/.+ $input $output)) - (/.set (list $index) (/.+ (/.int +1) $index)) - )) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input)))))) - (_.cover [/.for_in] - (expression (|>> (as Int) (i.= expected)) - (|> (all /.then - (/.set (list $output) (/.int +0)) - (/.for_in $index (/.array (list.repeated iterations (/.int input))) - (/.set (list $output) (/.+ $index $output))) - (/.return $output)) - [(list $input)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.int input)))))) + (_.coverage [/.while] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.set (list $index) (/.int +0)) + (/.set (list $output) (/.int +0)) + (/.while (/.< (/.int (.int iterations)) $index) + (all /.then + (/.set (list $output) (/.+ $input $output)) + (/.set (list $index) (/.+ (/.int +1) $index)) + )) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input)))))) + (_.coverage [/.for_in] + (expression (|>> (as Int) (i.= expected)) + (|> (all /.then + (/.set (list $output) (/.int +0)) + (/.for_in $index (/.array (list.repeated iterations (/.int input))) + (/.set (list $output) (/.+ $index $output))) + (/.return $output)) + [(list $input)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.int input)))))) ..test|label ))) @@ -834,71 +834,71 @@ .let [expected_tag (/.int expected_tag) dummy_tag (/.int dummy_tag)]] (all _.and - (_.cover [/.begin] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin (/.return (/.float expected)) - (list [(list) $ex (/.return (/.float dummy))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.Rescue /.throw/1] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin (all /.then - (/.throw/1 (/.string error)) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.float expected))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.raise] - (expression (|>> (as Frac) (f.= expected)) - (|> (/.begin (all /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.float expected))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.catch /.throw/2] - (and (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch expected_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch expected_tag) [(list)] - /.statement (/.catch dummy_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))) - (expression (|>> (as Frac) (f.= expected)) - (<| (/.apply_lambda/* (list)) - (/.lambda {.#None}) [(list)] - /.return - (/.catch dummy_tag) [(list)] - /.statement (/.catch expected_tag) [(list)] - (/.throw/2 expected_tag (/.float expected)))))) - (_.cover [/.latest_error_message] - (expression (|>> (as Text) (text#= error)) - (|> (/.begin (all /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (/.the "message" /.latest_error_message))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.latest_error_location] - (and (|> (/.return /.latest_error_location) + (_.coverage [/.begin] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (/.return (/.float expected)) + (list [(list) $ex (/.return (/.float dummy))])) [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)) - ..nil) - (expression (|>> (as Bit) (bit#= true)) - (|> (/.begin (all /.then - (/.statement (/.raise (/.string error))) - (/.return (/.float dummy))) - (list [(list) $ex (/.return (all /.and - (/.do "kind_of?" (list (is /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) - (/.> (/.int +0) (/.the "length" /.latest_error_location))))])) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))))) + (/.apply_lambda/* (list))))) + (_.coverage [/.Rescue /.throw/1] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (all /.then + (/.throw/1 (/.string error)) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.float expected))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.raise] + (expression (|>> (as Frac) (f.= expected)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.float expected))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.catch /.throw/2] + (and (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch expected_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))) + (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch expected_tag) [(list)] + /.statement (/.catch dummy_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))) + (expression (|>> (as Frac) (f.= expected)) + (<| (/.apply_lambda/* (list)) + (/.lambda {.#None}) [(list)] + /.return + (/.catch dummy_tag) [(list)] + /.statement (/.catch expected_tag) [(list)] + (/.throw/2 expected_tag (/.float expected)))))) + (_.coverage [/.latest_error_message] + (expression (|>> (as Text) (text#= error)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (/.the "message" /.latest_error_message))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.latest_error_location] + (and (|> (/.return /.latest_error_location) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)) + ..nil) + (expression (|>> (as Bit) (bit#= true)) + (|> (/.begin (all /.then + (/.statement (/.raise (/.string error))) + (/.return (/.float dummy))) + (list [(list) $ex (/.return (all /.and + (/.do "kind_of?" (list (is /.CVar (/.manual "Array"))) {.#None} /.latest_error_location) + (/.> (/.int +0) (/.the "length" /.latest_error_location))))])) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))))) ))) (def: test|function @@ -916,40 +916,40 @@ $arg/1 (# ! each /.local (random.lower_case 11)) $arg/2 (# ! each /.local (random.lower_case 12))] (all _.and - (_.cover [/.lambda /.return] - (and (expression (|>> (as Frac) (f.= float/0)) - (|> (/.return (/.float float/0)) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list)))) - (expression (|>> (as Frac) f.nat (n.= iterations)) - (|> (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self) - $arg/0)) - [(list $arg/0)] (/.lambda {.#Some $self}) - (/.apply_lambda/* (list (/.int +0))))))) - (_.cover [/.apply_lambda/*] - (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) - (|> (/.return (all /.+ $arg/0 $arg/1 $arg/2)) - [(list $arg/0 $arg/1 $arg/2)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2)))))) - (_.cover [/.function] - (expression (|>> (as Frac) f.nat (n.= iterations)) - (|> (all /.then - (/.function $self (list $arg/0) - (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) - (/.apply/* (list (/.+ (/.int +1) $arg/0)) {.#None} $self) - $arg/0))) - (/.return (/.apply/* (list (/.int +0)) {.#None} $self))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.apply/*] - (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) - (|> (all /.then - (/.function $self (list $arg/0 $arg/1 $arg/2) - (/.return (all /.+ $arg/0 $arg/1 $arg/2))) - (/.return (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) {.#None} $self))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.lambda /.return] + (and (expression (|>> (as Frac) (f.= float/0)) + (|> (/.return (/.float float/0)) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list)))) + (expression (|>> (as Frac) f.nat (n.= iterations)) + (|> (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply_lambda/* (list (/.+ (/.int +1) $arg/0)) $self) + $arg/0)) + [(list $arg/0)] (/.lambda {.#Some $self}) + (/.apply_lambda/* (list (/.int +0))))))) + (_.coverage [/.apply_lambda/*] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (|> (/.return (all /.+ $arg/0 $arg/1 $arg/2)) + [(list $arg/0 $arg/1 $arg/2)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0) (/.float float/1) (/.float float/2)))))) + (_.coverage [/.function] + (expression (|>> (as Frac) f.nat (n.= iterations)) + (|> (all /.then + (/.function $self (list $arg/0) + (/.return (/.? (/.< (/.int (.int iterations)) $arg/0) + (/.apply/* (list (/.+ (/.int +1) $arg/0)) {.#None} $self) + $arg/0))) + (/.return (/.apply/* (list (/.int +0)) {.#None} $self))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.apply/*] + (expression (|>> (as Frac) (f.= (all f.+ float/0 float/1 float/2))) + (|> (all /.then + (/.function $self (list $arg/0 $arg/1 $arg/2) + (/.return (all /.+ $arg/0 $arg/1 $arg/2))) + (/.return (/.apply/* (list (/.float float/0) (/.float float/1) (/.float float/2)) {.#None} $self))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|branching @@ -969,21 +969,21 @@ $arg/2 (/.local arg/2)] ??? random.bit] (all _.and - (_.cover [/.if] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> (/.if (/.bool ???) - (/.return (/.float float/0)) - (/.return (/.float float/1))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) - (_.cover [/.when] - (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) - (|> (all /.then - (/.when (/.bool ???) - (/.return (/.float float/0))) - (/.return (/.float float/1))) - [(list)] (/.lambda {.#None}) - (/.apply_lambda/* (list))))) + (_.coverage [/.if] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (/.if (/.bool ???) + (/.return (/.float float/0)) + (/.return (/.float float/1))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) + (_.coverage [/.when] + (expression (|>> (as Frac) (f.= (if ??? float/0 float/1))) + (|> (all /.then + (/.when (/.bool ???) + (/.return (/.float float/0))) + (/.return (/.float float/1))) + [(list)] (/.lambda {.#None}) + (/.apply_lambda/* (list))))) ))) (def: test|statement @@ -998,29 +998,29 @@ expected (# ! each (|>> %.int (text.replaced "+" "")) random.int)] (all _.and - (_.cover [/.statement] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.statement (/.+ $arg/0 $arg/0)) - (/.return $arg/0)) - [(list $arg/0)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0)))))) - (_.cover [/.then] - (expression (|>> (as Frac) (f.= float/0)) - (|> (all /.then - (/.return $arg/0) - (/.return $arg/1)) - [(list $arg/0 $arg/1)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.float float/0) (/.float float/1)))))) - (_.cover [/.require/1] - (let [$JSON (is /.CVar (/.manual "JSON"))] - (expression (|>> (as Text) (text#= expected)) - (|> (all /.then - (/.statement (/.require/1 (/.string "json"))) - (/.return (let [json (/.do "parse" (list $arg/0) {.#None} $JSON)] - (/.do "generate" (list json) {.#None} $JSON)))) - [(list $arg/0)] (/.lambda {.#None}) - (/.apply_lambda/* (list (/.string expected))))))) + (_.coverage [/.statement] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.statement (/.+ $arg/0 $arg/0)) + (/.return $arg/0)) + [(list $arg/0)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0)))))) + (_.coverage [/.then] + (expression (|>> (as Frac) (f.= float/0)) + (|> (all /.then + (/.return $arg/0) + (/.return $arg/1)) + [(list $arg/0 $arg/1)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.float float/0) (/.float float/1)))))) + (_.coverage [/.require/1] + (let [$JSON (is /.CVar (/.manual "JSON"))] + (expression (|>> (as Text) (text#= expected)) + (|> (all /.then + (/.statement (/.require/1 (/.string "json"))) + (/.return (let [json (/.do "parse" (list $arg/0) {.#None} $JSON)] + (/.do "generate" (list json) {.#None} $JSON)))) + [(list $arg/0)] (/.lambda {.#None}) + (/.apply_lambda/* (list (/.string expected))))))) ..test|exception ..test|branching ..test|loop @@ -1051,10 +1051,10 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random_expression)) - (_.cover [/.code /.manual] - (|> (/.manual (/.code expected)) - (is /.Expression) - (/#= expected))) + (_.coverage [/.code /.manual] + (|> (/.manual (/.code expected)) + (is /.Expression) + (/#= expected))) (_.for [/.Expression] ..test|expression) (_.for [/.Statement] diff --git a/stdlib/source/test/lux/test.lux b/stdlib/source/test/lux/test.lux index b14540cdb..94bfaa193 100644 --- a/stdlib/source/test/lux/test.lux +++ b/stdlib/source/test/lux/test.lux @@ -39,13 +39,13 @@ (in (do async.monad [[success_tally success_message] (/.assertion expected_message/0 true) [failure_tally failure_message] (/.assertion expected_message/0 false)] - (/.cover' [/.assertion /.Tally] - (and (text.ends_with? expected_message/0 success_message) - (text.ends_with? expected_message/0 failure_message) - (and (n.= 1 (the /.#successes success_tally)) - (n.= 0 (the /.#failures success_tally))) - (and (n.= 0 (the /.#successes failure_tally)) - (n.= 1 (the /.#failures failure_tally))))))) + (/.coverage' [/.assertion /.Tally] + (and (text.ends_with? expected_message/0 success_message) + (text.ends_with? expected_message/0 failure_message) + (and (n.= 1 (the /.#successes success_tally)) + (n.= 0 (the /.#failures success_tally))) + (and (n.= 0 (the /.#successes failure_tally)) + (n.= 1 (the /.#failures failure_tally))))))) (in (do async.monad [tt (/.and' (/.assertion expected_message/0 true) (/.assertion expected_message/1 true)) @@ -55,11 +55,11 @@ (/.assertion expected_message/1 false)) ft (/.and' (/.assertion expected_message/0 false) (/.assertion expected_message/1 true))] - (/.cover' [/.and'] - (and (..verify expected_message/0 expected_message/1 2 0 tt) - (..verify expected_message/0 expected_message/1 0 2 ff) - (..verify expected_message/0 expected_message/1 1 1 tf) - (..verify expected_message/0 expected_message/1 1 1 ft))))) + (/.coverage' [/.and'] + (and (..verify expected_message/0 expected_message/1 2 0 tt) + (..verify expected_message/0 expected_message/1 0 2 ff) + (..verify expected_message/0 expected_message/1 1 1 tf) + (..verify expected_message/0 expected_message/1 1 1 ft))))) ))) (def: seed @@ -72,7 +72,7 @@ (do ! [sample random.nat .let [wrote? (io.run! (write sample))]] - (/.test "" wrote?))) + (/.property "" wrote?))) post (<| (/.seed seed) (do ! [actual random.nat] @@ -82,23 +82,23 @@ (in (do async.monad [[pre_tally pre_message] pre [post_tally post_message] post] - (/.cover' [/.seed] - (and (and (n.= 1 (the /.#successes pre_tally)) - (n.= 0 (the /.#failures pre_tally))) - (and (n.= 1 (the /.#successes post_tally)) - (n.= 0 (the /.#failures post_tally))))))))) + (/.coverage' [/.seed] + (and (and (n.= 1 (the /.#successes pre_tally)) + (n.= 0 (the /.#failures pre_tally))) + (and (n.= 1 (the /.#successes post_tally)) + (n.= 0 (the /.#failures post_tally))))))))) (def: times /.Test (all /.and (do [! random.monad] - [times_assertion (/.times 0 (/.test "" true))] + [times_assertion (/.times 0 (/.property "" true))] (in (do async.monad [[tally error] times_assertion] - (/.cover' [/.must_try_test_at_least_once] - (and (text.contains? (the exception.#label /.must_try_test_at_least_once) error) - (n.= 0 (the /.#successes tally)) - (n.= 1 (the /.#failures tally))))))) + (/.coverage' [/.must_try_test_at_least_once] + (and (text.contains? (the exception.#label /.must_try_test_at_least_once) error) + (n.= 0 (the /.#successes tally)) + (n.= 1 (the /.#failures tally))))))) (do [! random.monad] [expected (# ! each (|>> (n.% 10) ++) random.nat) .let [counter (is (Atom Nat) @@ -107,14 +107,14 @@ (do ! [_ (in []) .let [_ (io.run! (atom.update! ++ counter))]] - (/.test "" true)))] + (/.property "" true)))] (in (do async.monad [[tally error] times_assertion actual (async.future (atom.read! counter))] - (/.cover' [/.times] - (and (n.= expected actual) - (n.= 1 (the /.#successes tally)) - (n.= 0 (the /.#failures tally))))))) + (/.coverage' [/.times] + (and (n.= expected actual) + (n.= 1 (the /.#successes tally)) + (n.= 0 (the /.#failures tally))))))) )) (def: in_parallel @@ -130,14 +130,14 @@ (do ! [_ (in []) .let [_ (io.run! (atom.update! ++ counter))]] - (/.test "" true)))] + (/.property "" true)))] (in (do async.monad [[tally error] assertion actual (async.future (atom.read! counter))] - (/.cover' [/.in_parallel] - (and (n.= expected actual) - (n.= expected (the /.#successes tally)) - (n.= 0 (the /.#failures tally))))))) + (/.coverage' [/.in_parallel] + (and (n.= expected actual) + (n.= expected (the /.#successes tally)) + (n.= 0 (the /.#failures tally))))))) (do [! random.monad] [expected (# ! each (|>> (n.% 10) ++) random.nat) .let [counter (is (Atom Nat) @@ -149,19 +149,19 @@ [_ (in []) .let [_ (undefined) _ (io.run! (atom.update! ++ counter))]] - (/.test "" true)))] + (/.property "" true)))] (in (do async.monad [[tally error] assertion actual (async.future (atom.read! counter))] - (/.cover' [/.error_during_execution] - (let [correct_error! (text.contains? (the exception.#label /.error_during_execution) error) - no_complete_run! (n.= 0 actual) - no_successes! (n.= 0 (the /.#successes tally)) - ran_all_tests! (n.= expected (the /.#failures tally))] - (and correct_error! - no_complete_run! - no_successes! - ran_all_tests!)))))) + (/.coverage' [/.error_during_execution] + (let [correct_error! (text.contains? (the exception.#label /.error_during_execution) error) + no_complete_run! (n.= 0 actual) + no_successes! (n.= 0 (the /.#successes tally)) + ran_all_tests! (n.= expected (the /.#failures tally))] + (and correct_error! + no_complete_run! + no_successes! + ran_all_tests!)))))) )) (def: .public dummy_target @@ -171,49 +171,49 @@ /.Test (all /.and (do random.monad - [not_covering (/.test "" true) - covering (/.covering .._ (/.test "" true))] + [not_covering (/.property "" true) + covering (/.covering .._ (/.property "" true))] (in (do async.monad [[not_covering _] not_covering [covering _] covering] - (/.cover' [/.covering] - (and (and (set.empty? (the /.#expected_coverage not_covering)) - (set.empty? (the /.#actual_coverage not_covering))) - (and (not (set.empty? (the /.#expected_coverage covering))) - (set.empty? (the /.#actual_coverage covering)))))))) + (/.coverage' [/.covering] + (and (and (set.empty? (the /.#expected_coverage not_covering)) + (set.empty? (the /.#actual_coverage not_covering))) + (and (not (set.empty? (the /.#expected_coverage covering))) + (set.empty? (the /.#actual_coverage covering)))))))) (do random.monad - [not_covering (/.covering .._ (/.test "" true)) - covering (/.covering .._ (/.cover [..dummy_target] true))] + [not_covering (/.covering .._ (/.property "" true)) + covering (/.covering .._ (/.coverage [..dummy_target] true))] (in (do async.monad [[not_covering _] not_covering [covering _] covering] - (/.cover' [/.cover] - (and (and (not (set.empty? (the /.#expected_coverage not_covering))) - (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) - (and (not (set.empty? (the /.#expected_coverage covering))) - (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) + (/.coverage' [/.coverage] + (and (and (not (set.empty? (the /.#expected_coverage not_covering))) + (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) + (and (not (set.empty? (the /.#expected_coverage covering))) + (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) (do random.monad - [not_covering (/.covering .._ (/.test "" true)) - covering (/.covering .._ (in (/.cover' [..dummy_target] true)))] + [not_covering (/.covering .._ (/.property "" true)) + covering (/.covering .._ (in (/.coverage' [..dummy_target] true)))] (in (do async.monad [[not_covering _] not_covering [covering _] covering] - (/.cover' [/.cover'] - (and (and (not (set.empty? (the /.#expected_coverage not_covering))) - (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) - (and (not (set.empty? (the /.#expected_coverage covering))) - (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) + (/.coverage' [/.coverage'] + (and (and (not (set.empty? (the /.#expected_coverage not_covering))) + (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) + (and (not (set.empty? (the /.#expected_coverage covering))) + (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) (do random.monad - [not_covering (/.covering .._ (/.test "" true)) - covering (/.covering .._ (/.for [..dummy_target] (/.test "" true)))] + [not_covering (/.covering .._ (/.property "" true)) + covering (/.covering .._ (/.for [..dummy_target] (/.property "" true)))] (in (do async.monad [[not_covering _] not_covering [covering _] covering] - (/.cover' [/.for] - (and (and (not (set.empty? (the /.#expected_coverage not_covering))) - (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) - (and (not (set.empty? (the /.#expected_coverage covering))) - (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) + (/.coverage' [/.for] + (and (and (not (set.empty? (the /.#expected_coverage not_covering))) + (not (set.member? (the /.#actual_coverage not_covering) (symbol ..dummy_target)))) + (and (not (set.empty? (the /.#expected_coverage covering))) + (set.member? (the /.#actual_coverage covering) (symbol ..dummy_target)))))))) )) (def: .public test @@ -232,73 +232,73 @@ (/.for [/.Seed] seed) (do ! - [success_assertion (/.test expected_message/0 true) - failure_assertion (/.test expected_message/0 false)] + [success_assertion (/.property expected_message/0 true) + failure_assertion (/.property expected_message/0 false)] (in (do async.monad [[success_tally success_message] success_assertion [failure_tally failure_message] failure_assertion] - (/.cover' [/.test] - (and (text.ends_with? (%.text expected_message/0) success_message) - (text.ends_with? (%.text expected_message/0) failure_message) - (and (n.= 1 (the /.#successes success_tally)) - (n.= 0 (the /.#failures success_tally))) - (and (n.= 0 (the /.#successes failure_tally)) - (n.= 1 (the /.#failures failure_tally)))))))) + (/.coverage' [/.property] + (and (text.ends_with? (%.text expected_message/0) success_message) + (text.ends_with? (%.text expected_message/0) failure_message) + (and (n.= 1 (the /.#successes success_tally)) + (n.= 0 (the /.#failures success_tally))) + (and (n.= 0 (the /.#successes failure_tally)) + (n.= 1 (the /.#failures failure_tally)))))))) (do ! - [tt (/.and (/.test expected_message/0 true) - (/.test expected_message/1 true)) - ff (/.and (/.test expected_message/0 false) - (/.test expected_message/1 false)) - tf (/.and (/.test expected_message/0 true) - (/.test expected_message/1 false)) - ft (/.and (/.test expected_message/0 false) - (/.test expected_message/1 true))] + [tt (/.and (/.property expected_message/0 true) + (/.property expected_message/1 true)) + ff (/.and (/.property expected_message/0 false) + (/.property expected_message/1 false)) + tf (/.and (/.property expected_message/0 true) + (/.property expected_message/1 false)) + ft (/.and (/.property expected_message/0 false) + (/.property expected_message/1 true))] (in (do async.monad [tt tt ff ff tf tf ft ft] - (/.cover' [/.and] - (and (..verify expected_message/0 expected_message/1 2 0 tt) - (..verify expected_message/0 expected_message/1 0 2 ff) - (..verify expected_message/0 expected_message/1 1 1 tf) - (..verify expected_message/0 expected_message/1 1 1 ft)))))) + (/.coverage' [/.and] + (and (..verify expected_message/0 expected_message/1 2 0 tt) + (..verify expected_message/0 expected_message/1 0 2 ff) + (..verify expected_message/0 expected_message/1 1 1 tf) + (..verify expected_message/0 expected_message/1 1 1 ft)))))) (do ! - [success_assertion (/.context expected_context (/.test expected_message/0 true)) - failure_assertion (/.context expected_context (/.test expected_message/0 false))] + [success_assertion (/.context expected_context (/.property expected_message/0 true)) + failure_assertion (/.context expected_context (/.property expected_message/0 false))] (in (do async.monad [[success_tally success_message] success_assertion [failure_tally failure_message] failure_assertion] - (/.cover' [/.context] - (and (and (text.contains? expected_context success_message) - (text.contains? expected_message/0 success_message)) - (and (text.contains? expected_context failure_message) - (text.contains? expected_message/0 failure_message)) - (and (n.= 1 (the /.#successes success_tally)) - (n.= 0 (the /.#failures success_tally))) - (and (n.= 0 (the /.#successes failure_tally)) - (n.= 1 (the /.#failures failure_tally)))))))) + (/.coverage' [/.context] + (and (and (text.contains? expected_context success_message) + (text.contains? expected_message/0 success_message)) + (and (text.contains? expected_context failure_message) + (text.contains? expected_message/0 failure_message)) + (and (n.= 1 (the /.#successes success_tally)) + (n.= 0 (the /.#failures success_tally))) + (and (n.= 0 (the /.#successes failure_tally)) + (n.= 1 (the /.#failures failure_tally)))))))) (do ! [failure_assertion (/.failure expected_message/0)] (in (do async.monad [[failure_tally failure_message] failure_assertion] - (/.cover' [/.failure] - (and (text.contains? expected_message/0 failure_message) - (and (n.= 0 (the /.#successes failure_tally)) - (n.= 1 (the /.#failures failure_tally)))))))) + (/.coverage' [/.failure] + (and (text.contains? expected_message/0 failure_message) + (and (n.= 0 (the /.#successes failure_tally)) + (n.= 1 (the /.#failures failure_tally)))))))) (do ! [success_assertion (/.lifted expected_message/0 (in true)) failure_assertion (/.lifted expected_message/0 (in false))] (in (do async.monad [[success_tally success_message] success_assertion [failure_tally failure_message] failure_assertion] - (/.cover' [/.lifted] - (and (text.contains? expected_message/0 success_message) - (text.contains? expected_message/0 failure_message) - (and (n.= 1 (the /.#successes success_tally)) - (n.= 0 (the /.#failures success_tally))) - (and (n.= 0 (the /.#successes failure_tally)) - (n.= 1 (the /.#failures failure_tally)))))))) + (/.coverage' [/.lifted] + (and (text.contains? expected_message/0 success_message) + (text.contains? expected_message/0 failure_message) + (and (n.= 1 (the /.#successes success_tally)) + (n.= 0 (the /.#failures success_tally))) + (and (n.= 0 (the /.#successes failure_tally)) + (n.= 1 (the /.#failures failure_tally)))))))) ..times ..in_parallel ..coverage diff --git a/stdlib/source/test/lux/time.lux b/stdlib/source/test/lux/time.lux index 74bdeb3f4..91bd45a3e 100644 --- a/stdlib/source/test/lux/time.lux +++ b/stdlib/source/test/lux/time.lux @@ -49,12 +49,12 @@ Test (do [! random.monad] [expected random.time] - (_.cover [/.clock /.time] - (|> expected - /.clock - /.time - (try#each (# /.equivalence = expected)) - (try.else false))))) + (_.coverage [/.clock /.time] + (|> expected + /.clock + /.time + (try#each (# /.equivalence = expected)) + (try.else false))))) (def: for_ranges Test @@ -69,44 +69,44 @@ invalid_second (|> valid_second (n.+ /.seconds) (n.min 99))]] (`` (all _.and (~~ (template [<cap> <exception> <prefix> <suffix> <valid> <invalid>] - [(_.cover [<cap> <exception>] - (let [valid! - (|> <valid> - %.nat - (text.prefix <prefix>) - (text.suffix <suffix>) - (# /.codec decoded) - (pipe.case - {try.#Success _} true - {try.#Failure error} false)) - - invalid! - (|> <invalid> - %.nat - (text.prefix <prefix>) - (text.suffix <suffix>) - (# /.codec decoded) - (pipe.case - {try.#Success _} - false - - {try.#Failure error} - (exception.match? <exception> error)))] - (and valid! - invalid!)))] + [(_.coverage [<cap> <exception>] + (let [valid! + (|> <valid> + %.nat + (text.prefix <prefix>) + (text.suffix <suffix>) + (# /.codec decoded) + (pipe.case + {try.#Success _} true + {try.#Failure error} false)) + + invalid! + (|> <invalid> + %.nat + (text.prefix <prefix>) + (text.suffix <suffix>) + (# /.codec decoded) + (pipe.case + {try.#Success _} + false + + {try.#Failure error} + (exception.match? <exception> error)))] + (and valid! + invalid!)))] [/.hours /.invalid_hour "" ":00:00.000" valid_hour invalid_hour] [/.minutes /.invalid_minute "00:" ":00.000" valid_minute invalid_minute] [/.seconds /.invalid_second "00:00:" ".000" valid_second invalid_second] )) - (_.cover [/.milli_seconds] - (|> valid_milli_second - %.nat - (format "00:00:00.") - (# /.codec decoded) - (pipe.case - {try.#Success _} true - {try.#Failure error} false))) + (_.coverage [/.milli_seconds] + (|> valid_milli_second + %.nat + (format "00:00:00.") + (# /.codec decoded) + (pipe.case + {try.#Success _} true + {try.#Failure error} false))) )))) (def: .public test @@ -122,29 +122,29 @@ (`` (all _.and ..for_implementation - (_.cover [/.millis /.of_millis] - (|> expected - /.millis - /.of_millis - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.time_exceeds_a_day] - (case (/.of_millis out_of_bounds) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.time_exceeds_a_day error))) - (_.cover [/.midnight] - (|> /.midnight - /.millis - (n.= 0))) - (_.cover [/.parser] - (|> expected - (# /.codec encoded) - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) + (_.coverage [/.millis /.of_millis] + (|> expected + /.millis + /.of_millis + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.time_exceeds_a_day] + (case (/.of_millis out_of_bounds) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.time_exceeds_a_day error))) + (_.coverage [/.midnight] + (|> /.midnight + /.millis + (n.= 0))) + (_.coverage [/.parser] + (|> expected + (# /.codec encoded) + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) ..for_ranges (_.for [/.Clock] ..for_clock) diff --git a/stdlib/source/test/lux/time/date.lux b/stdlib/source/test/lux/time/date.lux index e24194825..5f341d04f 100644 --- a/stdlib/source/test/lux/time/date.lux +++ b/stdlib/source/test/lux/time/date.lux @@ -41,41 +41,41 @@ (do random.monad [expected random.date] - (_.cover [/.date /.year /.month /.day_of_month] - (|> (/.date (/.year expected) - (/.month expected) - (/.day_of_month expected)) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.date /.year /.month /.day_of_month] + (|> (/.date (/.year expected) + (/.month expected) + (/.day_of_month expected)) + (try#each (# /.equivalence = expected)) + (try.else false)))) (do random.monad [expected random.date] - (_.cover [/.invalid_day] - (case (/.date (/.year expected) - (/.month expected) - (n.+ 31 (/.day_of_month expected))) - {try.#Failure error} - (exception.match? /.invalid_day error) - - {try.#Success _} - false))) + (_.coverage [/.invalid_day] + (case (/.date (/.year expected) + (/.month expected) + (n.+ 31 (/.day_of_month expected))) + {try.#Failure error} + (exception.match? /.invalid_day error) + + {try.#Success _} + false))) (do random.monad [expected random.date] - (_.cover [/.days /.of_days] - (|> expected - /.days - /.of_days - (# /.equivalence = expected)))) - (_.cover [/.epoch] - (|> /.epoch - /.days - (i.= +0))) + (_.coverage [/.days /.of_days] + (|> expected + /.days + /.of_days + (# /.equivalence = expected)))) + (_.coverage [/.epoch] + (|> /.epoch + /.days + (i.= +0))) (do random.monad [expected random.date] - (_.cover [/.parser] - (|> (# /.codec encoded expected) - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.parser] + (|> (# /.codec encoded expected) + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) (do [! random.monad] [year (# ! each (|>> (n.% 10,000) ++) random.nat) @@ -86,11 +86,11 @@ .let [input (format (%.nat year) "-" (%.nat month) "-" (%.nat day))]] - (_.cover [/.invalid_month] - (case (<text>.result /.parser input) - {try.#Failure error} - (exception.match? /.invalid_month error) - - {try.#Success _} - false))) + (_.coverage [/.invalid_month] + (case (<text>.result /.parser input) + {try.#Failure error} + (exception.match? /.invalid_month error) + + {try.#Success _} + false))) ))) diff --git a/stdlib/source/test/lux/time/day.lux b/stdlib/source/test/lux/time/day.lux index 638e28ee6..85b387bca 100644 --- a/stdlib/source/test/lux/time/day.lux +++ b/stdlib/source/test/lux/time/day.lux @@ -58,31 +58,31 @@ (do random.monad [not_a_day (random.upper_case 1)] - (_.cover [/.not_a_day_of_the_week] - (case (# /.codec decoded not_a_day) - {try.#Failure error} - (exception.match? /.not_a_day_of_the_week error) - - {try.#Success _} - false))) - (_.cover [/.number /.by_number] - (|> expected - /.number - /.by_number - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.invalid_day] - (case (/.by_number invalid) - {try.#Failure error} - (exception.match? /.invalid_day error) - - {try.#Success _} - false)) - (_.cover [/.week] - (let [all (list.size /.week) - uniques (set.size (set.of_list /.hash /.week))] - (and (n.= (/.number {/.#Saturday}) - all) - (n.= all - uniques)))) + (_.coverage [/.not_a_day_of_the_week] + (case (# /.codec decoded not_a_day) + {try.#Failure error} + (exception.match? /.not_a_day_of_the_week error) + + {try.#Success _} + false))) + (_.coverage [/.number /.by_number] + (|> expected + /.number + /.by_number + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.invalid_day] + (case (/.by_number invalid) + {try.#Failure error} + (exception.match? /.invalid_day error) + + {try.#Success _} + false)) + (_.coverage [/.week] + (let [all (list.size /.week) + uniques (set.size (set.of_list /.hash /.week))] + (and (n.= (/.number {/.#Saturday}) + all) + (n.= all + uniques)))) )))) diff --git a/stdlib/source/test/lux/time/duration.lux b/stdlib/source/test/lux/time/duration.lux index 74c05500e..f106e7730 100644 --- a/stdlib/source/test/lux/time/duration.lux +++ b/stdlib/source/test/lux/time/duration.lux @@ -38,31 +38,31 @@ (do random.monad [duration random.duration] - (_.cover [/.of_millis /.millis] - (|> duration /.millis /.of_millis (# /.equivalence = duration)))) + (_.coverage [/.of_millis /.millis] + (|> duration /.millis /.of_millis (# /.equivalence = duration)))) (do random.monad [.let [(open "#[0]") /.equivalence] expected random.duration parameter random.duration] (all _.and - (_.cover [/.composite /.difference] - (|> expected (/.composite parameter) (/.difference parameter) (#= expected))) - (_.cover [/.empty] - (|> expected (/.composite /.empty) (#= expected))) - (_.cover [/.inverse] - (and (|> expected /.inverse /.inverse (#= expected)) - (|> expected (/.composite (/.inverse expected)) (#= /.empty)))) - (_.cover [/.positive? /.negative? /.neutral?] - (or (bit#= (/.positive? expected) - (/.negative? (/.inverse expected))) - (bit#= (/.neutral? expected) - (/.neutral? (/.inverse expected))))) + (_.coverage [/.composite /.difference] + (|> expected (/.composite parameter) (/.difference parameter) (#= expected))) + (_.coverage [/.empty] + (|> expected (/.composite /.empty) (#= expected))) + (_.coverage [/.inverse] + (and (|> expected /.inverse /.inverse (#= expected)) + (|> expected (/.composite (/.inverse expected)) (#= /.empty)))) + (_.coverage [/.positive? /.negative? /.neutral?] + (or (bit#= (/.positive? expected) + (/.negative? (/.inverse expected))) + (bit#= (/.neutral? expected) + (/.neutral? (/.inverse expected))))) )) (do random.monad [.let [(open "#[0]") /.equivalence] factor random.nat] - (_.cover [/.up /.down] - (|> /.milli_second (/.up factor) (/.down factor) (#= /.milli_second)))) + (_.coverage [/.up /.down] + (|> /.milli_second (/.up factor) (/.down factor) (#= /.milli_second)))) (do [! random.monad] [.let [(open "#[0]") /.order positive (|> random.duration @@ -74,18 +74,18 @@ sample positive frame positive] (`` (all _.and - (_.cover [/.framed] - (let [sample' (/.framed frame sample)] - (and (#< frame sample') - (bit#= (#< frame sample) - (#= sample sample'))))) - (_.cover [/.ticks] - (i.= +1 (/.ticks sample sample))) - (_.cover [/.milli_second] - (#= /.empty (# /.enum pred /.milli_second))) + (_.coverage [/.framed] + (let [sample' (/.framed frame sample)] + (and (#< frame sample') + (bit#= (#< frame sample) + (#= sample sample'))))) + (_.coverage [/.ticks] + (i.= +1 (/.ticks sample sample))) + (_.coverage [/.milli_second] + (#= /.empty (# /.enum pred /.milli_second))) (~~ (template [<factor> <big> <small>] - [(_.cover [<big>] - (|> <big> (/.ticks <small>) (i.= <factor>)))] + [(_.coverage [<big>] + (|> <big> (/.ticks <small>) (i.= <factor>)))] [+1,000 /.second /.milli_second] [+60 /.minute /.second] diff --git a/stdlib/source/test/lux/time/instant.lux b/stdlib/source/test/lux/time/instant.lux index 16299a1a4..b31bf3749 100644 --- a/stdlib/source/test/lux/time/instant.lux +++ b/stdlib/source/test/lux/time/instant.lux @@ -42,14 +42,14 @@ [.let [(open "#[0]") /.equivalence] expected random.instant] (all _.and - (_.cover [/.millis /.of_millis] - (|> expected /.millis /.of_millis (#= expected))) - (_.cover [/.relative /.absolute] - (|> expected /.relative /.absolute (#= expected))) - (_.cover [/.date /.time /.of_date_time] - (#= expected - (/.of_date_time (/.date expected) - (/.time expected)))) + (_.coverage [/.millis /.of_millis] + (|> expected /.millis /.of_millis (#= expected))) + (_.coverage [/.relative /.absolute] + (|> expected /.relative /.absolute (#= expected))) + (_.coverage [/.date /.time /.of_date_time] + (#= expected + (/.of_date_time (/.date expected) + (/.time expected)))) )) (do random.monad [.let [(open "#[0]") /.equivalence @@ -57,50 +57,50 @@ from random.instant to random.instant] (all _.and - (_.cover [/.span] - (|> from (/.span from) (duration#= duration.empty))) - (_.cover [/.after] - (|> from (/.after (/.span from to)) (#= to))) - (_.cover [/.epoch] - (duration#= (/.relative to) - (/.span /.epoch to))) + (_.coverage [/.span] + (|> from (/.span from) (duration#= duration.empty))) + (_.coverage [/.after] + (|> from (/.after (/.span from to)) (#= to))) + (_.coverage [/.epoch] + (duration#= (/.relative to) + (/.span /.epoch to))) )) (do random.monad [instant random.instant .let [d0 (/.day_of_week instant)]] - (_.cover [/.day_of_week] - (let [apply (is (-> (-> Duration Duration) (-> Day Day) Nat Bit) - (function (_ polarity move steps) - (let [day_shift (list#mix (function.constant move) - d0 - (list.repeated steps [])) - instant_shift (|> instant - (/.after (polarity (duration.up steps duration.day))) - /.day_of_week)] - (day#= day_shift - instant_shift))))] - (and (apply function.identity day#succ 0) - (apply function.identity day#succ 1) - (apply function.identity day#succ 2) - (apply function.identity day#succ 3) - (apply function.identity day#succ 4) - (apply function.identity day#succ 5) - (apply function.identity day#succ 6) - (apply function.identity day#succ 7) + (_.coverage [/.day_of_week] + (let [apply (is (-> (-> Duration Duration) (-> Day Day) Nat Bit) + (function (_ polarity move steps) + (let [day_shift (list#mix (function.constant move) + d0 + (list.repeated steps [])) + instant_shift (|> instant + (/.after (polarity (duration.up steps duration.day))) + /.day_of_week)] + (day#= day_shift + instant_shift))))] + (and (apply function.identity day#succ 0) + (apply function.identity day#succ 1) + (apply function.identity day#succ 2) + (apply function.identity day#succ 3) + (apply function.identity day#succ 4) + (apply function.identity day#succ 5) + (apply function.identity day#succ 6) + (apply function.identity day#succ 7) - (apply duration.inverse day#pred 0) - (apply duration.inverse day#pred 1) - (apply duration.inverse day#pred 2) - (apply duration.inverse day#pred 3) - (apply duration.inverse day#pred 4) - (apply duration.inverse day#pred 5) - (apply duration.inverse day#pred 6) - (apply duration.inverse day#pred 7))))) - (_.cover [/.now] - (case (try (io.run! /.now)) - {try.#Success _} - true - - {try.#Failure _} - false)) + (apply duration.inverse day#pred 0) + (apply duration.inverse day#pred 1) + (apply duration.inverse day#pred 2) + (apply duration.inverse day#pred 3) + (apply duration.inverse day#pred 4) + (apply duration.inverse day#pred 5) + (apply duration.inverse day#pred 6) + (apply duration.inverse day#pred 7))))) + (_.coverage [/.now] + (case (try (io.run! /.now)) + {try.#Success _} + true + + {try.#Failure _} + false)) ))) diff --git a/stdlib/source/test/lux/time/month.lux b/stdlib/source/test/lux/time/month.lux index cc43a57a8..8bc9438ce 100644 --- a/stdlib/source/test/lux/time/month.lux +++ b/stdlib/source/test/lux/time/month.lux @@ -56,45 +56,45 @@ (n.> (/.number {/.#December}))) random.nat)] (all _.and - (_.cover [/.number /.by_number] - (|> expected - /.number - /.by_number - (try#each (# /.equivalence = expected)) - (try.else false))) - (_.cover [/.invalid_month] - (case (/.by_number invalid) - {try.#Failure error} - (exception.match? /.invalid_month error) - - {try.#Success _} - false)) - (_.cover [/.year] - (let [all (list.size /.year) - uniques (set.size (set.of_list /.hash /.year))] - (and (n.= (/.number {/.#December}) - all) - (n.= all - uniques)))) - (_.cover [/.days] - (let [expected (.nat (duration.ticks duration.day duration.normal_year))] - (|> /.year - (list#each /.days) - (list#mix n.+ 0) - (n.= expected)))) - (_.cover [/.leap_year_days] - (let [expected (.nat (duration.ticks duration.day duration.leap_year))] - (|> /.year - (list#each /.leap_year_days) - (list#mix n.+ 0) - (n.= expected)))) + (_.coverage [/.number /.by_number] + (|> expected + /.number + /.by_number + (try#each (# /.equivalence = expected)) + (try.else false))) + (_.coverage [/.invalid_month] + (case (/.by_number invalid) + {try.#Failure error} + (exception.match? /.invalid_month error) + + {try.#Success _} + false)) + (_.coverage [/.year] + (let [all (list.size /.year) + uniques (set.size (set.of_list /.hash /.year))] + (and (n.= (/.number {/.#December}) + all) + (n.= all + uniques)))) + (_.coverage [/.days] + (let [expected (.nat (duration.ticks duration.day duration.normal_year))] + (|> /.year + (list#each /.days) + (list#mix n.+ 0) + (n.= expected)))) + (_.coverage [/.leap_year_days] + (let [expected (.nat (duration.ticks duration.day duration.leap_year))] + (|> /.year + (list#each /.leap_year_days) + (list#mix n.+ 0) + (n.= expected)))) (do random.monad [not_a_month (random.upper_case 1)] - (_.cover [/.not_a_month_of_the_year] - (case (# /.codec decoded not_a_month) - {try.#Failure error} - (exception.match? /.not_a_month_of_the_year error) - - {try.#Success _} - false))) + (_.coverage [/.not_a_month_of_the_year] + (case (# /.codec decoded not_a_month) + {try.#Failure error} + (exception.match? /.not_a_month_of_the_year error) + + {try.#Success _} + false))) ))))) diff --git a/stdlib/source/test/lux/time/year.lux b/stdlib/source/test/lux/time/year.lux index e7c316e65..3c47d811f 100644 --- a/stdlib/source/test/lux/time/year.lux +++ b/stdlib/source/test/lux/time/year.lux @@ -46,52 +46,52 @@ (do random.monad [expected random.int] (all _.and - (_.cover [/.year] - (bit#= (i.= +0 expected) - (case (/.year expected) - {try.#Success _} - false - - {try.#Failure _} - true))) - (_.cover [/.value] + (_.coverage [/.year] + (bit#= (i.= +0 expected) (case (/.year expected) - {try.#Success year} - (i.= expected (/.value year)) + {try.#Success _} + false {try.#Failure _} - (i.= +0 expected))) + true))) + (_.coverage [/.value] + (case (/.year expected) + {try.#Success year} + (i.= expected (/.value year)) + + {try.#Failure _} + (i.= +0 expected))) )) - (_.cover [/.there_is_no_year_0] - (case (/.year +0) - {try.#Success _} - false + (_.coverage [/.there_is_no_year_0] + (case (/.year +0) + {try.#Success _} + false - {try.#Failure error} - (exception.match? /.there_is_no_year_0 error))) - (_.cover [/.days] - (n.= (.nat (//duration.ticks //duration.day //duration.normal_year)) - /.days)) - (_.cover [/.epoch] - (# /.equivalence = - (//date.year (//instant.date //instant.epoch)) - /.epoch)) + {try.#Failure error} + (exception.match? /.there_is_no_year_0 error))) + (_.coverage [/.days] + (n.= (.nat (//duration.ticks //duration.day //duration.normal_year)) + /.days)) + (_.coverage [/.epoch] + (# /.equivalence = + (//date.year (//instant.date //instant.epoch)) + /.epoch)) (_.for [/.Period] - (_.cover [/.leap /.century /.era] - (n.= /.leap (n./ /.century /.era)))) + (_.coverage [/.leap /.century /.era] + (n.= /.leap (n./ /.century /.era)))) (let [leap (try.trusted (/.year (.int /.leap))) century (try.trusted (/.year (.int /.century))) era (try.trusted (/.year (.int /.era)))] (all _.and - (_.cover [/.leap?] - (and (/.leap? leap) - (not (/.leap? century)) - (/.leap? era))) - (_.cover [/.leaps] - (and (i.= +1 (/.leaps leap)) - (i.= (.int (n./ /.leap /.century)) - (/.leaps century)) - (i.= (++ (i.* +4 (-- (/.leaps century)))) - (/.leaps era)))) + (_.coverage [/.leap?] + (and (/.leap? leap) + (not (/.leap? century)) + (/.leap? era))) + (_.coverage [/.leaps] + (and (i.= +1 (/.leaps leap)) + (i.= (.int (n./ /.leap /.century)) + (/.leaps century)) + (i.= (++ (i.* +4 (-- (/.leaps century)))) + (/.leaps era)))) )) ))) diff --git a/stdlib/source/test/lux/tool/compiler/arity.lux b/stdlib/source/test/lux/tool/compiler/arity.lux index cd39f3380..ad89541f5 100644 --- a/stdlib/source/test/lux/tool/compiler/arity.lux +++ b/stdlib/source/test/lux/tool/compiler/arity.lux @@ -20,10 +20,10 @@ (do [! random.monad] [arity (# ! each (n.% 3) random.nat)] (all _.and - (_.cover [/.nullary?] - (bit#= (n.= 0 arity) (/.nullary? arity))) - (_.cover [/.unary?] - (bit#= (n.= 1 arity) (/.unary? arity))) - (_.cover [/.multiary?] - (bit#= (n.>= 2 arity) (/.multiary? arity))) + (_.coverage [/.nullary?] + (bit#= (n.= 0 arity) (/.nullary? arity))) + (_.coverage [/.unary?] + (bit#= (n.= 1 arity) (/.unary? arity))) + (_.coverage [/.multiary?] + (bit#= (n.>= 2 arity) (/.multiary? arity))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux index e4f33919f..f620d1a10 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis.lux @@ -109,21 +109,21 @@ frac random.frac text (random.lower_case 1)] (`` (all _.and - (_.cover [/.unit] - (case (/.unit) - (pattern (/.unit)) - true + (_.coverage [/.unit] + (case (/.unit) + (pattern (/.unit)) + true + + _ + false)) + (~~ (template [<tag> <expected>] + [(_.coverage [<tag>] + (case (<tag> <expected>) + (pattern (<tag> actual)) + (same? <expected> actual) _ - false)) - (~~ (template [<tag> <expected>] - [(_.cover [<tag>] - (case (<tag> <expected>) - (pattern (<tag> actual)) - (same? <expected> actual) - - _ - false))] + false))] [/.bit bit] [/.nat nat] @@ -141,26 +141,26 @@ expected_lefts random.nat expected_right? random.bit] (all _.and - (_.cover [/.variant] - (let [expected (if expected_right? - expected_right - expected_left)] - (case (/.variant [expected_lefts expected_right? expected]) - (pattern (/.variant [actual_lefts actual_right? actual])) - (and (same? expected_lefts actual_lefts) - (same? expected_right? actual_right?) - (same? expected actual)) - - _ - false))) - (_.cover [/.tuple] - (case (/.tuple (list expected_left expected_right)) - (pattern (/.tuple (list actual_left actual_right))) - (and (same? expected_left actual_left) - (same? expected_right actual_right)) - - _ - false)) + (_.coverage [/.variant] + (let [expected (if expected_right? + expected_right + expected_left)] + (case (/.variant [expected_lefts expected_right? expected]) + (pattern (/.variant [actual_lefts actual_right? actual])) + (and (same? expected_lefts actual_lefts) + (same? expected_right? actual_right?) + (same? expected actual)) + + _ + false))) + (_.coverage [/.tuple] + (case (/.tuple (list expected_left expected_right)) + (pattern (/.tuple (list actual_left actual_right))) + (and (same? expected_left actual_left) + (same? expected_right actual_right)) + + _ + false)) ))) (def: test|reference @@ -171,13 +171,13 @@ expected_variable /variable.random] (`` (all _.and (~~ (template [<tag> <expected>] - [(_.cover [<tag>] - (case (<tag> <expected>) - (pattern (<tag> actual)) - (same? <expected> actual) + [(_.coverage [<tag>] + (case (<tag> <expected>) + (pattern (<tag> actual)) + (same? <expected> actual) - _ - false))] + _ + false))] [/.local expected_register] [/.foreign expected_register] @@ -202,24 +202,24 @@ expected_parameter/0 (..random 2) expected_parameter/1 (..random 2)] (all _.and - (_.cover [/.reified /.reification] - (case (|> [expected_abstraction (list expected_parameter/0 expected_parameter/1)] - /.reified - /.reification) - (pattern [actual_abstraction (list actual_parameter/0 actual_parameter/1)]) - (and (same? expected_abstraction actual_abstraction) - (same? expected_parameter/0 actual_parameter/0) - (same? expected_parameter/1 actual_parameter/1)) - - _ - false)) - (_.cover [/.no_op] - (case (/.no_op expected_parameter/0) - (pattern (/.no_op actual)) - (same? expected_parameter/0 actual) - - _ - false)) + (_.coverage [/.reified /.reification] + (case (|> [expected_abstraction (list expected_parameter/0 expected_parameter/1)] + /.reified + /.reification) + (pattern [actual_abstraction (list actual_parameter/0 actual_parameter/1)]) + (and (same? expected_abstraction actual_abstraction) + (same? expected_parameter/0 actual_parameter/0) + (same? expected_parameter/1 actual_parameter/1)) + + _ + false)) + (_.coverage [/.no_op] + (case (/.no_op expected_parameter/0) + (pattern (/.no_op actual)) + (same? expected_parameter/0 actual) + + _ + false)) ))) (def: test|case @@ -228,14 +228,14 @@ [expected_input (..random 2) expected_match (random_match 2 (..random 2))] (all _.and - (_.cover [/.case] - (case (/.case [expected_input expected_match]) - (pattern (/.case [actual_input actual_match])) - (and (same? expected_input actual_input) - (same? expected_match actual_match)) - - _ - false)) + (_.coverage [/.case] + (case (/.case [expected_input expected_match]) + (pattern (/.case [actual_input actual_match])) + (and (same? expected_input actual_input) + (same? expected_match actual_match)) + + _ + false)) ))) (with_expansions [<id> (static.random_nat) @@ -258,71 +258,71 @@ state/1 (has .#location location/1 (/.state (/.info version/1 host/1 configuration)))]] (all _.and - (_.cover [/.set_state] - (|> (do phase.monad - [pre (extension.read function.identity) - _ (/.set_state state/1) - post (extension.read function.identity)] - (in (and (same? state/0 pre) - (same? state/1 post)))) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (try.else false))) - (_.cover [/.failure] - (|> (/.failure expected_error) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (pipe.case - {try.#Failure actual_error} - (and (text.contains? expected_error actual_error) - (text.contains? (location.format location/0) actual_error)) - - _ - false))) - (_.cover [/.except] - (|> (/.except <exception> []) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (pipe.case - {try.#Failure actual_error} - (and (text.contains? (exception.error <exception> []) actual_error) - (text.contains? (location.format location/0) actual_error)) - - _ - false))) - (_.cover [/.with_exception] - (|> (/.failure expected_error) - (/.with_exception <exception> []) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (pipe.case - {try.#Failure actual_error} - (and (text.contains? expected_error actual_error) - (text.contains? (exception.error <exception> []) actual_error) - (text.contains? (location.format location/0) actual_error)) - - _ - false))) - (_.cover [/.assertion] - (and (|> (/.assertion <exception> [] false) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (pipe.case - {try.#Failure actual_error} - (and (text.contains? (exception.error <exception> []) actual_error) - (text.contains? (location.format location/0) actual_error)) - - _ - false)) - (|> (/.assertion <exception> [] true) - (phase.result [extension.#bundle extension.empty - extension.#state state/0]) - (pipe.case - {try.#Success _} - true - - _ - false)))) + (_.coverage [/.set_state] + (|> (do phase.monad + [pre (extension.read function.identity) + _ (/.set_state state/1) + post (extension.read function.identity)] + (in (and (same? state/0 pre) + (same? state/1 post)))) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (try.else false))) + (_.coverage [/.failure] + (|> (/.failure expected_error) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (pipe.case + {try.#Failure actual_error} + (and (text.contains? expected_error actual_error) + (text.contains? (location.format location/0) actual_error)) + + _ + false))) + (_.coverage [/.except] + (|> (/.except <exception> []) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (pipe.case + {try.#Failure actual_error} + (and (text.contains? (exception.error <exception> []) actual_error) + (text.contains? (location.format location/0) actual_error)) + + _ + false))) + (_.coverage [/.with_exception] + (|> (/.failure expected_error) + (/.with_exception <exception> []) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (pipe.case + {try.#Failure actual_error} + (and (text.contains? expected_error actual_error) + (text.contains? (exception.error <exception> []) actual_error) + (text.contains? (location.format location/0) actual_error)) + + _ + false))) + (_.coverage [/.assertion] + (and (|> (/.assertion <exception> [] false) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (pipe.case + {try.#Failure actual_error} + (and (text.contains? (exception.error <exception> []) actual_error) + (text.contains? (location.format location/0) actual_error)) + + _ + false)) + (|> (/.assertion <exception> [] true) + (phase.result [extension.#bundle extension.empty + extension.#state state/0]) + (pipe.case + {try.#Success _} + true + + _ + false)))) )))) (def: test|state @@ -343,116 +343,116 @@ .let [state (has .#location location (/.state (/.info version host configuration)))]] (all _.and - (_.cover [/.info] - (let [it (/.info version host configuration)] - (and (text#= (version.format version) - (the .#version it)) - (same? host - (the .#target it)) - (..tagged? .#Build (the .#mode it)) - (same? configuration (the .#configuration it))))) - (_.cover [/.state] - (let [info (/.info version host configuration) - it (/.state info)] - (and (same? info - (the .#info it)) - (same? location.dummy - (the .#location it)) - (..tagged? .#None (the .#current_module it)) - (..tagged? .#None (the .#expected it)) - (list.empty? (the .#modules it)) - (list.empty? (the .#scopes it)) - (list.empty? (the [.#type_context .#var_bindings] it)) - (case (the .#source it) - [location 0 ""] - (same? location.dummy location) - - _ - false)))) - (_.cover [/.set_current_module] - (|> (do phase.monad - [_ (/.set_current_module expected_module)] - (extension.read (|>> (the .#current_module) (maybe.else "")))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (pipe.case - {try.#Success actual} - (same? expected_module actual) + (_.coverage [/.info] + (let [it (/.info version host configuration)] + (and (text#= (version.format version) + (the .#version it)) + (same? host + (the .#target it)) + (..tagged? .#Build (the .#mode it)) + (same? configuration (the .#configuration it))))) + (_.coverage [/.state] + (let [info (/.info version host configuration) + it (/.state info)] + (and (same? info + (the .#info it)) + (same? location.dummy + (the .#location it)) + (..tagged? .#None (the .#current_module it)) + (..tagged? .#None (the .#expected it)) + (list.empty? (the .#modules it)) + (list.empty? (the .#scopes it)) + (list.empty? (the [.#type_context .#var_bindings] it)) + (case (the .#source it) + [location 0 ""] + (same? location.dummy location) - _ - false))) - (_.cover [/.with_current_module] - (let [current_module (extension.read (|>> (the .#current_module) (maybe.else "")))] - (|> (do phase.monad - [_ (/.set_current_module expected_module) - pre current_module - mid (/.with_current_module dummy_module - current_module) - post current_module] - (in (and (same? expected_module pre) - (same? dummy_module mid) - (same? expected_module post)))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (try.else false)))) - (_.cover [/.location /.set_location] - (let [expected (/.location expected_file)] - (|> (do phase.monad - [_ (/.set_location expected)] - (extension.read (the .#location))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (pipe.case - {try.#Success actual} - (same? expected actual) - - _ - false)))) - (_.cover [/.with_location] - (let [expected (/.location expected_file) - dummy (/.location expected_code) - location (extension.read (the .#location))] - (|> (do phase.monad - [_ (/.set_location expected) - pre location - mid (/.with_location dummy - location) - post location] - (in (and (same? expected pre) - (same? dummy mid) - (same? expected post)))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (try.else false)))) - (_.cover [/.source /.set_source_code] - (let [expected (/.source expected_file expected_code)] - (|> (do phase.monad - [_ (/.set_source_code expected)] - (extension.read (the .#source))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (pipe.case - {try.#Success actual} - (same? expected actual) - - _ - false)))) - (_.cover [/.with_source_code] - (let [expected (/.source expected_file expected_code) - dummy (/.source expected_code expected_file) - source (extension.read (the .#source))] - (|> (do phase.monad - [_ (/.set_source_code expected) - pre source - mid (/.with_source_code dummy - source) - post source] - (in (and (same? expected pre) - (same? dummy mid) - (same? expected post)))) - (phase.result [extension.#bundle extension.empty - extension.#state state]) - (try.else false)))) + _ + false)))) + (_.coverage [/.set_current_module] + (|> (do phase.monad + [_ (/.set_current_module expected_module)] + (extension.read (|>> (the .#current_module) (maybe.else "")))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (pipe.case + {try.#Success actual} + (same? expected_module actual) + + _ + false))) + (_.coverage [/.with_current_module] + (let [current_module (extension.read (|>> (the .#current_module) (maybe.else "")))] + (|> (do phase.monad + [_ (/.set_current_module expected_module) + pre current_module + mid (/.with_current_module dummy_module + current_module) + post current_module] + (in (and (same? expected_module pre) + (same? dummy_module mid) + (same? expected_module post)))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (try.else false)))) + (_.coverage [/.location /.set_location] + (let [expected (/.location expected_file)] + (|> (do phase.monad + [_ (/.set_location expected)] + (extension.read (the .#location))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (pipe.case + {try.#Success actual} + (same? expected actual) + + _ + false)))) + (_.coverage [/.with_location] + (let [expected (/.location expected_file) + dummy (/.location expected_code) + location (extension.read (the .#location))] + (|> (do phase.monad + [_ (/.set_location expected) + pre location + mid (/.with_location dummy + location) + post location] + (in (and (same? expected pre) + (same? dummy mid) + (same? expected post)))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (try.else false)))) + (_.coverage [/.source /.set_source_code] + (let [expected (/.source expected_file expected_code)] + (|> (do phase.monad + [_ (/.set_source_code expected)] + (extension.read (the .#source))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (pipe.case + {try.#Success actual} + (same? expected actual) + + _ + false)))) + (_.coverage [/.with_source_code] + (let [expected (/.source expected_file expected_code) + dummy (/.source expected_code expected_file) + source (extension.read (the .#source))] + (|> (do phase.monad + [_ (/.set_source_code expected) + pre source + mid (/.with_source_code dummy + source) + post source] + (in (and (same? expected pre) + (same? dummy mid) + (same? expected post)))) + (phase.result [extension.#bundle extension.empty + extension.#state state]) + (try.else false)))) ))) (def: .public test @@ -477,9 +477,9 @@ ..test|phase) (_.for [/.State+] ..test|state) - (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right)))) + (_.coverage [/.format] + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right)))) /complex.test /inference.test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/complex.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/complex.lux index 5d331f85e..2a351ec37 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/complex.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/complex.lux @@ -26,20 +26,20 @@ lefts random.nat right? random.bit] (all _.and - (_.cover [/.tag /.lefts] - (and (|> lefts - (/.tag right?) - (/.lefts right?) - (n.= lefts)) - (|> tag - (/.lefts right?) - (/.tag right?) - (n.= tag)))) - (_.cover [/.choice] - (let [[lefts right?] (/.choice multiplicity tag)] - (if right? - (n.= (-- tag) lefts) - (n.= tag lefts)))) + (_.coverage [/.tag /.lefts] + (and (|> lefts + (/.tag right?) + (/.lefts right?) + (n.= lefts)) + (|> tag + (/.lefts right?) + (/.tag right?) + (n.= tag)))) + (_.coverage [/.choice] + (let [[lefts right?] (/.choice multiplicity tag)] + (if right? + (n.= (-- tag) lefts) + (n.= tag lefts)))) ))) (def: .public (random multiplicity it) @@ -70,7 +70,7 @@ (do random.monad [left random right random] - (_.cover [/.format] - (bit#= (# (/.equivalence n.equivalence) = left right) - (text#= (/.format %.nat left) (/.format %.nat right))))) + (_.coverage [/.format] + (bit#= (# (/.equivalence n.equivalence) = left right) + (text#= (/.format %.nat left) (/.format %.nat right))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux index 3bfe7d2fb..01d4e8481 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -154,12 +154,12 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.exhaustive?] - (bit#= (/#= {/.#Exhaustive} left) - (/.exhaustive? left))) - (_.cover [/.format] - (bit#= (/#= left right) - (text#= (/.format left) (/.format right)))) + (_.coverage [/.exhaustive?] + (bit#= (/#= {/.#Exhaustive} left) + (/.exhaustive? left))) + (_.coverage [/.format] + (bit#= (/#= left right) + (text#= (/.format left) (/.format right)))) )))) (def: test|coverage @@ -168,29 +168,29 @@ (do [! random.monad] [[expected pattern] ..random_pattern] (all _.and - (_.cover [/.coverage] - (|> pattern + (_.coverage [/.coverage] + (|> pattern + /.coverage + (try#each (/#= expected)) + (try.else false))) + (_.coverage [/.invalid_tuple] + (let [invalid? (..failure? /.invalid_tuple)] + (and (|> (list) + {//complex.#Tuple} + {//pattern.#Complex} /.coverage - (try#each (/#= expected)) - (try.else false))) - (_.cover [/.invalid_tuple] - (let [invalid? (..failure? /.invalid_tuple)] - (and (|> (list) - {//complex.#Tuple} - {//pattern.#Complex} - /.coverage - invalid?) - (|> (list pattern) - {//complex.#Tuple} - {//pattern.#Complex} - /.coverage - invalid?) - (|> (list pattern pattern) - {//complex.#Tuple} - {//pattern.#Complex} - /.coverage - invalid? - not)))) + invalid?) + (|> (list pattern) + {//complex.#Tuple} + {//pattern.#Complex} + /.coverage + invalid?) + (|> (list pattern pattern) + {//complex.#Tuple} + {//pattern.#Complex} + /.coverage + invalid? + not)))) )))) (def: random_partial_pattern @@ -213,12 +213,12 @@ [tag/1 expected/1])) expected_minimum (++ (n.max tag/0 tag/1))]] (all _.and - (_.cover [/.minimum] - (and (n.= expected_minimum (/.minimum [{.#None} cases])) - (n.= expected_maximum (/.minimum [{.#Some expected_maximum} cases])))) - (_.cover [/.maximum] - (and (n.= n#top (/.maximum [{.#None} cases])) - (n.= expected_maximum (/.maximum [{.#Some expected_maximum} cases])))) + (_.coverage [/.minimum] + (and (n.= expected_minimum (/.minimum [{.#None} cases])) + (n.= expected_maximum (/.minimum [{.#Some expected_maximum} cases])))) + (_.coverage [/.maximum] + (and (n.= n#top (/.maximum [{.#None} cases])) + (n.= expected_maximum (/.maximum [{.#Some expected_maximum} cases])))) )))) (def: random_value_pattern @@ -257,200 +257,200 @@ tag/0 random_tag tag/1 (random.only (|>> (n.= tag/0) not) random_tag)] (all _.and - (_.cover [/.composite] - (let [composes_simples! - (`` (and (|> (/.composite {/.#Bit bit} {/.#Bit (not bit)}) - (try#each (/#= {/.#Exhaustive})) + (_.coverage [/.composite] + (let [composes_simples! + (`` (and (|> (/.composite {/.#Bit bit} {/.#Bit (not bit)}) + (try#each (/#= {/.#Exhaustive})) + (try.else false)) + (|> {/.#Bit bit} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false)) + (~~ (template [<tag> <hash> <value> <next>] + [(|> (/.composite {<tag> (set.of_list <hash> (list <value>))} + {<tag> (set.of_list <hash> (list (|> <value> <next>)))}) + (try#each (/#= {<tag> (set.of_list <hash> (list <value> (|> <value> <next>)))})) (try.else false)) - (|> {/.#Bit bit} + (|> {<tag> (set.of_list <hash> (list <value>))} (/.composite {/.#Exhaustive}) (try#each (/#= {/.#Exhaustive})) - (try.else false)) - (~~ (template [<tag> <hash> <value> <next>] - [(|> (/.composite {<tag> (set.of_list <hash> (list <value>))} - {<tag> (set.of_list <hash> (list (|> <value> <next>)))}) - (try#each (/#= {<tag> (set.of_list <hash> (list <value> (|> <value> <next>)))})) - (try.else false)) - (|> {<tag> (set.of_list <hash> (list <value>))} - (/.composite {/.#Exhaustive}) - (try#each (/#= {/.#Exhaustive})) - (try.else false))] - - [/.#Nat n.hash nat ++] - [/.#Int i.hash int ++] - [/.#Rev r.hash rev ++] - [/.#Frac f.hash frac (f.+ frac)] - [/.#Text text.hash text (%.format text)] - )))) + (try.else false))] - composes_variants! - (let [composes_different_variants! - (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) - (function (_ left right both) - (|> (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant right (dictionary.of_list n.hash (list [tag/1 expected/1]))}) - (try#each (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected/0] - [tag/1 expected/1]))})) - (try.else false))))] - (and (composes? {.#None} {.#None} {.#None}) - (composes? {.#Some arity} {.#None} {.#Some arity}) - (composes? {.#None} {.#Some arity} {.#Some arity}) - (composes? {.#Some arity} {.#Some arity} {.#Some arity}))) + [/.#Nat n.hash nat ++] + [/.#Int i.hash int ++] + [/.#Rev r.hash rev ++] + [/.#Frac f.hash frac (f.+ frac)] + [/.#Text text.hash text (%.format text)] + )))) - composes_same_variants! - (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) - (function (_ left right both) - (|> (do try.monad - [variant (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant right (dictionary.of_list n.hash (list [tag/0 expected/1]))}) - expected (/.composite expected/0 expected/1)] - (in (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected]))} - variant))) - (try.else false))))] - (and (composes? {.#None} {.#None} {.#None}) - (composes? {.#Some arity} {.#None} {.#Some arity}) - (composes? {.#None} {.#Some arity} {.#Some arity}) - (composes? {.#Some arity} {.#Some arity} {.#Some arity})))] - (and composes_different_variants! - composes_same_variants! - (and (|> {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - (/.composite {/.#Exhaustive}) - (try#each (/#= {/.#Exhaustive})) - (try.else false)) - (|> {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - (/.composite {/.#Exhaustive}) - (try#each (/#= {/.#Exhaustive})) - (try.else false))))) + composes_variants! + (let [composes_different_variants! + (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/1 expected/1]))}) + (try#each (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1]))})) + (try.else false))))] + (and (composes? {.#None} {.#None} {.#None}) + (composes? {.#Some arity} {.#None} {.#Some arity}) + (composes? {.#None} {.#Some arity} {.#Some arity}) + (composes? {.#Some arity} {.#Some arity} {.#Some arity}))) - composes_sequences! - (and (|> (/.composite {/.#Seq expected/0 expected/1} - {/.#Seq expected/1 expected/0}) - (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} - {/.#Seq expected/1 expected/0}})) - (try.else false)) - (|> (do try.monad - [seq (/.composite {/.#Seq expected/0 expected/0} - {/.#Seq expected/0 expected/1}) - expected (/.composite expected/0 expected/1)] - (in (/#= (if (/.exhaustive? expected) - expected/0 - {/.#Seq expected/0 expected}) - seq))) - (try.else false)) - (|> (do try.monad - [seq (/.composite {/.#Seq expected/0 expected/0} - {/.#Seq expected/1 expected/0}) - expected (/.composite expected/0 expected/1)] - (in (/#= {/.#Seq expected expected/0} - seq))) - (try.else false)) - (|> (/.composite {/.#Seq expected/0 expected/1} - expected/1) - (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} - expected/1})) + composes_same_variants! + (let [composes? (is (-> (Maybe Nat) (Maybe Nat) (Maybe Nat) Bit) + (function (_ left right both) + (|> (do try.monad + [variant (/.composite {/.#Variant left (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant right (dictionary.of_list n.hash (list [tag/0 expected/1]))}) + expected (/.composite expected/0 expected/1)] + (in (/#= {/.#Variant both (dictionary.of_list n.hash (list [tag/0 expected]))} + variant))) + (try.else false))))] + (and (composes? {.#None} {.#None} {.#None}) + (composes? {.#Some arity} {.#None} {.#Some arity}) + (composes? {.#None} {.#Some arity} {.#Some arity}) + (composes? {.#Some arity} {.#Some arity} {.#Some arity})))] + (and composes_different_variants! + composes_same_variants! + (and (|> {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) (try.else false)) - (|> (/.composite expected/1 - {/.#Seq expected/0 expected/1}) - (try#each (/#= {/.#Alt expected/1 - {/.#Seq expected/0 expected/1}})) - (try.else false)) - (|> (/.composite expected/0 + (|> {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + (/.composite {/.#Exhaustive}) + (try#each (/#= {/.#Exhaustive})) + (try.else false))))) + + composes_sequences! + (and (|> (/.composite {/.#Seq expected/0 expected/1} + {/.#Seq expected/1 expected/0}) + (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} + {/.#Seq expected/1 expected/0}})) + (try.else false)) + (|> (do try.monad + [seq (/.composite {/.#Seq expected/0 expected/0} {/.#Seq expected/0 expected/1}) - (try#each (/#= expected/0)) - (try.else false))) + expected (/.composite expected/0 expected/1)] + (in (/#= (if (/.exhaustive? expected) + expected/0 + {/.#Seq expected/0 expected}) + seq))) + (try.else false)) + (|> (do try.monad + [seq (/.composite {/.#Seq expected/0 expected/0} + {/.#Seq expected/1 expected/0}) + expected (/.composite expected/0 expected/1)] + (in (/#= {/.#Seq expected expected/0} + seq))) + (try.else false)) + (|> (/.composite {/.#Seq expected/0 expected/1} + expected/1) + (try#each (/#= {/.#Alt {/.#Seq expected/0 expected/1} + expected/1})) + (try.else false)) + (|> (/.composite expected/1 + {/.#Seq expected/0 expected/1}) + (try#each (/#= {/.#Alt expected/1 + {/.#Seq expected/0 expected/1}})) + (try.else false)) + (|> (/.composite expected/0 + {/.#Seq expected/0 expected/1}) + (try#each (/#= expected/0)) + (try.else false))) - composes_alts! - (and (|> (do try.monad - [alt (/.composite {/.#Exhaustive} - {/.#Alt expected/0 - expected/1})] - (in (/#= {/.#Exhaustive} - alt))) - (try.else false)) - (|> (do try.monad - [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} - {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/1]))}})] - (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} - alt))) - (try.else false)) - (|> (do try.monad - [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} - {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}})] - (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}] - [tag/1 expected/1]))} - alt))) - (try.else false)) - (|> (do try.monad - [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/2]))} - {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) - expected (/.composite expected/2 expected/0)] - (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected] - [tag/1 expected/1]))} - alt))) - (try.else false)) - (|> (do try.monad - [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/2]))} - {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) - expected (/.composite expected/2 expected/1)] - (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] - [tag/1 expected]))} - alt))) - (try.else false)) - (|> (do try.monad - [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))} - {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - expected/2})] - (in (/#= {/.#Alt expected/2 - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] - [tag/1 expected/1]))}} - alt))) - (try.else false)))] - (and composes_simples! - composes_variants! - composes_sequences! - composes_alts!))) - (_.cover [/.redundancy] - (let [redundant? (..failure? /.redundancy)] - (`` (and (redundant? (/.composite {/.#Exhaustive} {/.#Exhaustive})) - (~~ (template [<it>] - [(redundant? (/.composite <it> <it>)) - (redundant? (/.composite <it> {/.#Exhaustive}))] - - [{/.#Bit bit}] - [{/.#Nat (set.of_list n.hash (list nat))}] - [{/.#Int (set.of_list i.hash (list int))}] - [{/.#Rev (set.of_list r.hash (list rev))}] - [{/.#Frac (set.of_list f.hash (list frac))}] - [{/.#Text (set.of_list text.hash (list text))}] - [{/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] - [{/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] - [{/.#Seq expected/0 expected/1}])) - (redundant? (/.composite {/.#Seq expected/0 expected/1} expected/0)))))) - (_.cover [/.variant_mismatch] - (let [mismatch? (..failure? /.variant_mismatch)] - (and (not (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) - - (mismatch? (/.composite {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) - (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) - - (mismatch? (/.composite {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) - (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) - - (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) - (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [arity expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) - (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [(-- arity) expected/0]))} - {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})))))) + composes_alts! + (and (|> (do try.monad + [alt (/.composite {/.#Exhaustive} + {/.#Alt expected/0 + expected/1})] + (in (/#= {/.#Exhaustive} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/1]))}})] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}})] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 {/.#Exhaustive}] + [tag/1 expected/1]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/2]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) + expected (/.composite expected/2 expected/0)] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected] + [tag/1 expected/1]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/2]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}}) + expected (/.composite expected/2 expected/1)] + (in (/#= {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected]))} + alt))) + (try.else false)) + (|> (do try.monad + [alt (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))} + {/.#Alt {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + expected/2})] + (in (/#= {/.#Alt expected/2 + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0] + [tag/1 expected/1]))}} + alt))) + (try.else false)))] + (and composes_simples! + composes_variants! + composes_sequences! + composes_alts!))) + (_.coverage [/.redundancy] + (let [redundant? (..failure? /.redundancy)] + (`` (and (redundant? (/.composite {/.#Exhaustive} {/.#Exhaustive})) + (~~ (template [<it>] + [(redundant? (/.composite <it> <it>)) + (redundant? (/.composite <it> {/.#Exhaustive}))] + + [{/.#Bit bit}] + [{/.#Nat (set.of_list n.hash (list nat))}] + [{/.#Int (set.of_list i.hash (list int))}] + [{/.#Rev (set.of_list r.hash (list rev))}] + [{/.#Frac (set.of_list f.hash (list frac))}] + [{/.#Text (set.of_list text.hash (list text))}] + [{/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] + [{/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))}] + [{/.#Seq expected/0 expected/1}])) + (redundant? (/.composite {/.#Seq expected/0 expected/1} expected/0)))))) + (_.coverage [/.variant_mismatch] + (let [mismatch? (..failure? /.variant_mismatch)] + (and (not (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) + + (mismatch? (/.composite {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some (++ arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + + (mismatch? (/.composite {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (mismatch? (/.composite {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some (-- arity)} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + + (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [tag/0 expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))}))) + (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [arity expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})) + (not (mismatch? (/.composite {/.#Variant {.#None} (dictionary.of_list n.hash (list [(-- arity) expected/0]))} + {/.#Variant {.#Some arity} (dictionary.of_list n.hash (list [tag/1 expected/1]))})))))) )))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux index cb50147c5..b35d2f857 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/inference.lux @@ -108,107 +108,107 @@ arity (# ! each (n.% 10) random.nat) nats (random.list arity random.nat)] (all _.and - (_.cover [/.general] - (and (|> (/.general archive.empty ..analysis expected (list)) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try#each (|>> product.left (type#= expected))) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type.function (list.repeated arity .Nat) expected) - (list#each code.nat nats)) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try#each (function (_ [actual analysis/*]) - (and (type#= expected actual) - (# (list.equivalence //.equivalence) = - (list#each (|>> //.nat) nats) - analysis/*)))) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type (-> type/0 expected)) - (list term/0)) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try#each (|>> product.left (type#= expected))) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type {.#Named name (-> type/0 expected)}) - (list term/0)) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try#each (|>> product.left (type#= expected))) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type (All (_ a) (-> a a))) - (list term/0)) - (//type.expecting type/0) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase#each (|>> product.left (check.clean (list)) //type.check)) - /phase#conjoint - (/phase.result state) - (try#each (type#= type/0)) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type ((All (_ a) (-> a a)) type/0)) - (list term/0)) - (//type.expecting type/0) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try#each (|>> product.left (type#= type/0))) - (try.else false)) - (|> (do /phase.monad - [[@var varT] (//type.check check.var) - _ (//type.check (check.check varT (type (-> type/0 expected))))] - (/.general archive.empty ..analysis varT (list term/0))) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase#each (|>> product.left (check.clean (list)) //type.check)) - /phase#conjoint - (/phase.result state) - (try#each (type#= expected)) - (try.else false)) - (|> (/.general archive.empty ..analysis - (type (Ex (_ a) (-> a a))) - (list (` ("lux io error" "")))) - //type.inferring - (//module.with 0 (product.left name)) - (/phase#each (|>> product.right product.left (check.clean (list)) //type.check)) - /phase#conjoint - (/phase.result state) - (try#each //type.existential?) - (try.else false)) - )) - (_.cover [/.cannot_infer] - (and (|> (/.general archive.empty ..analysis expected (list term/0)) - (//type.expecting expected) - (/phase.result state) - (..fails? /.cannot_infer)) - (|> (do /phase.monad - [[@var varT] (//type.check check.var)] - (/.general archive.empty ..analysis varT (list term/0))) - (//type.expecting expected) - (/phase.result state) - (..fails? /.cannot_infer)))) - (_.cover [/.cannot_infer_argument] - (|> (/.general archive.empty ..analysis - (type (-> expected expected)) - (list term/0)) - (//type.expecting expected) - (//module.with 0 (product.left name)) - (/phase.result state) - (..fails? /.cannot_infer_argument))) + (_.coverage [/.general] + (and (|> (/.general archive.empty ..analysis expected (list)) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type.function (list.repeated arity .Nat) expected) + (list#each code.nat nats)) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try#each (function (_ [actual analysis/*]) + (and (type#= expected actual) + (# (list.equivalence //.equivalence) = + (list#each (|>> //.nat) nats) + analysis/*)))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type (-> type/0 expected)) + (list term/0)) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type {.#Named name (-> type/0 expected)}) + (list term/0)) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type (All (_ a) (-> a a))) + (list term/0)) + (//type.expecting type/0) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase#each (|>> product.left (check.clean (list)) //type.check)) + /phase#conjoint + (/phase.result state) + (try#each (type#= type/0)) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type ((All (_ a) (-> a a)) type/0)) + (list term/0)) + (//type.expecting type/0) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try#each (|>> product.left (type#= type/0))) + (try.else false)) + (|> (do /phase.monad + [[@var varT] (//type.check check.var) + _ (//type.check (check.check varT (type (-> type/0 expected))))] + (/.general archive.empty ..analysis varT (list term/0))) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase#each (|>> product.left (check.clean (list)) //type.check)) + /phase#conjoint + (/phase.result state) + (try#each (type#= expected)) + (try.else false)) + (|> (/.general archive.empty ..analysis + (type (Ex (_ a) (-> a a))) + (list (` ("lux io error" "")))) + //type.inferring + (//module.with 0 (product.left name)) + (/phase#each (|>> product.right product.left (check.clean (list)) //type.check)) + /phase#conjoint + (/phase.result state) + (try#each //type.existential?) + (try.else false)) + )) + (_.coverage [/.cannot_infer] + (and (|> (/.general archive.empty ..analysis expected (list term/0)) + (//type.expecting expected) + (/phase.result state) + (..fails? /.cannot_infer)) + (|> (do /phase.monad + [[@var varT] (//type.check check.var)] + (/.general archive.empty ..analysis varT (list term/0))) + (//type.expecting expected) + (/phase.result state) + (..fails? /.cannot_infer)))) + (_.coverage [/.cannot_infer_argument] + (|> (/.general archive.empty ..analysis + (type (-> expected expected)) + (list term/0)) + (//type.expecting expected) + (//module.with 0 (product.left name)) + (/phase.result state) + (..fails? /.cannot_infer_argument))) ))) (def: test|variant @@ -227,97 +227,97 @@ .let [[lefts right?] (//complex.choice arity tag)] arbitrary_right? random.bit] (all _.and - (_.cover [/.variant] - (let [variantT (type.variant (list#each product.left types/*,terms/*)) - [tagT tagC] (|> types/*,terms/* - (list.item tag) - (maybe.else [Any (' [])])) - variant?' (is (-> Type (Maybe Type) Nat Bit Code Bit) - (function (_ variant inferred lefts right? term) - (|> (do /phase.monad - [inferT (/.variant lefts right? variant) - [_ [it _]] (|> (/.general archive.empty ..analysis inferT (list term)) - //type.inferring)] - (case inferred - {.#Some inferred} - (//type.check - (do check.monad - [_ (check.check inferred it) - _ (check.check it inferred)] - (in true))) - - {.#None} - (in true))) - (//module.with 0 (product.left name)) - (/phase#each product.right) - (/phase.result state) - (try.else false)))) - variant? (is (-> Type Nat Bit Code Bit) - (function (_ type lefts right? term) - (variant?' type {.#Some type} lefts right? term))) + (_.coverage [/.variant] + (let [variantT (type.variant (list#each product.left types/*,terms/*)) + [tagT tagC] (|> types/*,terms/* + (list.item tag) + (maybe.else [Any (' [])])) + variant?' (is (-> Type (Maybe Type) Nat Bit Code Bit) + (function (_ variant inferred lefts right? term) + (|> (do /phase.monad + [inferT (/.variant lefts right? variant) + [_ [it _]] (|> (/.general archive.empty ..analysis inferT (list term)) + //type.inferring)] + (case inferred + {.#Some inferred} + (//type.check + (do check.monad + [_ (check.check inferred it) + _ (check.check it inferred)] + (in true))) + + {.#None} + (in true))) + (//module.with 0 (product.left name)) + (/phase#each product.right) + (/phase.result state) + (try.else false)))) + variant? (is (-> Type Nat Bit Code Bit) + (function (_ type lefts right? term) + (variant?' type {.#Some type} lefts right? term))) - can_match_case! - (variant? variantT lefts right? tagC) + can_match_case! + (variant? variantT lefts right? tagC) - names_do_not_matter! - (variant? {.#Named name variantT} lefts right? tagC) + names_do_not_matter! + (variant? {.#Named name variantT} lefts right? tagC) - cases_independent_of_parameters_conform_to_anything! - (variant? (type (Maybe type/0)) 0 #0 (' [])) + cases_independent_of_parameters_conform_to_anything! + (variant? (type (Maybe type/0)) 0 #0 (' [])) - cases_dependent_on_parameters_are_tettered_to_those_parameters! - (and (variant? (type (Maybe type/0)) 0 #1 term/0) - (not (variant? (type (Maybe type/0)) 0 #1 term/1))) + cases_dependent_on_parameters_are_tettered_to_those_parameters! + (and (variant? (type (Maybe type/0)) 0 #1 term/0) + (not (variant? (type (Maybe type/0)) 0 #1 term/1))) - only_bottom_conforms_to_tags_outside_of_range! - (`` (and (~~ (template [<verdict> <term>] - [(bit#= <verdict> (variant? variantT arity arbitrary_right? <term>))] + only_bottom_conforms_to_tags_outside_of_range! + (`` (and (~~ (template [<verdict> <term>] + [(bit#= <verdict> (variant? variantT arity arbitrary_right? <term>))] - [#0 term/0] - [#1 (` ("lux io error" ""))])))) + [#0 term/0] + [#1 (` ("lux io error" ""))])))) - can_handle_universal_quantification! - (and (variant?' (type (All (_ a) (Maybe a))) - {.#Some Maybe} - 0 #0 (' [])) - (variant?' (type (All (_ a) (Maybe a))) - {.#Some (type (Maybe type/0))} - 0 #1 term/0) - (not (variant?' (type (All (_ a) (Maybe a))) - {.#Some Maybe} - 0 #1 term/0))) + can_handle_universal_quantification! + (and (variant?' (type (All (_ a) (Maybe a))) + {.#Some Maybe} + 0 #0 (' [])) + (variant?' (type (All (_ a) (Maybe a))) + {.#Some (type (Maybe type/0))} + 0 #1 term/0) + (not (variant?' (type (All (_ a) (Maybe a))) + {.#Some Maybe} + 0 #1 term/0))) - existential_types_do_not_affect_independent_cases! - (variant?' (type (Ex (_ a) (Maybe a))) - {.#None} - 0 #0 (' [])) + existential_types_do_not_affect_independent_cases! + (variant?' (type (Ex (_ a) (Maybe a))) + {.#None} + 0 #0 (' [])) - existential_types_affect_dependent_cases! - (`` (and (~~ (template [<verdict> <term>] - [(bit#= <verdict> (variant?' (type (Ex (_ a) (Maybe a))) {.#None} 0 #1 <term>))] + existential_types_affect_dependent_cases! + (`` (and (~~ (template [<verdict> <term>] + [(bit#= <verdict> (variant?' (type (Ex (_ a) (Maybe a))) {.#None} 0 #1 <term>))] - [#0 term/0] - [#1 (` ("lux io error" ""))]))))] - (and can_match_case! - names_do_not_matter! + [#0 term/0] + [#1 (` ("lux io error" ""))]))))] + (and can_match_case! + names_do_not_matter! - cases_independent_of_parameters_conform_to_anything! - cases_dependent_on_parameters_are_tettered_to_those_parameters! + cases_independent_of_parameters_conform_to_anything! + cases_dependent_on_parameters_are_tettered_to_those_parameters! - only_bottom_conforms_to_tags_outside_of_range! + only_bottom_conforms_to_tags_outside_of_range! - can_handle_universal_quantification! + can_handle_universal_quantification! - existential_types_do_not_affect_independent_cases! - existential_types_affect_dependent_cases! - ))) - (_.cover [/.not_a_variant] - (let [[tagT tagC] (|> types/*,terms/* - (list.item tag) - (maybe.else [Any (' [])]))] - (|> (/.variant lefts right? tagT) - (/phase.result state) - (..fails? /.not_a_variant)))) + existential_types_do_not_affect_independent_cases! + existential_types_affect_dependent_cases! + ))) + (_.coverage [/.not_a_variant] + (let [[tagT tagC] (|> types/*,terms/* + (list.item tag) + (maybe.else [Any (' [])]))] + (|> (/.variant lefts right? tagT) + (/phase.result state) + (..fails? /.not_a_variant)))) ))) (def: test|record @@ -355,43 +355,43 @@ record (type.tuple (list#each product.left types/*,terms/*)) terms (list#each product.right types/*,terms/*)]] (all _.and - (_.cover [/.record] - (let [can_infer_record! - (record? record {.#None} arity terms) + (_.coverage [/.record] + (let [can_infer_record! + (record? record {.#None} arity terms) - names_do_not_matter! - (record? {.#Named name record} {.#None} arity terms) + names_do_not_matter! + (record? {.#Named name record} {.#None} arity terms) - can_handle_universal_quantification! - (and (record? (All (_ a) (Tuple type/0 a)) - {.#Some (Tuple type/0 type/1)} - 2 (list term/0 term/1)) - (record? (All (_ a) (Tuple a type/0)) - {.#Some (Tuple type/1 type/0)} - 2 (list term/1 term/0))) + can_handle_universal_quantification! + (and (record? (All (_ a) (Tuple type/0 a)) + {.#Some (Tuple type/0 type/1)} + 2 (list term/0 term/1)) + (record? (All (_ a) (Tuple a type/0)) + {.#Some (Tuple type/1 type/0)} + 2 (list term/1 term/0))) - can_handle_existential_quantification! - (and (not (record? (Ex (_ a) (Tuple type/0 a)) - {.#Some (Tuple type/0 type/1)} - 2 (list term/0 term/1))) - (record? (Ex (_ a) (Tuple type/0 a)) - {.#None} - 2 (list term/0 (` ("lux io error" "")))) - (not (record? (Ex (_ a) (Tuple a type/0)) - {.#Some (Tuple type/1 type/0)} - 2 (list term/1 term/0))) - (record? (Ex (_ a) (Tuple a type/0)) - {.#None} - 2 (list (` ("lux io error" "")) term/0)))] - (and can_infer_record! - names_do_not_matter! - can_handle_universal_quantification! - can_handle_existential_quantification! - ))) - (_.cover [/.not_a_record] - (|> (/.record arity type/0) - (/phase.result state) - (..fails? /.not_a_record))) + can_handle_existential_quantification! + (and (not (record? (Ex (_ a) (Tuple type/0 a)) + {.#Some (Tuple type/0 type/1)} + 2 (list term/0 term/1))) + (record? (Ex (_ a) (Tuple type/0 a)) + {.#None} + 2 (list term/0 (` ("lux io error" "")))) + (not (record? (Ex (_ a) (Tuple a type/0)) + {.#Some (Tuple type/1 type/0)} + 2 (list term/1 term/0))) + (record? (Ex (_ a) (Tuple a type/0)) + {.#None} + 2 (list (` ("lux io error" "")) term/0)))] + (and can_infer_record! + names_do_not_matter! + can_handle_universal_quantification! + can_handle_existential_quantification! + ))) + (_.coverage [/.not_a_record] + (|> (/.record arity type/0) + (/phase.result state) + (..fails? /.not_a_record))) ))) (def: .public test @@ -410,14 +410,14 @@ ..test|general ..test|variant ..test|record - (_.cover [/.invalid_type_application] - (and (|> (/.general archive.empty ..analysis (type (type/0 type/1)) (list term/0)) - (/phase.result state) - (..fails? /.invalid_type_application)) - (|> (/.variant lefts right? (type (type/0 type/1))) - (/phase.result state) - (..fails? /.invalid_type_application)) - (|> (/.record lefts (type (type/0 type/1))) - (/phase.result state) - (..fails? /.invalid_type_application)))) + (_.coverage [/.invalid_type_application] + (and (|> (/.general archive.empty ..analysis (type (type/0 type/1)) (list term/0)) + (/phase.result state) + (..fails? /.invalid_type_application)) + (|> (/.variant lefts right? (type (type/0 type/1))) + (/phase.result state) + (..fails? /.invalid_type_application)) + (|> (/.record lefts (type (type/0 type/1))) + (/phase.result state) + (..fails? /.invalid_type_application)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux index 23ba015dd..18fc868ec 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/macro.lux @@ -78,34 +78,34 @@ (list.repeated multiplicity) list#conjoint)]}))]]) (all _.and - (_.cover [/.expansion] - (|> (/.expansion ..expander name multiple (list mono)) - (meta.result lux) - (try#each (# (list.equivalence code.equivalence) = - (list.repeated multiplicity mono))) - (try.else false))) - (_.cover [/.expansion_failed] - (|> (/.expansion ..expander name singular (list)) - (meta.result lux) - (pipe.case - {try.#Failure it} - (and (text.contains? expected_error it) - (text.contains? (the exception.#label /.expansion_failed) it)) + (_.coverage [/.expansion] + (|> (/.expansion ..expander name multiple (list mono)) + (meta.result lux) + (try#each (# (list.equivalence code.equivalence) = + (list.repeated multiplicity mono))) + (try.else false))) + (_.coverage [/.expansion_failed] + (|> (/.expansion ..expander name singular (list)) + (meta.result lux) + (pipe.case + {try.#Failure it} + (and (text.contains? expected_error it) + (text.contains? (the exception.#label /.expansion_failed) it)) - _ - false))) - (_.cover [/.single_expansion] - (|> (/.single_expansion ..expander name singular poly) - (meta.result lux) - (try#each (code#= (|> poly (list.item choice) maybe.trusted))) - (try.else false))) - (_.cover [/.must_have_single_expansion] - (|> (/.single_expansion ..expander name multiple (list mono)) - (meta.result lux) - (pipe.case - {try.#Failure it} - (text.contains? (the exception.#label /.must_have_single_expansion) it) + _ + false))) + (_.coverage [/.single_expansion] + (|> (/.single_expansion ..expander name singular poly) + (meta.result lux) + (try#each (code#= (|> poly (list.item choice) maybe.trusted))) + (try.else false))) + (_.coverage [/.must_have_single_expansion] + (|> (/.single_expansion ..expander name multiple (list mono)) + (meta.result lux) + (pipe.case + {try.#Failure it} + (text.contains? (the exception.#label /.must_have_single_expansion) it) - _ - false))) + _ + false))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux index 418f5824b..96d27be9c 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/module.lux @@ -68,67 +68,67 @@ expected_import (random.lower_case 2) expected_alias (random.lower_case 3)] (all _.and - (_.cover [/.empty] - (..new? hash (/.empty hash))) - (_.cover [/.create] - (|> (do /phase.monad - [_ (/.create hash name)] - (/extension.lifted (meta.module name))) - (/phase.result state) - (try#each (..new? hash)) - (try.else false))) - (_.cover [/.exists?] - (|> (do /phase.monad - [pre (/.exists? name) - _ (/.create hash name) - post (/.exists? name)] - (in (and (not pre) post))) - (/phase.result state) - (try.else false))) - (_.cover [/.with] - (|> (do /phase.monad - [[it _] (/.with hash name - (in []))] - (in it)) - (/phase.result state) - (try#each (..new? hash)) - (try.else false))) - (_.cover [/.import] - (`` (and (~~ (template [<expected>] - [(|> (do [! /phase.monad] - [_ (/.create hash expected_import) - [it ?] (/.with hash name - (do ! - [_ (if <expected> - (/.import expected_import) - (in []))] - (/extension.lifted - (meta.imported? expected_import))))] - (in ?)) - (/phase.result state) - (try#each (bit#= <expected>)) - (try.else false))] + (_.coverage [/.empty] + (..new? hash (/.empty hash))) + (_.coverage [/.create] + (|> (do /phase.monad + [_ (/.create hash name)] + (/extension.lifted (meta.module name))) + (/phase.result state) + (try#each (..new? hash)) + (try.else false))) + (_.coverage [/.exists?] + (|> (do /phase.monad + [pre (/.exists? name) + _ (/.create hash name) + post (/.exists? name)] + (in (and (not pre) post))) + (/phase.result state) + (try.else false))) + (_.coverage [/.with] + (|> (do /phase.monad + [[it _] (/.with hash name + (in []))] + (in it)) + (/phase.result state) + (try#each (..new? hash)) + (try.else false))) + (_.coverage [/.import] + (`` (and (~~ (template [<expected>] + [(|> (do [! /phase.monad] + [_ (/.create hash expected_import) + [it ?] (/.with hash name + (do ! + [_ (if <expected> + (/.import expected_import) + (in []))] + (/extension.lifted + (meta.imported? expected_import))))] + (in ?)) + (/phase.result state) + (try#each (bit#= <expected>)) + (try.else false))] - [false] - [true]))))) - (_.cover [/.alias] - (|> (do [! /phase.monad] - [_ (/.create hash expected_import) - [it _] (/.with hash name - (do ! - [_ (/.import expected_import)] - (/.alias expected_alias expected_import)))] - (in it)) - (/phase.result state) - (try#each (|>> (the .#module_aliases) - (pipe.case - (pattern (list [actual_alias actual_import])) - (and (same? expected_alias actual_alias) - (same? expected_import actual_import)) + [false] + [true]))))) + (_.coverage [/.alias] + (|> (do [! /phase.monad] + [_ (/.create hash expected_import) + [it _] (/.with hash name + (do ! + [_ (/.import expected_import)] + (/.alias expected_alias expected_import)))] + (in it)) + (/phase.result state) + (try#each (|>> (the .#module_aliases) + (pipe.case + (pattern (list [actual_alias actual_import])) + (and (same? expected_alias actual_alias) + (same? expected_import actual_import)) - _ - false))) - (try.else false))) + _ + false))) + (try.else false))) ))) (def: test|state @@ -141,59 +141,59 @@ hash random.nat] (`` (all _.and (~~ (template [<set> <query> <not/0> <not/1>] - [(_.cover [<set> <query>] - (|> (do [! /phase.monad] - [[it ?] (/.with hash name - (do ! - [_ (<set> name) - ? (<query> name) - ~0 (<not/0> name) - ~1 (<not/1> name)] - (in (and ? (not ~0) (not ~1)))))] - (in ?)) - (/phase.result state) - (try.else false)))] + [(_.coverage [<set> <query>] + (|> (do [! /phase.monad] + [[it ?] (/.with hash name + (do ! + [_ (<set> name) + ? (<query> name) + ~0 (<not/0> name) + ~1 (<not/1> name)] + (in (and ? (not ~0) (not ~1)))))] + (in ?)) + (/phase.result state) + (try.else false)))] [/.set_active /.active? /.compiled? /.cached?] [/.set_compiled /.compiled? /.cached? /.active?] [/.set_cached /.cached? /.active? /.compiled?] )) - (_.cover [/.can_only_change_state_of_active_module] - (and (~~ (template [<pre> <post>] - [(|> (/.with hash name - (do /phase.monad - [_ (<pre> name)] - (<post> name))) - (/phase.result state) - (pipe.case - {try.#Success _} - false - - {try.#Failure error} - (text.contains? (the exception.#label /.can_only_change_state_of_active_module) error)))] + (_.coverage [/.can_only_change_state_of_active_module] + (and (~~ (template [<pre> <post>] + [(|> (/.with hash name + (do /phase.monad + [_ (<pre> name)] + (<post> name))) + (/phase.result state) + (pipe.case + {try.#Success _} + false + + {try.#Failure error} + (text.contains? (the exception.#label /.can_only_change_state_of_active_module) error)))] - [/.set_compiled /.set_active] - [/.set_compiled /.set_compiled] - [/.set_compiled /.set_cached] - [/.set_cached /.set_active] - [/.set_cached /.set_compiled] - [/.set_cached /.set_cached] - )))) - (_.cover [/.unknown_module] - (and (~~ (template [<set>] - [(|> (<set> name) - (/phase.result state) - (pipe.case - {try.#Success _} - false - - {try.#Failure error} - (text.contains? (the exception.#label /.unknown_module) error)))] + [/.set_compiled /.set_active] + [/.set_compiled /.set_compiled] + [/.set_compiled /.set_cached] + [/.set_cached /.set_active] + [/.set_cached /.set_compiled] + [/.set_cached /.set_cached] + )))) + (_.coverage [/.unknown_module] + (and (~~ (template [<set>] + [(|> (<set> name) + (/phase.result state) + (pipe.case + {try.#Success _} + false + + {try.#Failure error} + (text.contains? (the exception.#label /.unknown_module) error)))] - [/.set_active] - [/.set_compiled] - [/.set_cached] - )))) + [/.set_active] + [/.set_compiled] + [/.set_cached] + )))) )))) (def: test|definition @@ -219,53 +219,53 @@ .let [definition {.#Definition [public? def_type []]} alias {.#Alias [module_name def_name]}]] (all _.and - (_.cover [/.define] - (`` (and (~~ (template [<global>] - [(|> (/.with hash module_name - (/.define def_name <global>)) - (/phase.result state) - (pipe.case - {try.#Success _} true - {try.#Failure _} false))] - - [definition] - [{.#Type [public? def_type {.#Left [labels|head labels|tail]}]}] - [{.#Type [public? def_type {.#Right [labels|head labels|tail]}]}] - [{.#Tag [public? def_type (partial_list labels|head labels|tail) index]}] - [{.#Slot [public? def_type (partial_list labels|head labels|tail) index]}])) - (|> (/.with hash module_name - (do /phase.monad - [_ (/.define def_name definition)] - (/.define alias_name alias))) + (_.coverage [/.define] + (`` (and (~~ (template [<global>] + [(|> (/.with hash module_name + (/.define def_name <global>)) (/phase.result state) (pipe.case {try.#Success _} true - {try.#Failure _} false))))) - (_.cover [/.cannot_define_more_than_once] - (`` (and (~~ (template [<global>] - [(|> (/.with hash module_name - (do /phase.monad - [_ (/.define def_name <global>)] - (/.define def_name <global>))) - (/phase.result state) - (pipe.case - {try.#Success _} false - {try.#Failure _} true))] + {try.#Failure _} false))] - [{.#Definition [public? def_type []]}] - [{.#Type [public? def_type {.#Left [labels|head labels|tail]}]}] - [{.#Type [public? def_type {.#Right [labels|head labels|tail]}]}] - [{.#Tag [public? def_type (partial_list labels|head labels|tail) index]}] - [{.#Slot [public? def_type (partial_list labels|head labels|tail) index]}])) - (|> (/.with hash module_name + [definition] + [{.#Type [public? def_type {.#Left [labels|head labels|tail]}]}] + [{.#Type [public? def_type {.#Right [labels|head labels|tail]}]}] + [{.#Tag [public? def_type (partial_list labels|head labels|tail) index]}] + [{.#Slot [public? def_type (partial_list labels|head labels|tail) index]}])) + (|> (/.with hash module_name + (do /phase.monad + [_ (/.define def_name definition)] + (/.define alias_name alias))) + (/phase.result state) + (pipe.case + {try.#Success _} true + {try.#Failure _} false))))) + (_.coverage [/.cannot_define_more_than_once] + (`` (and (~~ (template [<global>] + [(|> (/.with hash module_name (do /phase.monad - [_ (/.define def_name definition) - _ (/.define alias_name alias)] - (/.define alias_name alias))) + [_ (/.define def_name <global>)] + (/.define def_name <global>))) (/phase.result state) (pipe.case {try.#Success _} false - {try.#Failure _} true))))) + {try.#Failure _} true))] + + [{.#Definition [public? def_type []]}] + [{.#Type [public? def_type {.#Left [labels|head labels|tail]}]}] + [{.#Type [public? def_type {.#Right [labels|head labels|tail]}]}] + [{.#Tag [public? def_type (partial_list labels|head labels|tail) index]}] + [{.#Slot [public? def_type (partial_list labels|head labels|tail) index]}])) + (|> (/.with hash module_name + (do /phase.monad + [_ (/.define def_name definition) + _ (/.define alias_name alias)] + (/.define alias_name alias))) + (/phase.result state) + (pipe.case + {try.#Success _} false + {try.#Failure _} true))))) ))) (def: test|label @@ -288,58 +288,58 @@ (random.set text.hash (-- arity)) (# ! each set.list))] (all _.and - (_.cover [/.declare_labels] - (`` (and (~~ (template [<side> <record?> <query> <on_success>] - [(|> (/.with hash module_name - (do [! /phase.monad] - [.let [it {.#Named [module_name def_name] def_type}] - _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]}) - _ (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it)] - (monad.each ! (|>> [module_name] <query> /extension.lifted) - (partial_list labels|head labels|tail)))) - (/phase.result state) - (pipe.case - {try.#Success _} <on_success> - {try.#Failure _} (not <on_success>)))] + (_.coverage [/.declare_labels] + (`` (and (~~ (template [<side> <record?> <query> <on_success>] + [(|> (/.with hash module_name + (do [! /phase.monad] + [.let [it {.#Named [module_name def_name] def_type}] + _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]}) + _ (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it)] + (monad.each ! (|>> [module_name] <query> /extension.lifted) + (partial_list labels|head labels|tail)))) + (/phase.result state) + (pipe.case + {try.#Success _} <on_success> + {try.#Failure _} (not <on_success>)))] - [.#Left false meta.tag true] - [.#Left false meta.slot false] - [.#Right true meta.slot true] - [.#Right true meta.tag false]))))) - (_.cover [/.cannot_declare_labels_for_anonymous_type] - (`` (and (~~ (template [<side> <record?>] - [(|> (/.with hash module_name - (do [! /phase.monad] - [.let [it def_type] - _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]})] - (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it))) - (/phase.result state) - (pipe.case - {try.#Success _} - false - - {try.#Failure error} - (text.contains? (the exception.#label /.cannot_declare_labels_for_anonymous_type) error)))] + [.#Left false meta.tag true] + [.#Left false meta.slot false] + [.#Right true meta.slot true] + [.#Right true meta.tag false]))))) + (_.coverage [/.cannot_declare_labels_for_anonymous_type] + (`` (and (~~ (template [<side> <record?>] + [(|> (/.with hash module_name + (do [! /phase.monad] + [.let [it def_type] + _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]})] + (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it))) + (/phase.result state) + (pipe.case + {try.#Success _} + false + + {try.#Failure error} + (text.contains? (the exception.#label /.cannot_declare_labels_for_anonymous_type) error)))] - [.#Left false] - [.#Right true]))))) - (_.cover [/.cannot_declare_labels_for_foreign_type] - (`` (and (~~ (template [<side> <record?>] - [(|> (/.with hash module_name - (do [! /phase.monad] - [.let [it {.#Named [foreign_module def_name] def_type}] - _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]})] - (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it))) - (/phase.result state) - (pipe.case - {try.#Success _} - false - - {try.#Failure error} - (text.contains? (the exception.#label /.cannot_declare_labels_for_foreign_type) error)))] + [.#Left false] + [.#Right true]))))) + (_.coverage [/.cannot_declare_labels_for_foreign_type] + (`` (and (~~ (template [<side> <record?>] + [(|> (/.with hash module_name + (do [! /phase.monad] + [.let [it {.#Named [foreign_module def_name] def_type}] + _ (/.define def_name {.#Type [public? it {<side> [labels|head labels|tail]}]})] + (/.declare_labels <record?> (partial_list labels|head labels|tail) public? it))) + (/phase.result state) + (pipe.case + {try.#Success _} + false + + {try.#Failure error} + (text.contains? (the exception.#label /.cannot_declare_labels_for_foreign_type) error)))] - [.#Left false] - [.#Right true]))))) + [.#Left false] + [.#Right true]))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux index 01eb25f11..ac6ce0392 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/pattern.lux @@ -51,24 +51,24 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right)))) - (_.cover [/.unit] - (case (/.unit) - (pattern (/.unit)) - true + (_.coverage [/.format] + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right)))) + (_.coverage [/.unit] + (case (/.unit) + (pattern (/.unit)) + true - _ - false)) + _ + false)) (~~ (template [<tag> <value>] - [(_.cover [<tag>] - (case (<tag> <value>) - (pattern (<tag> actual)) - (same? <value> actual) + [(_.coverage [<tag>] + (case (<tag> <value>) + (pattern (<tag> actual)) + (same? <value> actual) - _ - false))] + _ + false))] [/.bind expected_register] [/.bit expected_bit] @@ -78,35 +78,35 @@ [/.frac expected_frac] [/.text expected_text] )) - (_.cover [/.variant] - (case (/.variant [expected_lefts expected_right? (/.text expected_text)]) - (pattern (/.variant [actual_lefts actual_right? (/.text actual_text)])) - (and (same? expected_lefts actual_lefts) - (same? expected_right? actual_right?) - (same? expected_text actual_text)) + (_.coverage [/.variant] + (case (/.variant [expected_lefts expected_right? (/.text expected_text)]) + (pattern (/.variant [actual_lefts actual_right? (/.text actual_text)])) + (and (same? expected_lefts actual_lefts) + (same? expected_right? actual_right?) + (same? expected_text actual_text)) - _ - false)) - (_.cover [/.tuple] - (case (/.tuple (list (/.bit expected_bit) - (/.nat expected_nat) - (/.int expected_int) - (/.rev expected_rev) - (/.frac expected_frac) - (/.text expected_text))) - (pattern (/.tuple (list (/.bit actual_bit) - (/.nat actual_nat) - (/.int actual_int) - (/.rev actual_rev) - (/.frac actual_frac) - (/.text actual_text)))) - (and (same? expected_bit actual_bit) - (same? expected_nat actual_nat) - (same? expected_int actual_int) - (same? expected_rev actual_rev) - (same? expected_frac actual_frac) - (same? expected_text actual_text)) + _ + false)) + (_.coverage [/.tuple] + (case (/.tuple (list (/.bit expected_bit) + (/.nat expected_nat) + (/.int expected_int) + (/.rev expected_rev) + (/.frac expected_frac) + (/.text expected_text))) + (pattern (/.tuple (list (/.bit actual_bit) + (/.nat actual_nat) + (/.int actual_int) + (/.rev actual_rev) + (/.frac actual_frac) + (/.text actual_text)))) + (and (same? expected_bit actual_bit) + (same? expected_nat actual_nat) + (same? expected_int actual_int) + (same? expected_rev actual_rev) + (same? expected_frac actual_frac) + (same? expected_text actual_text)) - _ - false)) + _ + false)) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux index f6bedb278..9de7bd8ec 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/scope.lux @@ -59,146 +59,146 @@ type/0 ($type.random 0) type/1 ($type.random 0)] (all _.and - (_.cover [/.variable] - (|> (/.variable name/0) - /.with - (//phase.result state) - (try#each (|>> product.right - (pipe.case - {.#None} true - {.#Some _} false))) - (try.else false))) - (_.cover [/.with_local] - (|> (/.with_local [name/0 type/0] - (/.variable name/0)) - /.with + (_.coverage [/.variable] + (|> (/.variable name/0) + /.with + (//phase.result state) + (try#each (|>> product.right + (pipe.case + {.#None} true + {.#Some _} false))) + (try.else false))) + (_.coverage [/.with_local] + (|> (/.with_local [name/0 type/0] + (/.variable name/0)) + /.with + (//phase.result state) + (try#each (|>> product.right + (maybe#each (..local? type/0 0)) + (maybe.else false))) + (try.else false))) + (_.coverage [/.next] + (|> (<| (do [! //phase.monad] + [register/0 /.next]) + (/.with_local [name/0 type/0]) + (do ! + [var/0 (/.variable name/0)]) + (do ! + [register/1 /.next]) + (/.with_local [name/1 type/1]) + (do ! + [var/1 (/.variable name/1)]) + (in (do maybe.monad + [var/0 var/0 + var/1 var/1] + (in [[register/0 var/0] [register/1 var/1]])))) + /.with + (//phase.result state) + (try#each (|>> product.right + (maybe#each (function (_ [[register/0 var/0] [register/1 var/1]]) + (and (..local? type/0 register/0 var/0) + (..local? type/1 register/1 var/1)))) + (maybe.else false))) + (try.else false))) + (_.coverage [/.no_scope] + (and (|> (/.with_local [name/0 type/0] + (//phase#in false)) + (//phase.result state) + (exception.otherwise (exception.match? /.no_scope))) + (|> (do //phase.monad + [_ /.next] + (in false)) + (//phase.result state) + (exception.otherwise (exception.match? /.no_scope))))) + (_.coverage [/.reset] + (and (|> /.next + (/.with_local [name/0 type/0]) + /.with + (//phase.result state) + (try#each (|>> product.right + (n.= 1))) + (try.else false)) + (|> /.next + /.reset + (/.with_local [name/0 type/0]) + /.with + (//phase.result state) + (try#each (|>> product.right + (n.= 0))) + (try.else false)))) + (_.coverage [/.drained] + (|> (function (_ [bundle state]) + {try.#Success [[bundle (has .#scopes (list) state)] + false]}) + (/.with_local [name/0 type/0]) + /.with + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (exception.match? /.drained)))) + (_.coverage [/.with] + (|> (<| /.with + (/.with_local [name/0 type/0]) + (do //phase.monad + [var/0' (/.variable name/0) + [scope/1 var/0''] (/.with (/.variable name/0))] + (<| //phase.lifted + try.of_maybe + (do maybe.monad + [var/0' var/0' + var/0'' var/0''] + (in [var/0' scope/1 var/0'']))))) + (//phase.result state) + (try#each (function (_ [scope/0 var/0' scope/1 var/0'']) + (and (local? type/0 0 var/0') + (n.= 0 (list.size (the [.#locals .#mappings] scope/0))) + (n.= 0 (list.size (the [.#captured .#mappings] scope/0))) + + (foreign? type/0 0 var/0'') + (n.= 0 (list.size (the [.#locals .#mappings] scope/1))) + (n.= 1 (list.size (the [.#captured .#mappings] scope/1)))))) + (try.else false))) + (_.coverage [/.environment] + (let [(open "list#[0]") (list.equivalence //variable.equivalence)] + (and (|> (<| /.with + (/.with_local [name/0 type/0]) + (/.with_local [name/1 type/1]) + (do //phase.monad + [[scope/1 _] (/.with (in []))] + (in (/.environment scope/1)))) (//phase.result state) (try#each (|>> product.right - (maybe#each (..local? type/0 0)) - (maybe.else false))) - (try.else false))) - (_.cover [/.next] - (|> (<| (do [! //phase.monad] + (list#= (list)))) + (try.else false)) + (|> (<| /.with + (do [! //phase.monad] [register/0 /.next]) (/.with_local [name/0 type/0]) - (do ! - [var/0 (/.variable name/0)]) - (do ! - [register/1 /.next]) (/.with_local [name/1 type/1]) (do ! - [var/1 (/.variable name/1)]) - (in (do maybe.monad - [var/0 var/0 - var/1 var/1] - (in [[register/0 var/0] [register/1 var/1]])))) - /.with - (//phase.result state) - (try#each (|>> product.right - (maybe#each (function (_ [[register/0 var/0] [register/1 var/1]]) - (and (..local? type/0 register/0 var/0) - (..local? type/1 register/1 var/1)))) - (maybe.else false))) - (try.else false))) - (_.cover [/.no_scope] - (and (|> (/.with_local [name/0 type/0] - (//phase#in false)) - (//phase.result state) - (exception.otherwise (exception.match? /.no_scope))) - (|> (do //phase.monad - [_ /.next] - (in false)) - (//phase.result state) - (exception.otherwise (exception.match? /.no_scope))))) - (_.cover [/.reset] - (and (|> /.next - (/.with_local [name/0 type/0]) - /.with - (//phase.result state) - (try#each (|>> product.right - (n.= 1))) - (try.else false)) - (|> /.next - /.reset - (/.with_local [name/0 type/0]) - /.with - (//phase.result state) - (try#each (|>> product.right - (n.= 0))) - (try.else false)))) - (_.cover [/.drained] - (|> (function (_ [bundle state]) - {try.#Success [[bundle (has .#scopes (list) state)] - false]}) - (/.with_local [name/0 type/0]) - /.with - (//phase#each product.right) + [[scope/1 _] (/.with (/.variable name/0))] + (in [register/0 (/.environment scope/1)]))) (//phase.result state) - (exception.otherwise (exception.match? /.drained)))) - (_.cover [/.with] + (try#each (function (_ [_ [register/0 environment]]) + (list#= (list {//variable.#Local register/0}) + environment))) + (try.else false)) (|> (<| /.with + (do [! //phase.monad] + [register/0 /.next]) (/.with_local [name/0 type/0]) - (do //phase.monad - [var/0' (/.variable name/0) - [scope/1 var/0''] (/.with (/.variable name/0))] - (<| //phase.lifted - try.of_maybe - (do maybe.monad - [var/0' var/0' - var/0'' var/0''] - (in [var/0' scope/1 var/0'']))))) + (do [! //phase.monad] + [register/1 /.next]) + (/.with_local [name/1 type/1]) + (do [! //phase.monad] + [[scope/1 _] (/.with (do ! + [_ (/.variable name/1) + _ (/.variable name/0)] + (in [])))] + (in [register/0 register/1 (/.environment scope/1)]))) (//phase.result state) - (try#each (function (_ [scope/0 var/0' scope/1 var/0'']) - (and (local? type/0 0 var/0') - (n.= 0 (list.size (the [.#locals .#mappings] scope/0))) - (n.= 0 (list.size (the [.#captured .#mappings] scope/0))) - - (foreign? type/0 0 var/0'') - (n.= 0 (list.size (the [.#locals .#mappings] scope/1))) - (n.= 1 (list.size (the [.#captured .#mappings] scope/1)))))) - (try.else false))) - (_.cover [/.environment] - (let [(open "list#[0]") (list.equivalence //variable.equivalence)] - (and (|> (<| /.with - (/.with_local [name/0 type/0]) - (/.with_local [name/1 type/1]) - (do //phase.monad - [[scope/1 _] (/.with (in []))] - (in (/.environment scope/1)))) - (//phase.result state) - (try#each (|>> product.right - (list#= (list)))) - (try.else false)) - (|> (<| /.with - (do [! //phase.monad] - [register/0 /.next]) - (/.with_local [name/0 type/0]) - (/.with_local [name/1 type/1]) - (do ! - [[scope/1 _] (/.with (/.variable name/0))] - (in [register/0 (/.environment scope/1)]))) - (//phase.result state) - (try#each (function (_ [_ [register/0 environment]]) - (list#= (list {//variable.#Local register/0}) - environment))) - (try.else false)) - (|> (<| /.with - (do [! //phase.monad] - [register/0 /.next]) - (/.with_local [name/0 type/0]) - (do [! //phase.monad] - [register/1 /.next]) - (/.with_local [name/1 type/1]) - (do [! //phase.monad] - [[scope/1 _] (/.with (do ! - [_ (/.variable name/1) - _ (/.variable name/0)] - (in [])))] - (in [register/0 register/1 (/.environment scope/1)]))) - (//phase.result state) - (try#each (function (_ [_ [register/0 register/1 environment]]) - (list#= (list {//variable.#Local register/1} - {//variable.#Local register/0}) - environment))) - (try.else false))))) + (try#each (function (_ [_ [register/0 register/1 environment]]) + (list#= (list {//variable.#Local register/1} + {//variable.#Local register/0}) + environment))) + (try.else false))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/simple.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/simple.lux index 12448028f..ba3ba6096 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/simple.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/simple.lux @@ -39,7 +39,7 @@ (do random.monad [left ..random right ..random] - (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right))))) + (_.coverage [/.format] + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right))))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux index ed8f42dde..b3634b2e8 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/analysis/type.lux @@ -52,84 +52,84 @@ ..primitive) module (random.lower_case 1)] (all _.and - (_.cover [/.expecting /.inference] - (and (|> (/.inference expected) - (/.expecting expected) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} true - {try.#Failure _} false)) - (|> (/.inference dummy) - (/.expecting expected) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} false - {try.#Failure _} true)) - (|> (/.inference expected) - (/.expecting dummy) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} false - {try.#Failure _} true)))) - (_.cover [/.inferring] - (|> (/.inference expected) - /.inferring - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (try#each (|>> product.left (type#= expected))) - (try.else false))) - (_.cover [/.check] - (|> (do /phase.monad - [exT (/.check (do check.monad - [[id type] check.existential] - (in type)))] - (|> (/.inference exT) - (/.expecting exT))) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} true - {try.#Failure _} false))) - (_.cover [/.existential /.existential?] - (|> (do /phase.monad - [:it: /.existential] - (in (/.existential? :it:))) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (try.else false))) - (_.cover [/.fresh] - (and (|> (do /phase.monad - [varT (/.check (do check.monad - [[id type] check.var] - (in type)))] - (|> (/.inference expected) - (/.expecting varT))) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} true - {try.#Failure _} false)) - (|> (do /phase.monad - [varT (/.check (do check.monad - [[id type] check.var] - (in type)))] - (|> (/.inference expected) - (/.expecting varT) - /.fresh)) - (/module.with 0 module) - (/phase#each product.right) - (/phase.result state) - (pipe.case - {try.#Success _} false - {try.#Failure _} true)))) + (_.coverage [/.expecting /.inference] + (and (|> (/.inference expected) + (/.expecting expected) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} true + {try.#Failure _} false)) + (|> (/.inference dummy) + (/.expecting expected) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} false + {try.#Failure _} true)) + (|> (/.inference expected) + (/.expecting dummy) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} false + {try.#Failure _} true)))) + (_.coverage [/.inferring] + (|> (/.inference expected) + /.inferring + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (try#each (|>> product.left (type#= expected))) + (try.else false))) + (_.coverage [/.check] + (|> (do /phase.monad + [exT (/.check (do check.monad + [[id type] check.existential] + (in type)))] + (|> (/.inference exT) + (/.expecting exT))) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} true + {try.#Failure _} false))) + (_.coverage [/.existential /.existential?] + (|> (do /phase.monad + [:it: /.existential] + (in (/.existential? :it:))) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (try.else false))) + (_.coverage [/.fresh] + (and (|> (do /phase.monad + [varT (/.check (do check.monad + [[id type] check.var] + (in type)))] + (|> (/.inference expected) + (/.expecting varT))) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} true + {try.#Failure _} false)) + (|> (do /phase.monad + [varT (/.check (do check.monad + [[id type] check.var] + (in type)))] + (|> (/.inference expected) + (/.expecting varT) + /.fresh)) + (/module.with 0 module) + (/phase#each product.right) + (/phase.result state) + (pipe.case + {try.#Success _} false + {try.#Failure _} true)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux index 9e97fd917..7e0445312 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis.lux @@ -922,41 +922,41 @@ $abstraction/1 (# ! each code.local (random.lower_case 13)) $parameter/1 (# ! each code.local (random.lower_case 14))]) (all _.and - (_.cover [/.phase] - (and (..can_analyse_unit! lux module/0) - (..can_analyse_simple_literal_or_singleton_tuple! lux module/0 [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) - (..can_analyse_sum! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] [@left @right]) - (..can_analyse_variant! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] [@left @right]) - (..can_analyse_tuple! lux module/0 [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) - (..can_analyse_record! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) - (..can_analyse_function! lux module/0 nat/0 [$abstraction/0 $parameter/0 $abstraction/1 $parameter/1]) - (..can_analyse_apply! lux module/0 bit/0 nat/0 [$abstraction/0 $parameter/0 $abstraction/1 $parameter/1]) - (..can_analyse_extension! lux module/0 text/0) - (..can_analyse_pattern_matching! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] $parameter/0) - )) - (_.cover [/.invalid] - (`` (and (~~ (template [<syntax>] - [(|> (do phase.monad - [_ (|> <syntax> - (/.phase ..expander archive.empty) - (//type.expecting .Any))] - (in false)) - //scope.with - (//module.with 0 module/0) - (phase#each (|>> product.right product.right)) - (phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.invalid))))] - - [(` ({#0} (~ (code.bit bit/0))))] - [(` ({#0 [] #1} (~ (code.bit bit/0))))] - [(` {(~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0))})] - [(` {(~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0))})] - [(` {(~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0))})] - [(` {(~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0))})] - [(` {(~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0))})] - [(` {(~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0))})] - )) - ))) + (_.coverage [/.phase] + (and (..can_analyse_unit! lux module/0) + (..can_analyse_simple_literal_or_singleton_tuple! lux module/0 [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) + (..can_analyse_sum! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] [@left @right]) + (..can_analyse_variant! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] [@left @right]) + (..can_analyse_tuple! lux module/0 [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) + (..can_analyse_record! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0]) + (..can_analyse_function! lux module/0 nat/0 [$abstraction/0 $parameter/0 $abstraction/1 $parameter/1]) + (..can_analyse_apply! lux module/0 bit/0 nat/0 [$abstraction/0 $parameter/0 $abstraction/1 $parameter/1]) + (..can_analyse_extension! lux module/0 text/0) + (..can_analyse_pattern_matching! lux module/0 [@any @bit @nat @int @rev @frac @text] [bit/0 nat/0 int/0 rev/0 frac/0 text/0] $parameter/0) + )) + (_.coverage [/.invalid] + (`` (and (~~ (template [<syntax>] + [(|> (do phase.monad + [_ (|> <syntax> + (/.phase ..expander archive.empty) + (//type.expecting .Any))] + (in false)) + //scope.with + (//module.with 0 module/0) + (phase#each (|>> product.right product.right)) + (phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.invalid))))] + + [(` ({#0} (~ (code.bit bit/0))))] + [(` ({#0 [] #1} (~ (code.bit bit/0))))] + [(` {(~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0))})] + [(` {(~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0))})] + [(` {(~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0))})] + [(` {(~ (code.rev rev/0)) (~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0))})] + [(` {(~ (code.frac frac/0)) (~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0))})] + [(` {(~ (code.text text/0)) (~ (code.bit bit/0)) (~ (code.nat nat/0)) (~ (code.int int/0)) (~ (code.rev rev/0)) (~ (code.frac frac/0))})] + )) + ))) /simple.test /complex.test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux index 4eb36a953..a62410d37 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -67,77 +67,77 @@ $binding/1 (# ! each code.local (random.lower_case 4)) $binding/2 (# ! each code.local (random.lower_case 5))] (all _.and - (_.cover [/.tuple] - (let [tuple? (is (-> Type Type Bit) - (function (_ :input: :expected:) - (and (|> :input: - /.tuple - (check.result check.fresh_context) - (try#each (|>> product.right (type#= :expected:))) - (try.else false)) - (|> (do check.monad - [[@var :var:] check.var - _ (check.check :var: :input:)] - (/.tuple :var:)) - (check.result check.fresh_context) - (try#each (|>> product.right (type#= :expected:))) - (try.else false)))))] - (and (tuple? input/0 - (type.anonymous input/0)) - (tuple? (Tuple input/0 input/1 input/2) - (Tuple input/0 input/1 input/2)) - (tuple? {.#Named name/0 (Tuple input/0 input/1 input/2)} - (Tuple input/0 input/1 input/2)) - (tuple? (All (_ a b c) (Tuple input/0 input/1 input/2)) - (Tuple (All (_ a b c) input/0) - (All (_ a b c) input/1) - (All (_ a b c) input/2))) - (tuple? (type ((All (_ a b c) (Tuple a b c)) input/0 input/1 input/2)) - (Tuple input/0 input/1 input/2)) - (|> (do check.monad - [[@var :var:] check.var - _ (check.bind (All (_ a b c) (Tuple a b c)) @var)] - (/.tuple (type (:var: input/0 input/1 input/2)))) - (check.result check.fresh_context) - (try#each (|>> product.right (type#= (Tuple input/0 input/1 input/2)))) - (try.else false)) - (|> (do check.monad - [[@0 :0:] check.existential - [@1 :1:] check.existential - [_ :tuple:] (/.tuple (Ex (_ a b c) (Tuple a input/1 c))) - context check.context - _ (check.with context) - _ (check.check (Tuple :0: input/1 :1:) :tuple:) - _ (check.with context) - _ (check.check :tuple: (Tuple :0: input/1 :1:))] - (in true)) - (check.result check.fresh_context) - (try.else false))))) - (_.cover [/.non_tuple] - (and (|> (do check.monad - [[@var :var:] check.var - _ (/.tuple :var:)] - (in false)) - (check.result check.fresh_context) - (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) - (|> (do check.monad - [[@var :var:] check.var - _ (/.tuple (type (:var: input/0 input/1 input/2)))] - (in false)) - (check.result check.fresh_context) - (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) - (|> (do check.monad - [_ (/.tuple (type (input/0 input/1 input/2)))] - (in false)) - (check.result check.fresh_context) - (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) - (|> (do check.monad - [[@var :var:] check.var - _ (check.bind input/0 @var) - _ (/.tuple (type (:var: input/1 input/2)))] - (in false)) - (check.result check.fresh_context) - (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))))) + (_.coverage [/.tuple] + (let [tuple? (is (-> Type Type Bit) + (function (_ :input: :expected:) + (and (|> :input: + /.tuple + (check.result check.fresh_context) + (try#each (|>> product.right (type#= :expected:))) + (try.else false)) + (|> (do check.monad + [[@var :var:] check.var + _ (check.check :var: :input:)] + (/.tuple :var:)) + (check.result check.fresh_context) + (try#each (|>> product.right (type#= :expected:))) + (try.else false)))))] + (and (tuple? input/0 + (type.anonymous input/0)) + (tuple? (Tuple input/0 input/1 input/2) + (Tuple input/0 input/1 input/2)) + (tuple? {.#Named name/0 (Tuple input/0 input/1 input/2)} + (Tuple input/0 input/1 input/2)) + (tuple? (All (_ a b c) (Tuple input/0 input/1 input/2)) + (Tuple (All (_ a b c) input/0) + (All (_ a b c) input/1) + (All (_ a b c) input/2))) + (tuple? (type ((All (_ a b c) (Tuple a b c)) input/0 input/1 input/2)) + (Tuple input/0 input/1 input/2)) + (|> (do check.monad + [[@var :var:] check.var + _ (check.bind (All (_ a b c) (Tuple a b c)) @var)] + (/.tuple (type (:var: input/0 input/1 input/2)))) + (check.result check.fresh_context) + (try#each (|>> product.right (type#= (Tuple input/0 input/1 input/2)))) + (try.else false)) + (|> (do check.monad + [[@0 :0:] check.existential + [@1 :1:] check.existential + [_ :tuple:] (/.tuple (Ex (_ a b c) (Tuple a input/1 c))) + context check.context + _ (check.with context) + _ (check.check (Tuple :0: input/1 :1:) :tuple:) + _ (check.with context) + _ (check.check :tuple: (Tuple :0: input/1 :1:))] + (in true)) + (check.result check.fresh_context) + (try.else false))))) + (_.coverage [/.non_tuple] + (and (|> (do check.monad + [[@var :var:] check.var + _ (/.tuple :var:)] + (in false)) + (check.result check.fresh_context) + (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) + (|> (do check.monad + [[@var :var:] check.var + _ (/.tuple (type (:var: input/0 input/1 input/2)))] + (in false)) + (check.result check.fresh_context) + (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) + (|> (do check.monad + [_ (/.tuple (type (input/0 input/1 input/2)))] + (in false)) + (check.result check.fresh_context) + (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))) + (|> (do check.monad + [[@var :var:] check.var + _ (check.bind input/0 @var) + _ (/.tuple (type (:var: input/1 input/2)))] + (in false)) + (check.result check.fresh_context) + (exception.otherwise (text.contains? (the exception.#label /.non_tuple)))))) ))) (def: (test|case lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]) @@ -515,38 +515,23 @@ bit/0 random.bit nat/0 random.nat] (all _.and - (_.cover [/.case] - (and (test|case lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]) - (test|redundancy lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/1] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [bit/0]) - (test|variant lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]) - (test|record lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]))) - (_.cover [/.empty_branches] - (|> (do //phase.monad - [analysis (|> (/.case ..analysis (list) archive.empty simple/0) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.empty_branches))))) - (_.cover [/.non_exhaustive] - (let [non_exhaustive? (is (-> (List [Code Code]) Bit) - (function (_ branches) - (|> (do //phase.monad - [analysis (|> (/.case ..analysis branches archive.empty simple/0) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.non_exhaustive))))))] - (and (non_exhaustive? (list [simple/0 body/0])) - (not (non_exhaustive? (list [simple/0 body/0] - [$binding/0 body/0])))))) - (_.cover [/.invalid] - (let [invalid? (is (-> (List [Code Code]) Bit) + (_.coverage [/.case] + (and (test|case lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]) + (test|redundancy lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/1] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [bit/0]) + (test|variant lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]) + (test|record lux [module/0 name/0] [input/0 simple/0] [input/1 simple/1] [input/2 simple/2] [$binding/0 $binding/1 $binding/2] [output/0 body/0] [output/1 body/1] [bit/0 nat/0]))) + (_.coverage [/.empty_branches] + (|> (do //phase.monad + [analysis (|> (/.case ..analysis (list) archive.empty simple/0) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.empty_branches))))) + (_.coverage [/.non_exhaustive] + (let [non_exhaustive? (is (-> (List [Code Code]) Bit) (function (_ branches) (|> (do //phase.monad [analysis (|> (/.case ..analysis branches archive.empty simple/0) @@ -556,80 +541,95 @@ (//module.with 0 module/0) (//phase#each (|>> product.right product.right)) (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.invalid))))))] - (and (invalid? (list [(` ((~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2))) - body/0])) - (invalid? (list [(` {(~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2)}) - body/0])) - (invalid? (list [(` {[] (~ $binding/0) (~ $binding/1) (~ $binding/2)}) - body/0]))))) - (_.cover [/.sum_has_no_case] - (let [tag/0 (%.code $binding/0) - tag/1 (%.code $binding/1) - tag/2 (%.code $binding/2) - - tags/* (list tag/0 tag/1 tag/2) - :variant: {.#Named [module/0 name/0] (type.variant (list input/0 input/1 input/2))} - - tag/0 (code.symbol [module/0 tag/0]) - tag/1 (code.symbol [module/0 tag/1]) - tag/2 (code.symbol [module/0 tag/2])] - (|> (do //phase.monad - [_ (//module.declare_labels false tags/* false :variant:) - analysis (|> (` {(~ tag/0) (~ simple/0)}) - (/.case ..analysis - (list [(` {0 #0 (~ $binding/0)}) body/0] - [(` {1 #0 (~ $binding/1)}) body/0] - [(` {2 #0 (~ $binding/2)}) body/0] - [(` {2 #1 (~ $binding/2)}) body/0]) - archive.empty) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.sum_has_no_case)))))) - (_.cover [/.mismatch] - (let [slot/0 (%.code $binding/0) - slot/1 (%.code $binding/1) - slot/2 (%.code $binding/2) - - slots/* (list slot/0 slot/1 slot/2) - :record: {.#Named [module/0 name/0] (type.tuple (list input/0 input/1 input/2))} - - slot/0 (code.symbol [module/0 slot/0]) - slot/1 (code.symbol [module/0 slot/1]) - slot/2 (code.symbol [module/0 slot/2])] - (and (|> (do //phase.monad - [analysis (|> (` (~ simple/0)) - (/.case ..analysis - (list [(` {0 #0 (~ $binding/0)}) body/0] - [(` {1 #0 (~ $binding/1)}) body/0] - [(` {1 #1 (~ $binding/2)}) body/0]) - archive.empty) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.mismatch)))) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/* false :record:) - analysis (|> (` (~ simple/0)) - (/.case ..analysis - (list [(` [(~ slot/0) (~ $binding/0) - (~ slot/1) (~ $binding/1) - (~ slot/2) (~ $binding/2)]) body/0]) - archive.empty) - (//type.expecting output/0))] - (in false)) - //scope.with - (//module.with 0 module/0) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.mismatch))))))) + (exception.otherwise (text.contains? (the exception.#label /.non_exhaustive))))))] + (and (non_exhaustive? (list [simple/0 body/0])) + (not (non_exhaustive? (list [simple/0 body/0] + [$binding/0 body/0])))))) + (_.coverage [/.invalid] + (let [invalid? (is (-> (List [Code Code]) Bit) + (function (_ branches) + (|> (do //phase.monad + [analysis (|> (/.case ..analysis branches archive.empty simple/0) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.invalid))))))] + (and (invalid? (list [(` ((~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2))) + body/0])) + (invalid? (list [(` {(~ extension/0) (~ $binding/0) (~ $binding/1) (~ $binding/2)}) + body/0])) + (invalid? (list [(` {[] (~ $binding/0) (~ $binding/1) (~ $binding/2)}) + body/0]))))) + (_.coverage [/.sum_has_no_case] + (let [tag/0 (%.code $binding/0) + tag/1 (%.code $binding/1) + tag/2 (%.code $binding/2) + + tags/* (list tag/0 tag/1 tag/2) + :variant: {.#Named [module/0 name/0] (type.variant (list input/0 input/1 input/2))} + + tag/0 (code.symbol [module/0 tag/0]) + tag/1 (code.symbol [module/0 tag/1]) + tag/2 (code.symbol [module/0 tag/2])] + (|> (do //phase.monad + [_ (//module.declare_labels false tags/* false :variant:) + analysis (|> (` {(~ tag/0) (~ simple/0)}) + (/.case ..analysis + (list [(` {0 #0 (~ $binding/0)}) body/0] + [(` {1 #0 (~ $binding/1)}) body/0] + [(` {2 #0 (~ $binding/2)}) body/0] + [(` {2 #1 (~ $binding/2)}) body/0]) + archive.empty) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.sum_has_no_case)))))) + (_.coverage [/.mismatch] + (let [slot/0 (%.code $binding/0) + slot/1 (%.code $binding/1) + slot/2 (%.code $binding/2) + + slots/* (list slot/0 slot/1 slot/2) + :record: {.#Named [module/0 name/0] (type.tuple (list input/0 input/1 input/2))} + + slot/0 (code.symbol [module/0 slot/0]) + slot/1 (code.symbol [module/0 slot/1]) + slot/2 (code.symbol [module/0 slot/2])] + (and (|> (do //phase.monad + [analysis (|> (` (~ simple/0)) + (/.case ..analysis + (list [(` {0 #0 (~ $binding/0)}) body/0] + [(` {1 #0 (~ $binding/1)}) body/0] + [(` {1 #1 (~ $binding/2)}) body/0]) + archive.empty) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.mismatch)))) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/* false :record:) + analysis (|> (` (~ simple/0)) + (/.case ..analysis + (list [(` [(~ slot/0) (~ $binding/0) + (~ slot/1) (~ $binding/1) + (~ slot/2) (~ $binding/2)]) body/0]) + archive.empty) + (//type.expecting output/0))] + (in false)) + //scope.with + (//module.with 0 module/0) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.mismatch))))))) ..test|tuple )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 4bdb21d48..cea405776 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -142,50 +142,50 @@ (list.item tag) (maybe.else [Any (' [])]))]] (all _.and - (_.cover [/.sum] - (let [variantT (type.variant (list#each product.left types/*,terms/*)) - sum? (is (-> Type Nat Bit Code Bit) - (function (_ type lefts right? code) - (|> (do //phase.monad - [analysis (|> (/.sum ..analysis lefts right? archive.empty code) - (//type.expecting type))] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? code analysis)) - - _ - false))) - (//module.with 0 (product.left name)) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] - (and (sum? variantT lefts right? tagC) - (sum? {.#Named name variantT} lefts right? tagC) - (|> (do //phase.monad - [[@var varT] (//type.check check.var) - _ (//type.check (check.check varT variantT)) - analysis (|> (/.sum ..analysis lefts right? archive.empty tagC) - (//type.expecting varT))] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' it])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? tagC it)) - - _ - false))) - (//module.with 0 (product.left name)) - (//phase#each product.right) - (//phase.result state) - (try.else false)) - (and (sum? (type (Maybe tagT)) 0 #0 (` [])) - (sum? (type (Maybe tagT)) 0 #1 tagC)) - (and (sum? (type (All (_ a) (Maybe a))) 0 #0 (` [])) - (not (sum? (type (All (_ a) (Maybe a))) 0 #1 tagC))) - (and (sum? (type (Ex (_ a) (Maybe a))) 0 #0 (` [])) - (sum? (type (Ex (_ a) (Maybe a))) 0 #1 tagC))))) + (_.coverage [/.sum] + (let [variantT (type.variant (list#each product.left types/*,terms/*)) + sum? (is (-> Type Nat Bit Code Bit) + (function (_ type lefts right? code) + (|> (do //phase.monad + [analysis (|> (/.sum ..analysis lefts right? archive.empty code) + (//type.expecting type))] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? code analysis)) + + _ + false))) + (//module.with 0 (product.left name)) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] + (and (sum? variantT lefts right? tagC) + (sum? {.#Named name variantT} lefts right? tagC) + (|> (do //phase.monad + [[@var varT] (//type.check check.var) + _ (//type.check (check.check varT variantT)) + analysis (|> (/.sum ..analysis lefts right? archive.empty tagC) + (//type.expecting varT))] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' it])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? tagC it)) + + _ + false))) + (//module.with 0 (product.left name)) + (//phase#each product.right) + (//phase.result state) + (try.else false)) + (and (sum? (type (Maybe tagT)) 0 #0 (` [])) + (sum? (type (Maybe tagT)) 0 #1 tagC)) + (and (sum? (type (All (_ a) (Maybe a))) 0 #0 (` [])) + (not (sum? (type (All (_ a) (Maybe a))) 0 #1 tagC))) + (and (sum? (type (Ex (_ a) (Maybe a))) 0 #0 (` [])) + (sum? (type (Ex (_ a) (Maybe a))) 0 #1 tagC))))) (_.for [/.cannot_analyse_variant] (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) (function (_ exception analysis) @@ -193,21 +193,21 @@ (and (..failure? /.cannot_analyse_variant it) (..failure? exception it)))))] (all _.and - (_.cover [/.invalid_variant_type] - (and (|> (/.sum ..analysis lefts right? archive.empty tagC) - (//type.expecting tagT) - (failure? /.invalid_variant_type)) - (|> (do //phase.monad - [[@var varT] (//type.check check.var)] - (|> (/.sum ..analysis lefts right? archive.empty tagC) - (//type.expecting (type (varT tagT))))) - (failure? /.invalid_variant_type)))) - (_.cover [/.cannot_infer_sum] - (|> (do //phase.monad - [[@var varT] (//type.check check.var)] - (|> (/.sum ..analysis lefts right? archive.empty tagC) - (//type.expecting varT))) - (failure? /.cannot_infer_sum))) + (_.coverage [/.invalid_variant_type] + (and (|> (/.sum ..analysis lefts right? archive.empty tagC) + (//type.expecting tagT) + (failure? /.invalid_variant_type)) + (|> (do //phase.monad + [[@var varT] (//type.check check.var)] + (|> (/.sum ..analysis lefts right? archive.empty tagC) + (//type.expecting (type (varT tagT))))) + (failure? /.invalid_variant_type)))) + (_.coverage [/.cannot_infer_sum] + (|> (do //phase.monad + [[@var varT] (//type.check check.var)] + (|> (/.sum ..analysis lefts right? archive.empty tagC) + (//type.expecting varT))) + (failure? /.cannot_infer_sum))) ))) ))) @@ -234,51 +234,51 @@ (list.item tag) (maybe.else ""))]] (all _.and - (_.cover [/.variant] - (let [expected_variant? (is (-> Symbol Bit) - (function (_ tag) - (|> (do //phase.monad - [_ (//module.declare_labels false tags false variantT) - analysis (|> (/.variant ..analysis tag archive.empty tagC) - (//type.expecting variantT))] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? tagC analysis)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false)))) - inferred_variant? (is (-> Symbol Bit) - (function (_ tag) - (|> (do //phase.monad - [_ (//module.declare_labels false tags false variantT) - [actualT analysis] (|> (/.variant ..analysis tag archive.empty tagC) - //type.inferring)] - (in (case analysis - (pattern (//analysis.variant [lefts' right?' analysis])) - (and (n.= lefts lefts') - (bit#= right? right?') - (..analysed? tagC analysis) - (type#= variantT actualT)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] - (and (expected_variant? [module tag]) - (expected_variant? ["" tag]) - (inferred_variant? [module tag]) - (inferred_variant? ["" tag]) - - ... TODO: Test what happens when tags are shadowed by local bindings. - ))) + (_.coverage [/.variant] + (let [expected_variant? (is (-> Symbol Bit) + (function (_ tag) + (|> (do //phase.monad + [_ (//module.declare_labels false tags false variantT) + analysis (|> (/.variant ..analysis tag archive.empty tagC) + (//type.expecting variantT))] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? tagC analysis)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false)))) + inferred_variant? (is (-> Symbol Bit) + (function (_ tag) + (|> (do //phase.monad + [_ (//module.declare_labels false tags false variantT) + [actualT analysis] (|> (/.variant ..analysis tag archive.empty tagC) + //type.inferring)] + (in (case analysis + (pattern (//analysis.variant [lefts' right?' analysis])) + (and (n.= lefts lefts') + (bit#= right? right?') + (..analysed? tagC analysis) + (type#= variantT actualT)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] + (and (expected_variant? [module tag]) + (expected_variant? ["" tag]) + (inferred_variant? [module tag]) + (inferred_variant? ["" tag]) + + ... TODO: Test what happens when tags are shadowed by local bindings. + ))) ))) (type: (Triple a) @@ -299,133 +299,133 @@ productT (type.tuple (list#each product.left types/*,terms/*)) expected (list#each product.right types/*,terms/*)]] (all _.and - (_.cover [/.product] - (let [product? (is (-> Type (List Code) Bit) - (function (_ type expected) - (|> (do //phase.monad - [analysis (|> expected - (/.product ..analysis archive.empty) - (//type.expecting type))] - (in (case analysis - (pattern (//analysis.tuple actual)) - (and (n.= (list.size expected) - (list.size actual)) - (list.every? (function (_ [expected actual]) - (..analysed? expected actual)) - (list.zipped_2 expected actual))) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] - (and (product? productT expected) - (product? {.#Named name productT} expected) - (product? (type (Ex (_ a) [a a])) (list term/0 term/0)) - (not (product? (type (All (_ a) [a a])) (list term/0 term/0))) - (product? (type (Triple type/0)) (list term/0 term/0 term/0)) - (|> (do //phase.monad - [[@var varT] (//type.check check.var) - _ (//type.check (check.check varT productT)) - analysis (|> expected - (/.product ..analysis archive.empty) - (//type.expecting varT))] - (in (case analysis - (pattern (//analysis.tuple actual)) - (and (n.= (list.size expected) - (list.size actual)) - (list.every? (function (_ [expected actual]) - (..analysed? expected actual)) - (list.zipped_2 expected actual))) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false)) - (|> (do //phase.monad - [[:inferred: analysis] (|> expected - (/.product ..analysis archive.empty) - //type.inferring)] - (in (case analysis - (pattern (//analysis.tuple actual)) - (and (n.= (list.size expected) - (list.size actual)) - (list.every? (function (_ [expected actual]) - (..analysed? expected actual)) - (list.zipped_2 expected actual)) - (type#= productT :inferred:)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false)) - (|> (do [! //phase.monad] - [[@var varT] (//type.check check.var) - [:inferred: analysis] (//type.inferring - (do ! - [_ (//type.inference (Tuple type/0 type/1 varT))] - (/.product ..analysis archive.empty - (list term/0 term/1 term/2 term/2 term/2)))) - :inferred: (//type.check (check.clean (list @var) :inferred:))] - (in (case analysis - (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) - (and (type#= (Tuple type/0 type/1 type/2 type/2 type/2) - :inferred:) - (..analysed? term/0 analysis/0) - (..analysed? term/1 analysis/1) - (..analysed? term/2 analysis/2) - (..analysed? term/2 analysis/3) - (..analysed? term/2 analysis/4)) - - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false)) - (|> (do [! //phase.monad] - [analysis (|> (list term/0 term/1 (code.tuple (list term/2 term/2 term/2))) - (/.product ..analysis archive.empty) - (//type.expecting (Tuple type/0 type/1 type/2 type/2 type/2)))] - (in (case analysis - (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) - (and (..analysed? term/0 analysis/0) - (..analysed? term/1 analysis/1) - (..analysed? term/2 analysis/2) - (..analysed? term/2 analysis/3) - (..analysed? term/2 analysis/4)) + (_.coverage [/.product] + (let [product? (is (-> Type (List Code) Bit) + (function (_ type expected) + (|> (do //phase.monad + [analysis (|> expected + (/.product ..analysis archive.empty) + (//type.expecting type))] + (in (case analysis + (pattern (//analysis.tuple actual)) + (and (n.= (list.size expected) + (list.size actual)) + (list.every? (function (_ [expected actual]) + (..analysed? expected actual)) + (list.zipped_2 expected actual))) - _ - false))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (try.else false))))) + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] + (and (product? productT expected) + (product? {.#Named name productT} expected) + (product? (type (Ex (_ a) [a a])) (list term/0 term/0)) + (not (product? (type (All (_ a) [a a])) (list term/0 term/0))) + (product? (type (Triple type/0)) (list term/0 term/0 term/0)) + (|> (do //phase.monad + [[@var varT] (//type.check check.var) + _ (//type.check (check.check varT productT)) + analysis (|> expected + (/.product ..analysis archive.empty) + (//type.expecting varT))] + (in (case analysis + (pattern (//analysis.tuple actual)) + (and (n.= (list.size expected) + (list.size actual)) + (list.every? (function (_ [expected actual]) + (..analysed? expected actual)) + (list.zipped_2 expected actual))) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false)) + (|> (do //phase.monad + [[:inferred: analysis] (|> expected + (/.product ..analysis archive.empty) + //type.inferring)] + (in (case analysis + (pattern (//analysis.tuple actual)) + (and (n.= (list.size expected) + (list.size actual)) + (list.every? (function (_ [expected actual]) + (..analysed? expected actual)) + (list.zipped_2 expected actual)) + (type#= productT :inferred:)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false)) + (|> (do [! //phase.monad] + [[@var varT] (//type.check check.var) + [:inferred: analysis] (//type.inferring + (do ! + [_ (//type.inference (Tuple type/0 type/1 varT))] + (/.product ..analysis archive.empty + (list term/0 term/1 term/2 term/2 term/2)))) + :inferred: (//type.check (check.clean (list @var) :inferred:))] + (in (case analysis + (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) + (and (type#= (Tuple type/0 type/1 type/2 type/2 type/2) + :inferred:) + (..analysed? term/0 analysis/0) + (..analysed? term/1 analysis/1) + (..analysed? term/2 analysis/2) + (..analysed? term/2 analysis/3) + (..analysed? term/2 analysis/4)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false)) + (|> (do [! //phase.monad] + [analysis (|> (list term/0 term/1 (code.tuple (list term/2 term/2 term/2))) + (/.product ..analysis archive.empty) + (//type.expecting (Tuple type/0 type/1 type/2 type/2 type/2)))] + (in (case analysis + (pattern (//analysis.tuple (list analysis/0 analysis/1 (//analysis.tuple (list analysis/2 analysis/3 analysis/4))))) + (and (..analysed? term/0 analysis/0) + (..analysed? term/1 analysis/1) + (..analysed? term/2 analysis/2) + (..analysed? term/2 analysis/3) + (..analysed? term/2 analysis/4)) + + _ + false))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (try.else false))))) (_.for [/.cannot_analyse_tuple] - (_.cover [/.invalid_tuple_type] - (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) - (function (_ exception operation) - (let [it (//phase.result state operation)] - (and (..failure? /.cannot_analyse_tuple it) - (..failure? exception it)))))] - (and (|> expected - (/.product ..analysis archive.empty) - (//type.expecting (|> types/*,terms/* - list.head - (maybe#each product.left) - (maybe.else .Any))) - (failure? /.invalid_tuple_type)) - (|> (do //phase.monad - [[@var varT] (//type.check check.var)] - (|> expected - (/.product ..analysis archive.empty) - (//type.expecting (type (varT type/0))))) - (failure? /.invalid_tuple_type)))))) + (_.coverage [/.invalid_tuple_type] + (let [failure? (is (All (_ a) (-> (Exception a) (//analysis.Operation Any) Bit)) + (function (_ exception operation) + (let [it (//phase.result state operation)] + (and (..failure? /.cannot_analyse_tuple it) + (..failure? exception it)))))] + (and (|> expected + (/.product ..analysis archive.empty) + (//type.expecting (|> types/*,terms/* + list.head + (maybe#each product.left) + (maybe.else .Any))) + (failure? /.invalid_tuple_type)) + (|> (do //phase.monad + [[@var varT] (//type.check check.var)] + (|> expected + (/.product ..analysis archive.empty) + (//type.expecting (type (varT type/0))))) + (failure? /.invalid_tuple_type)))))) ))) (def: test|record @@ -471,161 +471,161 @@ _ slots/0)]] (all _.and - (_.cover [/.normal] - (let [normal? (is (-> (List [Symbol Code]) (List Code) Bit) - (function (_ expected input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.normal false input)) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (pipe.case - {try.#Success {.#Some actual}} - (let [(open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] - (list#= expected (list.reversed actual))) - - _ - false))))] - (and (normal? (list) (list)) - (normal? expected_record global_record) - (normal? expected_record local_record) - (|> (/.normal false tuple) - (//phase.result state) - (pipe.case - {try.#Success {.#None}} - true - - _ - false))))) - (_.cover [/.order] - (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/0) tuple) - global_record (list.zipped_2 (list#each (|>> [module]) slots/0) tuple) - ordered? (is (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (pipe.case - {try.#Success {.#Some [actual_arity actual_tuple actual_type]}} - (and (n.= arity actual_arity) - (# code.equivalence = (code.tuple tuple) (code.tuple actual_tuple)) - (type#= :record: actual_type)) - - _ - false)))) - unit? (is (-> Bit Bit) - (function (_ pattern_matching?) - (|> (/.order false (list)) - (//phase.result state) - (pipe.case - (pattern {try.#Success {.#Some [0 (list) actual_type]}}) - (same? .Any actual_type) - - _ - false))))] - (and (ordered? false global_record) - (ordered? false (list.reversed global_record)) - (ordered? false local_record) - (ordered? false (list.reversed local_record)) - - (ordered? true global_record) - (ordered? true (list.reversed global_record)) - (not (ordered? true local_record)) - (not (ordered? true (list.reversed local_record))) - - (unit? false) - (unit? true) - - ... TODO: Test what happens when slots are shadowed by local bindings. - ))) - (_.cover [/.cannot_repeat_slot] - (let [repeated? (is (-> Bit Bit) - (function (_ pattern_matching?) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? (list.repeated arity [[module head_slot/0] head_term/0]))) - (//module.with 0 module) - (//phase#each product.right) - (//phase.result state) - (..failure? /.cannot_repeat_slot))))] - (and (repeated? false) - (repeated? true)))) - (_.cover [/.record_size_mismatch] - (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/0) tuple) - global_record (list.zipped_2 (list#each (|>> [module]) slots/0) tuple) - mismatched? (is (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase.result state) - (..failure? /.record_size_mismatch))))] - (and (mismatched? false (list.first slice local_record)) - (mismatched? false (list#composite local_record (list.first slice local_record))) - - (mismatched? false (list.first slice global_record)) - (mismatched? true (list.first slice global_record)) - (mismatched? false (list#composite global_record (list.first slice global_record))) - (mismatched? true (list#composite global_record (list.first slice global_record)))))) - (_.cover [/.slot_does_not_belong_to_record] - (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/01) tuple) - global_record (list.zipped_2 (list#each (|>> [module]) slots/01) tuple) - mismatched? (is (-> Bit (List [Symbol Code]) Bit) - (function (_ pattern_matching? input) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:) - _ (//module.declare_labels true slots/1 false :record:)] - (/.order pattern_matching? input)) - //scope.with - (//module.with 0 module) - (//phase.result state) - (..failure? /.slot_does_not_belong_to_record))))] - (and (mismatched? false local_record) - - (mismatched? false global_record) - (mismatched? true global_record)))) - (_.cover [/.record] - (let [record? (is (-> Type (List Text) (List Code) Code Bit) - (function (_ type slots tuple expected) - (|> (do //phase.monad - [_ (//module.declare_labels true slots false type)] - (/.record ..analysis archive.empty tuple)) - (//type.expecting type) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try#each (analysed? expected)) - (try.else false)))) - inferred? (is (-> (List Code) Bit) - (function (_ record) - (|> (do //phase.monad - [_ (//module.declare_labels true slots/0 false :record:)] - (//type.inferring - (/.record ..analysis archive.empty record))) - //scope.with - (//module.with 0 module) - (//phase#each (|>> product.right product.right)) - (//phase.result state) - (try#each (function (_ [actual_type actual_term]) - (and (same? :record: actual_type) - (analysed? (code.tuple tuple) actual_term)))) - (try.else false))))] - (and (record? {.#Named name .Any} (list) (list) (' [])) - (record? {.#Named name type/0} (list) (list term/0) term/0) - (record? {.#Named name type/0} (list slot/0) (list term/0) term/0) - (record? :record: slots/0 tuple (code.tuple tuple)) - (record? :record: slots/0 local_record (code.tuple tuple)) - (record? :record: slots/0 global_record (code.tuple tuple)) - (inferred? local_record) - (inferred? global_record)))) + (_.coverage [/.normal] + (let [normal? (is (-> (List [Symbol Code]) (List Code) Bit) + (function (_ expected input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.normal false input)) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (pipe.case + {try.#Success {.#Some actual}} + (let [(open "list#[0]") (list.equivalence (product.equivalence symbol.equivalence code.equivalence))] + (list#= expected (list.reversed actual))) + + _ + false))))] + (and (normal? (list) (list)) + (normal? expected_record global_record) + (normal? expected_record local_record) + (|> (/.normal false tuple) + (//phase.result state) + (pipe.case + {try.#Success {.#None}} + true + + _ + false))))) + (_.coverage [/.order] + (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/0) tuple) + global_record (list.zipped_2 (list#each (|>> [module]) slots/0) tuple) + ordered? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (pipe.case + {try.#Success {.#Some [actual_arity actual_tuple actual_type]}} + (and (n.= arity actual_arity) + (# code.equivalence = (code.tuple tuple) (code.tuple actual_tuple)) + (type#= :record: actual_type)) + + _ + false)))) + unit? (is (-> Bit Bit) + (function (_ pattern_matching?) + (|> (/.order false (list)) + (//phase.result state) + (pipe.case + (pattern {try.#Success {.#Some [0 (list) actual_type]}}) + (same? .Any actual_type) + + _ + false))))] + (and (ordered? false global_record) + (ordered? false (list.reversed global_record)) + (ordered? false local_record) + (ordered? false (list.reversed local_record)) + + (ordered? true global_record) + (ordered? true (list.reversed global_record)) + (not (ordered? true local_record)) + (not (ordered? true (list.reversed local_record))) + + (unit? false) + (unit? true) + + ... TODO: Test what happens when slots are shadowed by local bindings. + ))) + (_.coverage [/.cannot_repeat_slot] + (let [repeated? (is (-> Bit Bit) + (function (_ pattern_matching?) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? (list.repeated arity [[module head_slot/0] head_term/0]))) + (//module.with 0 module) + (//phase#each product.right) + (//phase.result state) + (..failure? /.cannot_repeat_slot))))] + (and (repeated? false) + (repeated? true)))) + (_.coverage [/.record_size_mismatch] + (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/0) tuple) + global_record (list.zipped_2 (list#each (|>> [module]) slots/0) tuple) + mismatched? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase.result state) + (..failure? /.record_size_mismatch))))] + (and (mismatched? false (list.first slice local_record)) + (mismatched? false (list#composite local_record (list.first slice local_record))) + + (mismatched? false (list.first slice global_record)) + (mismatched? true (list.first slice global_record)) + (mismatched? false (list#composite global_record (list.first slice global_record))) + (mismatched? true (list#composite global_record (list.first slice global_record)))))) + (_.coverage [/.slot_does_not_belong_to_record] + (let [local_record (list.zipped_2 (list#each (|>> [""]) slots/01) tuple) + global_record (list.zipped_2 (list#each (|>> [module]) slots/01) tuple) + mismatched? (is (-> Bit (List [Symbol Code]) Bit) + (function (_ pattern_matching? input) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:) + _ (//module.declare_labels true slots/1 false :record:)] + (/.order pattern_matching? input)) + //scope.with + (//module.with 0 module) + (//phase.result state) + (..failure? /.slot_does_not_belong_to_record))))] + (and (mismatched? false local_record) + + (mismatched? false global_record) + (mismatched? true global_record)))) + (_.coverage [/.record] + (let [record? (is (-> Type (List Text) (List Code) Code Bit) + (function (_ type slots tuple expected) + (|> (do //phase.monad + [_ (//module.declare_labels true slots false type)] + (/.record ..analysis archive.empty tuple)) + (//type.expecting type) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try#each (analysed? expected)) + (try.else false)))) + inferred? (is (-> (List Code) Bit) + (function (_ record) + (|> (do //phase.monad + [_ (//module.declare_labels true slots/0 false :record:)] + (//type.inferring + (/.record ..analysis archive.empty record))) + //scope.with + (//module.with 0 module) + (//phase#each (|>> product.right product.right)) + (//phase.result state) + (try#each (function (_ [actual_type actual_term]) + (and (same? :record: actual_type) + (analysed? (code.tuple tuple) actual_term)))) + (try.else false))))] + (and (record? {.#Named name .Any} (list) (list) (' [])) + (record? {.#Named name type/0} (list) (list term/0) term/0) + (record? {.#Named name type/0} (list slot/0) (list term/0) term/0) + (record? :record: slots/0 tuple (code.tuple tuple)) + (record? :record: slots/0 local_record (code.tuple tuple)) + (record? :record: slots/0 global_record (code.tuple tuple)) + (inferred? local_record) + (inferred? global_record)))) ))) (def: .public test @@ -645,15 +645,15 @@ ..test|variant ..test|product ..test|record - (_.cover [/.not_a_quantified_type] - (and (|> (/.sum ..analysis lefts right? archive.empty term/0) - (//type.expecting (type (type/0 type/1))) - (//phase.result state) - (..failure? /.not_a_quantified_type)) - (|> types/*,terms/* - (list#each product.right) - (/.product ..analysis archive.empty) - (//type.expecting (type (type/0 type/1))) - (//phase.result state) - (..failure? /.not_a_quantified_type)))) + (_.coverage [/.not_a_quantified_type] + (and (|> (/.sum ..analysis lefts right? archive.empty term/0) + (//type.expecting (type (type/0 type/1))) + (//phase.result state) + (..failure? /.not_a_quantified_type)) + (|> types/*,terms/* + (list#each product.right) + (/.product ..analysis archive.empty) + (//type.expecting (type (type/0 type/1))) + (//phase.result state) + (..failure? /.not_a_quantified_type)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux index f14599150..5f002867e 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -81,106 +81,84 @@ $argument/0 (code.local argument/0) $argument/1 (code.local argument/1)]] (all _.and - (_.cover [/.function] - (let [function?' (is (-> Type Code (-> [(List Analysis) Analysis] Bit) Bit) - (function (_ function_type output_term ?) - (|> (do //phase.monad - [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty - output_term) - (//type.expecting function_type))] - (in (case analysis - {//analysis.#Function it} - (? it) + (_.coverage [/.function] + (let [function?' (is (-> Type Code (-> [(List Analysis) Analysis] Bit) Bit) + (function (_ function_type output_term ?) + (|> (do //phase.monad + [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty + output_term) + (//type.expecting function_type))] + (in (case analysis + {//analysis.#Function it} + (? it) - _ - false))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false)))) - function? (is (-> Type Code Bit) - (function (_ function_type output_term) - (function?' function_type output_term (function.constant true)))) - inferring? (is (-> Type Code Bit) - (function (_ :expected: term) - (|> (do //phase.monad - [[:actual: analysis] (|> (/.function ..analysis function/0 argument/0 archive.empty - term) - //type.inferring)] - (in (case analysis - {//analysis.#Function [actual_env actual_body]} - (type#= :expected: :actual:) - - _ - false))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] - (and (function? (-> input/0 output/0) term/0) - (function? (-> input/0 input/0) $argument/0) + _ + false))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false)))) + function? (is (-> Type Code Bit) + (function (_ function_type output_term) + (function?' function_type output_term (function.constant true)))) + inferring? (is (-> Type Code Bit) + (function (_ :expected: term) + (|> (do //phase.monad + [[:actual: analysis] (|> (/.function ..analysis function/0 argument/0 archive.empty + term) + //type.inferring)] + (in (case analysis + {//analysis.#Function [actual_env actual_body]} + (type#= :expected: :actual:) - (function? {.#Named name/0 (-> input/0 output/0)} term/0) - - (function? (All (_ a) (-> a a)) $argument/0) - (function? (Ex (_ a) (-> a a)) $argument/0) - (function? (Ex (_ a) (-> input/0 a)) term/0) - (function? (Ex (_ a) (-> a a)) term/0) - (function? (Rec self (-> input/0 self)) $function/0) + _ + false))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] + (and (function? (-> input/0 output/0) term/0) + (function? (-> input/0 input/0) $argument/0) - (function? (type ((All (_ a) (-> a a)) output/0)) term/0) - (not (function? (type ((All (_ a) (-> a a)) output/1)) term/0)) + (function? {.#Named name/0 (-> input/0 output/0)} term/0) + + (function? (All (_ a) (-> a a)) $argument/0) + (function? (Ex (_ a) (-> a a)) $argument/0) + (function? (Ex (_ a) (-> input/0 a)) term/0) + (function? (Ex (_ a) (-> a a)) term/0) + (function? (Rec self (-> input/0 self)) $function/0) - (function? (type ((Ex (_ a) (-> a a)) output/0)) term/0) - (not (function? (type ((Ex (_ a) (-> a a)) output/1)) term/0)) + (function? (type ((All (_ a) (-> a a)) output/0)) term/0) + (not (function? (type ((All (_ a) (-> a a)) output/1)) term/0)) - (function?' (-> input/0 input/1 input/0) (` ([(~ $function/1) (~ $argument/1)] (~ $argument/0))) - (function (_ [outer body]) - (and (list.empty? outer) - (case body - {//analysis.#Function [inner body]} - (n.= 1 (list.size inner)) + (function? (type ((Ex (_ a) (-> a a)) output/0)) term/0) + (not (function? (type ((Ex (_ a) (-> a a)) output/1)) term/0)) - _ - false)))) - (function?' (-> input/0 input/1 input/1) (` ([(~ $function/1) (~ $argument/1)] (~ $argument/1))) - (function (_ [outer body]) - (and (list.empty? outer) - (case body - {//analysis.#Function [inner body]} - (n.= 0 (list.size inner)) + (function?' (-> input/0 input/1 input/0) (` ([(~ $function/1) (~ $argument/1)] (~ $argument/0))) + (function (_ [outer body]) + (and (list.empty? outer) + (case body + {//analysis.#Function [inner body]} + (n.= 1 (list.size inner)) - _ - false)))) + _ + false)))) + (function?' (-> input/0 input/1 input/1) (` ([(~ $function/1) (~ $argument/1)] (~ $argument/1))) + (function (_ [outer body]) + (and (list.empty? outer) + (case body + {//analysis.#Function [inner body]} + (n.= 0 (list.size inner)) - (|> (do //phase.monad - [[@var :var:] (//type.check check.var) - _ (//type.check (check.check :var: (-> input/0 output/0))) - analysis (|> (/.function ..analysis function/0 argument/0 archive.empty - term/0) - (//type.expecting :var:))] - (in (case analysis - {//analysis.#Function [actual_env actual_body]} - true + _ + false)))) - _ - false))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false)) - - (inferring? (All (_ a) (-> a output/0)) term/0) - (inferring? (All (_ a) (-> a a)) $argument/0) - (inferring? (All (_ @0) (-> @0 @0 (And .Bit @0))) - (` ([(~ $function/1) (~ $argument/1)] - [("lux is" (~ $argument/0) (~ $argument/1)) - (~ $argument/1)])))))) - (_.cover [/.cannot_analyse] (|> (do //phase.monad - [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty - term/1) - (//type.expecting (-> input/0 output/0)))] + [[@var :var:] (//type.check check.var) + _ (//type.check (check.check :var: (-> input/0 output/0))) + analysis (|> (/.function ..analysis function/0 argument/0 archive.empty + term/0) + (//type.expecting :var:))] (in (case analysis {//analysis.#Function [actual_env actual_body]} true @@ -190,7 +168,29 @@ (//module.with 0 module/0) (//phase#each product.right) (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.cannot_analyse))))) + (try.else false)) + + (inferring? (All (_ a) (-> a output/0)) term/0) + (inferring? (All (_ a) (-> a a)) $argument/0) + (inferring? (All (_ @0) (-> @0 @0 (And .Bit @0))) + (` ([(~ $function/1) (~ $argument/1)] + [("lux is" (~ $argument/0) (~ $argument/1)) + (~ $argument/1)])))))) + (_.coverage [/.cannot_analyse] + (|> (do //phase.monad + [analysis (|> (/.function ..analysis function/0 argument/0 archive.empty + term/1) + (//type.expecting (-> input/0 output/0)))] + (in (case analysis + {//analysis.#Function [actual_env actual_body]} + true + + _ + false))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.cannot_analyse))))) ))) (def: test|apply @@ -205,48 +205,48 @@ output/0 ($type.random 0) module/0 (random.lower_case 1)] (all _.and - (_.cover [/.apply] - (let [reification? (is (-> Type (List Code) Type Bit) - (function (_ :abstraction: terms :expected:) - (|> (do //phase.monad - [[:actual: analysis] (|> (/.apply ..analysis terms - :abstraction: - (//analysis.unit) - archive.empty - (' [])) - //type.inferring)] - (in (and (check.subsumes? :expected: :actual:) - (case analysis - {//analysis.#Apply _} - true + (_.coverage [/.apply] + (let [reification? (is (-> Type (List Code) Type Bit) + (function (_ :abstraction: terms :expected:) + (|> (do //phase.monad + [[:actual: analysis] (|> (/.apply ..analysis terms + :abstraction: + (//analysis.unit) + archive.empty + (' [])) + //type.inferring)] + (in (and (check.subsumes? :expected: :actual:) + (case analysis + {//analysis.#Apply _} + true - _ - false)))) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (try.else false))))] - (and (reification? (-> input/0 input/1 output/0) (list term/0 term/1) output/0) - (reification? (-> input/0 input/1 output/0) (list term/0) (-> input/1 output/0)) - (reification? (All (_ a) (-> a a)) (list term/0) input/0) - (reification? (All (_ a) (-> a a a)) (list term/0) (-> input/0 input/0)) - (reification? (All (_ a) (-> input/0 a)) (list term/0) .Nothing) - (reification? (All (_ a b) (-> a b a)) (list term/0) (All (_ b) (-> b input/0))) - (reification? (Ex (_ a) (-> a input/0)) (list (` ("lux io error" ""))) input/0) - (reification? (Ex (_ a) (-> input/0 a)) (list term/0) .Any)))) - (_.cover [/.cannot_apply] - (|> (do //phase.monad - [_ (|> (/.apply ..analysis (list term/1 term/0) - (-> input/0 input/1 output/0) - (//analysis.unit) - archive.empty - (' [])) - (//type.expecting output/0))] - (in false)) - (//module.with 0 module/0) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.cannot_apply))))) + _ + false)))) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (try.else false))))] + (and (reification? (-> input/0 input/1 output/0) (list term/0 term/1) output/0) + (reification? (-> input/0 input/1 output/0) (list term/0) (-> input/1 output/0)) + (reification? (All (_ a) (-> a a)) (list term/0) input/0) + (reification? (All (_ a) (-> a a a)) (list term/0) (-> input/0 input/0)) + (reification? (All (_ a) (-> input/0 a)) (list term/0) .Nothing) + (reification? (All (_ a b) (-> a b a)) (list term/0) (All (_ b) (-> b input/0))) + (reification? (Ex (_ a) (-> a input/0)) (list (` ("lux io error" ""))) input/0) + (reification? (Ex (_ a) (-> input/0 a)) (list term/0) .Any)))) + (_.coverage [/.cannot_apply] + (|> (do //phase.monad + [_ (|> (/.apply ..analysis (list term/1 term/0) + (-> input/0 input/1 output/0) + (//analysis.unit) + archive.empty + (' [])) + (//type.expecting output/0))] + (in false)) + (//module.with 0 module/0) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.cannot_apply))))) ))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux index 66df51d4e..ff0b55372 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -43,181 +43,181 @@ expected_label (random.lower_case 4) record? random.bit] (all _.and - (_.cover [/.reference] - (let [can_find_local_variable! - (|> (/.reference ["" expected_name]) - (//scope.with_local [expected_name expected_type]) - //type.inferring - //scope.with - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (try#each (|>> product.right - (pipe.case - (pattern [actual_type (//analysis.local 0)]) - (type#= expected_type actual_type) + (_.coverage [/.reference] + (let [can_find_local_variable! + (|> (/.reference ["" expected_name]) + (//scope.with_local [expected_name expected_type]) + //type.inferring + //scope.with + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (try#each (|>> product.right + (pipe.case + (pattern [actual_type (//analysis.local 0)]) + (type#= expected_type actual_type) - _ - false))) - (try.else false)) + _ + false))) + (try.else false)) - can_find_foreign_variable! - (|> (/.reference ["" expected_name]) - //type.inferring - //scope.with - (//scope.with_local [expected_name expected_type]) - //scope.with - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (try#each (|>> product.right - product.right - (pipe.case - (pattern [actual_type (//analysis.foreign 0)]) - (type#= expected_type actual_type) + can_find_foreign_variable! + (|> (/.reference ["" expected_name]) + //type.inferring + //scope.with + (//scope.with_local [expected_name expected_type]) + //scope.with + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (try#each (|>> product.right + product.right + (pipe.case + (pattern [actual_type (//analysis.foreign 0)]) + (type#= expected_type actual_type) - _ - false))) - (try.else false)) + _ + false))) + (try.else false)) - can_find_local_definition! - (|> (do //phase.monad - [_ (//module.define expected_name {.#Definition [#0 expected_type []]})] - (/.reference ["" expected_name])) - //type.inferring - (//module.with 0 expected_module) - (//phase.result state) - (try#each (|>> product.right - (pipe.case - (pattern [actual_type (//analysis.constant [actual_module actual_name])]) - (and (type#= expected_type actual_type) - (same? expected_module actual_module) - (same? expected_name actual_name)) + can_find_local_definition! + (|> (do //phase.monad + [_ (//module.define expected_name {.#Definition [#0 expected_type []]})] + (/.reference ["" expected_name])) + //type.inferring + (//module.with 0 expected_module) + (//phase.result state) + (try#each (|>> product.right + (pipe.case + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) + (and (type#= expected_type actual_type) + (same? expected_module actual_module) + (same? expected_name actual_name)) - _ - false))) - (try.else false)) + _ + false))) + (try.else false)) - can_find_foreign_definition! - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name {.#Definition [#1 expected_type []]})) - _ (//module.import import)] - (/.reference [import expected_name])) - //type.inferring - (//module.with 0 expected_module) - (//phase.result state) - (try#each (|>> product.right - (pipe.case - (pattern [actual_type (//analysis.constant [actual_module actual_name])]) - (and (type#= expected_type actual_type) - (same? import actual_module) - (same? expected_name actual_name)) + can_find_foreign_definition! + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name {.#Definition [#1 expected_type []]})) + _ (//module.import import)] + (/.reference [import expected_name])) + //type.inferring + (//module.with 0 expected_module) + (//phase.result state) + (try#each (|>> product.right + (pipe.case + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) + (and (type#= expected_type actual_type) + (same? import actual_module) + (same? expected_name actual_name)) - _ - false))) - (try.else false)) + _ + false))) + (try.else false)) - can_find_alias! - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name {.#Definition [#1 expected_type []]})) - _ (//module.import import) - _ (//module.define expected_name {.#Alias [import expected_name]})] - (/.reference [expected_module expected_name])) - //type.inferring - (//module.with 0 expected_module) - (//phase.result state) - (try#each (|>> product.right - (pipe.case - (pattern [actual_type (//analysis.constant [actual_module actual_name])]) - (and (type#= expected_type actual_type) - (same? import actual_module) - (same? expected_name actual_name)) + can_find_alias! + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name {.#Definition [#1 expected_type []]})) + _ (//module.import import) + _ (//module.define expected_name {.#Alias [import expected_name]})] + (/.reference [expected_module expected_name])) + //type.inferring + (//module.with 0 expected_module) + (//phase.result state) + (try#each (|>> product.right + (pipe.case + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) + (and (type#= expected_type actual_type) + (same? import actual_module) + (same? expected_name actual_name)) - _ - false))) - (try.else false)) + _ + false))) + (try.else false)) - can_find_type! - (|> (do //phase.monad - [_ (//module.define expected_name {.#Type [#0 expected_type - (if record? - {.#Right [expected_label (list)]} - {.#Left [expected_label (list)]})]})] - (/.reference [expected_module expected_name])) - //type.inferring - (//module.with 0 expected_module) - (//phase.result state) - (try#each (|>> product.right - (pipe.case - (pattern [actual_type (//analysis.constant [actual_module actual_name])]) - (and (type#= .Type actual_type) - (same? expected_module actual_module) - (same? expected_name actual_name)) + can_find_type! + (|> (do //phase.monad + [_ (//module.define expected_name {.#Type [#0 expected_type + (if record? + {.#Right [expected_label (list)]} + {.#Left [expected_label (list)]})]})] + (/.reference [expected_module expected_name])) + //type.inferring + (//module.with 0 expected_module) + (//phase.result state) + (try#each (|>> product.right + (pipe.case + (pattern [actual_type (//analysis.constant [actual_module actual_name])]) + (and (type#= .Type actual_type) + (same? expected_module actual_module) + (same? expected_name actual_name)) - _ - false))) - (try.else false))] - (and can_find_local_variable! - can_find_foreign_variable! - - can_find_local_definition! - can_find_foreign_definition! + _ + false))) + (try.else false))] + (and can_find_local_variable! + can_find_foreign_variable! + + can_find_local_definition! + can_find_foreign_definition! - can_find_alias! - can_find_type!))) - (_.cover [/.foreign_module_has_not_been_imported] - (let [scenario (is (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name it)) - _ (/.reference [import expected_name])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.foreign_module_has_not_been_imported))) - )))] - (and (scenario expected_type {.#Definition [#1 expected_type []]}) - (scenario .Type {.#Type [#1 expected_type - (if record? - {.#Right [expected_label (list)]} - {.#Left [expected_label (list)]})]})))) - (_.cover [/.definition_has_not_been_exported] - (let [scenario (is (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_name it)) - _ (/.reference [import expected_name])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.definition_has_not_been_exported))) - )))] - (and (scenario expected_type {.#Definition [#0 expected_type []]}) - (scenario .Type {.#Type [#0 expected_type - (if record? - {.#Right [expected_label (list)]} - {.#Left [expected_label (list)]})]})))) - (_.cover [/.labels_are_not_definitions] - (let [scenario (is (-> Type Global Bit) - (function (_ expected_type it) - (|> (do //phase.monad - [_ (//module.with 0 import - (//module.define expected_label it)) - _ (/.reference [import expected_label])] - (in false)) - (//type.expecting expected_type) - (//module.with 0 expected_module) - (//phase#each product.right) - (//phase.result state) - (exception.otherwise (text.contains? (the exception.#label /.labels_are_not_definitions))))))] - (and (scenario expected_type {.#Tag [#1 expected_type (list) 0]}) - (scenario expected_type {.#Slot [#1 expected_type (list) 0]})))) + can_find_alias! + can_find_type!))) + (_.coverage [/.foreign_module_has_not_been_imported] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name it)) + _ (/.reference [import expected_name])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.foreign_module_has_not_been_imported))) + )))] + (and (scenario expected_type {.#Definition [#1 expected_type []]}) + (scenario .Type {.#Type [#1 expected_type + (if record? + {.#Right [expected_label (list)]} + {.#Left [expected_label (list)]})]})))) + (_.coverage [/.definition_has_not_been_exported] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_name it)) + _ (/.reference [import expected_name])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.definition_has_not_been_exported))) + )))] + (and (scenario expected_type {.#Definition [#0 expected_type []]}) + (scenario .Type {.#Type [#0 expected_type + (if record? + {.#Right [expected_label (list)]} + {.#Left [expected_label (list)]})]})))) + (_.coverage [/.labels_are_not_definitions] + (let [scenario (is (-> Type Global Bit) + (function (_ expected_type it) + (|> (do //phase.monad + [_ (//module.with 0 import + (//module.define expected_label it)) + _ (/.reference [import expected_label])] + (in false)) + (//type.expecting expected_type) + (//module.with 0 expected_module) + (//phase#each product.right) + (//phase.result state) + (exception.otherwise (text.contains? (the exception.#label /.labels_are_not_definitions))))))] + (and (scenario expected_type {.#Tag [#1 expected_type (list) 0]}) + (scenario expected_type {.#Slot [#1 expected_type (list) 0]})))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux index c096da534..dceaee0b2 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/analysis/simple.lux @@ -85,15 +85,15 @@ configuration ($configuration.random 5) .let [state (/analysis.state (/analysis.info version host configuration))]] (`` (all _.and - (_.cover [/.unit] - (..analysis state module .Any /.unit - (|>> (pipe.case (pattern (/analysis.unit)) true _ false)))) + (_.coverage [/.unit] + (..analysis state module .Any /.unit + (|>> (pipe.case (pattern (/analysis.unit)) true _ false)))) (~~ (template [<analysis> <type> <random> <tag>] [(do ! [sample <random>] - (_.cover [<analysis>] - (..analysis state module <type> (<analysis> sample) - ((..analysis? <type> <tag>) sample))))] + (_.coverage [<analysis>] + (..analysis state module <type> (<analysis> sample) + ((..analysis? <type> <tag>) sample))))] [/.bit .Bit random.bit /analysis.bit] [/.nat .Nat random.nat /analysis.nat] diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux index 59bafc3d7..3833dfa63 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension.lux @@ -44,54 +44,54 @@ dummy (random.only (|>> (i.= state) not) random.int)] (all _.and - (_.cover [/.read] - (|> (is (/.Operation Int Nat Nat Text) - (/.read %.int)) - (# phase.functor each (text#= (%.int state))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false))) - (_.cover [/.update] - (|> (is (/.Operation Int Nat Nat Text) - (do phase.monad - [_ (/.update ++)] - (/.read %.int))) - (# phase.functor each (text#= (%.int (++ state)))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false))) - (_.cover [/.temporary] - (|> (is (/.Operation Int Nat Nat Text) - (do phase.monad - [|state'| (/.temporary ++ (/.read %.int)) - |state| (/.read %.int)] - (in (format |state'| " " |state|)))) - (# phase.functor each (text#= (format (%.int (++ state)) " " (%.int state)))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false))) - (_.cover [/.with_state] - (|> (is (/.Operation Int Nat Nat Text) - (/.with_state state - (/.read %.int))) - (# phase.functor each (text#= (%.int state))) - (phase.result [/.#bundle /.empty - /.#state dummy]) - (try.else false))) - (_.cover [/.localized] - (|> (is (/.Operation Int Nat Nat Text) - (do phase.monad - [|state| (/.localized %.int - (function (_ _ old) (++ old)) - (text.enclosed ["<" ">"]) - (/.read %.int)) - |state'| (/.read %.int)] - (in (format |state'| " " |state|)))) - (# phase.functor each (text#= (format (%.int (i.+ +2 state)) - " " (%.int (i.+ +1 state))))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false)))) + (_.coverage [/.read] + (|> (is (/.Operation Int Nat Nat Text) + (/.read %.int)) + (# phase.functor each (text#= (%.int state))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false))) + (_.coverage [/.update] + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [_ (/.update ++)] + (/.read %.int))) + (# phase.functor each (text#= (%.int (++ state)))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false))) + (_.coverage [/.temporary] + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [|state'| (/.temporary ++ (/.read %.int)) + |state| (/.read %.int)] + (in (format |state'| " " |state|)))) + (# phase.functor each (text#= (format (%.int (++ state)) " " (%.int state)))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false))) + (_.coverage [/.with_state] + (|> (is (/.Operation Int Nat Nat Text) + (/.with_state state + (/.read %.int))) + (# phase.functor each (text#= (%.int state))) + (phase.result [/.#bundle /.empty + /.#state dummy]) + (try.else false))) + (_.coverage [/.localized] + (|> (is (/.Operation Int Nat Nat Text) + (do phase.monad + [|state| (/.localized %.int + (function (_ _ old) (++ old)) + (text.enclosed ["<" ">"]) + (/.read %.int)) + |state'| (/.read %.int)] + (in (format |state'| " " |state|)))) + (# phase.functor each (text#= (format (%.int (i.+ +2 state)) + " " (%.int (i.+ +1 state))))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false)))) )) (def: extender @@ -116,30 +116,30 @@ left random.nat right random.nat] (all _.and - (_.cover [/.cannot_overwrite] - (|> (do phase.monad - [_ (/.install extender extension handler/0)] - (/.install extender extension handler/1)) - (phase.result [/.#bundle /.empty - /.#state state]) - (pipe.case - {try.#Failure error} - (exception.match? /.cannot_overwrite error) + (_.coverage [/.cannot_overwrite] + (|> (do phase.monad + [_ (/.install extender extension handler/0)] + (/.install extender extension handler/1)) + (phase.result [/.#bundle /.empty + /.#state state]) + (pipe.case + {try.#Failure error} + (exception.match? /.cannot_overwrite error) - _ - false))) - (_.cover [/.unknown] - (|> (/.apply archive.empty (function (_ archive input) - (# phase.monad in (++ input))) - [extension (list left right)]) - (phase.result [/.#bundle /.empty - /.#state state]) - (pipe.case - {try.#Failure error} - (exception.match? /.unknown error) + _ + false))) + (_.coverage [/.unknown] + (|> (/.apply archive.empty (function (_ archive input) + (# phase.monad in (++ input))) + [extension (list left right)]) + (phase.result [/.#bundle /.empty + /.#state state]) + (pipe.case + {try.#Failure error} + (exception.match? /.unknown error) - _ - false))) + _ + false))) ))) (def: test|bundle @@ -154,72 +154,72 @@ left random.nat right random.nat] (all _.and - (_.cover [/.empty] - (dictionary.empty? /.empty)) + (_.coverage [/.empty] + (dictionary.empty? /.empty)) (<| (_.for [/.Extender /.Handler]) (all _.and - (_.cover [/.install /.apply] - (|> (do phase.monad - [_ (/.install extender extension handler/0)] - (/.apply archive.empty phase [extension (list left right)])) - (# phase.functor each (n.= (n.+ left right))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false))) - (_.cover [/.Phase] - (let [handler (is (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (let [! phase.monad] - (|> inputs - (monad.each ! (phase archive)) - (# ! each (list#mix n.+ 0))))))] - (|> (do phase.monad - [_ (/.install extender extension handler)] - (/.apply archive.empty phase [extension (list left right)])) - (# phase.functor each (n.= (n.+ (++ left) (++ right)))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false)))) - (_.cover [/.with] - (|> (do phase.monad - [_ (/.with extender (dictionary.of_list text.hash (list [extension handler/1])))] - (/.apply archive.empty (function (_ archive input) - (# phase.monad in (++ input))) - [extension (list left right)])) - (# phase.functor each (n.= (n.* left right))) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false))) - (_.cover [/.incorrect_arity] - (let [handler (is (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (phase.except /.incorrect_arity [@self 2 (list.size inputs)])))] - (|> (do phase.monad - [_ (/.install extender extension handler)] - (/.apply archive.empty phase [extension (list)])) - (phase.result [/.#bundle /.empty - /.#state state]) - (pipe.case - {try.#Failure error} - (exception.match? /.incorrect_arity error) + (_.coverage [/.install /.apply] + (|> (do phase.monad + [_ (/.install extender extension handler/0)] + (/.apply archive.empty phase [extension (list left right)])) + (# phase.functor each (n.= (n.+ left right))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false))) + (_.coverage [/.Phase] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (let [! phase.monad] + (|> inputs + (monad.each ! (phase archive)) + (# ! each (list#mix n.+ 0))))))] + (|> (do phase.monad + [_ (/.install extender extension handler)] + (/.apply archive.empty phase [extension (list left right)])) + (# phase.functor each (n.= (n.+ (++ left) (++ right)))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false)))) + (_.coverage [/.with] + (|> (do phase.monad + [_ (/.with extender (dictionary.of_list text.hash (list [extension handler/1])))] + (/.apply archive.empty (function (_ archive input) + (# phase.monad in (++ input))) + [extension (list left right)])) + (# phase.functor each (n.= (n.* left right))) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false))) + (_.coverage [/.incorrect_arity] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (phase.except /.incorrect_arity [@self 2 (list.size inputs)])))] + (|> (do phase.monad + [_ (/.install extender extension handler)] + (/.apply archive.empty phase [extension (list)])) + (phase.result [/.#bundle /.empty + /.#state state]) + (pipe.case + {try.#Failure error} + (exception.match? /.incorrect_arity error) - _ - false)))) - (_.cover [/.invalid_syntax] - (let [handler (is (/.Handler Int Nat Nat) - (function (_ @self phase archive inputs) - (phase.except /.invalid_syntax [@self %.nat inputs])))] - (|> (do phase.monad - [_ (/.install extender extension handler)] - (/.apply archive.empty phase [extension (list left right)])) - (phase.result [/.#bundle /.empty - /.#state state]) - (pipe.case - {try.#Failure error} - (exception.match? /.invalid_syntax error) + _ + false)))) + (_.coverage [/.invalid_syntax] + (let [handler (is (/.Handler Int Nat Nat) + (function (_ @self phase archive inputs) + (phase.except /.invalid_syntax [@self %.nat inputs])))] + (|> (do phase.monad + [_ (/.install extender extension handler)] + (/.apply archive.empty phase [extension (list left right)])) + (phase.result [/.#bundle /.empty + /.#state state]) + (pipe.case + {try.#Failure error} + (exception.match? /.invalid_syntax error) - _ - false)))) + _ + false)))) (_.for [/.Name] ..test|name) )) @@ -243,35 +243,35 @@ (<| (_.for [/.Operation]) (all _.and - (_.cover [/.lifted] - (and (|> (is (/.Operation Int Nat Nat Nat) - (/.lifted (do phase.monad - [] - (in expected)))) - (# phase.functor each (same? expected)) - (phase.result [/.#bundle /.empty - /.#state state]) - (try.else false)) - (|> (is (/.Operation Int Nat Nat Nat) - (/.lifted (phase.lifted {try.#Failure expected_error}))) - (phase.result [/.#bundle /.empty - /.#state state]) - (pipe.case - {try.#Failure actual_error} - (same? expected_error actual_error) + (_.coverage [/.lifted] + (and (|> (is (/.Operation Int Nat Nat Nat) + (/.lifted (do phase.monad + [] + (in expected)))) + (# phase.functor each (same? expected)) + (phase.result [/.#bundle /.empty + /.#state state]) + (try.else false)) + (|> (is (/.Operation Int Nat Nat Nat) + (/.lifted (phase.lifted {try.#Failure expected_error}))) + (phase.result [/.#bundle /.empty + /.#state state]) + (pipe.case + {try.#Failure actual_error} + (same? expected_error actual_error) - _ - false)))) - (_.cover [/.up] - (|> (do phase.monad - [] - (in expected)) - (is (/.Operation Int Nat Nat Nat)) - /.up - (is (phase.Operation Int Nat)) - (# phase.functor each (same? expected)) - (phase.result state) - (try.else false))) + _ + false)))) + (_.coverage [/.up] + (|> (do phase.monad + [] + (in expected)) + (is (/.Operation Int Nat Nat Nat)) + /.up + (is (phase.Operation Int Nat)) + (# phase.functor each (same? expected)) + (phase.result state) + (try.else false))) )) (_.for [/.State] ..test|state) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index cbcd636f4..712eaad17 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -62,14 +62,14 @@ [antiT antiC] (|> ..primitive (r.only (|>> product.left (type#= primT) not)))] (all _.and - (_.test "Can test for reference equality." - (check_success+ "lux is" (list primC primC) Bit)) - (_.test "Reference equality must be done with elements of the same type." - (check_failure+ "lux is" (list primC antiC) Bit)) - (_.test "Can 'try' risky IO computations." - (check_success+ "lux try" - (list (` ("lux io error" "YOLO"))) - (type (Either Text primT)))) + (_.property "Can test for reference equality." + (check_success+ "lux is" (list primC primC) Bit)) + (_.property "Reference equality must be done with elements of the same type." + (check_failure+ "lux is" (list primC antiC) Bit)) + (_.property "Can 'try' risky IO computations." + (check_success+ "lux try" + (list (` ("lux io error" "YOLO"))) + (type (Either Text primT)))) ))) (def: i64 @@ -79,24 +79,24 @@ signedC (|> r.int (# ! each code.int)) paramC (|> r.nat (# ! each code.nat))] (all _.and - (_.test "i64 'and'." - (check_success+ "lux i64 and" (list paramC subjectC) Nat)) - (_.test "i64 'or'." - (check_success+ "lux i64 or" (list paramC subjectC) Nat)) - (_.test "i64 'xor'." - (check_success+ "lux i64 xor" (list paramC subjectC) Nat)) - (_.test "i64 left-shift." - (check_success+ "lux i64 left-shift" (list paramC subjectC) Nat)) - (_.test "i64 logical-right-shift." - (check_success+ "lux i64 logical-right-shift" (list paramC subjectC) Nat)) - (_.test "i64 arithmetic-right-shift." - (check_success+ "lux i64 arithmetic-right-shift" (list paramC signedC) Int)) - (_.test "i64 equivalence." - (check_success+ "lux i64 =" (list paramC subjectC) Bit)) - (_.test "i64 addition." - (check_success+ "lux i64 +" (list paramC subjectC) Int)) - (_.test "i64 subtraction." - (check_success+ "lux i64 -" (list paramC subjectC) Int)) + (_.property "i64 'and'." + (check_success+ "lux i64 and" (list paramC subjectC) Nat)) + (_.property "i64 'or'." + (check_success+ "lux i64 or" (list paramC subjectC) Nat)) + (_.property "i64 'xor'." + (check_success+ "lux i64 xor" (list paramC subjectC) Nat)) + (_.property "i64 left-shift." + (check_success+ "lux i64 left-shift" (list paramC subjectC) Nat)) + (_.property "i64 logical-right-shift." + (check_success+ "lux i64 logical-right-shift" (list paramC subjectC) Nat)) + (_.property "i64 arithmetic-right-shift." + (check_success+ "lux i64 arithmetic-right-shift" (list paramC signedC) Int)) + (_.property "i64 equivalence." + (check_success+ "lux i64 =" (list paramC subjectC) Bit)) + (_.property "i64 addition." + (check_success+ "lux i64 +" (list paramC subjectC) Int)) + (_.property "i64 subtraction." + (check_success+ "lux i64 -" (list paramC subjectC) Int)) ))) (def: int @@ -105,18 +105,18 @@ [subjectC (|> r.int (# ! each code.int)) paramC (|> r.int (# ! each code.int))] (all _.and - (_.test "Can multiply integers." - (check_success+ "lux i64 *" (list paramC subjectC) Int)) - (_.test "Can divide integers." - (check_success+ "lux i64 /" (list paramC subjectC) Int)) - (_.test "Can calculate remainder of integers." - (check_success+ "lux i64 %" (list paramC subjectC) Int)) - (_.test "Can compare integers." - (check_success+ "lux i64 <" (list paramC subjectC) Bit)) - (_.test "Can convert integer to text." - (check_success+ "lux i64 char" (list subjectC) Text)) - (_.test "Can convert integer to fraction." - (check_success+ "lux i64 f64" (list subjectC) Frac)) + (_.property "Can multiply integers." + (check_success+ "lux i64 *" (list paramC subjectC) Int)) + (_.property "Can divide integers." + (check_success+ "lux i64 /" (list paramC subjectC) Int)) + (_.property "Can calculate remainder of integers." + (check_success+ "lux i64 %" (list paramC subjectC) Int)) + (_.property "Can compare integers." + (check_success+ "lux i64 <" (list paramC subjectC) Bit)) + (_.property "Can convert integer to text." + (check_success+ "lux i64 char" (list subjectC) Text)) + (_.property "Can convert integer to fraction." + (check_success+ "lux i64 f64" (list subjectC) Frac)) ))) (def: frac @@ -126,32 +126,32 @@ paramC (|> r.safe_frac (# ! each code.frac)) encodedC (|> r.safe_frac (# ! each (|>> %.frac code.text)))] (all _.and - (_.test "Can add frac numbers." - (check_success+ "lux f64 +" (list paramC subjectC) Frac)) - (_.test "Can subtract frac numbers." - (check_success+ "lux f64 -" (list paramC subjectC) Frac)) - (_.test "Can multiply frac numbers." - (check_success+ "lux f64 *" (list paramC subjectC) Frac)) - (_.test "Can divide frac numbers." - (check_success+ "lux f64 /" (list paramC subjectC) Frac)) - (_.test "Can calculate remainder of frac numbers." - (check_success+ "lux f64 %" (list paramC subjectC) Frac)) - (_.test "Can test equivalence of frac numbers." - (check_success+ "lux f64 =" (list paramC subjectC) Bit)) - (_.test "Can compare frac numbers." - (check_success+ "lux f64 <" (list paramC subjectC) Bit)) - (_.test "Can obtain minimum frac number." - (check_success+ "lux f64 min" (list) Frac)) - (_.test "Can obtain maximum frac number." - (check_success+ "lux f64 max" (list) Frac)) - (_.test "Can obtain smallest frac number." - (check_success+ "lux f64 smallest" (list) Frac)) - (_.test "Can convert frac number to integer." - (check_success+ "lux f64 i64" (list subjectC) Int)) - (_.test "Can convert frac number to text." - (check_success+ "lux f64 encode" (list subjectC) Text)) - (_.test "Can convert text to frac number." - (check_success+ "lux f64 decode" (list encodedC) (type (Maybe Frac)))) + (_.property "Can add frac numbers." + (check_success+ "lux f64 +" (list paramC subjectC) Frac)) + (_.property "Can subtract frac numbers." + (check_success+ "lux f64 -" (list paramC subjectC) Frac)) + (_.property "Can multiply frac numbers." + (check_success+ "lux f64 *" (list paramC subjectC) Frac)) + (_.property "Can divide frac numbers." + (check_success+ "lux f64 /" (list paramC subjectC) Frac)) + (_.property "Can calculate remainder of frac numbers." + (check_success+ "lux f64 %" (list paramC subjectC) Frac)) + (_.property "Can test equivalence of frac numbers." + (check_success+ "lux f64 =" (list paramC subjectC) Bit)) + (_.property "Can compare frac numbers." + (check_success+ "lux f64 <" (list paramC subjectC) Bit)) + (_.property "Can obtain minimum frac number." + (check_success+ "lux f64 min" (list) Frac)) + (_.property "Can obtain maximum frac number." + (check_success+ "lux f64 max" (list) Frac)) + (_.property "Can obtain smallest frac number." + (check_success+ "lux f64 smallest" (list) Frac)) + (_.property "Can convert frac number to integer." + (check_success+ "lux f64 i64" (list subjectC) Int)) + (_.property "Can convert frac number to text." + (check_success+ "lux f64 encode" (list subjectC) Text)) + (_.property "Can convert text to frac number." + (check_success+ "lux f64 decode" (list encodedC) (type (Maybe Frac)))) ))) (def: text @@ -163,20 +163,20 @@ fromC (|> r.nat (# ! each code.nat)) toC (|> r.nat (# ! each code.nat))] (all _.and - (_.test "Can test text equivalence." - (check_success+ "lux text =" (list paramC subjectC) Bit)) - (_.test "Compare texts in lexicographical order." - (check_success+ "lux text <" (list paramC subjectC) Bit)) - (_.test "Can concatenate one text to another." - (check_success+ "lux text concat" (list subjectC paramC) Text)) - (_.test "Can find the index of a piece of text inside a larger one that (may) contain it." - (check_success+ "lux text index" (list fromC paramC subjectC) (type (Maybe Nat)))) - (_.test "Can query the size/length of a text." - (check_success+ "lux text size" (list subjectC) Nat)) - (_.test "Can obtain the character code of a text at a given index." - (check_success+ "lux text char" (list fromC subjectC) Nat)) - (_.test "Can clip a piece of text between 2 indices." - (check_success+ "lux text clip" (list fromC toC subjectC) Text)) + (_.property "Can test text equivalence." + (check_success+ "lux text =" (list paramC subjectC) Bit)) + (_.property "Compare texts in lexicographical order." + (check_success+ "lux text <" (list paramC subjectC) Bit)) + (_.property "Can concatenate one text to another." + (check_success+ "lux text concat" (list subjectC paramC) Text)) + (_.property "Can find the index of a piece of text inside a larger one that (may) contain it." + (check_success+ "lux text index" (list fromC paramC subjectC) (type (Maybe Nat)))) + (_.property "Can query the size/length of a text." + (check_success+ "lux text size" (list subjectC) Nat)) + (_.property "Can obtain the character code of a text at a given index." + (check_success+ "lux text char" (list fromC subjectC) Nat)) + (_.property "Can clip a piece of text between 2 indices." + (check_success+ "lux text clip" (list fromC toC subjectC) Text)) ))) (def: io @@ -185,12 +185,12 @@ [logC (|> (r.unicode 5) (# ! each code.text)) exitC (|> r.int (# ! each code.int))] (all _.and - (_.test "Can log messages to standard output." - (check_success+ "lux io log" (list logC) Any)) - (_.test "Can throw a run-time error." - (check_success+ "lux io error" (list logC) Nothing)) - (_.test "Can query the current time (as milliseconds since epoch)." - (check_success+ "lux io current-time" (list) Int)) + (_.property "Can log messages to standard output." + (check_success+ "lux io log" (list logC) Any)) + (_.property "Can throw a run-time error." + (check_success+ "lux io error" (list logC) Nothing)) + (_.property "Can query the current time (as milliseconds since epoch)." + (check_success+ "lux io current-time" (list) Int)) ))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux index 4ea071954..ee7bdec19 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -49,12 +49,12 @@ [[{analysis.#Bind temp} {analysis.#Reference (////reference.local temp)}] (list)]])]] - (_.cover [/.synthesize_masking] - (|> maskA - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (try#each (//primitive.corresponds? maskedA)) - (try.default false))))) + (_.coverage [/.synthesize_masking] + (|> maskA + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (try#each (//primitive.corresponds? maskedA)) + (try.default false))))) (def: let_test Test @@ -67,18 +67,18 @@ [[{analysis.#Bind registerA} outputA] (list)]])]] - (_.cover [/.synthesize_let] - (|> letA - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (pipe.case - (pattern {try.#Success (synthesis.branch/let [inputS registerS outputS])}) - (and (n.= registerA registerS) - (//primitive.corresponds? inputA inputS) - (//primitive.corresponds? outputA outputS)) + (_.coverage [/.synthesize_let] + (|> letA + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (pipe.case + (pattern {try.#Success (synthesis.branch/let [inputS registerS outputS])}) + (and (n.= registerA registerS) + (//primitive.corresponds? inputA inputS) + (//primitive.corresponds? outputA outputS)) - _ - false))))) + _ + false))))) (def: if_test Test @@ -96,18 +96,18 @@ ifA (if then|else (analysis.case [inputA [thenB (list elseB)]]) (analysis.case [inputA [elseB (list thenB)]]))]] - (_.cover [/.synthesize_if] - (|> ifA - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (pipe.case - (pattern {try.#Success (synthesis.branch/if [inputS thenS elseS])}) - (and (//primitive.corresponds? inputA inputS) - (//primitive.corresponds? thenA thenS) - (//primitive.corresponds? elseA elseS)) + (_.coverage [/.synthesize_if] + (|> ifA + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (pipe.case + (pattern {try.#Success (synthesis.branch/if [inputS thenS elseS])}) + (and (//primitive.corresponds? inputA inputS) + (//primitive.corresponds? thenA thenS) + (//primitive.corresponds? elseA elseS)) - _ - false))))) + _ + false))))) (def: random_member (Random synthesis.Member) @@ -156,17 +156,17 @@ .let [getA (analysis.case [recordA [[pattern {analysis.#Reference (////reference.local @member)}] (list)]])]] - (_.cover [/.synthesize_get] - (|> getA - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (pipe.case - (pattern {try.#Success (synthesis.branch/get [pathS recordS])}) - (and (# (list.equivalence (sum.equivalence n.= n.=)) = pathA pathS) - (//primitive.corresponds? recordA recordS)) + (_.coverage [/.synthesize_get] + (|> getA + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (pipe.case + (pattern {try.#Success (synthesis.branch/get [pathS recordS])}) + (and (# (list.equivalence (sum.equivalence n.= n.=)) = pathA pathS) + (//primitive.corresponds? recordA recordS)) - _ - false))))) + _ + false))))) (def: random_bit (Random [Path Match]) @@ -334,16 +334,16 @@ (do [! random.monad] [expected_input (# ! each (|>> .i64 synthesis.i64) random.nat) [expected_path match] ..random_case] - (_.cover [/.synthesize_case] - (|> (/.synthesize_case //.phase archive.empty expected_input match) - (phase.result [///bundle.empty synthesis.init]) - (pipe.case - (pattern {try.#Success (synthesis.branch/case [actual_input actual_path])}) - (and (# synthesis.equivalence = expected_input actual_input) - (# synthesis.path_equivalence = expected_path actual_path)) + (_.coverage [/.synthesize_case] + (|> (/.synthesize_case //.phase archive.empty expected_input match) + (phase.result [///bundle.empty synthesis.init]) + (pipe.case + (pattern {try.#Success (synthesis.branch/case [actual_input actual_path])}) + (and (# synthesis.equivalence = expected_input actual_input) + (# synthesis.path_equivalence = expected_path actual_path)) - _ - false))))) + _ + false))))) (def: .public test Test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux index df05fcc1a..51f9d87b9 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -430,12 +430,12 @@ Test (do random.monad [[expected input] ..random_abstraction] - (_.cover [/.abstraction] - (|> input - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (!expect (^.multi {try.#Success actual} - (# synthesis.equivalence = expected actual))))))) + (_.coverage [/.abstraction] + (|> input + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual))))))) (def: application Test @@ -443,19 +443,19 @@ [arity (|> random.nat (# ! each (|>> (n.% 10) (n.max 1)))) funcA //primitive.primitive argsA (random.list arity //primitive.primitive)] - (_.cover [/.apply] - (and (|> (analysis.apply [funcA argsA]) - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (!expect (^.multi (pattern {try.#Success (synthesis.function/apply [funcS argsS])}) - (and (//primitive.corresponds? funcA funcS) - (list.every? (product.uncurried //primitive.corresponds?) - (list.zipped_2 argsA argsS)))))) - (|> (analysis.apply [funcA (list)]) - (//.phase archive.empty) - (phase.result [///bundle.empty synthesis.init]) - (!expect (^.multi {try.#Success funcS} - (//primitive.corresponds? funcA funcS)))))))) + (_.coverage [/.apply] + (and (|> (analysis.apply [funcA argsA]) + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (!expect (^.multi (pattern {try.#Success (synthesis.function/apply [funcS argsS])}) + (and (//primitive.corresponds? funcA funcS) + (list.every? (product.uncurried //primitive.corresponds?) + (list.zipped_2 argsA argsS)))))) + (|> (analysis.apply [funcA (list)]) + (//.phase archive.empty) + (phase.result [///bundle.empty synthesis.init]) + (!expect (^.multi {try.#Success funcS} + (//primitive.corresponds? funcA funcS)))))))) (def: .public test Test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 7120348e1..2a6cb934b 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -272,22 +272,22 @@ (# ! each (|>> .i64 //.i64)) (random.list arity)) [_ [expected iteration]] (..scenario expected_offset arity 0)] - (_.cover [/.Transform /.optimization /.register_optimization] - (case (/.optimization true expected_offset expected_inits - [//.#environment (|> expected_offset - list.indices - (list#each (|>> {variable.#Local}))) - //.#arity arity - //.#body iteration]) - (pattern {.#Some (//.loop/scope [actual_offset actual_inits - actual])}) - (and (n.= expected_offset - actual_offset) - (# (list.equivalence //.equivalence) = - expected_inits - actual_inits) - (# //.equivalence = expected actual)) - - _ - false))) + (_.coverage [/.Transform /.optimization /.register_optimization] + (case (/.optimization true expected_offset expected_inits + [//.#environment (|> expected_offset + list.indices + (list#each (|>> {variable.#Local}))) + //.#arity arity + //.#body iteration]) + (pattern {.#Some (//.loop/scope [actual_offset actual_inits + actual])}) + (and (n.= expected_offset + actual_offset) + (# (list.equivalence //.equivalence) = + expected_inits + actual_inits) + (# //.equivalence = expected actual)) + + _ + false))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux index b1b494810..327a799ef 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/primitive.lux @@ -78,16 +78,16 @@ (~~ (template [<analysis> <synthesis> <generator>] [(do r.monad [expected <generator>] - (_.test (%.symbol (symbol <synthesis>)) - (|> {////analysis.#Primitive {<analysis> expected}} - (//.phase archive.empty) - (phase.result [///bundle.empty ////synthesis.init]) - (pipe.case - {try.#Success {////synthesis.#Primitive {<synthesis> actual}}} - (same? expected actual) + (_.property (%.symbol (symbol <synthesis>)) + (|> {////analysis.#Primitive {<analysis> expected}} + (//.phase archive.empty) + (phase.result [///bundle.empty ////synthesis.init]) + (pipe.case + {try.#Success {////synthesis.#Primitive {<synthesis> actual}}} + (same? expected actual) - _ - false))))] + _ + false))))] [////analysis.#Unit ////synthesis.#Text (r#in ////synthesis.unit)] [////analysis.#Bit ////synthesis.#Bit r.bit] diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux index 08a90da4b..5cfb0ecd6 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/structure.lux @@ -44,37 +44,37 @@ (-- tagA) tagA)] memberA //primitive.primitive] - (_.test "Can synthesize variants." - (|> (////analysis.variant [lefts right? memberA]) - (//.phase archive.empty) - (phase.result [///bundle.empty ////synthesis.init]) - (pipe.case - (pattern {try.#Success (////synthesis.variant [leftsS right?S valueS])}) - (let [tagS (if right?S (++ leftsS) leftsS)] - (and (n.= tagA tagS) - (|> tagS (n.= (-- size)) (bit#= right?S)) - (//primitive.corresponds? memberA valueS))) - - _ - false))))) + (_.property "Can synthesize variants." + (|> (////analysis.variant [lefts right? memberA]) + (//.phase archive.empty) + (phase.result [///bundle.empty ////synthesis.init]) + (pipe.case + (pattern {try.#Success (////synthesis.variant [leftsS right?S valueS])}) + (let [tagS (if right?S (++ leftsS) leftsS)] + (and (n.= tagA tagS) + (|> tagS (n.= (-- size)) (bit#= right?S)) + (//primitive.corresponds? memberA valueS))) + + _ + false))))) (def: tuple Test (do [! r.monad] [size (|> r.nat (# ! each (|>> (n.% 10) (n.max 2)))) membersA (r.list size //primitive.primitive)] - (_.test "Can synthesize tuple." - (|> (////analysis.tuple membersA) - (//.phase archive.empty) - (phase.result [///bundle.empty ////synthesis.init]) - (pipe.case - (pattern {try.#Success (////synthesis.tuple membersS)}) - (and (n.= size (list.size membersS)) - (list.every? (product.uncurried //primitive.corresponds?) - (list.zipped_2 membersA membersS))) + (_.property "Can synthesize tuple." + (|> (////analysis.tuple membersA) + (//.phase archive.empty) + (phase.result [///bundle.empty ////synthesis.init]) + (pipe.case + (pattern {try.#Success (////synthesis.tuple membersS)}) + (and (n.= size (list.size membersS)) + (list.every? (product.uncurried //primitive.corresponds?) + (list.zipped_2 membersA membersS))) - _ - false))))) + _ + false))))) (def: .public test Test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 7e69f4420..ee364756a 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -329,8 +329,8 @@ (all _.and (do random.monad [[expected input] (..scenario ..default)] - (_.cover [/.optimization] - (|> (/.optimization input) - (!expect (^.multi {try.#Success actual} - (# synthesis.equivalence = expected actual)))))) + (_.coverage [/.optimization] + (|> (/.optimization input) + (!expect (^.multi {try.#Success actual} + (# synthesis.equivalence = expected actual)))))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux index e8dad37cf..21a76beb9 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux @@ -76,34 +76,34 @@ (do [! r.monad] [sample code^] (all _.and - (_.test "Can parse Lux code." - (case (let [source_code (%.code sample)] - (/.parse "" (dictionary.empty text.hash) (text.size source_code) - [location.dummy 0 source_code])) - {.#Left error} - false + (_.property "Can parse Lux code." + (case (let [source_code (%.code sample)] + (/.parse "" (dictionary.empty text.hash) (text.size source_code) + [location.dummy 0 source_code])) + {.#Left error} + false - {.#Right [_ parsed]} - (# code.equivalence = parsed sample))) + {.#Right [_ parsed]} + (# code.equivalence = parsed sample))) (do ! [other code^] - (_.test "Can parse multiple Lux code nodes." - (let [source_code (format (%.code sample) " " (%.code other)) - source_code//size (text.size source_code)] - (case (/.parse "" (dictionary.empty text.hash) source_code//size - [location.dummy 0 source_code]) - {.#Left error} - false + (_.property "Can parse multiple Lux code nodes." + (let [source_code (format (%.code sample) " " (%.code other)) + source_code//size (text.size source_code)] + (case (/.parse "" (dictionary.empty text.hash) source_code//size + [location.dummy 0 source_code]) + {.#Left error} + false - {.#Right [remaining =sample]} - (case (/.parse "" (dictionary.empty text.hash) source_code//size - remaining) - {.#Left error} - false + {.#Right [remaining =sample]} + (case (/.parse "" (dictionary.empty text.hash) source_code//size + remaining) + {.#Left error} + false - {.#Right [_ =other]} - (and (# code.equivalence = sample =sample) - (# code.equivalence = other =other))))))) + {.#Right [_ =other]} + (and (# code.equivalence = sample =sample) + (# code.equivalence = other =other))))))) ))) (def: comment_text^ @@ -125,16 +125,16 @@ [sample code^ comment comment^] (all _.and - (_.test "Can handle comments." - (case (let [source_code (format comment (%.code sample)) - source_code//size (text.size source_code)] - (/.parse "" (dictionary.empty text.hash) source_code//size - [location.dummy 0 source_code])) - {.#Left error} - false + (_.property "Can handle comments." + (case (let [source_code (format comment (%.code sample)) + source_code//size (text.size source_code)] + (/.parse "" (dictionary.empty text.hash) source_code//size + [location.dummy 0 source_code])) + {.#Left error} + false - {.#Right [_ parsed]} - (# code.equivalence = parsed sample))) + {.#Right [_ parsed]} + (# code.equivalence = parsed sample))) ))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/member.lux b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/member.lux index a7c72b262..ecd3cd328 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/member.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/member.lux @@ -35,7 +35,7 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right)))) + (_.coverage [/.format] + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/side.lux b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/side.lux index c5706bc14..f9156206e 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/side.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/access/side.lux @@ -35,7 +35,7 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.format] - (bit#= (# /.equivalence = left right) - (text#= (/.format left) (/.format right)))) + (_.coverage [/.format] + (bit#= (# /.equivalence = left right) + (text#= (/.format left) (/.format right)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/simple.lux index 98beda337..2a6910daa 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/simple.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/synthesis/simple.lux @@ -39,7 +39,7 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.format] - (bit#= (text#= (/.format left) (/.format right)) - (# /.equivalence = left right))) + (_.coverage [/.format] + (bit#= (text#= (/.format left) (/.format right)) + (# /.equivalence = left right))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive.lux b/stdlib/source/test/lux/tool/compiler/meta/archive.lux index d43e6a03b..1d0851bbf 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive.lux @@ -59,139 +59,139 @@ hash random.nat .let [key (/key.key signature content/0)]] (all _.and - (_.cover [/.has /.find] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - .let [entry [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry archive) - entry' (/.find module/0 archive)] - (in (same? entry entry'))) - (try.else false))) - (_.cover [/.module_is_only_reserved] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - entry' (/.find module/0 archive)] - (in false)) - (exception.otherwise (exception.match? /.module_is_only_reserved)))) - (_.cover [/.cannot_replace_document] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - .let [entry/0 [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty] - entry/1 [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/1)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry/0 archive) - archive (/.has module/0 entry/1 archive)] - (in false)) - (exception.otherwise (exception.match? /.cannot_replace_document)))) - (_.cover [/.module_must_be_reserved_before_it_can_be_added] - (|> (do try.monad - [.let [entry [/.#module [/module.#id 0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry /.empty)] - (in false)) - (exception.otherwise (exception.match? /.module_must_be_reserved_before_it_can_be_added)))) - (_.cover [/.archived?] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - .let [pre (/.archived? archive module/0) - entry [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry archive) - .let [post (/.archived? archive module/0)]] - (in (and (not pre) post))) - (try.else false))) - (_.cover [/.unknown_document] - (and (|> (do try.monad - [_ (/.id module/0 /.empty)] - (in false)) - (exception.otherwise (exception.match? /.unknown_document))) - (|> (do try.monad - [_ (/.find module/0 /.empty)] - (in false)) - (exception.otherwise (exception.match? /.unknown_document))))) - (_.cover [/.archived] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - .let [pre (/.archived archive) - entry [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry archive) - .let [post (/.archived archive) - (open "list#[0]") (list.equivalence text.equivalence)]] - (in (and (list#= (list) pre) - (list#= (list module/0) post)))) - (try.else false))) - (_.cover [/.entries] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - .let [pre (/.entries archive) - entry [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry archive)] - (in (and (list.empty? pre) - (case (/.entries archive) - (pattern (list [module/0' @module/0' entry'])) - (and (same? module/0 module/0') - (same? @module/0 @module/0') - (same? entry entry')) + (_.coverage [/.has /.find] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + .let [entry [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry archive) + entry' (/.find module/0 archive)] + (in (same? entry entry'))) + (try.else false))) + (_.coverage [/.module_is_only_reserved] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + entry' (/.find module/0 archive)] + (in false)) + (exception.otherwise (exception.match? /.module_is_only_reserved)))) + (_.coverage [/.cannot_replace_document] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + .let [entry/0 [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty] + entry/1 [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/1)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry/0 archive) + archive (/.has module/0 entry/1 archive)] + (in false)) + (exception.otherwise (exception.match? /.cannot_replace_document)))) + (_.coverage [/.module_must_be_reserved_before_it_can_be_added] + (|> (do try.monad + [.let [entry [/.#module [/module.#id 0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry /.empty)] + (in false)) + (exception.otherwise (exception.match? /.module_must_be_reserved_before_it_can_be_added)))) + (_.coverage [/.archived?] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + .let [pre (/.archived? archive module/0) + entry [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry archive) + .let [post (/.archived? archive module/0)]] + (in (and (not pre) post))) + (try.else false))) + (_.coverage [/.unknown_document] + (and (|> (do try.monad + [_ (/.id module/0 /.empty)] + (in false)) + (exception.otherwise (exception.match? /.unknown_document))) + (|> (do try.monad + [_ (/.find module/0 /.empty)] + (in false)) + (exception.otherwise (exception.match? /.unknown_document))))) + (_.coverage [/.archived] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + .let [pre (/.archived archive) + entry [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry archive) + .let [post (/.archived archive) + (open "list#[0]") (list.equivalence text.equivalence)]] + (in (and (list#= (list) pre) + (list#= (list module/0) post)))) + (try.else false))) + (_.coverage [/.entries] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + .let [pre (/.entries archive) + entry [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry archive)] + (in (and (list.empty? pre) + (case (/.entries archive) + (pattern (list [module/0' @module/0' entry'])) + (and (same? module/0 module/0') + (same? @module/0 @module/0') + (same? entry entry')) - _ - false)))) - (try.else false))) - (_.cover [/.export /.import] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - [@module/1 archive] (/.reserve module/1 archive) - .let [entry/0 [/.#module [/module.#id @module/0 - /module.#descriptor (..descriptor module/0 hash) - /module.#document (/document.document key content/0)] - /.#output sequence.empty - /.#registry /registry.empty] - entry/1 [/.#module [/module.#id @module/1 - /module.#descriptor (..descriptor module/1 hash) - /module.#document (/document.document key content/1)] - /.#output sequence.empty - /.#registry /registry.empty]] - archive (/.has module/0 entry/0 archive) - archive (/.has module/1 entry/1 archive) - .let [pre (/.reserved archive)] - archive (|> archive - (/.export version) - (/.import version)) - .let [post (/.reserved archive)]] - (in (set#= (set.of_list text.hash pre) - (set.of_list text.hash post)))) - (try.else false))) - (_.cover [/.version_mismatch] - (|> (do try.monad - [archive (|> /.empty - (/.export version) - (/.import fake_version))] - (in false)) - (exception.otherwise (exception.match? /.version_mismatch)))) + _ + false)))) + (try.else false))) + (_.coverage [/.export /.import] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + [@module/1 archive] (/.reserve module/1 archive) + .let [entry/0 [/.#module [/module.#id @module/0 + /module.#descriptor (..descriptor module/0 hash) + /module.#document (/document.document key content/0)] + /.#output sequence.empty + /.#registry /registry.empty] + entry/1 [/.#module [/module.#id @module/1 + /module.#descriptor (..descriptor module/1 hash) + /module.#document (/document.document key content/1)] + /.#output sequence.empty + /.#registry /registry.empty]] + archive (/.has module/0 entry/0 archive) + archive (/.has module/1 entry/1 archive) + .let [pre (/.reserved archive)] + archive (|> archive + (/.export version) + (/.import version)) + .let [post (/.reserved archive)]] + (in (set#= (set.of_list text.hash pre) + (set.of_list text.hash post)))) + (try.else false))) + (_.coverage [/.version_mismatch] + (|> (do try.monad + [archive (|> /.empty + (/.export version) + (/.import fake_version))] + (in false)) + (exception.otherwise (exception.match? /.version_mismatch)))) ))) (def: .public test @@ -207,44 +207,44 @@ hash random.nat .let [key (/key.key signature content/0)]]) (all _.and - (_.cover [/.empty] - (list.empty? (/.entries /.empty))) - (_.cover [/.reserve /.id] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - [@module/1 archive] (/.reserve module/1 archive) - @module/0' (/.id module/0 archive) - @module/1' (/.id module/1 archive)] - (in (and (same? @module/0 @module/0') - (same? @module/1 @module/1')))) - (try.else false))) - (_.cover [/.reserved] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - [@module/1 archive] (/.reserve module/1 archive)] - (in (set#= (set.of_list text.hash (list module/0 module/1)) - (set.of_list text.hash (/.reserved archive))))) - (try.else false))) - (_.cover [/.reservations] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - [@module/1 archive] (/.reserve module/1 archive) - .let [hash (product.hash text.hash n.hash)]] - (in (set#= (set.of_list hash (list [module/0 @module/0] [module/1 @module/1])) - (set.of_list hash (/.reservations archive))))) - (try.else false))) - (_.cover [/.module_has_already_been_reserved] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty) - _ (/.reserve module/0 archive)] - (in false)) - (exception.otherwise (exception.match? /.module_has_already_been_reserved)))) - (_.cover [/.reserved?] - (|> (do try.monad - [[@module/0 archive] (/.reserve module/0 /.empty)] - (in (and (/.reserved? archive module/0) - (not (/.reserved? archive module/1))))) - (try.else false))) + (_.coverage [/.empty] + (list.empty? (/.entries /.empty))) + (_.coverage [/.reserve /.id] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + [@module/1 archive] (/.reserve module/1 archive) + @module/0' (/.id module/0 archive) + @module/1' (/.id module/1 archive)] + (in (and (same? @module/0 @module/0') + (same? @module/1 @module/1')))) + (try.else false))) + (_.coverage [/.reserved] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + [@module/1 archive] (/.reserve module/1 archive)] + (in (set#= (set.of_list text.hash (list module/0 module/1)) + (set.of_list text.hash (/.reserved archive))))) + (try.else false))) + (_.coverage [/.reservations] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + [@module/1 archive] (/.reserve module/1 archive) + .let [hash (product.hash text.hash n.hash)]] + (in (set#= (set.of_list hash (list [module/0 @module/0] [module/1 @module/1])) + (set.of_list hash (/.reservations archive))))) + (try.else false))) + (_.coverage [/.module_has_already_been_reserved] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty) + _ (/.reserve module/0 archive)] + (in false)) + (exception.otherwise (exception.match? /.module_has_already_been_reserved)))) + (_.coverage [/.reserved?] + (|> (do try.monad + [[@module/0 archive] (/.reserve module/0 /.empty)] + (in (and (/.reserved? archive module/0) + (not (/.reserved? archive module/1))))) + (try.else false))) (_.for [/.Entry] ..test|entry) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/key.lux index 5d9457c91..ff80c5289 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/key.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/key.lux @@ -19,9 +19,9 @@ [expected //signature.random document random.nat] (all _.and - (_.cover [/.key /.signature] - (|> document - (/.key expected) - /.signature - (same? expected))) + (_.coverage [/.key /.signature] + (|> document + (/.key expected) + /.signature + (same? expected))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module.lux index f86ab62d6..5251a1c86 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/module.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module.lux @@ -35,8 +35,8 @@ (<| (_.covering /._) (_.for [/.Module]) (all _.and - (_.cover [/.ID /.runtime] - (n.= 0 /.runtime)) + (_.coverage [/.ID /.runtime] + (n.= 0 /.runtime)) /document.test /descriptor.test diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux index 6de17ec32..446a91717 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/descriptor.lux @@ -48,12 +48,12 @@ ($equivalence.spec /.equivalence (..random 1))) (_.for [/.Module] - (_.cover [/.runtime] - (text#= "" /.runtime))) - (_.cover [/.writer /.parser] - (|> expected - (binary.result /.writer) - (<binary>.result /.parser) - (try#each (|>> (# /.equivalence = (has /.#state {.#Cached} expected)))) - (try.else false))) + (_.coverage [/.runtime] + (text#= "" /.runtime))) + (_.coverage [/.writer /.parser] + (|> expected + (binary.result /.writer) + (<binary>.result /.parser) + (try#each (|>> (# /.equivalence = (has /.#state {.#Cached} expected)))) + (try.else false))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux index 182b127f4..289ab40fd 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/module/document.lux @@ -37,62 +37,62 @@ key/1 (/key.key signature/1 0)] expected random.nat] (all _.and - (_.cover [/.document /.content] - (|> expected - (/.document key/0) - (/.content key/0) - (try#each (same? expected)) - (try.else false))) - (_.cover [/.signature] - (|> expected - (/.document key/0) - /.signature - (same? signature/0))) - (_.cover [/.marked?] - (and (|> expected - (/.document key/0) - (/.marked? key/0) - (pipe.case - {try.#Success it} true - {try.#Failure error} false)) - (|> expected - (/.document key/0) - (/.marked? key/1) - (pipe.case - {try.#Success it} false - {try.#Failure error} true)))) - (_.cover [/.invalid_signature] - (and (|> expected - (/.document key/0) - (/.content key/1) - (pipe.case - {try.#Success it} - false - - {try.#Failure error} - (exception.match? /.invalid_signature error))) - (|> expected - (/.document key/0) - (/.marked? key/1) - (pipe.case - {try.#Success it} - false - - {try.#Failure error} - (exception.match? /.invalid_signature error))))) - (_.cover [/.writer /.parser] - (|> expected - (/.document key/0) - (binaryF.result (/.writer binaryF.nat)) - (<binary>.result (/.parser key/0 <binary>.nat)) - (pipe.case - {try.#Success it} - (and (/signature#= signature/0 (/.signature it)) - (|> it - (/.content key/0) - (try#each (nat.= expected)) - (try.else false))) - - {try.#Failure error} - false))) + (_.coverage [/.document /.content] + (|> expected + (/.document key/0) + (/.content key/0) + (try#each (same? expected)) + (try.else false))) + (_.coverage [/.signature] + (|> expected + (/.document key/0) + /.signature + (same? signature/0))) + (_.coverage [/.marked?] + (and (|> expected + (/.document key/0) + (/.marked? key/0) + (pipe.case + {try.#Success it} true + {try.#Failure error} false)) + (|> expected + (/.document key/0) + (/.marked? key/1) + (pipe.case + {try.#Success it} false + {try.#Failure error} true)))) + (_.coverage [/.invalid_signature] + (and (|> expected + (/.document key/0) + (/.content key/1) + (pipe.case + {try.#Success it} + false + + {try.#Failure error} + (exception.match? /.invalid_signature error))) + (|> expected + (/.document key/0) + (/.marked? key/1) + (pipe.case + {try.#Success it} + false + + {try.#Failure error} + (exception.match? /.invalid_signature error))))) + (_.coverage [/.writer /.parser] + (|> expected + (/.document key/0) + (binaryF.result (/.writer binaryF.nat)) + (<binary>.result (/.parser key/0 <binary>.nat)) + (pipe.case + {try.#Success it} + (and (/signature#= signature/0 (/.signature it)) + (|> it + (/.content key/0) + (try#each (nat.= expected)) + (try.else false))) + + {try.#Failure error} + false))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux index c097d5190..1e8c54fba 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/registry.lux @@ -62,54 +62,54 @@ (random.set text.hash expected_amount) (# ! each set.list))] (`` (all _.and - (_.cover [/.empty] - (|> /.empty - /.artifacts - sequence.size - (n.= 0))) - (_.cover [/.resource] - (let [[@it registry] (/.resource mandatory? expected_dependencies /.empty)] - (case (sequence.list (/.artifacts registry)) - (pattern (list [artifact actual_dependencies])) - (and (same? @it (the artifact.#id artifact)) - (same? mandatory? (the artifact.#mandatory? artifact)) - (tagged? category.#Anonymous (the artifact.#category artifact)) - (same? expected_dependencies actual_dependencies)) + (_.coverage [/.empty] + (|> /.empty + /.artifacts + sequence.size + (n.= 0))) + (_.coverage [/.resource] + (let [[@it registry] (/.resource mandatory? expected_dependencies /.empty)] + (case (sequence.list (/.artifacts registry)) + (pattern (list [artifact actual_dependencies])) + (and (same? @it (the artifact.#id artifact)) + (same? mandatory? (the artifact.#mandatory? artifact)) + (tagged? category.#Anonymous (the artifact.#category artifact)) + (same? expected_dependencies actual_dependencies)) - _ - false))) + _ + false))) (~~ (template [<new> <expected>' <query> <tag> <wrong_new> <wrong_expected>'] - [(_.cover [<new> <query>] - (let [<expected> <expected>' - <wrong_expected> <wrong_expected>'] - (and (let [[@it registry] (<new> <expected> mandatory? expected_dependencies /.empty)] - (and (case (<query> registry) - (pattern (list actual_name)) + [(_.coverage [<new> <query>] + (let [<expected> <expected>' + <wrong_expected> <wrong_expected>'] + (and (let [[@it registry] (<new> <expected> mandatory? expected_dependencies /.empty)] + (and (case (<query> registry) + (pattern (list actual_name)) + (same? <expected> actual_name) + + _ + false) + (case (sequence.list (/.artifacts registry)) + (pattern (list [artifact actual_dependencies])) + (and (same? @it (the artifact.#id artifact)) + (same? mandatory? (the artifact.#mandatory? artifact)) + (case (the artifact.#category artifact) + {<tag> actual_name} (same? <expected> actual_name) _ false) - (case (sequence.list (/.artifacts registry)) - (pattern (list [artifact actual_dependencies])) - (and (same? @it (the artifact.#id artifact)) - (same? mandatory? (the artifact.#mandatory? artifact)) - (case (the artifact.#category artifact) - {<tag> actual_name} - (same? <expected> actual_name) - - _ - false) - (same? expected_dependencies actual_dependencies)) + (same? expected_dependencies actual_dependencies)) - _ - false))) - (let [[@it registry] (<wrong_new> <wrong_expected> mandatory? expected_dependencies /.empty)] - (case (<query> registry) - (pattern (list)) - true + _ + false))) + (let [[@it registry] (<wrong_new> <wrong_expected> mandatory? expected_dependencies /.empty)] + (case (<query> registry) + (pattern (list)) + true - _ - false)))))] + _ + false)))))] [/.definition (is category.Definition [expected_name {.#None}]) /.definitions category.#Definition /.analyser expected_name] [/.analyser expected_name /.analysers category.#Analyser /.synthesizer expected_name] @@ -118,63 +118,63 @@ [/.directive expected_name /.directives category.#Directive /.custom expected_name] [/.custom expected_name /.customs category.#Custom /.definition (is category.Definition [expected_name {.#None}])] )) - (_.cover [/.id] - (and (~~ (template [<new> <expected>' <name>] - [(let [<expected> <expected>' - [@expected registry] (<new> <expected> mandatory? expected_dependencies /.empty)] - (|> (/.id (<name> <expected>) registry) - (maybe#each (same? @expected)) - (maybe.else false)))] + (_.coverage [/.id] + (and (~~ (template [<new> <expected>' <name>] + [(let [<expected> <expected>' + [@expected registry] (<new> <expected> mandatory? expected_dependencies /.empty)] + (|> (/.id (<name> <expected>) registry) + (maybe#each (same? @expected)) + (maybe.else false)))] - [/.definition (is category.Definition [expected_name {.#None}]) product.left] - [/.analyser expected_name |>] - [/.synthesizer expected_name |>] - [/.generator expected_name |>] - [/.directive expected_name |>] - [/.custom expected_name |>] - )))) - (_.cover [/.artifacts] - (and (~~ (template [<new> <query> <equivalence> <$>] - [(let [expected/* (list#each <$> expected_names) - [ids registry] (is [(Sequence artifact.ID) /.Registry] - (list#mix (function (_ expected [ids registry]) - (let [[@new registry] (<new> expected mandatory? expected_dependencies registry)] - [(sequence.suffix @new ids) registry])) - [sequence.empty /.empty] - expected/*)) - it (/.artifacts registry)] - (and (n.= expected_amount (sequence.size it)) - (list.every? (function (_ [@it [it dependencies]]) - (same? @it (the artifact.#id it))) - (list.zipped_2 (sequence.list ids) (sequence.list it))) - (# (list.equivalence <equivalence>) = expected/* (<query> registry))))] + [/.definition (is category.Definition [expected_name {.#None}]) product.left] + [/.analyser expected_name |>] + [/.synthesizer expected_name |>] + [/.generator expected_name |>] + [/.directive expected_name |>] + [/.custom expected_name |>] + )))) + (_.coverage [/.artifacts] + (and (~~ (template [<new> <query> <equivalence> <$>] + [(let [expected/* (list#each <$> expected_names) + [ids registry] (is [(Sequence artifact.ID) /.Registry] + (list#mix (function (_ expected [ids registry]) + (let [[@new registry] (<new> expected mandatory? expected_dependencies registry)] + [(sequence.suffix @new ids) registry])) + [sequence.empty /.empty] + expected/*)) + it (/.artifacts registry)] + (and (n.= expected_amount (sequence.size it)) + (list.every? (function (_ [@it [it dependencies]]) + (same? @it (the artifact.#id it))) + (list.zipped_2 (sequence.list ids) (sequence.list it))) + (# (list.equivalence <equivalence>) = expected/* (<query> registry))))] - [/.definition /.definitions category.definition_equivalence (is (-> Text category.Definition) - (function (_ it) - [it {.#None}]))] - [/.analyser /.analysers text.equivalence (|>>)] - [/.synthesizer /.synthesizers text.equivalence (|>>)] - [/.generator /.generators text.equivalence (|>>)] - [/.directive /.directives text.equivalence (|>>)] - [/.custom /.customs text.equivalence (|>>)] - )))) - (_.cover [/.writer /.parser] - (and (~~ (template [<new> <expected>' <name>] - [(let [<expected> <expected>' - [@expected before] (<new> <expected> mandatory? expected_dependencies /.empty)] - (|> before - (binary.result /.writer) - (<binary>.result /.parser) - (try#each (|>> (/.id (<name> <expected>)) - (maybe#each (same? @expected)) - (maybe.else false))) - (try.else false)))] + [/.definition /.definitions category.definition_equivalence (is (-> Text category.Definition) + (function (_ it) + [it {.#None}]))] + [/.analyser /.analysers text.equivalence (|>>)] + [/.synthesizer /.synthesizers text.equivalence (|>>)] + [/.generator /.generators text.equivalence (|>>)] + [/.directive /.directives text.equivalence (|>>)] + [/.custom /.customs text.equivalence (|>>)] + )))) + (_.coverage [/.writer /.parser] + (and (~~ (template [<new> <expected>' <name>] + [(let [<expected> <expected>' + [@expected before] (<new> <expected> mandatory? expected_dependencies /.empty)] + (|> before + (binary.result /.writer) + (<binary>.result /.parser) + (try#each (|>> (/.id (<name> <expected>)) + (maybe#each (same? @expected)) + (maybe.else false))) + (try.else false)))] - [/.definition (is category.Definition [expected_name {.#None}]) product.left] - [/.analyser expected_name |>] - [/.synthesizer expected_name |>] - [/.generator expected_name |>] - [/.directive expected_name |>] - [/.custom expected_name |>] - )))) + [/.definition (is category.Definition [expected_name {.#None}]) product.left] + [/.analyser expected_name |>] + [/.synthesizer expected_name |>] + [/.generator expected_name |>] + [/.directive expected_name |>] + [/.custom expected_name |>] + )))) ))))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux index 7981c04c1..7321e07da 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/signature.lux @@ -42,15 +42,15 @@ (do random.monad [left ..random right ..random] - (_.cover [/.description] - (bit#= (# /.equivalence = left right) - (text#= (/.description left) (/.description right))))) + (_.coverage [/.description] + (bit#= (# /.equivalence = left right) + (text#= (/.description left) (/.description right))))) (do random.monad [expected ..random] - (_.cover [/.writer /.parser] - (|> expected - (binaryF.result /.writer) - (<binary>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false)))) + (_.coverage [/.writer /.parser] + (|> expected + (binaryF.result /.writer) + (<binary>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false)))) ))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/test/lux/tool/compiler/meta/archive/unit.lux index 0bda3ebc3..fedec7da6 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/archive/unit.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/archive/unit.lux @@ -31,6 +31,6 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.none] - (set.empty? /.none)) + (_.coverage [/.none] + (set.empty? /.none)) ))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache.lux b/stdlib/source/test/lux/tool/compiler/meta/cache.lux index 41e6a00e9..27e3c1ded 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache.lux @@ -36,16 +36,16 @@ outcome (/.enable! ! fs context) post/0 (# fs directory? (/.path fs context)) post/1 (/.enabled? fs context)] - (_.cover' [/.path /.enabled? /.enable!] - (and (not pre/0) - (not pre/1) - - (case outcome - {try.#Success _} true - {try.#Failure _} false) - - post/0 - post/1)))) + (_.coverage' [/.path /.enabled? /.enable!] + (and (not pre/0) + (not pre/1) + + (case outcome + {try.#Success _} true + {try.#Failure _} false) + + post/0 + post/1)))) /archive.test /module.test diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache/archive.lux b/stdlib/source/test/lux/tool/compiler/meta/cache/archive.lux index f7be805d6..061dda399 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache/archive.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache/archive.lux @@ -72,13 +72,13 @@ cached? (/.cache! fs context archive) actual (# fs read (/.descriptor fs context)) post/0 (# fs file? (/.descriptor fs context))] - (_.cover' [/.descriptor /.cache!] - (and (not pre/0) - (|> (do try.monad - [_ enabled? - _ cached?] - actual) - (try#each (binary#= expected)) - (try.else false)) - post/0)))) + (_.coverage' [/.descriptor /.cache!] + (and (not pre/0) + (|> (do try.monad + [_ enabled? + _ cached?] + actual) + (try#each (binary#= expected)) + (try.else false)) + post/0)))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache/artifact.lux b/stdlib/source/test/lux/tool/compiler/meta/cache/artifact.lux index b27211525..319a19d7a 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache/artifact.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache/artifact.lux @@ -41,13 +41,13 @@ write! (/.cache! fs context @module @artifact expected) post (# fs file? (/.path fs context @module @artifact)) read! (/.cache fs context @module @artifact)] - (_.cover' [/.path /.cache! /.cache] - (and (not pre) - (case write! - {try.#Success _} true - {try.#Failure _} false) - post - (case read! - {try.#Success actual} (binary#= expected actual) - {try.#Failure _} false))))) + (_.coverage' [/.path /.cache! /.cache] + (and (not pre) + (case write! + {try.#Success _} true + {try.#Failure _} false) + post + (case read! + {try.#Success actual} (binary#= expected actual) + {try.#Failure _} false))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache/module.lux b/stdlib/source/test/lux/tool/compiler/meta/cache/module.lux index 6605bf05e..7923e4929 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache/module.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache/module.lux @@ -60,16 +60,16 @@ outcome (/.enable! ! fs context @module) post/0 (# fs directory? (/.path fs context @module)) post/1 (/.enabled? fs context @module)] - (_.cover' [/.path /.enabled? /.enable!] - (and (not pre/0) - (not pre/1) - - (case outcome - {try.#Success _} true - {try.#Failure _} false) - - post/0 - post/1)))) + (_.coverage' [/.path /.enabled? /.enable!] + (and (not pre/0) + (not pre/1) + + (case outcome + {try.#Success _} true + {try.#Failure _} false) + + post/0 + post/1)))) (in (do [! async.monad] [.let [/ "/" fs (file.mock /)] @@ -78,17 +78,17 @@ outcome (/.enable! ! (..bad fs) context @module) post/0 (# fs directory? (/.path fs context @module)) post/1 (/.enabled? fs context @module)] - (_.cover' [/.cannot_enable] - (and (not pre/0) - (not pre/1) - - (case outcome - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_enable error)) - - (not post/0) - (not post/1))))) + (_.coverage' [/.cannot_enable] + (and (not pre/0) + (not pre/1) + + (case outcome + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_enable error)) + + (not post/0) + (not post/1))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux index d84c092e3..419b247c1 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cache/purge.lux @@ -67,53 +67,53 @@ (all _.and (_.for [/.Cache] (all _.and - (_.cover [/.valid?] - (and (/.valid? descriptor input) - (not (/.valid? descriptor (has ////.#module source_code input))) - (not (/.valid? descriptor (has ////.#file source_code input))) - (not (/.valid? descriptor (revised ////.#hash ++ input))))) + (_.coverage [/.valid?] + (and (/.valid? descriptor input) + (not (/.valid? descriptor (has ////.#module source_code input))) + (not (/.valid? descriptor (has ////.#file source_code input))) + (not (/.valid? descriptor (revised ////.#hash ++ input))))) )) (_.for [/.Purge] (all _.and - (_.cover [/.purge] - (and (dictionary.empty? (/.purge (list) (list))) - (let [order (is (dependency.Order Nat) - (list [name/0 id/0 - [archive.#module module/0 - archive.#output (sequence.sequence) - archive.#registry registry.empty]]))] - (and (let [cache (is (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty]))] - (dictionary.empty? (/.purge cache order))) - (let [cache (is (List /.Cache) - (list [#0 name/0 id/0 module/0 registry.empty]))] - (dictionary.key? (/.purge cache order) name/0)))) - (let [order (is (dependency.Order Nat) - (list [name/0 id/0 - [archive.#module module/0 - archive.#output (sequence.sequence) - archive.#registry registry.empty]] - [name/1 id/1 - [archive.#module module/1 - archive.#output (sequence.sequence) - archive.#registry registry.empty]]))] - (and (let [cache (is (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty] - [#1 name/1 id/1 module/1 registry.empty])) - purge (/.purge cache order)] - (dictionary.empty? purge)) - (let [cache (is (List /.Cache) - (list [#1 name/0 id/0 module/0 registry.empty] - [#0 name/1 id/1 module/1 registry.empty])) - purge (/.purge cache order)] - (and (not (dictionary.key? (/.purge cache order) name/0)) - (dictionary.key? (/.purge cache order) name/1))) - (let [cache (is (List /.Cache) - (list [#0 name/0 id/0 module/0 registry.empty] - [#1 name/1 id/1 module/1 registry.empty])) - purge (/.purge cache order)] - (and (dictionary.key? (/.purge cache order) name/0) - (dictionary.key? (/.purge cache order) name/1))))))) + (_.coverage [/.purge] + (and (dictionary.empty? (/.purge (list) (list))) + (let [order (is (dependency.Order Nat) + (list [name/0 id/0 + [archive.#module module/0 + archive.#output (sequence.sequence) + archive.#registry registry.empty]]))] + (and (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty]))] + (dictionary.empty? (/.purge cache order))) + (let [cache (is (List /.Cache) + (list [#0 name/0 id/0 module/0 registry.empty]))] + (dictionary.key? (/.purge cache order) name/0)))) + (let [order (is (dependency.Order Nat) + (list [name/0 id/0 + [archive.#module module/0 + archive.#output (sequence.sequence) + archive.#registry registry.empty]] + [name/1 id/1 + [archive.#module module/1 + archive.#output (sequence.sequence) + archive.#registry registry.empty]]))] + (and (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty] + [#1 name/1 id/1 module/1 registry.empty])) + purge (/.purge cache order)] + (dictionary.empty? purge)) + (let [cache (is (List /.Cache) + (list [#1 name/0 id/0 module/0 registry.empty] + [#0 name/1 id/1 module/1 registry.empty])) + purge (/.purge cache order)] + (and (not (dictionary.key? (/.purge cache order) name/0)) + (dictionary.key? (/.purge cache order) name/1))) + (let [cache (is (List /.Cache) + (list [#0 name/0 id/0 module/0 registry.empty] + [#1 name/1 id/1 module/1 registry.empty])) + purge (/.purge cache order)] + (and (dictionary.key? (/.purge cache order) name/0) + (dictionary.key? (/.purge cache order) name/1))))))) (in (do [! async.monad] [_ (//module.enable! ! fs context id/0) .let [dir (//module.path fs context id/0) @@ -124,18 +124,18 @@ pre (# fs directory_files dir) _ (/.purge! fs context id/0) post (# fs directory_files dir)] - (_.cover' [/.purge!] - (<| (try.else false) - (do try.monad - [pre pre] - (in (and (# set.equivalence = - (set.of_list text.hash pre) - (set.of_list text.hash (list file/0 file/1))) - (case post - {try.#Failure error} - (exception.match? file.cannot_find_directory error) + (_.coverage' [/.purge!] + (<| (try.else false) + (do try.monad + [pre pre] + (in (and (# set.equivalence = + (set.of_list text.hash pre) + (set.of_list text.hash (list file/0 file/1))) + (case post + {try.#Failure error} + (exception.match? file.cannot_find_directory error) - success - false)))))))) + success + false)))))))) )) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cli.lux b/stdlib/source/test/lux/tool/compiler/meta/cli.lux index b6eca2b43..657015461 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cli.lux @@ -58,18 +58,18 @@ (_.for [/.Compilation] (`` (all _.and (~~ (template [<type> <slot> <?>] - [(_.cover [<type>] - (|> (partial_list "build" compilation') - (<cli>.result /.service) - (try#each (|>> (pipe.case - {/.#Compilation it} - (|> it - (the <slot>) - <?>) - - _ - false))) - (try.else false)))] + [(_.coverage [<type>] + (|> (partial_list "build" compilation') + (<cli>.result /.service) + (try#each (|>> (pipe.case + {/.#Compilation it} + (|> it + (the <slot>) + <?>) + + _ + false))) + (try.else false)))] [/.Host_Dependency /.#host_dependencies (list#= host_dependencies)] [/.Library /.#libraries (list#= libraries)] @@ -80,65 +80,65 @@ [configuration.Configuration /.#configuration (configuration#= configuration)] )) ))) - (_.cover [/.Interpretation] - (`` (and (~~ (template [<slot> <?>] - [(|> (partial_list "repl" compilation') - (<cli>.result /.service) - (try#each (|>> (pipe.case - {/.#Interpretation it} - (|> it - (the <slot>) - <?>) - - _ - false))) - (try.else false))] + (_.coverage [/.Interpretation] + (`` (and (~~ (template [<slot> <?>] + [(|> (partial_list "repl" compilation') + (<cli>.result /.service) + (try#each (|>> (pipe.case + {/.#Interpretation it} + (|> it + (the <slot>) + <?>) + + _ + false))) + (try.else false))] - [/.#host_dependencies (list#= host_dependencies)] - [/.#libraries (list#= libraries)] - [/.#compilers (# (list.equivalence /compiler.equivalence) = compilers)] - [/.#sources (list#= sources)] - [/.#target (same? target)] - [/.#module (same? module)] - [/.#configuration (configuration#= configuration)] - ))))) - (_.cover [/.Export] - (`` (and (~~ (template [<side> <?>] - [(|> (partial_list "export" export) - (<cli>.result /.service) - (try#each (|>> (pipe.case - {/.#Export it} - (|> it - <side> - <?>) - - _ - false))) - (try.else false))] + [/.#host_dependencies (list#= host_dependencies)] + [/.#libraries (list#= libraries)] + [/.#compilers (# (list.equivalence /compiler.equivalence) = compilers)] + [/.#sources (list#= sources)] + [/.#target (same? target)] + [/.#module (same? module)] + [/.#configuration (configuration#= configuration)] + ))))) + (_.coverage [/.Export] + (`` (and (~~ (template [<side> <?>] + [(|> (partial_list "export" export) + (<cli>.result /.service) + (try#each (|>> (pipe.case + {/.#Export it} + (|> it + <side> + <?>) + + _ + false))) + (try.else false))] - [product.left (list#= sources)] - [product.right (same? target)] - ))))) - (_.cover [/.target] - (`` (and (~~ (template [<it>] - [(same? target (/.target <it>))] + [product.left (list#= sources)] + [product.right (same? target)] + ))))) + (_.coverage [/.target] + (`` (and (~~ (template [<it>] + [(same? target (/.target <it>))] - [{/.#Compilation [/.#host_dependencies host_dependencies - /.#libraries libraries - /.#compilers compilers - /.#sources sources - /.#target target - /.#module module - /.#configuration configuration]}] - [{/.#Interpretation [/.#host_dependencies host_dependencies - /.#libraries libraries - /.#compilers compilers - /.#sources sources - /.#target target - /.#module module - /.#configuration configuration]}] - [{/.#Export [sources target]}] - ))))) + [{/.#Compilation [/.#host_dependencies host_dependencies + /.#libraries libraries + /.#compilers compilers + /.#sources sources + /.#target target + /.#module module + /.#configuration configuration]}] + [{/.#Interpretation [/.#host_dependencies host_dependencies + /.#libraries libraries + /.#compilers compilers + /.#sources sources + /.#target target + /.#module module + /.#configuration configuration]}] + [{/.#Export [sources target]}] + ))))) $/compiler.test )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/cli/compiler.lux b/stdlib/source/test/lux/tool/compiler/meta/cli/compiler.lux index f9048293b..accb94da5 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/cli/compiler.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/cli/compiler.lux @@ -39,10 +39,10 @@ (_.for [/.equivalence] ($equivalence.spec /.equivalence ..random)) - (_.cover [/.format /.parser] - (|> expected - /.format - (<text>.result /.parser) - (try#each (# /.equivalence = expected)) - (try.else false))) + (_.coverage [/.format /.parser] + (|> expected + /.format + (<text>.result /.parser) + (try#each (# /.equivalence = expected)) + (try.else false))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/context.lux b/stdlib/source/test/lux/tool/compiler/meta/context.lux index 0641b4bcd..954f34791 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/context.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/context.lux @@ -34,23 +34,23 @@ (do [! random.monad] [target (random.lower_case 1)] (all _.and - (_.cover [/.js /.jvm /.lua /.python /.ruby] - (let [contexts (list (/.js target) - (/.jvm target) - (/.lua target) - (/.python target) - (/.ruby target)) - maximum (list.size contexts)] - (`` (and (~~ (template [<amount> <slot>] - [(|> contexts - (list#each (the <slot>)) - (set.of_list text.hash) - set.size - (n.= <amount>))] + (_.coverage [/.js /.jvm /.lua /.python /.ruby] + (let [contexts (list (/.js target) + (/.jvm target) + (/.lua target) + (/.python target) + (/.ruby target)) + maximum (list.size contexts)] + (`` (and (~~ (template [<amount> <slot>] + [(|> contexts + (list#each (the <slot>)) + (set.of_list text.hash) + set.size + (n.= <amount>))] - [maximum /.#host] - [maximum /.#host_module_extension] - [maximum /.#artifact_extension] - [1 /.#target] - )))))) + [maximum /.#host] + [maximum /.#host_module_extension] + [maximum /.#artifact_extension] + [1 /.#target] + )))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/export.lux b/stdlib/source/test/lux/tool/compiler/meta/export.lux index 46f139850..c2fb768b2 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/export.lux @@ -75,47 +75,47 @@ export_tar (# ! in (<binary>.result tar.parser export_tar))] (in [library_tar export_tar]))] (all _.and' - (_.cover' [/.library /.mode /.ownership] - (|> it - (try#each (|>> product.left - sequence.list - (pipe.case - (pattern (list {tar.#Normal [actual_path/0 when/0 mode/0 ownership/0 actual_content/0]} - {tar.#Normal [actual_path/1 when/1 mode/1 ownership/1 actual_content/1]})) - (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) - (same? /.mode mode/0) - (same? /.ownership ownership/0) - (binary#= content/0 (tar.data actual_content/0))) - (and (text#= file/1' (tar.from_path actual_path/1)) - (same? /.mode mode/1) - (same? /.ownership ownership/1) - (binary#= content/1 (tar.data actual_content/1))))] - (or <test> - (let [[[actual_path/0 actual_content/0] [actual_path/1 actual_content/1]] - [[actual_path/1 actual_content/1] [actual_path/0 actual_content/0]]] - <test>))) - - _ - false))) - (try.else false))) - (_.cover' [/.export /.file] - (|> it - (try#each (|>> product.right - sequence.list - (pipe.case - (pattern (list {tar.#Normal [actual_path/0 _ _ _ actual_content/0]} - {tar.#Normal [actual_path/1 _ _ _ actual_content/1]})) - (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) - (binary#= content/0 (tar.data actual_content/0))) - (and (text#= file/1' (tar.from_path actual_path/1)) - (binary#= content/1 (tar.data actual_content/1))))] - (or <test> - (let [[[actual_path/0 actual_content/0] [actual_path/1 actual_content/1]] - [[actual_path/1 actual_content/1] [actual_path/0 actual_content/0]]] - <test>))) - - _ - false))) - (try.else false))) + (_.coverage' [/.library /.mode /.ownership] + (|> it + (try#each (|>> product.left + sequence.list + (pipe.case + (pattern (list {tar.#Normal [actual_path/0 when/0 mode/0 ownership/0 actual_content/0]} + {tar.#Normal [actual_path/1 when/1 mode/1 ownership/1 actual_content/1]})) + (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) + (same? /.mode mode/0) + (same? /.ownership ownership/0) + (binary#= content/0 (tar.data actual_content/0))) + (and (text#= file/1' (tar.from_path actual_path/1)) + (same? /.mode mode/1) + (same? /.ownership ownership/1) + (binary#= content/1 (tar.data actual_content/1))))] + (or <test> + (let [[[actual_path/0 actual_content/0] [actual_path/1 actual_content/1]] + [[actual_path/1 actual_content/1] [actual_path/0 actual_content/0]]] + <test>))) + + _ + false))) + (try.else false))) + (_.coverage' [/.export /.file] + (|> it + (try#each (|>> product.right + sequence.list + (pipe.case + (pattern (list {tar.#Normal [actual_path/0 _ _ _ actual_content/0]} + {tar.#Normal [actual_path/1 _ _ _ actual_content/1]})) + (with_expansions [<test> (and (and (text#= file/0' (tar.from_path actual_path/0)) + (binary#= content/0 (tar.data actual_content/0))) + (and (text#= file/1' (tar.from_path actual_path/1)) + (binary#= content/1 (tar.data actual_content/1))))] + (or <test> + (let [[[actual_path/0 actual_content/0] [actual_path/1 actual_content/1]] + [[actual_path/1 actual_content/1] [actual_path/0 actual_content/0]]] + <test>))) + + _ + false))) + (try.else false))) ))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/meta/import.lux b/stdlib/source/test/lux/tool/compiler/meta/import.lux index a0710729f..1c59ed494 100644 --- a/stdlib/source/test/lux/tool/compiler/meta/import.lux +++ b/stdlib/source/test/lux/tool/compiler/meta/import.lux @@ -119,21 +119,21 @@ _ (# fs write library/0 library_content/0) _ (# fs write library/1 library_content/1)] (/.import fs (list library/0 library/1)))] - (_.cover' [/.import] - (and (|> it/0 - (try#each imported?) - (try.else false)) - (|> it/1 - (try#each imported?) - (try.else false)))))) + (_.coverage' [/.import] + (and (|> it/0 + (try#each imported?) + (try.else false)) + (|> it/1 + (try#each imported?) + (try.else false)))))) (in (do [! async.monad] [it (do (try.with !) [.let [fs (file.mock /)] _ (# fs write library/0 library_content) _ (/.import fs (list library/0 library/0))] (in false))] - (_.cover' [/.duplicate] - (exception.otherwise (exception.match? /.duplicate) it)))) + (_.coverage' [/.duplicate] + (exception.otherwise (exception.match? /.duplicate) it)))) (in (do [! async.monad] [it/0 (do (try.with !) [.let [fs (file.mock /)] @@ -150,8 +150,8 @@ _ (# fs write library/0 library_content/-2) _ (/.import fs (list library/0))] (in false))] - (_.cover' [/.useless_tar_entry] - (and (exception.otherwise (exception.match? /.useless_tar_entry) it/0) - (exception.otherwise (exception.match? /.useless_tar_entry) it/1) - (exception.otherwise (exception.match? /.useless_tar_entry) it/2))))) + (_.coverage' [/.useless_tar_entry] + (and (exception.otherwise (exception.match? /.useless_tar_entry) it/0) + (exception.otherwise (exception.match? /.useless_tar_entry) it/1) + (exception.otherwise (exception.match? /.useless_tar_entry) it/2))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/phase.lux b/stdlib/source/test/lux/tool/compiler/phase.lux index 26217bc46..dd956f90f 100644 --- a/stdlib/source/test/lux/tool/compiler/phase.lux +++ b/stdlib/source/test/lux/tool/compiler/phase.lux @@ -51,49 +51,49 @@ expected random.int expected_error (random.lower_case 1)] (all _.and - (_.cover [/.failure] - (|> (/.failure expected_error) - (/.result state) - (pipe.case {try.#Failure actual_error} - (same? expected_error actual_error) - - _ - false))) - (_.cover [/.lifted] - (and (|> (/.lifted {try.#Failure expected_error}) - (/.result state) - (pipe.case {try.#Failure actual_error} - (same? expected_error actual_error) - - _ - false)) - (|> (/.lifted {try.#Success expected}) - (# /.functor each (same? expected)) - (/.result state) - (try.else false)))) - (_.cover [/.except] - (|> (/.except ..oops []) - (/.result state) - (pipe.case {try.#Failure error} - (exception.match? ..oops error) - - _ - false))) - (_.cover [/.assertion] - (and (|> (/.assertion ..oops [] false) - (/.result state) - (pipe.case {try.#Failure error} - (exception.match? ..oops error) - - _ - false)) - (|> (/.assertion ..oops [] true) - (/.result state) - (pipe.case {try.#Success _} - true - - _ - false)))) + (_.coverage [/.failure] + (|> (/.failure expected_error) + (/.result state) + (pipe.case {try.#Failure actual_error} + (same? expected_error actual_error) + + _ + false))) + (_.coverage [/.lifted] + (and (|> (/.lifted {try.#Failure expected_error}) + (/.result state) + (pipe.case {try.#Failure actual_error} + (same? expected_error actual_error) + + _ + false)) + (|> (/.lifted {try.#Success expected}) + (# /.functor each (same? expected)) + (/.result state) + (try.else false)))) + (_.coverage [/.except] + (|> (/.except ..oops []) + (/.result state) + (pipe.case {try.#Failure error} + (exception.match? ..oops error) + + _ + false))) + (_.coverage [/.assertion] + (and (|> (/.assertion ..oops [] false) + (/.result state) + (pipe.case {try.#Failure error} + (exception.match? ..oops error) + + _ + false)) + (|> (/.assertion ..oops [] true) + (/.result state) + (pipe.case {try.#Success _} + true + + _ + false)))) ))) (def: test|state @@ -103,34 +103,34 @@ dummy random.nat expected random.int] (all _.and - (_.cover [/.state] - (|> /.state - (# /.functor each (same? state)) - (/.result state) - (try.else false))) - (_.cover [/.with] - (|> (do /.monad - [_ (/.with state)] - /.state) - (# /.functor each (same? state)) - (/.result dummy) - (try.else false))) - (_.cover [/.sub] - (|> (/.sub [(# n.hex encoded) - (function (_ new old) - (|> new (# n.hex decoded) (try.else dummy)))] - (do /.monad - [state/hex /.state] - (in (|> state - (# n.hex encoded) - (text#= state/hex))))) - (/.result' state) - (pipe.case {try.#Success [state' verdict]} - (and verdict - (n.= state state')) - - _ - false))) + (_.coverage [/.state] + (|> /.state + (# /.functor each (same? state)) + (/.result state) + (try.else false))) + (_.coverage [/.with] + (|> (do /.monad + [_ (/.with state)] + /.state) + (# /.functor each (same? state)) + (/.result dummy) + (try.else false))) + (_.coverage [/.sub] + (|> (/.sub [(# n.hex encoded) + (function (_ new old) + (|> new (# n.hex decoded) (try.else dummy)))] + (do /.monad + [state/hex /.state] + (in (|> state + (# n.hex encoded) + (text#= state/hex))))) + (/.result' state) + (pipe.case {try.#Success [state' verdict]} + (and verdict + (n.= state state')) + + _ + false))) ))) (def: test|operation @@ -144,23 +144,23 @@ (_.for [/.monad] ($monad.spec ..injection (..comparison state) /.monad)) - (_.cover [/.result] - (|> (# /.monad in expected) - (/.result state) - (pipe.case {try.#Success actual} - (same? expected actual) - - _ - false))) - (_.cover [/.result'] - (|> (# /.monad in expected) - (/.result' state) - (pipe.case {try.#Success [state' actual]} - (and (same? state state') - (same? expected actual)) - - _ - false))) + (_.coverage [/.result] + (|> (# /.monad in expected) + (/.result state) + (pipe.case {try.#Success actual} + (same? expected actual) + + _ + false))) + (_.coverage [/.result'] + (|> (# /.monad in expected) + (/.result' state) + (pipe.case {try.#Success [state' actual]} + (and (same? state state') + (same? expected actual)) + + _ + false))) ..test|state ..test|error ))) @@ -172,27 +172,27 @@ state/1 random.rev expected random.int] (all _.and - (_.cover [/.identity] - (|> (/.identity archive.empty expected) - (/.result state/0) - (try#each (same? expected)) - (try.else false))) - (_.cover [/.composite] - (let [phase (/.composite (is (/.Phase Nat Int Frac) - (function (_ archive input) - (# /.monad in (i.frac input)))) - (is (/.Phase Rev Frac Text) - (function (_ archive input) - (# /.monad in (%.frac input)))))] - (|> (phase archive.empty expected) - (/.result' [state/0 state/1]) - (pipe.case {try.#Success [[state/0' state/1'] actual]} - (and (text#= (%.frac (i.frac expected)) actual) - (same? state/0 state/0') - (same? state/1 state/1')) - - _ - false)))) + (_.coverage [/.identity] + (|> (/.identity archive.empty expected) + (/.result state/0) + (try#each (same? expected)) + (try.else false))) + (_.coverage [/.composite] + (let [phase (/.composite (is (/.Phase Nat Int Frac) + (function (_ archive input) + (# /.monad in (i.frac input)))) + (is (/.Phase Rev Frac Text) + (function (_ archive input) + (# /.monad in (%.frac input)))))] + (|> (phase archive.empty expected) + (/.result' [state/0 state/1]) + (pipe.case {try.#Success [[state/0' state/1'] actual]} + (and (text#= (%.frac (i.frac expected)) actual) + (same? state/0 state/0') + (same? state/1 state/1')) + + _ + false)))) ))) (def: .public test diff --git a/stdlib/source/test/lux/tool/compiler/reference.lux b/stdlib/source/test/lux/tool/compiler/reference.lux index 337baa5ee..e29fc64bf 100644 --- a/stdlib/source/test/lux/tool/compiler/reference.lux +++ b/stdlib/source/test/lux/tool/compiler/reference.lux @@ -50,46 +50,46 @@ ($hash.spec /.hash ..random)) (~~ (template [<tag>] - [(_.cover [<tag>] - (case (<tag> expected_register) - (pattern (<tag> actual_register)) - (n.= expected_register actual_register) + [(_.coverage [<tag>] + (case (<tag> expected_register) + (pattern (<tag> actual_register)) + (n.= expected_register actual_register) - _ - false))] + _ + false))] [/.local] [/.foreign] )) - (_.cover [/.variable /.self] - (and (# /.equivalence = (/.self) (/.variable (variable.self))) - (case (/.self) - (pattern (/.self)) - true - - _ - false) - (case (/.variable (variable.self)) - (pattern (/.self)) - true - - _ - false))) - (_.cover [/.constant] - (case (/.constant expected_constant) - (pattern (/.constant actual_constant)) - (symbol#= expected_constant actual_constant) + (_.coverage [/.variable /.self] + (and (# /.equivalence = (/.self) (/.variable (variable.self))) + (case (/.self) + (pattern (/.self)) + true + + _ + false) + (case (/.variable (variable.self)) + (pattern (/.self)) + true + + _ + false))) + (_.coverage [/.constant] + (case (/.constant expected_constant) + (pattern (/.constant actual_constant)) + (symbol#= expected_constant actual_constant) - _ - false)) - (_.cover [/.format] - (and (text#= (/.format (/.local expected_register)) - (variable.format {variable.#Local expected_register})) - (text#= (/.format (/.foreign expected_register)) - (variable.format {variable.#Foreign expected_register})) - (text#= (/.format (/.constant expected_constant)) - (%.symbol expected_constant)))) + _ + false)) + (_.coverage [/.format] + (and (text#= (/.format (/.local expected_register)) + (variable.format {variable.#Local expected_register})) + (text#= (/.format (/.foreign expected_register)) + (variable.format {variable.#Foreign expected_register})) + (text#= (/.format (/.constant expected_constant)) + (%.symbol expected_constant)))) /variable.test )))) diff --git a/stdlib/source/test/lux/tool/compiler/reference/variable.lux b/stdlib/source/test/lux/tool/compiler/reference/variable.lux index d88aa2c56..69db9b255 100644 --- a/stdlib/source/test/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/test/lux/tool/compiler/reference/variable.lux @@ -32,14 +32,14 @@ ($equivalence.spec /.equivalence ..random)) (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [/.self] - (case (/.self) - (pattern (/.self)) true - _ false)) - (_.cover [/.self?] - (/.self? (/.self))) + (_.coverage [/.self] + (case (/.self) + (pattern (/.self)) true + _ false)) + (_.coverage [/.self?] + (/.self? (/.self))) (_.for [/.Register] - (_.cover [/.format] - (not (text#= (/.format {/.#Local register}) - (/.format {/.#Foreign register}))))) + (_.coverage [/.format] + (not (text#= (/.format {/.#Local register}) + (/.format {/.#Foreign register}))))) )))) diff --git a/stdlib/source/test/lux/tool/compiler/version.lux b/stdlib/source/test/lux/tool/compiler/version.lux index 492b02fa7..f76f8651d 100644 --- a/stdlib/source/test/lux/tool/compiler/version.lux +++ b/stdlib/source/test/lux/tool/compiler/version.lux @@ -27,13 +27,13 @@ [this ..random that ..random] (`` (all _.and - (_.cover [/.format] - (bit#= (n.= this that) - (text#= (/.format this) (/.format that)))) + (_.coverage [/.format] + (bit#= (n.= this that) + (text#= (/.format this) (/.format that)))) (~~ (template [<level>] - [(_.cover [<level>] - (text.contains? (%.nat (<level> this)) - (/.format this)))] + [(_.coverage [<level>] + (text.contains? (%.nat (<level> this)) + (/.format this)))] [/.patch] [/.minor] diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux index d2e0fed2b..8fbc8a066 100644 --- a/stdlib/source/test/lux/type.lux +++ b/stdlib/source/test/lux/type.lux @@ -89,10 +89,10 @@ .let [namedT {.#Named symbol/0 anonymousT} aliasedT {.#Named symbol/1 namedT}]] (all _.and - (_.cover [/.de_aliased] - (# /.equivalence = namedT (/.de_aliased aliasedT))) - (_.cover [/.anonymous] - (# /.equivalence = anonymousT (/.anonymous aliasedT))))) + (_.coverage [/.de_aliased] + (# /.equivalence = namedT (/.de_aliased aliasedT))) + (_.coverage [/.anonymous] + (# /.equivalence = anonymousT (/.anonymous aliasedT))))) (do [! random.monad] [size (|> random.nat (# ! each (n.% 3))) members (|> (..random 0) @@ -109,24 +109,24 @@ (open "list#[0]") (list.equivalence /.equivalence)]] (`` (all _.and (~~ (template [<ctor> <dtor> <unit>] - [(_.cover [<ctor> <dtor>] - (let [flat (|> members <ctor> <dtor>)] - (or (list#= members flat) - (and (list#= (list) members) - (list#= (list <unit>) flat)))))] + [(_.coverage [<ctor> <dtor>] + (let [flat (|> members <ctor> <dtor>)] + (or (list#= members flat) + (and (list#= (list) members) + (list#= (list <unit>) flat)))))] [/.variant /.flat_variant Nothing] [/.tuple /.flat_tuple Any] )) ))) - (_.cover [/.applied] - (and (<| (maybe.else #0) - (do maybe.monad - [partial (/.applied (list Bit) Ann) - full (/.applied (list Int) partial)] - (in (# /.equivalence = full {.#Product Bit Int})))) - (|> (/.applied (list Bit) Text) - (pipe.case {.#None} #1 _ #0)))) + (_.coverage [/.applied] + (and (<| (maybe.else #0) + (do maybe.monad + [partial (/.applied (list Bit) Ann) + full (/.applied (list Int) partial)] + (in (# /.equivalence = full {.#Product Bit Int})))) + (|> (/.applied (list Bit) Text) + (pipe.case {.#None} #1 _ #0)))) (do [! random.monad] [size (|> random.nat (# ! each (n.% 3))) members (monad.all ! (list.repeated size (..random 0))) @@ -141,13 +141,13 @@ .let [(open "/#[0]") /.equivalence (open "list#[0]") (list.equivalence /.equivalence)]] (all _.and - (_.cover [/.function /.flat_function] - (let [[inputs output] (|> (/.function members extra) /.flat_function)] - (and (list#= members inputs) - (/#= extra output)))) - (_.cover [/.application /.flat_application] - (let [[tfunc tparams] (|> extra (/.application members) /.flat_application)] - (n.= (list.size members) (list.size tparams)))) + (_.coverage [/.function /.flat_function] + (let [[inputs output] (|> (/.function members extra) /.flat_function)] + (and (list#= members inputs) + (/#= extra output)))) + (_.coverage [/.application /.flat_application] + (let [[tfunc tparams] (|> extra (/.application members) /.flat_application)] + (n.= (list.size members) (list.size tparams)))) )) (do [! random.monad] [size (|> random.nat (# ! each (|>> (n.% 3) ++))) @@ -162,18 +162,18 @@ .let [(open "/#[0]") /.equivalence]] (`` (all _.and (~~ (template [<ctor> <dtor>] - [(_.cover [<ctor> <dtor>] - (let [[flat_size flat_body] (|> body_type (<ctor> size) <dtor>)] - (and (n.= size flat_size) - (/#= body_type flat_body))))] + [(_.coverage [<ctor> <dtor>] + (let [[flat_size flat_body] (|> body_type (<ctor> size) <dtor>)] + (and (n.= size flat_size) + (/#= body_type flat_body))))] [/.univ_q /.flat_univ_q] [/.ex_q /.flat_ex_q] )) - (_.cover [/.quantified?] - (and (not (/.quantified? body_type)) - (|> body_type (/.univ_q size) /.quantified?) - (|> body_type (/.ex_q size) /.quantified?))) + (_.coverage [/.quantified?] + (and (not (/.quantified? body_type)) + (|> body_type (/.univ_q size) /.quantified?) + (|> body_type (/.ex_q size) /.quantified?))) ))) (do [! random.monad] [depth (|> random.nat (# ! each (|>> (n.% 3) ++))) @@ -187,69 +187,69 @@ #1)))) .let [(open "/#[0]") /.equivalence]] (all _.and - (_.cover [/.array /.flat_array] - (let [[flat_depth flat_element] (|> element_type (/.array depth) /.flat_array)] - (and (n.= depth flat_depth) - (/#= element_type flat_element)))) - (_.cover [/.array?] - (and (not (/.array? element_type)) - (/.array? (/.array depth element_type)))) + (_.coverage [/.array /.flat_array] + (let [[flat_depth flat_element] (|> element_type (/.array depth) /.flat_array)] + (and (n.= depth flat_depth) + (/#= element_type flat_element)))) + (_.coverage [/.array?] + (and (not (/.array? element_type)) + (/.array? (/.array depth element_type)))) )) - (_.cover [/.by_example] - (let [example (is (Maybe Nat) - {.#None})] - (/#= (.type (List Nat)) - (/.by_example [a] - (Maybe a) - example - - (List a))))) + (_.coverage [/.by_example] + (let [example (is (Maybe Nat) + {.#None})] + (/#= (.type (List Nat)) + (/.by_example [a] + (Maybe a) + example + + (List a))))) (do random.monad [sample random.nat] - (_.cover [/.log!] - (exec - (/.log! sample) - true))) + (_.coverage [/.log!] + (exec + (/.log! sample) + true))) (do random.monad [left random.nat right (random.lower_case 1) .let [left,right [left right]]] - (_.cover [/.as] - (|> left,right - (/.as [l r] (And l r) (Or l r)) - (/.as [l r] (Or l r) (And l r)) - (same? left,right)))) + (_.coverage [/.as] + (|> left,right + (/.as [l r] (And l r) (Or l r)) + (/.as [l r] (Or l r) (And l r)) + (same? left,right)))) (do random.monad [expected random.nat] - (_.cover [/.sharing] - (n.= expected - (/.sharing [a] - (I64 a) - expected + (_.coverage [/.sharing] + (n.= expected + (/.sharing [a] + (I64 a) + expected - (I64 a) - (.i64 expected))))) + (I64 a) + (.i64 expected))))) (do random.monad [expected_left random.nat expected_right random.nat] - (_.cover [/.let] - (let [[actual_left actual_right] - (is (/.let [side /.Nat] - [side side]) - [expected_left expected_right])] - (and (same? expected_left actual_left) - (same? expected_right actual_right))))) + (_.coverage [/.let] + (let [[actual_left actual_right] + (is (/.let [side /.Nat] + [side side]) + [expected_left expected_right])] + (and (same? expected_left actual_left) + (same? expected_right actual_right))))) (do random.monad [.let [(open "/#[0]") /.equivalence] left (..random 0) right (..random 0)] (all _.and - (_.cover [/.code] - (bit#= (/#= left right) - (code#= (/.code left) (/.code right)))) - (_.cover [/.format] - (bit#= (/#= left right) - (text#= (/.format left) (/.format right)))) + (_.coverage [/.code] + (bit#= (/#= left right) + (code#= (/.code left) (/.code right)))) + (_.coverage [/.format] + (bit#= (/#= left right) + (text#= (/.format left) (/.format right)))) )) /primitive.test diff --git a/stdlib/source/test/lux/type/check.lux b/stdlib/source/test/lux/type/check.lux index 16861e8cb..c5fb83a48 100644 --- a/stdlib/source/test/lux/type/check.lux +++ b/stdlib/source/test/lux/type/check.lux @@ -138,29 +138,29 @@ (all _.and (do random.monad [expected (random.upper_case 10)] - (_.cover [/.failure] - (case (/.result /.fresh_context - (is (/.Check Any) - (/.failure expected))) - {try.#Success _} false - {try.#Failure actual} (same? expected actual)))) + (_.coverage [/.failure] + (case (/.result /.fresh_context + (is (/.Check Any) + (/.failure expected))) + {try.#Success _} false + {try.#Failure actual} (same? expected actual)))) (do random.monad [expected (random.upper_case 10)] - (_.cover [/.assertion] - (and (case (/.result /.fresh_context - (is (/.Check Any) - (/.assertion expected true))) - {try.#Success _} true - {try.#Failure actual} false) - (case (/.result /.fresh_context (/.assertion expected false)) - {try.#Success _} false - {try.#Failure actual} (same? expected actual))))) - (_.cover [/.except] - (case (/.result /.fresh_context + (_.coverage [/.assertion] + (and (case (/.result /.fresh_context (is (/.Check Any) - (/.except ..yolo []))) + (/.assertion expected true))) + {try.#Success _} true + {try.#Failure actual} false) + (case (/.result /.fresh_context (/.assertion expected false)) {try.#Success _} false - {try.#Failure error} (exception.match? ..yolo error))) + {try.#Failure actual} (same? expected actual))))) + (_.coverage [/.except] + (case (/.result /.fresh_context + (is (/.Check Any) + (/.except ..yolo []))) + {try.#Success _} false + {try.#Failure error} (exception.match? ..yolo error))) (let [scenario (is (-> (-> Text Bit) Type Type Bit) (function (_ ? <left> <right>) (and (|> (/.check <left> <right>) @@ -174,193 +174,193 @@ (pipe.case {try.#Failure error} (? error) {try.#Success _} false)))))] (all _.and - (_.cover [/.type_check_failed] - (let [scenario (scenario (exception.match? /.type_check_failed))] - (and (scenario (Tuple left right) left) - (scenario (Tuple left right) (Or left right)) - (scenario (Tuple left right) (-> left right)) - (scenario (Tuple left right) {.#Ex ex}) - - (scenario (Or left right) left) - (scenario (Or left right) (-> left right)) - (scenario (Or left right) {.#Ex ex}) - - (scenario (-> left right) left) - (scenario (-> left right) {.#Ex ex}) - - (scenario {.#Ex ex} left) - ))) - (_.cover [/.invalid_type_application] - (let [scenario (scenario (text.contains? (the exception.#label /.invalid_type_application)))] - (scenario {.#Apply left right} left))))) + (_.coverage [/.type_check_failed] + (let [scenario (scenario (exception.match? /.type_check_failed))] + (and (scenario (Tuple left right) left) + (scenario (Tuple left right) (Or left right)) + (scenario (Tuple left right) (-> left right)) + (scenario (Tuple left right) {.#Ex ex}) + + (scenario (Or left right) left) + (scenario (Or left right) (-> left right)) + (scenario (Or left right) {.#Ex ex}) + + (scenario (-> left right) left) + (scenario (-> left right) {.#Ex ex}) + + (scenario {.#Ex ex} left) + ))) + (_.coverage [/.invalid_type_application] + (let [scenario (scenario (text.contains? (the exception.#label /.invalid_type_application)))] + (scenario {.#Apply left right} left))))) ))) (def: var Test (<| (_.for [/.Var]) (all _.and - (_.cover [/.var] - (case (/.result /.fresh_context - (do /.monad - [[var_id var_type] /.var] - (in (type#= var_type {.#Var var_id})))) - {try.#Success verdict} verdict - {try.#Failure error} false)) + (_.coverage [/.var] + (case (/.result /.fresh_context + (do /.monad + [[var_id var_type] /.var] + (in (type#= var_type {.#Var var_id})))) + {try.#Success verdict} verdict + {try.#Failure error} false)) (do random.monad [nominal (random.upper_case 10)] - (_.cover [/.bind] - (case (/.result /.fresh_context - (do /.monad - [[var_id var_type] /.var - _ (/.bind {.#Primitive nominal (list)} - var_id)] - (in true))) - {try.#Success _} true - {try.#Failure error} false))) - (do random.monad - [nominal (random.upper_case 10)] - (_.cover [/.bound?] - (and (|> (do /.monad + (_.coverage [/.bind] + (case (/.result /.fresh_context + (do /.monad [[var_id var_type] /.var - pre (/.bound? var_id) _ (/.bind {.#Primitive nominal (list)} - var_id) - post (/.bound? var_id)] - (in (and (not pre) - post))) - (/.result /.fresh_context) - (try.else false)) - (|> (do /.monad - [[var_id var/0] /.var - pre (/.bound? var_id) - [_ var/1] /.var - _ (/.check var/0 var/1) - post (/.bound? var_id)] - (in (and (not pre) - (not post)))) - (/.result /.fresh_context) - (try.else false))))) + var_id)] + (in true))) + {try.#Success _} true + {try.#Failure error} false))) (do random.monad [nominal (random.upper_case 10)] - (_.cover [/.cannot_rebind_var] - (case (/.result /.fresh_context - (do /.monad - [[var_id var_type] /.var - _ (/.bind {.#Primitive nominal (list)} - var_id)] - (/.bind {.#Primitive nominal (list)} - var_id))) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_rebind_var error)))) + (_.coverage [/.bound?] + (and (|> (do /.monad + [[var_id var_type] /.var + pre (/.bound? var_id) + _ (/.bind {.#Primitive nominal (list)} + var_id) + post (/.bound? var_id)] + (in (and (not pre) + post))) + (/.result /.fresh_context) + (try.else false)) + (|> (do /.monad + [[var_id var/0] /.var + pre (/.bound? var_id) + [_ var/1] /.var + _ (/.check var/0 var/1) + post (/.bound? var_id)] + (in (and (not pre) + (not post)))) + (/.result /.fresh_context) + (try.else false))))) + (do random.monad + [nominal (random.upper_case 10)] + (_.coverage [/.cannot_rebind_var] + (case (/.result /.fresh_context + (do /.monad + [[var_id var_type] /.var + _ (/.bind {.#Primitive nominal (list)} + var_id)] + (/.bind {.#Primitive nominal (list)} + var_id))) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_rebind_var error)))) (do random.monad [nominal (random.upper_case 10) var_id random.nat] - (_.cover [/.unknown_type_var] - (case (/.result /.fresh_context - (/.bind {.#Primitive nominal (list)} - var_id)) - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.unknown_type_var error)))) + (_.coverage [/.unknown_type_var] + (case (/.result /.fresh_context + (/.bind {.#Primitive nominal (list)} + var_id)) + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.unknown_type_var error)))) (do random.monad [nominal (random.upper_case 10) .let [expected {.#Primitive nominal (list)}]] - (_.cover [/.peek] - (and (|> (do /.monad - [[var_id var_type] /.var] - (/.peek var_id)) - (/.result /.fresh_context) - (pipe.case {try.#Success {.#None}} true - _ false)) - (|> (do /.monad - [[var_id var/0] /.var - [_ var/1] /.var - _ (/.check var/0 var/1)] - (/.peek var_id)) - (/.result /.fresh_context) - (pipe.case {try.#Success {.#None}} true - _ false)) - (|> (do /.monad - [[var_id var_type] /.var - _ (/.bind expected var_id)] - (/.peek var_id)) - (/.result /.fresh_context) - (pipe.case {try.#Success {.#Some actual}} - (same? expected actual) - - _ - false))))) + (_.coverage [/.peek] + (and (|> (do /.monad + [[var_id var_type] /.var] + (/.peek var_id)) + (/.result /.fresh_context) + (pipe.case {try.#Success {.#None}} true + _ false)) + (|> (do /.monad + [[var_id var/0] /.var + [_ var/1] /.var + _ (/.check var/0 var/1)] + (/.peek var_id)) + (/.result /.fresh_context) + (pipe.case {try.#Success {.#None}} true + _ false)) + (|> (do /.monad + [[var_id var_type] /.var + _ (/.bind expected var_id)] + (/.peek var_id)) + (/.result /.fresh_context) + (pipe.case {try.#Success {.#Some actual}} + (same? expected actual) + + _ + false))))) (do random.monad [nominal (random.upper_case 10) .let [expected {.#Primitive nominal (list)}]] - (_.cover [/.read] - (case (/.result /.fresh_context - (do /.monad - [[var_id var_type] /.var - _ (/.bind expected var_id)] - (/.read var_id))) - {try.#Success actual} - (same? expected actual) - - _ - false))) + (_.coverage [/.read] + (case (/.result /.fresh_context + (do /.monad + [[var_id var_type] /.var + _ (/.bind expected var_id)] + (/.read var_id))) + {try.#Success actual} + (same? expected actual) + + _ + false))) (do random.monad [nominal (random.upper_case 10) .let [expected {.#Primitive nominal (list)}]] - (_.cover [/.unbound_type_var] - (case (/.result /.fresh_context - (do /.monad - [[var_id var_type] /.var] - (/.read var_id))) - {try.#Failure error} - (exception.match? /.unbound_type_var error) - - _ - false))) + (_.coverage [/.unbound_type_var] + (case (/.result /.fresh_context + (do /.monad + [[var_id var_type] /.var] + (/.read var_id))) + {try.#Failure error} + (exception.match? /.unbound_type_var error) + + _ + false))) ))) (def: context Test (all _.and - (_.cover [/.fresh_context] - (and (n.= 0 (the .#var_counter /.fresh_context)) - (n.= 0 (the .#ex_counter /.fresh_context)) - (list.empty? (the .#var_bindings /.fresh_context)))) - (_.cover [/.context] - (and (case (/.result /.fresh_context /.context) - {try.#Success actual} - (same? /.fresh_context actual) - - {try.#Failure error} - false) - (case (/.result /.fresh_context - (do /.monad - [_ /.var] - /.context)) - {try.#Success actual} - (and (n.= 1 (the .#var_counter actual)) - (n.= 0 (the .#ex_counter actual)) - (n.= 1 (list.size (the .#var_bindings actual)))) - - {try.#Failure error} - false))) - (_.cover [/.existential] - (case (/.result /.fresh_context - (do /.monad - [_ /.existential] - /.context)) - {try.#Success actual} - (and (n.= 0 (the .#var_counter actual)) - (n.= 1 (the .#ex_counter actual)) - (n.= 0 (list.size (the .#var_bindings actual)))) - - {try.#Failure error} - false)) + (_.coverage [/.fresh_context] + (and (n.= 0 (the .#var_counter /.fresh_context)) + (n.= 0 (the .#ex_counter /.fresh_context)) + (list.empty? (the .#var_bindings /.fresh_context)))) + (_.coverage [/.context] + (and (case (/.result /.fresh_context /.context) + {try.#Success actual} + (same? /.fresh_context actual) + + {try.#Failure error} + false) + (case (/.result /.fresh_context + (do /.monad + [_ /.var] + /.context)) + {try.#Success actual} + (and (n.= 1 (the .#var_counter actual)) + (n.= 0 (the .#ex_counter actual)) + (n.= 1 (list.size (the .#var_bindings actual)))) + + {try.#Failure error} + false))) + (_.coverage [/.existential] + (case (/.result /.fresh_context + (do /.monad + [_ /.existential] + /.context)) + {try.#Success actual} + (and (n.= 0 (the .#var_counter actual)) + (n.= 1 (the .#ex_counter actual)) + (n.= 0 (list.size (the .#var_bindings actual)))) + + {try.#Failure error} + false)) )) (def: succeeds? @@ -667,19 +667,19 @@ left_name ..symbol right_name ..symbol ring_tail_size (# ! each (n.% 10) random.nat)] - (_.cover [/.check] - (and (..handles_nominal_types! name/0 name/1 parameter/0 parameter/1) - (..handles_products! name/0 name/1) - (..handles_sums! name/0 name/1) - (..handles_function_variance! nominal) - (..handles_vars! nominal) - (..handles_var_rings! ring_tail_size parameter/0 parameter/1) - ..handles_existentials! - (..handles_quantification! nominal) - (..handles_ultimates! nominal) - (..handles_application! parameter/0 parameter/1) - (..names_do_not_affect_types! left_name right_name nominal) - )))) + (_.coverage [/.check] + (and (..handles_nominal_types! name/0 name/1 parameter/0 parameter/1) + (..handles_products! name/0 name/1) + (..handles_sums! name/0 name/1) + (..handles_function_variance! nominal) + (..handles_vars! nominal) + (..handles_var_rings! ring_tail_size parameter/0 parameter/1) + ..handles_existentials! + (..handles_quantification! nominal) + (..handles_ultimates! nominal) + (..handles_application! parameter/0 parameter/1) + (..names_do_not_affect_types! left_name right_name nominal) + )))) (def: dirty_type (Random (-> Type Type)) @@ -730,24 +730,24 @@ Test (do random.monad [type_shape ..dirty_type] - (_.cover [/.clean] - (and (|> (do /.monad - [[var_id varT] /.var - cleanedT (/.clean (list) (type_shape varT))] - (in (type#= (type_shape varT) - cleanedT))) - (/.result /.fresh_context) - (try.else false)) - (|> (do /.monad - [[var_id varT] /.var - [_ replacementT] /.existential - _ (/.check varT replacementT) - cleanedT (/.clean (list) (type_shape varT))] - (in (type#= (type_shape replacementT) - cleanedT))) - (/.result /.fresh_context) - (try.else false)) - )))) + (_.coverage [/.clean] + (and (|> (do /.monad + [[var_id varT] /.var + cleanedT (/.clean (list) (type_shape varT))] + (in (type#= (type_shape varT) + cleanedT))) + (/.result /.fresh_context) + (try.else false)) + (|> (do /.monad + [[var_id varT] /.var + [_ replacementT] /.existential + _ (/.check varT replacementT) + cleanedT (/.clean (list) (type_shape varT))] + (in (type#= (type_shape replacementT) + cleanedT))) + (/.result /.fresh_context) + (try.else false)) + )))) (def: for_subsumption|ultimate (Random Bit) @@ -866,17 +866,17 @@ for_subsumption|existential ..for_subsumption|existential for_subsumption|quantification+application ..for_subsumption|quantification+application for_subsumption|named ..for_subsumption|named] - (_.cover [/.subsumes?] - (and for_subsumption|ultimate - for_subsumption|nominal - for_subsumption|sum - for_subsumption|product - for_subsumption|function - for_subsumption|variable - for_subsumption|existential - for_subsumption|quantification+application - for_subsumption|named - )))) + (_.coverage [/.subsumes?] + (and for_subsumption|ultimate + for_subsumption|nominal + for_subsumption|sum + for_subsumption|product + for_subsumption|function + for_subsumption|variable + for_subsumption|existential + for_subsumption|quantification+application + for_subsumption|named + )))) (def: .public test Test @@ -886,11 +886,11 @@ ..polymorphism (do random.monad [expected random.nat] - (_.cover [/.result] - (case (/.result /.fresh_context - (# /.monad in expected)) - {try.#Success actual} (same? expected actual) - {try.#Failure error} false))) + (_.coverage [/.result] + (case (/.result /.fresh_context + (# /.monad in expected)) + {try.#Success actual} (same? expected actual) + {try.#Failure error} false))) ..error_handling ..var ..context diff --git a/stdlib/source/test/lux/type/dynamic.lux b/stdlib/source/test/lux/type/dynamic.lux index d180815e5..d057ed790 100644 --- a/stdlib/source/test/lux/type/dynamic.lux +++ b/stdlib/source/test/lux/type/dynamic.lux @@ -24,25 +24,25 @@ (do random.monad [expected random.nat] (all _.and - (_.cover [/.dynamic /.static] - (case (/.static Nat (/.dynamic expected)) - {try.#Success actual} - (n.= expected actual) - - {try.#Failure _} - false)) - (_.cover [/.wrong_type] - (case (/.static Text (/.dynamic expected)) - {try.#Success actual} - false - - {try.#Failure error} - (exception.match? /.wrong_type error))) - (_.cover [/.format] - (case (/.format (/.dynamic expected)) - {try.#Success actual} - (text#= (%.nat expected) actual) - - {try.#Failure _} - false)) + (_.coverage [/.dynamic /.static] + (case (/.static Nat (/.dynamic expected)) + {try.#Success actual} + (n.= expected actual) + + {try.#Failure _} + false)) + (_.coverage [/.wrong_type] + (case (/.static Text (/.dynamic expected)) + {try.#Success actual} + false + + {try.#Failure error} + (exception.match? /.wrong_type error))) + (_.coverage [/.format] + (case (/.format (/.dynamic expected)) + {try.#Success actual} + (text#= (%.nat expected) actual) + + {try.#Failure _} + false)) )))) diff --git a/stdlib/source/test/lux/type/implicit.lux b/stdlib/source/test/lux/type/implicit.lux index 8fa84731b..aeba6758c 100644 --- a/stdlib/source/test/lux/type/implicit.lux +++ b/stdlib/source/test/lux/type/implicit.lux @@ -34,31 +34,31 @@ left random.nat right random.nat] (all _.and - (_.cover [/.##] - (let [first_order! - (let [(open "list#[0]") (list.equivalence n.equivalence)] - (and (bit#= (# n.equivalence = left right) - (/.## = left right)) - (list#= (# list.functor each ++ (enum.range n.enum start end)) - (/.## each ++ (enum.range n.enum start end))))) + (_.coverage [/.##] + (let [first_order! + (let [(open "list#[0]") (list.equivalence n.equivalence)] + (and (bit#= (# n.equivalence = left right) + (/.## = left right)) + (list#= (# list.functor each ++ (enum.range n.enum start end)) + (/.## each ++ (enum.range n.enum start end))))) - second_order! - (/.## = - (enum.range n.enum start end) - (enum.range n.enum start end)) + second_order! + (/.## = + (enum.range n.enum start end) + (enum.range n.enum start end)) - third_order! - (let [lln (/.## each (enum.range n.enum start) - (enum.range n.enum start end))] - (/.## = lln lln))] - (and first_order! - second_order! - third_order!))) - (_.cover [/.with] - (/.with [n.addition] - (n.= (# n.addition composite left right) - (/.## composite left right)))) - (_.cover [/.implicit:] - (n.= (# n.multiplication composite left right) - (/.## composite left right))) + third_order! + (let [lln (/.## each (enum.range n.enum start) + (enum.range n.enum start end))] + (/.## = lln lln))] + (and first_order! + second_order! + third_order!))) + (_.coverage [/.with] + (/.with [n.addition] + (n.= (# n.addition composite left right) + (/.## composite left right)))) + (_.coverage [/.implicit:] + (n.= (# n.multiplication composite left right) + (/.## composite left right))) )))) diff --git a/stdlib/source/test/lux/type/poly/equivalence.lux b/stdlib/source/test/lux/type/poly/equivalence.lux index 410627c53..47caf14ac 100644 --- a/stdlib/source/test/lux/type/poly/equivalence.lux +++ b/stdlib/source/test/lux/type/poly/equivalence.lux @@ -85,5 +85,5 @@ Test (<| (_.covering /._) (_.for [/.equivalence] - (for @.old (_.test "PLACEHOLDER" true) + (for @.old (_.property "PLACEHOLDER" true) ($equivalence.spec ..equivalence ..random))))) diff --git a/stdlib/source/test/lux/type/poly/functor.lux b/stdlib/source/test/lux/type/poly/functor.lux index b7debe316..e37d05dd0 100644 --- a/stdlib/source/test/lux/type/poly/functor.lux +++ b/stdlib/source/test/lux/type/poly/functor.lux @@ -34,5 +34,5 @@ (def: .public test Test (<| (_.covering /._) - (_.cover [/.functor] - true))) + (_.coverage [/.functor] + true))) diff --git a/stdlib/source/test/lux/type/poly/json.lux b/stdlib/source/test/lux/type/poly/json.lux index 00eec73fa..3e9c4cea1 100644 --- a/stdlib/source/test/lux/type/poly/json.lux +++ b/stdlib/source/test/lux/type/poly/json.lux @@ -120,5 +120,5 @@ Test (<| (_.covering /._) (_.for [/.codec] - (for @.old (_.test "PLACEHOLDER" true) + (for @.old (_.property "PLACEHOLDER" true) ($codec.spec ..equivalence ..codec ..gen_record))))) diff --git a/stdlib/source/test/lux/type/primitive.lux b/stdlib/source/test/lux/type/primitive.lux index 5b4a3fe06..f438abcb2 100644 --- a/stdlib/source/test/lux/type/primitive.lux +++ b/stdlib/source/test/lux/type/primitive.lux @@ -60,45 +60,45 @@ [expected_foo (random.lower_case 5) expected_bar random.nat] (all _.and - (_.cover [/.abstraction] - (and (exec (is (g!Foo Text) - (/.abstraction g!Foo expected_foo)) - true) - (exec (is (g!Bar Text) - (/.abstraction expected_bar)) - true))) - (_.cover [/.representation] - (and (|> expected_foo - (/.abstraction g!Foo) - (is (g!Foo Bit)) - (/.representation g!Foo) - (text#= expected_foo)) - (|> (/.abstraction expected_bar) - (is (g!Bar Bit)) - /.representation - (n.= expected_bar)))) - (_.cover [/.transmutation] - (and (exec (|> expected_foo - (/.abstraction g!Foo) - (is (g!Foo .Macro)) - (/.transmutation g!Foo) - (is (g!Foo .Lux))) - true) - (exec (|> (/.abstraction expected_bar) - (is (g!Bar .Macro)) - /.transmutation - (is (g!Bar .Lux))) - true))) + (_.coverage [/.abstraction] + (and (exec (is (g!Foo Text) + (/.abstraction g!Foo expected_foo)) + true) + (exec (is (g!Bar Text) + (/.abstraction expected_bar)) + true))) + (_.coverage [/.representation] + (and (|> expected_foo + (/.abstraction g!Foo) + (is (g!Foo Bit)) + (/.representation g!Foo) + (text#= expected_foo)) + (|> (/.abstraction expected_bar) + (is (g!Bar Bit)) + /.representation + (n.= expected_bar)))) + (_.coverage [/.transmutation] + (and (exec (|> expected_foo + (/.abstraction g!Foo) + (is (g!Foo .Macro)) + (/.transmutation g!Foo) + (is (g!Foo .Lux))) + true) + (exec (|> (/.abstraction expected_bar) + (is (g!Bar .Macro)) + /.transmutation + (is (g!Bar .Lux))) + true))) (_.for [/.Frame] (all _.and - (_.cover [/.current] - (text#= (template.text [g!Bar]) - (..current))) - (_.cover [/.specific] - (text#= (template.text [g!Foo]) - (..specific))) - (_.cover [/.no_active_frames] - (and no_current! - no_specific!)) + (_.coverage [/.current] + (text#= (template.text [g!Bar]) + (..current))) + (_.coverage [/.specific] + (text#= (template.text [g!Foo]) + (..specific))) + (_.coverage [/.no_active_frames] + (and no_current! + no_specific!)) )) ))))))))) diff --git a/stdlib/source/test/lux/type/quotient.lux b/stdlib/source/test/lux/type/quotient.lux index 44258d4bd..f10d2a4c2 100644 --- a/stdlib/source/test/lux/type/quotient.lux +++ b/stdlib/source/test/lux/type/quotient.lux @@ -40,21 +40,21 @@ (..random (/.class class) random.nat))) (_.for [/.Class] - (_.cover [/.class] - (same? (is Any class) - (is Any (/.class class))))) + (_.coverage [/.class] + (same? (is Any class) + (is Any (/.class class))))) (_.for [/.Quotient] (all _.and - (_.cover [/.quotient /.value /.label] - (let [quotient (/.quotient (/.class class) value)] - (and (same? value - (/.value quotient)) - (text#= (class value) - (/.label quotient))))) - (_.cover [/.type] - (exec - (is ..Mod_10 - (/.quotient ..mod_10_class value)) - true)) + (_.coverage [/.quotient /.value /.label] + (let [quotient (/.quotient (/.class class) value)] + (and (same? value + (/.value quotient)) + (text#= (class value) + (/.label quotient))))) + (_.coverage [/.type] + (exec + (is ..Mod_10 + (/.quotient ..mod_10_class value)) + true)) )) )))) diff --git a/stdlib/source/test/lux/type/refinement.lux b/stdlib/source/test/lux/type/refinement.lux index d6d5bf660..26617a2fc 100644 --- a/stdlib/source/test/lux/type/refinement.lux +++ b/stdlib/source/test/lux/type/refinement.lux @@ -37,54 +37,54 @@ (all _.and (_.for [/.Refiner] (all _.and - (_.cover [/.refiner] - (case (/.refiner predicate raw) - {.#Some refined} - (predicate raw) - - {.#None} - (not (predicate raw)))) - (_.cover [/.predicate] - (|> (/.refiner predicate modulus) - (maybe#each (|>> /.predicate (same? predicate))) - (maybe.else false))) - )) - (_.cover [/.value] - (|> (/.refiner predicate modulus) - (maybe#each (|>> /.value (n.= modulus))) - (maybe.else false))) - (_.cover [/.lifted] - (and (|> (/.refiner predicate modulus) - (maybe#each (/.lifted (n.+ modulus))) - maybe#conjoint - (maybe#each (|>> /.value (n.= (n.+ modulus modulus)))) - (maybe.else false)) + (_.coverage [/.refiner] + (case (/.refiner predicate raw) + {.#Some refined} + (predicate raw) + + {.#None} + (not (predicate raw)))) + (_.coverage [/.predicate] (|> (/.refiner predicate modulus) - (maybe#each (/.lifted (n.+ (++ modulus)))) - maybe#conjoint - (maybe#each (|>> /.value (n.= (n.+ modulus (++ modulus))))) - (maybe.else false) - not))) - (_.cover [/.only] - (let [expected (list.only predicate raws) - actual (/.only (/.refiner predicate) raws)] - (and (n.= (list.size expected) - (list.size actual)) - (# (list.equivalence n.equivalence) = - expected - (list#each /.value actual))))) - (_.cover [/.partition] - (let [expected (list.only predicate raws) - [actual alternative] (/.partition (/.refiner predicate) raws)] - (and (n.= (list.size expected) - (list.size actual)) - (n.= (n.- (list.size expected) total_raws) - (list.size alternative)) - (# (list.equivalence n.equivalence) = - expected - (list#each /.value actual))))) - (_.cover [/.type] - (exec (is (Maybe .._type) - (.._refiner raw)) - true)) + (maybe#each (|>> /.predicate (same? predicate))) + (maybe.else false))) + )) + (_.coverage [/.value] + (|> (/.refiner predicate modulus) + (maybe#each (|>> /.value (n.= modulus))) + (maybe.else false))) + (_.coverage [/.lifted] + (and (|> (/.refiner predicate modulus) + (maybe#each (/.lifted (n.+ modulus))) + maybe#conjoint + (maybe#each (|>> /.value (n.= (n.+ modulus modulus)))) + (maybe.else false)) + (|> (/.refiner predicate modulus) + (maybe#each (/.lifted (n.+ (++ modulus)))) + maybe#conjoint + (maybe#each (|>> /.value (n.= (n.+ modulus (++ modulus))))) + (maybe.else false) + not))) + (_.coverage [/.only] + (let [expected (list.only predicate raws) + actual (/.only (/.refiner predicate) raws)] + (and (n.= (list.size expected) + (list.size actual)) + (# (list.equivalence n.equivalence) = + expected + (list#each /.value actual))))) + (_.coverage [/.partition] + (let [expected (list.only predicate raws) + [actual alternative] (/.partition (/.refiner predicate) raws)] + (and (n.= (list.size expected) + (list.size actual)) + (n.= (n.- (list.size expected) total_raws) + (list.size alternative)) + (# (list.equivalence n.equivalence) = + expected + (list#each /.value actual))))) + (_.coverage [/.type] + (exec (is (Maybe .._type) + (.._refiner raw)) + true)) )))) diff --git a/stdlib/source/test/lux/type/resource.lux b/stdlib/source/test/lux/type/resource.lux index 69709555a..755978e8c 100644 --- a/stdlib/source/test/lux/type/resource.lux +++ b/stdlib/source/test/lux/type/resource.lux @@ -35,13 +35,13 @@ (_.for [/.Linear /.run! /.monad] (`` (all _.and (~~ (template [<coverage> <bindings>] - [(_.cover <coverage> - (<| (text#= (format pre post)) - (is (Identity Text)) - (/.run! !) - (do (/.monad !) - <bindings> - (in (format left right)))))] + [(_.coverage <coverage> + (<| (text#= (format pre post)) + (is (Identity Text)) + (/.run! !) + (do (/.monad !) + <bindings> + (in (format left right)))))] [[/.Affine /.Key /.Res /.Ordered /.ordered /.Relevant /.read] @@ -77,14 +77,14 @@ (_.for [/.Linear /.run! /.monad] (`` (all _.and (~~ (template [<coverage> <bindings>] - [(_.cover <coverage> - (<| (text#= (format pre post)) - io.run! - (is (IO Text)) - (/.run! !) - (do (/.monad !) - <bindings> - (in (format left right)))))] + [(_.coverage <coverage> + (<| (text#= (format pre post)) + io.run! + (is (IO Text)) + (/.run! !) + (do (/.monad !) + <bindings> + (in (format left right)))))] [[/.Affine /.Key /.Res /.Ordered /.ordered /.Relevant /.read] @@ -126,9 +126,9 @@ (do (/.monad !) <bindings> (in (format left right))))] - (_.cover' <coverage> - (text#= (format pre post) - outcome))))] + (_.coverage' <coverage> + (text#= (format pre post) + outcome))))] [[/.Affine /.Key /.Res /.Ordered /.ordered /.Relevant /.read] @@ -177,15 +177,15 @@ ..sync ..async - (_.cover [/.amount_cannot_be_zero] - (`` (and (~~ (template [<group|un_group>] - [(with_error /.amount_cannot_be_zero - (<group|un_group> 0))] + (_.coverage [/.amount_cannot_be_zero] + (`` (and (~~ (template [<group|un_group>] + [(with_error /.amount_cannot_be_zero + (<group|un_group> 0))] - [/.group] - [/.un_group] - ))))) - (_.cover [/.index_cannot_be_repeated] - (with_error /.index_cannot_be_repeated - (/.exchange [0 0]))) + [/.group] + [/.un_group] + ))))) + (_.coverage [/.index_cannot_be_repeated] + (with_error /.index_cannot_be_repeated + (/.exchange [0 0]))) ))) diff --git a/stdlib/source/test/lux/type/unit.lux b/stdlib/source/test/lux/type/unit.lux index dac454fee..306d4391a 100644 --- a/stdlib/source/test/lux/type/unit.lux +++ b/stdlib/source/test/lux/type/unit.lux @@ -54,27 +54,27 @@ (_.for [/.Unit] (`` (all _.and (~~ (template [<type> <unit>] - [(_.cover [<type> <unit>] - (|> expected - (# <unit> in) - (# <unit> out) - (i.= expected)))] + [(_.coverage [<type> <unit>] + (|> expected + (# <unit> in) + (# <unit> out) + (i.= expected)))] [/.Gram /.gram] [/.Meter /.meter] [/.Litre /.litre] [/.Second /.second] )) - (_.cover [/.Pure /.pure /.number] - (|> expected - /.pure - /.number - (i.= expected))) - (_.cover [/.unit:] - (|> expected - (# ..what in) - (# ..what out) - (i.= expected))) + (_.coverage [/.Pure /.pure /.number] + (|> expected + /.pure + /.number + (i.= expected))) + (_.coverage [/.unit:] + (|> expected + (# ..what in) + (# ..what out) + (i.= expected))) ))))) (syntax: (natural []) @@ -110,46 +110,46 @@ (_.for [/.Scale] (`` (all _.and (~~ (template [<type> <scale>] - [(_.cover [<type> <scale>] - (|> large - (# <scale> scale) - (is (/.Qty (<type> /.Meter))) - (# <scale> de_scale) - (is (/.Qty /.Meter)) - (meter#= large)))] + [(_.coverage [<type> <scale>] + (|> large + (# <scale> scale) + (is (/.Qty (<type> /.Meter))) + (# <scale> de_scale) + (is (/.Qty /.Meter)) + (meter#= large)))] [/.Kilo /.kilo] [/.Mega /.mega] [/.Giga /.giga] )) (~~ (template [<type> <scale>] - [(_.cover [<type> <scale>] - (|> small - (# <scale> scale) - (is (/.Qty (<type> /.Meter))) - (# <scale> de_scale) - (is (/.Qty /.Meter)) - (meter#= small)))] + [(_.coverage [<type> <scale>] + (|> small + (# <scale> scale) + (is (/.Qty (<type> /.Meter))) + (# <scale> de_scale) + (is (/.Qty /.Meter)) + (meter#= small)))] [/.Milli /.milli] [/.Micro /.micro] [/.Nano /.nano] )) - (_.cover [/.re_scaled] - (|> large (is (/.Qty /.Meter)) - (# /.kilo scale) (is (/.Qty (/.Kilo /.Meter))) - (/.re_scaled /.kilo /.milli) (is (/.Qty (/.Milli /.Meter))) - (/.re_scaled /.milli /.kilo) (is (/.Qty (/.Kilo /.Meter))) - (# /.kilo de_scale) (is (/.Qty /.Meter)) - (meter#= large))) - (_.cover [/.scale:] - (and (|> unscaled - (# ..how scale) - (# ..how de_scale) - (meter#= unscaled)) - (ratio#= [..how::from - ..how::to] - (# ..how ratio)))) + (_.coverage [/.re_scaled] + (|> large (is (/.Qty /.Meter)) + (# /.kilo scale) (is (/.Qty (/.Kilo /.Meter))) + (/.re_scaled /.kilo /.milli) (is (/.Qty (/.Milli /.Meter))) + (/.re_scaled /.milli /.kilo) (is (/.Qty (/.Kilo /.Meter))) + (# /.kilo de_scale) (is (/.Qty /.Meter)) + (meter#= large))) + (_.coverage [/.scale:] + (and (|> unscaled + (# ..how scale) + (# ..how de_scale) + (meter#= unscaled)) + (ratio#= [..how::from + ..how::to] + (# ..how ratio)))) ))))) (def: arithmetic @@ -163,23 +163,23 @@ extra (..second 1,000)] (`` (all _.and (~~ (template [<q> <i>] - [(_.cover [<q>] - (i.= (<i> (# /.meter out left) (# /.meter out right)) - (# /.meter out (<q> left right))))] + [(_.coverage [<q>] + (i.= (<i> (# /.meter out left) (# /.meter out right)) + (# /.meter out (<q> left right))))] [/.+ i.+] [/.- i.-] )) - (_.cover [/.*] - (let [expected (i.* (# /.meter out left) (# /.meter out right)) - actual ((debug.private /.out') (is (/.Qty [/.Meter /.Meter]) - (/.* left right)))] - (i.= expected actual))) - (_.cover [/./] - (|> right - (/.* left) - (/./ left) - (meter#= right))) + (_.coverage [/.*] + (let [expected (i.* (# /.meter out left) (# /.meter out right)) + actual ((debug.private /.out') (is (/.Qty [/.Meter /.Meter]) + (/.* left right)))] + (i.= expected actual))) + (_.coverage [/./] + (|> right + (/.* left) + (/./ left) + (meter#= right))) )))) (def: .public test diff --git a/stdlib/source/test/lux/type/variance.lux b/stdlib/source/test/lux/type/variance.lux index 5f4cbe862..8b7e62f1a 100644 --- a/stdlib/source/test/lux/type/variance.lux +++ b/stdlib/source/test/lux/type/variance.lux @@ -21,15 +21,15 @@ Test (<| (_.covering /._) (all _.and - (_.cover [/.Co] - (and (//check.subsumes? (type (/.Co Super)) (type (/.Co Sub))) - (not (//check.subsumes? (type (/.Co Sub)) (type (/.Co Super)))))) - (_.cover [/.Contra] - (and (//check.subsumes? (type (/.Contra Sub)) (type (/.Contra Super))) - (not (//check.subsumes? (type (/.Contra Super)) (type (/.Contra Sub)))))) - (_.cover [/.In] - (and (//check.subsumes? (type (/.In Super)) (type (/.In Super))) - (//check.subsumes? (type (/.In Sub)) (type (/.In Sub))) - (not (//check.subsumes? (type (/.In Sub)) (type (/.In Super)))) - (not (//check.subsumes? (type (/.In Super)) (type (/.In Sub)))))) + (_.coverage [/.Co] + (and (//check.subsumes? (type (/.Co Super)) (type (/.Co Sub))) + (not (//check.subsumes? (type (/.Co Sub)) (type (/.Co Super)))))) + (_.coverage [/.Contra] + (and (//check.subsumes? (type (/.Contra Sub)) (type (/.Contra Super))) + (not (//check.subsumes? (type (/.Contra Super)) (type (/.Contra Sub)))))) + (_.coverage [/.In] + (and (//check.subsumes? (type (/.In Super)) (type (/.In Super))) + (//check.subsumes? (type (/.In Sub)) (type (/.In Sub))) + (not (//check.subsumes? (type (/.In Sub)) (type (/.In Super)))) + (not (//check.subsumes? (type (/.In Super)) (type (/.In Sub)))))) ))) diff --git a/stdlib/source/test/lux/world/console.lux b/stdlib/source/test/lux/world/console.lux index ebae69a0d..29e8f66e5 100644 --- a/stdlib/source/test/lux/world/console.lux +++ b/stdlib/source/test/lux/world/console.lux @@ -57,14 +57,14 @@ (do random.monad [expected (random.alphabetic 10) .let [console (/.mock ..mock [false ""])]] - (_.cover [/.write_line] - (io.run! - (do io.monad - [?_ (/.write_line expected console) - ?actual (# console read_line [])] - (in (<| (try.else false) - (do try.monad - [_ ?_ - actual ?actual] - (in (text#= expected actual))))))))) + (_.coverage [/.write_line] + (io.run! + (do io.monad + [?_ (/.write_line expected console) + ?actual (# console read_line [])] + (in (<| (try.else false) + (do try.monad + [_ ?_ + actual ?actual] + (in (text#= expected actual))))))))) ))) diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index c4c8689cd..0ff782b56 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -253,35 +253,35 @@ (in (do async.monad [.let [fs (/.mock /)] ? (# fs delete file)] - (_.cover' [/.cannot_delete] - (case ? - {try.#Failure error} - (exception.match? /.cannot_delete error) + (_.coverage' [/.cannot_delete] + (case ? + {try.#Failure error} + (exception.match? /.cannot_delete error) - _ - false)))) + _ + false)))) (in (do async.monad [.let [fs (/.mock /)] ? (# fs read file)] - (_.cover' [/.cannot_find_file] - (case ? - {try.#Failure error} - (exception.match? /.cannot_find_file error) + (_.coverage' [/.cannot_find_file] + (case ? + {try.#Failure error} + (exception.match? /.cannot_find_file error) - _ - false)))) + _ + false)))) (in (do async.monad [.let [fs (/.mock /)] ?/0 (# fs directory_files file) ?/1 (# fs sub_directories file)] - (_.cover' [/.cannot_find_directory] - (case [?/0 ?/1] - [{try.#Failure error/0} {try.#Failure error/1}] - (and (exception.match? /.cannot_find_directory error/0) - (exception.match? /.cannot_find_directory error/1)) + (_.coverage' [/.cannot_find_directory] + (case [?/0 ?/1] + [{try.#Failure error/0} {try.#Failure error/1}] + (and (exception.match? /.cannot_find_directory error/0) + (exception.match? /.cannot_find_directory error/1)) - _ - false)))) + _ + false)))) /watch.test )))) diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index 1243694a5..73e09ee96 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -36,32 +36,32 @@ (def: concern##test Test (all _.and - (_.cover [/.creation /.creation?] - (and (/.creation? /.creation) - (not (/.creation? /.modification)) - (not (/.creation? /.deletion)))) - (_.cover [/.modification /.modification?] - (and (not (/.modification? /.creation)) - (/.modification? /.modification) - (not (/.modification? /.deletion)))) - (_.cover [/.deletion /.deletion?] - (and (not (/.deletion? /.creation)) - (not (/.deletion? /.modification)) - (/.deletion? /.deletion))) + (_.coverage [/.creation /.creation?] + (and (/.creation? /.creation) + (not (/.creation? /.modification)) + (not (/.creation? /.deletion)))) + (_.coverage [/.modification /.modification?] + (and (not (/.modification? /.creation)) + (/.modification? /.modification) + (not (/.modification? /.deletion)))) + (_.coverage [/.deletion /.deletion?] + (and (not (/.deletion? /.creation)) + (not (/.deletion? /.modification)) + (/.deletion? /.deletion))) (do random.monad [left ..concern right (random.only (|>> (same? left) not) ..concern) .let [[left left?] left [right right?] right]] - (_.cover [/.also] - (let [composition (/.also left right)] - (and (left? composition) - (right? composition))))) - (_.cover [/.all] - (and (/.creation? /.all) - (/.modification? /.all) - (/.deletion? /.all))) + (_.coverage [/.also] + (let [composition (/.also left right)] + (and (left? composition) + (right? composition))))) + (_.coverage [/.all] + (and (/.creation? /.all) + (/.modification? /.all) + (/.deletion? /.all))) )) (def: exception @@ -73,19 +73,19 @@ (in (do async.monad [?concern (# watcher concern directory) ?stop (# watcher stop directory)] - (_.cover' [/.not_being_watched] - (and (case ?concern - {try.#Failure error} - (exception.match? /.not_being_watched error) - - {try.#Success _} - false) - (case ?stop - {try.#Failure error} - (exception.match? /.not_being_watched error) - - {try.#Success _} - false))))) + (_.coverage' [/.not_being_watched] + (and (case ?concern + {try.#Failure error} + (exception.match? /.not_being_watched error) + + {try.#Success _} + false) + (case ?stop + {try.#Failure error} + (exception.match? /.not_being_watched error) + + {try.#Success _} + false))))) ))) (def: (no_events_prior_to_creation! fs watcher directory) @@ -181,19 +181,19 @@ after_creation! after_modification! after_deletion!)))] - (_.cover' [/.mock /.polling] - (try.else false verdict))))) + (_.coverage' [/.mock /.polling] + (try.else false verdict))))) (do random.monad [directory (random.alphabetic 5) .let [/ "/" [fs watcher] (/.mock /)]] (in (do async.monad [started? (# watcher start /.all directory)] - (_.cover' [/.cannot_poll_a_non_existent_directory] - (case started? - {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.cannot_poll_a_non_existent_directory error)))))) + (_.coverage' [/.cannot_poll_a_non_existent_directory] + (case started? + {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.cannot_poll_a_non_existent_directory error)))))) ))) diff --git a/stdlib/source/test/lux/world/input/keyboard.lux b/stdlib/source/test/lux/world/input/keyboard.lux index 0e509448c..5e2e33364 100644 --- a/stdlib/source/test/lux/world/input/keyboard.lux +++ b/stdlib/source/test/lux/world/input/keyboard.lux @@ -131,8 +131,8 @@ (template [<definition> <keys>] [(def: <definition> Test - (_.cover <keys> - ..verdict))] + (_.coverage <keys> + ..verdict))] <groups>) @@ -159,9 +159,9 @@ [(do random.monad [key ..random .let [sample (<function> key)]] - (_.cover [<function>] - (and (bit#= <pressed?> (the /.#pressed? sample)) - (n.= key (the /.#input sample)))))] + (_.coverage [<function>] + (and (bit#= <pressed?> (the /.#pressed? sample)) + (n.= key (the /.#input sample)))))] [#0 /.release] [#1 /.press] diff --git a/stdlib/source/test/lux/world/net/http/client.lux b/stdlib/source/test/lux/world/net/http/client.lux index 7ed8fa32d..560162875 100644 --- a/stdlib/source/test/lux/world/net/http/client.lux +++ b/stdlib/source/test/lux/world/net/http/client.lux @@ -99,19 +99,19 @@ [/.trace on_trace])] (`` (all _.and (~~ (template [<definition> <expected>] - [(_.cover [<definition>] - (|> (<definition> "" //.empty {.#None} mock) - (verification io.monad <expected>) - io.run!))] + [(_.coverage [<definition>] + (|> (<definition> "" //.empty {.#None} mock) + (verification io.monad <expected>) + io.run!))] <cases> )) - (_.cover [/.headers] - (nat.= (dictionary.size headers) - (|> headers - dictionary.entries - /.headers - dictionary.size))) + (_.coverage [/.headers] + (nat.= (dictionary.size headers) + (|> headers + dictionary.entries + /.headers + dictionary.size))) (in (do [! async.monad] [.let [mock (/.async mock)] (~~ (template [<definition> <expected>] @@ -119,9 +119,9 @@ (verification ! <expected>))] <cases>))] - (_.cover' [/.async] - (and (~~ (template [<definition> <expected>] - [<expected>] + (_.coverage' [/.async] + (and (~~ (template [<definition> <expected>] + [<expected>] - <cases>)))))) + <cases>)))))) )))))) diff --git a/stdlib/source/test/lux/world/net/http/status.lux b/stdlib/source/test/lux/world/net/http/status.lux index 3dc8326ae..90ad92906 100644 --- a/stdlib/source/test/lux/world/net/http/status.lux +++ b/stdlib/source/test/lux/world/net/http/status.lux @@ -103,8 +103,8 @@ (template [<category> <status+>] [(def: <category> Test - (_.cover <status+> - ..verdict))] + (_.coverage <status+> + ..verdict))] <categories>) diff --git a/stdlib/source/test/lux/world/output/video/resolution.lux b/stdlib/source/test/lux/world/output/video/resolution.lux index 65713e748..3d46dc916 100644 --- a/stdlib/source/test/lux/world/output/video/resolution.lux +++ b/stdlib/source/test/lux/world/output/video/resolution.lux @@ -60,7 +60,7 @@ (_.for [/.hash] ($hash.spec /.hash ..random)) - (_.cover [<resolutions>] - (n.= (list.size ..listing) - (set.size ..catalogue))) + (_.coverage [<resolutions>] + (n.= (list.size ..listing) + (set.size ..catalogue))) )))) diff --git a/stdlib/source/test/lux/world/program.lux b/stdlib/source/test/lux/world/program.lux index d9c04e2ba..6c82d00da 100644 --- a/stdlib/source/test/lux/world/program.lux +++ b/stdlib/source/test/lux/world/program.lux @@ -51,28 +51,28 @@ (all _.and (_.for [/.mock /.async] ($/.spec (/.async (/.mock environment home directory)))) - (_.cover [/.environment] - (let [program (/.mock environment home directory)] - (io.run! - (do io.monad - [actual (/.environment io.monad program)] - (in (and (n.= (dictionary.size environment) - (dictionary.size actual)) - (|> actual - dictionary.entries - (list.every? (function (_ [key value]) - (|> environment - (dictionary.value key) - (maybe#each (text#= value)) - (maybe.else false))))))))))) - (_.cover [/.unknown_environment_variable] - (let [program (/.mock environment home directory)] - (|> unknown - (# program variable) - io.run! - (pipe.case {try.#Success _} - false - - {try.#Failure error} - (exception.match? /.unknown_environment_variable error))))) + (_.coverage [/.environment] + (let [program (/.mock environment home directory)] + (io.run! + (do io.monad + [actual (/.environment io.monad program)] + (in (and (n.= (dictionary.size environment) + (dictionary.size actual)) + (|> actual + dictionary.entries + (list.every? (function (_ [key value]) + (|> environment + (dictionary.value key) + (maybe#each (text#= value)) + (maybe.else false))))))))))) + (_.coverage [/.unknown_environment_variable] + (let [program (/.mock environment home directory)] + (|> unknown + (# program variable) + io.run! + (pipe.case {try.#Success _} + false + + {try.#Failure error} + (exception.match? /.unknown_environment_variable error))))) )))) diff --git a/stdlib/source/test/lux/world/shell.lux b/stdlib/source/test/lux/world/shell.lux index 6de1d8a38..1c51086d6 100644 --- a/stdlib/source/test/lux/world/shell.lux +++ b/stdlib/source/test/lux/world/shell.lux @@ -87,8 +87,8 @@ (_.for [/.async /.mock /.Mock] ($/.spec (/.async (/.mock (|>> ..mock {try.#Success}) false)))) - (_.cover [/.error] - (not (i.= /.normal /.error))) + (_.coverage [/.error] + (not (i.= /.normal /.error))) (do random.monad [command (random.alphabetic 5) oops (random.alphabetic 5) @@ -123,6 +123,6 @@ wrote! destroyed! (i.= exit await))))] - (_.cover' [/.Shell] - (try.else false verdict))))) + (_.coverage' [/.Shell] + (try.else false verdict))))) ))) |