diff options
Diffstat (limited to 'stdlib/source/test/lux/data')
-rw-r--r-- | stdlib/source/test/lux/data/binary.lux | 42 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary.lux | 2 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary/ordered.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/dictionary/plist.lux | 48 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/list.lux | 30 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/set/multi.lux | 44 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/collection/tree/finger.lux | 2 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/format/json.lux | 64 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/data/text/format.lux | 138 |
10 files changed, 189 insertions, 189 deletions
diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux index 25877dfd7..656dbf9bf 100644 --- a/stdlib/source/test/lux/data/binary.lux +++ b/stdlib/source/test/lux/data/binary.lux @@ -42,7 +42,7 @@ (if (n.< size idx) (do random.monad [byte random.nat] - (exec (try.trusted (/.has/1! idx byte output)) + (exec (try.trusted (/.has_8! idx byte output)) (again (++ idx)))) (# random.monad in output))))) @@ -115,10 +115,10 @@ (and (n.= 0 pre) (n.= capped_value post))))] - [0 !.bytes/1 !.has/1!] - [1 !.bytes/2 !.has/2!] - [2 !.bytes/4 !.has/4!] - [3 !.bytes/8 !.has/8!])) + [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) @@ -126,7 +126,7 @@ 0 (list) _ (enum.range n.enum 0 (-- length)))) reader (function (_ binary idx) - (!.bytes/1 idx binary))] + (!.bits_8 idx binary))] (and (n.= length (!.size random_slice)) (# (list.equivalence n.equivalence) = (list#each (|>> (n.+ offset) (reader sample)) idxs) @@ -135,10 +135,10 @@ (and (let [it (!.copy! size 0 sample 0 (!.empty size))] (and (not (same? sample it)) (!.= sample it))) - (let [sample/0 (!.bytes/1 0 sample) + (let [sample/0 (!.bits_8 0 sample) copy (!.copy! 1 0 sample 0 (!.empty 2)) - copy/0 (!.bytes/1 0 copy) - copy/1 (!.bytes/1 1 copy)] + copy/0 (!.bits_8 0 copy) + copy/1 (!.bits_8 1 copy)] (and (n.= sample/0 copy/0) (n.= 0 copy/1))))) ))))) @@ -172,14 +172,14 @@ (|> (/.empty size) /.size (n.= size))) (_.for [/.index_out_of_bounds] ($_ _.and - (_.cover [/.bytes/1 /.has/1!] - (..binary_io 0 /.bytes/1 /.has/1! value)) - (_.cover [/.bytes/2 /.has/2!] - (..binary_io 1 /.bytes/2 /.has/2! value)) - (_.cover [/.bytes/4 /.has/4!] - (..binary_io 2 /.bytes/4 /.has/4! value)) - (_.cover [/.bytes/8 /.has/8!] - (..binary_io 3 /.bytes/8 /.has/8! value)))) + (_.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) @@ -187,7 +187,7 @@ 0 (list) _ (enum.range n.enum 0 (-- length)))) reader (function (_ binary idx) - (/.bytes/1 idx binary))] + (/.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)] @@ -223,10 +223,10 @@ false) (succeed (do try.monad - [sample/0 (/.bytes/1 0 sample) + [sample/0 (/.bits_8 0 sample) copy (/.copy! 1 0 sample 0 (/.empty 2)) - copy/0 (/.bytes/1 0 copy) - copy/1 (/.bytes/1 1 copy)] + 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] diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux index 0a1f9d295..95f2bed9e 100644 --- a/stdlib/source/test/lux/data/collection/dictionary.lux +++ b/stdlib/source/test/lux/data/collection/dictionary.lux @@ -121,7 +121,7 @@ (_.cover [/.merged_with] (list.every? (function (_ [x x*2]) (n.= (n.* 2 x) x*2)) - (list.zipped/2 (/.values dict) + (list.zipped_2 (/.values dict) (/.values (/.merged_with n.+ dict dict))))) (_.cover [/.of_list] diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux index c20a3b480..471565d52 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux @@ -50,7 +50,7 @@ random.nat) extra_value random.nat shift random.nat - .let [pairs (list.zipped/2 (set.list keys) + .let [pairs (list.zipped_2 (set.list keys) (set.list values)) sample (/.of_list n.order pairs) sorted_pairs (list.sorted (function (_ [left _] [right _]) @@ -98,7 +98,7 @@ sorted_pairs)) (_.cover [/.keys /.values] (list#= (/.entries sample) - (list.zipped/2 (/.keys sample) (/.values sample)))) + (list.zipped_2 (/.keys sample) (/.values sample)))) (_.cover [/.of_list] (|> sample /.entries (/.of_list n.order) diff --git a/stdlib/source/test/lux/data/collection/dictionary/plist.lux b/stdlib/source/test/lux/data/collection/dictionary/plist.lux index 346dc5d77..fa4e221cd 100644 --- a/stdlib/source/test/lux/data/collection/dictionary/plist.lux +++ b/stdlib/source/test/lux/data/collection/dictionary/plist.lux @@ -1,26 +1,26 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" monoid]]] - [control - ["[0]" maybe ("[1]#[0]" monad)]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - ["[0]" text] - [collection - ["[0]" set] - ["[0]" list]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" monoid]]] + [control + ["[0]" maybe ("[1]#[0]" monad)]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + ["[0]" text] + [collection + ["[0]" set] + ["[0]" list]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: .public (random size gen_key gen_value) (All (_ v) @@ -28,7 +28,7 @@ (do random.monad [keys (random.set text.hash size gen_key) values (random.list size gen_value)] - (in (list.zipped/2 (set.list keys) values)))) + (in (list.zipped_2 (set.list keys) values)))) (def: .public test Test @@ -63,7 +63,7 @@ (_.cover [/.keys /.values] (# (/.equivalence n.equivalence) = sample - (list.zipped/2 (/.keys sample) + (list.zipped_2 (/.keys sample) (/.values sample)))) (_.cover [/.contains?] (and (list.every? (function (_ key) diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux index c1440d110..5fe98b03c 100644 --- a/stdlib/source/test/lux/data/collection/list.lux +++ b/stdlib/source/test/lux/data/collection/list.lux @@ -148,7 +148,7 @@ expected_numbers! (/.every? (n.= (-- size)) - (/.zipped_with/2 n.+ + (/.zipped_with_2 n.+ indices (/.sorted n.> indices)))] (and expected_amount! @@ -305,8 +305,8 @@ {.#None} (not even_sized?)))) - (_.cover [/.zipped/2] - (let [zipped (/.zipped/2 sample/0 sample/1) + (_.cover [/.zipped_2] + (let [zipped (/.zipped_2 sample/0 sample/1) zipped::size (/.size zipped) size_of_smaller_list! @@ -320,8 +320,8 @@ (/#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) + (_.cover [/.zipped_3] + (let [zipped (/.zipped_3 sample/0 sample/1 sample/2) zipped::size (/.size zipped) size_of_smaller_list! @@ -342,26 +342,26 @@ 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) ((/.zipped 2) sample/0 sample/1)) (# (/.equivalence ($_ product.equivalence n.equivalence n.equivalence n.equivalence)) = - (/.zipped/3 sample/0 sample/1 sample/2) + (/.zipped_3 sample/0 sample/1 sample/2) ((/.zipped 3) sample/0 sample/1 sample/2)))) - (_.cover [/.zipped_with/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] + (/.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))) + (/.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) + (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) ((/.zipped_with 3) +/3 sample/0 sample/1 sample/2)))) (_.cover [/.together] (and (/#= (/#composite sample/0 sample/1) diff --git a/stdlib/source/test/lux/data/collection/set/multi.lux b/stdlib/source/test/lux/data/collection/set/multi.lux index 73dba4b3e..755efb685 100644 --- a/stdlib/source/test/lux/data/collection/set/multi.lux +++ b/stdlib/source/test/lux/data/collection/set/multi.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [hash {"+" Hash}] - [monad {"+" do}] - ["[0]" predicate] - [\\specification - ["$[0]" equivalence] - ["$[0]" hash]]] - [data - ["[0]" bit ("[1]#[0]" equivalence)] - [collection - ["[0]" set] - ["[0]" list ("[1]#[0]" mix)]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat]]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [hash {"+" Hash}] + [monad {"+" do}] + ["[0]" predicate] + [\\specification + ["$[0]" equivalence] + ["$[0]" hash]]] + [data + ["[0]" bit ("[1]#[0]" equivalence)] + [collection + ["[0]" set] + ["[0]" list ("[1]#[0]" mix)]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat]]]]] + [\\library + ["[0]" /]]) (def: count (Random Nat) @@ -33,7 +33,7 @@ (in (list#mix (function (_ [count element] set) (/.has count element set)) (/.empty hash) - (list.zipped/2 element_counts + (list.zipped_2 element_counts (set.list elements)))))) (def: signature diff --git a/stdlib/source/test/lux/data/collection/tree/finger.lux b/stdlib/source/test/lux/data/collection/tree/finger.lux index 06c77591e..85c5ec037 100644 --- a/stdlib/source/test/lux/data/collection/tree/finger.lux +++ b/stdlib/source/test/lux/data/collection/tree/finger.lux @@ -89,7 +89,7 @@ (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))] + (list.zipped_2 tags/T values/T))] (and (# tags_equivalence = (list& tags/H tags/T) (/.tags tree)) (# values_equivalence = (list& values/H values/T) (/.values tree)))))) (_.cover [/.one] diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux index 08e87df0f..3d10458af 100644 --- a/stdlib/source/test/lux/data/format/json.lux +++ b/stdlib/source/test/lux/data/format/json.lux @@ -1,35 +1,35 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - ["[0]" meta] - [abstract - [monad {"+" do}] - [\\specification - ["$[0]" equivalence] - ["$[0]" codec]]] - [control - ["[0]" try ("[1]#[0]" functor)]] - [data - ["[0]" product] - ["[0]" bit] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" sequence] - ["[0]" dictionary] - ["[0]" set] - ["[0]" list ("[1]#[0]" functor)]]] - [math - ["[0]" random {"+" Random}] - [number - ["n" nat] - ["[0]" frac]]] - ["[0]" macro - ["[0]" syntax {"+" syntax:}] - ["[0]" code]]]] - [\\library - ["[0]" / {"+" JSON} ("#[0]" equivalence)]]) + [library + [lux "*" + ["_" test {"+" Test}] + ["[0]" meta] + [abstract + [monad {"+" do}] + [\\specification + ["$[0]" equivalence] + ["$[0]" codec]]] + [control + ["[0]" try ("[1]#[0]" functor)]] + [data + ["[0]" product] + ["[0]" bit] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" sequence] + ["[0]" dictionary] + ["[0]" set] + ["[0]" list ("[1]#[0]" functor)]]] + [math + ["[0]" random {"+" Random}] + [number + ["n" nat] + ["[0]" frac]]] + ["[0]" macro + ["[0]" syntax {"+" syntax:}] + ["[0]" code]]]] + [\\library + ["[0]" / {"+" JSON} ("#[0]" equivalence)]]) (def: .public random (Random /.JSON) @@ -90,7 +90,7 @@ (do random.monad [keys (random.set text.hash 3 (random.ascii/alpha 1)) values (random.set frac.hash 3 random.safe_frac) - .let [expected (list.zipped/2 (set.list keys) + .let [expected (list.zipped_2 (set.list keys) (list#each (|>> {/.#Number}) (set.list values))) object (/.object expected)]] ($_ _.and diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux index 8503e08ac..8825bc192 100644 --- a/stdlib/source/test/lux/data/text.lux +++ b/stdlib/source/test/lux/data/text.lux @@ -204,10 +204,10 @@ (# /.equivalence = (/.together (set.list characters)) (/.interposed "" (set.list characters))))) - (_.cover [/.replaced/1] + (_.cover [/.replaced_once] (# /.equivalence = (# /.monoid composite post static) - (/.replaced/1 pre post (# /.monoid composite pre static)))) + (/.replaced_once pre post (# /.monoid composite pre static)))) (_.cover [/.split_by] (case (/.split_by static ($_ (# /.monoid composite) pre static post)) {.#Some [left right]} diff --git a/stdlib/source/test/lux/data/text/format.lux b/stdlib/source/test/lux/data/text/format.lux index b8ebe1d7f..62dfcd17d 100644 --- a/stdlib/source/test/lux/data/text/format.lux +++ b/stdlib/source/test/lux/data/text/format.lux @@ -1,57 +1,57 @@ (.using - [library - [lux "*" - ["_" test {"+" Test}] - [abstract - [monad {"+" do}] - [equivalence {"+" Equivalence}] - [functor - [\\specification - ["$[0]" contravariant]]]] - [control - ["[0]" try]] - [data - ["[0]" text ("[1]#[0]" equivalence)] - ["[0]" bit] - [format - ["[0]" xml] - ["[0]" json]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - ["[0]" time - ["[0]" day] - ["[0]" month] - ["[0]" instant] - ["[0]" duration] - ["[0]" date]] - [math - ["[0]" random {"+" Random} ("[1]#[0]" monad)] - ["[0]" modulus] - ["[0]" modular] - [number - ["[0]" nat] - ["[0]" int] - ["[0]" rev] - ["[0]" frac] - ["[0]" ratio]]] - [macro - ["[0]" code]] - [meta - ["[0]" location] - ["[0]" symbol]] - ["[0]" type]]] - ["$[0]" /// "_" - [format - ["[1][0]" xml] - ["[1][0]" json]] - [// - ["[1][0]" type] - [macro - ["[1][0]" code]] - [meta - ["[1][0]" symbol]]]] - [\\library - ["[0]" /]]) + [library + [lux "*" + ["_" test {"+" Test}] + [abstract + [monad {"+" do}] + [equivalence {"+" Equivalence}] + [functor + [\\specification + ["$[0]" contravariant]]]] + [control + ["[0]" try]] + [data + ["[0]" text ("[1]#[0]" equivalence)] + ["[0]" bit] + [format + ["[0]" xml] + ["[0]" json]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + ["[0]" time + ["[0]" day] + ["[0]" month] + ["[0]" instant] + ["[0]" duration] + ["[0]" date]] + [math + ["[0]" random {"+" Random} ("[1]#[0]" monad)] + ["[0]" modulus] + ["[0]" modular] + [number + ["[0]" nat] + ["[0]" int] + ["[0]" rev] + ["[0]" frac] + ["[0]" ratio]]] + [macro + ["[0]" code]] + [meta + ["[0]" location] + ["[0]" symbol]] + ["[0]" type]]] + ["$[0]" /// "_" + [format + ["[1][0]" xml] + ["[1][0]" json]] + [// + ["[1][0]" type] + [macro + ["[1][0]" code]] + [meta + ["[1][0]" symbol]]]] + [\\library + ["[0]" /]]) (implementation: (equivalence example) (All (_ a) (-> a (Equivalence (/.Format a)))) @@ -96,25 +96,25 @@ [/.date date.codec random.date] [/.time time.codec random.time] - [/.nat/2 nat.binary random.nat] - [/.nat/8 nat.octal random.nat] - [/.nat/10 nat.decimal random.nat] - [/.nat/16 nat.hex random.nat] + [/.nat_2 nat.binary random.nat] + [/.nat_8 nat.octal random.nat] + [/.nat_10 nat.decimal random.nat] + [/.nat_16 nat.hex random.nat] - [/.int/2 int.binary random.int] - [/.int/8 int.octal random.int] - [/.int/10 int.decimal random.int] - [/.int/16 int.hex random.int] + [/.int_2 int.binary random.int] + [/.int_8 int.octal random.int] + [/.int_10 int.decimal random.int] + [/.int_16 int.hex random.int] - [/.rev/2 rev.binary random.rev] - [/.rev/8 rev.octal random.rev] - [/.rev/10 rev.decimal random.rev] - [/.rev/16 rev.hex random.rev] + [/.rev_2 rev.binary random.rev] + [/.rev_8 rev.octal random.rev] + [/.rev_10 rev.decimal random.rev] + [/.rev_16 rev.hex random.rev] - [/.frac/2 frac.binary random.frac] - [/.frac/8 frac.octal random.frac] - [/.frac/10 frac.decimal random.frac] - [/.frac/16 frac.hex random.frac] + [/.frac_2 frac.binary random.frac] + [/.frac_8 frac.octal random.frac] + [/.frac_10 frac.decimal random.frac] + [/.frac_16 frac.hex random.frac] )) ))) |