From bcd70df3568d71f14763959f454c15d8164e2d15 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sun, 1 Aug 2021 03:36:11 -0400 Subject: Even more renamings. --- stdlib/source/test/aedifex/cache.lux | 2 +- .../source/test/aedifex/dependency/deployment.lux | 4 +- stdlib/source/test/aedifex/repository.lux | 2 +- stdlib/source/test/lux.lux | 40 +++-- stdlib/source/test/lux/abstract/enum.lux | 2 +- stdlib/source/test/lux/control/function/memo.lux | 4 +- stdlib/source/test/lux/control/parser/text.lux | 72 ++++---- stdlib/source/test/lux/control/parser/xml.lux | 18 +- stdlib/source/test/lux/data/binary.lux | 2 +- stdlib/source/test/lux/data/collection/array.lux | 18 +- .../source/test/lux/data/collection/dictionary.lux | 20 +-- .../lux/data/collection/dictionary/ordered.lux | 6 +- stdlib/source/test/lux/data/collection/list.lux | 10 +- stdlib/source/test/lux/data/collection/row.lux | 6 +- stdlib/source/test/lux/data/collection/set.lux | 10 +- .../source/test/lux/data/collection/set/multi.lux | 8 +- .../test/lux/data/collection/set/ordered.lux | 8 +- stdlib/source/test/lux/data/color.lux | 14 +- stdlib/source/test/lux/data/product.lux | 2 +- stdlib/source/test/lux/data/sum.lux | 20 +-- stdlib/source/test/lux/data/text.lux | 24 +-- stdlib/source/test/lux/data/text/encoding.lux | 2 +- stdlib/source/test/lux/data/text/escape.lux | 6 +- stdlib/source/test/lux/data/text/regex.lux | 8 +- stdlib/source/test/lux/debug.lux | 4 +- stdlib/source/test/lux/ffi.jvm.lux | 38 +++- stdlib/source/test/lux/locale/language.lux | 4 +- stdlib/source/test/lux/locale/territory.lux | 4 +- stdlib/source/test/lux/macro/poly/equivalence.lux | 2 +- stdlib/source/test/lux/macro/poly/json.lux | 2 +- stdlib/source/test/lux/math/number/i64.lux | 8 +- stdlib/source/test/lux/program.lux | 2 +- stdlib/source/test/lux/time/duration.lux | 12 +- .../compiler/language/lux/phase/synthesis/case.lux | 4 +- .../language/lux/phase/synthesis/function.lux | 2 +- .../language/lux/phase/synthesis/variable.lux | 2 +- .../test/lux/tool/compiler/language/lux/syntax.lux | 8 +- stdlib/source/test/lux/type.lux | 4 +- stdlib/source/test/lux/type/resource.lux | 191 ++++++++++----------- 39 files changed, 313 insertions(+), 282 deletions(-) (limited to 'stdlib/source/test') diff --git a/stdlib/source/test/aedifex/cache.lux b/stdlib/source/test/aedifex/cache.lux index 4b7fcc885..614420fde 100644 --- a/stdlib/source/test/aedifex/cache.lux +++ b/stdlib/source/test/aedifex/cache.lux @@ -88,7 +88,7 @@ (do ! [pom (random.one (function (_ [identity profile pom]) (|> profile - (set@ #//.dependencies (set.new //dependency.hash)) + (set@ #//.dependencies (set.empty //dependency.hash)) (set@ #//.identity (#.Some (get@ #//dependency.artifact dependency))) //pom.write try.to_maybe)) diff --git a/stdlib/source/test/aedifex/dependency/deployment.lux b/stdlib/source/test/aedifex/dependency/deployment.lux index e62e7b2e4..9c575ff53 100644 --- a/stdlib/source/test/aedifex/dependency/deployment.lux +++ b/stdlib/source/test/aedifex/dependency/deployment.lux @@ -153,7 +153,7 @@ (do {! random.monad} [[dependency expected_artifact package] ..bundle #let [cache (: Cache - (atom.atom (dictionary.new text.hash))) + (atom.atom (dictionary.empty text.hash))) http (..http cache) repository (repository.async (remote.repository http #.None address))]] (in (do async.monad @@ -176,7 +176,7 @@ resolution.empty bundles) cache (: Cache - (atom.atom (dictionary.new text.hash))) + (atom.atom (dictionary.empty text.hash))) http (..http cache) repository (repository.async (remote.repository http #.None address))]] (in (do async.monad diff --git a/stdlib/source/test/aedifex/repository.lux b/stdlib/source/test/aedifex/repository.lux index a926db9a7..88efb42fe 100644 --- a/stdlib/source/test/aedifex/repository.lux +++ b/stdlib/source/test/aedifex/repository.lux @@ -55,7 +55,7 @@ (def: #export empty Store - (dictionary.new text.hash)) + (dictionary.empty text.hash)) (def: valid_version Version diff --git a/stdlib/source/test/lux.lux b/stdlib/source/test/lux.lux index 793fd23b3..63d468945 100644 --- a/stdlib/source/test/lux.lux +++ b/stdlib/source/test/lux.lux @@ -423,22 +423,24 @@ (#.Right [lux (list)])))] (do random.monad [expected random.nat] - ($_ _.and - (_.cover [/.Macro'] - (|> macro - (: /.Macro') - (is? macro))) - (_.cover [/.Macro] - (|> macro - "lux macro" - (: /.Macro) - (: Any) - (is? (: Any macro)))) - (_.cover [/.macro:] - (is? expected (..identity_macro expected))) - (_.cover [/.Source] - (..found_crosshair?)) - )))) + (with_expansions [ (for {@.old (~~ (as_is))} + (_.cover [/.Source] + (..found_crosshair?)))] + (`` ($_ _.and + (_.cover [/.Macro'] + (|> macro + (: /.Macro') + (is? macro))) + (_.cover [/.Macro] + (|> macro + "lux macro" + (: /.Macro) + (: Any) + (is? (: Any macro)))) + (_.cover [/.macro:] + (is? expected (..identity_macro expected))) + + )))))) (/.type: for_type/variant #Case/0 @@ -484,7 +486,7 @@ (_.cover [/.:let] (let [[actual_left actual_right] (: (/.:let [side /.Nat] - (& side side)) + [side side]) [expected_left expected_right])] (and (is? expected_left actual_left) (is? expected_right actual_right)))) @@ -506,7 +508,7 @@ _ false) - (case (/.type (| expected/0 expected/1)) + (case (/.type (/.Or expected/0 expected/1)) (#.Sum actual/0 actual/1) (and (is? expected/0 actual/0) (is? expected/1 actual/1)) @@ -626,7 +628,7 @@ _ false)) (_.cover [/.char] (|> (`` (/.char (~~ (/.static static_char)))) - text.of_code + text.of_char (text\= static_char))) ))) diff --git a/stdlib/source/test/lux/abstract/enum.lux b/stdlib/source/test/lux/abstract/enum.lux index b389a9c8b..6284381d7 100644 --- a/stdlib/source/test/lux/abstract/enum.lux +++ b/stdlib/source/test/lux/abstract/enum.lux @@ -35,7 +35,7 @@ expected_end? (|> range list.last (maybe\map (n.= end)) (maybe.else false)) can_be_backwards? (\ (list.equivalence n.equivalence) = (/.range n.enum start end) - (list.reverse (/.range n.enum end start))) + (list.reversed (/.range n.enum end start))) every_element_is_a_successor? (case range (#.Item head tail) (|> (list\fold (function (_ next [verdict prev]) diff --git a/stdlib/source/test/lux/control/function/memo.lux b/stdlib/source/test/lux/control/function/memo.lux index 67824f3f3..dbdeee0f6 100644 --- a/stdlib/source/test/lux/control/function/memo.lux +++ b/stdlib/source/test/lux/control/function/memo.lux @@ -81,7 +81,7 @@ (io.run (do io.monad [#let [none (/.none n.hash ..fibonacci) - memory (dictionary.new n.hash) + memory (dictionary.empty n.hash) open (/.open fibonacci)] [none_time none_output] (..time none input) [open_time [memory open_output]] (..time open [memory input]) @@ -114,7 +114,7 @@ (list\map inc) (list\fold n.* 1)) actual (|> (memo input) - (state.run (dictionary.new n.hash)) + (state.run (dictionary.empty n.hash)) product.right)] (n.= expected actual))) ))) diff --git a/stdlib/source/test/lux/control/parser/text.lux b/stdlib/source/test/lux/control/parser/text.lux index b3031cc26..c8fa56388 100644 --- a/stdlib/source/test/lux/control/parser/text.lux +++ b/stdlib/source/test/lux/control/parser/text.lux @@ -75,10 +75,10 @@ [offset (\ ! map (n.% 50) random.nat) range (\ ! map (|>> (n.% 50) (n.+ 10)) random.nat) #let [limit (n.+ offset range)] - expected (\ ! map (|>> (n.% range) (n.+ offset) text.of_code) random.nat) + expected (\ ! map (|>> (n.% range) (n.+ offset) text.of_char) random.nat) out_of_range (case offset - 0 (\ ! map (|>> (n.% 10) inc (n.+ limit) text.of_code) random.nat) - _ (\ ! map (|>> (n.% offset) text.of_code) random.nat))] + 0 (\ ! map (|>> (n.% 10) inc (n.+ limit) text.of_char) random.nat) + _ (\ ! map (|>> (n.% offset) text.of_char) random.nat))] (_.cover [/.range] (and (..should_pass expected (/.range offset limit)) (..should_fail out_of_range (/.range offset limit))))) @@ -87,33 +87,33 @@ invalid (random.only (|>> (unicode/block.within? unicode/block.basic_latin/upper) not) (random.char unicode.character))] (_.cover [/.upper] - (and (..should_pass (text.of_code expected) /.upper) - (..should_fail (text.of_code invalid) /.upper)))) + (and (..should_pass (text.of_char expected) /.upper) + (..should_fail (text.of_char invalid) /.upper)))) (do {! random.monad} [expected (random.char unicode.ascii/lower) invalid (random.only (|>> (unicode/block.within? unicode/block.basic_latin/lower) not) (random.char unicode.character))] (_.cover [/.lower] - (and (..should_pass (text.of_code expected) /.lower) - (..should_fail (text.of_code invalid) /.lower)))) + (and (..should_pass (text.of_char expected) /.lower) + (..should_fail (text.of_char invalid) /.lower)))) (do {! random.monad} [expected (\ ! map (n.% 10) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] (_.cover [/.decimal] (and (..should_pass (\ n.decimal encode expected) /.decimal) - (..should_fail (text.of_code invalid) /.decimal)))) + (..should_fail (text.of_char invalid) /.decimal)))) (do {! random.monad} [expected (\ ! map (n.% 8) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] (_.cover [/.octal] (and (..should_pass (\ n.octal encode expected) /.octal) - (..should_fail (text.of_code invalid) /.octal)))) + (..should_fail (text.of_char invalid) /.octal)))) (do {! random.monad} [expected (\ ! map (n.% 16) random.nat) invalid (random.char (unicode.set [unicode/block.number_forms (list)]))] (_.cover [/.hexadecimal] (and (..should_pass (\ n.hex encode expected) /.hexadecimal) - (..should_fail (text.of_code invalid) /.hexadecimal)))) + (..should_fail (text.of_char invalid) /.hexadecimal)))) (do {! random.monad} [expected (random.char unicode.ascii/alpha) invalid (random.only (function (_ char) @@ -121,8 +121,8 @@ (unicode/block.within? unicode/block.basic_latin/lower char)))) (random.char unicode.character))] (_.cover [/.alpha] - (and (..should_pass (text.of_code expected) /.alpha) - (..should_fail (text.of_code invalid) /.alpha)))) + (and (..should_pass (text.of_char expected) /.alpha) + (..should_fail (text.of_char invalid) /.alpha)))) (do {! random.monad} [expected (random.char unicode.ascii/alpha_num) invalid (random.only (function (_ char) @@ -131,8 +131,8 @@ (unicode/block.within? unicode/block.basic_latin/decimal char)))) (random.char unicode.character))] (_.cover [/.alpha_num] - (and (..should_pass (text.of_code expected) /.alpha_num) - (..should_fail (text.of_code invalid) /.alpha_num)))) + (and (..should_pass (text.of_char expected) /.alpha_num) + (..should_fail (text.of_char invalid) /.alpha_num)))) (do {! random.monad} [expected ($_ random.either (in text.tab) @@ -156,7 +156,7 @@ options (|> (random.char unicode.character) (random.set n.hash num_options) (\ ! map (|>> set.to_list - (list\map text.of_code) + (list\map text.of_char) (text.join_with "")))) expected (\ ! map (function (_ value) (|> options @@ -164,17 +164,17 @@ maybe.assume)) random.nat) invalid (random.only (function (_ char) - (not (text.contains? (text.of_code char) options))) + (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_code expected) (/.one_of options)) - (..should_fail (text.of_code invalid) (/.one_of options)) - (..should_fail' (text.of_code invalid) (/.one_of options) + (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_code expected) (/.one_of! options)) - (..should_fail (text.of_code invalid) (/.one_of! options)) - (..should_fail' (text.of_code invalid) (/.one_of! options) + (..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} @@ -182,7 +182,7 @@ options (|> (random.char unicode.character) (random.set n.hash num_options) (\ ! map (|>> set.to_list - (list\map text.of_code) + (list\map text.of_char) (text.join_with "")))) invalid (\ ! map (function (_ value) (|> options @@ -190,17 +190,17 @@ maybe.assume)) random.nat) expected (random.only (function (_ char) - (not (text.contains? (text.of_code char) options))) + (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_code expected) (/.none_of options)) - (..should_fail (text.of_code invalid) (/.none_of options)) - (..should_fail' (text.of_code invalid) (/.none_of options) + (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_code expected) (/.none_of! options)) - (..should_fail (text.of_code invalid) (/.none_of! options)) - (..should_fail' (text.of_code invalid) (/.none_of! options) + (..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) ))) )) @@ -402,13 +402,13 @@ (random.char unicode.character)) #let [upper! (/.one_of! "ABCDEFGHIJKLMNOPQRSTUVWXYZ")]] (_.cover [/.not /.not! /.expected_to_fail] - (and (..should_pass (text.of_code expected) (/.not /.upper)) + (and (..should_pass (text.of_char expected) (/.not /.upper)) (|> invalid (/.run (/.not /.upper)) (!expect (^multi (#try.Failure error) (exception.match? /.expected_to_fail error)))) - (..should_pass! (text.of_code expected) (/.not! upper!)) + (..should_pass! (text.of_char expected) (/.not! upper!)) (|> invalid (/.run (/.not! upper!)) (!expect (^multi (#try.Failure error) @@ -424,12 +424,12 @@ lower! (/.one_of! "abcdefghijklmnopqrstuvwxyz")]] (_.cover [/.and /.and!] (and (..should_pass (format upper lower) (/.and /.upper /.lower)) - (..should_fail (format (text.of_code invalid) lower) (/.and /.upper /.lower)) - (..should_fail (format upper (text.of_code invalid)) (/.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_code invalid) lower) (/.and! upper! lower!)) - (..should_fail (format upper (text.of_code invalid)) (/.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)] diff --git a/stdlib/source/test/lux/control/parser/xml.lux b/stdlib/source/test/lux/control/parser/xml.lux index a6e7e7c2e..966da9edd 100644 --- a/stdlib/source/test/lux/control/parser/xml.lux +++ b/stdlib/source/test/lux/control/parser/xml.lux @@ -80,17 +80,17 @@ [actual /.tag _ /.ignore] (in (name\= expected actual))) - (list (#xml.Node expected (dictionary.new name.hash) (list)))) + (list (#xml.Node expected (dictionary.empty name.hash) (list)))) (!expect (#try.Success #1))))) (do {! random.monad} [expected ..random_tag] (_.cover [/.node] (|> (/.run (/.node expected (//\in [])) - (list (#xml.Node expected (dictionary.new name.hash) (list)))) + (list (#xml.Node expected (dictionary.empty name.hash) (list)))) (!expect (#try.Success []))))) (!failure /.wrong_tag [[(/.node ["" expected] (//\in [])) - (#xml.Node [expected ""] (dictionary.new name.hash) (list))]]) + (#xml.Node [expected ""] (dictionary.empty name.hash) (list))]]) (do {! random.monad} [expected_tag ..random_tag expected_attribute ..random_attribute @@ -100,14 +100,14 @@ (//.after (/.attribute expected_attribute)) (//\in [])) (list (#xml.Node expected_tag - (|> (dictionary.new name.hash) + (|> (dictionary.empty name.hash) (dictionary.put expected_attribute expected_value)) (list)))) (!expect (#try.Success []))))) (!failure /.unknown_attribute [[(/.attribute ["" expected]) (#xml.Node [expected expected] - (|> (dictionary.new name.hash) + (|> (dictionary.empty name.hash) (dictionary.put [expected ""] expected)) (list))]]) (!failure /.empty_input @@ -124,19 +124,19 @@ (/.node [expected expected] (//\in []))) (#xml.Node [expected expected] - (dictionary.new name.hash) + (dictionary.empty name.hash) (list))] [(do //.monad [_ /.ignore] (/.node [expected expected] (/.attribute [expected expected]))) (#xml.Node [expected expected] - (|> (dictionary.new name.hash) + (|> (dictionary.empty name.hash) (dictionary.put [expected expected] expected)) (list))]]) (!failure /.unexpected_input [[/.text - (#xml.Node [expected expected] (dictionary.new name.hash) (list))] + (#xml.Node [expected expected] (dictionary.empty name.hash) (list))] [(/.node [expected expected] (//\in [])) (#xml.Text expected)] @@ -146,7 +146,7 @@ (do {! random.monad} [#let [node (: (-> xml.Tag (List xml.XML) xml.XML) (function (_ tag children) - (#xml.Node tag (dictionary.new name.hash) children)))] + (#xml.Node tag (dictionary.empty name.hash) children)))] parent ..random_tag right ..random_tag wrong (random.only (|>> (name\= right) not) diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index 638668ec5..2d1a25092 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -137,7 +137,7 @@ (_.cover [/.drop] (and (\ /.equivalence = sample (/.drop 0 sample)) (\ /.equivalence = (/.create 0) (/.drop size sample)) - (case (list.reverse (..as_list sample)) + (case (list.reversed (..as_list sample)) #.End false diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux index 29f0c733a..d5ea9badf 100644 --- a/stdlib/source/test/lux/data/collection/array.lux +++ b/stdlib/source/test/lux/data/collection/array.lux @@ -103,9 +103,9 @@ ..structures ..search - (_.cover [/.new /.size] + (_.cover [/.empty /.size] (n.= size (/.size (: (Array Nat) - (/.new size))))) + (/.empty size))))) (_.cover [/.type_name] (case /.Array (^ (#.Named _ (#.UnivQ _ (#.Primitive nominal_type (list (#.Parameter 1)))))) @@ -114,7 +114,7 @@ _ false)) (_.cover [/.read /.write!] - (let [the_array (|> (/.new 2) + (let [the_array (|> (/.empty 2) (: (Array Nat)) (/.write! 0 expected))] (case [(/.read 0 the_array) @@ -125,7 +125,7 @@ _ false))) (_.cover [/.delete!] - (let [the_array (|> (/.new 1) + (let [the_array (|> (/.empty 1) (: (Array Nat)) (/.write! 0 expected))] (case [(/.read 0 the_array) @@ -136,14 +136,14 @@ _ false))) (_.cover [/.contains?] - (let [the_array (|> (/.new 2) + (let [the_array (|> (/.empty 2) (: (Array Nat)) (/.write! 0 expected))] (and (/.contains? 0 the_array) (not (/.contains? 1 the_array))))) (_.cover [/.update!] - (let [the_array (|> (/.new 1) + (let [the_array (|> (/.empty 1) (: (Array Nat)) (/.write! 0 base) (/.update! 0 (n.+ shift)))] @@ -154,7 +154,7 @@ _ false))) (_.cover [/.upsert!] - (let [the_array (|> (/.new 2) + (let [the_array (|> (/.empty 2) (: (Array Nat)) (/.write! 0 base) (/.upsert! 0 dummy (n.+ shift)) @@ -171,7 +171,7 @@ [occupancy (\ ! map (n.% (inc size)) random.nat)] (_.cover [/.occupancy /.vacancy] (let [the_array (loop [output (: (Array Nat) - (/.new size)) + (/.empty size)) idx 0] (if (n.< occupancy idx) (recur (/.write! idx expected output) @@ -191,7 +191,7 @@ [amount (\ ! map (n.% (inc size)) random.nat)] (_.cover [/.copy!] (let [copy (: (Array Nat) - (/.new size))] + (/.empty size))] (exec (/.copy! amount 0 the_array 0 copy) (\ (list.equivalence n.equivalence) = (list.take amount (/.to_list the_array)) diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 2cec43439..11c4b59cd 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -47,8 +47,8 @@ 0 (/.empty? dict) _ (not (/.empty? dict)))) - (_.cover [/.new] - (let [sample (/.new n.hash)] + (_.cover [/.empty] + (let [sample (/.empty n.hash)] (and (n.= 0 (/.size sample)) (/.empty? sample)))) @@ -60,7 +60,7 @@ (def: (hash _) constant)))]] (_.cover [/.key_hash] - (is? hash (/.key_hash (/.new hash))))) + (is? hash (/.key_hash (/.empty hash))))) (_.cover [/.entries] (let [entries (/.entries dict) @@ -108,21 +108,21 @@ (n.= (/.size dict) (list.size (/.values dict)))) - (_.cover [/.merge] + (_.cover [/.merged] (let [merging_with_oneself (let [(^open ".") (/.equivalence n.equivalence)] - (= dict (/.merge dict dict))) + (= dict (/.merged dict dict))) overwritting_keys (let [dict' (|> dict /.entries (list\map (function (_ [k v]) [k (inc v)])) (/.of_list n.hash)) (^open ".") (/.equivalence n.equivalence)] - (= dict' (/.merge dict' dict)))] + (= dict' (/.merged dict' dict)))] (and merging_with_oneself overwritting_keys))) - (_.cover [/.merge_with] + (_.cover [/.merged_with] (list.every? (function (_ [x x*2]) (n.= (n.* 2 x) x*2)) (list.zipped/2 (/.values dict) - (/.values (/.merge_with n.+ dict dict))))) + (/.values (/.merged_with n.+ dict dict))))) (_.cover [/.of_list] (let [(^open ".") (/.equivalence n.equivalence)] @@ -230,10 +230,10 @@ (and can_upsert_new_key! can_upsert_old_key!))) - (_.cover [/.select] + (_.cover [/.sub] (|> dict (/.put non_key test_val) - (/.select (list non_key)) + (/.sub (list non_key)) /.size (n.= 1))) diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index 8302cdf38..4637d3058 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -27,7 +27,7 @@ (-> (Order k) (Random k) (Random v) Nat (Random (/.Dictionary k v)))) (case size 0 - (random\in (/.new order)) + (random\in (/.empty order)) _ (do random.monad @@ -70,8 +70,8 @@ (_.cover [/.empty?] (bit\= (n.= 0 (/.size sample)) (/.empty? sample))) - (_.cover [/.new] - (/.empty? (/.new n.order))) + (_.cover [/.empty] + (/.empty? (/.empty n.order))) (_.cover [/.min] (case [(/.min sample) (list.head sorted_values)] [#.None #.None] diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index a2fc3911d..872c21e2d 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -98,15 +98,15 @@ (n.= 0 (/.size sample)))) (_.cover [/.repeat] (n.= size (/.size (/.repeat size [])))) - (_.cover [/.reverse] + (_.cover [/.reversed] (or (n.< 2 (/.size sample)) (let [not_same! (not (/\= sample - (/.reverse sample))) + (/.reversed sample))) self_symmetry! (/\= sample - (/.reverse (/.reverse sample)))] + (/.reversed (/.reversed sample)))] (and not_same! self_symmetry!)))) (_.cover [/.every? /.any?] @@ -122,7 +122,7 @@ symmetry! (/\= (/.sort <<< sample) - (/.reverse (/.sort (function.flip <<<) sample)))] + (/.reversed (/.sort (function.flip <<<) sample)))] (and size_preservation! symmetry!))) ))) @@ -259,7 +259,7 @@ )] [/.head /.tail |>] - [/.last /.inits /.reverse] + [/.last /.inits /.reversed] )) ))))) diff --git a/stdlib/source/test/lux/data/collection/row.lux b/stdlib/source/test/lux/data/collection/row.lux index 3ac6e8965..902fec0d8 100644 --- a/stdlib/source/test/lux/data/collection/row.lux +++ b/stdlib/source/test/lux/data/collection/row.lux @@ -61,15 +61,15 @@ (/.empty? /.empty)) (_.cover [/.to_list /.of_list] (|> sample /.to_list /.of_list (/\= sample))) - (_.cover [/.reverse] + (_.cover [/.reversed] (or (n.< 2 (/.size sample)) (let [not_same! (not (/\= sample - (/.reverse sample))) + (/.reversed sample))) self_symmetry! (/\= sample - (/.reverse (/.reverse sample)))] + (/.reversed (/.reversed sample)))] (and not_same! self_symmetry!)))) (_.cover [/.every? /.any?] diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux index 64556ed63..d092dcf6f 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)] ($_ _.and - (_.cover [/.new] - (/.empty? (/.new n.hash))) + (_.cover [/.empty] + (/.empty? (/.empty n.hash))) (do ! [hash (\ ! map (function (_ constant) (: (Hash Nat) @@ -61,7 +61,7 @@ constant)))) random.nat)] (_.cover [/.member_hash] - (is? hash (/.member_hash (/.new hash))))) + (is? hash (/.member_hash (/.empty hash))))) (_.cover [/.size] (n.= sizeL (/.size setL))) (_.cover [/.empty?] @@ -106,7 +106,7 @@ union_with_empty_set! (|> setL - (/.union (/.new n.hash)) + (/.union (/.empty n.hash)) (\= setL))] (and sets_are_subs_of_their_unions! union_with_empty_set!))) @@ -119,7 +119,7 @@ intersection_with_empty_set! (|> setL - (/.intersection (/.new n.hash)) + (/.intersection (/.empty n.hash)) /.empty?)] (and sets_are_supers_of_their_intersections! intersection_with_empty_set!))) diff --git a/stdlib/source/test/lux/data/collection/set/multi.lux b/stdlib/source/test/lux/data/collection/set/multi.lux index 197f35e93..7f23bfe3d 100644 --- a/stdlib/source/test/lux/data/collection/set/multi.lux +++ b/stdlib/source/test/lux/data/collection/set/multi.lux @@ -32,7 +32,7 @@ element_counts (random.list size ..count)] (in (list\fold (function (_ [count element] set) (/.add count element set)) - (/.new hash) + (/.empty hash) (list.zipped/2 element_counts (set.to_list elements)))))) @@ -46,7 +46,7 @@ (_.for [/.hash] (|> random.nat (\ random.monad map (function (_ single) - (/.add 1 single (/.new n.hash)))) + (/.add 1 single (/.empty n.hash)))) ($hash.spec /.hash))) ))) @@ -132,8 +132,8 @@ (_.cover [/.empty?] (bit\= (/.empty? sample) (n.= 0 (/.size sample)))) - (_.cover [/.new] - (/.empty? (/.new n.hash))) + (_.cover [/.empty] + (/.empty? (/.empty n.hash))) (_.cover [/.support] (list.every? (set.member? (/.support sample)) (/.to_list sample))) diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux index 0614a1938..89ce681b0 100644 --- a/stdlib/source/test/lux/data/collection/set/ordered.lux +++ b/stdlib/source/test/lux/data/collection/set/ordered.lux @@ -27,7 +27,7 @@ (All [a] (-> Nat (Order a) (Random a) (Random (Set a)))) (case size 0 - (random\in (/.new &order)) + (random\in (/.empty &order)) _ (do random.monad @@ -51,7 +51,7 @@ #let [(^open "/\.") /.equivalence setL (/.of_list n.order listL) setR (/.of_list n.order listR) - empty (/.new n.order)]] + empty (/.empty n.order)]] (`` ($_ _.and (_.for [/.equivalence] ($equivalence.spec /.equivalence (..random sizeL n.order random.nat))) @@ -61,8 +61,8 @@ (_.cover [/.empty?] (bit\= (n.= 0 (/.size setL)) (/.empty? setL))) - (_.cover [/.new] - (/.empty? (/.new n.order))) + (_.cover [/.empty] + (/.empty? (/.empty n.order))) (_.cover [/.to_list] (\ (list.equivalence n.equivalence) = (/.to_list (/.of_list n.order listL)) diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux index c118a98ad..81c45a8e2 100644 --- a/stdlib/source/test/lux/data/color.lux +++ b/stdlib/source/test/lux/data/color.lux @@ -106,17 +106,17 @@ (distance/3 (/.darker ratio colorful) /.black)) (f.<= (distance/3 colorful /.white) (distance/3 (/.brighter ratio colorful) /.white)))) - (_.cover [/.interpolate] + (_.cover [/.interpolated] (and (f.<= (distance/3 colorful /.black) - (distance/3 (/.interpolate ratio /.black colorful) /.black)) + (distance/3 (/.interpolated ratio /.black colorful) /.black)) (f.<= (distance/3 colorful /.white) - (distance/3 (/.interpolate ratio /.white colorful) /.white)))) - (_.cover [/.saturate] + (distance/3 (/.interpolated ratio /.white colorful) /.white)))) + (_.cover [/.saturated] (f.> (saturation mediocre) - (saturation (/.saturate ratio mediocre)))) - (_.cover [/.de_saturate] + (saturation (/.saturated ratio mediocre)))) + (_.cover [/.un_saturated] (f.< (saturation mediocre) - (saturation (/.de_saturate ratio mediocre)))) + (saturation (/.un_saturated ratio mediocre)))) (_.cover [/.gray_scale] (let [gray'ed (/.gray_scale mediocre)] (and (f.= +0.0 diff --git a/stdlib/source/test/lux/data/product.lux b/stdlib/source/test/lux/data/product.lux index 867d8bb84..2f781972d 100644 --- a/stdlib/source/test/lux/data/product.lux +++ b/stdlib/source/test/lux/data/product.lux @@ -17,7 +17,7 @@ (def: #export test Test (<| (_.covering /._) - (_.for [.&]) + (_.for [.Tuple .And]) (do random.monad [expected random.nat shift random.nat diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux index 05a2746f7..73765d85f 100644 --- a/stdlib/source/test/lux/data/sum.lux +++ b/stdlib/source/test/lux/data/sum.lux @@ -23,7 +23,7 @@ (def: #export test Test (<| (_.covering /._) - (_.for [.|]) + (_.for [.Variant .Or]) (do {! random.monad} [expected random.nat shift random.nat] @@ -43,30 +43,30 @@ (_.cover [/.left] (|> (/.left expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (case> (0 #0 actual) (n.= expected actual) _ false))) (_.cover [/.right] (|> (/.right expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (case> (0 #1 actual) (n.= expected actual) _ false))) (_.cover [/.either] (and (|> (/.left expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (/.either (n.+ shift) (n.- shift)) (n.= (n.+ shift expected))) (|> (/.right expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (/.either (n.+ shift) (n.- shift)) (n.= (n.- shift expected))))) (_.cover [/.apply] (and (|> (/.left expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (/.apply (n.+ shift) (n.- shift)) (case> (0 #0 actual) (n.= (n.+ shift expected) actual) _ false)) (|> (/.right expected) - (: (| Nat Nat)) + (: (Or Nat Nat)) (/.apply (n.+ shift) (n.- shift)) (case> (0 #1 actual) (n.= (n.- shift expected) actual) _ false)))) (do ! @@ -74,7 +74,7 @@ expected (random.list size random.nat)] ($_ _.and (_.cover [/.lefts] - (let [actual (: (List (| Nat Nat)) + (let [actual (: (List (Or Nat Nat)) (list\map /.left expected))] (and (\ (list.equivalence n.equivalence) = expected @@ -83,7 +83,7 @@ (list) (/.rights actual))))) (_.cover [/.rights] - (let [actual (: (List (| Nat Nat)) + (let [actual (: (List (Or Nat Nat)) (list\map /.right expected))] (and (\ (list.equivalence n.equivalence) = expected @@ -97,7 +97,7 @@ (if (n.even? value) (/.left value) (/.right value)))) - (: (List (| Nat Nat))) + (: (List (Or Nat Nat))) /.partition)] (and (\ (list.equivalence n.equivalence) = (list.only n.even? expected) diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index e1f9c1e4f..82a364120 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -98,20 +98,20 @@ (n.= 1)))) (_.cover [/.index_of'] (let [full (\ /.monoid compose inner outer)] - (and (|> (/.index_of' inner 0 full) + (and (|> (/.index_of' 0 inner full) (maybe.else fake_index) (n.= 0)) - (|> (/.index_of' inner 1 full) + (|> (/.index_of' 1 inner full) (maybe.else fake_index) (n.= fake_index)) - (|> (/.index_of' outer 0 full) + (|> (/.index_of' 0 outer full) (maybe.else fake_index) (n.= 1)) - (|> (/.index_of' outer 1 full) + (|> (/.index_of' 1 outer full) (maybe.else fake_index) (n.= 1)) - (|> (/.index_of' outer 2 full) + (|> (/.index_of' 2 outer full) (maybe.else fake_index) (n.= fake_index))))) (_.cover [/.last_index_of] @@ -124,20 +124,20 @@ (n.= 2))))) (_.cover [/.last_index_of'] (let [full ($_ (\ /.monoid compose) outer inner outer)] - (and (|> (/.last_index_of' inner 0 full) + (and (|> (/.last_index_of' 0 inner full) (maybe.else fake_index) (n.= 1)) - (|> (/.last_index_of' inner 2 full) + (|> (/.last_index_of' 2 inner full) (maybe.else fake_index) (n.= fake_index)) - (|> (/.last_index_of' outer 0 full) + (|> (/.last_index_of' 0 outer full) (maybe.else fake_index) (n.= 2)) - (|> (/.last_index_of' outer 2 full) + (|> (/.last_index_of' 2 outer full) (maybe.else fake_index) (n.= 2)) - (|> (/.last_index_of' outer 3 full) + (|> (/.last_index_of' 3 outer full) (maybe.else fake_index) (n.= fake_index))))) ))) @@ -145,7 +145,7 @@ (def: char Test ($_ _.and - (_.for [/.Char /.of_code] + (_.for [/.Char /.of_char] (`` ($_ _.and (~~ (template [ ] [(_.cover [ ] @@ -171,7 +171,7 @@ (_.cover [/.nth] (case (/.nth expected sample) (#.Some char) - (case (/.index_of (/.of_code char) sample) + (case (/.index_of (/.of_char char) sample) (#.Some actual) (n.= expected actual) diff --git a/stdlib/source/test/lux/data/text/encoding.lux b/stdlib/source/test/lux/data/text/encoding.lux index 11a68ea33..f5670b35f 100644 --- a/stdlib/source/test/lux/data/text/encoding.lux +++ b/stdlib/source/test/lux/data/text/encoding.lux @@ -195,7 +195,7 @@ (def: unique_encodings (list\fold (function (_ encoding set) (set.add (/.name encoding) set)) - (set.new text.hash) + (set.empty text.hash) ..all_encodings)) (def: verdict diff --git a/stdlib/source/test/lux/data/text/escape.lux b/stdlib/source/test/lux/data/text/escape.lux index 73f9455d7..6899c6f62 100644 --- a/stdlib/source/test/lux/data/text/escape.lux +++ b/stdlib/source/test/lux/data/text/escape.lux @@ -100,7 +100,7 @@ [left (random.char unicode.character) right (random.char unicode.character)] (_.cover [/.escape /.un_escape] - (let [expected (format (text.of_code left) (text.of_code right))] + (let [expected (format (text.of_char left) (text.of_char right))] (if (or (/.escapable? left) (/.escapable? right)) (let [escaped (/.escape expected)] @@ -114,7 +114,7 @@ (text\= expected (/.escape expected)))))) (do {! random.monad} [dummy (|> (random.char unicode.character) - (\ ! map text.of_code))] + (\ ! map text.of_char))] (_.cover [/.dangling_escape] (case (/.un_escape (format (/.escape dummy) "\")) (#try.Success _) @@ -125,7 +125,7 @@ (do {! random.monad} [dummy (|> (random.char unicode.character) (random.only (|>> (set.member? ..valid_sigils) not)) - (\ ! map text.of_code))] + (\ ! map text.of_char))] (_.cover [/.invalid_escape] (case (/.un_escape (format "\" dummy)) (#try.Success _) diff --git a/stdlib/source/test/lux/data/text/regex.lux b/stdlib/source/test/lux/data/text/regex.lux index ea81e2c77..95f82e502 100644 --- a/stdlib/source/test/lux/data/text/regex.lux +++ b/stdlib/source/test/lux/data/text/regex.lux @@ -132,9 +132,9 @@ (should_fail (/.regex "\p{Blank}") "."))) (_.test "ASCII." (and (should_pass (/.regex "\p{ASCII}") text.tab) - (should_fail (/.regex "\p{ASCII}") (text.of_code (hex "1234"))))) + (should_fail (/.regex "\p{ASCII}") (text.of_char (hex "1234"))))) (_.test "Control characters." - (and (should_pass (/.regex "\p{Contrl}") (text.of_code (hex "12"))) + (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}") "@") @@ -143,8 +143,8 @@ (and (should_pass (/.regex "\p{Graph}") "@") (should_fail (/.regex "\p{Graph}") " "))) (_.test "Print." - (and (should_pass (/.regex "\p{Print}") (text.of_code (hex "20"))) - (should_fail (/.regex "\p{Print}") (text.of_code (hex "1234"))))) + (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 diff --git a/stdlib/source/test/lux/debug.lux b/stdlib/source/test/lux/debug.lux index 9089e080f..a0900230d 100644 --- a/stdlib/source/test/lux/debug.lux +++ b/stdlib/source/test/lux/debug.lux @@ -87,8 +87,8 @@ false) ## TODO: Uncomment after switching from the old (tag+last?) to the new (lefts+right?) representation for variants ## (~~ (template [ ] - ## [(|> (/.representation (type (| Bit Int Frac)) - ## (: (| Bit Int Frac) + ## [(|> (/.representation (type (Or Bit Int Frac)) + ## (: (Or Bit Int Frac) ## ( ))) ## (try\map (text\= (format "(" (%.nat ) ## " " (%.bit ) diff --git a/stdlib/source/test/lux/ffi.jvm.lux b/stdlib/source/test/lux/ffi.jvm.lux index 96da12763..e2d7e4f4d 100644 --- a/stdlib/source/test/lux/ffi.jvm.lux +++ b/stdlib/source/test/lux/ffi.jvm.lux @@ -12,12 +12,14 @@ ["." exception]] [data ["." bit ("#\." equivalence)] - ["." text ("#\." equivalence)] + ["." text ("#\." equivalence) + ["%" format (#+ format)]] [collection ["." array (#+ Array)]]] ["." macro [syntax (#+ syntax:)] - ["." code]] + ["." code] + ["." template]] [math ["." random (#+ Random)] [number @@ -119,7 +121,7 @@ (i.= (:as Int value)))) (_.cover [/.cannot_convert_to_jvm_type] (let [array (:as (Array Nothing) - (array.new 1))] + (array.empty 1))] (|> array /.array_length ..macro_error @@ -571,6 +573,35 @@ example/9!) ))) +(syntax: (expands? expression) + (function (_ lux) + (|> (macro.single_expansion expression) + (meta.run lux) + (case> (#try.Success expansion) + true + + (#try.Failure error) + false) + code.bit + list + [lux] + #try.Success))) + +(def: for_exception + Test + ($_ _.and + (_.cover [/.class_names_cannot_contain_periods] + (with_expansions [ (template.identifier ["java.lang.Float"])] + (not (expands? (/.import: ))))) + (_.cover [/.class_name_cannot_be_a_type_variable] + (and (not (expands? (/.import: (java/lang/Double a) + ["#::." + (invalid [] (a java/lang/String))]))) + (not (expands? (/.import: java/lang/Double + ["#::." + ([a] invalid [] (a java/lang/String))]))))) + )) + (def: #export test (<| (_.covering /._) ($_ _.and @@ -579,4 +610,5 @@ ..for_miscellaneous ..for_interface ..for_class + ..for_exception ))) diff --git a/stdlib/source/test/lux/locale/language.lux b/stdlib/source/test/lux/locale/language.lux index 3bbae852f..ed2e8401d 100644 --- a/stdlib/source/test/lux/locale/language.lux +++ b/stdlib/source/test/lux/locale/language.lux @@ -190,13 +190,13 @@ (list\fold (function (_ bundle [amount set]) [(n.+ amount (get@ #amount bundle)) (set.union set (lens bundle))]) - [0 (set.new hash)] + [0 (set.empty hash)] territories)) (def: languages_test Test (|> ..languages - list.reverse + list.reversed (list\map (get@ #test)) (list\fold _.and (`` ($_ _.and diff --git a/stdlib/source/test/lux/locale/territory.lux b/stdlib/source/test/lux/locale/territory.lux index 10619ea9f..a949e9bf0 100644 --- a/stdlib/source/test/lux/locale/territory.lux +++ b/stdlib/source/test/lux/locale/territory.lux @@ -145,13 +145,13 @@ (list\fold (function (_ bundle [amount set]) [(n.+ amount (get@ #amount bundle)) (set.union set (lens bundle))]) - [0 (set.new hash)] + [0 (set.empty hash)] territories)) (def: territories_test Test (|> ..territories - list.reverse + list.reversed (list\map (get@ #test)) (list\fold _.and (`` ($_ _.and diff --git a/stdlib/source/test/lux/macro/poly/equivalence.lux b/stdlib/source/test/lux/macro/poly/equivalence.lux index 6682c2375..c14525e7d 100644 --- a/stdlib/source/test/lux/macro/poly/equivalence.lux +++ b/stdlib/source/test/lux/macro/poly/equivalence.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux (#- Variant) ["%" data/text/format (#+ format)] ["_" test (#+ Test)] [abstract diff --git a/stdlib/source/test/lux/macro/poly/json.lux b/stdlib/source/test/lux/macro/poly/json.lux index 4137ad271..d688dab2f 100644 --- a/stdlib/source/test/lux/macro/poly/json.lux +++ b/stdlib/source/test/lux/macro/poly/json.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux (#- Variant) ["_" test (#+ Test)] ["." debug] [abstract diff --git a/stdlib/source/test/lux/math/number/i64.lux b/stdlib/source/test/lux/math/number/i64.lux index d6f531613..4024003c9 100644 --- a/stdlib/source/test/lux/math/number/i64.lux +++ b/stdlib/source/test/lux/math/number/i64.lux @@ -247,14 +247,14 @@ inverse! nullity! futility!))) - (_.cover [/.reverse] - (and (|> pattern /.reverse /.reverse (\= pattern)) - (or (|> pattern /.reverse (\= pattern) not) + (_.cover [/.reversed] + (and (|> pattern /.reversed /.reversed (\= pattern)) + (or (|> pattern /.reversed (\= pattern) not) (let [high (/.and (hex "FFFFFFFF00000000") pattern) low (/.and (hex "00000000FFFFFFFF") pattern)] - (\= (/.reverse high) + (\= (/.reversed high) low))))) ..bit diff --git a/stdlib/source/test/lux/program.lux b/stdlib/source/test/lux/program.lux index 15c7f2215..c7b4cf98c 100644 --- a/stdlib/source/test/lux/program.lux +++ b/stdlib/source/test/lux/program.lux @@ -44,7 +44,7 @@ (let [outcome ((: (-> (List Text) (io.IO Any)) (..actual_program )) inputs)] - (list\= (list.reverse inputs) + (list\= (list.reversed inputs) (:as (List Text) (io.run outcome))))) (with_expansions [ (/.program: [{all_arguments (<>.many .any)}] (io.io all_arguments))] diff --git a/stdlib/source/test/lux/time/duration.lux b/stdlib/source/test/lux/time/duration.lux index 0aba9b880..5f1f3a74b 100644 --- a/stdlib/source/test/lux/time/duration.lux +++ b/stdlib/source/test/lux/time/duration.lux @@ -45,13 +45,13 @@ expected random.duration parameter random.duration] ($_ _.and - (_.cover [/.merge /.difference] - (|> expected (/.merge parameter) (/.difference parameter) (\= expected))) + (_.cover [/.merged /.difference] + (|> expected (/.merged parameter) (/.difference parameter) (\= expected))) (_.cover [/.empty] - (|> expected (/.merge /.empty) (\= expected))) + (|> expected (/.merged /.empty) (\= expected))) (_.cover [/.inverse] (and (|> expected /.inverse /.inverse (\= expected)) - (|> expected (/.merge (/.inverse expected)) (\= /.empty)))) + (|> expected (/.merged (/.inverse expected)) (\= /.empty)))) (_.cover [/.positive? /.negative? /.neutral?] (or (bit\= (/.positive? expected) (/.negative? (/.inverse expected))) @@ -74,8 +74,8 @@ sample positive frame positive] (`` ($_ _.and - (_.cover [/.frame] - (let [sample' (/.frame frame sample)] + (_.cover [/.framed] + (let [sample' (/.framed frame sample)] (and (\< frame sample') (bit\= (\< frame sample) (\= sample sample'))))) 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 e24fac097..d9dab4854 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 @@ -139,7 +139,7 @@ (list\compose (list.repeat (inc lefts) (analysis.pattern/unit)) (list inner))))) (#analysis.Bind @member) - (list.reverse path)) + (list.reversed path)) @member]))) (def: get_test @@ -305,7 +305,7 @@ list.enumeration (list\map (function (_ [lefts' [value body]]) (path lefts' false value body))) - list.reverse)) + list.reversed)) [(branch 0 false value/first body/first) (list\compose (|> (list.zipped/2 value/mid body/mid) list.enumeration 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 4b9b9a9f3..dce97193e 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 @@ -60,7 +60,7 @@ (list (#variable.Local 1))) body))) body - (list.reverse (list.indices arity)))) + (list.reversed (list.indices arity)))) (template: (!expect ) (case 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 e9f9268ac..9c34b539f 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 @@ -320,7 +320,7 @@ (def: default Context {#redundants 0 - #necessary (dictionary.new n.hash)}) + #necessary (dictionary.empty n.hash)}) (def: #export test Test 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 48f1f9817..7a103d60a 100644 --- a/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/test/lux/tool/compiler/language/lux/syntax.lux @@ -78,7 +78,7 @@ ($_ _.and (_.test "Can parse Lux code." (case (let [source_code (%.code sample)] - (/.parse "" (dictionary.new text.hash) (text.size source_code) + (/.parse "" (dictionary.empty text.hash) (text.size source_code) [location.dummy 0 source_code])) (#.Left error) false @@ -90,13 +90,13 @@ (_.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.new text.hash) source_code//size + (case (/.parse "" (dictionary.empty text.hash) source_code//size [location.dummy 0 source_code]) (#.Left error) false (#.Right [remaining =sample]) - (case (/.parse "" (dictionary.new text.hash) source_code//size + (case (/.parse "" (dictionary.empty text.hash) source_code//size remaining) (#.Left error) false @@ -128,7 +128,7 @@ (_.test "Can handle comments." (case (let [source_code (format comment (%.code sample)) source_code//size (text.size source_code)] - (/.parse "" (dictionary.new text.hash) source_code//size + (/.parse "" (dictionary.empty text.hash) source_code//size [location.dummy 0 source_code])) (#.Left error) false diff --git a/stdlib/source/test/lux/type.lux b/stdlib/source/test/lux/type.lux index 24097be23..45d263509 100644 --- a/stdlib/source/test/lux/type.lux +++ b/stdlib/source/test/lux/type.lux @@ -205,8 +205,8 @@ #let [left,right [left right]]] (_.cover [/.:cast] (|> left,right - (/.:cast [l r] (& l r) (| l r)) - (/.:cast [l r] (| l r) (& l r)) + (/.:cast [l r] (And l r) (Or l r)) + (/.:cast [l r] (Or l r) (And l r)) (is? left,right)))) (do random.monad [expected random.nat] diff --git a/stdlib/source/test/lux/type/resource.lux b/stdlib/source/test/lux/type/resource.lux index f761a0f3f..a281a476b 100644 --- a/stdlib/source/test/lux/type/resource.lux +++ b/stdlib/source/test/lux/type/resource.lux @@ -7,14 +7,15 @@ ["." monad [indexed (#+ do)]]] [control - ["." io] + ["." io (#+ IO)] ["." try] ["." exception (#+ Exception)] [concurrency - ["." async]] + ["." async (#+ Async)]] [parser ["<.>" code]]] [data + ["." identity (#+ Identity)] ["." text ("#\." equivalence) ["%" format (#+ format)]]] ["." macro @@ -29,39 +30,41 @@ Test (monad.do {! random.monad} [pre (\ ! map %.nat random.nat) - post (\ ! map %.nat random.nat)] - (_.for [/.Linear /.pure /.run_pure] + post (\ ! map %.nat random.nat) + #let [! identity.monad]] + (_.for [/.Linear /.run] (`` ($_ _.and (~~ (template [ ] [(_.cover (<| (text\= (format pre post)) - /.run_pure - (do /.pure + (: (Identity Text)) + (/.run !) + (do (/.monad !) (in (format left right)))))] - [[/.Affine /.Key /.Res /.Ordered /.ordered_pure - /.Relevant /.read_pure] - [res|left (/.ordered_pure pre) - res|right (/.ordered_pure post) - right (/.read_pure res|right) - left (/.read_pure res|left)]] - [[/.Commutative /.commutative_pure /.exchange_pure] - [res|left (/.commutative_pure pre) - res|right (/.commutative_pure post) - _ (/.exchange_pure [1 0]) - left (/.read_pure res|left) - right (/.read_pure res|right)]] - [[/.group_pure /.un_group_pure] - [res|left (/.commutative_pure pre) - res|right (/.commutative_pure post) - _ (/.group_pure 2) - _ (/.un_group_pure 2) - right (/.read_pure res|right) - left (/.read_pure res|left)]] - [[/.lift_pure] - [left (/.lift_pure pre) - right (/.lift_pure post)]] + [[/.Affine /.Key /.Res /.Ordered /.ordered + /.Relevant /.read] + [res|left (/.ordered ! pre) + res|right (/.ordered ! post) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.Commutative /.commutative /.exchange] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.exchange [1 0]) !) + left (/.read ! res|left) + right (/.read ! res|right)]] + [[/.group /.un_group] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.group 2) !) + _ ((/.un_group 2) !) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.lifted] + [left (/.lifted ! pre) + right (/.lifted ! post)]] )) ))))) @@ -69,40 +72,42 @@ Test (monad.do {! random.monad} [pre (\ ! map %.nat random.nat) - post (\ ! map %.nat random.nat)] - (_.for [/.Linear /.sync /.run_sync] + post (\ ! map %.nat random.nat) + #let [! io.monad]] + (_.for [/.Linear /.run] (`` ($_ _.and (~~ (template [ ] [(_.cover (<| (text\= (format pre post)) io.run - /.run_sync - (do /.sync + (: (IO Text)) + (/.run !) + (do (/.monad !) (in (format left right)))))] - [[/.Affine /.Key /.Res /.Ordered /.ordered_sync - /.Relevant /.read_sync] - [res|left (/.ordered_sync pre) - res|right (/.ordered_sync post) - right (/.read_sync res|right) - left (/.read_sync res|left)]] - [[/.Commutative /.commutative_sync /.exchange_sync] - [res|left (/.commutative_sync pre) - res|right (/.commutative_sync post) - _ (/.exchange_sync [1 0]) - left (/.read_sync res|left) - right (/.read_sync res|right)]] - [[/.group_sync /.un_group_sync] - [res|left (/.commutative_sync pre) - res|right (/.commutative_sync post) - _ (/.group_sync 2) - _ (/.un_group_sync 2) - right (/.read_sync res|right) - left (/.read_sync res|left)]] - [[/.lift_sync] - [left (/.lift_sync (io.io pre)) - right (/.lift_sync (io.io post))]] + [[/.Affine /.Key /.Res /.Ordered /.ordered + /.Relevant /.read] + [res|left (/.ordered ! pre) + res|right (/.ordered ! post) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.Commutative /.commutative /.exchange] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.exchange [1 0]) !) + left (/.read ! res|left) + right (/.read ! res|right)]] + [[/.group /.un_group] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.group 2) !) + _ ((/.un_group 2) !) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.lifted] + [left (/.lifted ! (io.io pre)) + right (/.lifted ! (io.io post))]] )) ))))) @@ -110,41 +115,43 @@ Test (monad.do {! random.monad} [pre (\ ! map %.nat random.nat) - post (\ ! map %.nat random.nat)] - (_.for [/.Linear /.async /.run_async] + post (\ ! map %.nat random.nat) + #let [! async.monad]] + (_.for [/.Linear /.run] (`` ($_ _.and (~~ (template [ ] - [(in (monad.do async.monad - [outcome (/.run_async - (do /.async - - (in (format left right))))] + [(in (monad.do ! + [outcome (<| (: (Async Text)) + (/.run !) + (do (/.monad !) + + (in (format left right))))] (_.cover' (text\= (format pre post) outcome))))] - [[/.Affine /.Key /.Res /.Ordered /.ordered_async - /.Relevant /.read_async] - [res|left (/.ordered_async pre) - res|right (/.ordered_async post) - right (/.read_async res|right) - left (/.read_async res|left)]] - [[/.Commutative /.commutative_async /.exchange_async] - [res|left (/.commutative_async pre) - res|right (/.commutative_async post) - _ (/.exchange_async [1 0]) - left (/.read_async res|left) - right (/.read_async res|right)]] - [[/.group_async /.un_group_async] - [res|left (/.commutative_async pre) - res|right (/.commutative_async post) - _ (/.group_async 2) - _ (/.un_group_async 2) - right (/.read_async res|right) - left (/.read_async res|left)]] - [[/.lift_async] - [left (/.lift_async (async.resolved pre)) - right (/.lift_async (async.resolved post))]] + [[/.Affine /.Key /.Res /.Ordered /.ordered + /.Relevant /.read] + [res|left (/.ordered ! pre) + res|right (/.ordered ! post) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.Commutative /.commutative /.exchange] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.exchange [1 0]) !) + left (/.read ! res|left) + right (/.read ! res|right)]] + [[/.group /.un_group] + [res|left (/.commutative ! pre) + res|right (/.commutative ! post) + _ ((/.group 2) !) + _ ((/.un_group 2) !) + right (/.read ! res|right) + left (/.read ! res|left)]] + [[/.lifted] + [left (/.lifted ! (async.resolved pre)) + right (/.lifted ! (async.resolved post))]] )) ))))) @@ -174,20 +181,10 @@ [(with_error /.amount_cannot_be_zero ( 0))] - [/.group_pure] - [/.group_sync] - [/.group_async] - [/.un_group_pure] - [/.un_group_sync] - [/.un_group_async] + [/.group] + [/.un_group] ))))) (_.cover [/.index_cannot_be_repeated] - (`` (and (~~ (template [] - [(with_error /.index_cannot_be_repeated - ( [0 0]))] - - [/.exchange_pure] - [/.exchange_sync] - [/.exchange_async] - ))))) + (with_error /.index_cannot_be_repeated + (/.exchange [0 0]))) ))) -- cgit v1.2.3