diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/test/aedifex/command/auto.lux | 58 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/build.lux | 166 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/clean.lux | 58 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/deploy.lux | 88 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/deps.lux | 58 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/install.lux | 60 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/pom.lux | 58 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/test.lux | 98 | ||||
-rw-r--r-- | stdlib/source/test/aedifex/command/version.lux | 30 |
9 files changed, 337 insertions, 337 deletions
diff --git a/stdlib/source/test/aedifex/command/auto.lux b/stdlib/source/test/aedifex/command/auto.lux index 27b12bc42..e27fd039a 100644 --- a/stdlib/source/test/aedifex/command/auto.lux +++ b/stdlib/source/test/aedifex/command/auto.lux @@ -55,13 +55,13 @@ (do {! async.monad} [[_ actual_runs] (async.future (atom.update inc @runs))] (if (n.= expected_runs actual_runs) - (wrap (#try.Failure end_signal)) + (in (#try.Failure end_signal)) (do (try.with !) [_ (\ fs write (\ utf8.codec encode (%.nat actual_runs)) dummy_file) _ (\ fs modify (|> actual_runs .int instant.of_millis) dummy_file)] - (wrap [shell.normal []])))))])) + (in [shell.normal []])))))])) (def: #export test Test @@ -95,32 +95,32 @@ ($_ _.and (_.cover [/.delay] (n.> 0 /.delay)) - (wrap (do async.monad - [verdict (do ///action.monad - [_ (\ fs make_directory source) - _ (\ fs write (binary.create 0) dummy_path) - #let [[@runs command] (..command expected_runs end_signal fs dummy_path)] - _ (\ watcher poll [])] - (do {! async.monad} - [no_dangling_process! (|> profile - (set@ #///.compiler compiler) - ((/.do! 1 watcher command) - ($version.echo "") - (program.async (program.mock environment.empty home working_directory)) - fs - (shell.async ($build.good_shell [])) - resolution) - (\ ! map (|>> (case> (#try.Failure error) - (is? end_signal error) + (in (do async.monad + [verdict (do ///action.monad + [_ (\ fs make_directory source) + _ (\ fs write (binary.create 0) dummy_path) + #let [[@runs command] (..command expected_runs end_signal fs dummy_path)] + _ (\ watcher poll [])] + (do {! async.monad} + [no_dangling_process! (|> profile + (set@ #///.compiler compiler) + ((/.do! 1 watcher command) + ($version.echo "") + (program.async (program.mock environment.empty home working_directory)) + fs + (shell.async ($build.good_shell [])) + resolution) + (\ ! map (|>> (case> (#try.Failure error) + (is? end_signal error) - (#try.Success _) - false)))) - correct_number_of_runs! (|> @runs - atom.read - async.future - (\ ! map (n.= expected_runs)))] - (wrap (#try.Success (and correct_number_of_runs! - no_dangling_process!)))))] - (_.cover' [/.do!] - (try.default false verdict)))) + (#try.Success _) + false)))) + correct_number_of_runs! (|> @runs + atom.read + async.future + (\ ! map (n.= expected_runs)))] + (in (#try.Success (and correct_number_of_runs! + no_dangling_process!)))))] + (_.cover' [/.do!] + (try.default false verdict)))) )))) diff --git a/stdlib/source/test/aedifex/command/build.lux b/stdlib/source/test/aedifex/command/build.lux index 3bc7f86dc..141573f6f 100644 --- a/stdlib/source/test/aedifex/command/build.lux +++ b/stdlib/source/test/aedifex/command/build.lux @@ -45,9 +45,9 @@ (: (shell.Mock []) (implementation (def: (on_read state) - (exception.throw shell.no_more_output [])) + (exception.except shell.no_more_output [])) (def: (on_error state) - (exception.throw shell.no_more_output [])) + (exception.except shell.no_more_output [])) (def: (on_write input state) (#try.Failure "on_write")) (def: (on_destroy state) @@ -63,9 +63,9 @@ (: (shell.Mock []) (implementation (def: (on_read state) - (exception.throw shell.no_more_output [])) + (exception.except shell.no_more_output [])) (def: (on_error state) - (exception.throw shell.no_more_output [])) + (exception.except shell.no_more_output [])) (def: (on_write input state) (#try.Failure "on_write")) (def: (on_destroy state) @@ -82,13 +82,13 @@ (implementation (def: (on_read state) (if error? - (exception.throw shell.no_more_output []) + (exception.except shell.no_more_output []) (case state (#.Cons head tail) (#try.Success [tail head]) #.Nil - (exception.throw shell.no_more_output [])))) + (exception.except shell.no_more_output [])))) (def: (on_error state) (if error? (case state @@ -96,8 +96,8 @@ (#try.Success [tail head]) #.Nil - (exception.throw shell.no_more_output [])) - (exception.throw shell.no_more_output []))) + (exception.except shell.no_more_output [])) + (exception.except shell.no_more_output []))) (def: (on_write input state) (#try.Failure "on_write")) (def: (on_destroy state) @@ -114,12 +114,12 @@ #///artifact.version lux_version} #///dependency.type ///artifact/type.js_library}]] (`` ($_ random.either - (wrap js_compiler) + (in js_compiler) (~~ (template [<compiler>] - [(wrap {#///dependency.artifact {#///artifact.group /.lux_group - #///artifact.name <compiler> - #///artifact.version lux_version} - #///dependency.type ///artifact/type.lux_library})] + [(in {#///dependency.artifact {#///artifact.group /.lux_group + #///artifact.name <compiler> + #///artifact.version lux_version} + #///dependency.type ///artifact/type.lux_library})] [/.jvm_compiler_name] [/.python_compiler_name] @@ -132,9 +132,9 @@ (do random.monad [dependency ..compiler [_ package] $///package.random] - (wrap [dependency - (|> ///dependency/resolution.empty - (dictionary.put dependency package))]))) + (in [dependency + (|> ///dependency/resolution.empty + (dictionary.put dependency package))]))) (def: #export test Test @@ -159,61 +159,61 @@ with_program with_target)]] ($_ _.and - (wrap (do async.monad - [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty - (with_target empty_profile))] - (_.cover' [/.no_specified_program] - (case outcome - (#try.Success _) - false + (in (do async.monad + [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty + (with_target empty_profile))] + (_.cover' [/.no_specified_program] + (case outcome + (#try.Success _) + false - (#try.Failure error) - (exception.match? /.no_specified_program error))))) - (wrap (do async.monad - [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty profile)] - (_.cover' [/.Compiler /.no_available_compiler] - (case outcome - (#try.Success _) - false + (#try.Failure error) + (exception.match? /.no_specified_program error))))) + (in (do async.monad + [outcome (/.do! (@version.echo "") (program.async (program.mock environment.empty home working_directory)) fs shell ///dependency/resolution.empty profile)] + (_.cover' [/.Compiler /.no_available_compiler] + (case outcome + (#try.Success _) + false - (#try.Failure error) - (exception.match? /.no_available_compiler error))))) + (#try.Failure error) + (exception.match? /.no_available_compiler error))))) (do ! [#let [console (@version.echo "")] [compiler resolution] ..resolution] - (wrap (do async.monad - [verdict (do ///action.monad - [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) - fs shell resolution - (set@ #///.compiler compiler profile)) - start (\ console read_line []) - end (\ console read_line [])] - (wrap (and (text\= /.start start) - (text\= /.success end))))] - (_.cover' [/.do! - /.lux_group - /.jvm_compiler_name - /.js_compiler_name - /.python_compiler_name - /.lua_compiler_name - /.ruby_compiler_name - /.start - /.success] - (try.default false verdict))))) + (in (do async.monad + [verdict (do ///action.monad + [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) + fs shell resolution + (set@ #///.compiler compiler profile)) + start (\ console read_line []) + end (\ console read_line [])] + (in (and (text\= /.start start) + (text\= /.success end))))] + (_.cover' [/.do! + /.lux_group + /.jvm_compiler_name + /.js_compiler_name + /.python_compiler_name + /.lua_compiler_name + /.ruby_compiler_name + /.start + /.success] + (try.default false verdict))))) (do ! [#let [console (@version.echo "")] [compiler resolution] ..resolution] - (wrap (do async.monad - [verdict (do ///action.monad - [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) - fs (shell.async (..bad_shell [])) resolution - (set@ #///.compiler compiler profile)) - start (\ console read_line []) - end (\ console read_line [])] - (wrap (and (text\= /.start start) - (text\= /.failure end))))] - (_.cover' [/.failure] - (try.default false verdict))))) + (in (do async.monad + [verdict (do ///action.monad + [_ (/.do! console (program.async (program.mock environment.empty home working_directory)) + fs (shell.async (..bad_shell [])) resolution + (set@ #///.compiler compiler profile)) + start (\ console read_line []) + end (\ console read_line [])] + (in (and (text\= /.start start) + (text\= /.failure end))))] + (_.cover' [/.failure] + (try.default false verdict))))) (do ! [expected/0 (random.ascii/alpha 5) expected/1 (random.ascii/alpha 5) @@ -224,26 +224,26 @@ shell (|> (list expected/0 expected/1 expected/2) (..reader_shell <error?>) shell.async)] - (wrap (do {! async.monad} - [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 []) - (\ ! map (|>> (case> (#try.Failure error) - true - - (#try.Success _) - false) - #try.Success)))] - (wrap (and (text\= expected/0 actual/0) - (text\= expected/1 actual/1) - (text\= expected/2 actual/2) - end!)))] - (_.cover' [<log!>] - (try.default false verdict)))))] + (in (do {! async.monad} + [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 []) + (\ ! map (|>> (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) + end!)))] + (_.cover' [<log!>] + (try.default false verdict)))))] [#0 /.log_output!] [#1 /.log_error!] diff --git a/stdlib/source/test/aedifex/command/clean.lux b/stdlib/source/test/aedifex/command/clean.lux index 568c6fb76..238fa824b 100644 --- a/stdlib/source/test/aedifex/command/clean.lux +++ b/stdlib/source/test/aedifex/command/clean.lux @@ -46,8 +46,8 @@ [count (\ ! map (n.% 10) random.nat) names (random.set text.hash count ..node_name) contents (random.list count ($binary.random 100))] - (wrap (list.zipped/2 (list\map (|>> (format prefix)) (set.to_list names)) - contents)))) + (in (list.zipped/2 (list\map (|>> (format prefix)) (set.to_list names)) + contents)))) (def: (create_file! fs [path content]) (-> (file.System Async) [Path Binary] (Async (Try Any))) @@ -59,15 +59,15 @@ [_ (: (Async (Try Any)) (file.make_directories async.monad fs path)) _ (monad.map ! (..create_file! fs) files)] - (wrap []))) + (in []))) (def: (directory_exists? fs) (-> (file.System Async) Path (Async (Try Bit))) - (|>> (\ fs directory?) (try.lift async.monad))) + (|>> (\ fs directory?) (try.lifted async.monad))) (def: (file_exists? fs) (-> (file.System Async) Path (Async (Try Bit))) - (|>> (\ fs file?) (try.lift async.monad))) + (|>> (\ fs file?) (try.lifted async.monad))) (def: (assets_exist? fs directory_path files) (-> (file.System Async) Path (List [Path Binary]) (Async (Try Bit))) @@ -77,8 +77,8 @@ (|> files (list\map product.left) (monad.map ///action.monad (..file_exists? fs))))] - (wrap (and directory_exists? - (list.every? (|>>) files_exist?))))) + (in (and directory_exists? + (list.every? (|>>) files_exist?))))) (def: #export test Test @@ -95,25 +95,25 @@ sub_files (..files (format sub_path /)) dummy @profile.random] - (wrap (do async.monad - [#let [console (@version.echo "")] - verdict (do {! (try.with async.monad)} - [_ (..create_directory! fs target_path direct_files) - _ (..create_directory! fs sub_path sub_files) - context_exists!/pre (..directory_exists? fs context) - target_exists!/pre (..assets_exist? fs target_path direct_files) - sub_exists!/pre (..assets_exist? fs sub_path sub_files) - _ (/.do! console fs (set@ #///.target target_path dummy)) - 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 [])] - (wrap (and (and context_exists!/pre - context_exists!/post) - (and target_exists!/pre - (not target_exists!/post)) - (and sub_exists!/pre - (not sub_exists!/post)) - (text\= (/.success target_path) logging))))] - (_.cover' [/.do! /.success] - (try.default false verdict))))))) + (in (do async.monad + [#let [console (@version.echo "")] + verdict (do {! (try.with async.monad)} + [_ (..create_directory! fs target_path direct_files) + _ (..create_directory! fs sub_path sub_files) + context_exists!/pre (..directory_exists? fs context) + target_exists!/pre (..assets_exist? fs target_path direct_files) + sub_exists!/pre (..assets_exist? fs sub_path sub_files) + _ (/.do! console fs (set@ #///.target target_path dummy)) + 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 [])] + (in (and (and context_exists!/pre + context_exists!/post) + (and target_exists!/pre + (not target_exists!/post)) + (and sub_exists!/pre + (not sub_exists!/post)) + (text\= (/.success target_path) logging))))] + (_.cover' [/.do! /.success] + (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/deploy.lux b/stdlib/source/test/aedifex/command/deploy.lux index e2f7cfa4a..41a997d6f 100644 --- a/stdlib/source/test/aedifex/command/deploy.lux +++ b/stdlib/source/test/aedifex/command/deploy.lux @@ -67,8 +67,8 @@ (random.one (function (_ profile) (do maybe.monad [artifact (get@ #///.identity profile) - expected_pom (try.to_maybe (///pom.write profile))] - (wrap [artifact expected_pom profile]))) + expected_pom (try.maybe (///pom.write profile))] + (in [artifact expected_pom profile]))) $profile.random) home (random.ascii/alpha 5) @@ -77,52 +77,52 @@ $repository.empty) fs (file.mock (\ file.default separator)) program (program.async (program.mock environment.empty home working_directory))]] - (wrap (do {! async.monad} - [verdict (do {! ///action.monad} - [logging (..execute! program repository fs artifact profile) - expected_library (|> profile - (get@ #///.sources) - set.to_list - (export.library fs) - (\ ! map (format.run tar.writer))) + (in (do {! async.monad} + [verdict (do {! ///action.monad} + [logging (..execute! program repository fs artifact profile) + expected_library (|> profile + (get@ #///.sources) + set.to_list + (export.library fs) + (\ ! map (format.run tar.writer))) - actual_pom (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact ///artifact/extension.pom)) - actual_library (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact ///artifact/extension.lux_library)) - actual_sha-1 (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.sha-1))) - actual_sha-1 (\ async.monad wrap - (do try.monad - [actual_sha-1 (\ utf8.codec decode actual_sha-1)] - (\ ///hash.sha-1_codec decode actual_sha-1))) - actual_md5 (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.md5))) - actual_md5 (\ async.monad wrap + actual_pom (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact ///artifact/extension.pom)) + actual_library (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact ///artifact/extension.lux_library)) + actual_sha-1 (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.sha-1))) + actual_sha-1 (\ async.monad in (do try.monad - [actual_md5 (\ utf8.codec decode actual_md5)] - (\ ///hash.md5_codec decode actual_md5))) + [actual_sha-1 (\ utf8.codec decode actual_sha-1)] + (\ ///hash.sha-1_codec decode actual_sha-1))) + actual_md5 (\ repository download (///repository/remote.uri (get@ #///artifact.version artifact) artifact (format ///artifact/extension.lux_library ///artifact/extension.md5))) + actual_md5 (\ async.monad in + (do try.monad + [actual_md5 (\ utf8.codec decode actual_md5)] + (\ ///hash.md5_codec decode actual_md5))) - #let [succeeded! - (text\= /.success logging) + #let [succeeded! + (text\= /.success logging) - deployed_library! - (binary\= expected_library - actual_library) + deployed_library! + (binary\= expected_library + actual_library) - deployed_pom! - (binary\= (|> expected_pom (\ xml.codec encode) (\ utf8.codec encode)) - actual_pom) + deployed_pom! + (binary\= (|> expected_pom (\ xml.codec encode) (\ utf8.codec encode)) + actual_pom) - deployed_sha-1! - (\ ///hash.equivalence = - (///hash.sha-1 expected_library) - actual_sha-1) + deployed_sha-1! + (\ ///hash.equivalence = + (///hash.sha-1 expected_library) + actual_sha-1) - deployed_md5! - (\ ///hash.equivalence = - (///hash.md5 expected_library) - actual_md5)]] - (wrap (and succeeded! - deployed_library! - deployed_pom! - deployed_sha-1! - deployed_md5!)))] - (_.cover' [/.do! /.success] - (try.default false verdict))))))) + deployed_md5! + (\ ///hash.equivalence = + (///hash.md5 expected_library) + actual_md5)]] + (in (and succeeded! + deployed_library! + deployed_pom! + deployed_sha-1! + deployed_md5!)))] + (_.cover' [/.do! /.success] + (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/deps.lux b/stdlib/source/test/aedifex/command/deps.lux index 1a54ae89d..c00c88078 100644 --- a/stdlib/source/test/aedifex/command/deps.lux +++ b/stdlib/source/test/aedifex/command/deps.lux @@ -95,36 +95,36 @@ fs (file.mock (\ file.default separator)) program (program.async (program.mock environment.empty home working_directory))]] - (wrap (do async.monad - [verdict (do ///action.monad - [#let [console (@version.echo "") - local (///repository/local.repository program fs)] - pre (|> ///dependency/resolution.empty - (dictionary.put dependee dependee_package) - (///dependency/deployment.all local)) - post (|> (\ ///.monoid identity) - (set@ #///.dependencies (set.of_list ///dependency.hash (list dependee depender))) - (/.do! console local - (list (///repository.mock ($///dependency/resolution.single depender_artifact depender_package) - [])) - (function (_ url) - (///repository.mock $///dependency/resolution.nope [])))) + (in (do async.monad + [verdict (do ///action.monad + [#let [console (@version.echo "") + local (///repository/local.repository program fs)] + pre (|> ///dependency/resolution.empty + (dictionary.put dependee dependee_package) + (///dependency/deployment.all local)) + post (|> (\ ///.monoid identity) + (set@ #///.dependencies (set.of_list ///dependency.hash (list dependee depender))) + (/.do! console local + (list (///repository.mock ($///dependency/resolution.single depender_artifact depender_package) + [])) + (function (_ url) + (///repository.mock $///dependency/resolution.nope [])))) - #let [had_dependee_before! - (set.member? pre dependee_artifact) + #let [had_dependee_before! + (set.member? pre dependee_artifact) - lacked_depender_before! - (not (set.member? pre depender_artifact)) + lacked_depender_before! + (not (set.member? pre depender_artifact)) - had_dependee_after! - (dictionary.key? post dependee) + had_dependee_after! + (dictionary.key? post dependee) + + had_depender_after! + (dictionary.key? post depender)]] + (in (and had_dependee_before! + lacked_depender_before! - had_depender_after! - (dictionary.key? post depender)]] - (wrap (and had_dependee_before! - lacked_depender_before! - - had_dependee_after! - had_depender_after!)))] - (_.cover' [/.do!] - (try.default false verdict))))))) + had_dependee_after! + had_depender_after!)))] + (_.cover' [/.do!] + (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/command/install.lux b/stdlib/source/test/aedifex/command/install.lux index 3ba225206..a9de141ff 100644 --- a/stdlib/source/test/aedifex/command/install.lux +++ b/stdlib/source/test/aedifex/command/install.lux @@ -71,35 +71,35 @@ working_directory (random.ascii/alpha 5) #let [/ (\ file.default separator)]] ($_ _.and - (wrap (do {! async.monad} - [#let [fs (file.mock /) - program (program.async (program.mock environment.empty home working_directory)) + (in (do {! async.monad} + [#let [fs (file.mock /) + program (program.async (program.mock environment.empty home working_directory)) - artifact_path (///local.uri (get@ #///artifact.version identity) identity) - library_path (format artifact_path ///artifact/extension.lux_library) - pom_path (format artifact_path ///artifact/extension.pom)] - verdict (do {! ///action.monad} - [succeeded! (\ ! map (text\= /.success) - (..execute! program fs sample)) - library_exists! (|> library_path - (format home /) - (\ fs file?) - (\ async.monad map exception.return)) - pom_exists! (|> pom_path - (format home /) - (\ fs file?) - (\ async.monad map exception.return))] - (wrap (and succeeded! - library_exists! - pom_exists!)))] - (_.cover' [/.do! /.success] - (try.default false verdict)))) - (wrap (do {! async.monad} - [#let [fs (file.mock /) - program (program.async (program.mock environment.empty home working_directory))] - logging (..execute! program fs (set@ #///.identity #.None sample))] - (_.cover' [/.failure] - (|> logging - (try\map (text\= /.failure)) - (try.default false))))) + artifact_path (///local.uri (get@ #///artifact.version identity) identity) + library_path (format artifact_path ///artifact/extension.lux_library) + pom_path (format artifact_path ///artifact/extension.pom)] + verdict (do {! ///action.monad} + [succeeded! (\ ! map (text\= /.success) + (..execute! program fs sample)) + library_exists! (|> library_path + (format home /) + (\ fs file?) + (\ async.monad map exception.return)) + pom_exists! (|> pom_path + (format home /) + (\ fs file?) + (\ async.monad map exception.return))] + (in (and succeeded! + library_exists! + pom_exists!)))] + (_.cover' [/.do! /.success] + (try.default false verdict)))) + (in (do {! async.monad} + [#let [fs (file.mock /) + program (program.async (program.mock environment.empty home working_directory))] + logging (..execute! program fs (set@ #///.identity #.None sample))] + (_.cover' [/.failure] + (|> logging + (try\map (text\= /.failure)) + (try.default false))))) )))) diff --git a/stdlib/source/test/aedifex/command/pom.lux b/stdlib/source/test/aedifex/command/pom.lux index 4ee1c49f4..ebc0ae09e 100644 --- a/stdlib/source/test/aedifex/command/pom.lux +++ b/stdlib/source/test/aedifex/command/pom.lux @@ -36,35 +36,35 @@ (do random.monad [sample @profile.random #let [fs (file.mock (\ file.default separator))]] - (wrap (do {! async.monad} - [#let [console (@version.echo "")] - outcome (/.do! console fs sample)] - (case outcome - (#try.Success _) - (do ! - [verdict (do ///action.monad - [expected (|> (///pom.write sample) - (try\map (|>> (\ xml.codec encode) - (\ utf8.codec encode))) - (\ ! wrap)) - actual (\ fs read ///pom.file) + (in (do {! async.monad} + [#let [console (@version.echo "")] + outcome (/.do! console fs sample)] + (case outcome + (#try.Success _) + (do ! + [verdict (do ///action.monad + [expected (|> (///pom.write sample) + (try\map (|>> (\ xml.codec encode) + (\ utf8.codec encode))) + (\ ! in)) + actual (\ fs read ///pom.file) - logging! (\ ///action.monad map - (text\= /.success) - (\ console read_line [])) + logging! (\ ///action.monad map + (text\= /.success) + (\ console read_line [])) - #let [expected_content! - (binary\= expected actual)]] - (wrap (and logging! - expected_content!)))] - (_.cover' [/.do! /.success] - (try.default false verdict))) - - (#try.Failure error) - (_.cover' [/.do!] - (case (get@ #///.identity sample) - (#.Some _) - false + #let [expected_content! + (binary\= expected actual)]] + (in (and logging! + expected_content!)))] + (_.cover' [/.do! /.success] + (try.default false verdict))) + + (#try.Failure error) + (_.cover' [/.do!] + (case (get@ #///.identity sample) + (#.Some _) + false - #.None - true)))))))) + #.None + true)))))))) diff --git a/stdlib/source/test/aedifex/command/test.lux b/stdlib/source/test/aedifex/command/test.lux index 5882992a9..93c6642f7 100644 --- a/stdlib/source/test/aedifex/command/test.lux +++ b/stdlib/source/test/aedifex/command/test.lux @@ -61,55 +61,55 @@ ($_ _.and (let [fs (file.mock (\ file.default separator)) console (@version.echo "")] - (wrap (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 - (set@ #///.compiler compiler profile)) - build_start (\ console read_line []) - build_end (\ console read_line []) - test_start (\ console read_line []) - test_end (\ console read_line [])] - (wrap (and (and (text\= //build.start build_start) - (text\= //build.success build_end)) - (and (text\= /.start test_start) - (text\= /.success test_end)))))] - (_.cover' [/.do! - /.start /.success] - (try.default false verdict))))) + (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 + (set@ #///.compiler compiler profile)) + build_start (\ console read_line []) + build_end (\ console read_line []) + test_start (\ console read_line []) + test_end (\ console read_line [])] + (in (and (and (text\= //build.start build_start) + (text\= //build.success build_end)) + (and (text\= /.start test_start) + (text\= /.success test_end)))))] + (_.cover' [/.do! + /.start /.success] + (try.default false verdict))))) (let [fs (file.mock (\ file.default separator)) console (@version.echo "")] - (wrap (do async.monad - [verdict (do ///action.monad - [#let [bad_shell (shell.mock - (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) - (#try.Success - (: (shell.Mock []) - (implementation - (def: (on_read state) - (exception.throw shell.no_more_output [])) - (def: (on_error state) - (exception.throw shell.no_more_output [])) - (def: (on_write input state) - (#try.Failure "on_write")) - (def: (on_destroy state) - (#try.Failure "on_destroy")) - (def: (on_await state) - (#try.Success [state (if (list.any? (text\= "build") actual_arguments) - shell.normal - shell.error)])))))) - [])] - _ (/.do! console (program.async (program.mock environment.empty home working_directory)) - fs (shell.async bad_shell) resolution - (set@ #///.compiler compiler profile)) - build_start (\ console read_line []) - build_end (\ console read_line []) - test_start (\ console read_line []) - test_end (\ console read_line [])] - (wrap (and (and (text\= //build.start build_start) - (text\= //build.success build_end)) - (and (text\= /.start test_start) - (text\= /.failure test_end)))))] - (_.cover' [/.failure] - (try.default false verdict))))) + (in (do async.monad + [verdict (do ///action.monad + [#let [bad_shell (shell.mock + (function (_ [actual_environment actual_working_directory actual_command actual_arguments]) + (#try.Success + (: (shell.Mock []) + (implementation + (def: (on_read state) + (exception.except shell.no_more_output [])) + (def: (on_error state) + (exception.except shell.no_more_output [])) + (def: (on_write input state) + (#try.Failure "on_write")) + (def: (on_destroy state) + (#try.Failure "on_destroy")) + (def: (on_await state) + (#try.Success [state (if (list.any? (text\= "build") actual_arguments) + shell.normal + shell.error)])))))) + [])] + _ (/.do! console (program.async (program.mock environment.empty home working_directory)) + fs (shell.async bad_shell) resolution + (set@ #///.compiler compiler profile)) + build_start (\ console read_line []) + build_end (\ console read_line []) + test_start (\ console read_line []) + test_end (\ console read_line [])] + (in (and (and (text\= //build.start build_start) + (text\= //build.success build_end)) + (and (text\= /.start test_start) + (text\= /.failure test_end)))))] + (_.cover' [/.failure] + (try.default false verdict))))) )))) diff --git a/stdlib/source/test/aedifex/command/version.lux b/stdlib/source/test/aedifex/command/version.lux index 739a02fef..30c7d3f80 100644 --- a/stdlib/source/test/aedifex/command/version.lux +++ b/stdlib/source/test/aedifex/command/version.lux @@ -39,23 +39,23 @@ (do maybe.monad [head (text.nth 0 state) [_ tail] (text.split 1 state)] - (wrap [[open? tail] head]))) - (exception.throw ..console_is_closed! []))) + (in [[open? tail] head]))) + (exception.except ..console_is_closed! []))) (def: (on_read_line [open? state]) (if open? (try.of_maybe (do maybe.monad [[output state] (text.split_with text.new_line state)] - (wrap [[open? state] output]))) - (exception.throw ..console_is_closed! []))) + (in [[open? state] output]))) + (exception.except ..console_is_closed! []))) (def: (on_write input [open? state]) (if open? (#try.Success [open? (format state input)]) - (exception.throw ..console_is_closed! []))) + (exception.except ..console_is_closed! []))) (def: (on_close [open? buffer]) (if open? (#try.Success [false buffer]) - (exception.throw ..console_is_closed! [])))) + (exception.except ..console_is_closed! [])))) (def: #export echo (-> Text (Console Async)) @@ -68,12 +68,12 @@ (<| (_.covering /._) (do random.monad [profile @profile.random] - (wrap (do async.monad - [#let [console (..echo "")] - verdict (do (try.with async.monad) - [_ (/.do! console profile) - logging (\ console read_line [])] - (wrap (text\= (version.format language/lux.version) - logging)))] - (_.cover' [/.do!] - (try.default false verdict))))))) + (in (do async.monad + [#let [console (..echo "")] + verdict (do (try.with async.monad) + [_ (/.do! console profile) + logging (\ console read_line [])] + (in (text\= (version.format language/lux.version) + logging)))] + (_.cover' [/.do!] + (try.default false verdict))))))) |