diff options
author | Eduardo Julian | 2021-07-02 03:11:36 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-07-02 03:11:36 -0400 |
commit | 5cf4efa861075f8276f43a2516f5beacaf610b44 (patch) | |
tree | e21cf528d960c29d22cbc7e41180fa09e62f16d6 /stdlib/source/test/lux/world | |
parent | 744ee69630de59ca3ba660b0aab6361cd17ce1b4 (diff) |
No longer employing the capabilities model on the lux/world/* modules.
Capabilities should be opt-in, but using them in the standard library makes them mandatory.
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/test/lux/world.lux | 4 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/console.lux | 16 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/file.lux | 6 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/file/watch.lux | 12 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/net/http/status.lux | 119 | ||||
-rw-r--r-- | stdlib/source/test/lux/world/shell.lux | 67 |
6 files changed, 162 insertions, 62 deletions
diff --git a/stdlib/source/test/lux/world.lux b/stdlib/source/test/lux/world.lux index 47e4ceb27..c5ea26a6f 100644 --- a/stdlib/source/test/lux/world.lux +++ b/stdlib/source/test/lux/world.lux @@ -13,7 +13,8 @@ ["#/." resolution]]] ["#." net #_ ["#/." http #_ - ["#/." client]]]]) + ["#/." client] + ["#/." status]]]]) (def: #export test Test @@ -25,4 +26,5 @@ /input/keyboard.test /output/video/resolution.test /net/http/client.test + /net/http/status.test )) diff --git a/stdlib/source/test/lux/world/console.lux b/stdlib/source/test/lux/world/console.lux index 56e3902f0..b196199fc 100644 --- a/stdlib/source/test/lux/world/console.lux +++ b/stdlib/source/test/lux/world/console.lux @@ -6,9 +6,7 @@ [control ["." io] ["." try (#+ Try)] - ["." exception (#+ exception:)] - [security - ["!" capability]]] + ["." exception (#+ exception:)]] [data ["." text ("#\." equivalence) ["%" format (#+ format)]]] @@ -21,8 +19,8 @@ (exception: dead) -(def: simulation - (/.Simulation [Bit Text]) +(def: mock + (/.Mock [Bit Text]) (implementation (def: (on_read [dead? content]) (do try.monad @@ -53,16 +51,16 @@ Test (<| (_.covering /._) ($_ _.and - (_.for [/.async /.mock /.Simulation] - ($/.spec (io.io (/.async (/.mock ..simulation [false ""]))))) + (_.for [/.async /.mock /.Mock] + ($/.spec (io.io (/.async (/.mock ..mock [false ""]))))) (do random.monad [expected (random.ascii/alpha 10) - #let [console (/.mock ..simulation [false ""])]] + #let [console (/.mock ..mock [false ""])]] (_.cover [/.write_line] (io.run (do io.monad [?_ (/.write_line expected console) - ?actual (!.use (\ console read_line) [])] + ?actual (\ console read_line [])] (wrap (<| (try.default false) (do try.monad [_ ?_ diff --git a/stdlib/source/test/lux/world/file.lux b/stdlib/source/test/lux/world/file.lux index c7f546a1b..8a0c416be 100644 --- a/stdlib/source/test/lux/world/file.lux +++ b/stdlib/source/test/lux/world/file.lux @@ -7,9 +7,7 @@ ["." io (#+ IO)] ["." try (#+ Try)] [concurrency - ["." promise]] - [security - ["!" capability]]] + ["." promise]]] [data ["." binary (#+ Binary)] ["." text] @@ -72,7 +70,7 @@ (def: #export test Test - (<| (_.context (%.name (name_of /._))) + (<| (_.covering /._) (do {! random.monad} [file_size (|> random.nat (\ ! map (|>> (n.% 100) (n.max 10)))) dataL (_binary.random file_size) diff --git a/stdlib/source/test/lux/world/file/watch.lux b/stdlib/source/test/lux/world/file/watch.lux index c0873b41a..9c1b31811 100644 --- a/stdlib/source/test/lux/world/file/watch.lux +++ b/stdlib/source/test/lux/world/file/watch.lux @@ -8,9 +8,7 @@ ["." try] ["." exception] [concurrency - ["." promise]] - [security - ["!" capability]]] + ["." promise]]] [data ["." binary ("#\." equivalence)] ["." text ("#\." equivalence) @@ -106,12 +104,12 @@ data (_binary.random 10)] (wrap (do {! promise.monad} [verdict (do (try.with !) - [_ (!.use (\ fs create_directory) [directory]) + [_ (\ fs create_directory directory) _ (\ watcher start /.all directory) poll/0 (\ watcher poll []) #let [no_events_prior_to_creation! (list.empty? poll/0)] - file (!.use (\ fs create_file) [expected_path]) + file (\ fs create_file expected_path) poll/1 (\ watcher poll []) poll/1' (\ watcher poll []) #let [after_creation! @@ -126,7 +124,7 @@ false) (list.empty? poll/1'))] _ (promise.delay 1 (#try.Success "Delay to make sure the over_write time-stamp always changes.")) - _ (!.use (\ file over_write) data) + _ (\ file over_write data) poll/2 (\ watcher poll []) poll/2' (\ watcher poll []) #let [after_modification! @@ -140,7 +138,7 @@ _ false) (list.empty? poll/2'))] - _ (!.use (\ file delete) []) + _ (\ file delete []) poll/3 (\ watcher poll []) poll/3' (\ watcher poll []) #let [after_deletion! diff --git a/stdlib/source/test/lux/world/net/http/status.lux b/stdlib/source/test/lux/world/net/http/status.lux new file mode 100644 index 000000000..801dc1b43 --- /dev/null +++ b/stdlib/source/test/lux/world/net/http/status.lux @@ -0,0 +1,119 @@ +(.module: + [lux #* + ["_" test (#+ Test)] + [data + [collection + ["." list] + ["." set (#+ Set)]]] + [macro + ["." template]] + [math + [number + ["n" nat]]]] + {1 + ["." / + ["/#" //]]}) + +(with_expansions [<categories> (as_is [informational + [/.continue + /.switching_protocols + /.processing + /.early_hints]] + [success + [/.ok + /.created + /.accepted + /.non_authoritative_information + /.no_content + /.reset_content + /.partial_content + /.multi_status + /.already_reported + /.im_used]] + [redirection + [/.multiple_choices + /.moved_permanently + /.found + /.see_other + /.not_modified + /.use_proxy + /.switch_proxy + /.temporary_redirect + /.permanent_redirect]] + [client + [/.bad_request + /.unauthorized + /.payment_required + /.forbidden + /.not_found + /.method_not_allowed + /.not_acceptable + /.proxy_authentication_required + /.request_timeout + /.conflict + /.gone + /.length_required + /.precondition_failed + /.payload_too_large + /.uri_too_long + /.unsupported_media_type + /.range_not_satisfiable + /.expectation_failed + /.im_a_teapot + /.misdirected_request + /.unprocessable_entity + /.locked + /.failed_dependency + /.upgrade_required + /.precondition_required + /.too_many_requests + /.request_header_fields_too_large + /.unavailable_for_legal_reasons]] + [server + [/.internal_server_error + /.not_implemented + /.bad_gateway + /.service_unavailable + /.gateway_timeout + /.http_version_not_supported + /.variant_also_negotiates + /.insufficient_storage + /.loop_detected + /.not_extended + /.network_authentication_required]])] + (def: all + (List //.Status) + (list.concat (`` (list (~~ (template [<category> <status+>] + [((: (-> Any (List //.Status)) + (function (_ _) + (`` (list (~~ (template.splice <status+>)))))) + 123)] + + <categories>)))))) + + (def: unique + (Set //.Status) + (set.from_list n.hash ..all)) + + (def: verdict + (n.= (list.size ..all) + (set.size ..unique))) + + (template [<category> <status+>] + [(def: <category> + Test + (_.cover <status+> + ..verdict))] + + <categories>) + + (def: #export test + Test + (<| (_.covering /._) + (`` ($_ _.and + (~~ (template [<category> <status+>] + [<category>] + + <categories>)) + )))) + ) diff --git a/stdlib/source/test/lux/world/shell.lux b/stdlib/source/test/lux/world/shell.lux index 334250a96..64fa47d28 100644 --- a/stdlib/source/test/lux/world/shell.lux +++ b/stdlib/source/test/lux/world/shell.lux @@ -1,7 +1,6 @@ (.module: [lux #* ["_" test (#+ Test)] - ["." debug] [abstract [monad (#+ do)]] [control @@ -10,8 +9,6 @@ ["." io (#+ IO)] [concurrency ["." promise (#+ Promise)]] - [security - ["!" capability]] [parser ["." environment (#+ Environment)]]] [data @@ -32,9 +29,9 @@ (exception: dead) -(def: (simulation [environment working_directory command arguments]) +(def: (mock [environment working_directory command arguments]) (-> [Environment Path /.Command (List /.Argument)] - (/.Simulation Bit)) + (/.Mock Bit)) (implementation (def: (on_read dead?) (if dead? @@ -66,40 +63,28 @@ (def: (io_shell command oops input destruction exit) (-> /.Command Text Text Text /.Exit (/.Shell IO)) (implementation - (def: execute - ((debug.private /.can_execute) - (function (_ [environment working_directory command arguments]) - (io.io - (#try.Success - (: (/.Process IO) - (implementation - (def: read - ((debug.private /.can_read) - (function (_ _) - (io.io (#try.Success command))))) - (def: error - ((debug.private /.can_read) - (function (_ _) - (io.io (#try.Success oops))))) - (def: write - ((debug.private /.can_write) - (function (_ message) - (io.io (#try.Failure message))))) - (def: destroy - ((debug.private /.can_destroy) - (function (_ _) - (io.io (#try.Failure destruction))))) - (def: await - ((debug.private /.can_wait) - (function (_ _) - (io.io (#try.Success exit)))))))))))))) + (def: (execute [environment working_directory command arguments]) + (<| io.io + #try.Success + (: (/.Process IO)) + (implementation + (def: (read _) + (io.io (#try.Success command))) + (def: (error _) + (io.io (#try.Success oops))) + (def: (write message) + (io.io (#try.Failure message))) + (def: (destroy _) + (io.io (#try.Failure destruction))) + (def: (await _) + (io.io (#try.Success exit)))))))) (def: #export test Test (<| (_.covering /._) ($_ _.and - (_.for [/.async /.mock /.Simulation] - ($/.spec (/.async (/.mock (|>> ..simulation #try.Success) + (_.for [/.async /.mock /.Mock] + ($/.spec (/.async (/.mock (|>> ..mock #try.Success) false)))) (_.cover [/.error] (not (i.= /.normal /.error))) @@ -112,11 +97,11 @@ #let [shell (/.async (..io_shell command oops input destruction exit))]] (wrap (do {! promise.monad} [verdict (do (try.with !) - [process (!.use (\ shell execute) [environment.empty "~" command (list)]) - read (!.use (\ process read) []) - error (!.use (\ process error) []) + [process (\ shell execute [environment.empty "~" command (list)]) + read (\ process read []) + error (\ process error []) wrote! (do ! - [write (!.use (\ process write) [input])] + [write (\ process write input)] (wrap (#try.Success (case write (#try.Success _) false @@ -124,19 +109,19 @@ (#try.Failure write) (text\= input write))))) destroyed! (do ! - [destroy (!.use (\ process destroy) [])] + [destroy (\ process destroy [])] (wrap (#try.Success (case destroy (#try.Success _) false (#try.Failure destroy) (text\= destruction destroy))))) - await (!.use (\ process await) [])] + await (\ process await [])] (wrap (and (text\= command read) (text\= oops error) wrote! destroyed! (i.= exit await))))] - (_.cover' [/.Can_Write] + (_.cover' [/.Shell] (try.default false verdict))))) ))) |