From 061fd8a209bbcaffc2bfb850ac6046752a567d50 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 27 Jul 2021 03:51:10 -0400 Subject: Re-named wrap => in && unwrap => out. --- stdlib/source/test/aedifex/artifact/snapshot.lux | 2 +- .../aedifex/artifact/snapshot/version/value.lux | 2 +- stdlib/source/test/aedifex/artifact/time.lux | 2 +- stdlib/source/test/aedifex/artifact/time/date.lux | 2 +- stdlib/source/test/aedifex/artifact/type.lux | 10 +- stdlib/source/test/aedifex/cache.lux | 66 ++++---- stdlib/source/test/aedifex/cli.lux | 14 +- stdlib/source/test/aedifex/command/auto.lux | 58 +++---- stdlib/source/test/aedifex/command/build.lux | 166 ++++++++++---------- stdlib/source/test/aedifex/command/clean.lux | 58 +++---- stdlib/source/test/aedifex/command/deploy.lux | 88 +++++------ stdlib/source/test/aedifex/command/deps.lux | 58 +++---- stdlib/source/test/aedifex/command/install.lux | 60 ++++---- stdlib/source/test/aedifex/command/pom.lux | 58 +++---- stdlib/source/test/aedifex/command/test.lux | 98 ++++++------ stdlib/source/test/aedifex/command/version.lux | 30 ++-- .../source/test/aedifex/dependency/deployment.lux | 60 ++++---- .../source/test/aedifex/dependency/resolution.lux | 167 ++++++++++----------- stdlib/source/test/aedifex/dependency/status.lux | 2 +- stdlib/source/test/aedifex/input.lux | 32 ++-- stdlib/source/test/aedifex/metadata/artifact.lux | 48 +++--- stdlib/source/test/aedifex/metadata/snapshot.lux | 50 +++--- stdlib/source/test/aedifex/package.lux | 8 +- stdlib/source/test/aedifex/profile.lux | 14 +- stdlib/source/test/aedifex/project.lux | 2 +- stdlib/source/test/aedifex/repository.lux | 8 +- stdlib/source/test/aedifex/repository/local.lux | 22 +-- stdlib/source/test/aedifex/runtime.lux | 10 +- 28 files changed, 595 insertions(+), 600 deletions(-) (limited to 'stdlib/source/test/aedifex') diff --git a/stdlib/source/test/aedifex/artifact/snapshot.lux b/stdlib/source/test/aedifex/artifact/snapshot.lux index 5f29620c9..931fefd17 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot.lux @@ -22,7 +22,7 @@ (def: #export random (Random /.Snapshot) - (random.or (random\wrap []) + (random.or (random\in []) $/stamp.random)) (def: #export test diff --git a/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux b/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux index c55b71cd1..cfd8a7f17 100644 --- a/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux +++ b/stdlib/source/test/aedifex/artifact/snapshot/version/value.lux @@ -32,7 +32,7 @@ (Random /.Value) ($_ random.and (random.ascii/alpha 5) - (random.or (random\wrap []) + (random.or (random\in []) $///stamp.random) )) diff --git a/stdlib/source/test/aedifex/artifact/time.lux b/stdlib/source/test/aedifex/artifact/time.lux index 8873a7f1d..9ac9be6ae 100644 --- a/stdlib/source/test/aedifex/artifact/time.lux +++ b/stdlib/source/test/aedifex/artifact/time.lux @@ -27,7 +27,7 @@ (do random.monad [date /date.random time /time.random] - (wrap [date time]))) + (in [date time]))) (def: #export test Test diff --git a/stdlib/source/test/aedifex/artifact/time/date.lux b/stdlib/source/test/aedifex/artifact/time/date.lux index 35ae3a157..4d44b5358 100644 --- a/stdlib/source/test/aedifex/artifact/time/date.lux +++ b/stdlib/source/test/aedifex/artifact/time/date.lux @@ -25,7 +25,7 @@ (def: #export random (Random /.Date) (random.one (function (_ raw) - (try.to_maybe + (try.maybe (do try.monad [year (|> raw date.year year.value i.abs (i.% +9,000) (i.+ +1,000) year.year) raw (date.date year diff --git a/stdlib/source/test/aedifex/artifact/type.lux b/stdlib/source/test/aedifex/artifact/type.lux index 017e417cb..b34db299c 100644 --- a/stdlib/source/test/aedifex/artifact/type.lux +++ b/stdlib/source/test/aedifex/artifact/type.lux @@ -20,12 +20,12 @@ (Random /.Type) ($_ random.either ($_ random.either - (random\wrap /.lux_library) - (random\wrap /.jvm_library)) + (random\in /.lux_library) + (random\in /.jvm_library)) ($_ random.either - (random\wrap /.pom) - (random\wrap /.md5) - (random\wrap /.sha-1)) + (random\in /.pom) + (random\in /.md5) + (random\in /.sha-1)) )) (def: #export test diff --git a/stdlib/source/test/aedifex/cache.lux b/stdlib/source/test/aedifex/cache.lux index 19fd23203..2a2d3d2e4 100644 --- a/stdlib/source/test/aedifex/cache.lux +++ b/stdlib/source/test/aedifex/cache.lux @@ -48,8 +48,8 @@ (def: type (Random Type) ($_ random.either - (random\wrap //artifact/type.lux_library) - (random\wrap //artifact/type.jvm_library))) + (random\in //artifact/type.lux_library) + (random\in //artifact/type.jvm_library))) (def: profile (Random [Artifact Profile XML]) @@ -58,7 +58,7 @@ (do try.monad [pom (//pom.write profile) identity (try.of_maybe (get@ #//.identity profile))] - (wrap [identity profile pom])))) + (in [identity profile pom])))) @profile.random)) (def: content @@ -73,9 +73,9 @@ [[identity profile pom] ..profile type ..type content ..content] - (wrap [{#//dependency.artifact identity - #//dependency.type type} - (set@ #//package.origin (#//repository/origin.Remote "") (//package.local pom content))]))) + (in [{#//dependency.artifact identity + #//dependency.type type} + (set@ #//package.origin (#//repository/origin.Remote "") (//package.local pom content))]))) (def: resolution (Random Resolution) @@ -94,9 +94,9 @@ try.to_maybe)) ..profile) content ..content] - (wrap [dependency - (set@ #//package.origin (#//repository/origin.Remote "") (//package.local pom content))])))))] - (wrap (dictionary.of_list //dependency.hash (list& [main_dependency main_package] dependencies))))) + (in [dependency + (set@ #//package.origin (#//repository/origin.Remote "") (//package.local pom content))])))))] + (in (dictionary.of_list //dependency.hash (list& [main_dependency main_package] dependencies))))) (def: singular Test @@ -107,17 +107,17 @@ #let [fs (: (file.System Async) (file.mock (\ file.default separator))) program (program.async (program.mock environment.empty home working_directory))]] - (wrap (do async.monad - [wrote! (/.write_one program fs dependency expected_package) - read! (/.read_one program fs dependency)] - (_.cover' [/.write_one /.read_one] - (<| (try.default false) - (do try.monad - [_ wrote! - actual_package read!] - (wrap (\ //package.equivalence = - (set@ #//package.origin (#//repository/origin.Local "") expected_package) - actual_package))))))))) + (in (do async.monad + [wrote! (/.write_one program fs dependency expected_package) + read! (/.read_one program fs dependency)] + (_.cover' [/.write_one /.read_one] + (<| (try.default false) + (do try.monad + [_ wrote! + actual_package read!] + (in (\ //package.equivalence = + (set@ #//package.origin (#//repository/origin.Local "") expected_package) + actual_package))))))))) (def: plural Test @@ -128,19 +128,19 @@ #let [fs (: (file.System Async) (file.mock (\ file.default separator))) program (program.async (program.mock environment.empty home working_directory))]] - (wrap (do async.monad - [wrote! (/.write_all program fs expected) - read! (/.read_all program fs (dictionary.keys expected) //dependency/resolution.empty)] - (_.cover' [/.write_all /.read_all] - (<| (try.default false) - (do try.monad - [_ wrote! - actual read!] - (wrap (\ //dependency/resolution.equivalence = - (\ dictionary.functor map - (set@ #//package.origin (#//repository/origin.Local "")) - expected) - actual))))))))) + (in (do async.monad + [wrote! (/.write_all program fs expected) + read! (/.read_all program fs (dictionary.keys expected) //dependency/resolution.empty)] + (_.cover' [/.write_all /.read_all] + (<| (try.default false) + (do try.monad + [_ wrote! + actual read!] + (in (\ //dependency/resolution.equivalence = + (\ dictionary.functor map + (set@ #//package.origin (#//repository/origin.Local "")) + expected) + actual))))))))) (def: #export test Test diff --git a/stdlib/source/test/aedifex/cli.lux b/stdlib/source/test/aedifex/cli.lux index 6f83f5a11..6c251b0a4 100644 --- a/stdlib/source/test/aedifex/cli.lux +++ b/stdlib/source/test/aedifex/cli.lux @@ -22,22 +22,22 @@ (def: compilation (Random /.Compilation) - (random.or (random\wrap []) - (random\wrap []))) + (random.or (random\in []) + (random\in []))) (def: command (Random /.Command) ($_ random.or ## #Version - (random\wrap []) + (random\in []) ## #Clean - (random\wrap []) + (random\in []) ## #POM - (random\wrap []) + (random\in []) ## #Dependencies - (random\wrap []) + (random\in []) ## #Install - (random\wrap []) + (random\in []) ## #Deploy ($_ random.and (random.ascii/alpha 1) 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 [] - [(wrap {#///dependency.artifact {#///artifact.group /.lux_group - #///artifact.name - #///artifact.version lux_version} - #///dependency.type ///artifact/type.lux_library})] + [(in {#///dependency.artifact {#///artifact.group /.lux_group + #///artifact.name + #///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 ) shell.async)] - (wrap (do {! async.monad} - [verdict (do ///action.monad - [process (shell [environment.empty working_directory "" (list "")]) - _ ( 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' [] - (try.default false verdict)))))] + (in (do {! async.monad} + [verdict (do ///action.monad + [process (shell [environment.empty working_directory "" (list "")]) + _ ( 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' [] + (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))))))) diff --git a/stdlib/source/test/aedifex/dependency/deployment.lux b/stdlib/source/test/aedifex/dependency/deployment.lux index 218bbaf07..3688e56aa 100644 --- a/stdlib/source/test/aedifex/dependency/deployment.lux +++ b/stdlib/source/test/aedifex/dependency/deployment.lux @@ -72,8 +72,8 @@ (atom.update (dictionary.put url input) cache) _ - (wrap [])))] - (wrap (#try.Success ..good_upload)))))) + (in [])))] + (in (#try.Success ..good_upload)))))) (def: (verify_one expected_deployments address package cache expected_artifact actual_artifact) (-> Nat URL Package (Dictionary URL Binary) Artifact Artifact Bit) @@ -141,7 +141,7 @@ dependency (: Dependency [artifact artifact/type.lux_library])]] - (wrap [dependency artifact package]))) + (in [dependency artifact package]))) (def: #export test Test @@ -156,13 +156,13 @@ (atom.atom (dictionary.new text.hash))) http (..http cache) repository (repository.async (remote.repository http #.None address))]] - (wrap (do async.monad - [?outcome (/.one repository dependency package) - cache (async.future (atom.read cache))] - (_.cover' [/.one] - (|> ?outcome - (try\map (verify_one 1 address package cache expected_artifact)) - (try.default false)))))) + (in (do async.monad + [?outcome (/.one repository dependency package) + cache (async.future (atom.read cache))] + (_.cover' [/.one] + (|> ?outcome + (try\map (verify_one 1 address package cache expected_artifact)) + (try.default false)))))) (do {! random.monad} [#let [hash (: (Hash [Dependency Artifact Package]) (\ hash.functor map (|>> product.right product.left product.left) @@ -179,26 +179,26 @@ (atom.atom (dictionary.new text.hash))) http (..http cache) repository (repository.async (remote.repository http #.None address))]] - (wrap (do async.monad - [?outcome (/.all repository resolution) - cache (async.future (atom.read cache))] - (_.cover' [/.all] - (|> ?outcome - (try\map (function (_ actual_artifacts) - (let [expected_deployments! - (n.= num_bundles (set.size actual_artifacts)) + (in (do async.monad + [?outcome (/.all repository resolution) + cache (async.future (atom.read cache))] + (_.cover' [/.all] + (|> ?outcome + (try\map (function (_ actual_artifacts) + (let [expected_deployments! + (n.= num_bundles (set.size actual_artifacts)) - every_deployment_was_correct! - (list.every? (function (_ [dependency expected_artifact package]) - (let [deployed! - (set.member? actual_artifacts expected_artifact) + every_deployment_was_correct! + (list.every? (function (_ [dependency expected_artifact package]) + (let [deployed! + (set.member? actual_artifacts expected_artifact) - deployed_correctly! - (verify_one num_bundles address package cache expected_artifact expected_artifact)] - (and deployed! - deployed_correctly!))) - bundles)] - (and expected_deployments! - every_deployment_was_correct!)))) - (try.default false)))))) + deployed_correctly! + (verify_one num_bundles address package cache expected_artifact expected_artifact)] + (and deployed! + deployed_correctly!))) + bundles)] + (and expected_deployments! + every_deployment_was_correct!)))) + (try.default false)))))) )))) diff --git a/stdlib/source/test/aedifex/dependency/resolution.lux b/stdlib/source/test/aedifex/dependency/resolution.lux index ea468f851..fa0391761 100644 --- a/stdlib/source/test/aedifex/dependency/resolution.lux +++ b/stdlib/source/test/aedifex/dependency/resolution.lux @@ -53,10 +53,10 @@ (do {! random.monad} [artifact $///artifact.random [_ package] $///package.random] - (wrap (dictionary.put {#///dependency.artifact artifact - #///dependency.type ///artifact/type.lux_library} - package - /.empty)))) + (in (dictionary.put {#///dependency.artifact artifact + #///dependency.type ///artifact/type.lux_library} + package + /.empty)))) (def: lux_sha-1 Text @@ -258,33 +258,31 @@ bad_sha-1 (..bad_sha-1 expected_artifact expected_package dummy_package) bad_md5 (..bad_md5 expected_artifact expected_package dummy_package)]] (`` ($_ _.and - (wrap - (do async.monad - [actual_package (/.one (///repository.mock good []) - {#///dependency.artifact expected_artifact - #///dependency.type ///artifact/type.lux_library})] - (_.cover' [/.one] - (case actual_package - (#try.Success actual_package) - (\ ///package.equivalence = - (set@ #///package.origin (#///repository/origin.Remote "") expected_package) - actual_package) - - (#try.Failure _) - false)))) + (in (do async.monad + [actual_package (/.one (///repository.mock good []) + {#///dependency.artifact expected_artifact + #///dependency.type ///artifact/type.lux_library})] + (_.cover' [/.one] + (case actual_package + (#try.Success actual_package) + (\ ///package.equivalence = + (set@ #///package.origin (#///repository/origin.Remote "") expected_package) + actual_package) + + (#try.Failure _) + false)))) (~~ (template [ ] - [(wrap - (do async.monad - [actual_package (/.one (///repository.mock []) - {#///dependency.artifact expected_artifact - #///dependency.type ///artifact/type.lux_library})] - (_.cover' [] - (case actual_package - (#try.Failure error) - (exception.match? error) - - (#try.Success _) - false))))] + [(in (do async.monad + [actual_package (/.one (///repository.mock []) + {#///dependency.artifact expected_artifact + #///dependency.type ///artifact/type.lux_library})] + (_.cover' [] + (case actual_package + (#try.Failure error) + (exception.match? error) + + (#try.Success _) + false))))] [/.sha-1_does_not_match bad_sha-1] [/.md5_does_not_match bad_md5] @@ -305,39 +303,37 @@ bad_sha-1 (..bad_sha-1 expected_artifact expected_package dummy_package) bad_md5 (..bad_md5 expected_artifact expected_package dummy_package)]] ($_ _.and - (wrap - (do async.monad - [#let [console ($///version.echo "")] - actual_package (/.any console - (list (///repository.mock bad_sha-1 []) - (///repository.mock bad_md5 []) - (///repository.mock good [])) - {#///dependency.artifact expected_artifact - #///dependency.type ///artifact/type.lux_library})] - (_.cover' [/.any] - (case actual_package - (#try.Success actual_package) - (\ ///package.equivalence = - (set@ #///package.origin (#///repository/origin.Remote "") expected_package) - actual_package) - - (#try.Failure _) - false)))) - (wrap - (do async.monad - [#let [console ($///version.echo "")] - actual_package (/.any console - (list (///repository.mock bad_sha-1 []) - (///repository.mock bad_md5 [])) - {#///dependency.artifact expected_artifact - #///dependency.type ///artifact/type.lux_library})] - (_.cover' [/.cannot_resolve] - (case actual_package - (#try.Failure error) - (exception.match? /.cannot_resolve error) - - (#try.Success _) - false)))) + (in (do async.monad + [#let [console ($///version.echo "")] + actual_package (/.any console + (list (///repository.mock bad_sha-1 []) + (///repository.mock bad_md5 []) + (///repository.mock good [])) + {#///dependency.artifact expected_artifact + #///dependency.type ///artifact/type.lux_library})] + (_.cover' [/.any] + (case actual_package + (#try.Success actual_package) + (\ ///package.equivalence = + (set@ #///package.origin (#///repository/origin.Remote "") expected_package) + actual_package) + + (#try.Failure _) + false)))) + (in (do async.monad + [#let [console ($///version.echo "")] + actual_package (/.any console + (list (///repository.mock bad_sha-1 []) + (///repository.mock bad_md5 [])) + {#///dependency.artifact expected_artifact + #///dependency.type ///artifact/type.lux_library})] + (_.cover' [/.cannot_resolve] + (case actual_package + (#try.Failure error) + (exception.match? /.cannot_resolve error) + + (#try.Success _) + false)))) ))) (def: artifacts @@ -351,7 +347,7 @@ (predicate.unite (\ ///artifact.equivalence = dependee_artifact) (\ ///artifact.equivalence = depender_artifact))) $///artifact.random)] - (wrap [dependee_artifact depender_artifact ignored_artifact]))) + (in [dependee_artifact depender_artifact ignored_artifact]))) (def: (packages [dependee_artifact depender_artifact ignored_artifact]) (-> [Artifact Artifact Artifact] @@ -398,8 +394,8 @@ (|> ignored_pom (\ xml.codec encode) (\ utf8.codec encode)) #///dependency/status.Unverified] ignored_package)]] - (wrap [[dependee depender ignored] - [dependee_package depender_package ignored_package]]))) + (in [[dependee depender ignored] + [dependee_package depender_package ignored_package]]))) (def: all Test @@ -410,26 +406,25 @@ [dependee_package depender_package ignored_package]] (..packages [dependee_artifact depender_artifact ignored_artifact])] ($_ _.and - (wrap - (do async.monad - [#let [console ($///version.echo "")] - [successes failures resolution] (/.all console - (list (///repository.mock (..single dependee_artifact dependee_package) []) - (///repository.mock (..single depender_artifact depender_package) []) - (///repository.mock (..single ignored_artifact ignored_package) [])) - (function (_ url) - (///repository.mock ..nope [])) - (list depender) - /.empty)] - (_.cover' [/.all] - (and (dictionary.key? resolution depender) - (list.any? (///dependency\= depender) successes) - - (dictionary.key? resolution dependee) - (list.any? (///dependency\= dependee) successes) - - (list.empty? failures) - (not (dictionary.key? resolution ignored)))))) + (in (do async.monad + [#let [console ($///version.echo "")] + [successes failures resolution] (/.all console + (list (///repository.mock (..single dependee_artifact dependee_package) []) + (///repository.mock (..single depender_artifact depender_package) []) + (///repository.mock (..single ignored_artifact ignored_package) [])) + (function (_ url) + (///repository.mock ..nope [])) + (list depender) + /.empty)] + (_.cover' [/.all] + (and (dictionary.key? resolution depender) + (list.any? (///dependency\= depender) successes) + + (dictionary.key? resolution dependee) + (list.any? (///dependency\= dependee) successes) + + (list.empty? failures) + (not (dictionary.key? resolution ignored)))))) ))) (def: #export test diff --git a/stdlib/source/test/aedifex/dependency/status.lux b/stdlib/source/test/aedifex/dependency/status.lux index 64bb2f642..5b446d643 100644 --- a/stdlib/source/test/aedifex/dependency/status.lux +++ b/stdlib/source/test/aedifex/dependency/status.lux @@ -21,7 +21,7 @@ (def: #export random (Random /.Status) ($_ random.or - (random\wrap []) + (random\in []) (random.or ($///hash.random ///hash.sha-1) ($///hash.random ///hash.md5)) (random.and ($///hash.random ///hash.sha-1) diff --git a/stdlib/source/test/aedifex/input.lux b/stdlib/source/test/aedifex/input.lux index e7f02569f..0cea854c4 100644 --- a/stdlib/source/test/aedifex/input.lux +++ b/stdlib/source/test/aedifex/input.lux @@ -48,19 +48,19 @@ [expected (\ ! map (set@ #//.parents (list)) $profile.random) #let [fs (: (file.System Async) (file.mock (\ file.default separator)))]] - (wrap (do async.monad - [verdict (do //action.monad - [#let [profile (|> expected - //format.profile - %.code - (\ utf8.codec encode))] - _ (\ fs write profile //project.file) - actual (: (Async (Try Profile)) - (/.read async.monad fs //.default))] - (wrap (\ //.equivalence = - (|> expected - (update@ #//.sources ..with_default_source) - (update@ #//.repositories ..with_default_repository)) - actual)))] - (_.cover' [/.read] - (try.default false verdict))))))) + (in (do async.monad + [verdict (do //action.monad + [#let [profile (|> expected + //format.profile + %.code + (\ utf8.codec encode))] + _ (\ fs write profile //project.file) + actual (: (Async (Try Profile)) + (/.read async.monad fs //.default))] + (in (\ //.equivalence = + (|> expected + (update@ #//.sources ..with_default_source) + (update@ #//.repositories ..with_default_repository)) + actual)))] + (_.cover' [/.read] + (try.default false verdict))))))) diff --git a/stdlib/source/test/aedifex/metadata/artifact.lux b/stdlib/source/test/aedifex/metadata/artifact.lux index 6a2106ad3..acd0575a0 100644 --- a/stdlib/source/test/aedifex/metadata/artifact.lux +++ b/stdlib/source/test/aedifex/metadata/artifact.lux @@ -54,17 +54,17 @@ hour (\ ! map (n.% 24) random.nat) minute (\ ! map (n.% 60) random.nat) second (\ ! map (n.% 60) random.nat)] - (wrap (try.assumed - (do try.monad - [year (year.year year) - month (month.by_number month) - date (date.date year month day_of_month) - time (time.time - {#time.hour hour - #time.minute minute - #time.second second - #time.milli_second 0})] - (wrap (instant.of_date_time date time)))))))) + (in (try.assumed + (do try.monad + [year (year.year year) + month (month.by_number month) + date (date.date year month day_of_month) + time (time.time + {#time.hour hour + #time.minute minute + #time.second second + #time.milli_second 0})] + (in (instant.of_date_time date time)))))))) (def: #export test Test @@ -100,17 +100,17 @@ #let [program (program.async (program.mock environment.empty home working_directory)) fs (file.mock (\ file.default separator)) repository (///repository/local.repository program fs)]] - (wrap (do async.monad - [wrote? (/.write repository artifact expected) - actual (/.read repository artifact)] - (_.cover' [/.write /.read] - (and (case wrote? - (#try.Success _) true - (#try.Failure _) false) - (case actual - (#try.Success actual) - (\ /.equivalence = expected actual) - - (#try.Failure _) - false)))))) + (in (do async.monad + [wrote? (/.write repository artifact expected) + actual (/.read repository artifact)] + (_.cover' [/.write /.read] + (and (case wrote? + (#try.Success _) true + (#try.Failure _) false) + (case actual + (#try.Success actual) + (\ /.equivalence = expected actual) + + (#try.Failure _) + false)))))) )))) diff --git a/stdlib/source/test/aedifex/metadata/snapshot.lux b/stdlib/source/test/aedifex/metadata/snapshot.lux index ea0a26a5a..c9787d8bb 100644 --- a/stdlib/source/test/aedifex/metadata/snapshot.lux +++ b/stdlib/source/test/aedifex/metadata/snapshot.lux @@ -58,22 +58,22 @@ hour (\ ! map (n.% 24) random.nat) minute (\ ! map (n.% 60) random.nat) second (\ ! map (n.% 60) random.nat)] - (wrap (try.assumed - (do try.monad - [year (year.year year) - month (month.by_number month) - date (date.date year month day_of_month) - time (time.time - {#time.hour hour - #time.minute minute - #time.second second - #time.milli_second 0})] - (wrap (instant.of_date_time date time))))))) + (in (try.assumed + (do try.monad + [year (year.year year) + month (month.by_number month) + date (date.date year month day_of_month) + time (time.time + {#time.hour hour + #time.minute minute + #time.second second + #time.milli_second 0})] + (in (instant.of_date_time date time))))))) (def: random_versioning (Random Versioning) ($_ random.and - (random\wrap #///snapshot.Local) + (random\in #///snapshot.Local) $///artifact/time.random (random.list 5 $///artifact/snapshot/version.random) )) @@ -112,17 +112,17 @@ #let [program (program.async (program.mock environment.empty home working_directory)) fs (file.mock (\ file.default separator)) repository (///repository/local.repository program fs)]] - (wrap (do async.monad - [wrote? (/.write repository artifact expected) - actual (/.read repository artifact)] - (_.cover' [/.write /.read] - (and (case wrote? - (#try.Success _) true - (#try.Failure _) false) - (case actual - (#try.Success actual) - (\ /.equivalence = expected actual) - - (#try.Failure _) - false)))))) + (in (do async.monad + [wrote? (/.write repository artifact expected) + actual (/.read repository artifact)] + (_.cover' [/.write /.read] + (and (case wrote? + (#try.Success _) true + (#try.Failure _) false) + (case actual + (#try.Success actual) + (\ /.equivalence = expected actual) + + (#try.Failure _) + false)))))) )))) diff --git a/stdlib/source/test/aedifex/package.lux b/stdlib/source/test/aedifex/package.lux index 61201456a..8896b731d 100644 --- a/stdlib/source/test/aedifex/package.lux +++ b/stdlib/source/test/aedifex/package.lux @@ -46,12 +46,12 @@ [content_size (\ ! map (n.% 100) random.nat) content ($binary.random content_size) [profile pom] (random.one (function (_ profile) - (try.to_maybe + (try.maybe (do try.monad [pom (//pom.write profile)] - (wrap [profile pom])))) + (in [profile pom])))) $profile.random)] - (wrap [profile (/.local pom content)]))) + (in [profile (/.local pom content)]))) (def: #export test Test @@ -94,7 +94,7 @@ (|> (do try.monad [xml_pom (\ utf8.codec decode binary_pom) decoded_pom (\ xml.codec decode xml_pom)] - (wrap (\ xml.equivalence = actual_pom decoded_pom))) + (in (\ xml.equivalence = actual_pom decoded_pom))) (try.default false)) (case pom_status (#//status.Verified actual_sha1 expected_md5) diff --git a/stdlib/source/test/aedifex/profile.lux b/stdlib/source/test/aedifex/profile.lux index f29ae7087..755c0e13a 100644 --- a/stdlib/source/test/aedifex/profile.lux +++ b/stdlib/source/test/aedifex/profile.lux @@ -36,8 +36,8 @@ (def: distribution (Random /.Distribution) - (random.or (random\wrap []) - (random\wrap []))) + (random.or (random\in []) + (random\in []))) (def: license (Random /.License) @@ -131,11 +131,11 @@ (random.maybe (random.ascii/alpha 1)) (random.maybe (random.ascii/alpha 1)) (..dictionary_of text.hash (random.ascii/alpha 1) ..repository) - (random\wrap //runtime.default_java) - (random\wrap //runtime.default_js) - (random\wrap //runtime.default_python) - (random\wrap //runtime.default_lua) - (random\wrap //runtime.default_ruby) + (random\in //runtime.default_java) + (random\in //runtime.default_js) + (random\in //runtime.default_python) + (random\in //runtime.default_lua) + (random\in //runtime.default_ruby) )) (def: #export test diff --git a/stdlib/source/test/aedifex/project.lux b/stdlib/source/test/aedifex/project.lux index d76d4afb3..4df06a337 100644 --- a/stdlib/source/test/aedifex/project.lux +++ b/stdlib/source/test/aedifex/project.lux @@ -34,7 +34,7 @@ (Random /.Project) (do random.monad [[name profile] ..profile] - (wrap (/.project name profile)))) + (in (/.project name profile)))) (def: #export test Test diff --git a/stdlib/source/test/aedifex/repository.lux b/stdlib/source/test/aedifex/repository.lux index 67cc4c10f..a926db9a7 100644 --- a/stdlib/source/test/aedifex/repository.lux +++ b/stdlib/source/test/aedifex/repository.lux @@ -74,14 +74,14 @@ (case (dictionary.get uri state) (#.Some content) (case (binary.size content) - 0 (exception.throw ..not_found [uri]) + 0 (exception.except ..not_found [uri]) _ (exception.return [state content])) #.None - (exception.throw ..not_found [uri]))) + (exception.except ..not_found [uri]))) (def: (on_upload uri content state) (if (dictionary.key? state uri) - (exception.throw ..cannot_upload [uri]) + (exception.except ..cannot_upload [uri]) (exception.return (dictionary.put uri content state))))) (def: #export test @@ -90,7 +90,7 @@ ($_ _.and (_.for [/.mock /.Mock] (do random.monad - [_ (wrap [])] + [_ (in [])] ($/.spec (..artifact ..valid_version) (..artifact ..invalid_version) (/.mock ..mock diff --git a/stdlib/source/test/aedifex/repository/local.lux b/stdlib/source/test/aedifex/repository/local.lux index a40924dea..180ea404a 100644 --- a/stdlib/source/test/aedifex/repository/local.lux +++ b/stdlib/source/test/aedifex/repository/local.lux @@ -38,15 +38,15 @@ expected (\ ! map (\ utf8.codec encode) (random.ascii/lower 10))] ($_ _.and - (wrap (do async.monad - [before_upload (\ repo download uri) - _ (\ repo upload uri expected) - actual (\ repo download uri)] - (_.cover' [/.repository] - (and (case before_upload - (#try.Success _) false - (#try.Failure _) true) - (|> actual - (try\map (binary\= expected)) - (try.default false)))))) + (in (do async.monad + [before_upload (\ repo download uri) + _ (\ repo upload uri expected) + actual (\ repo download uri)] + (_.cover' [/.repository] + (and (case before_upload + (#try.Success _) false + (#try.Failure _) true) + (|> actual + (try\map (binary\= expected)) + (try.default false)))))) )))) diff --git a/stdlib/source/test/aedifex/runtime.lux b/stdlib/source/test/aedifex/runtime.lux index f9749c968..cb6d1a8fe 100644 --- a/stdlib/source/test/aedifex/runtime.lux +++ b/stdlib/source/test/aedifex/runtime.lux @@ -22,11 +22,11 @@ (def: #export random (Random /.Runtime) ($_ random.either - (random\wrap /.default_java) - (random\wrap /.default_js) - (random\wrap /.default_python) - (random\wrap /.default_lua) - (random\wrap /.default_ruby) + (random\in /.default_java) + (random\in /.default_js) + (random\in /.default_python) + (random\in /.default_lua) + (random\in /.default_ruby) )) (def: #export test -- cgit v1.2.3