aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/program
diff options
context:
space:
mode:
authorEduardo Julian2022-03-16 08:37:23 -0400
committerEduardo Julian2022-03-16 08:37:23 -0400
commitbf53ee92fc3c33a4885aa227e55d24f7ba3cb2c4 (patch)
tree49683a62ae8e110c62b42a9a6386bb2ddb3c47c6 /stdlib/source/program
parentd710d9f4fc098e7c243c8a5f23cd42683f13e07f (diff)
De-sigil-ification: prefix :
Diffstat (limited to 'stdlib/source/program')
-rw-r--r--stdlib/source/program/aedifex/action.lux18
-rw-r--r--stdlib/source/program/aedifex/artifact/time/date.lux20
-rw-r--r--stdlib/source/program/aedifex/command/build.lux10
-rw-r--r--stdlib/source/program/aedifex/dependency/deployment.lux16
-rw-r--r--stdlib/source/program/aedifex/dependency/resolution.lux10
-rw-r--r--stdlib/source/program/aedifex/hash.lux14
-rw-r--r--stdlib/source/program/aedifex/metadata/snapshot.lux14
-rw-r--r--stdlib/source/program/aedifex/parser.lux78
-rw-r--r--stdlib/source/program/aedifex/repository.lux54
-rw-r--r--stdlib/source/program/aedifex/repository/remote.lux32
-rw-r--r--stdlib/source/program/compositor.lux36
11 files changed, 151 insertions, 151 deletions
diff --git a/stdlib/source/program/aedifex/action.lux b/stdlib/source/program/aedifex/action.lux
index 4990dfed9..d9e168e9f 100644
--- a/stdlib/source/program/aedifex/action.lux
+++ b/stdlib/source/program/aedifex/action.lux
@@ -1,16 +1,16 @@
(.using
- [library
- [lux "*"
- [abstract
- [monad {"+" Monad}]]
- [control
- ["[0]" try {"+" Try}]
- [concurrency
- ["[0]" async {"+" Async}]]]]])
+ [library
+ [lux "*"
+ [abstract
+ [monad {"+" Monad}]]
+ [control
+ ["[0]" try {"+" Try}]
+ [concurrency
+ ["[0]" async {"+" Async}]]]]])
(type: .public (Action a)
(Async (Try a)))
(def: .public monad
(Monad Action)
- (:expected (try.with async.monad)))
+ (as_expected (try.with async.monad)))
diff --git a/stdlib/source/program/aedifex/artifact/time/date.lux b/stdlib/source/program/aedifex/artifact/time/date.lux
index 8189c6978..862eeec23 100644
--- a/stdlib/source/program/aedifex/artifact/time/date.lux
+++ b/stdlib/source/program/aedifex/artifact/time/date.lux
@@ -21,7 +21,7 @@
["[0]" year]
["[0]" month]]
[type
- abstract]]])
+ [abstract {"-" pattern}]]]])
(def: .public (pad value)
(-> Nat Text)
@@ -43,7 +43,7 @@
(def: .public epoch
Date
- (:abstraction date.epoch))
+ (abstraction date.epoch))
(def: .public (date raw)
(-> date.Date (Try Date))
@@ -51,24 +51,24 @@
(if (or (i.< ..min_year year)
(i.> ..max_year year))
(exception.except ..year_is_out_of_range [(date.year raw)])
- {try.#Success (:abstraction raw)})))
+ {try.#Success (abstraction raw)})))
(def: .public value
(-> Date date.Date)
- (|>> :representation))
+ (|>> representation))
(implementation: .public equivalence
(Equivalence Date)
(def: (= reference subject)
- (date#= (:representation reference)
- (:representation subject))))
+ (date#= (representation reference)
+ (representation subject))))
(def: .public (format value)
(%.Format Date)
- (%.format (|> value :representation date.year year.value .nat %.nat)
- (|> value :representation date.month month.number ..pad)
- (|> value :representation date.day_of_month ..pad)))
+ (%.format (|> value representation date.year year.value .nat %.nat)
+ (|> value representation date.month month.number ..pad)
+ (|> value representation date.day_of_month ..pad)))
(def: .public parser
(Parser Date)
@@ -79,4 +79,4 @@
month (<>.lifted (month.by_number month))
day_of_month (<>.codec n.decimal (<text>.exactly 2 <text>.decimal))
date (<>.lifted (date.date year month day_of_month))]
- (in (:abstraction date)))))
+ (in (abstraction date)))))
diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux
index b9211ceb0..f55d026a3 100644
--- a/stdlib/source/program/aedifex/command/build.lux
+++ b/stdlib/source/program/aedifex/command/build.lux
@@ -184,8 +184,8 @@
{.#None}
(dictionary.has identity [version dependency] uniques))))
- (: (Dictionary [Group Name] [Version Dependency])
- (dictionary.empty (product.hash text.hash text.hash))))
+ (is (Dictionary [Group Name] [Version Dependency])
+ (dictionary.empty (product.hash text.hash text.hash))))
dictionary.values
(list#each (|>> product.right (..path fs home)))))
@@ -209,9 +209,9 @@
... eventually led to the function hanging/freezing.
... I'm not sure why it happened, but I got this weirder implementation to work.
... TODO: Improve this implementation.
- (let [[read! write!] (: [(Async (Try Any))
- (async.Resolver (Try Any))]
- (async.async []))
+ (let [[read! write!] (is [(Async (Try Any))
+ (async.Resolver (Try Any))]
+ (async.async []))
_ (|> (# process <capability> [])
(async.upon! (function (again ?line)
(case ?line
diff --git a/stdlib/source/program/aedifex/dependency/deployment.lux b/stdlib/source/program/aedifex/dependency/deployment.lux
index f55520ec1..735ec1ebd 100644
--- a/stdlib/source/program/aedifex/dependency/deployment.lux
+++ b/stdlib/source/program/aedifex/dependency/deployment.lux
@@ -44,12 +44,12 @@
(-> (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) (Async (Try Any))))
- (function (_ codec extension hash)
- (|> hash
- (# codec encoded)
- (# utf8.codec encoded)
- (# repository upload (format artifact extension)))))]
+ deploy_hash (is (All (_ h) (-> (Codec Text (Hash h)) Extension (Hash h) (Async (Try Any))))
+ (function (_ codec extension hash)
+ (|> hash
+ (# codec encoded)
+ (# utf8.codec encoded)
+ (# repository upload (format artifact extension)))))]
(do [! (try.with async.monad)]
[_ (# repository upload artifact data)]
(case status
@@ -89,8 +89,8 @@
(def: (update_snapshot [artifact type] now snapshot)
(-> Dependency Instant Metadata (Try Metadata))
(do try.monad
- [now (: (Try ///artifact/time.Time)
- (///artifact/time.of_instant now))
+ [now (is (Try ///artifact/time.Time)
+ (///artifact/time.of_instant now))
.let [version_template (the ///artifact.#version artifact)
snapshot (|> snapshot
(revised [///metadata/snapshot.#versioning ///artifact/versioning.#snapshot]
diff --git a/stdlib/source/program/aedifex/dependency/resolution.lux b/stdlib/source/program/aedifex/dependency/resolution.lux
index 67dbfc37c..45d275527 100644
--- a/stdlib/source/program/aedifex/dependency/resolution.lux
+++ b/stdlib/source/program/aedifex/dependency/resolution.lux
@@ -204,8 +204,8 @@
(List Dependency)
Resolution]))
(loop [repositories repositories
- successes (: (List Dependency) (list))
- failures (: (List Dependency) (list))
+ successes (is (List Dependency) (list))
+ failures (is (List Dependency) (list))
dependencies dependencies
resolution resolution]
(case dependencies
@@ -231,9 +231,9 @@
(case ?package
{try.#Success package}
(do !
- [.let [redundant? (: (Predicate Dependency)
- (predicate.or (# //.equivalence = head)
- (dictionary.key? resolution)))
+ [.let [redundant? (is (Predicate Dependency)
+ (predicate.or (# //.equivalence = head)
+ (dictionary.key? resolution)))
sub_dependencies (|> package
///package.dependencies
(try#each (|>> set.list
diff --git a/stdlib/source/program/aedifex/hash.lux b/stdlib/source/program/aedifex/hash.lux
index d45c8bb6e..e0548920f 100644
--- a/stdlib/source/program/aedifex/hash.lux
+++ b/stdlib/source/program/aedifex/hash.lux
@@ -21,7 +21,7 @@
["n" nat]
["[0]" i64]]]
[type
- abstract]]])
+ [abstract {"-" pattern}]]]])
... TODO: Replace with pure-Lux implementations of these algorithms
... https://en.wikipedia.org/wiki/SHA-1#SHA-1_pseudocode
@@ -42,14 +42,14 @@
(def: .public data
(All (_ h) (-> (Hash h) Binary))
- (|>> :representation))
+ (|>> representation))
(template [<name> <kind> <algorithm>]
[(def: .public (<name> value)
(-> Binary (Hash <kind>))
(|> (java/security/MessageDigest::getInstance [(ffi.as_string <algorithm>)])
(java/security/MessageDigest::digest [value])
- :abstraction))]
+ abstraction))]
[sha-1 ..SHA-1 "SHA-1"]
[md5 ..MD5 "MD5"]
@@ -102,7 +102,7 @@
[(def: .public (<name> data)
(-> Binary (Try (Hash <kind>)))
(if (n.= <size> (binary.size data))
- {try.#Success (:abstraction data)}
+ {try.#Success (abstraction data)}
(exception.except <exception> [data])))]
[as_sha-1 SHA-1 ..sha-1::size ..not_a_sha-1]
@@ -153,7 +153,7 @@
[(implementation: .public <codec>
(Codec Text (Hash <hash>))
- (def: encoded (|>> :representation ..encoded))
+ (def: encoded (|>> representation ..encoded))
(def: decoded (..decoded <nat> <constructor>)))]
[sha-1_codec SHA-1 ..sha-1::size ..as_sha-1]
@@ -165,6 +165,6 @@
(def: (= reference subject)
(# binary.equivalence =
- (:representation reference)
- (:representation subject))))
+ (representation reference)
+ (representation subject))))
)
diff --git a/stdlib/source/program/aedifex/metadata/snapshot.lux b/stdlib/source/program/aedifex/metadata/snapshot.lux
index cc41be0b5..a6552ee00 100644
--- a/stdlib/source/program/aedifex/metadata/snapshot.lux
+++ b/stdlib/source/program/aedifex/metadata/snapshot.lux
@@ -97,14 +97,14 @@
(|> (<xml>.somewhere ///artifact/versioning.parser)
(# ! each
(revised ///artifact/versioning.#versions
- (: (-> (List ///artifact/snapshot/version.Version)
- (List ///artifact/snapshot/version.Version))
- (|>> (pipe.case
- (pattern (list))
- (list <default_version>)
+ (is (-> (List ///artifact/snapshot/version.Version)
+ (List ///artifact/snapshot/version.Version))
+ (|>> (pipe.case
+ (pattern (list))
+ (list <default_version>)
- versions
- versions)))))
+ versions
+ versions)))))
(<>.else [///artifact/versioning.#snapshot {///artifact/snapshot.#Local}
///artifact/versioning.#last_updated ///artifact/time.epoch
///artifact/versioning.#versions (list <default_version>)])))]
diff --git a/stdlib/source/program/aedifex/parser.lux b/stdlib/source/program/aedifex/parser.lux
index 097373529..7b1447b8c 100644
--- a/stdlib/source/program/aedifex/parser.lux
+++ b/stdlib/source/program/aedifex/parser.lux
@@ -202,51 +202,51 @@
(dictionary.of_list text.hash)
(<code>.tuple (<>.some (<>.and <code>.text
<code>.any))))
- .let [^parents (: (Parser (List /.Name))
- (<>.else (list)
- (..plural input "parents" <code>.text)))
- ^identity (: (Parser (Maybe Artifact))
- (<>.maybe
- (..singular input "identity" ..artifact)))
- ^info (: (Parser (Maybe /.Info))
- (<>.maybe
- (..singular input "info" ..info)))
- ^repositories (: (Parser (Set //repository.Address))
- (|> (..plural input "repositories" ..repository)
- (# ! each (set.of_list text.hash))
- (<>.else (set.empty text.hash))
- (# ! each (set.has /.default_repository))))
- ^dependencies (: (Parser (Set //dependency.Dependency))
- (|> (..plural input "dependencies" ..dependency)
- (# ! each (set.of_list //dependency.hash))
- (<>.else (set.empty //dependency.hash))))
+ .let [^parents (is (Parser (List /.Name))
+ (<>.else (list)
+ (..plural input "parents" <code>.text)))
+ ^identity (is (Parser (Maybe Artifact))
+ (<>.maybe
+ (..singular input "identity" ..artifact)))
+ ^info (is (Parser (Maybe /.Info))
+ (<>.maybe
+ (..singular input "info" ..info)))
+ ^repositories (is (Parser (Set //repository.Address))
+ (|> (..plural input "repositories" ..repository)
+ (# ! each (set.of_list text.hash))
+ (<>.else (set.empty text.hash))
+ (# ! each (set.has /.default_repository))))
+ ^dependencies (is (Parser (Set //dependency.Dependency))
+ (|> (..plural input "dependencies" ..dependency)
+ (# ! each (set.of_list //dependency.hash))
+ (<>.else (set.empty //dependency.hash))))
^lux (|> ..dependency
(..singular input //format.lux_compiler_label)
(<>.else /.default_compiler))
^compilers (|> ..compiler
(..plural input "compilers")
(<>.else (list)))
- ^sources (: (Parser (Set /.Source))
- (|> (..plural input "sources" ..source)
- (# ! each (set.of_list text.hash))
- (<>.else (set.of_list text.hash (list /.default_source)))))
- ^target (: (Parser /.Target)
- (|> ..target
- (..singular input "target")
- (<>.else /.default_target)))
- ^program (: (Parser (Maybe Module))
- (<>.maybe
- (..singular input "program" ..module)))
- ^test (: (Parser (Maybe Module))
- (<>.maybe
- (..singular input "test" ..module)))
- ^deploy_repositories (: (Parser (Dictionary Text //repository.Address))
- (<| (# ! each (dictionary.of_list text.hash))
- (<>.else (list))
- (..plural input "deploy_repositories" ..deploy_repository)))
- ^configuration (: (Parser (PList Text))
- (<| (<>.else (list))
- (..plural input "configuration" ..configuration/1)))
+ ^sources (is (Parser (Set /.Source))
+ (|> (..plural input "sources" ..source)
+ (# ! each (set.of_list text.hash))
+ (<>.else (set.of_list text.hash (list /.default_source)))))
+ ^target (is (Parser /.Target)
+ (|> ..target
+ (..singular input "target")
+ (<>.else /.default_target)))
+ ^program (is (Parser (Maybe Module))
+ (<>.maybe
+ (..singular input "program" ..module)))
+ ^test (is (Parser (Maybe Module))
+ (<>.maybe
+ (..singular input "test" ..module)))
+ ^deploy_repositories (is (Parser (Dictionary Text //repository.Address))
+ (<| (# ! each (dictionary.of_list text.hash))
+ (<>.else (list))
+ (..plural input "deploy_repositories" ..deploy_repository)))
+ ^configuration (is (Parser (PList Text))
+ (<| (<>.else (list))
+ (..plural input "configuration" ..configuration/1)))
^java (|> ..runtime
(..singular input "java")
(<>.else //runtime.default_java))
diff --git a/stdlib/source/program/aedifex/repository.lux b/stdlib/source/program/aedifex/repository.lux
index b373db4f8..b44be720f 100644
--- a/stdlib/source/program/aedifex/repository.lux
+++ b/stdlib/source/program/aedifex/repository.lux
@@ -1,28 +1,28 @@
(.using
- [library
- [lux "*"
- [abstract
- [monad {"+" do}]]
- [control
- [io {"+" IO}]
- ["[0]" try {"+" Try}]
- [concurrency
- ["[0]" async {"+" Async}]
- ["[0]" stm]]]
- [data
- [binary {"+" Binary}]]
- [world
- [net
- [uri {"+" URI}]]]]])
+ [library
+ [lux "*"
+ [abstract
+ [monad {"+" do}]]
+ [control
+ [io {"+" IO}]
+ ["[0]" try {"+" Try}]
+ [concurrency
+ ["[0]" async {"+" Async}]
+ ["[0]" stm]]]
+ [data
+ [binary {"+" Binary}]]
+ [world
+ [net
+ [uri {"+" URI}]]]]])
(type: .public (Repository !)
(Interface
- (: Text
- description)
- (: (-> URI (! (Try Binary)))
- download)
- (: (-> URI Binary (! (Try Any)))
- upload)))
+ (is Text
+ description)
+ (is (-> URI (! (Try Binary)))
+ download)
+ (is (-> URI Binary (! (Try Any)))
+ upload)))
(def: .public (async repository)
(-> (Repository IO) (Repository Async))
@@ -38,12 +38,12 @@
(type: .public (Mock s)
(Interface
- (: Text
- the_description)
- (: (-> URI s (Try [s Binary]))
- on_download)
- (: (-> URI Binary s (Try s))
- on_upload)))
+ (is Text
+ the_description)
+ (is (-> URI s (Try [s Binary]))
+ on_download)
+ (is (-> URI Binary s (Try s))
+ on_upload)))
(def: .public (mock mock init)
(All (_ s) (-> (Mock s) s (Repository Async)))
diff --git a/stdlib/source/program/aedifex/repository/remote.lux b/stdlib/source/program/aedifex/repository/remote.lux
index efe3263a4..782b872f1 100644
--- a/stdlib/source/program/aedifex/repository/remote.lux
+++ b/stdlib/source/program/aedifex/repository/remote.lux
@@ -61,11 +61,11 @@
address)
(def: (download uri)
(do [! (try.with io.monad)]
- [[status message] (: (IO (Try (@http.Response IO)))
- (http.get (format address uri)
- (http.headers ..base_headers)
- {.#None}
- http))]
+ [[status message] (is (IO (Try (@http.Response IO)))
+ (http.get (format address uri)
+ (http.headers ..base_headers)
+ {.#None}
+ http))]
(case status
(pattern (static http/status.ok))
(# ! each product.right ((the @http.#body message) {.#None}))
@@ -77,17 +77,17 @@
(def: (upload uri content)
(do (try.with io.monad)
- [[status message] (: (IO (Try (@http.Response IO)))
- (http.put (format address uri)
- (http.headers (case identity
- {.#None}
- ..base_headers
-
- {.#Some [user password]}
- (list& ["Authorization" (//identity.basic_auth user password)]
- ..base_headers)))
- {.#Some content}
- http))
+ [[status message] (is (IO (Try (@http.Response IO)))
+ (http.put (format address uri)
+ (http.headers (case identity
+ {.#None}
+ ..base_headers
+
+ {.#Some [user password]}
+ (list& ["Authorization" (//identity.basic_auth user password)]
+ ..base_headers)))
+ {.#Some content}
+ http))
_ ((the @http.#body message) {.#Some 0})]
(case status
(pattern (static http/status.created))
diff --git a/stdlib/source/program/compositor.lux b/stdlib/source/program/compositor.lux
index 13b2e434e..e67c28d0d 100644
--- a/stdlib/source/program/compositor.lux
+++ b/stdlib/source/program/compositor.lux
@@ -1,7 +1,7 @@
(.using
[library
[lux {"-" Module}
- [type {"+" :sharing}]
+ [type {"+" sharing}]
["@" target]
["[0]" debug]
[abstract
@@ -117,8 +117,8 @@
(do [! (try.with async.monad)]
[]
(loop [pending host_dependencies
- output (: (Dictionary file.Path Binary)
- (dictionary.empty text.hash))]
+ output (is (Dictionary file.Path Binary)
+ (dictionary.empty text.hash))]
(case pending
{.#End}
(in output)
@@ -157,21 +157,21 @@
(do (try.with async.monad)
[.let [[compilation_host_dependencies compilation_libraries compilation_compilers compilation_sources compilation_target compilation_module compilation_configuration] compilation]
import (import.import (the platform.#&file_system platform) compilation_libraries)
- [state archive phase_wrapper] (:sharing [<parameters>]
- (Platform <parameters>)
- platform
-
- (Async (Try [(directive.State+ <parameters>)
- Archive
- phase.Wrapper]))
- (:expected (platform.initialize file_context compilation_module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender
- import compilation_sources compilation_configuration)))
- [archive state] (:sharing [<parameters>]
- (Platform <parameters>)
- platform
-
- (Async (Try [Archive (directive.State+ <parameters>)]))
- (:expected (platform.compile lux_compiler phase_wrapper import file_context expander platform compilation [archive state])))
+ [state archive phase_wrapper] (sharing [<parameters>]
+ (Platform <parameters>)
+ platform
+
+ (Async (Try [(directive.State+ <parameters>)
+ Archive
+ phase.Wrapper]))
+ (as_expected (platform.initialize file_context compilation_module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender
+ import compilation_sources compilation_configuration)))
+ [archive state] (sharing [<parameters>]
+ (Platform <parameters>)
+ platform
+
+ (Async (Try [Archive (directive.State+ <parameters>)]))
+ (as_expected (platform.compile lux_compiler phase_wrapper import file_context expander platform compilation [archive state])))
_ (cache.cache! (the platform.#&file_system platform) file_context archive)
host_dependencies (..load_host_dependencies (the platform.#&file_system platform) compilation_host_dependencies)
_ (..package! (for @.old (file.async file.default)