diff options
Diffstat (limited to '')
20 files changed, 129 insertions, 90 deletions
diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index bfdc93f30..11e3b6c73 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -22,11 +22,13 @@ ["%" format (#+ format)]] [collection ["." list]]] - [macro + ["." macro ["." code ("#\." equivalence)]] ["." math ["." random (#+ Random) ("#\." functor)] [number + [i8 (#+)] + [i16 (#+)] ["n" nat] ["i" int] ["r" rev] @@ -989,6 +991,36 @@ (and (is? expected (identity/constant expected)) (is? expected (identity/function expected)))))) +(.refer "library/lux/target" #*) +(.refer "library/lux/macro" #all) +(.refer "library/lux/math/number/nat" #_) +(.refer "library/lux/math/number/int" #nothing) +(.refer "library/lux/math/number/rev" (#+ /4096)) +(.refer "library/lux/math/number/frac" (#only positive_infinity)) +(.refer "library/lux/math/number/i8" (#- equivalence width i8 i64)) +(.refer "library/lux/math/number/i16" (#exclude equivalence width i16 i64)) + +(def: for_import + Test + (let [can_access? (: (All [a] (-> a a Bit)) + (function (_ global local) + (is? global local)))] + ($_ _.and + (_.cover [/.refer] + (and (can_access? library/lux/target.jvm + jvm) + (can_access? library/lux/macro.single_expansion + single_expansion) + (can_access? library/lux/math/number/rev./4096 + /4096) + (can_access? library/lux/math/number/frac.positive_infinity + positive_infinity) + (can_access? library/lux/math/number/i8.I8 + I8) + (can_access? library/lux/math/number/i16.I16 + I16))) + ))) + (def: test Test (<| (_.covering /._) @@ -1013,6 +1045,7 @@ ..for_case ..for_control_flow ..for_def: + ..for_import ..sub_tests ))) diff --git a/stdlib/source/test/lux/control/concurrency/semaphore.lux b/stdlib/source/test/lux/control/concurrency/semaphore.lux index 1e6dd9a48..3dff3aba1 100644 --- a/stdlib/source/test/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/test/lux/control/concurrency/semaphore.lux @@ -150,7 +150,7 @@ [_ (#.Some limit)] (and (n.> 0 raw) - (n.= raw (refinement.un_refine limit))) + (n.= raw (refinement.value limit))) _ false))) diff --git a/stdlib/source/test/lux/control/parser.lux b/stdlib/source/test/lux/control/parser.lux index b71ab1256..7370e0db0 100644 --- a/stdlib/source/test/lux/control/parser.lux +++ b/stdlib/source/test/lux/control/parser.lux @@ -220,13 +220,13 @@ actual))))) (_.cover [/.between] (and (|> (list\map code.nat expected+) - (/.run (/.between times variadic <code>.nat)) + (/.run (/.between times (n.- times variadic) <code>.nat)) (match actual (\ (list.equivalence n.equivalence) = expected+ actual))) (|> (list\map code.nat (list.take times expected+)) - (/.run (/.between times variadic <code>.nat)) + (/.run (/.between times (n.- times variadic) <code>.nat)) (match actual (\ (list.equivalence n.equivalence) = (list.take times expected+) diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index 84758e83b..055a2f858 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -282,13 +282,13 @@ second octal third octal] (_.cover [/.between /.between!] - (and (..should_pass (format first second) (/.between 2 3 /.octal)) - (..should_pass (format first second third) (/.between 2 3 /.octal)) - (..should_fail (format first) (/.between 2 3 /.octal)) + (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 3 octal!)) - (..should_pass! (format first second third) (/.between! 2 3 octal!)) - (..should_fail (format first) (/.between! 2 3 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: #export test diff --git a/stdlib/source/test/lux/control/parser/tree.lux b/stdlib/source/test/lux/control/parser/tree.lux index 4b3bf2cad..25f6c350c 100644 --- a/stdlib/source/test/lux/control/parser/tree.lux +++ b/stdlib/source/test/lux/control/parser/tree.lux @@ -61,7 +61,7 @@ [expected random.nat] (_.cover [/.run'] (|> (/.run' /.value - (zipper.zip (tree.leaf expected))) + (zipper.zipper (tree.leaf expected))) (!expect (^multi (#try.Success actual) (n.= expected actual)))))) (!cover [/.down] diff --git a/stdlib/source/test/lux/control/remember.lux b/stdlib/source/test/lux/control/remember.lux index 5f62bac4b..bd9833aec 100644 --- a/stdlib/source/test/lux/control/remember.lux +++ b/stdlib/source/test/lux/control/remember.lux @@ -72,10 +72,10 @@ message (product.right (random.run prng ..message)) expected (product.right (random.run prng ..focus))] (do meta.monad - [should_fail0 (..attempt (macro.expand (to_remember macro yesterday message #.None))) - should_fail1 (..attempt (macro.expand (to_remember macro yesterday message (#.Some expected)))) - should_succeed0 (..attempt (macro.expand (to_remember macro tomorrow message #.None))) - should_succeed1 (..attempt (macro.expand (to_remember macro tomorrow message (#.Some expected))))] + [should_fail0 (..attempt (macro.expansion (to_remember macro yesterday message #.None))) + should_fail1 (..attempt (macro.expansion (to_remember macro yesterday message (#.Some expected)))) + should_succeed0 (..attempt (macro.expansion (to_remember macro tomorrow message #.None))) + should_succeed1 (..attempt (macro.expansion (to_remember macro tomorrow message (#.Some expected))))] (in (list (code.bit (and (case should_fail0 (#try.Failure error) (and (test_failure yesterday message #.None error) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index 2374b2f21..a2fc3911d 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -280,9 +280,9 @@ sample/1 ..random sample/2 ..random] ($_ _.and - (_.cover [/.as_pairs] + (_.cover [/.pairs] (n.= (n./ 2 (/.size sample/0)) - (/.size (/.as_pairs sample/0)))) + (/.size (/.pairs sample/0)))) (_.cover [/.zipped/2] (let [zipped (/.zipped/2 sample/0 sample/1) zipped::size (/.size zipped) @@ -412,7 +412,7 @@ (let [sample+ (/.interpose separator sample)] (and (n.= (|> (/.size sample) (n.* 2) dec) (/.size sample+)) - (|> sample+ /.as_pairs (/.every? (|>> product.right (n.= separator)))))))) + (|> sample+ /.pairs (/.every? (|>> product.right (n.= separator)))))))) (_.cover [/.iterate] (or (/.empty? sample) (let [size (/.size sample)] diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux index 35b55f4bf..df7333db5 100644 --- a/stdlib/source/test/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux @@ -33,14 +33,14 @@ ($_ _.and (_.cover [/.down] (|> (tree.branch dummy (list (tree.leaf expected))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.value (n.= expected) in]) (maybe.default false))) (_.cover [/.up] (|> (tree.branch expected (list (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.up] @@ -48,7 +48,7 @@ (maybe.default false))) (_.cover [/.right] (|> (tree.branch dummy (list (tree.leaf dummy) (tree.leaf expected))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.right] @@ -60,7 +60,7 @@ (tree.leaf dummy) (tree.leaf dummy) (tree.leaf expected))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.rightmost] @@ -68,7 +68,7 @@ (maybe.default false))) (_.cover [/.left] (|> (tree.branch dummy (list (tree.leaf expected) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.right] @@ -81,7 +81,7 @@ (tree.leaf dummy) (tree.leaf dummy) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [/.rightmost] @@ -92,7 +92,7 @@ (and (|> (tree.branch dummy (list (tree.leaf expected) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.next] [/.value (n.= expected) in]) @@ -100,7 +100,7 @@ (|> (tree.branch dummy (list (tree.leaf dummy) (tree.leaf expected))) - /.zip + /.zipper (do> maybe.monad [/.next] [/.next] @@ -112,7 +112,7 @@ (tree.leaf dummy) (tree.leaf dummy) (tree.leaf expected))) - /.zip + /.zipper (do> maybe.monad [/.end] [/.value (n.= expected) in]) @@ -123,7 +123,7 @@ (tree.leaf dummy) (tree.leaf dummy) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.end] [/.start] @@ -133,7 +133,7 @@ (and (|> (tree.branch expected (list (tree.leaf dummy) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.next] [/.previous] @@ -142,7 +142,7 @@ (|> (tree.branch dummy (list (tree.leaf expected) (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.next] [/.next] @@ -163,45 +163,45 @@ (^open "list\.") (list.equivalence n.equivalence)]] ($_ _.and (_.for [/.equivalence] - ($equivalence.spec (/.equivalence n.equivalence) (\ ! map (|>> product.right /.zip) (//.tree random.nat)))) + ($equivalence.spec (/.equivalence n.equivalence) (\ ! map (|>> product.right /.zipper) (//.tree random.nat)))) (_.for [/.functor] - ($functor.spec (|>> tree.leaf /.zip) /.equivalence /.functor)) + ($functor.spec (|>> tree.leaf /.zipper) /.equivalence /.functor)) (_.for [/.comonad] - ($comonad.spec (|>> tree.leaf /.zip) /.equivalence /.comonad)) + ($comonad.spec (|>> tree.leaf /.zipper) /.equivalence /.comonad)) - (_.cover [/.zip /.unzip] - (|> sample /.zip /.unzip (tree\= sample))) + (_.cover [/.zipper /.tree] + (|> sample /.zipper /.tree (tree\= sample))) (_.cover [/.start?] - (|> sample /.zip /.start?)) + (|> sample /.zipper /.start?)) (_.cover [/.leaf?] - (/.leaf? (/.zip (tree.leaf expected)))) + (/.leaf? (/.zipper (tree.leaf expected)))) (_.cover [/.branch?] - (and (/.branch? (/.zip (tree.branch expected (list (tree.leaf expected))))) - (not (/.branch? (/.zip (tree.branch expected (list))))))) + (and (/.branch? (/.zipper (tree.branch expected (list (tree.leaf expected))))) + (not (/.branch? (/.zipper (tree.branch expected (list))))))) (_.cover [/.value] - (and (n.= expected (/.value (/.zip (tree.leaf expected)))) - (n.= expected (/.value (/.zip (tree.branch expected (list (tree.leaf expected)))))))) + (and (n.= expected (/.value (/.zipper (tree.leaf expected)))) + (n.= expected (/.value (/.zipper (tree.branch expected (list (tree.leaf expected)))))))) (_.cover [/.set] - (|> (/.zip (tree.leaf dummy)) + (|> (/.zipper (tree.leaf dummy)) (/.set expected) /.value (n.= expected))) (_.cover [/.update] - (|> (/.zip (tree.leaf expected)) + (|> (/.zipper (tree.leaf expected)) (/.update inc) /.value (n.= (inc expected)))) ..move (_.cover [/.end?] - (or (/.end? (/.zip sample)) + (or (/.end? (/.zipper sample)) (|> sample - /.zip + /.zipper /.end (maybe\map /.end?) (maybe.default false)))) (_.cover [/.interpose] (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zip + /.zipper (/.interpose expected))] (and (n.= dummy (/.value cursor)) (|> cursor @@ -217,7 +217,7 @@ (maybe.default false))))) (_.cover [/.adopt] (let [cursor (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zip + /.zipper (/.adopt expected))] (and (n.= dummy (/.value cursor)) (|> cursor @@ -233,7 +233,7 @@ (maybe.default false))))) (_.cover [/.insert_left] (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [(/.insert_left expected)] @@ -242,7 +242,7 @@ (maybe.default false))) (_.cover [/.insert_right] (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [(/.insert_right expected)] @@ -251,7 +251,7 @@ (maybe.default false))) (_.cover [/.remove] (|> (tree.branch dummy (list (tree.leaf dummy))) - /.zip + /.zipper (do> maybe.monad [/.down] [(/.insert_left expected)] diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index 7223497d1..f39c25c01 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -65,15 +65,15 @@ [/.prefix /.starts_with?] [/.suffix /.ends_with?] - [/.enclose' /.encloses?] + [/.enclosed' /.enclosed_by?] )) - (_.cover [/.enclose] - (let [value (/.enclose [left right] inner)] + (_.cover [/.enclosed] + (let [value (/.enclosed [left right] inner)] (and (/.starts_with? left value) (/.ends_with? right value)))) (_.cover [/.format] (let [sample (/.format inner)] - (and (/.encloses? /.double_quote sample) + (and (/.enclosed_by? /.double_quote sample) (/.contains? inner sample)))) )))) diff --git a/stdlib/source/test/lux/debug.lux b/stdlib/source/test/lux/debug.lux index 638afd90f..a7741082a 100644 --- a/stdlib/source/test/lux/debug.lux +++ b/stdlib/source/test/lux/debug.lux @@ -210,13 +210,13 @@ (: (List Any)) (list\map /.inspection) (text.join_with " ") - (text.enclose ["[" "]"])) + (text.enclosed ["[" "]"])) (/.inspection [sample_bit sample_int sample_frac sample_text])) ))))) (syntax: (macro_error macro) (function (_ compiler) - (case ((macro.expand macro) compiler) + (case ((macro.expansion macro) compiler) (#try.Failure error) (#try.Success [compiler (list (code.text error))]) diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux index 4eb815ff7..b5d9fffbf 100644 --- a/stdlib/source/test/lux/ffi.jvm.lux +++ b/stdlib/source/test/lux/ffi.jvm.lux @@ -56,7 +56,7 @@ (syntax: (macro_error expression) (function (_ lux) - (|> (macro.expand_once expression) + (|> (macro.single_expansion expression) (meta.run lux) (case> (#try.Success expansion) (#try.Failure "OOPS!") diff --git a/stdlib/source/test/lux/macro.lux b/stdlib/source/test/lux/macro.lux index 20db9b265..115b5168e 100644 --- a/stdlib/source/test/lux/macro.lux +++ b/stdlib/source/test/lux/macro.lux @@ -75,9 +75,9 @@ {#.module_hash 0 #.module_aliases (list) #.definitions (: (List [Text .Global]) - (list (!global /.log_expand_once!) - (!global /.log_expand!) - (!global /.log_expand_all!))) + (list (!global /.log_single_expansion!) + (!global /.log_expansion!) + (!global /.log_full_expansion!))) #.imports (list) #.tags (list) #.types (list) @@ -113,11 +113,11 @@ pow/1 (\ ! map code.nat random.nat) repetitions (\ ! map (nat.% 10) random.nat) - #let [expand_once (` (..pow/2 (..pow/2 (~ pow/1)))) - expand (` (nat.* (..pow/2 (~ pow/1)) + #let [single_expansion (` (..pow/2 (..pow/2 (~ pow/1)))) + expansion (` (nat.* (..pow/2 (~ pow/1)) (..pow/2 (~ pow/1)))) - expand_all (` (nat.* (nat.* (~ pow/1) (~ pow/1)) - (nat.* (~ pow/1) (~ pow/1))))]] + full_expansion (` (nat.* (nat.* (~ pow/1) (~ pow/1)) + (nat.* (~ pow/1) (~ pow/1))))]] (`` ($_ _.and (~~ (template [<expander> <logger> <expansion>] [(_.cover [<expander>] @@ -128,22 +128,22 @@ (try.default false))) (_.cover [<logger>] - (and (|> (/.expand_once (` (<logger> (~' #omit) (..pow/4 (~ pow/1))))) + (and (|> (/.single_expansion (` (<logger> (~' #omit) (..pow/4 (~ pow/1))))) (meta.run lux) (try\map (\ (list.equivalence code.equivalence) = (list))) (try.default false)) - (|> (/.expand_once (` (<logger> (..pow/4 (~ pow/1))))) + (|> (/.single_expansion (` (<logger> (..pow/4 (~ pow/1))))) (meta.run lux) (try\map (\ (list.equivalence code.equivalence) = (list <expansion>))) (try.default false))))] - [/.expand_once /.log_expand_once! expand_once] - [/.expand /.log_expand! expand] - [/.expand_all /.log_expand_all! expand_all] + [/.single_expansion /.log_single_expansion! single_expansion] + [/.expansion /.log_expansion! expansion] + [/.full_expansion /.log_full_expansion! full_expansion] )) - (_.cover [/.expand_1] + (_.cover [/.one_expansion] (bit\= (not (nat.= 1 repetitions)) - (|> (/.expand_1 (` (..repeat (~ (code.nat repetitions)) (~ pow/1)))) + (|> (/.one_expansion (` (..repeat (~ (code.nat repetitions)) (~ pow/1)))) (meta.run lux) (!expect (#try.Failure _))))) )))) @@ -163,10 +163,10 @@ (and (text.contains? gensym_prefix actual_gensym) (text.contains? (%.nat seed) actual_gensym)))))) (_.cover [/.wrong_syntax_error] - (|> (/.expand_once (` (/.log_expand_once!))) + (|> (/.single_expansion (` (/.log_single_expansion!))) (meta.run lux) (!expect (^multi (#try.Failure error) - (text.contains? (/.wrong_syntax_error (name_of /.log_expand_once!)) + (text.contains? (/.wrong_syntax_error (name_of /.log_single_expansion!)) error))))) (_.cover [/.with_gensyms] (with_expansions [<expected> (fresh_identifier)] diff --git a/stdlib/source/test/lux/macro/local.lux b/stdlib/source/test/lux/macro/local.lux index 37b718a8e..8b8a14790 100644 --- a/stdlib/source/test/lux/macro/local.lux +++ b/stdlib/source/test/lux/macro/local.lux @@ -29,7 +29,7 @@ (syntax: (macro_error macro) (function (_ compiler) - (case ((macro.expand macro) compiler) + (case ((macro.expansion macro) compiler) (#try.Failure error) (#try.Success [compiler (list (code.text error))]) @@ -61,7 +61,7 @@ (exec (~ pop!) (~ g!output))))] (if pre_remove - (macro.expand_all pre_expansion) + (macro.full_expansion pre_expansion) (in (list pre_expansion))))))) (def: #export test diff --git a/stdlib/source/test/lux/macro/template.lux b/stdlib/source/test/lux/macro/template.lux index c46bb5b8c..ecec132d7 100644 --- a/stdlib/source/test/lux/macro/template.lux +++ b/stdlib/source/test/lux/macro/template.lux @@ -28,7 +28,7 @@ (syntax: (macro_error macro) (function (_ compiler) - (case ((macro.expand macro) compiler) + (case ((macro.expansion macro) compiler) (#try.Failure error) (#try.Success [compiler (list (code.text error))]) diff --git a/stdlib/source/test/lux/math/number/int.lux b/stdlib/source/test/lux/math/number/int.lux index 99738824a..00b66d700 100644 --- a/stdlib/source/test/lux/math/number/int.lux +++ b/stdlib/source/test/lux/math/number/int.lux @@ -177,9 +177,11 @@ (and subtraction! inverse!)))) (do {! random.monad} - [expected (\ ! map (/.% +1,000,000) random.int)] + [expected (\ ! map (/.% +1,000,000) random.int) + sample random.int] (_.cover [/.frac] - (|> expected /.frac f.int (/.= expected)))) + (and (|> expected /.frac f.int (/.= expected)) + (f.number? (/.frac sample))))) (do {! random.monad} [pattern random.int idx (\ ! map (n.% i64.width) random.nat)] diff --git a/stdlib/source/test/lux/math/number/nat.lux b/stdlib/source/test/lux/math/number/nat.lux index 3d553e167..05fbfb303 100644 --- a/stdlib/source/test/lux/math/number/nat.lux +++ b/stdlib/source/test/lux/math/number/nat.lux @@ -121,9 +121,11 @@ (/.= 0 (/.% right lcm))))) )) (do {! random.monad} - [expected (\ ! map (/.% 1,000,000) random.nat)] + [expected (\ ! map (/.% 1,000,000) random.nat) + sample random.nat] (_.cover [/.frac] - (|> expected /.frac f.nat (/.= expected)))) + (and (|> expected /.frac f.nat (/.= expected)) + (f.number? (/.frac sample))))) ..predicate ..signature diff --git a/stdlib/source/test/lux/math/number/rev.lux b/stdlib/source/test/lux/math/number/rev.lux index a302b2fc3..e99a1f656 100644 --- a/stdlib/source/test/lux/math/number/rev.lux +++ b/stdlib/source/test/lux/math/number/rev.lux @@ -156,9 +156,11 @@ (|> sample /.reciprocal .nat /.reciprocal .nat /.reciprocal)))) (do {! random.monad} [expected (\ ! map (|>> f.abs (f.% +1.0)) - random.safe_frac)] + random.safe_frac) + sample random.rev] (_.cover [/.frac] - (|> expected f.rev /.frac (f.= expected)))) + (and (|> expected f.rev /.frac (f.= expected)) + (f.number? (/.frac sample))))) ..signature )))) diff --git a/stdlib/source/test/lux/type/abstract.lux b/stdlib/source/test/lux/type/abstract.lux index aaeb6f1b6..2b96f6788 100644 --- a/stdlib/source/test/lux/type/abstract.lux +++ b/stdlib/source/test/lux/type/abstract.lux @@ -34,7 +34,7 @@ (syntax: (with_no_active_frames macro) (function (_ compiler) - (let [verdict (case ((macro.expand macro) compiler) + (let [verdict (case ((macro.expansion macro) compiler) (#try.Failure error) (exception.match? /.no_active_frames error) diff --git a/stdlib/source/test/lux/type/refinement.lux b/stdlib/source/test/lux/type/refinement.lux index 52c8fac88..ecfbe8aab 100644 --- a/stdlib/source/test/lux/type/refinement.lux +++ b/stdlib/source/test/lux/type/refinement.lux @@ -48,20 +48,20 @@ (maybe\map (|>> /.predicate (is? predicate))) (maybe.default false))) )) - (_.cover [/.un_refine] + (_.cover [/.value] (|> (/.refinement predicate modulus) - (maybe\map (|>> /.un_refine (n.= modulus))) + (maybe\map (|>> /.value (n.= modulus))) (maybe.default false))) (_.cover [/.lift] (and (|> (/.refinement predicate modulus) (maybe\map (/.lift (n.+ modulus))) maybe\join - (maybe\map (|>> /.un_refine (n.= (n.+ modulus modulus)))) + (maybe\map (|>> /.value (n.= (n.+ modulus modulus)))) (maybe.default false)) (|> (/.refinement predicate modulus) (maybe\map (/.lift (n.+ (inc modulus)))) maybe\join - (maybe\map (|>> /.un_refine (n.= (n.+ modulus (inc modulus))))) + (maybe\map (|>> /.value (n.= (n.+ modulus (inc modulus))))) (maybe.default false) not))) (_.cover [/.only] @@ -71,7 +71,7 @@ (list.size actual)) (\ (list.equivalence n.equivalence) = expected - (list\map /.un_refine actual))))) + (list\map /.value actual))))) (_.cover [/.partition] (let [expected (list.only predicate raws) [actual alternative] (/.partition (/.refinement predicate) raws)] @@ -81,7 +81,7 @@ (list.size alternative)) (\ (list.equivalence n.equivalence) = expected - (list\map /.un_refine actual))))) + (list\map /.value actual))))) (_.cover [/.type] (exec (: (Maybe .._type) (.._refiner raw)) diff --git a/stdlib/source/test/lux/type/resource.lux b/stdlib/source/test/lux/type/resource.lux index cd6f78096..f761a0f3f 100644 --- a/stdlib/source/test/lux/type/resource.lux +++ b/stdlib/source/test/lux/type/resource.lux @@ -153,7 +153,7 @@ [[_ _ _ exception] (meta.export exception)] (function (_ compiler) (#.Right [compiler - (list (code.bit (case ((macro.expand_once to_expand) compiler) + (list (code.bit (case ((macro.single_expansion to_expand) compiler) (#try.Success _) false |