diff options
author | Eduardo Julian | 2022-12-02 19:33:00 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-12-02 19:33:00 -0400 |
commit | 94e5802f594a73245fce0fbd885103b8bf210d57 (patch) | |
tree | 65e5799c0be40f5f015b39bfa6c87c9c27fd9424 /stdlib/source/test/lux/world | |
parent | b491dfff00219d5206075ea65468e00ab657075d (diff) |
Added some simple time-series handling machinery.
Diffstat (limited to '')
29 files changed, 278 insertions, 113 deletions
diff --git a/stdlib/source/test/lux/world/console.lux b/stdlib/source/test/lux/world/console.lux index e4d595dec..7d933d926 100644 --- a/stdlib/source/test/lux/world/console.lux +++ b/stdlib/source/test/lux/world/console.lux @@ -62,7 +62,7 @@ (io.run! (do io.monad [?_ (/.write_line expected console) - ?actual (at console read_line [])] + ?actual (of console read_line [])] (in (<| (try.else false) (do try.monad [_ ?_ diff --git a/stdlib/source/test/lux/world/environment.lux b/stdlib/source/test/lux/world/environment.lux index df434f657..8c2484e7b 100644 --- a/stdlib/source/test/lux/world/environment.lux +++ b/stdlib/source/test/lux/world/environment.lux @@ -40,7 +40,7 @@ [expected random.nat] (_.coverage [\\parser.result] (|> (\\parser.result (//#in expected) \\parser.empty) - (at try.functor each (n.= expected)) + (of try.functor each (n.= expected)) (try.else false)))) (do random.monad [property (random.alphabetic 1) @@ -49,7 +49,7 @@ (|> \\parser.empty (dictionary.has property expected) (\\parser.result (\\parser.property property)) - (at try.functor each (text#= expected)) + (of try.functor each (text#= expected)) (try.else false)))) (do random.monad [property (random.alphabetic 1)] @@ -76,7 +76,7 @@ Test (<| (_.covering /._) (do [! random.monad] - [env_size (at ! each (|>> (n.% 10) ++) random.nat) + [env_size (of ! each (|>> (n.% 10) ++) random.nat) environment (..environment env_size) home ..path directory ..path @@ -102,7 +102,7 @@ (_.coverage [/.unknown_environment_variable] (let [it (/.mock environment home directory)] (|> unknown - (at it variable) + (of it variable) io.run! (pipe.when {try.#Success _} false diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index d2f3cde55..b7ffb5f6c 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -193,7 +193,7 @@ {.#Some {.#Right children}} (|> children (monad.only ! (..file? disk)) - (at ! each (|>> {try.#Success}))) + (of ! each (|>> {try.#Success}))) _ (in {try.#Failure ""})))) @@ -204,7 +204,7 @@ {.#Some {.#Right children}} (|> children (monad.only ! (..directory? disk)) - (at ! each (|>> {try.#Success}))) + (of ! each (|>> {try.#Success}))) _ (in {try.#Failure ""})))) @@ -257,7 +257,7 @@ (in (do async.monad [.let [fs (/.mock /)] - ? (at fs delete file)] + ? (of fs delete file)] (unit.coverage [/.cannot_delete] (when ? {try.#Failure error} @@ -267,7 +267,7 @@ false)))) (in (do async.monad [.let [fs (/.mock /)] - ? (at fs read file)] + ? (of fs read file)] (unit.coverage [/.cannot_find_file] (when ? {try.#Failure error} @@ -277,8 +277,8 @@ false)))) (in (do async.monad [.let [fs (/.mock /)] - ?/0 (at fs directory_files file) - ?/1 (at fs sub_directories file)] + ?/0 (of fs directory_files file) + ?/1 (of fs sub_directories file)] (unit.coverage [/.cannot_find_directory] (when [?/0 ?/1] [{try.#Failure error/0} {try.#Failure error/1}] diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index e8ce8182e..75bcf5a2e 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -74,8 +74,8 @@ .let [[fs watcher] (/.mock "/")]] (all _.and (in (do async.monad - [?concern (at watcher concern directory) - ?stop (at watcher stop directory)] + [?concern (of watcher concern directory) + ?stop (of watcher stop directory)] (unit.coverage [/.not_being_watched] (and (when ?concern {try.#Failure error} @@ -94,18 +94,18 @@ (def (no_events_prior_to_creation! fs watcher directory) (-> (//.System Async) (/.Watcher Async) //.Path (Async (Try Bit))) (do [! (try.with async.monad)] - [_ (at fs make_directory directory) - _ (at watcher start /.all directory)] - (|> (at watcher poll []) - (at ! each list.empty?)))) + [_ (of fs make_directory directory) + _ (of watcher start /.all directory)] + (|> (of watcher poll []) + (of ! each list.empty?)))) (def (after_creation! fs watcher expected_path) (-> (//.System Async) (/.Watcher Async) //.Path (Async (Try Bit))) (do (try.with async.monad) [_ (is (Async (Try Any)) (//.make_file async.monad fs (binary.empty 0) expected_path)) - poll/pre (at watcher poll []) - poll/post (at watcher poll [])] + poll/pre (of watcher poll []) + poll/post (of watcher poll [])] (in (and (when poll/pre (list [concern actual_path]) (and (text#= expected_path actual_path) @@ -121,9 +121,9 @@ (-> (//.System Async) (/.Watcher Async) Binary //.Path (Async (Try Bit))) (do (try.with async.monad) [_ (async.after 1 {try.#Success "Delay to make sure the over_write time-stamp always changes."}) - _ (at fs write expected_path data) - poll/2 (at watcher poll []) - poll/2' (at watcher poll [])] + _ (of fs write expected_path data) + poll/2 (of watcher poll []) + poll/2' (of watcher poll [])] (in (and (when poll/2 (list [concern actual_path]) (and (text#= expected_path actual_path) @@ -138,9 +138,9 @@ (def (after_deletion! fs watcher expected_path) (-> (//.System Async) (/.Watcher Async) //.Path (Async (Try Bit))) (do (try.with async.monad) - [_ (at fs delete expected_path) - poll/3 (at watcher poll []) - poll/3' (at watcher poll [])] + [_ (of fs delete expected_path) + poll/3 (of watcher poll []) + poll/3' (of watcher poll [])] (in (and (when poll/3 (list [concern actual_path]) (and (not (/.creation? concern)) @@ -164,7 +164,7 @@ [directory (random.alphabetic 5) .let [/ "/" [fs watcher] (/.mock /)] - expected_path (at ! each (|>> (format directory /)) + expected_path (of ! each (|>> (format directory /)) (random.alphabetic 5)) data ($binary.random 10)] (in (do [! async.monad] @@ -191,7 +191,7 @@ .let [/ "/" [fs watcher] (/.mock /)]] (in (do async.monad - [started? (at watcher start /.all directory)] + [started? (of watcher start /.all directory)] (unit.coverage [/.cannot_poll_a_non_existent_directory] (when started? {try.#Success _} diff --git a/stdlib/source/test/lux/world/input/keyboard.lux b/stdlib/source/test/lux/world/input/keyboard.lux index d04d4dba0..06330ca69 100644 --- a/stdlib/source/test/lux/world/input/keyboard.lux +++ b/stdlib/source/test/lux/world/input/keyboard.lux @@ -142,7 +142,7 @@ (Random /.Key) (let [count (list.size ..listing)] (do [! random.monad] - [choice (at ! each (n.% count) random.nat)] + [choice (of ! each (n.% count) random.nat)] (in (maybe.trusted (list.item choice ..listing)))))) (def .public test diff --git a/stdlib/source/test/lux/world/locale.lux b/stdlib/source/test/lux/world/locale.lux index f4e8f7919..57ae892a0 100644 --- a/stdlib/source/test/lux/world/locale.lux +++ b/stdlib/source/test/lux/world/locale.lux @@ -60,15 +60,15 @@ fixed_encoding ..random_encoding] (all _.and (|> ..random_language - (at ! each (function (_ language) + (of ! each (function (_ language) (/.locale language {.#Some fixed_territory} {.#Some fixed_encoding}))) ($hash.spec /.hash)) (|> ..random_territory - (at ! each (function (_ territory) + (of ! each (function (_ territory) (/.locale fixed_language {.#Some territory} {.#Some fixed_encoding}))) ($hash.spec /.hash)) (|> ..random_encoding - (at ! each (function (_ encoding) + (of ! each (function (_ encoding) (/.locale fixed_language {.#Some fixed_territory} {.#Some encoding}))) ($hash.spec /.hash)) ))) diff --git a/stdlib/source/test/lux/world/locale/language.lux b/stdlib/source/test/lux/world/locale/language.lux index 8e203a4d9..12020bfe7 100644 --- a/stdlib/source/test/lux/world/locale/language.lux +++ b/stdlib/source/test/lux/world/locale/language.lux @@ -218,7 +218,7 @@ (def !aliases (template (_ <reference> <aliases>) [(_.coverage <aliases> - (list.every? (at /.equivalence = <reference>) + (list.every? (of /.equivalence = <reference>) (`` (list (,, (template.spliced <aliases>))))))])) (def aliases_test/0 @@ -285,7 +285,7 @@ (list#each (|>> (the #languages) set.list)) list.together)] (do [! random.monad] - [choice (at ! each (n.% (list.size options)) + [choice (of ! each (n.% (list.size options)) random.nat)] (in (maybe.trusted (list.item choice options)))))) diff --git a/stdlib/source/test/lux/world/locale/territory.lux b/stdlib/source/test/lux/world/locale/territory.lux index 06ab0b2d5..f39ff6627 100644 --- a/stdlib/source/test/lux/world/locale/territory.lux +++ b/stdlib/source/test/lux/world/locale/territory.lux @@ -175,7 +175,7 @@ (def !aliases (template (_ <reference> <aliases>) [(_.coverage <aliases> - (list.every? (at /.equivalence = <reference>) + (list.every? (of /.equivalence = <reference>) (`` (list (,, (template.spliced <aliases>))))))])) (def aliases_test @@ -211,7 +211,7 @@ (list#each (|>> (the #territories) set.list)) list.together)] (do [! random.monad] - [choice (at ! each (n.% (list.size options)) + [choice (of ! each (n.% (list.size options)) random.nat)] (in (maybe.trusted (list.item choice options)))))) diff --git a/stdlib/source/test/lux/world/logging.lux b/stdlib/source/test/lux/world/logging.lux index f2d56ff15..bcc559448 100644 --- a/stdlib/source/test/lux/world/logging.lux +++ b/stdlib/source/test/lux/world/logging.lux @@ -49,8 +49,8 @@ (let [console (console.async (console.mock ..mock "")) it (/.console console)] (in (do async.monad - [logged? (at it log expected_message) - actual_message (at console read_line [])] + [logged? (of it log expected_message) + actual_message (of console read_line [])] (unit.coverage [/.console /.log] (when [logged? actual_message] [{try.#Success _} @@ -64,7 +64,7 @@ it (/.console console)] (in (do async.monad [logged? (<level> expected_message it) - actual_message (at console read_line [])] + actual_message (of console read_line [])] (unit.coverage [<level>] (when [logged? actual_message] [{try.#Success _} @@ -85,8 +85,8 @@ (/.with (text.suffix expected_appendix) (/.console console)))] (in (do async.monad - [logged? (at it log expected_message) - actual_message (at console read_line [])] + [logged? (of it log expected_message) + actual_message (of console read_line [])] (unit.coverage [/.with] (when [logged? actual_message] [{try.#Success _} @@ -103,8 +103,8 @@ (async#in expected_instant)) (/.console console)))] (in (do async.monad - [logged? (at it log expected_message) - actual_message (at console read_line [])] + [logged? (of it log expected_message) + actual_message (of console read_line [])] (unit.coverage [/.timed] (when [logged? actual_message] [{try.#Success _} diff --git a/stdlib/source/test/lux/world/money.lux b/stdlib/source/test/lux/world/money.lux index dc21b0603..4ebd46bf2 100644 --- a/stdlib/source/test/lux/world/money.lux +++ b/stdlib/source/test/lux/world/money.lux @@ -53,12 +53,12 @@ subject (/.money expected_currency expected_subject)] (and (|> subject (/.+ parameter) - (at /.equivalence = subject) + (of /.equivalence = subject) not) (|> subject (/.+ parameter) (/.- parameter) - (maybe#each (at /.equivalence = subject)) + (maybe#each (of /.equivalence = subject)) (maybe.else false))))) (do ! [it ..random] diff --git a/stdlib/source/test/lux/world/net/http/client.lux b/stdlib/source/test/lux/world/net/http/client.lux index 3eee7b77a..0e4a05fb8 100644 --- a/stdlib/source/test/lux/world/net/http/client.lux +++ b/stdlib/source/test/lux/world/net/http/client.lux @@ -45,10 +45,10 @@ product.right (the //.#body) (function.on {.#None}) - (at ! each (|>> (pipe.do try.monad + (of ! each (|>> (pipe.do try.monad [] - [product.right (at utf8.codec decoded)] - [(at nat.decimal decoded)] + [product.right (of utf8.codec decoded)] + [(of nat.decimal decoded)] [(nat.= expected) in]) (try.else false)))) @@ -69,7 +69,7 @@ on_connect random.nat on_options random.nat on_trace random.nat - num_headers (at ! each (nat.% 10) random.nat) + num_headers (of ! each (nat.% 10) random.nat) headers (random.dictionary text.hash num_headers (random.lower_cased 3) (random.lower_cased 3)) .let [mock (is (/.Client IO) (implementation @@ -85,8 +85,8 @@ {//.#Options} on_options {//.#Trace} on_trace) data (|> value - (at nat.decimal encoded) - (at utf8.codec encoded))] + (of nat.decimal encoded) + (of utf8.codec encoded))] {try.#Success [//status.ok [//.#headers headers //.#body (function (_ ?wanted_bytes) diff --git a/stdlib/source/test/lux/world/net/http/header.lux b/stdlib/source/test/lux/world/net/http/header.lux index 7302fd653..1baa300af 100644 --- a/stdlib/source/test/lux/world/net/http/header.lux +++ b/stdlib/source/test/lux/world/net/http/header.lux @@ -85,6 +85,6 @@ (|> /.empty (/.has /.set_cookies expected_jar) (/.one /.set_cookies) - (try#each (at cookie.equivalence = expected_jar)) + (try#each (of cookie.equivalence = expected_jar)) (try.else false)))) ))) diff --git a/stdlib/source/test/lux/world/net/http/response.lux b/stdlib/source/test/lux/world/net/http/response.lux index bdefd87c2..4e4e0baac 100644 --- a/stdlib/source/test/lux/world/net/http/response.lux +++ b/stdlib/source/test/lux/world/net/http/response.lux @@ -50,11 +50,11 @@ [expected_status statusT.random expected_mime mimeT.random - utf8_length (at ! each (n.% 10) random.nat) + utf8_length (of ! each (n.% 10) random.nat) utf8 (random.upper_cased utf8_length) .let [utf8_data (utf8#encoded utf8)] - expected_url (at ! each (text.prefix "http://www.example.com/") + expected_url (of ! each (text.prefix "http://www.example.com/") (random.upper_cased 1)) .let [expected_html (html.html/5 diff --git a/stdlib/source/test/lux/world/net/http/server.lux b/stdlib/source/test/lux/world/net/http/server.lux index 92f57b953..a78a5f345 100644 --- a/stdlib/source/test/lux/world/net/http/server.lux +++ b/stdlib/source/test/lux/world/net/http/server.lux @@ -99,7 +99,7 @@ (all random.and (random#in header.empty) (random#in (function (_ _) - (at ! in {try.#Success [(binary.size body) body]}))) + (of ! in {try.#Success [(binary.size body) body]}))) )) (def data @@ -131,7 +131,7 @@ [expected_data_size expected_data] ..data .let [expected_server (is /.Server (function (_ ! request) - (at ! in (response.content ! expected_status expected_mime expected_data))))]]) + (of ! in (response.content ! expected_status expected_mime expected_data))))]]) (`` (all _.and (,, (with_template [<server> <scheme>] [(in (do [! async.monad] @@ -170,7 +170,7 @@ [expected_data_size expected_data] ..data .let [expected_server (is /.Server (function (_ ! request) - (at ! in (response.content ! expected_status expected_mime expected_data))))]]) + (of ! in (response.content ! expected_status expected_mime expected_data))))]]) (`` (all _.and (,, (with_template [<server> <correct_method> <incorrect_method>] [(in (do [! async.monad] @@ -217,7 +217,7 @@ [expected_data_size expected_data] ..data .let [expected_server (is /.Server (function (_ ! request) - (at ! in (response.content ! expected_status expected_mime expected_data))))]]) + (of ! in (response.content ! expected_status expected_mime expected_data))))]]) (_.for [/.Server]) (`` (all _.and ..scheme_test diff --git a/stdlib/source/test/lux/world/net/http/status.lux b/stdlib/source/test/lux/world/net/http/status.lux index a7cb40039..550e8b0f6 100644 --- a/stdlib/source/test/lux/world/net/http/status.lux +++ b/stdlib/source/test/lux/world/net/http/status.lux @@ -105,7 +105,7 @@ (def .public random (Random /.Status) (do [! random.monad] - [choice (at ! each (n.% (set.size ..unique)) + [choice (of ! each (n.% (set.size ..unique)) random.nat)] (in (maybe.trusted (list.item choice all))))) diff --git a/stdlib/source/test/lux/world/net/mime.lux b/stdlib/source/test/lux/world/net/mime.lux index 3b36e7ecd..30b34affc 100644 --- a/stdlib/source/test/lux/world/net/mime.lux +++ b/stdlib/source/test/lux/world/net/mime.lux @@ -165,7 +165,7 @@ (|> expected /.name /.mime - (at /.equivalence = expected))) + (of /.equivalence = expected))) <coverages> (_.coverage [/.text] (|> (/.text encoding) diff --git a/stdlib/source/test/lux/world/net/uri/encoding.lux b/stdlib/source/test/lux/world/net/uri/encoding.lux index 0bdb9a7a0..c302dceac 100644 --- a/stdlib/source/test/lux/world/net/uri/encoding.lux +++ b/stdlib/source/test/lux/world/net/uri/encoding.lux @@ -32,8 +32,8 @@ left (random.lower_cased 1) middle (random.lower_cased 1) right (random.lower_cased 1) - left_choice (at ! each (n.% variety) random.nat) - right_choice (at ! each (n.% variety) random.nat) + left_choice (of ! each (n.% variety) random.nat) + right_choice (of ! each (n.% variety) random.nat) .let [left_choice (maybe.trusted (list.item left_choice choices)) right_choice (maybe.trusted (list.item right_choice choices)) unsafe (%.format left diff --git a/stdlib/source/test/lux/world/net/uri/path.lux b/stdlib/source/test/lux/world/net/uri/path.lux index 968fd990c..9ea2e75fe 100644 --- a/stdlib/source/test/lux/world/net/uri/path.lux +++ b/stdlib/source/test/lux/world/net/uri/path.lux @@ -20,7 +20,7 @@ Test (<| (_.covering /._) (do [! random.monad] - [segments (at ! each (n.% 10) random.nat) + [segments (of ! each (n.% 10) random.nat) segments (random.list segments (random.lower_cased 1))]) (_.for [/.Path]) (all _.and diff --git a/stdlib/source/test/lux/world/net/uri/scheme.lux b/stdlib/source/test/lux/world/net/uri/scheme.lux index 4a651646c..66d51ea0d 100644 --- a/stdlib/source/test/lux/world/net/uri/scheme.lux +++ b/stdlib/source/test/lux/world/net/uri/scheme.lux @@ -66,7 +66,7 @@ (|> expected /.name /.scheme - (at /.equivalence = expected))) + (of /.equivalence = expected))) (_.coverage [(,, (with_template [<scheme>] [<scheme>] @@ -83,7 +83,7 @@ (set.size uniques)))) (,, (with_template [<original> <alias>] [(_.coverage [<alias>] - (at /.equivalence = <original> <alias>))] + (of /.equivalence = <original> <alias>))] [/.acap /.application_configuration_access_protocol] diff --git a/stdlib/source/test/lux/world/output/video/resolution.lux b/stdlib/source/test/lux/world/output/video/resolution.lux index c5444497e..4123a0b7d 100644 --- a/stdlib/source/test/lux/world/output/video/resolution.lux +++ b/stdlib/source/test/lux/world/output/video/resolution.lux @@ -48,7 +48,7 @@ (Random /.Resolution) (let [count (list.size ..listing)] (do [! random.monad] - [choice (at ! each (n.% count) random.nat)] + [choice (of ! each (n.% count) random.nat)] (in (maybe.trusted (list.item choice ..listing)))))) (def .public test diff --git a/stdlib/source/test/lux/world/shell.lux b/stdlib/source/test/lux/world/shell.lux index 32e2d3494..03dff9dba 100644 --- a/stdlib/source/test/lux/world/shell.lux +++ b/stdlib/source/test/lux/world/shell.lux @@ -100,11 +100,11 @@ .let [shell (/.async (..io_shell command oops input destruction exit))]] (in (do [! async.monad] [verdict (do (try.with !) - [process (at shell execute [environment.empty "~" command (list)]) - read (at process read []) - failure (at process fail []) + [process (of shell execute [environment.empty "~" command (list)]) + read (of process read []) + failure (of process fail []) wrote! (do ! - [write (at process write input)] + [write (of process write input)] (in {try.#Success (when write {try.#Success _} false @@ -112,14 +112,14 @@ {try.#Failure write} (text#= input write))})) destroyed! (do ! - [destroy (at process destroy [])] + [destroy (of process destroy [])] (in {try.#Success (when destroy {try.#Success _} false {try.#Failure destroy} (text#= destruction destroy))})) - await (at process await [])] + await (of process await [])] (in (and (text#= command read) (text#= oops failure) wrote! diff --git a/stdlib/source/test/lux/world/time.lux b/stdlib/source/test/lux/world/time.lux index d6ee9b953..95ddb6370 100644 --- a/stdlib/source/test/lux/world/time.lux +++ b/stdlib/source/test/lux/world/time.lux @@ -29,7 +29,8 @@ ["[1][0]" instant] ["[1][0]" month] ["[1][0]" year] - ["[1][0]" solar]] + ["[1][0]" solar] + ["[1][0]" series]] [\\library ["[0]" / (.only) ["[0]" duration]]]) @@ -55,7 +56,7 @@ (|> expected /.clock /.time - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false))) (let [expected (/.clock expected)] (`` (all _.and @@ -73,10 +74,10 @@ (def for_ranges Test (do [! random.monad] - [valid_hour (at ! each (|>> (n.% /.hours) (n.max 10)) random.nat) - valid_minute (at ! each (|>> (n.% /.minutes) (n.max 10)) random.nat) - valid_second (at ! each (|>> (n.% /.seconds) (n.max 10)) random.nat) - valid_milli_second (at ! each (n.% /.milli_seconds) random.nat) + [valid_hour (of ! each (|>> (n.% /.hours) (n.max 10)) random.nat) + valid_minute (of ! each (|>> (n.% /.minutes) (n.max 10)) random.nat) + valid_second (of ! each (|>> (n.% /.seconds) (n.max 10)) random.nat) + valid_milli_second (of ! each (n.% /.milli_seconds) random.nat) .let [invalid_hour (|> valid_hour (n.+ /.hours)) invalid_minute (|> valid_minute (n.+ /.minutes) (n.min 99)) @@ -89,7 +90,7 @@ %.nat (text.prefix <prefix>) (text.suffix <suffix>) - (at /.codec decoded) + (of /.codec decoded) (pipe.when {try.#Success _} true {try.#Failure error} false)) @@ -99,7 +100,7 @@ %.nat (text.prefix <prefix>) (text.suffix <suffix>) - (at /.codec decoded) + (of /.codec decoded) (pipe.when {try.#Success _} false @@ -117,7 +118,7 @@ (|> valid_milli_second %.nat (format "00:00:00.") - (at /.codec decoded) + (of /.codec decoded) (pipe.when {try.#Success _} true {try.#Failure error} false))) @@ -131,7 +132,7 @@ [.let [day (.nat (duration.millis duration.day))] expected random.time - out_of_bounds (at ! each (|>> /.millis (n.+ day)) + out_of_bounds (of ! each (|>> /.millis (n.+ day)) random.time)] (`` (all _.and ..for_implementation @@ -140,7 +141,7 @@ (|> expected /.millis /.of_millis - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false))) (_.coverage [/.time_exceeds_a_day] (when (/.of_millis out_of_bounds) @@ -155,9 +156,9 @@ (n.= 0))) (_.coverage [/.parser] (|> expected - (at /.codec encoded) + (of /.codec encoded) (<text>.result /.parser) - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false))) ..for_ranges (_.for [/.Clock] @@ -170,4 +171,5 @@ /month.test /year.test /solar.test + /series.test ))))) diff --git a/stdlib/source/test/lux/world/time/date.lux b/stdlib/source/test/lux/world/time/date.lux index 3dd22343b..d2a3bdc0d 100644 --- a/stdlib/source/test/lux/world/time/date.lux +++ b/stdlib/source/test/lux/world/time/date.lux @@ -45,7 +45,7 @@ (|> (/.date (/.year expected) (/.month expected) (/.day_of_month expected)) - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false)))) (do random.monad [expected random.date] @@ -64,7 +64,7 @@ (|> expected /.days /.of_days - (at /.equivalence = expected)))) + (of /.equivalence = expected)))) (_.coverage [/.epoch] (|> /.epoch /.days @@ -72,16 +72,16 @@ (do random.monad [expected random.date] (_.coverage [/.parser] - (|> (at /.codec encoded expected) + (|> (of /.codec encoded expected) (<text>.result /.parser) - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false)))) (do [! random.monad] - [year (at ! each (|>> (n.% 10,000) ++) + [year (of ! each (|>> (n.% 10,000) ++) random.nat) - month (at ! each (|>> (n.% 10) (n.+ 13)) + month (of ! each (|>> (n.% 10) (n.+ 13)) random.nat) - day (at ! each (|>> (n.% 10) (n.+ 10)) + day (of ! each (|>> (n.% 10) (n.+ 10)) random.nat) .let [input (format (%.nat year) "-" (%.nat month) diff --git a/stdlib/source/test/lux/world/time/day.lux b/stdlib/source/test/lux/world/time/day.lux index 6f1ea4b3d..5e1c3a2fe 100644 --- a/stdlib/source/test/lux/world/time/day.lux +++ b/stdlib/source/test/lux/world/time/day.lux @@ -60,8 +60,8 @@ (,, (with_template [<before> <current> <after>] [(_.coverage [<current>] - (and (at /.equivalence = {<before>} (at /.enum pred {<current>})) - (at /.equivalence = {<after>} (at /.enum succ {<current>}))))] + (and (of /.equivalence = {<before>} (of /.enum pred {<current>})) + (of /.equivalence = {<after>} (of /.enum succ {<current>}))))] [/.#Saturday /.#Sunday /.#Monday] [/.#Sunday /.#Monday /.#Tuesday] @@ -74,7 +74,7 @@ (do random.monad [not_a_day (random.upper_cased 1)] (_.coverage [/.not_a_day_of_the_week] - (when (at /.codec decoded not_a_day) + (when (of /.codec decoded not_a_day) {try.#Failure error} (exception.match? /.not_a_day_of_the_week error) @@ -84,7 +84,7 @@ (|> expected /.number /.by_number - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false))) (_.coverage [/.invalid_day] (when (/.by_number invalid) diff --git a/stdlib/source/test/lux/world/time/duration.lux b/stdlib/source/test/lux/world/time/duration.lux index 093f98f0d..c3546fe7a 100644 --- a/stdlib/source/test/lux/world/time/duration.lux +++ b/stdlib/source/test/lux/world/time/duration.lux @@ -40,7 +40,7 @@ (do random.monad [duration random.duration] (_.coverage [/.of_millis /.millis] - (|> duration /.millis /.of_millis (at /.equivalence = duration)))) + (|> duration /.millis /.of_millis (of /.equivalence = duration)))) (do random.monad [.let [(open "#[0]") /.equivalence] expected random.duration @@ -68,7 +68,7 @@ [.let [(open "#[0]") /.order positive (|> random.duration (random.only (|>> (#= /.empty) not)) - (at ! each (function (_ duration) + (of ! each (function (_ duration) (if (/.positive? duration) duration (/.inverse duration)))))] @@ -83,7 +83,7 @@ (_.coverage [/.ticks] (i.= +1 (/.ticks sample sample))) (_.coverage [/.milli_second] - (#= /.empty (at /.enum pred /.milli_second))) + (#= /.empty (of /.enum pred /.milli_second))) (,, (with_template [<factor> <big> <small>] [(_.coverage [<big>] (|> <big> (/.ticks <small>) (i.= <factor>)))] diff --git a/stdlib/source/test/lux/world/time/instant.lux b/stdlib/source/test/lux/world/time/instant.lux index d81a5ad27..ef6773eac 100644 --- a/stdlib/source/test/lux/world/time/instant.lux +++ b/stdlib/source/test/lux/world/time/instant.lux @@ -45,33 +45,44 @@ ($codec.spec /.equivalence /.codec random.instant)) (do random.monad - [.let [(open "#[0]") /.equivalence] + [.let [(open "/#[0]") /.equivalence] expected random.instant] (all _.and (_.coverage [/.millis /.of_millis] - (|> expected /.millis /.of_millis (#= expected))) + (|> expected /.millis /.of_millis (/#= expected))) (_.coverage [/.relative /.absolute] - (|> expected /.relative /.absolute (#= expected))) + (|> expected /.relative /.absolute (/#= expected))) (_.coverage [/.date /.time /.of_date_time] - (#= expected - (/.of_date_time (/.date expected) - (/.time expected)))) + (/#= expected + (/.of_date_time (/.date expected) + (/.time expected)))) )) (do random.monad - [.let [(open "#[0]") /.equivalence + [.let [(open "/#[0]") /.equivalence (open "duration#[0]") duration.equivalence] from random.instant to random.instant] (all _.and (_.coverage [/.span] (|> from (/.span from) (duration#= duration.empty))) + (_.coverage [/.before] + (|> from (/.before (/.span to from)) (/#= to))) (_.coverage [/.after] - (|> from (/.after (/.span from to)) (#= to))) + (|> from (/.after (/.span from to)) (/#= to))) (_.coverage [/.epoch] (duration#= (/.relative to) (/.span /.epoch to))) )) (do random.monad + [.let [(open "/#[0]") /.order] + it random.instant] + (all _.and + (_.coverage [/.earliest] + (not (/#< /.earliest it))) + (_.coverage [/.latest] + (not (/#< it /.latest))) + )) + (do random.monad [instant random.instant .let [d0 (/.day_of_week instant)]] (_.coverage [/.day_of_week] @@ -115,6 +126,6 @@ (|> expected /.format (?text.result /.parser) - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false)))) ))) diff --git a/stdlib/source/test/lux/world/time/month.lux b/stdlib/source/test/lux/world/time/month.lux index 620af8077..bc095c947 100644 --- a/stdlib/source/test/lux/world/time/month.lux +++ b/stdlib/source/test/lux/world/time/month.lux @@ -33,7 +33,7 @@ (Random /.Month) (let [december (/.number {/.#December})] (|> random.nat - (at random.monad each (|>> (n.% december) ++)) + (of random.monad each (|>> (n.% december) ++)) (random.one (|>> /.by_number try.maybe))))) (def .public test @@ -54,8 +54,8 @@ (,, (with_template [<before> <current> <after>] [(_.coverage [<current>] - (and (at /.equivalence = {<before>} (at /.enum pred {<current>})) - (at /.equivalence = {<after>} (at /.enum succ {<current>}))))] + (and (of /.equivalence = {<before>} (of /.enum pred {<current>})) + (of /.equivalence = {<after>} (of /.enum succ {<current>}))))] [/.#December /.#January /.#February] [/.#January /.#February /.#March] @@ -80,7 +80,7 @@ (|> expected /.number /.by_number - (try#each (at /.equivalence = expected)) + (try#each (of /.equivalence = expected)) (try.else false))) (_.coverage [/.invalid_month] (when (/.by_number invalid) @@ -111,7 +111,7 @@ (do random.monad [not_a_month (random.upper_cased 1)] (_.coverage [/.not_a_month_of_the_year] - (when (at /.codec decoded not_a_month) + (when (of /.codec decoded not_a_month) {try.#Failure error} (exception.match? /.not_a_month_of_the_year error) diff --git a/stdlib/source/test/lux/world/time/series.lux b/stdlib/source/test/lux/world/time/series.lux new file mode 100644 index 000000000..806241c2b --- /dev/null +++ b/stdlib/source/test/lux/world/time/series.lux @@ -0,0 +1,152 @@ +(.require + [library + [lux (.except) + [abstract + [monad (.only do)] + [\\specification + ["[0]S" equivalence] + ["[0]S" mix] + ["[0]S" functor (.only Injection)]]] + [control + ["|" pipe] + ["[0]" try (.use "[1]#[0]" functor)] + ["[0]" exception]] + [data + ["[0]" product] + [collection + ["[0]" list (.use "[1]#[0]" functor mix)] + ["[0]" set]]] + [math + ["[0]" random (.only Random) (.use "[1]#[0]" functor)] + [number + ["n" nat] + ["i" int]]] + [world + [time + ["[0]" instant (.only Instant) (.use "[1]#[0]" order)] + ["[0]" duration]]] + [test + ["_" property (.only Test)]]]] + [\\library + ["[0]" /]]) + +(def .public (event it) + (All (_ of) + (-> (Random of) + (Random (/.Event of)))) + (do random.monad + [when random.instant + what it] + (in [/.#when when + /.#what what]))) + +(def .public (random size it) + (All (_ of) + (-> Nat (Random of) + (Random (/.Series of)))) + (|> it + (random.list size) + (random#each (|>> (list#mix (function (_ what [when events]) + [(instant.before duration.milli_second when) + (list.partial [/.#when when + /.#what what] + events)]) + [instant.latest (list)]) + product.right)) + (random.one (|>> /.series + try.maybe)))) + +(def (injection when) + (-> Instant + (Injection /.Series)) + (|>> [/.#when when + /.#what] + list + /.series + try.trusted)) + +(def .public test + Test + (<| (_.covering /._) + (do [! random.monad] + [before (..event random.nat) + after (random.only (|>> (the /.#when) + (instant#= (the /.#when before)) + not) + (..event random.nat)) + .let [[before after] (if (instant#< (the /.#when after) + (the /.#when before)) + [before after] + [after before])] + + expected_instant random.instant + expected_size (of ! each (n.% 10) random.nat) + events (is (Random (List (/.Event Int))) + (|> random.int + (random.set i.hash expected_size) + (of ! each (|>> set.list + (list.sorted i.<) + (list#each (function (_ it) + [/.#when (instant.of_millis it) + /.#what it]))))))]) + (all _.and + (<| (_.for [/.Event + /.#what /.#when]) + (`` (all _.and + (,, (with_template [<event> <expected>] + [(_.coverage [<event>] + (|> (do try.monad + [it (/.series (list before after)) + actual (<event> it)] + (in (same? <expected> actual))) + (try.else false)))] + + [/.earliest before] + [/.latest after] + )) + ))) + (<| (_.for [/.Series]) + (`` (all _.and + (_.for [/.equivalence] + (equivalenceS.spec (/.equivalence n.equivalence) (..random expected_size random.nat))) + (_.for [/.mix] + (mixS.spec (..injection expected_instant) /.equivalence /.mix)) + (_.for [/.functor] + (functorS.spec (..injection expected_instant) /.equivalence /.functor)) + + (_.coverage [/.series /.size] + (|> (do try.monad + [it (/.series events)] + (in (/.size it))) + (try#each (n.= expected_size)) + (try.else false))) + (_.coverage [/.empty] + (and (,, (with_template [<event> <expected>] + [(|> (do try.monad + [it (/.series (list))] + (<event> it)) + (|.when + {try.#Failure error} + (exception.match? /.empty error) + + _ + false))] + + [/.earliest before] + [/.latest after] + )))) + (,, (with_template [<exception> <left> <right>] + [(_.coverage [<exception>] + (|> (/.series (list <left> <right>)) + (|.when + {try.#Failure error} + (exception.match? <exception> error) + + _ + false)))] + + [/.disordered after before] + [/.duplicated before before] + )) + ))) + ))) diff --git a/stdlib/source/test/lux/world/time/year.lux b/stdlib/source/test/lux/world/time/year.lux index ec4638abd..a635804ea 100644 --- a/stdlib/source/test/lux/world/time/year.lux +++ b/stdlib/source/test/lux/world/time/year.lux @@ -74,7 +74,7 @@ (n.= (.nat (//duration.ticks //duration.day //duration.normal_year)) /.days)) (_.coverage [/.epoch] - (at /.equivalence = + (of /.equivalence = (//date.year (//instant.date //instant.epoch)) /.epoch)) (_.for [/.Period] |