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.lux82
-rw-r--r--stdlib/source/test/lux/data/bit.lux12
-rw-r--r--stdlib/source/test/lux/data/collection/array.lux46
-rw-r--r--stdlib/source/test/lux/data/collection/bits.lux18
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary.lux6
-rw-r--r--stdlib/source/test/lux/data/collection/dictionary/ordered.lux2
-rw-r--r--stdlib/source/test/lux/data/collection/list.lux30
-rw-r--r--stdlib/source/test/lux/data/collection/list/property.lux6
-rw-r--r--stdlib/source/test/lux/data/collection/queue.lux13
-rw-r--r--stdlib/source/test/lux/data/collection/queue/priority.lux2
-rw-r--r--stdlib/source/test/lux/data/collection/sequence.lux14
-rw-r--r--stdlib/source/test/lux/data/collection/set.lux6
-rw-r--r--stdlib/source/test/lux/data/collection/set/multi.lux24
-rw-r--r--stdlib/source/test/lux/data/collection/set/ordered.lux22
-rw-r--r--stdlib/source/test/lux/data/collection/stack.lux4
-rw-r--r--stdlib/source/test/lux/data/collection/stream.lux8
-rw-r--r--stdlib/source/test/lux/data/collection/tree.lux16
-rw-r--r--stdlib/source/test/lux/data/collection/tree/finger.lux64
-rw-r--r--stdlib/source/test/lux/data/collection/tree/zipper.lux2
-rw-r--r--stdlib/source/test/lux/data/color.lux120
-rw-r--r--stdlib/source/test/lux/data/color/cmyk.lux54
-rw-r--r--stdlib/source/test/lux/data/color/hsb.lux6
-rw-r--r--stdlib/source/test/lux/data/color/hsl.lux6
-rw-r--r--stdlib/source/test/lux/data/color/named.lux6
-rw-r--r--stdlib/source/test/lux/data/color/pigment.lux34
-rw-r--r--stdlib/source/test/lux/data/color/rgb.lux4
-rw-r--r--stdlib/source/test/lux/data/color/terminal.lux4
-rw-r--r--stdlib/source/test/lux/data/format/json.lux60
-rw-r--r--stdlib/source/test/lux/data/format/tar.lux16
-rw-r--r--stdlib/source/test/lux/data/format/xml.lux6
-rw-r--r--stdlib/source/test/lux/data/product.lux6
-rw-r--r--stdlib/source/test/lux/data/sum.lux14
-rw-r--r--stdlib/source/test/lux/data/text.lux126
-rw-r--r--stdlib/source/test/lux/data/text/buffer.lux2
-rw-r--r--stdlib/source/test/lux/data/text/encoding.lux2
-rw-r--r--stdlib/source/test/lux/data/text/escape.lux12
-rw-r--r--stdlib/source/test/lux/data/text/unicode/block.lux10
-rw-r--r--stdlib/source/test/lux/data/text/unicode/set.lux2
38 files changed, 448 insertions, 419 deletions
diff --git a/stdlib/source/test/lux/data/binary.lux b/stdlib/source/test/lux/data/binary.lux
index 05c3c2c6a..44af3a44e 100644
--- a/stdlib/source/test/lux/data/binary.lux
+++ b/stdlib/source/test/lux/data/binary.lux
@@ -66,8 +66,8 @@
(def (utf8_conversion_does_not_alter? value)
(Predicate Text)
(|> value
- (at utf8.codec encoded)
- (at utf8.codec decoded)
+ (of utf8.codec encoded)
+ (of utf8.codec decoded)
(pipe.when
{try.#Success converted}
(text#= value converted)
@@ -105,7 +105,7 @@
(random.rec
(function (_ again)
(let [random_sequence (do [! random.monad]
- [size (at ! each (n.% 2) random.nat)]
+ [size (of ! each (n.% 2) random.nat)]
(random.list size again))]
(all random.and
..random_location
@@ -138,7 +138,7 @@
(`` (all _.and
(,, (with_template [<size> <parser> <format>]
[(do [! random.monad]
- [expected (at ! each (i64.and (i64.mask <size>))
+ [expected (of ! each (i64.and (i64.mask <size>))
random.nat)]
(_.coverage [<size> <parser> <format>]
(|> (\\format.result <format> expected)
@@ -158,12 +158,12 @@
(`` (all _.and
(,, (with_template [<parser> <format>]
[(do [! random.monad]
- [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [<parser> <format>]
(|> (\\format.result <format> expected)
(\\parser.result <parser>)
(!expect (^.multi {try.#Success actual}
- (at /.equivalence = expected actual))))))]
+ (of /.equivalence = expected actual))))))]
[\\parser.binary_8 \\format.binary_8]
[\\parser.binary_16 \\format.binary_16]
@@ -181,7 +181,7 @@
(|> (\\format.result <format> expected)
(\\parser.result <parser>)
(!expect (^.multi {try.#Success actual}
- (at text.equivalence = expected actual))))))]
+ (of text.equivalence = expected actual))))))]
[\\parser.utf8_8 \\format.utf8_8]
[\\parser.utf8_16 \\format.utf8_16]
@@ -201,7 +201,7 @@
(\\format.result (<format> \\format.nat))
(\\parser.result (<parser> \\parser.nat))
(!expect (^.multi {try.#Success actual}
- (at (sequence.equivalence n.equivalence) = expected actual))))))]
+ (of (sequence.equivalence n.equivalence) = expected actual))))))]
[\\parser.sequence_8 \\format.sequence_8]
[\\parser.sequence_16 \\format.sequence_16]
@@ -220,7 +220,7 @@
(\\format.result <format>)
(\\parser.result <parser>)
(!expect (^.multi {try.#Success actual}
- (at <equivalence> = expected actual))))))]
+ (of <equivalence> = expected actual))))))]
[\\parser.bit \\format.bit random.bit bit.equivalence]
[\\parser.nat \\format.nat random.nat n.equivalence]
@@ -233,11 +233,11 @@
(\\format.result \\format.frac)
(\\parser.result \\parser.frac)
(!expect (^.multi {try.#Success actual}
- (or (at frac.equivalence = expected actual)
+ (or (of frac.equivalence = expected actual)
(and (frac.not_a_number? expected)
(frac.not_a_number? actual))))))))
(do [! random.monad]
- [expected (at ! each (|>> (i64.and (i64.mask \\parser.size_8))
+ [expected (of ! each (|>> (i64.and (i64.mask \\parser.size_8))
(n.max 2))
random.nat)]
(_.coverage [\\parser.not_a_bit]
@@ -259,7 +259,7 @@
(\\format.result <format>)
(\\parser.result <parser>)
(!expect (^.multi {try.#Success actual}
- (at <equivalence> = expected actual))))))]
+ (of <equivalence> = expected actual))))))]
[\\parser.location \\format.location random_location location_equivalence]
[\\parser.code \\format.code random_code code.equivalence]
@@ -273,14 +273,14 @@
(\\format.result <format>)
(\\parser.result <parser>)
(!expect (^.multi {try.#Success actual}
- (at <equivalence> = expected actual))))))]
+ (of <equivalence> = expected actual))))))]
[\\parser.maybe (\\parser.maybe \\parser.nat) \\format.maybe (\\format.maybe \\format.nat) (random.maybe random.nat) (maybe.equivalence n.equivalence)]
[\\parser.list (\\parser.list \\parser.nat) \\format.list (\\format.list \\format.nat) (random.list ..segment_size random.nat) (list.equivalence n.equivalence)]
[\\parser.set (\\parser.set n.hash \\parser.nat) \\format.set (\\format.set \\format.nat) (random.set n.hash ..segment_size random.nat) set.equivalence]
[\\parser.symbol \\parser.symbol \\format.symbol \\format.symbol ..random_symbol symbol.equivalence]))
(do [! random.monad]
- [expected (at ! each (list.repeated ..segment_size) random.nat)]
+ [expected (of ! each (list.repeated ..segment_size) random.nat)]
(_.coverage [\\parser.set_elements_are_not_unique]
(|> expected
(\\format.result (\\format.list \\format.nat))
@@ -295,11 +295,11 @@
(\\parser.result (is (\\parser.Parser (Either Bit Nat))
(\\parser.or \\parser.bit \\parser.nat)))
(!expect (^.multi {try.#Success actual}
- (at (sum.equivalence bit.equivalence n.equivalence) =
+ (of (sum.equivalence bit.equivalence n.equivalence) =
expected
actual))))))
(do [! random.monad]
- [tag (at ! each (|>> (i64.and (i64.mask \\parser.size_8))
+ [tag (of ! each (|>> (i64.and (i64.mask \\parser.size_8))
(n.max 2))
random.nat)
value random.bit]
@@ -323,7 +323,7 @@
(<>.and \\parser.nat
again))))))
(!expect (^.multi {try.#Success actual}
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
expected
actual))))))
)))
@@ -339,22 +339,22 @@
(\\parser.result \\parser.any)
(!expect {try.#Success _})))
(do [! random.monad]
- [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [\\parser.binary_was_not_fully_read]
(|> data
(\\parser.result \\parser.any)
(!expect (^.multi {try.#Failure error}
(exception.match? \\parser.binary_was_not_fully_read error))))))
(do [! random.monad]
- [expected (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [expected (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [\\parser.segment \\format.segment \\format.result]
(|> expected
(\\format.result (\\format.segment ..segment_size))
(\\parser.result (\\parser.segment ..segment_size))
(!expect (^.multi {try.#Success actual}
- (at /.equivalence = expected actual))))))
+ (of /.equivalence = expected actual))))))
(do [! random.monad]
- [data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [data (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [\\parser.end?]
(|> data
(\\parser.result (do <>.monad
@@ -365,8 +365,8 @@
post))))
(!expect {try.#Success .true}))))
(do [! random.monad]
- [to_read (at ! each (n.% (++ ..segment_size)) random.nat)
- data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (of ! each (n.% (++ ..segment_size)) random.nat)
+ data (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [\\parser.Offset \\parser.offset]
(|> data
(\\parser.result (do <>.monad
@@ -380,8 +380,8 @@
(n.= ..segment_size nothing_left)))))
(!expect {try.#Success .true}))))
(do [! random.monad]
- [to_read (at ! each (n.% (++ ..segment_size)) random.nat)
- data (at ! each (at utf8.codec encoded) (random.ascii ..segment_size))]
+ [to_read (of ! each (n.% (++ ..segment_size)) random.nat)
+ data (of ! each (of utf8.codec encoded) (random.ascii ..segment_size))]
(_.coverage [\\parser.remaining]
(|> data
(\\parser.result (do <>.monad
@@ -410,7 +410,7 @@
(def random_specification
(Random \\format.Specification)
- (at random.monad each \\format.nat random.nat))
+ (of random.monad each \\format.nat random.nat))
(def \\format
Test
@@ -439,7 +439,7 @@
[byte random.nat]
(exec (try.trusted (/.has_8! idx byte output))
(again (++ idx))))
- (at random.monad in output)))))
+ (of random.monad in output)))))
(def (throws? exception try)
(All (_ e a) (-> (Exception e) (Try a) Bit))
@@ -479,13 +479,13 @@
(<| (_.covering !._)
(_.for [!.Binary])
(do [! random.monad]
- [.let [gen_size (|> random.nat (at ! each (|>> (n.% 100) (n.max 8))))]
+ [.let [gen_size (|> random.nat (of ! each (|>> (n.% 100) (n.max 8))))]
size gen_size
sample (..random size)
value random.nat
- .let [gen_idx (|> random.nat (at ! each (n.% size)))]
+ .let [gen_idx (|> random.nat (of ! each (n.% size)))]
offset gen_idx
- length (at ! each (n.% (n.- offset size)) random.nat)]
+ length (of ! each (n.% (n.- offset size)) random.nat)]
(`` (all _.and
(_.for [!.=]
($equivalence.spec (function (_ left right)
@@ -523,7 +523,7 @@
reader (function (_ binary idx)
(!.bits_8 idx binary))]
(and (n.= length (!.size random_slice))
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list#each (|>> (n.+ offset) (reader sample)) idxs)
(list#each (reader random_slice) idxs)))))
(_.coverage [!.copy!]
@@ -543,24 +543,24 @@
(<| (_.covering /._)
(_.for [/.Binary])
(do [! random.monad]
- [.let [gen_size (|> random.nat (at ! each (|>> (n.% 100) (n.max 8))))]
+ [.let [gen_size (|> random.nat (of ! each (|>> (n.% 100) (n.max 8))))]
size gen_size
sample (..random size)
value random.nat
- .let [gen_idx (|> random.nat (at ! each (n.% size)))]
- offset (at ! each (n.max 1) gen_idx)
- length (at ! each (n.% (n.- offset size)) random.nat)]
+ .let [gen_idx (|> random.nat (of ! each (n.% size)))]
+ offset (of ! each (n.max 1) gen_idx)
+ length (of ! each (n.% (n.- offset size)) random.nat)]
(all _.and
(_.for [/.equivalence]
($equivalence.spec /.equivalence (..random size)))
(_.for [/.monoid]
($monoid.spec /.equivalence /.monoid (..random size)))
(_.coverage [/.mix]
- (n.= (at list.mix mix n.+ 0 (..as_list sample))
+ (n.= (of list.mix mix n.+ 0 (..as_list sample))
(/.mix n.+ 0 sample)))
(_.coverage [/.empty]
- (at /.equivalence =
+ (of /.equivalence =
(/.empty size)
(/.empty size)))
(_.coverage [/.size]
@@ -587,7 +587,7 @@
(when [(monad.each try.monad (|>> (n.+ offset) (reader sample)) idxs)
(monad.each try.monad (reader random_slice) idxs)]
[{try.#Success binary_vals} {try.#Success slice_vals}]
- (at (list.equivalence n.equivalence) = binary_vals slice_vals)
+ (of (list.equivalence n.equivalence) = binary_vals slice_vals)
_
false))))
@@ -598,8 +598,8 @@
0 (not verdict)
_ verdict))))
(_.coverage [/.after]
- (and (at /.equivalence = sample (/.after 0 sample))
- (at /.equivalence = (/.empty 0) (/.after size sample))
+ (and (of /.equivalence = sample (/.after 0 sample))
+ (of /.equivalence = (/.empty 0) (/.after size sample))
(n.= (n.- offset size) (/.size (/.after offset sample)))
(when (list.reversed (..as_list sample))
{.#End}
@@ -612,7 +612,7 @@
(and (when (/.copy! size 0 sample 0 (/.empty size))
{try.#Success output}
(and (not (same? sample output))
- (at /.equivalence = sample output))
+ (of /.equivalence = sample output))
{try.#Failure _}
false)
diff --git a/stdlib/source/test/lux/data/bit.lux b/stdlib/source/test/lux/data/bit.lux
index edd3fd68b..ebdf744af 100644
--- a/stdlib/source/test/lux/data/bit.lux
+++ b/stdlib/source/test/lux/data/bit.lux
@@ -35,12 +35,12 @@
($codec.spec /.equivalence /.codec random.bit))
(_.coverage [/.no /.yes]
- (and (at /.equivalence = false /.no)
- (at /.equivalence = true /.yes)))
+ (and (of /.equivalence = false /.no)
+ (of /.equivalence = true /.yes)))
(_.coverage [/.off /.on]
- (and (at /.equivalence = false /.off)
- (at /.equivalence = true /.on)))
+ (and (of /.equivalence = false /.off)
+ (of /.equivalence = true /.on)))
(_.coverage [/.complement]
- (and (not (at /.equivalence = value ((/.complement function.identity) value)))
- (at /.equivalence = value ((/.complement not) value))))
+ (and (not (of /.equivalence = value ((/.complement function.identity) value)))
+ (of /.equivalence = value ((/.complement not) value))))
))))
diff --git a/stdlib/source/test/lux/data/collection/array.lux b/stdlib/source/test/lux/data/collection/array.lux
index a923891aa..68ba9480c 100644
--- a/stdlib/source/test/lux/data/collection/array.lux
+++ b/stdlib/source/test/lux/data/collection/array.lux
@@ -35,7 +35,7 @@
(def bounded_size
(Random Nat)
- (at random.monad each (|>> (n.% 20) ++)
+ (of random.monad each (|>> (n.% 20) ++)
random.nat))
(def structures
@@ -67,11 +67,11 @@
choose (is (-> Nat (Maybe Text))
(function (_ value)
(if (n.even? value)
- {.#Some (at n.decimal encoded value)}
+ {.#Some (of n.decimal encoded value)}
{.#None})))]
(_.coverage [/.one]
(when [(|> evens
- (/#each (at n.decimal encoded))
+ (/#each (of n.decimal encoded))
(/.item 0))
(/.one choose evens)]
[{.#Some expected} {.#Some actual}]
@@ -83,7 +83,7 @@
_
false)))
(_.coverage [/.example]
- (at (maybe.equivalence n.equivalence) =
+ (of (maybe.equivalence n.equivalence) =
(/.example n.even? the_array)
(list.example n.even? (/.list {.#None} the_array))))
(_.coverage [/.example']
@@ -106,11 +106,11 @@
_
false))
(_.coverage [/.every?]
- (at bit.equivalence =
+ (of bit.equivalence =
(list.every? n.even? (/.list {.#None} the_array))
(/.every? n.even? the_array)))
(_.coverage [/.any?]
- (at bit.equivalence =
+ (of bit.equivalence =
(list.any? n.even? (/.list {.#None} the_array))
(/.any? n.even? the_array)))
)))
@@ -210,7 +210,7 @@
(and (n.= expected (!.item 0 the_array))
(n.= expected (!.item 1 the_array)))))
(do !
- [occupancy (at ! each (n.% (++ size)) random.nat)]
+ [occupancy (of ! each (n.% (++ size)) random.nat)]
(_.coverage [!.occupancy !.vacancy]
(let [the_array (loop (again [output (is (Array Nat)
(!.empty size))
@@ -232,7 +232,7 @@
random.nat)]
(_.coverage [!.of_list !.list]
(and (|> the_list !.of_list (!.list {.#None})
- (at (list.equivalence n.equivalence) = the_list))
+ (of (list.equivalence n.equivalence) = the_list))
(|> the_array (!.list {.#None}) !.of_list
(!.= n.equivalence the_array))
(exec
@@ -242,12 +242,12 @@
(same? default value)))
(!.list {.#Some default} the_array))))))
(do !
- [amount (at ! each (n.% (++ size)) random.nat)]
+ [amount (of ! each (n.% (++ size)) random.nat)]
(_.coverage [!.copy!]
(let [copy (is (Array Nat)
(!.empty size))]
(exec (!.copy! amount 0 the_array 0 copy)
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list.first amount (!.list {.#None} the_array))
(!.list {.#None} copy))))))
(_.coverage [!.clone]
@@ -263,21 +263,21 @@
(n.= (list.size odds) (!.vacancy the_array))
(|> the_array
(!.list {.#None})
- (at (list.equivalence n.equivalence) = evens))))))
+ (of (list.equivalence n.equivalence) = evens))))))
(let [choose (is (-> Nat (Maybe Text))
(function (_ value)
(if (n.even? value)
- {.#Some (at n.decimal encoded value)}
+ {.#Some (of n.decimal encoded value)}
{.#None})))]
(_.coverage [!.one]
(|> evens
(!.one choose)
(maybe#each (text#= (|> evens
- (!.each (at n.decimal encoded))
+ (!.each (of n.decimal encoded))
(!.item 0))))
(maybe.else false))))
(_.coverage [!.example]
- (at (maybe.equivalence n.equivalence) =
+ (of (maybe.equivalence n.equivalence) =
(!.example n.even? the_array)
(list.example n.even? (!.list {.#None} the_array))))
(_.coverage [!.example']
@@ -296,11 +296,11 @@
_
false))
(_.coverage [!.every?]
- (at bit.equivalence =
+ (of bit.equivalence =
(list.every? n.even? (!.list {.#None} the_array))
(!.every? n.even? the_array)))
(_.coverage [!.any?]
- (at bit.equivalence =
+ (of bit.equivalence =
(list.any? n.even? (!.list {.#None} the_array))
(!.any? n.even? the_array)))
)))))
@@ -393,7 +393,7 @@
_
false)))
(do !
- [occupancy (at ! each (n.% (++ size)) random.nat)]
+ [occupancy (of ! each (n.% (++ size)) random.nat)]
(_.coverage [/.occupancy /.vacancy]
(let [the_array (loop (again [output (is (Array Nat)
(/.empty size))
@@ -415,9 +415,9 @@
random.nat)]
(_.coverage [/.of_list /.list]
(and (|> the_list /.of_list (/.list {.#None})
- (at (list.equivalence n.equivalence) = the_list))
+ (of (list.equivalence n.equivalence) = the_list))
(|> the_array (/.list {.#None}) /.of_list
- (at (/.equivalence n.equivalence) = the_array))
+ (of (/.equivalence n.equivalence) = the_array))
(exec
(/.only! n.even? the_array)
(list.every? (function (_ value)
@@ -425,18 +425,18 @@
(same? default value)))
(/.list {.#Some default} the_array))))))
(do !
- [amount (at ! each (n.% (++ size)) random.nat)]
+ [amount (of ! each (n.% (++ size)) random.nat)]
(_.coverage [/.copy!]
(let [copy (is (Array Nat)
(/.empty size))]
(exec (/.copy! amount 0 the_array 0 copy)
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list.first amount (/.list {.#None} the_array))
(/.list {.#None} copy))))))
(_.coverage [/.clone]
(let [clone (/.clone the_array)]
(and (not (same? the_array clone))
- (at (/.equivalence n.equivalence) = the_array clone))))
+ (of (/.equivalence n.equivalence) = the_array clone))))
(let [the_array (/.clone the_array)
evens (|> the_array (/.list {.#None}) (list.only n.even?))
odds (|> the_array (/.list {.#None}) (list.only n.odd?))]
@@ -444,7 +444,7 @@
(exec (/.only! n.even? the_array)
(and (n.= (list.size evens) (/.occupancy the_array))
(n.= (list.size odds) (/.vacancy the_array))
- (|> the_array (/.list {.#None}) (at (list.equivalence n.equivalence) = evens))))))
+ (|> the_array (/.list {.#None}) (of (list.equivalence n.equivalence) = evens))))))
..test|unsafe
))))
diff --git a/stdlib/source/test/lux/data/collection/bits.lux b/stdlib/source/test/lux/data/collection/bits.lux
index 2a134ab17..965ad8e5a 100644
--- a/stdlib/source/test/lux/data/collection/bits.lux
+++ b/stdlib/source/test/lux/data/collection/bits.lux
@@ -20,16 +20,16 @@
(def (size min max)
(-> Nat Nat (Random Nat))
(|> random.nat
- (at random.monad each (|>> (n.% (++ max)) (n.max min)))))
+ (of random.monad each (|>> (n.% (++ max)) (n.max min)))))
(def .public random
(Random Bits)
(do [! random.monad]
- [size (at ! each (n.% 1,000) random.nat)]
+ [size (of ! each (n.% 1,000) random.nat)]
(when size
0 (in /.empty)
_ (do [! random.monad]
- [idx (|> random.nat (at ! each (n.% size)))]
+ [idx (|> random.nat (of ! each (n.% size)))]
(in (/.one idx /.empty))))))
(def .public test
@@ -50,8 +50,8 @@
(/.empty? /.empty))
(do [! random.monad]
- [size (at ! each (|>> (n.% 1,000) ++) random.nat)
- idx (at ! each (n.% size) random.nat)
+ [size (of ! each (|>> (n.% 1,000) ++) random.nat)
+ idx (of ! each (n.% size) random.nat)
sample ..random]
(all _.and
(_.coverage [/.bit /.one]
@@ -82,17 +82,17 @@
(_.coverage [/.not]
(and (same? /.empty (/.not /.empty))
(or (same? /.empty sample)
- (and (not (at /.equivalence = sample (/.not sample)))
- (at /.equivalence = sample (/.not (/.not sample)))))))
+ (and (not (of /.equivalence = sample (/.not sample)))
+ (of /.equivalence = sample (/.not (/.not sample)))))))
(_.coverage [/.xor]
(and (same? /.empty (/.xor sample sample))
(n.= (/.size (/.xor sample (/.not sample)))
(/.capacity sample))))
(_.coverage [/.or]
- (and (at /.equivalence = sample (/.or sample sample))
+ (and (of /.equivalence = sample (/.or sample sample))
(n.= (/.size (/.or sample (/.not sample)))
(/.capacity sample))))
(_.coverage [/.and]
- (and (at /.equivalence = sample (/.and sample sample))
+ (and (of /.equivalence = sample (/.and sample sample))
(same? /.empty (/.and sample (/.not sample)))))
)))))
diff --git a/stdlib/source/test/lux/data/collection/dictionary.lux b/stdlib/source/test/lux/data/collection/dictionary.lux
index d02d9f3a4..121fefce2 100644
--- a/stdlib/source/test/lux/data/collection/dictionary.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary.lux
@@ -32,7 +32,7 @@
(def for_dictionaries
Test
(do [! random.monad]
- [.let [capped_nat (at random.monad each (n.% 100) random.nat)]
+ [.let [capped_nat (of random.monad each (n.% 100) random.nat)]
size capped_nat
dict (random.dictionary n.hash size random.nat capped_nat)
non_key (random.only (|>> (/.key? dict) not)
@@ -134,7 +134,7 @@
(def for_entries
Test
(do random.monad
- [.let [capped_nat (at random.monad each (n.% 100) random.nat)]
+ [.let [capped_nat (of random.monad each (n.% 100) random.nat)]
size capped_nat
dict (random.dictionary n.hash size random.nat capped_nat)
non_key (random.only (|>> (/.key? dict) not)
@@ -254,7 +254,7 @@
(<| (_.covering /._)
(_.for [/.Dictionary])
(do random.monad
- [.let [capped_nat (at random.monad each (n.% 100) random.nat)]
+ [.let [capped_nat (of random.monad each (n.% 100) random.nat)]
size capped_nat
dict (random.dictionary n.hash size random.nat capped_nat)
non_key (random.only (|>> (/.key? dict) not)
diff --git a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
index 951d6c891..d1c9ba933 100644
--- a/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/dictionary/ordered.lux
@@ -44,7 +44,7 @@
(<| (_.covering /._)
(_.for [/.Dictionary])
(do [! random.monad]
- [size (at ! each (n.% 100) random.nat)
+ [size (of ! each (n.% 100) random.nat)
keys (random.set n.hash size random.nat)
values (random.set n.hash size random.nat)
extra_key (random.only (|>> (set.member? keys) not)
diff --git a/stdlib/source/test/lux/data/collection/list.lux b/stdlib/source/test/lux/data/collection/list.lux
index 3b079d53d..93af39185 100644
--- a/stdlib/source/test/lux/data/collection/list.lux
+++ b/stdlib/source/test/lux/data/collection/list.lux
@@ -35,7 +35,7 @@
(def bounded_size
(Random Nat)
- (at random.monad each (n.% 100)
+ (of random.monad each (n.% 100)
random.nat))
(def random
@@ -44,7 +44,7 @@
[size ..bounded_size]
(|> random.nat
(random.set n.hash size)
- (at ! each set.list))))
+ (of ! each set.list))))
(def signatures
Test
@@ -53,7 +53,7 @@
($equivalence.spec (/.equivalence n.equivalence) ..random))
(_.for [/.hash]
(|> random.nat
- (at random.monad each (|>> list))
+ (of random.monad each (|>> list))
($hash.spec (/.hash n.hash))))
(_.for [/.monoid]
($monoid.spec (/.equivalence n.equivalence) /.monoid ..random))
@@ -90,12 +90,12 @@
(do [! random.monad]
[size ..bounded_size
.let [(open "/#[0]") (/.equivalence n.equivalence)]
- sample (at ! each set.list (random.set n.hash size random.nat))]
+ sample (of ! each set.list (random.set n.hash size random.nat))]
(all _.and
(_.coverage [/.size]
(n.= size (/.size sample)))
(_.coverage [/.empty?]
- (at bit.equivalence =
+ (of bit.equivalence =
(/.empty? sample)
(n.= 0 (/.size sample))))
(_.coverage [/.repeated]
@@ -179,7 +179,7 @@
(do !
[index (when size
0 random.nat
- _ (at ! each (n.% size) random.nat))
+ _ (of ! each (n.% size) random.nat))
.let [changed? (/#= sample (/.revised index ++ sample))
same? (/#= sample (/.revised size ++ sample))]]
(_.coverage [/.revised]
@@ -197,8 +197,8 @@
[sample (random.only (|>> /.size (n.> 0))
..random)
.let [size (/.size sample)]
- idx (at ! each (n.% size) random.nat)
- sub_size (at ! each (|>> (n.% size) ++) random.nat)]
+ idx (of ! each (n.% size) random.nat)
+ sub_size (of ! each (|>> (n.% size) ++) random.nat)]
(all _.and
(_.coverage [/.only]
(let [positives (/.only n.even? sample)
@@ -342,10 +342,10 @@
(and size_of_smaller_list!
can_extract_values!)))
(_.coverage [/.zipped]
- (and (at (/.equivalence (product.equivalence n.equivalence n.equivalence)) =
+ (and (of (/.equivalence (product.equivalence n.equivalence n.equivalence)) =
(/.zipped_2 sample/0 sample/1)
((/.zipped 2) sample/0 sample/1))
- (at (/.equivalence (all product.equivalence n.equivalence n.equivalence n.equivalence)) =
+ (of (/.equivalence (all product.equivalence n.equivalence n.equivalence n.equivalence)) =
(/.zipped_3 sample/0 sample/1 sample/2)
((/.zipped 3) sample/0 sample/1 sample/2))))
@@ -378,7 +378,7 @@
choice (is (-> Nat (Maybe Text))
(function (_ value)
(if (n.even? value)
- {.#Some (at n.decimal encoded value)}
+ {.#Some (of n.decimal encoded value)}
{.#None})))]
(do [! random.monad]
[sample ..random]
@@ -386,7 +386,7 @@
(_.coverage [/.one]
(when [(|> sample
(/.only n.even?)
- (/#each (at n.decimal encoded))
+ (/#each (of n.decimal encoded))
/.head)
(/.one choice sample)]
[{.#Some expected} {.#Some actual}]
@@ -398,10 +398,10 @@
_
false))
(_.coverage [/.all]
- (at (/.equivalence text.equivalence) =
+ (of (/.equivalence text.equivalence) =
(|> sample
(/.only n.even?)
- (/#each (at n.decimal encoded)))
+ (/#each (of n.decimal encoded)))
(/.all choice sample)))
(_.coverage [/.example]
(when (/.example n.even? sample)
@@ -451,7 +451,7 @@
0)))))
(_.coverage [/.mixes]
(/#= (/#each (function (_ index)
- (at /.mix mix n.+ 0 (/.first index sample)))
+ (of /.mix mix n.+ 0 (/.first index sample)))
(/.indices (++ (/.size sample))))
(/.mixes n.+ 0 sample)))
(do random.monad
diff --git a/stdlib/source/test/lux/data/collection/list/property.lux b/stdlib/source/test/lux/data/collection/list/property.lux
index fa8161e16..719a17179 100644
--- a/stdlib/source/test/lux/data/collection/list/property.lux
+++ b/stdlib/source/test/lux/data/collection/list/property.lux
@@ -37,7 +37,7 @@
(_.for [/.List])
(do [! random.monad]
[.let [gen_key (random.alphabetic 10)]
- size (at ! each (n.% 100) random.nat)
+ size (of ! each (n.% 100) random.nat)
sample (..random size gen_key random.nat)
.let [keys (|> sample /.keys (set.of_list text.hash))]
@@ -62,7 +62,7 @@
(_.coverage [/.empty]
(/.empty? /.empty))
(_.coverage [/.keys /.values]
- (at (/.equivalence n.equivalence) =
+ (of (/.equivalence n.equivalence) =
sample
(list.zipped_2 (/.keys sample)
(/.values sample))))
@@ -94,5 +94,5 @@
(|> sample
(/.has extra_key extra_value)
(/.lacks extra_key)
- (at (/.equivalence n.equivalence) = sample)))
+ (of (/.equivalence n.equivalence) = sample)))
))))
diff --git a/stdlib/source/test/lux/data/collection/queue.lux b/stdlib/source/test/lux/data/collection/queue.lux
index 99511bab5..2a99ba497 100644
--- a/stdlib/source/test/lux/data/collection/queue.lux
+++ b/stdlib/source/test/lux/data/collection/queue.lux
@@ -27,9 +27,10 @@
(def .public test
Test
(<| (_.covering /._)
- (_.for [/.Queue])
+ (_.for [/.Queue
+ /.#front /.#rear])
(do [! random.monad]
- [size (at ! each (n.% 100) random.nat)
+ [size (of ! each (n.% 100) random.nat)
members (random.set n.hash size random.nat)
non_member (random.only (|>> (set.member? members) not)
random.nat)
@@ -43,7 +44,7 @@
(_.coverage [/.of_list /.list]
(|> members /.of_list /.list
- (at (list.equivalence n.equivalence) = members)))
+ (of (list.equivalence n.equivalence) = members)))
(_.coverage [/.size]
(n.= size (/.size sample)))
(_.coverage [/.empty?]
@@ -54,7 +55,7 @@
all_empty_queues_look_the_same!
(bit#= (/.empty? sample)
- (at (/.equivalence n.equivalence) =
+ (of (/.equivalence n.equivalence) =
sample
/.empty))]
(and empty_is_empty!
@@ -88,7 +89,7 @@
(/.member? n.equivalence pushed non_member)
has_expected_order!
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list#composite (/.list sample) (list non_member))
(/.list pushed))]
(and size_increases!
@@ -107,7 +108,7 @@
(not (/.member? n.equivalence popped target))
has_expected_order!
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
expected
(/.list popped))]
(and size_decreases!
diff --git a/stdlib/source/test/lux/data/collection/queue/priority.lux b/stdlib/source/test/lux/data/collection/queue/priority.lux
index b7a1028fe..b948fd8b2 100644
--- a/stdlib/source/test/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/test/lux/data/collection/queue/priority.lux
@@ -32,7 +32,7 @@
(<| (_.covering /._)
(_.for [/.Queue])
(do [! random.monad]
- [size (at ! each (n.% 100) random.nat)
+ [size (of ! each (n.% 100) random.nat)
sample (..random size)
non_member_priority random.nat
non_member (random.only (|>> (/.member? n.equivalence sample) not)
diff --git a/stdlib/source/test/lux/data/collection/sequence.lux b/stdlib/source/test/lux/data/collection/sequence.lux
index a24d05ed6..8a38c3a98 100644
--- a/stdlib/source/test/lux/data/collection/sequence.lux
+++ b/stdlib/source/test/lux/data/collection/sequence.lux
@@ -31,7 +31,7 @@
(def signatures
Test
(do [! random.monad]
- [size (at ! each (n.% 100) random.nat)]
+ [size (of ! each (n.% 100) random.nat)]
(all _.and
(_.for [/.equivalence]
($equivalence.spec (/.equivalence n.equivalence) (random.sequence size random.nat)))
@@ -50,7 +50,7 @@
(def whole
Test
(do [! random.monad]
- [size (at ! each (n.% 100) random.nat)
+ [size (of ! each (n.% 100) random.nat)
sample (random.set n.hash size random.nat)
.let [sample (|> sample set.list /.of_list)]
.let [(open "/#[0]") (/.equivalence n.equivalence)]]
@@ -83,10 +83,10 @@
(def index_based
Test
(do [! random.monad]
- [size (at ! each (|>> (n.% 100) ++) random.nat)]
+ [size (of ! each (|>> (n.% 100) ++) random.nat)]
(all _.and
(do !
- [good_index (|> random.nat (at ! each (n.% size)))
+ [good_index (|> random.nat (of ! each (n.% size)))
.let [bad_index (n.+ size good_index)]
sample (random.set n.hash size random.nat)
non_member (random.only (|>> (set.member? sample) not)
@@ -136,7 +136,7 @@
(<| (_.covering /._)
(_.for [/.Sequence])
(do [! random.monad]
- [size (at ! each (|>> (n.% 100) ++) random.nat)]
+ [size (of ! each (|>> (n.% 100) ++) random.nat)]
(all _.and
..signatures
..whole
@@ -199,11 +199,11 @@
choice (is (-> Nat (Maybe Text))
(function (_ value)
(if (n.even? value)
- {.#Some (at n.decimal encoded value)}
+ {.#Some (of n.decimal encoded value)}
{.#None})))]
(when [(|> sample
(/.only n.even?)
- (/#each (at n.decimal encoded))
+ (/#each (of n.decimal encoded))
(/.item 0))
(/.one choice sample)]
[{try.#Success expected} {.#Some actual}]
diff --git a/stdlib/source/test/lux/data/collection/set.lux b/stdlib/source/test/lux/data/collection/set.lux
index 16d7294d8..d4cff2607 100644
--- a/stdlib/source/test/lux/data/collection/set.lux
+++ b/stdlib/source/test/lux/data/collection/set.lux
@@ -23,7 +23,7 @@
(def gen_nat
(Random Nat)
- (at random.monad each (n.% 100)
+ (of random.monad each (n.% 100)
random.nat))
(def .public test
@@ -37,7 +37,7 @@
($equivalence.spec /.equivalence (random.set n.hash size random.nat)))
(_.for [/.hash]
(|> random.nat
- (at random.monad each (|>> list (/.of_list n.hash)))
+ (of random.monad each (|>> list (/.of_list n.hash)))
($hash.spec /.hash)))
(_.for [/.monoid]
($monoid.spec /.equivalence (/.monoid n.hash) (random.set n.hash size random.nat)))
@@ -53,7 +53,7 @@
(_.coverage [/.empty]
(/.empty? (/.empty n.hash)))
(do !
- [hash (at ! each (function (_ constant)
+ [hash (of ! each (function (_ constant)
(is (Hash Nat)
(implementation
(def equivalence n.equivalence)
diff --git a/stdlib/source/test/lux/data/collection/set/multi.lux b/stdlib/source/test/lux/data/collection/set/multi.lux
index 16e7986fa..f22c4c455 100644
--- a/stdlib/source/test/lux/data/collection/set/multi.lux
+++ b/stdlib/source/test/lux/data/collection/set/multi.lux
@@ -26,7 +26,7 @@
(def count
(Random Nat)
- (at random.monad each (|>> (n.% 10) ++) random.nat))
+ (of random.monad each (|>> (n.% 10) ++) random.nat))
(def .public (random size hash count element)
(All (_ a) (-> Nat (Hash a) (Random Nat) (Random a) (Random (/.Set a))))
@@ -42,13 +42,13 @@
(def signature
Test
(do [! random.monad]
- [diversity (at ! each (n.% 10) random.nat)]
+ [diversity (of ! each (n.% 10) random.nat)]
(all _.and
(_.for [/.equivalence]
($equivalence.spec /.equivalence (..random diversity n.hash ..count random.nat)))
(_.for [/.hash]
(|> random.nat
- (at random.monad each (function (_ single)
+ (of random.monad each (function (_ single)
(/.has 1 single (/.empty n.hash))))
($hash.spec /.hash)))
)))
@@ -56,7 +56,7 @@
(def composition
Test
(do [! random.monad]
- [diversity (at ! each (n.% 10) random.nat)
+ [diversity (of ! each (n.% 10) random.nat)
sample (..random diversity n.hash ..count random.nat)
another (..random diversity n.hash ..count random.nat)]
(`` (all _.and
@@ -116,19 +116,19 @@
(<| (_.covering /._)
(_.for [/.Set])
(do [! random.monad]
- [diversity (at ! each (n.% 10) random.nat)
+ [diversity (of ! each (n.% 10) random.nat)
sample (..random diversity n.hash ..count random.nat)
non_member (random.only (predicate.complement (set.member? (/.support sample)))
random.nat)
addition_count ..count
- partial_removal_count (at ! each (n.% addition_count) random.nat)
+ partial_removal_count (of ! each (n.% addition_count) random.nat)
another (..random diversity n.hash ..count random.nat)]
(all _.and
(_.coverage [/.list /.of_list]
(|> sample
/.list
(/.of_list n.hash)
- (at /.equivalence = sample)))
+ (of /.equivalence = sample)))
(_.coverage [/.size]
(n.= (list.size (/.list sample))
(/.size sample)))
@@ -162,7 +162,7 @@
(let [null_scenario!
(|> sample
(/.has 0 non_member)
- (at /.equivalence = sample))
+ (of /.equivalence = sample))
normal_scenario!
(let [sample+ (/.has addition_count non_member sample)]
@@ -173,7 +173,7 @@
normal_scenario!)))
(_.coverage [/.lacks]
(let [null_scenario!
- (at /.equivalence =
+ (of /.equivalence =
(|> sample
(/.has addition_count non_member))
(|> sample
@@ -193,7 +193,7 @@
(|> sample
(/.has addition_count non_member)
(/.lacks addition_count non_member)
- (at /.equivalence = sample))]
+ (of /.equivalence = sample))]
(and null_scenario!
partial_scenario!
total_scenario!)))
@@ -205,12 +205,12 @@
(let [unary (|> sample /.support /.of_set)]
(and (/.sub? sample unary)
(or (not (/.sub? unary sample))
- (at /.equivalence = sample unary)))))
+ (of /.equivalence = sample unary)))))
(_.coverage [/.super?]
(let [unary (|> sample /.support /.of_set)]
(and (/.super? unary sample)
(or (not (/.super? sample unary))
- (at /.equivalence = sample unary)))))
+ (of /.equivalence = sample unary)))))
(_.coverage [/.difference]
(let [|sample| (/.support sample)
|another| (/.support another)
diff --git a/stdlib/source/test/lux/data/collection/set/ordered.lux b/stdlib/source/test/lux/data/collection/set/ordered.lux
index cedc2db15..45c8a9a9e 100644
--- a/stdlib/source/test/lux/data/collection/set/ordered.lux
+++ b/stdlib/source/test/lux/data/collection/set/ordered.lux
@@ -22,7 +22,7 @@
(def size
(random.Random Nat)
- (at random.monad each (n.% 100) random.nat))
+ (of random.monad each (n.% 100) random.nat))
(def .public (random size order gen_value)
(All (_ a) (-> Nat (Order a) (Random a) (Random (Set a))))
@@ -48,7 +48,7 @@
non_memberL (random.only (|>> (//.member? usetL) not)
random.nat)
.let [listL (//.list usetL)]
- listR (|> (random.set n.hash sizeR random.nat) (at ! each //.list))
+ listR (|> (random.set n.hash sizeR random.nat) (of ! each //.list))
.let [(open "/#[0]") /.equivalence
setL (/.of_list n.order listL)
setR (/.of_list n.order listR)
@@ -65,9 +65,9 @@
(_.coverage [/.empty]
(/.empty? (/.empty n.order)))
(_.coverage [/.list]
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(/.list (/.of_list n.order listL))
- (list.sorted (at n.order <) listL)))
+ (list.sorted (of n.order <) listL)))
(_.coverage [/.of_list]
(|> setL
/.list (/.of_list n.order)
@@ -102,7 +102,7 @@
(|> setL
(/.has non_memberL)
(/.lacks non_memberL)
- (at /.equivalence = setL)))
+ (of /.equivalence = setL)))
(_.coverage [/.sub?]
(let [self!
(/.sub? setL setL)
@@ -127,7 +127,7 @@
(,, (with_template [<coverage> <relation> <empty?>]
[(_.coverage [<coverage>]
(let [self!
- (at /.equivalence =
+ (of /.equivalence =
setL
(<coverage> setL setL))
@@ -136,12 +136,12 @@
(<relation> (<coverage> setL setR) setR))
empty!
- (at /.equivalence =
+ (of /.equivalence =
(if <empty?> empty setL)
(<coverage> setL empty))
idempotence!
- (at /.equivalence =
+ (of /.equivalence =
(<coverage> setL (<coverage> setL setR))
(<coverage> setR (<coverage> setL setR)))]
(and self!
@@ -156,19 +156,19 @@
(let [self!
(|> setL
(/.difference setL)
- (at /.equivalence = empty))
+ (of /.equivalence = empty))
empty!
(|> setL
(/.difference empty)
- (at /.equivalence = setL))
+ (of /.equivalence = setL))
difference!
(not (list.any? (/.member? (/.difference setL setR))
(/.list setL)))
idempotence!
- (at /.equivalence =
+ (of /.equivalence =
(/.difference setL setR)
(/.difference setL (/.difference setL setR)))]
(and self!
diff --git a/stdlib/source/test/lux/data/collection/stack.lux b/stdlib/source/test/lux/data/collection/stack.lux
index 22935a5f9..fab3b7d91 100644
--- a/stdlib/source/test/lux/data/collection/stack.lux
+++ b/stdlib/source/test/lux/data/collection/stack.lux
@@ -28,7 +28,7 @@
(<| (_.covering /._)
(_.for [/.Stack])
(do random.monad
- [size (at random.monad each (n.% 100) random.nat)
+ [size (of random.monad each (n.% 100) random.nat)
sample (random.stack size random.nat)
expected_top random.nat]
(all _.and
@@ -57,7 +57,7 @@
(/.empty? sample)
{.#Some [top remaining]}
- (at (/.equivalence n.equivalence) =
+ (of (/.equivalence n.equivalence) =
sample
(/.top top remaining))))
(_.coverage [/.top]
diff --git a/stdlib/source/test/lux/data/collection/stream.lux b/stdlib/source/test/lux/data/collection/stream.lux
index df001ce0e..f14f53131 100644
--- a/stdlib/source/test/lux/data/collection/stream.lux
+++ b/stdlib/source/test/lux/data/collection/stream.lux
@@ -26,7 +26,7 @@
(All (_ a) (-> (Equivalence a) (Equivalence (/.Stream a))))
(implementation
(def (= reference subject)
- (at (list.equivalence super) =
+ (of (list.equivalence super) =
(/.first 100 reference)
(/.first 100 subject)))))
@@ -46,9 +46,9 @@
(let [(open "list#[0]") (list.equivalence n.equivalence)])
(do [! random.monad]
[repeated random.nat
- index (at ! each (n.% 100) random.nat)
- size (at ! each (|>> (n.% 10) ++) random.nat)
- offset (at ! each (n.% 100) random.nat)
+ index (of ! each (n.% 100) random.nat)
+ size (of ! each (|>> (n.% 10) ++) random.nat)
+ offset (of ! each (n.% 100) random.nat)
cycle_start random.nat
cycle_next (random.list size random.nat)]
(all _.and
diff --git a/stdlib/source/test/lux/data/collection/tree.lux b/stdlib/source/test/lux/data/collection/tree.lux
index 8f7ef89da..eef32ee7d 100644
--- a/stdlib/source/test/lux/data/collection/tree.lux
+++ b/stdlib/source/test/lux/data/collection/tree.lux
@@ -189,7 +189,7 @@
(All (_ a) (-> (Random a) (Random [Nat (Tree a)])))
(do [! random.monad]
[value gen_value
- num_children (at ! each (n.% 2) random.nat)
+ num_children (of ! each (n.% 2) random.nat)
children (random.list num_children (tree gen_value))]
(in [(|> children
(list#each product.left)
@@ -204,7 +204,7 @@
(all _.and
(_.for [/.equivalence]
(|> (..tree random.nat)
- (at random.monad each product.right)
+ (of random.monad each product.right)
($equivalence.spec (/.equivalence n.equivalence))))
(_.for [/.mix]
($mix.spec /.leaf /.equivalence /.mix))
@@ -219,15 +219,15 @@
(do random.monad
[expected random.nat]
(_.coverage [/.leaf]
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list expected)
(/.flat (/.leaf expected)))))
(do [! random.monad]
[value random.nat
- num_children (at ! each (n.% 3) random.nat)
+ num_children (of ! each (n.% 3) random.nat)
children (random.list num_children random.nat)]
(_.coverage [/.branch]
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list.partial value children)
(/.flat (/.branch value (list#each /.leaf children))))))
(do random.monad
@@ -238,15 +238,15 @@
expected/4 random.nat
expected/5 random.nat]
(_.coverage [/.tree]
- (and (at (list.equivalence n.equivalence) =
+ (and (of (list.equivalence n.equivalence) =
(list expected/0)
(/.flat (/.tree expected/0)))
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list expected/0 expected/1 expected/2)
(/.flat (/.tree expected/0
{expected/1 {}
expected/2 {}})))
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list expected/0 expected/1 expected/2
expected/3 expected/4 expected/5)
(/.flat (/.tree expected/0
diff --git a/stdlib/source/test/lux/data/collection/tree/finger.lux b/stdlib/source/test/lux/data/collection/tree/finger.lux
index ff6e1b62f..85d7cd123 100644
--- a/stdlib/source/test/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/test/lux/data/collection/tree/finger.lux
@@ -45,21 +45,21 @@
true))
(_.coverage [/.tag]
(and (text#= tag_left
- (/.tag (at ..builder leaf tag_left expected_left)))
+ (/.tag (of ..builder leaf tag_left expected_left)))
(text#= (text#composite tag_left tag_right)
- (/.tag (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right))))))
+ (/.tag (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right))))))
(_.coverage [/.root]
- (and (when (/.root (at ..builder leaf tag_left expected_left))
+ (and (when (/.root (of ..builder leaf tag_left expected_left))
{.#Left actual}
(n.= expected_left actual)
{.#Right _}
false)
- (when (/.root (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right)))
+ (when (/.root (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right)))
{.#Left _}
false
@@ -74,11 +74,11 @@
false))))
(_.coverage [/.value]
(and (n.= expected_left
- (/.value (at ..builder leaf tag_left expected_left)))
+ (/.value (of ..builder leaf tag_left expected_left)))
(n.= expected_left
- (/.value (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right))))))
+ (/.value (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right))))))
(do random.monad
[.let [tags_equivalence (list.equivalence text.equivalence)
values_equivalence (list.equivalence n.equivalence)]
@@ -88,37 +88,37 @@
values/T (random.list 5 random.nat)]
(_.coverage [/.tags /.values]
(let [tree (list#mix (function (_ [tag value] tree)
- (at builder branch tree (at builder leaf tag value)))
- (at builder leaf tags/H values/H)
+ (of builder branch tree (of builder leaf tag value)))
+ (of builder leaf tags/H values/H)
(list.zipped_2 tags/T values/T))]
- (and (at tags_equivalence = (list.partial tags/H tags/T) (/.tags tree))
- (at values_equivalence = (list.partial values/H values/T) (/.values tree))))))
+ (and (of tags_equivalence = (list.partial tags/H tags/T) (/.tags tree))
+ (of values_equivalence = (list.partial values/H values/T) (/.values tree))))))
(_.coverage [/.one]
(let [can_find_correct_one!
- (|> (at ..builder leaf tag_left expected_left)
+ (|> (of ..builder leaf tag_left expected_left)
(/.one (text.contains? tag_left))
(maybe#each (n.= expected_left))
(maybe.else false))
cannot_find_incorrect_one!
- (|> (at ..builder leaf tag_right expected_right)
+ (|> (of ..builder leaf tag_right expected_right)
(/.one (text.contains? tag_left))
(maybe#each (n.= expected_left))
(maybe.else false)
not)
can_find_left!
- (|> (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right))
+ (|> (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right))
(/.one (text.contains? tag_left))
(maybe#each (n.= expected_left))
(maybe.else false))
can_find_right!
- (|> (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right))
+ (|> (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right))
(/.one (text.contains? tag_right))
(maybe#each (n.= expected_right))
(maybe.else false))]
@@ -129,23 +129,23 @@
(_.coverage [/.exists?]
(let [can_find_correct_one!
(/.exists? (text.contains? tag_left)
- (at ..builder leaf tag_left expected_left))
+ (of ..builder leaf tag_left expected_left))
cannot_find_incorrect_one!
(not (/.exists? (text.contains? tag_left)
- (at ..builder leaf tag_right expected_right)))
+ (of ..builder leaf tag_right expected_right)))
can_find_left!
(/.exists? (text.contains? tag_left)
- (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right)))
+ (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right)))
can_find_right!
(/.exists? (text.contains? tag_right)
- (at ..builder branch
- (at ..builder leaf tag_left expected_left)
- (at ..builder leaf tag_right expected_right)))]
+ (of ..builder branch
+ (of ..builder leaf tag_left expected_left)
+ (of ..builder leaf tag_right expected_right)))]
(and can_find_correct_one!
cannot_find_incorrect_one!
can_find_left!
diff --git a/stdlib/source/test/lux/data/collection/tree/zipper.lux b/stdlib/source/test/lux/data/collection/tree/zipper.lux
index 0da1f808d..fe764d955 100644
--- a/stdlib/source/test/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/test/lux/data/collection/tree/zipper.lux
@@ -164,7 +164,7 @@
(open "list#[0]") (list.equivalence n.equivalence)]]
(all _.and
(_.for [/.equivalence]
- ($equivalence.spec (/.equivalence n.equivalence) (at ! each (|>> product.right /.zipper) (//.tree random.nat))))
+ ($equivalence.spec (/.equivalence n.equivalence) (of ! each (|>> product.right /.zipper) (//.tree random.nat))))
(_.for [/.functor]
($functor.spec (|>> tree.leaf /.zipper) /.equivalence /.functor))
(_.for [/.comonad]
diff --git a/stdlib/source/test/lux/data/color.lux b/stdlib/source/test/lux/data/color.lux
index 8198800e6..5d94addef 100644
--- a/stdlib/source/test/lux/data/color.lux
+++ b/stdlib/source/test/lux/data/color.lux
@@ -27,6 +27,8 @@
["[1][0]" rgb]
["[1][0]" cmyk]
["[1][0]" hsl]
+ ["[1][0]" hsb]
+ ["[1][0]" pigment]
["[1][0]" named]
["[1][0]" terminal]])
@@ -81,11 +83,7 @@
(all _.and
(_.coverage [/.rgb /.of_rgb]
(|> expected /.rgb /.of_rgb
- (at /.equivalence = expected)))
- (_.coverage [/.HSB /.hsb /.of_hsb]
- (|> expected /.hsb /.of_hsb
- (distance/3 expected)
- (f.<= ..rgb_error_margin)))
+ (of /.equivalence = expected)))
))
(def transformation
@@ -127,54 +125,54 @@
(f.<= ..rgb_error_margin)))))
)))
-(def palette
- Test
- (_.for [/.Spread /.Palette]
- (do [! random.monad]
- [eH (at ! each (|>> f.abs (f.% +0.9) (f.+ +0.05))
- random.safe_frac)
- .let [eS +0.5]
- variations (at ! each (|>> (n.% 3) (n.+ 2)) random.nat)
- .let [max_spread (f./ (|> variations ++ .int int.frac)
- +1.0)
- min_spread (f./ +2.0 max_spread)
- spread_space (f.- min_spread max_spread)]
- spread (at ! each (|>> f.abs (f.% spread_space) (f.+ min_spread))
- random.safe_frac)]
- (`` (all _.and
- (,, (with_template [<brightness> <palette>]
- [(_.coverage [<palette>]
- (let [eB <brightness>
- expected (/.of_hsb [eH eS eB])
- palette (<palette> spread variations expected)]
- (and (n.= variations (list.size palette))
- (not (list.any? (at /.equivalence = expected) palette)))))]
- [+1.0 /.analogous]
- [+0.5 /.monochromatic]
- ))
- (,, (with_template [<palette>]
- [(_.coverage [<palette>]
- (let [expected (/.of_hsb [eH eS +0.5])
- [c0 c1 c2] (<palette> expected)]
- (and (at /.equivalence = expected c0)
- (not (at /.equivalence = expected c1))
- (not (at /.equivalence = expected c2)))))]
-
- [/.triad]
- [/.clash]
- [/.split_complement]))
- (,, (with_template [<palette>]
- [(_.coverage [<palette>]
- (let [expected (/.of_hsb [eH eS +0.5])
- [c0 c1 c2 c3] (<palette> expected)]
- (and (at /.equivalence = expected c0)
- (not (at /.equivalence = expected c1))
- (not (at /.equivalence = expected c2))
- (not (at /.equivalence = expected c3)))))]
-
- [/.square]
- [/.tetradic]))
- )))))
+... (def palette
+... Test
+... (_.for [/.Spread /.Palette]
+... (do [! random.monad]
+... [eH (of ! each (|>> f.abs (f.% +0.9) (f.+ +0.05))
+... random.safe_frac)
+... .let [eS +0.5]
+... variations (of ! each (|>> (n.% 3) (n.+ 2)) random.nat)
+... .let [max_spread (f./ (|> variations ++ .int int.frac)
+... +1.0)
+... min_spread (f./ +2.0 max_spread)
+... spread_space (f.- min_spread max_spread)]
+... spread (of ! each (|>> f.abs (f.% spread_space) (f.+ min_spread))
+... random.safe_frac)]
+... (`` (all _.and
+... (,, (with_template [<brightness> <palette>]
+... [(_.coverage [<palette>]
+... (let [eB <brightness>
+... expected (/.of_hsb [eH eS eB])
+... palette (<palette> spread variations expected)]
+... (and (n.= variations (list.size palette))
+... (not (list.any? (of /.equivalence = expected) palette)))))]
+... [+1.0 /.analogous]
+... [+0.5 /.monochromatic]
+... ))
+... (,, (with_template [<palette>]
+... [(_.coverage [<palette>]
+... (let [expected (/.of_hsb [eH eS +0.5])
+... [c0 c1 c2] (<palette> expected)]
+... (and (of /.equivalence = expected c0)
+... (not (of /.equivalence = expected c1))
+... (not (of /.equivalence = expected c2)))))]
+
+... [/.triad]
+... [/.clash]
+... [/.split_complement]))
+... (,, (with_template [<palette>]
+... [(_.coverage [<palette>]
+... (let [expected (/.of_hsb [eH eS +0.5])
+... [c0 c1 c2 c3] (<palette> expected)]
+... (and (of /.equivalence = expected c0)
+... (not (of /.equivalence = expected c1))
+... (not (of /.equivalence = expected c2))
+... (not (of /.equivalence = expected c3)))))]
+
+... [/.square]
+... [/.tetradic]))
+... )))))
(def .public test
Test
@@ -199,22 +197,16 @@
(and (not (/#= expected ~expected))
(/#= expected (/.complement ~expected)))))
(_.coverage [/.black /.white]
- (and (at /.equivalence = /.white (/.complement /.black))
- (at /.equivalence = /.black (/.complement /.white))))
+ (and (of /.equivalence = /.white (/.complement /.black))
+ (of /.equivalence = /.black (/.complement /.white))))
..transformation
- ..palette
- (_.for [/.Alpha /.Pigment]
- (all _.and
- (_.coverage [/.transparent /.opaque]
- (and (r.= /.opaque (-- /.transparent))
- (r.= /.transparent (++ /.opaque))))
- (_.coverage [/.translucent]
- (r.= /.transparent (r.+ /.translucent /.translucent)))
- ))
+ ... ..palette
/rgb.test
/cmyk.test
/hsl.test
+ /hsb.test
+ /pigment.test
/named.test
/terminal.test
))))
diff --git a/stdlib/source/test/lux/data/color/cmyk.lux b/stdlib/source/test/lux/data/color/cmyk.lux
index 4a9736762..8c852cd4c 100644
--- a/stdlib/source/test/lux/data/color/cmyk.lux
+++ b/stdlib/source/test/lux/data/color/cmyk.lux
@@ -9,7 +9,7 @@
["[0]" try (.use "[1]#[0]" functor)]
["[0]" exception]]
[math
- ["[0]" random (.only Random)]
+ ["[0]" random (.only Random) (.use "[1]#[0]" functor)]
[number
["f" frac]]]
[test
@@ -23,8 +23,7 @@
(def .public value
(Random /.Value)
- (random.one (|>> /.value try.maybe)
- random.safe_frac))
+ (random#each /.value random.safe_frac))
(def .public random
(Random /.CMYK)
@@ -44,32 +43,35 @@
(do [! random.monad]
[expected_value ..value
expected_rgb rgbT.random
- expected_cmyk ..random])
+ expected_cmyk ..random
+
+ possible_value random.frac])
(all _.and
(_.for [/.Value]
(all _.and
- (_.coverage [/.number /.value]
- (|> expected_value
- /.number
- /.value
- (try#each (|>> /.number
- (f.= (/.number expected_value))))
- (try.else false)))
+ (_.coverage [/.value?]
+ (and (/.value? expected_value)
+ (not (/.value? (f.+ f.smallest /.most)))
+ (not (/.value? (f.- f.smallest /.least)))))
+ (_.coverage [/.value]
+ (if (/.value? possible_value)
+ (|> possible_value
+ /.value
+ (f.= possible_value))
+ (or (f.= /.least (/.value possible_value))
+ (f.= /.most (/.value possible_value)))))
(_.coverage [/.least]
- (when (/.value (f.+ +0.001 (/.number /.least)))
- {try.#Failure _} false
- {try.#Success _} true))
+ (and (f.< /.most
+ /.least)
+ (/.value? /.least)
+ (/.value? (f.+ f.smallest /.least))
+ (not (/.value? (f.- f.smallest /.least)))))
(_.coverage [/.most]
- (when (/.value (f.- +0.001 (/.number /.most)))
- {try.#Failure _} false
- {try.#Success _} true))
- (_.coverage [/.invalid]
- (and (when (/.value (f.- +0.001 (/.number /.least)))
- {try.#Failure it} (exception.match? /.invalid it)
- {try.#Success _} false)
- (when (/.value (f.+ +0.001 (/.number /.most)))
- {try.#Failure it} (exception.match? /.invalid it)
- {try.#Success _} false)))
+ (and (f.> /.least
+ /.most)
+ (/.value? /.most)
+ (/.value? (f.- f.smallest /.most))
+ (not (/.value? (f.+ f.smallest /.most)))))
))
(_.for [/.CMYK
/.#cyan /.#magenta /.#yellow /.#key]
@@ -81,10 +83,10 @@
(and (|> expected_rgb
/.cmyk
/.rgb
- (at rgb.equivalence = expected_rgb))
+ (of rgb.equivalence = expected_rgb))
(|> expected_cmyk
/.rgb
/.cmyk
- (at /.equivalence = expected_cmyk))))
+ (of /.equivalence = expected_cmyk))))
))
)))
diff --git a/stdlib/source/test/lux/data/color/hsb.lux b/stdlib/source/test/lux/data/color/hsb.lux
index 16f6d9dfb..2cb41fe7c 100644
--- a/stdlib/source/test/lux/data/color/hsb.lux
+++ b/stdlib/source/test/lux/data/color/hsb.lux
@@ -74,15 +74,15 @@
(_.coverage [/.hsb
/.hue /.saturation /.brightness]
(|> (/.hsb (/.hue expected_hsb) (/.saturation expected_hsb) (/.brightness expected_hsb))
- (at /.equivalence = expected_hsb)))
+ (of /.equivalence = expected_hsb)))
(_.coverage [/.of_rgb /.rgb]
(and (|> expected_rgb
/.of_rgb
/.rgb
- (at rgb.equivalence = expected_rgb))
+ (of rgb.equivalence = expected_rgb))
(|> expected_hsb
/.rgb
/.of_rgb
- (at /.equivalence = expected_hsb))))
+ (of /.equivalence = expected_hsb))))
))
)))
diff --git a/stdlib/source/test/lux/data/color/hsl.lux b/stdlib/source/test/lux/data/color/hsl.lux
index a0524d2b1..72782e0f2 100644
--- a/stdlib/source/test/lux/data/color/hsl.lux
+++ b/stdlib/source/test/lux/data/color/hsl.lux
@@ -74,15 +74,15 @@
(_.coverage [/.hsl
/.hue /.saturation /.luminance]
(|> (/.hsl (/.hue expected_hsl) (/.saturation expected_hsl) (/.luminance expected_hsl))
- (at /.equivalence = expected_hsl)))
+ (of /.equivalence = expected_hsl)))
(_.coverage [/.of_rgb /.rgb]
(and (|> expected_rgb
/.of_rgb
/.rgb
- (at rgb.equivalence = expected_rgb))
+ (of rgb.equivalence = expected_rgb))
(|> expected_hsl
/.rgb
/.of_rgb
- (at /.equivalence = expected_hsl))))
+ (of /.equivalence = expected_hsl))))
))
)))
diff --git a/stdlib/source/test/lux/data/color/named.lux b/stdlib/source/test/lux/data/color/named.lux
index 4a9a633c9..cb1201c74 100644
--- a/stdlib/source/test/lux/data/color/named.lux
+++ b/stdlib/source/test/lux/data/color/named.lux
@@ -219,7 +219,7 @@
(def .public random
(Random //.Color)
(do [! random.monad]
- [choice (at ! each (n.% (set.size ..unique_colors))
+ [choice (of ! each (n.% (set.size ..unique_colors))
random.nat)]
(in (maybe.trusted (list.item choice ..all_colors)))))
@@ -244,8 +244,8 @@
<colors>))
(_.coverage [/.aqua]
- (at //.equivalence = /.cyan /.aqua))
+ (of //.equivalence = /.cyan /.aqua))
(_.coverage [/.fuchsia]
- (at //.equivalence = /.magenta /.fuchsia))
+ (of //.equivalence = /.magenta /.fuchsia))
))))
)
diff --git a/stdlib/source/test/lux/data/color/pigment.lux b/stdlib/source/test/lux/data/color/pigment.lux
new file mode 100644
index 000000000..b1798e438
--- /dev/null
+++ b/stdlib/source/test/lux/data/color/pigment.lux
@@ -0,0 +1,34 @@
+(.require
+ [library
+ [lux (.except)
+ [abstract
+ [monad (.only do)]]
+ [math
+ ["[0]" random (.only Random)]
+ [number
+ ["r" rev]]]
+ [test
+ ["_" property (.only Test)]]]]
+ [\\library
+ ["[0]" /]])
+
+(def .public test
+ Test
+ (<| (_.covering /._)
+ (do [! random.monad]
+ [alpha random.rev])
+ (_.for [/.Alpha /.Pigment])
+ (all _.and
+ (_.coverage [/.transparent]
+ (and (not (r.< /.transparent alpha))
+ (|> alpha
+ (r.+ /.transparent)
+ (r.= alpha))))
+ (_.coverage [/.opaque]
+ (not (r.> /.opaque alpha)))
+ (_.coverage [/.translucent]
+ (and (r.< /.opaque /.translucent)
+ (r.> /.transparent /.translucent)
+ (r.= /.transparent
+ (r.+ /.translucent /.translucent))))
+ )))
diff --git a/stdlib/source/test/lux/data/color/rgb.lux b/stdlib/source/test/lux/data/color/rgb.lux
index c0d329631..a1899e63c 100644
--- a/stdlib/source/test/lux/data/color/rgb.lux
+++ b/stdlib/source/test/lux/data/color/rgb.lux
@@ -123,7 +123,7 @@
(and (not (/#= expected ~expected))
(/#= expected (/.complement ~expected)))))
(_.coverage [/.black /.white]
- (and (at /.equivalence = /.white (/.complement /.black))
- (at /.equivalence = /.black (/.complement /.white))))
+ (and (of /.equivalence = /.white (/.complement /.black))
+ (of /.equivalence = /.black (/.complement /.white))))
))
)))
diff --git a/stdlib/source/test/lux/data/color/terminal.lux b/stdlib/source/test/lux/data/color/terminal.lux
index a22173fbf..9b734041d 100644
--- a/stdlib/source/test/lux/data/color/terminal.lux
+++ b/stdlib/source/test/lux/data/color/terminal.lux
@@ -83,7 +83,7 @@
(and (text.contains? expected_text it)
(not (text#= expected_text it)))))
(_.coverage [/.foreground /.background]
- (not (at /.equivalence =
+ (not (of /.equivalence =
(/.foreground color)
(/.background color))))
(`` (_.coverage [(,, (with_template [<command>]
@@ -96,7 +96,7 @@
true
{.#Item head tail}
- (and (list.every? (|>> (at /.equivalence = head) not) tail)
+ (and (list.every? (|>> (of /.equivalence = head) not) tail)
(again tail))))))
)))
)
diff --git a/stdlib/source/test/lux/data/format/json.lux b/stdlib/source/test/lux/data/format/json.lux
index caabbe222..60140bae6 100644
--- a/stdlib/source/test/lux/data/format/json.lux
+++ b/stdlib/source/test/lux/data/format/json.lux
@@ -72,23 +72,23 @@
(_.for [\\parser.Parser])
(`` (all _.and
(do [! random.monad]
- [expected (at ! each (|>> {/.#String}) (random.unicode 1))]
+ [expected (of ! each (|>> {/.#String}) (random.unicode 1))]
(_.coverage [\\parser.result \\parser.any]
(|> (\\parser.result \\parser.any expected)
(!expect (^.multi {try.#Success actual}
- (at /.equivalence = expected actual))))))
+ (of /.equivalence = expected actual))))))
(_.coverage [\\parser.null]
(|> (\\parser.result \\parser.null {/.#Null})
(!expect {try.#Success _})))
(,, (with_template [<query> <test> <check> <random> <json> <equivalence>]
[(do [! random.monad]
[expected <random>
- dummy (|> <random> (random.only (|>> (at <equivalence> = expected) not)))]
+ dummy (|> <random> (random.only (|>> (of <equivalence> = expected) not)))]
(all _.and
(_.coverage [<query>]
(|> (\\parser.result <query> {<json> expected})
(!expect (^.multi {try.#Success actual}
- (at <equivalence> = expected actual)))))
+ (of <equivalence> = expected actual)))))
(_.coverage [<test>]
(and (|> (\\parser.result (<test> expected) {<json> expected})
(!expect {try.#Success .true}))
@@ -113,7 +113,7 @@
(exception.match? \\parser.unexpected_value error))))))
(do [! random.monad]
[expected (random.unicode 1)
- dummy (|> (random.unicode 1) (random.only (|>> (at text.equivalence = expected) not)))]
+ dummy (|> (random.unicode 1) (random.only (|>> (of text.equivalence = expected) not)))]
(_.coverage [\\parser.value_mismatch]
(|> (\\parser.result (\\parser.this_string expected) {/.#String dummy})
(!expect (^.multi {try.#Failure error}
@@ -123,22 +123,22 @@
(_.coverage [\\parser.nullable]
(and (|> (\\parser.result (\\parser.nullable \\parser.string) {/.#Null})
(!expect (^.multi {try.#Success actual}
- (at (maybe.equivalence text.equivalence) = {.#None} actual))))
+ (of (maybe.equivalence text.equivalence) = {.#None} actual))))
(|> (\\parser.result (\\parser.nullable \\parser.string) {/.#String expected})
(!expect (^.multi {try.#Success actual}
- (at (maybe.equivalence text.equivalence) = {.#Some expected} actual)))))))
+ (of (maybe.equivalence text.equivalence) = {.#Some expected} actual)))))))
(do [! random.monad]
- [size (at ! each (n.% 10) random.nat)
+ [size (of ! each (n.% 10) random.nat)
expected (|> (random.unicode 1)
(random.list size)
- (at ! each sequence.of_list))]
+ (of ! each sequence.of_list))]
(_.coverage [\\parser.array]
(|> (\\parser.result (\\parser.array (<>.some \\parser.string))
{/.#Array (sequence#each (|>> {/.#String}) expected)})
(!expect (^.multi {try.#Success actual}
- (at (sequence.equivalence text.equivalence) = expected (sequence.of_list actual)))))))
+ (of (sequence.equivalence text.equivalence) = expected (sequence.of_list actual)))))))
(do [! random.monad]
- [expected (at ! each (|>> {/.#String}) (random.unicode 1))]
+ [expected (of ! each (|>> {/.#String}) (random.unicode 1))]
(_.coverage [\\parser.unconsumed_input]
(|> (\\parser.result (\\parser.array \\parser.any) {/.#Array (sequence expected expected)})
(!expect (^.multi {try.#Failure error}
@@ -152,7 +152,7 @@
expected_number ..safe_frac
expected_string (random.unicode 1)
[boolean_field number_field string_field] (|> (random.set text.hash 3 (random.unicode 3))
- (at ! each (|>> set.list
+ (of ! each (|>> set.list
(pipe.when
(list boolean_field number_field string_field)
[boolean_field number_field string_field]
@@ -170,11 +170,11 @@
[number_field {/.#Number expected_number}]
[string_field {/.#String expected_string}]))})
(!expect (^.multi {try.#Success [actual_boolean actual_number actual_string]}
- (and (at bit.equivalence = expected_boolean actual_boolean)
- (at frac.equivalence = expected_number actual_number)
- (at text.equivalence = expected_string actual_string)))))))
+ (and (of bit.equivalence = expected_boolean actual_boolean)
+ (of frac.equivalence = expected_number actual_number)
+ (of text.equivalence = expected_string actual_string)))))))
(do [! random.monad]
- [size (at ! each (n.% 10) random.nat)
+ [size (of ! each (n.% 10) random.nat)
keys (random.list size (random.unicode 1))
values (random.list size (random.unicode 1))
.let [expected (dictionary.of_list text.hash (list.zipped_2 keys values))]]
@@ -186,7 +186,7 @@
(list.zipped_2 keys)
(dictionary.of_list text.hash))})
(!expect (^.multi {try.#Success actual}
- (at (dictionary.equivalence text.equivalence) = expected actual))))))
+ (of (dictionary.equivalence text.equivalence) = expected actual))))))
))))
(type Variant
@@ -227,12 +227,12 @@
(def measure
(All (_ unit) (Random (unit.Measure unit)))
- (at random.monad each unit.measure random.int))
+ (of random.monad each unit.measure random.int))
(def gen_record
(Random Record)
(do [! random.monad]
- [size (at ! each (n.% 2) random.nat)]
+ [size (of ! each (n.% 2) random.nat)]
(all random.and
random.bit
random.safe_frac
@@ -270,9 +270,9 @@
(random.rec
(function (_ again)
(do [! random.monad]
- [size (at ! each (n.% 2) random.nat)]
+ [size (of ! each (n.% 2) random.nat)]
(all random.or
- (at ! in [])
+ (of ! in [])
random.bit
random.safe_frac
(random.unicode size)
@@ -319,7 +319,7 @@
(random#in [text.double_quote text.double_quote])
(random#in ["\" "\\"])
(do [! random.monad]
- [char (at ! each (i64.and (hex "FF"))
+ [char (of ! each (i64.and (hex "FF"))
random.nat)]
(in [(text.of_char char)
(format "\u" (digits/4 char))]))
@@ -349,16 +349,16 @@
[expected escaped] any_string]
(_.coverage [/.#String]
(|> {/.#String escaped}
- (at /.codec encoded)
- (at /.codec decoded)
- (try#each (at /.equivalence = {/.#String expected}))
+ (of /.codec encoded)
+ (of /.codec decoded)
+ (try#each (of /.equivalence = {/.#String expected}))
(try.else false))))
))
(do random.monad
[sample ..random]
(_.coverage [/.Null /.#Null /.null?]
- (at bit.equivalence =
+ (of bit.equivalence =
(/.null? sample)
(when sample
{/.#Null} true
@@ -368,7 +368,7 @@
(_.coverage [/.format]
(|> expected
/.format
- (at /.codec decoded)
+ (of /.codec decoded)
(try#each (/#= expected))
(try.else false))))
(do random.monad
@@ -381,7 +381,7 @@
(_.coverage [/.object /.fields]
(when (/.fields object)
{try.#Success actual}
- (at (list.equivalence text.equivalence) =
+ (of (list.equivalence text.equivalence) =
(list#each product.left expected)
actual)
@@ -396,7 +396,7 @@
))
(do random.monad
[key (random.alphabetic 1)
- unknown (random.only (|>> (at text.equivalence = key) not)
+ unknown (random.only (|>> (of text.equivalence = key) not)
(random.alphabetic 1))
expected random.safe_frac]
(_.coverage [/.has]
@@ -425,7 +425,7 @@
(_.coverage [<type> <tag> <field>]
(|> (/.object (list [key {<tag> value}]))
(<field> key)
- (try#each (at <equivalence> = value))
+ (try#each (of <equivalence> = value))
(try.else false))))]
[/.Boolean /.boolean_field /.#Boolean random.bit bit.equivalence]
diff --git a/stdlib/source/test/lux/data/format/tar.lux b/stdlib/source/test/lux/data/format/tar.lux
index 01f8648c1..f5133d4e5 100644
--- a/stdlib/source/test/lux/data/format/tar.lux
+++ b/stdlib/source/test/lux/data/format/tar.lux
@@ -109,8 +109,8 @@
Test
(_.for [/.Small]
(do [! random.monad]
- [expected (|> random.nat (at ! each (n.% /.small_limit)))
- invalid (|> random.nat (at ! each (n.max /.small_limit)))]
+ [expected (|> random.nat (of ! each (n.% /.small_limit)))
+ invalid (|> random.nat (of ! each (n.max /.small_limit)))]
(`` (all _.and
(_.coverage [/.small /.from_small]
(when (/.small expected)
@@ -133,8 +133,8 @@
Test
(_.for [/.Big]
(do [! random.monad]
- [expected (|> random.nat (at ! each (n.% /.big_limit)))
- invalid (|> random.nat (at ! each (n.max /.big_limit)))]
+ [expected (|> random.nat (of ! each (n.% /.big_limit)))
+ invalid (|> random.nat (of ! each (n.max /.big_limit)))]
(`` (all _.and
(_.coverage [/.big /.from_big]
(when (/.big expected)
@@ -159,14 +159,14 @@
Test
(do [! random.monad]
[expected_path (random.lower_cased (-- /.path_size))
- expected_moment (at ! each (|>> (n.% 1,0,00,00,00,00,000) .int instant.of_millis)
+ expected_moment (of ! each (|>> (n.% 1,0,00,00,00,00,000) .int instant.of_millis)
random.nat)
chunk (random.lower_cased chunk_size)
- chunks (at ! each (n.% 100) random.nat)
+ chunks (of ! each (n.% 100) random.nat)
.let [content (|> chunk
(list.repeated chunks)
text.together
- (at utf8.codec encoded))]]
+ (of utf8.codec encoded))]]
(`` (all _.and
(,, (with_template [<type> <tag>]
[(_.coverage [<type>]
@@ -403,7 +403,7 @@
(|> sequence.empty
(\\format.result /.format)
(<b>.result /.parser)
- (at try.monad each sequence.empty?)
+ (of try.monad each sequence.empty?)
(try.else false)))
(_.coverage [/.invalid_end_of_archive]
(let [dump (\\format.result /.format sequence.empty)]
diff --git a/stdlib/source/test/lux/data/format/xml.lux b/stdlib/source/test/lux/data/format/xml.lux
index 653027509..644064c47 100644
--- a/stdlib/source/test/lux/data/format/xml.lux
+++ b/stdlib/source/test/lux/data/format/xml.lux
@@ -78,7 +78,7 @@
[[(<>#in expected)
{/.#Text expected}]])
(do [! random.monad]
- [expected (at ! each (|>> {/.#Text}) (random.alphabetic 1))]
+ [expected (of ! each (|>> {/.#Text}) (random.alphabetic 1))]
(_.coverage [\\parser.any]
(|> (\\parser.result \\parser.any (list expected))
(try#each (/#= expected))
@@ -168,7 +168,7 @@
(<>#in []))
_ (<>.some \\parser.any)]
(in [])))]
- repetitions (at ! each (n.% 10) random.nat)]
+ repetitions (of ! each (n.% 10) random.nat)]
(all _.and
(_.coverage [\\parser.somewhere]
(|> (\\parser.result parser
@@ -195,7 +195,7 @@
(def char
(Random Nat)
(do [! random.monad]
- [idx (|> random.nat (at ! each (n.% (text.size char_range))))]
+ [idx (|> random.nat (of ! each (n.% (text.size char_range))))]
(in (maybe.trusted (text.char idx char_range)))))
(def (size bottom top)
diff --git a/stdlib/source/test/lux/data/product.lux b/stdlib/source/test/lux/data/product.lux
index af76cff0c..458264a0f 100644
--- a/stdlib/source/test/lux/data/product.lux
+++ b/stdlib/source/test/lux/data/product.lux
@@ -33,9 +33,9 @@
right random.nat]
(_.coverage [/.hash]
(let [hash (/.hash i.hash n.hash)]
- (n.= (n.+ (at i.hash hash left)
- (at n.hash hash right))
- (at hash hash [left right])))))
+ (n.= (n.+ (of i.hash hash left)
+ (of n.hash hash right))
+ (of hash hash [left right])))))
(<| (_.coverage [/.left])
(n.= expected (/.left [expected dummy])))
diff --git a/stdlib/source/test/lux/data/sum.lux b/stdlib/source/test/lux/data/sum.lux
index b0956f5ba..ead537253 100644
--- a/stdlib/source/test/lux/data/sum.lux
+++ b/stdlib/source/test/lux/data/sum.lux
@@ -68,25 +68,25 @@
(/.then (n.+ shift) (n.- shift))
(pipe.when {0 #1 actual} (n.= (n.- shift expected) actual) _ false))))
(do !
- [size (at ! each (n.% 5) random.nat)
+ [size (of ! each (n.% 5) random.nat)
expected (random.list size random.nat)]
(all _.and
(_.coverage [/.lefts]
(let [actual (is (List (Or Nat Nat))
(list#each /.left expected))]
- (and (at (list.equivalence n.equivalence) =
+ (and (of (list.equivalence n.equivalence) =
expected
(/.lefts actual))
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list)
(/.rights actual)))))
(_.coverage [/.rights]
(let [actual (is (List (Or Nat Nat))
(list#each /.right expected))]
- (and (at (list.equivalence n.equivalence) =
+ (and (of (list.equivalence n.equivalence) =
expected
(/.rights actual))
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list)
(/.lefts actual)))))
(_.coverage [/.partition]
@@ -97,10 +97,10 @@
(/.right value))))
(is (List (Or Nat Nat)))
/.partition)]
- (and (at (list.equivalence n.equivalence) =
+ (and (of (list.equivalence n.equivalence) =
(list.only n.even? expected)
lefts)
- (at (list.equivalence n.equivalence) =
+ (of (list.equivalence n.equivalence) =
(list.only (|>> n.even? not) expected)
rights))))
))
diff --git a/stdlib/source/test/lux/data/text.lux b/stdlib/source/test/lux/data/text.lux
index 1ee5a2bf0..dd867436b 100644
--- a/stdlib/source/test/lux/data/text.lux
+++ b/stdlib/source/test/lux/data/text.lux
@@ -106,7 +106,7 @@
[(do random.monad
[sample <random>]
(_.coverage [<format>]
- (/#= (at <codec> encoded sample)
+ (/#= (of <codec> encoded sample)
(<format> sample))))]
[\\format.bit bit.codec random.bit]
@@ -207,10 +207,10 @@
[modulus (random.one (|>> modulus.modulus
try.maybe)
random.int)
- sample (at ! each (modular.modular modulus)
+ sample (of ! each (modular.modular modulus)
random.int)]
(_.coverage [\\format.mod]
- (/#= (at (modular.codec modulus) encoded sample)
+ (/#= (of (modular.codec modulus) encoded sample)
(\\format.mod sample))))
))))
@@ -245,7 +245,7 @@
(-> Text (\\parser.Parser Text) Bit)
(|> expected
(\\parser.result parser)
- (at try.functor each (/#= expected))
+ (of try.functor each (/#= expected))
(try.else false)))
(def (should_pass! expected parser)
@@ -256,13 +256,13 @@
Test
(all _.and
(do [! random.monad]
- [offset (at ! each (nat.% 50) random.nat)
- range (at ! each (|>> (nat.% 50) (nat.+ 10)) random.nat)
+ [offset (of ! each (nat.% 50) random.nat)
+ range (of ! each (|>> (nat.% 50) (nat.+ 10)) random.nat)
.let [limit (nat.+ offset range)]
- expected (at ! each (|>> (nat.% range) (nat.+ offset) /.of_char) random.nat)
+ expected (of ! each (|>> (nat.% range) (nat.+ offset) /.of_char) random.nat)
out_of_range (when offset
- 0 (at ! each (|>> (nat.% 10) ++ (nat.+ limit) /.of_char) random.nat)
- _ (at ! each (|>> (nat.% offset) /.of_char) random.nat))]
+ 0 (of ! each (|>> (nat.% 10) ++ (nat.+ limit) /.of_char) random.nat)
+ _ (of ! each (|>> (nat.% offset) /.of_char) random.nat))]
(_.coverage [\\parser.range]
(and (..should_pass expected (\\parser.range offset limit))
(..should_fail out_of_range (\\parser.range offset limit)))))
@@ -281,22 +281,22 @@
(and (..should_pass (/.of_char expected) \\parser.lower)
(..should_fail (/.of_char invalid) \\parser.lower))))
(do [! random.monad]
- [expected (at ! each (nat.% 10) random.nat)
+ [expected (of ! each (nat.% 10) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [\\parser.decimal]
- (and (..should_pass (at nat.decimal encoded expected) \\parser.decimal)
+ (and (..should_pass (of nat.decimal encoded expected) \\parser.decimal)
(..should_fail (/.of_char invalid) \\parser.decimal))))
(do [! random.monad]
- [expected (at ! each (nat.% 8) random.nat)
+ [expected (of ! each (nat.% 8) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [\\parser.octal]
- (and (..should_pass (at nat.octal encoded expected) \\parser.octal)
+ (and (..should_pass (of nat.octal encoded expected) \\parser.octal)
(..should_fail (/.of_char invalid) \\parser.octal))))
(do [! random.monad]
- [expected (at ! each (nat.% 16) random.nat)
+ [expected (of ! each (nat.% 16) random.nat)
invalid (random.char (unicode.set [unicode/block.number_forms (list)]))]
(_.coverage [\\parser.hexadecimal]
- (and (..should_pass (at nat.hex encoded expected) \\parser.hexadecimal)
+ (and (..should_pass (of nat.hex encoded expected) \\parser.hexadecimal)
(..should_fail (/.of_char invalid) \\parser.hexadecimal))))
(do [! random.monad]
[expected (random.char unicode.alphabetic)
@@ -339,10 +339,10 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set nat.hash num_options)
- (at ! each (|>> set.list
+ (of ! each (|>> set.list
(list#each /.of_char)
/.together)))
- expected (at ! each (function (_ value)
+ expected (of ! each (function (_ value)
(|> options
(/.char (nat.% num_options value))
maybe.trusted))
@@ -365,10 +365,10 @@
[.let [num_options 3]
options (|> (random.char unicode.character)
(random.set nat.hash num_options)
- (at ! each (|>> set.list
+ (of ! each (|>> set.list
(list#each /.of_char)
/.together)))
- invalid (at ! each (function (_ value)
+ invalid (of ! each (function (_ value)
(|> options
(/.char (nat.% num_options value))
maybe.trusted))
@@ -394,26 +394,26 @@
(let [octal! (\\parser.one_of! "01234567")]
(all _.and
(do [! random.monad]
- [left (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)
- right (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)
+ [left (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)
+ right (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)
.let [expected (\\format.format left right)]
invalid (|> random.nat
- (at ! each (nat.% 16))
+ (of ! each (nat.% 16))
(random.only (nat.>= 8))
- (at ! each (at nat.hex encoded)))]
+ (of ! each (of nat.hex encoded)))]
(_.coverage [\\parser.many \\parser.many!]
(and (..should_pass expected (\\parser.many \\parser.octal))
(..should_fail invalid (\\parser.many \\parser.octal))
(..should_pass! expected (\\parser.many! octal!)))))
(do [! random.monad]
- [left (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)
- right (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)
+ [left (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)
+ right (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)
.let [expected (\\format.format left right)]
invalid (|> random.nat
- (at ! each (nat.% 16))
+ (of ! each (nat.% 16))
(random.only (nat.>= 8))
- (at ! each (at nat.hex encoded)))]
+ (of ! each (of nat.hex encoded)))]
(_.coverage [\\parser.some \\parser.some!]
(and (..should_pass expected (\\parser.some \\parser.octal))
(..should_pass "" (\\parser.some \\parser.octal))
@@ -422,7 +422,7 @@
(..should_pass! expected (\\parser.some! octal!))
(..should_pass! "" (\\parser.some! octal!)))))
(do [! random.monad]
- [.let [octal (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)]
+ [.let [octal (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -435,7 +435,7 @@
(..should_fail (\\format.format first second third) (\\parser.exactly! 2 octal!))
(..should_fail (\\format.format first) (\\parser.exactly! 2 octal!)))))
(do [! random.monad]
- [.let [octal (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)]
+ [.let [octal (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -448,7 +448,7 @@
(..should_pass! (\\format.format first) (\\parser.at_most! 2 octal!))
(..should_fail (\\format.format first second third) (\\parser.at_most! 2 octal!)))))
(do [! random.monad]
- [.let [octal (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)]
+ [.let [octal (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -461,7 +461,7 @@
(..should_pass! (\\format.format first second third) (\\parser.at_least! 2 octal!))
(..should_fail (\\format.format first) (\\parser.at_least! 2 octal!)))))
(do [! random.monad]
- [.let [octal (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)]
+ [.let [octal (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)]
first octal
second octal
third octal]
@@ -573,7 +573,7 @@
(\\parser.this output)))
(!expect {try.#Success _}))))
(do [! random.monad]
- [expected (at ! each (|>> (nat.% 8) (at nat.octal encoded)) random.nat)]
+ [expected (of ! each (|>> (nat.% 8) (of nat.octal encoded)) random.nat)]
(_.coverage [\\parser.then]
(|> (list (code.text expected))
(<code>.result (\\parser.then \\parser.octal <code>.text))
@@ -629,12 +629,12 @@
(def bounded_size
(random.Random Nat)
(|> random.nat
- (at random.monad each (|>> (nat.% 20) (nat.+ 1)))))
+ (of random.monad each (|>> (nat.% 20) (nat.+ 1)))))
(def size
Test
(do [! random.monad]
- [size (at ! each (nat.% 10) random.nat)
+ [size (of ! each (nat.% 10) random.nat)
sample (random.unicode size)]
(all _.and
(_.coverage [/.size]
@@ -647,11 +647,11 @@
Test
(do [! random.monad]
[inner (random.unicode 1)
- outer (random.only (|>> (at /.equivalence = inner) not)
+ outer (random.only (|>> (of /.equivalence = inner) not)
(random.unicode 1))
left (random.unicode 1)
right (random.unicode 1)
- .let [full (at /.monoid composite inner outer)
+ .let [full (of /.monoid composite inner outer)
fake_index (-- 0)]]
(`` (all _.and
(,, (with_template [<affix> <predicate>]
@@ -676,23 +676,23 @@
Test
(do [! random.monad]
[inner (random.unicode 1)
- outer (random.only (|>> (at /.equivalence = inner) not)
+ outer (random.only (|>> (of /.equivalence = inner) not)
(random.unicode 1))
.let [fake_index (-- 0)]]
(all _.and
(_.coverage [/.contains?]
- (let [full (at /.monoid composite inner outer)]
+ (let [full (of /.monoid composite inner outer)]
(and (/.contains? inner full)
(/.contains? outer full))))
(_.coverage [/.index]
- (and (|> (/.index inner (at /.monoid composite inner outer))
+ (and (|> (/.index inner (of /.monoid composite inner outer))
(maybe.else fake_index)
(nat.= 0))
- (|> (/.index outer (at /.monoid composite inner outer))
+ (|> (/.index outer (of /.monoid composite inner outer))
(maybe.else fake_index)
(nat.= 1))))
(_.coverage [/.index_since]
- (let [full (at /.monoid composite inner outer)]
+ (let [full (of /.monoid composite inner outer)]
(and (|> (/.index_since 0 inner full)
(maybe.else fake_index)
(nat.= 0))
@@ -710,7 +710,7 @@
(maybe.else fake_index)
(nat.= fake_index)))))
(_.coverage [/.last_index]
- (let [full (all (at /.monoid composite) outer inner outer)]
+ (let [full (all (of /.monoid composite) outer inner outer)]
(and (|> (/.last_index inner full)
(maybe.else fake_index)
(nat.= 1))
@@ -726,7 +726,7 @@
(`` (all _.and
(,, (with_template [<short> <long>]
[(_.coverage [<short> <long>]
- (at /.equivalence = <short> <long>))]
+ (of /.equivalence = <short> <long>))]
[/.\0 /.null]
[/.\a /.alarm]
@@ -738,13 +738,13 @@
[/.\r /.carriage_return]
[/.\'' /.double_quote]))
(_.coverage [/.line_feed]
- (at /.equivalence = /.new_line /.line_feed))
+ (of /.equivalence = /.new_line /.line_feed))
)))
(do [! random.monad]
- [size (at ! each (|>> (nat.% 10) ++) random.nat)
+ [size (of ! each (|>> (nat.% 10) ++) random.nat)
characters (random.set /.hash size (random.alphabetic 1))
.let [sample (|> characters set.list /.together)]
- expected (at ! each (nat.% size) random.nat)]
+ expected (of ! each (nat.% size) random.nat)]
(_.coverage [/.char]
(when (/.char expected sample)
{.#Some char}
@@ -773,13 +773,13 @@
(def manipulation
Test
(do [! random.monad]
- [size (at ! each (|>> (nat.% 10) (nat.+ 2)) random.nat)
+ [size (of ! each (|>> (nat.% 10) (nat.+ 2)) random.nat)
characters (random.set /.hash size (random.alphabetic 1))
separator (random.only (|>> (set.member? characters) not)
(random.alphabetic 1))
.let [with_no_separator (|> characters set.list /.together)]
static (random.alphabetic 1)
- .let [dynamic (random.only (|>> (at /.equivalence = static) not)
+ .let [dynamic (random.only (|>> (of /.equivalence = static) not)
(random.alphabetic 1))]
pre dynamic
post dynamic
@@ -795,19 +795,19 @@
(/.interposed separator)
(/.all_split_by separator)
(set.of_list /.hash)
- (at set.equivalence = characters))
- (at /.equivalence =
+ (of set.equivalence = characters))
+ (of /.equivalence =
(/.together (set.list characters))
(/.interposed "" (set.list characters)))))
(_.coverage [/.replaced_once]
- (at /.equivalence =
- (at /.monoid composite post static)
- (/.replaced_once pre post (at /.monoid composite pre static))))
+ (of /.equivalence =
+ (of /.monoid composite post static)
+ (/.replaced_once pre post (of /.monoid composite pre static))))
(_.coverage [/.split_by]
- (when (/.split_by static (all (at /.monoid composite) pre static post))
+ (when (/.split_by static (all (of /.monoid composite) pre static post))
{.#Some [left right]}
- (and (at /.equivalence = pre left)
- (at /.equivalence = post right))
+ (and (of /.equivalence = pre left)
+ (of /.equivalence = post right))
{.#None}
false))
@@ -815,19 +815,19 @@
(let [effectiveness!
(|> upper
/.lower_cased
- (at /.equivalence = upper)
+ (of /.equivalence = upper)
not)
idempotence!
(|> lower
/.lower_cased
- (at /.equivalence = lower))
+ (of /.equivalence = lower))
inverse!
(|> lower
/.upper_cased
/.lower_cased
- (at /.equivalence = lower))]
+ (of /.equivalence = lower))]
(and effectiveness!
idempotence!
inverse!)))
@@ -835,19 +835,19 @@
(let [effectiveness!
(|> lower
/.upper_cased
- (at /.equivalence = lower)
+ (of /.equivalence = lower)
not)
idempotence!
(|> upper
/.upper_cased
- (at /.equivalence = upper))
+ (of /.equivalence = upper))
inverse!
(|> upper
/.lower_cased
/.upper_cased
- (at /.equivalence = upper))]
+ (of /.equivalence = upper))]
(and effectiveness!
idempotence!
inverse!)))
@@ -913,7 +913,7 @@
.let [... The wider unicode charset includes control characters that
... can make text replacement work improperly.
... Because of that, I restrict the charset.
- normal_char_gen (|> random.nat (at ! each (|>> (nat.% 128) (nat.max 1))))]
+ normal_char_gen (|> random.nat (of ! each (|>> (nat.% 128) (nat.max 1))))]
sep1 (random.text normal_char_gen 1)
sep2 (random.text normal_char_gen 1)
.let [part_gen (|> (random.text normal_char_gen sizeP)
diff --git a/stdlib/source/test/lux/data/text/buffer.lux b/stdlib/source/test/lux/data/text/buffer.lux
index 54f74359c..adf184d8f 100644
--- a/stdlib/source/test/lux/data/text/buffer.lux
+++ b/stdlib/source/test/lux/data/text/buffer.lux
@@ -18,7 +18,7 @@
(def part
(Random Text)
(do [! random.monad]
- [size (at ! each (|>> (n.% 10) ++) random.nat)]
+ [size (of ! each (|>> (n.% 10) ++) random.nat)]
(random.alphabetic size)))
(def .public test
diff --git a/stdlib/source/test/lux/data/text/encoding.lux b/stdlib/source/test/lux/data/text/encoding.lux
index 2e5b0fad9..e573de1d3 100644
--- a/stdlib/source/test/lux/data/text/encoding.lux
+++ b/stdlib/source/test/lux/data/text/encoding.lux
@@ -216,7 +216,7 @@
(Random /.Encoding)
(let [options (list.size ..all_encodings)]
(do [! random.monad]
- [choice (at ! each (n.% options) random.nat)]
+ [choice (of ! each (n.% options) random.nat)]
(in (maybe.trusted (list.item choice ..all_encodings))))))
(def .public test
diff --git a/stdlib/source/test/lux/data/text/escape.lux b/stdlib/source/test/lux/data/text/escape.lux
index 82be1dcb4..0ce18a8d8 100644
--- a/stdlib/source/test/lux/data/text/escape.lux
+++ b/stdlib/source/test/lux/data/text/escape.lux
@@ -35,7 +35,7 @@
(def (range max min)
(-> Char Char (Random Char))
(let [range (n.- min max)]
- (at random.monad each
+ (of random.monad each
(|>> (n.% range) (n.+ min))
random.nat)))
@@ -118,7 +118,7 @@
(text#= expected (/.escaped expected))))))
(do [! random.monad]
[dummy (|> (random.char unicode.character)
- (at ! each text.of_char))]
+ (of ! each text.of_char))]
(_.coverage [/.dangling_escape]
(when (/.un_escaped (format (/.escaped dummy) "\"))
{try.#Success _}
@@ -129,7 +129,7 @@
(do [! random.monad]
[dummy (|> (random.char unicode.character)
(random.only (|>> (set.member? ..valid_sigils) not))
- (at ! each text.of_char))]
+ (of ! each text.of_char))]
(_.coverage [/.invalid_escape]
(when (/.un_escaped (format "\" dummy))
{try.#Success _}
@@ -139,10 +139,10 @@
(exception.match? /.invalid_escape error))))
(do [! random.monad]
[too_short (|> (random.char unicode.character)
- (at ! each (n.% (hex "1000"))))
+ (of ! each (n.% (hex "1000"))))
code (|> (random.unicode 4)
(random.only (function (_ code)
- (when (at n.hex decoded code)
+ (when (of n.hex decoded code)
{try.#Failure error} true
{try.#Success _} false))))]
(_.coverage [/.invalid_unicode_escape]
@@ -153,7 +153,7 @@
{try.#Failure error}
(exception.match? /.invalid_unicode_escape error))]]
- (and (!invalid (at n.hex encoded too_short))
+ (and (!invalid (of n.hex encoded too_short))
(!invalid code)))))
(_.coverage [/.literal]
(with_expansions [<example> (..static_sample)]
diff --git a/stdlib/source/test/lux/data/text/unicode/block.lux b/stdlib/source/test/lux/data/text/unicode/block.lux
index 75756fd45..6ea3e3493 100644
--- a/stdlib/source/test/lux/data/text/unicode/block.lux
+++ b/stdlib/source/test/lux/data/text/unicode/block.lux
@@ -27,8 +27,8 @@
(def .public random
(Random /.Block)
(do [! random.monad]
- [start (at ! each (n.% 1,000,000) random.nat)
- additional (at ! each (n.% 1,000,000) random.nat)]
+ [start (of ! each (n.% 1,000,000) random.nat)
+ additional (of ! each (n.% 1,000,000) random.nat)]
(in (/.block start additional))))
(with_expansions [<blocks> (these [blocks/0
@@ -175,12 +175,12 @@
[.let [top_start (hex "AC00")
top_end (hex "D7AF")
end_range (n.- top_start top_end)]
- start (at ! each (|>> (n.% top_start) ++) random.nat)
- end (at ! each (|>> (n.% end_range) (n.+ top_start)) random.nat)
+ start (of ! each (|>> (n.% top_start) ++) random.nat)
+ end (of ! each (|>> (n.% end_range) (n.+ top_start)) random.nat)
.let [additional (n.- start end)
sample (/.block start additional)
size (/.size sample)]
- inside (at ! each
+ inside (of ! each
(|>> (n.% size)
(n.+ (/.start sample)))
random.nat)]
diff --git a/stdlib/source/test/lux/data/text/unicode/set.lux b/stdlib/source/test/lux/data/text/unicode/set.lux
index b5dbad749..1c62d0eda 100644
--- a/stdlib/source/test/lux/data/text/unicode/set.lux
+++ b/stdlib/source/test/lux/data/text/unicode/set.lux
@@ -37,7 +37,7 @@
(_.for [/.Set])
(do [! random.monad]
[block //block.random
- inside (at ! each
+ inside (of ! each
(|>> (n.% (block.size block))
(n.+ (block.start block)))
random.nat)