diff options
Diffstat (limited to 'stdlib/source/program')
23 files changed, 179 insertions, 179 deletions
diff --git a/stdlib/source/program/aedifex.lux b/stdlib/source/program/aedifex.lux index b046a7ace..c84f57170 100644 --- a/stdlib/source/program/aedifex.lux +++ b/stdlib/source/program/aedifex.lux @@ -13,7 +13,7 @@ [parser [environment (#+ Environment)]] [concurrency - ["." promise (#+ Promise) ("#\." monad)]]] + ["." async (#+ Async) ("#\." monad)]]] [data [binary (#+ Binary)] ["." text @@ -65,15 +65,15 @@ ["#/." deploy]]]) (def: repositories - (-> /.Profile (List (Repository Promise))) + (-> /.Profile (List (Repository Async))) (|>> (get@ #/.repositories) set.to_list (list\map (|>> (/repository/remote.repository http.default #.None) /repository.async)))) (def: (with_dependencies program console command profile) (All [a] - (-> (Program Promise) (Console Promise) - (-> (Console Promise) (Program Promise) (file.System Promise) (Shell Promise) Resolution (Command [Exit a])) + (-> (Program Async) (Console Async) + (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit a])) (Command a))) (do /action.monad [resolution (/command/deps.do! console @@ -88,7 +88,7 @@ (wrap []) _ - (do promise.monad + (do async.monad [_ (\ program exit exit_code)] (wrap (#try.Failure ""))))] (wrap output))) @@ -112,10 +112,10 @@ (\ program.default exit shell.error))) (def: (command action) - (All [a] (-> (Promise (Try a)) (IO Any))) - (exec (do promise.monad + (All [a] (-> (Async (Try a)) (IO Any))) + (exec (do async.monad [outcome action] - (promise.future + (async.future (case outcome (#try.Success _) ..succeed! @@ -175,10 +175,10 @@ profile) [#.None _] - (promise\wrap (exception.throw /.no_identity [])) + (async\wrap (exception.throw /.no_identity [])) [_ #.None] - (promise\wrap (exception.throw ..cannot_find_repository [repository (get@ #/.deploy_repositories profile)])))) + (async\wrap (exception.throw ..cannot_find_repository [repository (get@ #/.deploy_repositories profile)])))) #/cli.Dependencies (..command diff --git a/stdlib/source/program/aedifex/action.lux b/stdlib/source/program/aedifex/action.lux index 61c5ba3de..2da97fde2 100644 --- a/stdlib/source/program/aedifex/action.lux +++ b/stdlib/source/program/aedifex/action.lux @@ -6,11 +6,11 @@ [control ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)]]]]]) + ["." async (#+ Async)]]]]]) (type: #export (Action a) - (Promise (Try a))) + (Async (Try a))) (def: #export monad (Monad Action) - (:assume (try.with promise.monad))) + (:assume (try.with async.monad))) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/version.lux b/stdlib/source/program/aedifex/artifact/snapshot/version.lux index a1a50fcc2..89af452e2 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/version.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/version.lux @@ -40,16 +40,16 @@ [<snapshot_version> "snapshotVersion"] ) -(def: (format_text tag value) +(def: (text_format tag value) (-> xml.Tag Text XML) (|> value #xml.Text list (#xml.Node tag xml.attributes))) (def: #export (format (^slots [#extension #value #updated])) (-> Version XML) (<| (#xml.Node ..<snapshot_version> xml.attributes) - (list (..format_text ..<extension> extension) - (..format_text ..<value> value) - (..format_text ..<updated> (///time.format updated))))) + (list (..text_format ..<extension> extension) + (..text_format ..<value> value) + (..text_format ..<updated> (///time.format updated))))) (def: (text tag) (-> xml.Tag (Parser Text)) diff --git a/stdlib/source/program/aedifex/artifact/versioning.lux b/stdlib/source/program/aedifex/artifact/versioning.lux index 9fdc2d84d..9c9805571 100644 --- a/stdlib/source/program/aedifex/artifact/versioning.lux +++ b/stdlib/source/program/aedifex/artifact/versioning.lux @@ -57,7 +57,7 @@ [<versioning> "versioning"] ) -(def: format_last_updated +(def: last_updated_format (-> //time.Time XML) (|>> //time.format #xml.Text list (#xml.Node ..<last_updated> xml.attributes))) @@ -65,7 +65,7 @@ (-> Versioning XML) (<| (#xml.Node ..<versioning> xml.attributes) (list (//snapshot.format snapshot) - (..format_last_updated last_updated) + (..last_updated_format last_updated) (|> versions (list\map //snapshot/version.format) (#xml.Node ..<snapshot_versions> xml.attributes))))) diff --git a/stdlib/source/program/aedifex/command/auto.lux b/stdlib/source/program/aedifex/command/auto.lux index 2460215b4..a80193663 100644 --- a/stdlib/source/program/aedifex/command/auto.lux +++ b/stdlib/source/program/aedifex/command/auto.lux @@ -6,7 +6,7 @@ [control ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data [collection ["." list] @@ -26,8 +26,8 @@ [resolution (#+ Resolution)]]]]) (def: (targets fs path) - (-> (file.System Promise) file.Path (Promise (List file.Path))) - (let [! promise.monad] + (-> (file.System Async) file.Path (Async (List file.Path))) + (let [! async.monad] (|> path (\ fs sub_directories) (\ ! map (|>> (try.default (list)) @@ -40,18 +40,18 @@ 1,000) (def: (pause delay) - (-> Nat (Promise (Try Any))) - (promise.delay delay (#try.Success []))) + (-> Nat (Async (Try Any))) + (async.delay delay (#try.Success []))) (def: #export (do! delay watcher command) (All [a] - (-> Nat (Watcher Promise) - (-> (Console Promise) (Program Promise) (file.System Promise) (Shell Promise) Resolution (Command [Exit a])) - (-> (Console Promise) (Program Promise) (file.System Promise) (Shell Promise) Resolution (Command [Exit Any])))) + (-> Nat (Watcher Async) + (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit a])) + (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit Any])))) (function (_ console program fs shell resolution) (function (_ profile) (with_expansions [<call> ((command console program fs shell resolution) profile)] - (do {! promise.monad} + (do {! async.monad} [targets (|> profile (get@ #///.sources) set.to_list diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux index 52804be43..b5df31411 100644 --- a/stdlib/source/program/aedifex/command/build.lux +++ b/stdlib/source/program/aedifex/command/build.lux @@ -10,7 +10,7 @@ ["." exception (#+ exception:)] ["." io (#+ IO)] [concurrency - ["." promise (#+ Promise) ("#\." monad)]]] + ["." async (#+ Async) ("#\." monad)]]] [data ["." product] ["." maybe] @@ -192,32 +192,32 @@ (template [<name> <capability>] [(def: #export (<name> console process) - (-> (Console Promise) (Process Promise) (Promise (Try Any))) + (-> (Console Async) (Process Async) (Async (Try Any))) ## This is a very odd way of implementing this function. - ## But it's written this way because the more straightforward way (i.e. by using (try.with promise.monad)) + ## But it's written this way because the more straightforward way (i.e. by using (try.with async.monad)) ## eventually led to the function hanging/freezing. ## I'm not sure why it happened, but I got this weirder implementation to work. - (let [[read! write!] (: [(Promise (Try Any)) - (promise.Resolver (Try Any))] - (promise.promise [])) + (let [[read! write!] (: [(Async (Try Any)) + (async.Resolver (Try Any))] + (async.async [])) _ (|> (\ process <capability> []) - (promise.await (function (recur ?line) - (case ?line - (#try.Failure error) - (if (exception.match? shell.no_more_output error) - (write! (#try.Success [])) - (promise.await write! (console.write_line error console))) - - (#try.Success line) - (promise.await (function (_ outcome) - (case outcome - (#try.Failure error) - (write! (#try.Failure error)) - - (#try.Success _) - (promise.await recur - (\ process <capability> [])))) - (console.write_line line console))))) + (async.await (function (recur ?line) + (case ?line + (#try.Failure error) + (if (exception.match? shell.no_more_output error) + (write! (#try.Success [])) + (async.await write! (console.write_line error console))) + + (#try.Success line) + (async.await (function (_ outcome) + (case outcome + (#try.Failure error) + (write! (#try.Failure error)) + + (#try.Success _) + (async.await recur + (\ process <capability> [])))) + (console.write_line line console))))) io.run)] read!))] @@ -261,20 +261,20 @@ runtime))) (def: #export (do! console program fs shell resolution) - (-> (Console Promise) (Program Promise) (file.System Promise) (Shell Promise) Resolution (Command [Exit Compiler Path])) + (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit Compiler Path])) (function (_ profile) (let [target (get@ #///.target profile)] (case (get@ #///.program profile) #.None - (promise\wrap (exception.throw ..no_specified_program [])) + (async\wrap (exception.throw ..no_specified_program [])) (#.Some program_module) - (do promise.monad - [environment (program.environment promise.monad program) + (do async.monad + [environment (program.environment async.monad program) #let [home (\ program home) working_directory (\ program directory)]] (do ///action.monad - [[resolution compiler] (promise\wrap (..compiler resolution (get@ #///.compiler profile))) + [[resolution compiler] (async\wrap (..compiler resolution (get@ #///.compiler profile))) #let [host_dependencies (..host_dependencies fs home resolution) [[command compiler_params] output] (case compiler (#JVM dependency) diff --git a/stdlib/source/program/aedifex/command/clean.lux b/stdlib/source/program/aedifex/command/clean.lux index 3a27e400a..2ff701d2b 100644 --- a/stdlib/source/program/aedifex/command/clean.lux +++ b/stdlib/source/program/aedifex/command/clean.lux @@ -6,7 +6,7 @@ [control [try (#+ Try)] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data [text ["%" format (#+ format)]]] @@ -19,7 +19,7 @@ ["#." action (#+ Action)]]) (def: (clean_files! fs root) - (-> (file.System Promise) Path (Promise (Try Any))) + (-> (file.System Async) Path (Async (Try Any))) (let [! ///action.monad] (|> root (\ fs directory_files) @@ -31,8 +31,8 @@ (|>> (format "Successfully cleaned target directory: "))) (def: #export (do! console fs profile) - (-> (Console Promise) (file.System Promise) (Command Any)) - (do {! promise.monad} + (-> (Console Async) (file.System Async) (Command Any)) + (do {! async.monad} [#let [target (get@ #///.target profile)] ? (\ fs directory? target) _ (let [! ///action.monad] diff --git a/stdlib/source/program/aedifex/command/deploy.lux b/stdlib/source/program/aedifex/command/deploy.lux index e70e6f762..79f6e4f2f 100644 --- a/stdlib/source/program/aedifex/command/deploy.lux +++ b/stdlib/source/program/aedifex/command/deploy.lux @@ -7,7 +7,7 @@ [pipe (#+ do>)] ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise) ("#\." monad)]] + ["." async (#+ Async) ("#\." monad)]] ["<>" parser ["<.>" xml]]] [data @@ -57,14 +57,14 @@ "Successfully deployed the project.") (def: #export (do! console repository fs artifact profile) - (-> (Console Promise) (Repository Promise) (file.System Promise) Artifact (Command Any)) + (-> (Console Async) (Repository Async) (file.System Async) Artifact (Command Any)) (do {! ///action.monad} [library (|> profile (get@ #/.sources) set.to_list (export.library fs) (\ ! map (binary.run tar.writer))) - pom (\ promise.monad wrap (///pom.write profile)) + pom (\ async.monad wrap (///pom.write profile)) _ (///dependency/deployment.one repository [artifact ///artifact/type.lux_library] diff --git a/stdlib/source/program/aedifex/command/deps.lux b/stdlib/source/program/aedifex/command/deps.lux index a7db4af20..7e0d655e9 100644 --- a/stdlib/source/program/aedifex/command/deps.lux +++ b/stdlib/source/program/aedifex/command/deps.lux @@ -6,7 +6,7 @@ [control ["." exception] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data [collection ["." set (#+ Set)] @@ -38,8 +38,8 @@ %.text)) (def: #export (do! console local remotes new_repository profile) - (-> (Console Promise) (Repository Promise) (List (Repository Promise)) (-> URL (Repository Promise)) (Command Resolution)) - (do promise.monad + (-> (Console Async) (Repository Async) (List (Repository Async)) (-> URL (Repository Async)) (Command Resolution)) + (do async.monad [#let [dependencies (|> (get@ #///.dependencies profile) set.to_list (#.Cons (get@ #///.compiler profile)))] diff --git a/stdlib/source/program/aedifex/command/install.lux b/stdlib/source/program/aedifex/command/install.lux index 4cc4ede68..142829a8c 100644 --- a/stdlib/source/program/aedifex/command/install.lux +++ b/stdlib/source/program/aedifex/command/install.lux @@ -7,7 +7,7 @@ ["." try (#+ Try)] ["." exception] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data [binary (#+ Binary)] [text @@ -50,7 +50,7 @@ "Failure: No 'identity' defined for the project.") (def: #export (do! console fs repository profile) - (-> (Console Promise) (file.System Promise) (Repository Promise) (Command Any)) + (-> (Console Async) (file.System Async) (Repository Async) (Command Any)) (case (get@ #/.identity profile) (#.Some identity) (do ///action.monad @@ -60,7 +60,7 @@ (export.library fs)) pom (|> profile ///pom.write - (\ promise.monad wrap)) + (\ async.monad wrap)) _ (///dependency/deployment.one repository [identity ///artifact/type.lux_library] (let [pom_data (|> pom diff --git a/stdlib/source/program/aedifex/command/pom.lux b/stdlib/source/program/aedifex/command/pom.lux index 6d26f4792..73e10f0fc 100644 --- a/stdlib/source/program/aedifex/command/pom.lux +++ b/stdlib/source/program/aedifex/command/pom.lux @@ -6,7 +6,7 @@ [control ["." try ("#\." functor)] [concurrency - ["." promise (#+ Promise) ("#\." monad)]]] + ["." async (#+ Async) ("#\." monad)]]] [data [text ["%" format (#+ format)] @@ -26,11 +26,11 @@ (format "Successfully created POM file: " ///pom.file)) (def: #export (do! console fs profile) - (-> (Console Promise) (file.System Promise) (Command Any)) + (-> (Console Async) (file.System Async) (Command Any)) (do ///action.monad [content (|> (///pom.write profile) (try\map (|>> (\ xml.codec encode) (\ utf8.codec encode))) - promise\wrap) + async\wrap) _ (\ fs write content ///pom.file)] (console.write_line ..success console))) diff --git a/stdlib/source/program/aedifex/command/test.lux b/stdlib/source/program/aedifex/command/test.lux index 1f32b2fc2..e159a48f2 100644 --- a/stdlib/source/program/aedifex/command/test.lux +++ b/stdlib/source/program/aedifex/command/test.lux @@ -5,7 +5,7 @@ [monad (#+ do)]] [control [concurrency - ["." promise (#+ Promise) ("#\." monad)]]] + ["." async (#+ Async) ("#\." monad)]]] [math [number ["i" int]]] @@ -29,9 +29,9 @@ (def: #export failure "[TEST FAILED]") (def: #export (do! console program fs shell resolution profile) - (-> (Console Promise) (Program Promise) (file.System Promise) (Shell Promise) Resolution (Command [Exit Any])) - (do promise.monad - [environment (program.environment promise.monad program) + (-> (Console Async) (Program Async) (file.System Async) (Shell Async) Resolution (Command [Exit Any])) + (do async.monad + [environment (program.environment async.monad program) #let [working_directory (\ program directory)]] (do {! ///action.monad} [#let [home (\ program home)] diff --git a/stdlib/source/program/aedifex/command/version.lux b/stdlib/source/program/aedifex/command/version.lux index cd724843c..0c5c944b5 100644 --- a/stdlib/source/program/aedifex/command/version.lux +++ b/stdlib/source/program/aedifex/command/version.lux @@ -3,7 +3,7 @@ [lux #* [control [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [tool [compiler ["." version] @@ -16,6 +16,6 @@ [command (#+ Command)]]) (def: #export (do! console profile) - (-> (Console Promise) (Command Any)) + (-> (Console Async) (Command Any)) (console.write_line (version.format language/lux.version) console)) diff --git a/stdlib/source/program/aedifex/dependency/deployment.lux b/stdlib/source/program/aedifex/dependency/deployment.lux index 150055cf3..3a7cba41f 100644 --- a/stdlib/source/program/aedifex/dependency/deployment.lux +++ b/stdlib/source/program/aedifex/dependency/deployment.lux @@ -7,7 +7,7 @@ [control ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data [binary (#+ Binary)] ["." product] @@ -41,16 +41,16 @@ ["#/." status (#+ Status)]]]) (def: (with_status repository version_template [artifact type] [data status]) - (-> (Repository Promise) ///artifact.Version Dependency [Binary Status] (Promise (Try Any))) + (-> (Repository Async) ///artifact.Version Dependency [Binary Status] (Async (Try Any))) (let [artifact (format (///artifact.uri version_template artifact) (///artifact/extension.extension type)) - deploy_hash (: (All [h] (-> (Codec Text (Hash h)) Extension (Hash h) (Promise (Try Any)))) + deploy_hash (: (All [h] (-> (Codec Text (Hash h)) Extension (Hash h) (Async (Try Any)))) (function (_ codec extension hash) (|> hash (\ codec encode) (\ utf8.codec encode) (\ repository upload (format artifact extension)))))] - (do {! (try.with promise.monad)} + (do {! (try.with async.monad)} [_ (\ repository upload artifact data)] (case status #///dependency/status.Unverified @@ -116,9 +116,9 @@ )))) (def: #export (one repository [artifact type] package) - (-> (Repository Promise) Dependency Package (Promise (Try Artifact))) - (do {! promise.monad} - [now (promise.future instant.now) + (-> (Repository Async) Dependency Package (Async (Try Artifact))) + (do {! async.monad} + [now (async.future instant.now) #let [version_template (get@ #///artifact.version artifact)]] (do (try.with !) [_ (with_status repository version_template [artifact type] (get@ #///package.library package)) @@ -141,8 +141,8 @@ (wrap artifact)))) (def: #export (all repository resolution) - (-> (Repository Promise) Resolution (Promise (Try (Set Artifact)))) - (let [! (try.with promise.monad)] + (-> (Repository Async) Resolution (Async (Try (Set Artifact)))) + (let [! (try.with async.monad)] (|> (dictionary.entries resolution) (monad.map ! (function (_ [dependency package]) (..one repository dependency package))) diff --git a/stdlib/source/program/aedifex/dependency/resolution.lux b/stdlib/source/program/aedifex/dependency/resolution.lux index 1e0c522b9..1a97dad34 100644 --- a/stdlib/source/program/aedifex/dependency/resolution.lux +++ b/stdlib/source/program/aedifex/dependency/resolution.lux @@ -13,7 +13,7 @@ ["<>" parser ["<.>" xml (#+ Parser)]] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data ["." binary (#+ Binary)] ["." name] @@ -74,11 +74,11 @@ (def: (verified_hash library repository version_template artifact extension hash codec exception) (All [h] - (-> Binary (Repository Promise) Version Artifact Extension + (-> Binary (Repository Async) Version Artifact Extension (-> Binary (Hash h)) (Codec Text (Hash h)) (Exception [Artifact Extension Text]) - (Promise (Try (Maybe (Hash h)))))) - (do promise.monad + (Async (Try (Maybe (Hash h)))))) + (do async.monad [?actual (\ repository download (///repository/remote.uri version_template artifact extension))] (case ?actual (#try.Success actual) @@ -100,8 +100,8 @@ (wrap (#try.Success #.None))))) (def: (hashed repository version_template artifact extension) - (-> (Repository Promise) Version Artifact Extension (Promise (Try [Binary Status]))) - (do (try.with promise.monad) + (-> (Repository Async) Version Artifact Extension (Async (Try [Binary Status]))) + (do (try.with async.monad) [data (\ repository download (///repository/remote.uri version_template artifact extension)) ?sha-1 (..verified_hash data repository version_template artifact (format extension ///artifact/extension.sha-1) @@ -123,10 +123,10 @@ #//status.Unverified)]))) (def: #export (one repository dependency) - (-> (Repository Promise) Dependency (Promise (Try Package))) + (-> (Repository Async) Dependency (Async (Try Package))) (let [[artifact type] dependency extension (///artifact/extension.extension type)] - (do (try.with promise.monad) + (do (try.with async.monad) [snapshot (///metadata/snapshot.read repository artifact) #let [version_template (get@ [#///metadata/snapshot.artifact #///artifact.version] snapshot) artifact_version (value.format {#value.version version_template @@ -134,7 +134,7 @@ artifact (set@ #///artifact.version artifact_version artifact)] [pom_data pom_status] (..hashed repository version_template artifact ///artifact/extension.pom) library_&_status (..hashed repository version_template artifact extension)] - (\ promise.monad wrap + (\ async.monad wrap (do try.monad [pom (\ utf8.codec decode pom_data) pom (\ xml.codec decode pom) @@ -161,7 +161,7 @@ (template [<sigil> <name> <doing> <at>] [(def: (<name> console repository artifact) - (-> (Console Promise) (Repository Promise) Artifact (Promise (Try Any))) + (-> (Console Async) (Repository Async) Artifact (Async (Try Any))) (\ console write (format "[" <sigil> "]" " " <doing> " " (///artifact.format artifact) @@ -175,15 +175,15 @@ ) (def: #export (any console repositories dependency) - (-> (Console Promise) (List (Repository Promise)) Dependency (Promise (Try Package))) + (-> (Console Async) (List (Repository Async)) Dependency (Async (Try Package))) (case repositories #.Nil (|> dependency (exception.throw ..cannot_resolve) - (\ promise.monad wrap)) + (\ async.monad wrap)) (#.Cons repository alternatives) - (do {! promise.monad} + (do {! async.monad} [_ (..announce_fetching console repository (get@ #//.artifact dependency)) outcome (..one repository dependency)] (case outcome @@ -198,10 +198,10 @@ (any console alternatives dependency)))))) (def: #export (all console repositories new_repository dependencies resolution) - (-> (Console Promise) (List (Repository Promise)) (-> URL (Repository Promise)) (List Dependency) Resolution - (Promise [(List Dependency) - (List Dependency) - Resolution])) + (-> (Console Async) (List (Repository Async)) (-> URL (Repository Async)) (List Dependency) Resolution + (Async [(List Dependency) + (List Dependency) + Resolution])) (loop [repositories repositories successes (: (List Dependency) (list)) failures (: (List Dependency) (list)) @@ -209,7 +209,7 @@ resolution resolution] (case dependencies #.Nil - (\ promise.monad wrap + (\ async.monad wrap [successes failures resolution]) (#.Cons head tail) @@ -220,7 +220,7 @@ failures tail resolution) - _ (do {! promise.monad} + _ (do {! async.monad} [?package (case (dictionary.get head resolution) (#.Some package) (wrap (#try.Success package)) diff --git a/stdlib/source/program/aedifex/metadata/artifact.lux b/stdlib/source/program/aedifex/metadata/artifact.lux index 524272559..55659f391 100644 --- a/stdlib/source/program/aedifex/metadata/artifact.lux +++ b/stdlib/source/program/aedifex/metadata/artifact.lux @@ -11,7 +11,7 @@ ["<.>" xml (#+ Parser)] ["<.>" text]] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data ["." product] ["." text @@ -85,26 +85,26 @@ (-> <type> XML) (|>> <pre> #xml.Text list (#xml.Node <tag> xml.attributes)))] - [format_group Group ..<group> (|>)] - [format_name Name ..<name> (|>)] - [format_version Version ..<version> (|>)] - [format_last_updated Instant ..<last_updated> ..instant_format] + [group_format Group ..<group> (|>)] + [name_format Name ..<name> (|>)] + [version_format Version ..<version> (|>)] + [last_updated_format Instant ..<last_updated> ..instant_format] ) -(def: format_versions +(def: versions_format (-> (List Version) XML) - (|>> (list\map ..format_version) (#xml.Node ..<versions> xml.attributes))) + (|>> (list\map ..version_format) (#xml.Node ..<versions> xml.attributes))) (def: #export (format value) (-> Metadata XML) (#xml.Node ..<metadata> xml.attributes - (list (..format_group (get@ #group value)) - (..format_name (get@ #name value)) + (list (..group_format (get@ #group value)) + (..name_format (get@ #name value)) (#xml.Node ..<versioning> xml.attributes - (list (..format_versions (get@ #versions value)) - (..format_last_updated (get@ #last_updated value))))))) + (list (..versions_format (get@ #versions value)) + (..last_updated_format (get@ #last_updated value))))))) (def: (text tag) (-> xml.Tag (Parser Text)) @@ -173,8 +173,8 @@ (instant.of_millis +0)) (def: #export (read repository artifact) - (-> (Repository Promise) Artifact (Promise (Try Metadata))) - (do promise.monad + (-> (Repository Async) Artifact (Async (Try Metadata))) + (do async.monad [project (\ repository download (..uri artifact))] (case project (#try.Success project) @@ -193,7 +193,7 @@ #last_updated ..epoch})))))) (def: #export (write repository artifact metadata) - (-> (Repository Promise) Artifact Metadata (Promise (Try Any))) + (-> (Repository Async) Artifact Metadata (Async (Try Any))) (|> metadata ..format (\ xml.codec encode) diff --git a/stdlib/source/program/aedifex/metadata/snapshot.lux b/stdlib/source/program/aedifex/metadata/snapshot.lux index 032214c90..6faab7b3b 100644 --- a/stdlib/source/program/aedifex/metadata/snapshot.lux +++ b/stdlib/source/program/aedifex/metadata/snapshot.lux @@ -12,7 +12,7 @@ ["<.>" xml (#+ Parser)] ["<.>" text]] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data ["." product] ["." text @@ -63,9 +63,9 @@ (-> <type> XML) (|>> <pre> #xml.Text list (#xml.Node <tag> xml.attributes)))] - [format_group Group ..<group> (|>)] - [format_name Name ..<name> (|>)] - [format_version Version ..<version> (|>)] + [group_format Group ..<group> (|>)] + [name_format Name ..<name> (|>)] + [version_format Version ..<version> (|>)] ) (def: #export (format (^slots [#artifact #versioning])) @@ -73,9 +73,9 @@ (let [(^slots [#///artifact.group #///artifact.name #///artifact.version]) artifact] (#xml.Node ..<metadata> xml.attributes - (list (..format_group group) - (..format_name name) - (..format_version version) + (list (..group_format group) + (..name_format name) + (..version_format version) (///artifact/versioning.format versioning))))) (def: (text tag) @@ -123,8 +123,8 @@ //.remote_artifact_uri) (def: #export (read repository artifact) - (-> (Repository Promise) Artifact (Promise (Try Metadata))) - (do promise.monad + (-> (Repository Async) Artifact (Async (Try Metadata))) + (do async.monad [project (\ repository download (..uri artifact))] (case project (#try.Success project) @@ -140,7 +140,7 @@ #versioning ///artifact/versioning.init}))))) (def: #export (write repository artifact metadata) - (-> (Repository Promise) Artifact Metadata (Promise (Try Any))) + (-> (Repository Async) Artifact Metadata (Async (Try Any))) (|> metadata ..format (\ xml.codec encode) diff --git a/stdlib/source/program/aedifex/repository.lux b/stdlib/source/program/aedifex/repository.lux index 7ae07e9b5..8f92be270 100644 --- a/stdlib/source/program/aedifex/repository.lux +++ b/stdlib/source/program/aedifex/repository.lux @@ -7,7 +7,7 @@ [io (#+ IO)] ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)] + ["." async (#+ Async)] ["." stm]]] [data [binary (#+ Binary)]] @@ -24,15 +24,15 @@ upload)) (def: #export (async repository) - (-> (Repository IO) (Repository Promise)) + (-> (Repository IO) (Repository Async)) (implementation (def: description (\ repository description)) (def: (download uri) - (promise.future (\ repository download uri))) + (async.future (\ repository download uri))) (def: (upload uri content) - (promise.future (\ repository upload uri content))) + (async.future (\ repository upload uri content))) )) (interface: #export (Mock s) @@ -44,7 +44,7 @@ on_upload)) (def: #export (mock mock init) - (All [s] (-> (Mock s) s (Repository Promise))) + (All [s] (-> (Mock s) s (Repository Async))) (let [state (stm.var init)] (implementation (def: description diff --git a/stdlib/source/program/aedifex/repository/local.lux b/stdlib/source/program/aedifex/repository/local.lux index e7dbb7d4d..4620a1363 100644 --- a/stdlib/source/program/aedifex/repository/local.lux +++ b/stdlib/source/program/aedifex/repository/local.lux @@ -6,7 +6,7 @@ [control ["." try] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data ["." text ["%" format (#+ format)]]] @@ -21,7 +21,7 @@ ["#." metadata]]]) (def: (root program /) - (-> (Program Promise) Text file.Path) + (-> (Program Async) Text file.Path) (|> ///local.repository (text.replace_all uri.separator /) (format (\ program home) /))) @@ -31,13 +31,13 @@ (text.replace_all uri.separator /)) (def: (absolute_path program /) - (-> (Program Promise) Text (-> URI file.Path)) + (-> (Program Async) Text (-> URI file.Path)) (|>> ///metadata.local_uri (..path /) (format (..root program /) /))) (implementation: #export (repository program fs) - (-> (Program Promise) (file.System Promise) (//.Repository Promise)) + (-> (Program Async) (file.System Async) (//.Repository Async)) (def: description (..root program (\ fs separator))) @@ -47,16 +47,16 @@ (\ fs read))) (def: (upload uri content) - (do {! promise.monad} + (do {! async.monad} [#let [absolute_path (..absolute_path program (\ fs separator) uri)] ? (\ fs file? absolute_path) _ (if ? (wrap []) (case (file.parent fs absolute_path) (#.Some parent) - (file.make_directories promise.monad fs parent) + (file.make_directories async.monad fs parent) _ - (let [! (try.with promise.monad)] + (let [! (try.with async.monad)] (\ ! wrap []))))] (\ fs write content absolute_path)))) diff --git a/stdlib/source/program/compositor.lux b/stdlib/source/program/compositor.lux index bb102224d..8d9874216 100644 --- a/stdlib/source/program/compositor.lux +++ b/stdlib/source/program/compositor.lux @@ -10,7 +10,7 @@ ["." io (#+ IO io)] ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise) ("#\." monad)]]] + ["." async (#+ Async) ("#\." monad)]]] [data [binary (#+ Binary)] ["." product] @@ -59,8 +59,8 @@ (def: (or_crash! failure_description action) (All [a] - (-> Text (Promise (Try a)) (Promise a))) - (do promise.monad + (-> Text (Async (Try a)) (Async a))) + (do async.monad [?output action] (case ?output (#try.Failure error) @@ -74,8 +74,8 @@ (def: (timed process) (All [a] - (-> (Promise (Try a)) (Promise (Try a)))) - (do promise.monad + (-> (Async (Try a)) (Async (Try a)))) + (do async.monad [#let [start (io.run instant.now)] output process #let [_ ("lux io log" (|> (io.run instant.now) @@ -85,17 +85,17 @@ (wrap output))) (def: (package! fs host_dependencies [packager package] static archive context) - (-> (file.System Promise) (Dictionary file.Path Binary) [Packager file.Path] Static Archive Context (Promise (Try Any))) + (-> (file.System Async) (Dictionary file.Path Binary) [Packager file.Path] Static Archive Context (Async (Try Any))) (case (packager host_dependencies archive context) (#try.Success content) (\ fs write content package) (#try.Failure error) - (\ promise.monad wrap (#try.Failure error)))) + (\ async.monad wrap (#try.Failure error)))) (def: (load_host_dependencies fs host_dependencies) - (-> (file.System Promise) (List file.Path) (Promise (Try (Dictionary file.Path Binary)))) - (do {! (try.with promise.monad)} + (-> (file.System Async) (List file.Path) (Async (Try (Dictionary file.Path Binary)))) + (do {! (try.with async.monad)} [] (loop [pending host_dependencies output (: (Dictionary file.Path Binary) @@ -127,32 +127,32 @@ (-> platform.Phase_Wrapper Extender) Service [Packager file.Path] - (Promise Any))) - (do {! promise.monad} - [platform (promise.future platform)] + (Async Any))) + (do {! async.monad} + [platform (async.future platform)] (case service (#/cli.Compilation compilation) (<| (or_crash! "Compilation failed:") ..timed - (do (try.with promise.monad) + (do (try.with async.monad) [#let [[compilation_sources compilation_host_dependencies compilation_libraries compilation_target compilation_module] compilation] import (/import.import (get@ #platform.&file_system platform) compilation_libraries) [state archive] (:sharing [<parameters>] (Platform <parameters>) platform - (Promise (Try [(directive.State+ <parameters>) - Archive])) + (Async (Try [(directive.State+ <parameters>) + Archive])) (:assume (platform.initialize static compilation_module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender import compilation_sources))) [archive state] (:sharing [<parameters>] (Platform <parameters>) platform - (Promise (Try [Archive (directive.State+ <parameters>)])) + (Async (Try [Archive (directive.State+ <parameters>)])) (:assume (platform.compile import static expander platform compilation [archive state]))) _ (ioW.freeze (get@ #platform.&file_system platform) static archive) - program_context (promise\wrap ($/program.context archive)) + program_context (async\wrap ($/program.context archive)) host_dependencies (..load_host_dependencies (get@ #platform.&file_system platform) compilation_host_dependencies) _ (..package! (for {@.old (file.async file.default) @.jvm (file.async file.default) @@ -166,7 +166,7 @@ (#/cli.Export export) (<| (or_crash! "Export failed:") - (do (try.with promise.monad) + (do (try.with async.monad) [_ (/export.export (get@ #platform.&file_system platform) export)] (wrap (debug.log! "Export complete!")))) @@ -175,9 +175,9 @@ ## TODO: Fix the interpreter... (undefined) ## (<| (or_crash! "Interpretation failed:") - ## (do {! promise.monad} + ## (do {! async.monad} ## [console (|> console.default - ## promise.future + ## async.future ## (\ ! map (|>> try.assumed console.async)))] - ## (interpreter.run (try.with promise.monad) console platform interpretation generation_bundle))) + ## (interpreter.run (try.with async.monad) console platform interpretation generation_bundle))) )))) diff --git a/stdlib/source/program/compositor/export.lux b/stdlib/source/program/compositor/export.lux index 9fe95684e..f17feaf22 100644 --- a/stdlib/source/program/compositor/export.lux +++ b/stdlib/source/program/compositor/export.lux @@ -6,7 +6,7 @@ [control ["." try (#+ Try)] [concurrency - ["." promise (#+ Promise)]]] + ["." async (#+ Async)]]] [data ["." text ["%" format (#+ format)]] @@ -40,8 +40,8 @@ #tar.group commons})) (def: #export (library fs sources) - (-> (file.System Promise) (List Source) (Promise (Try tar.Tar))) - (do (try.with promise.monad) + (-> (file.System Async) (List Source) (Async (Try tar.Tar))) + (do (try.with async.monad) [files (io.enumerate fs sources)] (|> (dictionary.entries files) (monad.map try.monad @@ -60,11 +60,11 @@ ..no_ownership source_code]))))) (\ try.monad map row.of_list) - (\ promise.monad wrap)))) + (\ async.monad wrap)))) (def: #export (export fs [sources target]) - (-> (file.System Promise) Export (Promise (Try Any))) - (do {! (try.with promise.monad)} + (-> (file.System Async) Export (Async (Try Any))) + (do {! (try.with async.monad)} [tar (\ ! map (binary.run tar.writer) (..library fs sources))] (|> ..file diff --git a/stdlib/source/program/compositor/import.lux b/stdlib/source/program/compositor/import.lux index 4edb82a5e..db46d6c13 100644 --- a/stdlib/source/program/compositor/import.lux +++ b/stdlib/source/program/compositor/import.lux @@ -7,7 +7,7 @@ ["." try (#+ Try)] ["." exception (#+ exception:)] [concurrency - ["." promise (#+ Promise) ("#\." monad)]] + ["." async (#+ Async) ("#\." monad)]] ["<>" parser ["<.>" binary]]] [data @@ -30,7 +30,7 @@ [cli (#+ Library)]]) (def: Action - (type (All [a] (Promise (Try a))))) + (type (All [a] (Async (Try a))))) (exception: #export useless_tar_entry) @@ -43,8 +43,8 @@ (Dictionary file.Path Binary)) (def: (import_library system library import) - (-> (file.System Promise) Library Import (Action Import)) - (let [! promise.monad] + (-> (file.System Async) Library Import (Action Import)) + (let [! async.monad] (|> library (\ system read) (\ ! map (let [! try.monad] @@ -68,9 +68,9 @@ (\ ! join))))))) (def: #export (import system libraries) - (-> (file.System Promise) (List Library) (Action Import)) + (-> (file.System Async) (List Library) (Action Import)) (monad.fold (: (Monad Action) - (try.with promise.monad)) + (try.with async.monad)) (..import_library system) (dictionary.new text.hash) libraries)) diff --git a/stdlib/source/program/scriptum.lux b/stdlib/source/program/scriptum.lux index 708db73dd..5d3117062 100644 --- a/stdlib/source/program/scriptum.lux +++ b/stdlib/source/program/scriptum.lux @@ -127,7 +127,7 @@ _ (|> members - (list.zip/2 tags) + (list.zipped/2 tags) (list\map (function (_ [[_ t_name] type]) (case type (#.Product _) @@ -150,7 +150,7 @@ _ (let [member_docs (|> members - (list.zip/2 tags) + (list.zipped/2 tags) (list\map (function (_ [[_ t_name] type]) (if signature? (format "(: " (pprint_type_definition level type_func_info #.None module signature? recursive_type? type) text.new_line " " t_name ")") @@ -378,7 +378,7 @@ ")")))) _ - (meta.fail (exception.construct anonymous_type_definition type)))) + (meta.failure (exception.construct anonymous_type_definition type)))) (def: (document_types module types) (-> Text (List Value) (Meta (Markdown Block))) @@ -510,7 +510,7 @@ lux_exports (monad.map ! (function.compose meta.exports product.left) lux_modules) module_documentation (|> (list\map organize_definitions lux_exports) - (list.zip/2 lux_modules) + (list.zipped/2 lux_modules) (monad.map ! document_module)) #let [_ (io.run (monad.map io.monad save_documentation! module_documentation))]] (wrap (list)))) |