diff options
author | Eduardo Julian | 2022-06-04 19:34:42 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-06-04 19:34:42 -0400 |
commit | f9e33ae96aec4741385a576719786092c9e68043 (patch) | |
tree | 140057dfc054346eab721f9905f0f0fff22ad933 /stdlib/source/test/aedifex/command | |
parent | 56d2835d35093e2d92c5e8a4371aa322b55e037b (diff) |
De-sigil-ification: #
Diffstat (limited to 'stdlib/source/test/aedifex/command')
-rw-r--r-- | stdlib/source/test/aedifex/command/auto.lux | 30 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/build.lux | 34 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/clean.lux | 14 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/deploy.lux | 44 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/deps.lux | 14 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/install.lux | 22 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/pom.lux | 16 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/test.lux | 22 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/version.lux | 2 |
9 files changed, 99 insertions, 99 deletions
diff --git a/stdlib/source/test/aedifex/command/auto.lux b/stdlib/source/test/aedifex/command/auto.lux index c057d173d..b483ecd2c 100644 --- a/stdlib/source/test/aedifex/command/auto.lux +++ b/stdlib/source/test/aedifex/command/auto.lux @@ -57,8 +57,8 @@ (if (n.= expected_runs actual_runs) (in {try.#Failure end_signal}) (do (try.with !) - [_ (# fs write dummy_file (# utf8.codec encoded (%.nat actual_runs))) - _ (# fs modify dummy_file (|> actual_runs .int instant.of_millis))] + [_ (at fs write dummy_file (at utf8.codec encoded (%.nat actual_runs))) + _ (at fs modify dummy_file (|> actual_runs .int instant.of_millis))] (in [shell.normal []])))))])) (def: .public test @@ -66,14 +66,14 @@ (<| (_.covering /._) (do [! random.monad] [end_signal (random.alphabetic 5) - .let [/ (# file.default separator) + .let [/ (at file.default separator) [fs watcher] (watch.mock /)] program (random.alphabetic 5) target (random.alphabetic 5) source (random.alphabetic 5) .let [empty_profile (is Profile - (# ///.monoid identity)) + (at ///.monoid identity)) with_target (is (-> Profile Profile) (has ///.#target target)) with_program (is (-> Profile Profile) @@ -87,18 +87,18 @@ home (random.alphabetic 5) working_directory (random.alphabetic 5) - expected_runs (# ! each (|>> (n.% 10) (n.max 2)) random.nat) - dummy_path (# ! each (|>> (format source /)) (random.alphabetic 5)) + expected_runs (at ! each (|>> (n.% 10) (n.max 2)) random.nat) + dummy_path (at ! each (|>> (format source /)) (random.alphabetic 5)) [compiler resolution] $build.resolution] (all _.and (_.coverage [/.delay] (n.> 0 /.delay)) (in (do async.monad [verdict (do ///action.monad - [_ (# fs make_directory source) - _ (# fs write dummy_path (binary.empty 0)) + [_ (at fs make_directory source) + _ (at fs write dummy_path (binary.empty 0)) .let [[@runs command] (..command expected_runs end_signal fs dummy_path)] - _ (# watcher poll [])] + _ (at watcher poll [])] (do [! async.monad] [no_dangling_process! (|> profile (has ///.#lux compiler) @@ -108,16 +108,16 @@ fs (shell.async ($build.good_shell [])) resolution) - (# ! each (|>> (pipe.case - {try.#Failure error} - (same? end_signal error) + (at ! each (|>> (pipe.case + {try.#Failure error} + (same? end_signal error) - {try.#Success _} - false)))) + {try.#Success _} + false)))) correct_number_of_runs! (|> @runs atom.read! async.future - (# ! each (n.= expected_runs)))] + (at ! each (n.= expected_runs)))] (in {try.#Success (and correct_number_of_runs! no_dangling_process!)})))] (_.coverage' [/.do!] diff --git a/stdlib/source/test/aedifex/command/build.lux b/stdlib/source/test/aedifex/command/build.lux index 1bb77d307..25302fa71 100644 --- a/stdlib/source/test/aedifex/command/build.lux +++ b/stdlib/source/test/aedifex/command/build.lux @@ -142,14 +142,14 @@ (do [! random.monad] [last_read (random.alphabetic 5) last_error (random.alphabetic 5) - .let [fs (file.mock (# file.default separator)) + .let [fs (file.mock (at file.default separator)) shell (shell.async (..good_shell []))] program (random.alphabetic 5) target (random.alphabetic 5) home (random.alphabetic 5) working_directory (random.alphabetic 5) .let [empty_profile (is Profile - (# ///.monoid identity)) + (at ///.monoid identity)) with_target (is (-> Profile Profile) (has ///.#target target)) with_program (is (-> Profile Profile) @@ -186,8 +186,8 @@ [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) fs shell resolution (has ///.#lux compiler profile)) - start (# console read_line []) - end (# console read_line [])] + start (at console read_line []) + end (at console read_line [])] (in (and (text#= /.start start) (text#= /.success end))))] (_.coverage' [/.do! @@ -208,8 +208,8 @@ [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) fs (shell.async (..bad_shell [])) resolution (has ///.#lux compiler profile)) - start (# console read_line []) - end (# console read_line [])] + start (at console read_line []) + end (at console read_line [])] (in (and (text#= /.start start) (text#= /.failure end))))] (_.coverage' [/.failure] @@ -228,17 +228,17 @@ [verdict (do ///action.monad [process (shell [environment.empty working_directory "" (list "")]) _ (<log!> console process) - actual/0 (# console read_line []) - actual/1 (# console read_line []) - actual/2 (# console read_line []) - end! (|> (# console read_line []) - (# ! each (|>> (pipe.case - {try.#Failure error} - true - - {try.#Success _} - false) - {try.#Success})))] + actual/0 (at console read_line []) + actual/1 (at console read_line []) + actual/2 (at console read_line []) + end! (|> (at console read_line []) + (at ! each (|>> (pipe.case + {try.#Failure error} + true + + {try.#Success _} + false) + {try.#Success})))] (in (and (text#= expected/0 actual/0) (text#= expected/1 actual/1) (text#= expected/2 actual/2) diff --git a/stdlib/source/test/aedifex/command/clean.lux b/stdlib/source/test/aedifex/command/clean.lux index e7bf81855..4ead63063 100644 --- a/stdlib/source/test/aedifex/command/clean.lux +++ b/stdlib/source/test/aedifex/command/clean.lux @@ -43,7 +43,7 @@ (def: (files prefix) (-> Path (Random (List [Path Binary]))) (do [! random.monad] - [count (# ! each (n.% 10) random.nat) + [count (at ! each (n.% 10) random.nat) names (random.set text.hash count ..node_name) contents (random.list count ($binary.random 100))] (in (list.zipped_2 (list#each (|>> (format prefix)) (set.list names)) @@ -51,7 +51,7 @@ (def: (create_file! fs [path content]) (-> (file.System Async) [Path Binary] (Async (Try Any))) - (# fs write path content)) + (at fs write path content)) (def: (create_directory! fs path files) (-> (file.System Async) Path (List [Path Binary]) (Async (Try Any))) @@ -63,11 +63,11 @@ (def: (directory_exists? fs) (-> (file.System Async) Path (Async (Try Bit))) - (|>> (# fs directory?) (try.lifted async.monad))) + (|>> (at fs directory?) (try.lifted async.monad))) (def: (file_exists? fs) (-> (file.System Async) Path (Async (Try Bit))) - (|>> (# fs file?) (try.lifted async.monad))) + (|>> (at fs file?) (try.lifted async.monad))) (def: (assets_exist? fs directory_path files) (-> (file.System Async) Path (List [Path Binary]) (Async (Try Bit))) @@ -87,8 +87,8 @@ [context ..node_name target ..node_name sub ..node_name - .let [fs (file.mock (# file.default separator)) - / (# fs separator) + .let [fs (file.mock (at file.default separator)) + / (at fs separator) target_path (format context / target) sub_path (format target_path / sub)] direct_files (..files (format target_path /)) @@ -107,7 +107,7 @@ context_exists!/post (..directory_exists? fs context) target_exists!/post (..assets_exist? fs target_path direct_files) sub_exists!/post (..assets_exist? fs sub_path sub_files) - logging (# console read_line [])] + logging (at console read_line [])] (in (and (and context_exists!/pre context_exists!/post) (and target_exists!/pre diff --git a/stdlib/source/test/aedifex/command/deploy.lux b/stdlib/source/test/aedifex/command/deploy.lux index 0a4e08166..d62e027dd 100644 --- a/stdlib/source/test/aedifex/command/deploy.lux +++ b/stdlib/source/test/aedifex/command/deploy.lux @@ -62,7 +62,7 @@ shell (shell.async ($build.bad_shell []))] _ ($install.make_sources! fs (the ///.#sources profile)) _ (/.do! program shell console local remote fs artifact profile)] - (# console read_line []))) + (at console read_line []))) (def: .public test Test @@ -78,7 +78,7 @@ home (random.alphabetic 5) working_directory (random.alphabetic 5) - .let [fs (file.mock (# file.default separator)) + .let [fs (file.mock (at file.default separator)) program (program.async (program.mock environment.empty home working_directory)) local (///repository/local.repository program fs) remote (///repository.mock $repository.mock @@ -90,20 +90,20 @@ (the ///.#sources) set.list (export.library fs) - (# ! each (format.result tar.writer))) + (at ! each (format.result tar.writer))) - actual_pom (# remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.pom)) - actual_library (# remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.lux_library)) - actual_sha-1 (# remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.sha-1))) - actual_sha-1 (# async.monad in - (do try.monad - [actual_sha-1 (# utf8.codec decoded actual_sha-1)] - (# ///hash.sha-1_codec decoded actual_sha-1))) - actual_md5 (# remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.md5))) - actual_md5 (# async.monad in - (do try.monad - [actual_md5 (# utf8.codec decoded actual_md5)] - (# ///hash.md5_codec decoded actual_md5))) + actual_pom (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.pom)) + actual_library (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact ///artifact/extension.lux_library)) + actual_sha-1 (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.sha-1))) + actual_sha-1 (at async.monad in + (do try.monad + [actual_sha-1 (at utf8.codec decoded actual_sha-1)] + (at ///hash.sha-1_codec decoded actual_sha-1))) + actual_md5 (at remote download (///repository/remote.uri (the ///artifact.#version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.md5))) + actual_md5 (at async.monad in + (do try.monad + [actual_md5 (at utf8.codec decoded actual_md5)] + (at ///hash.md5_codec decoded actual_md5))) .let [succeeded! (text#= /.success logging) @@ -113,18 +113,18 @@ actual_library) deployed_pom! - (binary#= (|> expected_pom (# xml.codec encoded) (# utf8.codec encoded)) + (binary#= (|> expected_pom (at xml.codec encoded) (at utf8.codec encoded)) actual_pom) deployed_sha-1! - (# ///hash.equivalence = - (///hash.sha-1 expected_library) - actual_sha-1) + (at ///hash.equivalence = + (///hash.sha-1 expected_library) + actual_sha-1) deployed_md5! - (# ///hash.equivalence = - (///hash.md5 expected_library) - actual_md5)]] + (at ///hash.equivalence = + (///hash.md5 expected_library) + actual_md5)]] (in (and succeeded! deployed_library! deployed_pom! diff --git a/stdlib/source/test/aedifex/command/deps.lux b/stdlib/source/test/aedifex/command/deps.lux index c5e496e29..d9af2990b 100644 --- a/stdlib/source/test/aedifex/command/deps.lux +++ b/stdlib/source/test/aedifex/command/deps.lux @@ -61,7 +61,7 @@ dependee_artifact $///artifact.random depender_artifact (random.only (predicate.complement - (# ///artifact.equivalence = dependee_artifact)) + (at ///artifact.equivalence = dependee_artifact)) $///artifact.random) [_ dependee_package] $///package.random @@ -72,11 +72,11 @@ depender [///dependency.#artifact depender_artifact ///dependency.#type ///artifact/type.lux_library] - dependee_pom (|> (# ///.monoid identity) + dependee_pom (|> (at ///.monoid identity) (has ///.#identity {.#Some dependee_artifact}) ///pom.write try.trusted) - depender_pom (|> (# ///.monoid identity) + depender_pom (|> (at ///.monoid identity) (has ///.#identity {.#Some depender_artifact}) (has ///.#dependencies (set.of_list ///dependency.hash (list dependee))) ///pom.write @@ -85,15 +85,15 @@ dependee_package (|> dependee_package (has ///package.#origin {///repository/origin.#Remote ""}) (has ///package.#pom [dependee_pom - (|> dependee_pom (# xml.codec encoded) (# utf8.codec encoded)) + (|> dependee_pom (at xml.codec encoded) (at utf8.codec encoded)) {///dependency/status.#Unverified}])) depender_package (|> depender_package (has ///package.#origin {///repository/origin.#Remote ""}) (has ///package.#pom [depender_pom - (|> depender_pom (# xml.codec encoded) (# utf8.codec encoded)) + (|> depender_pom (at xml.codec encoded) (at utf8.codec encoded)) {///dependency/status.#Unverified}])) - fs (file.mock (# file.default separator)) + fs (file.mock (at file.default separator)) program (program.async (program.mock environment.empty home working_directory))]] (in (do async.monad [verdict (do ///action.monad @@ -102,7 +102,7 @@ pre (|> ///dependency/resolution.empty (dictionary.has dependee dependee_package) (///dependency/deployment.all local)) - post (|> (# ///.monoid identity) + post (|> (at ///.monoid identity) (has ///.#dependencies (set.of_list ///dependency.hash (list dependee depender))) (/.do! console local (list (///repository.mock ($///dependency/resolution.single depender_artifact depender_package) diff --git a/stdlib/source/test/aedifex/command/install.lux b/stdlib/source/test/aedifex/command/install.lux index 4de5c5226..55bb762d0 100644 --- a/stdlib/source/test/aedifex/command/install.lux +++ b/stdlib/source/test/aedifex/command/install.lux @@ -40,7 +40,7 @@ (def: .public (make_sources! fs sources) (-> (file.System Async) (Set file.Path) (Action (List Any))) - (let [/ (# fs separator) + (let [/ (at fs separator) ! ///action.monad] (|> sources set.list @@ -57,18 +57,18 @@ [.let [console ($version.echo "")] _ (..make_sources! fs (the ///.#sources sample)) _ (/.do! console fs (///repository/local.repository program fs) sample)] - (# console read_line []))) + (at console read_line []))) (def: .public test Test (<| (_.covering /._) (do [! random.monad] [identity $artifact.random - sample (# ! each (has ///.#identity {.#Some identity}) - $profile.random) + sample (at ! each (has ///.#identity {.#Some identity}) + $profile.random) home (random.alphabetic 5) working_directory (random.alphabetic 5) - .let [/ (# file.default separator)]] + .let [/ (at file.default separator)]] (all _.and (in (do [! async.monad] [.let [fs (file.mock /) @@ -78,16 +78,16 @@ library_path (format artifact_path ///artifact/extension.lux_library) pom_path (format artifact_path ///artifact/extension.pom)] verdict (do [! ///action.monad] - [succeeded! (# ! each (text#= /.success) - (..execute! program fs sample)) + [succeeded! (at ! each (text#= /.success) + (..execute! program fs sample)) library_exists! (|> library_path (format home /) - (# fs file?) - (# async.monad each (|>> {try.#Success}))) + (at fs file?) + (at async.monad each (|>> {try.#Success}))) pom_exists! (|> pom_path (format home /) - (# fs file?) - (# async.monad each (|>> {try.#Success})))] + (at fs file?) + (at async.monad each (|>> {try.#Success})))] (in (and succeeded! library_exists! pom_exists!)))] diff --git a/stdlib/source/test/aedifex/command/pom.lux b/stdlib/source/test/aedifex/command/pom.lux index 75509644d..278d91209 100644 --- a/stdlib/source/test/aedifex/command/pom.lux +++ b/stdlib/source/test/aedifex/command/pom.lux @@ -35,7 +35,7 @@ (<| (_.covering /._) (do random.monad [sample @profile.random - .let [fs (file.mock (# file.default separator))]] + .let [fs (file.mock (at file.default separator))]] (in (do [! async.monad] [.let [console (@version.echo "")] outcome (/.do! console fs sample)] @@ -44,14 +44,14 @@ (do ! [verdict (do ///action.monad [expected (|> (///pom.write sample) - (try#each (|>> (# xml.codec encoded) - (# utf8.codec encoded))) - (# ! in)) - actual (# fs read ///pom.file) + (try#each (|>> (at xml.codec encoded) + (at utf8.codec encoded))) + (at ! in)) + actual (at fs read ///pom.file) - logging! (# ///action.monad each - (text#= /.success) - (# console read_line [])) + logging! (at ///action.monad each + (text#= /.success) + (at console read_line [])) .let [expected_content! (binary#= expected actual)]] diff --git a/stdlib/source/test/aedifex/command/test.lux b/stdlib/source/test/aedifex/command/test.lux index 50bd8e183..9b01c2feb 100644 --- a/stdlib/source/test/aedifex/command/test.lux +++ b/stdlib/source/test/aedifex/command/test.lux @@ -48,7 +48,7 @@ home (random.alphabetic 5) working_directory (random.alphabetic 5) .let [empty_profile (is Profile - (# ///.monoid identity)) + (at ///.monoid identity)) with_target (is (-> Profile Profile) (has ///.#target target)) with_test (is (-> Profile Profile) @@ -59,17 +59,17 @@ with_target)] [compiler resolution] @build.resolution] (all _.and - (let [fs (file.mock (# file.default separator)) + (let [fs (file.mock (at file.default separator)) console (@version.echo "")] (in (do async.monad [verdict (do ///action.monad [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) fs (shell.async (@build.good_shell [])) resolution (has ///.#lux compiler profile)) - build_start (# console read_line []) - build_end (# console read_line []) - test_start (# console read_line []) - test_end (# console read_line [])] + build_start (at console read_line []) + build_end (at console read_line []) + test_start (at console read_line []) + test_end (at console read_line [])] (in (and (and (text#= //build.start build_start) (text#= //build.success build_end)) (and (text#= /.start test_start) @@ -77,7 +77,7 @@ (_.coverage' [/.do! /.start /.success] (try.else false verdict))))) - (let [fs (file.mock (# file.default separator)) + (let [fs (file.mock (at file.default separator)) console (@version.echo "")] (in (do async.monad [verdict (do ///action.monad @@ -102,10 +102,10 @@ _ (/.do! console (program.async (program.mock environment.empty home working_directory)) fs (shell.async bad_shell) resolution (has ///.#lux compiler profile)) - build_start (# console read_line []) - build_end (# console read_line []) - test_start (# console read_line []) - test_end (# console read_line [])] + build_start (at console read_line []) + build_end (at console read_line []) + test_start (at console read_line []) + test_end (at console read_line [])] (in (and (and (text#= //build.start build_start) (text#= //build.success build_end)) (and (text#= /.start test_start) diff --git a/stdlib/source/test/aedifex/command/version.lux b/stdlib/source/test/aedifex/command/version.lux index fbd864d4b..bb92fadfb 100644 --- a/stdlib/source/test/aedifex/command/version.lux +++ b/stdlib/source/test/aedifex/command/version.lux @@ -71,7 +71,7 @@ [.let [console (..echo "")] verdict (do (try.with async.monad) [_ (/.do! console profile) - logging (# console read_line [])] + logging (at console read_line [])] (in (text#= (version.format lux_version.latest) logging)))] (_.coverage' [/.do!] |