aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux/data')
-rw-r--r--stdlib/source/test/lux/data/binary.lux2
-rw-r--r--stdlib/source/test/lux/data/collection/array.lux22
-rw-r--r--stdlib/source/test/lux/data/collection/bits.lux40
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary.lux24
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary/ordered.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary/plist.lux6
-rw-r--r--stdlib/source/test/lux/data/collection/list.lux16
-rw-r--r--stdlib/source/test/lux/data/collection/row.lux2
-rw-r--r--stdlib/source/test/lux/data/collection/sequence.lux16
-rw-r--r--stdlib/source/test/lux/data/collection/set.lux2
-rw-r--r--stdlib/source/test/lux/data/collection/stack.lux4
-rw-r--r--stdlib/source/test/lux/data/format/json.lux42
-rw-r--r--stdlib/source/test/lux/data/name.lux4
-rw-r--r--stdlib/source/test/lux/data/text.lux8
-rw-r--r--stdlib/source/test/lux/data/text/format.lux2
15 files changed, 99 insertions, 99 deletions
diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux
index 3270e17a7..d45cc6554 100644
--- a/stdlib/source/test/lux/data/binary.lux
+++ b/stdlib/source/test/lux/data/binary.lux
@@ -147,7 +147,7 @@
(_.cover [/.copy]
(and (case (/.copy size 0 sample 0 (/.empty size))
(#try.Success output)
- (and (not (is? sample output))
+ (and (not (same? sample output))
(\ /.equivalence = sample output))
(#try.Failure _)
diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux
index 64e0f4268..c7433632e 100644
--- a/stdlib/source/test/lux/data/collection/array.lux
+++ b/stdlib/source/test/lux/data/collection/array.lux
@@ -56,15 +56,15 @@
.let [expected (n.+ base shift)]
the_array (random.array size random.nat)]
($_ _.and
- (_.cover [/.find]
+ (_.cover [/.example]
(\ (maybe.equivalence n.equivalence) =
- (/.find n.even? the_array)
- (list.find n.even? (/.list the_array))))
- (_.cover [/.find+]
- (case [(/.find n.even? the_array)
- (/.find+ (function (_ idx member)
- (n.even? member))
- the_array)]
+ (/.example n.even? the_array)
+ (list.example n.even? (/.list 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 (/.read idx the_array)
(#.Some again)
@@ -110,7 +110,7 @@
(_.cover [/.type_name]
(case /.Array
(^ (#.Named _ (#.UnivQ _ (#.Primitive nominal_type (list (#.Parameter 1))))))
- (is? /.type_name nominal_type)
+ (same? /.type_name nominal_type)
_
false))
@@ -199,7 +199,7 @@
(/.list copy))))))
(_.cover [/.clone]
(let [clone (/.clone the_array)]
- (and (not (is? the_array clone))
+ (and (not (same? the_array clone))
(\ (/.equivalence n.equivalence) = the_array clone))))
(let [the_array (/.clone the_array)
evens (|> the_array /.list (list.only n.even?))
@@ -220,6 +220,6 @@
(exec (/.filter! n.even? the_array)
(list.every? (function (_ value)
(or (n.even? value)
- (is? default value)))
+ (same? default value)))
(/.list' default the_array)))))
))))
diff --git a/stdlib/source/test/lux/data/collection/bits.lux b/stdlib/source/test/lux/data/collection/bits.lux
index da4a759e5..6710ef7c6 100644
--- a/stdlib/source/test/lux/data/collection/bits.lux
+++ b/stdlib/source/test/lux/data/collection/bits.lux
@@ -27,7 +27,7 @@
0 (in /.empty)
_ (do {! random.monad}
[idx (|> random.nat (\ ! map (n.% size)))]
- (in (/.set idx /.empty))))))
+ (in (/.one idx /.empty))))))
(def: .public test
Test
@@ -51,38 +51,38 @@
idx (\ ! map (n.% size) random.nat)
sample ..random]
($_ _.and
- (_.cover [/.get /.set]
- (and (|> /.empty (/.get idx) not)
- (|> /.empty (/.set idx) (/.get idx))))
- (_.cover [/.clear]
- (|> /.empty (/.set idx) (/.clear idx) (/.get idx) not))
- (_.cover [/.flip]
- (and (|> /.empty (/.flip idx) (/.get idx))
- (|> /.empty (/.flip idx) (/.flip idx) (/.get idx) not)))
+ (_.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 (/.set idx) /.capacity
+ (|> /.empty (/.one idx) /.capacity
(n.- idx)
(predicate.or (n.>= 0)
(n.< /.chunk_size)))
- (let [grown (/.flip idx /.empty)]
+ (let [grown (/.flipped idx /.empty)]
(and (n.> 0 (/.capacity grown))
- (is? /.empty (/.flip idx grown))))))
+ (same? /.empty (/.flipped idx grown))))))
(_.cover [/.intersects?]
(and (not (/.intersects? /.empty
/.empty))
- (/.intersects? (/.set idx /.empty)
- (/.set idx /.empty))
- (not (/.intersects? (/.set (inc idx) /.empty)
- (/.set idx /.empty)))
+ (/.intersects? (/.one idx /.empty)
+ (/.one idx /.empty))
+ (not (/.intersects? (/.one (inc idx) /.empty)
+ (/.one idx /.empty)))
(not (/.intersects? sample (/.not sample)))))
(_.cover [/.not]
- (and (is? /.empty (/.not /.empty))
- (or (is? /.empty sample)
+ (and (same? /.empty (/.not /.empty))
+ (or (same? /.empty sample)
(and (not (\ /.equivalence = sample (/.not sample)))
(\ /.equivalence = sample (/.not (/.not sample)))))))
(_.cover [/.xor]
- (and (is? /.empty (/.xor sample sample))
+ (and (same? /.empty (/.xor sample sample))
(n.= (/.size (/.xor sample (/.not sample)))
(/.capacity sample))))
(_.cover [/.or]
@@ -91,5 +91,5 @@
(/.capacity sample))))
(_.cover [/.and]
(and (\ /.equivalence = sample (/.and sample sample))
- (is? /.empty (/.and sample (/.not 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 8667b7054..7114a2eed 100644
--- a/stdlib/source/test/lux/data/collection/dictionary.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary.lux
@@ -60,7 +60,7 @@
(def: (hash _)
constant)))]]
(_.cover [/.key_hash]
- (is? hash (/.key_hash (/.empty hash)))))
+ (same? hash (/.key_hash (/.empty hash)))))
(_.cover [/.entries]
(let [entries (/.entries dict)
@@ -79,7 +79,7 @@
correct_pairing!
(list.every? (function (_ [key value])
(|> dict
- (/.get key)
+ (/.value key)
(maybe\map (n.= value))
(maybe.else false)))
entries)]
@@ -145,19 +145,19 @@
(list.every? (/.key? dict)
(/.keys dict)))
- (_.cover [/.get]
- (and (list.every? (function (_ key) (case (/.get key dict)
+ (_.cover [/.value]
+ (and (list.every? (function (_ key) (case (/.value key dict)
(#.Some _) true
_ false))
(/.keys dict))
- (case (/.get non_key dict)
+ (case (/.value non_key dict)
(#.Some _) false
_ true)))
(_.cover [/.has]
(and (n.= (inc (/.size dict))
(/.size (/.has non_key test_val dict)))
- (case (/.get non_key (/.has non_key test_val dict))
+ (case (/.value non_key (/.has non_key test_val dict))
(#.Some v) (n.= test_val v)
_ true)))
@@ -165,7 +165,7 @@
(let [can_put_new_keys!
(case (/.try_put non_key test_val dict)
(#try.Success dict)
- (case (/.get non_key dict)
+ (case (/.value non_key dict)
(#.Some v) (n.= test_val v)
_ true)
@@ -199,7 +199,7 @@
(_.cover [/.revised]
(let [base (/.has non_key test_val dict)
updt (/.revised non_key inc base)]
- (case [(/.get non_key base) (/.get non_key updt)]
+ (case [(/.value non_key base) (/.value non_key updt)]
[(#.Some x) (#.Some y)]
(n.= (inc x) y)
@@ -208,7 +208,7 @@
(_.cover [/.upsert]
(let [can_upsert_new_key!
- (case (/.get non_key (/.upsert non_key test_val inc dict))
+ (case (/.value non_key (/.upsert non_key test_val inc dict))
(#.Some inserted)
(n.= (inc test_val) inserted)
@@ -221,7 +221,7 @@
true
(#.Some [known_key known_value])
- (case (/.get known_key (/.upsert known_key test_val inc dict))
+ (case (/.value known_key (/.upsert known_key test_val inc dict))
(#.Some updated)
(n.= (inc known_value) updated)
@@ -244,8 +244,8 @@
(and (n.= (/.size dict) (/.size rebound))
(/.key? rebound non_key)
(not (/.key? rebound first_key))
- (n.= (maybe.assume (/.get first_key dict))
- (maybe.assume (/.get non_key rebound)))))))
+ (n.= (maybe.assume (/.value first_key dict))
+ (maybe.assume (/.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 b2bed04f9..838d2cf5d 100644
--- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
@@ -113,10 +113,10 @@
(and (/.key? sample+ extra_key)
(n.= (inc (/.size sample))
(/.size sample+))))))
- (_.cover [/.get]
+ (_.cover [/.value]
(let [sample+ (/.has extra_key extra_value sample)]
- (case [(/.get extra_key sample)
- (/.get extra_key sample+)]
+ (case [(/.value extra_key sample)
+ (/.value extra_key sample+)]
[#.None (#.Some actual)]
(n.= extra_value actual)
@@ -131,7 +131,7 @@
(|> sample
(/.has extra_key extra_value)
(/.revised extra_key (n.+ shift))
- (/.get extra_key)
+ (/.value extra_key)
(maybe\map (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 b36d5d9d2..c76892185 100644
--- a/stdlib/source/test/lux/data/collection/dictionary/plist.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary/plist.lux
@@ -71,17 +71,17 @@
(/.contains? extra_key sample+)
(n.= (inc (/.size sample))
(/.size sample+)))))
- (_.cover [/.get]
+ (_.cover [/.value]
(|> sample
(/.has extra_key extra_value)
- (/.get extra_key)
+ (/.value extra_key)
(maybe\map (n.= extra_value))
(maybe.else false)))
(_.cover [/.revised]
(|> sample
(/.has extra_key extra_value)
(/.revised extra_key (n.+ shift))
- (/.get extra_key)
+ (/.value extra_key)
(maybe\map (n.= (n.+ shift extra_value)))
(maybe.else false)))
(_.cover [/.lacks]
diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux
index e9be412e2..7fb1e8704 100644
--- a/stdlib/source/test/lux/data/collection/list.lux
+++ b/stdlib/source/test/lux/data/collection/list.lux
@@ -122,7 +122,7 @@
symmetry!
(/\= (/.sorted <<< sample)
- (/.reversed (/.sorted (function.flip <<<) sample)))]
+ (/.reversed (/.sorted (function.flipped <<<) sample)))]
(and size_preservation!
symmetry!)))
)))
@@ -206,18 +206,18 @@
(let [[left right] (/.split idx sample)]
(/\= sample
(/\compose left right))))
- (_.cover [/.split_with]
- (let [[left right] (/.split_with n.even? sample)]
+ (_.cover [/.split_when]
+ (let [[left right] (/.split_when n.even? sample)]
(/\= sample
(/\compose left right))))
(_.cover [/.take /.drop]
(/\= sample
(/\compose (/.take idx sample)
(/.drop idx sample))))
- (_.cover [/.take_while /.drop_while]
+ (_.cover [/.while /.until]
(/\= sample
- (/\compose (/.take_while n.even? sample)
- (/.drop_while n.even? sample))))
+ (/\compose (/.while n.even? sample)
+ (/.until n.even? sample))))
(_.cover [/.sub]
(let [subs (/.sub sub_size sample)]
(and (/.every? (|>> /.size (n.<= sub_size)) subs)
@@ -380,8 +380,8 @@
(/.only n.even?)
(/\map (\ n.decimal encode)))
(/.all choose sample)))
- (_.cover [/.find]
- (case (/.find n.even? sample)
+ (_.cover [/.example]
+ (case (/.example n.even? sample)
(#.Some found)
(n.even? found)
diff --git a/stdlib/source/test/lux/data/collection/row.lux b/stdlib/source/test/lux/data/collection/row.lux
index a6e4679fb..3ae89efba 100644
--- a/stdlib/source/test/lux/data/collection/row.lux
+++ b/stdlib/source/test/lux/data/collection/row.lux
@@ -103,7 +103,7 @@
(do try.monad
[sample (/.put good_index non_member sample)
actual (/.item good_index sample)]
- (in (is? non_member actual)))))
+ (in (same? non_member actual)))))
(_.cover [/.revised]
(<| (try.else false)
(do try.monad
diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux
index 61c301f94..9a2c78afb 100644
--- a/stdlib/source/test/lux/data/collection/sequence.lux
+++ b/stdlib/source/test/lux/data/collection/sequence.lux
@@ -65,19 +65,19 @@
drops)
(list\= (enum.range n.enum size (dec (n.* 2 size)))
(/.take size takes)))))
- (_.cover [/.take_while]
+ (_.cover [/.while]
(list\= (enum.range n.enum 0 (dec size))
- (/.take_while (n.< size) (/.iterations inc 0))))
- (_.cover [/.drop_while]
+ (/.while (n.< size) (/.iterations inc 0))))
+ (_.cover [/.until]
(list\= (enum.range n.enum offset (dec (n.+ size offset)))
- (/.take_while (n.< (n.+ size offset))
- (/.drop_while (n.< offset) (/.iterations inc 0)))))
- (_.cover [/.split_while]
- (let [[drops takes] (/.split_while (n.< size) (/.iterations inc 0))]
+ (/.while (n.< (n.+ size offset))
+ (/.until (n.< offset) (/.iterations inc 0)))))
+ (_.cover [/.split_when]
+ (let [[drops takes] (/.split_when (n.= size) (/.iterations inc 0))]
(and (list\= (enum.range n.enum 0 (dec size))
drops)
(list\= (enum.range n.enum size (dec (n.* 2 size)))
- (/.take_while (n.< (n.* 2 size)) takes)))))
+ (/.while (n.< (n.* 2 size)) takes)))))
(_.cover [/.head]
(n.= offset
(/.head (/.iterations inc offset))))
diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux
index bd76d5bf3..e6dbd5c3d 100644
--- a/stdlib/source/test/lux/data/collection/set.lux
+++ b/stdlib/source/test/lux/data/collection/set.lux
@@ -61,7 +61,7 @@
constant))))
random.nat)]
(_.cover [/.member_hash]
- (is? hash (/.member_hash (/.empty hash)))))
+ (same? hash (/.member_hash (/.empty hash)))))
(_.cover [/.size]
(n.= sizeL (/.size setL)))
(_.cover [/.empty?]
diff --git a/stdlib/source/test/lux/data/collection/stack.lux b/stdlib/source/test/lux/data/collection/stack.lux
index 1cb75755f..591308f56 100644
--- a/stdlib/source/test/lux/data/collection/stack.lux
+++ b/stdlib/source/test/lux/data/collection/stack.lux
@@ -62,8 +62,8 @@
(_.cover [/.push]
(case (/.pop (/.push expected_top sample))
(#.Some [actual_top actual_sample])
- (and (is? expected_top actual_top)
- (is? sample actual_sample))
+ (and (same? expected_top actual_top)
+ (same? sample actual_sample))
#.None
false))
diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux
index 51bc3ac0e..33b2622f4 100644
--- a/stdlib/source/test/lux/data/format/json.lux
+++ b/stdlib/source/test/lux/data/format/json.lux
@@ -103,9 +103,9 @@
(#try.Failure error)
false))
- (_.cover [/.get]
+ (_.cover [/.field]
(list.every? (function (_ [key expected])
- (|> (/.get key object)
+ (|> (/.field key object)
(try\map (\= expected))
(try.else false)))
expected))
@@ -115,18 +115,18 @@
unknown (random.only (|>> (\ text.equivalence = key) not)
(random.ascii/alpha 1))
expected random.safe_frac]
- (_.cover [/.set]
+ (_.cover [/.has]
(<| (try.else false)
(do try.monad
- [object (/.set key (#/.Number expected) (/.object (list)))
+ [object (/.has key (#/.Number expected) (/.object (list)))
.let [can_find_known_key!
(|> object
- (/.get key)
+ (/.field key)
(try\map (\= (#/.Number expected)))
(try.else false))
cannot_find_unknown_key!
- (case (/.get unknown object)
+ (case (/.field unknown object)
(#try.Success _)
false
@@ -134,21 +134,21 @@
true)]]
(in (and can_find_known_key!
cannot_find_unknown_key!))))))
- (~~ (template [<type> <get> <tag> <random> <equivalence>]
+ (~~ (template [<type> <field> <tag> <random> <equivalence>]
[(do random.monad
[key (random.ascii/alpha 1)
value <random>]
- (_.cover [<type> <get>]
+ (_.cover [<type> <field>]
(|> (/.object (list [key (<tag> value)]))
- (<get> key)
+ (<field> key)
(try\map (\ <equivalence> = value))
(try.else false))))]
- [/.Boolean /.get_boolean #/.Boolean random.bit bit.equivalence]
- [/.Number /.get_number #/.Number random.safe_frac frac.equivalence]
- [/.String /.get_string #/.String (random.ascii/alpha 1) text.equivalence]
- [/.Array /.get_array #/.Array (random.row 3 ..random) (row.equivalence /.equivalence)]
- [/.Object /.get_object #/.Object (random.dictionary text.hash 3 (random.ascii/alpha 1) ..random) (dictionary.equivalence /.equivalence)]
+ [/.Boolean /.boolean_field #/.Boolean random.bit bit.equivalence]
+ [/.Number /.number_field #/.Number random.safe_frac frac.equivalence]
+ [/.String /.string_field #/.String (random.ascii/alpha 1) text.equivalence]
+ [/.Array /.array_field #/.Array (random.row 3 ..random) (row.equivalence /.equivalence)]
+ [/.Object /.object_field #/.Object (random.dictionary text.hash 3 (random.ascii/alpha 1) ..random) (dictionary.equivalence /.equivalence)]
))
(with_expansions [<boolean> (boolean)
<number> (number)
@@ -182,13 +182,13 @@
<key5> {<key6> <number>}})]
(<| (try.else false)
(do try.monad
- [value0 (/.get <key0> object)
- value1 (/.get <key1> object)
- value2 (/.get <key2> object)
- value3 (/.get <key3> object)
- value4 (/.get <key4> object)
- value5 (/.get <key5> object)
- value6 (/.get <key6> value5)]
+ [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)
diff --git a/stdlib/source/test/lux/data/name.lux b/stdlib/source/test/lux/data/name.lux
index 2cde215a0..2856d3476 100644
--- a/stdlib/source/test/lux/data/name.lux
+++ b/stdlib/source/test/lux/data/name.lux
@@ -56,8 +56,8 @@
#1)))))
(_.cover [/.module /.short]
- (and (is? module1 (/.module name1))
- (is? short1 (/.short name1))))
+ (and (same? module1 (/.module name1))
+ (same? short1 (/.short name1))))
(_.for [.name_of]
(let [(^open "/\.") /.equivalence]
($_ _.and
diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux
index f2bcccfc6..f95757333 100644
--- a/stdlib/source/test/lux/data/text.lux
+++ b/stdlib/source/test/lux/data/text.lux
@@ -195,10 +195,10 @@
(_.cover [/.joined]
(n.= (set.size characters)
(/.size (/.joined (set.list characters)))))
- (_.cover [/.join_with /.split_all_with]
+ (_.cover [/.join_with /.all_split_by]
(and (|> (set.list characters)
(/.join_with separator)
- (/.split_all_with separator)
+ (/.all_split_by separator)
(set.of_list /.hash)
(\ set.equivalence = characters))
(\ /.equivalence =
@@ -208,8 +208,8 @@
(\ /.equivalence =
(\ /.monoid compose post static)
(/.replaced/1 pre post (\ /.monoid compose pre static))))
- (_.cover [/.split_with]
- (case (/.split_with static ($_ (\ /.monoid compose) pre static post))
+ (_.cover [/.split_by]
+ (case (/.split_by static ($_ (\ /.monoid compose) pre static post))
(#.Some [left right])
(and (\ /.equivalence = pre left)
(\ /.equivalence = post right))
diff --git a/stdlib/source/test/lux/data/text/format.lux b/stdlib/source/test/lux/data/text/format.lux
index e612dc9b6..f2887f530 100644
--- a/stdlib/source/test/lux/data/text/format.lux
+++ b/stdlib/source/test/lux/data/text/format.lux
@@ -147,7 +147,7 @@
[/.text text.format (random.unicode 5)]
[/.code code.format $///code.random]
- [/.type type.format $///type.random]
+ [/.type type.format ($///type.random 0)]
[/.location location.format
($_ random.and
(random.unicode 5)