aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/test/lux/data/format
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/test/lux/data/format')
-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
3 files changed, 41 insertions, 41 deletions
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)