aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux110
1 files changed, 55 insertions, 55 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
index a41580fd6..11b6414f6 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -10,16 +10,16 @@
["[0]" try {"+" [Try]}]
["[0]" exception {"+" [exception:]}]
[concurrency
- ["[0]" async {"+" [Async]} ("[1]\[0]" monad)]]
+ ["[0]" async {"+" [Async]} ("[1]#[0]" monad)]]
["<>" parser
["<[0]>" binary {"+" [Parser]}]]]
[data
[binary {"+" [Binary]}]
["[0]" product]
- ["[0]" text ("[1]\[0]" equivalence)
+ ["[0]" text ("[1]#[0]" equivalence)
["%" format {"+" [format]}]]
[collection
- ["[0]" list ("[1]\[0]" functor mix)]
+ ["[0]" list ("[1]#[0]" functor mix)]
["[0]" dictionary {"+" [Dictionary]}]
["[0]" row {"+" [Row]}]
["[0]" set]]]
@@ -62,55 +62,55 @@
(def: (archive fs static)
(All (_ !) (-> (file.System !) Static file.Path))
(format (value@ static.#target static)
- (\ fs separator)
+ (# fs separator)
(value@ static.#host static)))
(def: (unversioned_lux_archive fs static)
(All (_ !) (-> (file.System !) Static file.Path))
(format (..archive fs static)
- (\ fs separator)
+ (# fs separator)
//.lux_context))
(def: (versioned_lux_archive fs static)
(All (_ !) (-> (file.System !) Static file.Path))
(format (..unversioned_lux_archive fs static)
- (\ fs separator)
+ (# fs separator)
(%.nat version.version)))
(def: (module fs static module_id)
(All (_ !) (-> (file.System !) Static archive.ID file.Path))
(format (..versioned_lux_archive fs static)
- (\ fs separator)
+ (# fs separator)
(%.nat module_id)))
(def: .public (artifact fs static module_id artifact_id)
(All (_ !) (-> (file.System !) Static archive.ID artifact.ID file.Path))
(format (..module fs static module_id)
- (\ fs separator)
+ (# fs separator)
(%.nat artifact_id)
(value@ static.#artifact_extension static)))
(def: (ensure_directory fs path)
(-> (file.System Async) file.Path (Async (Try Any)))
(do async.monad
- [? (\ fs directory? path)]
+ [? (# fs directory? path)]
(if ?
(in {try.#Success []})
- (\ fs make_directory path))))
+ (# fs make_directory path))))
(def: .public (prepare fs static module_id)
(-> (file.System Async) Static archive.ID (Async (Try Any)))
(do [! async.monad]
[.let [module (..module fs static module_id)]
- module_exists? (\ fs directory? module)]
+ module_exists? (# fs directory? module)]
(if module_exists?
(in {try.#Success []})
(do (try.with !)
[_ (ensure_directory fs (..unversioned_lux_archive fs static))
_ (ensure_directory fs (..versioned_lux_archive fs static))]
(|> module
- (\ fs make_directory)
- (\ ! each (|>> (case> {try.#Success output}
+ (# fs make_directory)
+ (# ! each (|>> (case> {try.#Success output}
{try.#Success []}
{try.#Failure error}
@@ -120,7 +120,7 @@
(def: .public (write fs static module_id artifact_id content)
(-> (file.System Async) Static archive.ID artifact.ID Binary (Async (Try Any)))
- (\ fs write content (..artifact fs static module_id artifact_id)))
+ (# fs write content (..artifact fs static module_id artifact_id)))
(def: .public (enable fs static)
(-> (file.System Async) Static (Async (Try Any)))
@@ -131,12 +131,12 @@
(def: (general_descriptor fs static)
(-> (file.System Async) Static file.Path)
(format (..archive fs static)
- (\ fs separator)
+ (# fs separator)
"general_descriptor"))
(def: .public (freeze fs static archive)
(-> (file.System Async) Static Archive (Async (Try Any)))
- (\ fs write (archive.export ///.version archive) (..general_descriptor fs static)))
+ (# fs write (archive.export ///.version archive) (..general_descriptor fs static)))
(def: module_descriptor_file
"module_descriptor")
@@ -144,16 +144,16 @@
(def: (module_descriptor fs static module_id)
(-> (file.System Async) Static archive.ID file.Path)
(format (..module fs static module_id)
- (\ fs separator)
+ (# fs separator)
..module_descriptor_file))
(def: .public (cache fs static module_id content)
(-> (file.System Async) Static archive.ID Binary (Async (Try Any)))
- (\ fs write content (..module_descriptor fs static module_id)))
+ (# fs write content (..module_descriptor fs static module_id)))
(def: (read_module_descriptor fs static module_id)
(-> (file.System Async) Static archive.ID (Async (Try Binary)))
- (\ fs read (..module_descriptor fs static module_id)))
+ (# fs read (..module_descriptor fs static module_id)))
(def: parser
(Parser [Descriptor (Document .Module)])
@@ -180,16 +180,16 @@
(-> (file.System Async) Static archive.ID (Async (Try (Dictionary Text Binary))))
(let [! (try.with async.monad)]
(|> (..module fs static module_id)
- (\ fs directory_files)
- (\ ! each (|>> (list\each (function (_ file)
+ (# fs directory_files)
+ (# ! each (|>> (list#each (function (_ file)
[(file.name fs file) file]))
- (list.only (|>> product.left (text\= ..module_descriptor_file) not))
+ (list.only (|>> product.left (text#= ..module_descriptor_file) not))
(monad.each ! (function (_ [name path])
(|> path
- (\ fs read)
- (\ ! each (|>> [name])))))
- (\ ! each (dictionary.of_list text.hash))))
- (\ ! conjoint))))
+ (# fs read)
+ (# ! each (|>> [name])))))
+ (# ! each (dictionary.of_list text.hash))))
+ (# ! conjoint))))
(type: Definitions (Dictionary Text Any))
(type: Analysers (Dictionary Text analysis.Handler))
@@ -227,12 +227,12 @@
(case (do !
[data (try.of_maybe (dictionary.value (format (%.nat artifact_id) extension) actual))
.let [context [module_id artifact_id]
- directive (\ host ingest context data)]]
+ directive (# host ingest context data)]]
(case artifact_category
{artifact.#Anonymous}
(do !
[.let [output (row.suffix [artifact_id .#None data] output)]
- _ (\ host re_learn context {.#None} directive)]
+ _ (# host re_learn context {.#None} directive)]
(in [definitions
[analysers
synthesizers
@@ -242,7 +242,7 @@
{artifact.#Definition name}
(let [output (row.suffix [artifact_id {.#None} data] output)]
- (if (text\= $/program.name name)
+ (if (text#= $/program.name name)
(in [definitions
[analysers
synthesizers
@@ -250,7 +250,7 @@
directives]
output])
(do !
- [value (\ host re_load context {.#None} directive)]
+ [value (# host re_load context {.#None} directive)]
(in [(dictionary.has name value definitions)
[analysers
synthesizers
@@ -261,7 +261,7 @@
{artifact.#Analyser extension}
(do !
[.let [output (row.suffix [artifact_id {.#None} data] output)]
- value (\ host re_load context {.#None} directive)]
+ value (# host re_load context {.#None} directive)]
(in [definitions
[(dictionary.has extension (:as analysis.Handler value) analysers)
synthesizers
@@ -272,7 +272,7 @@
{artifact.#Synthesizer extension}
(do !
[.let [output (row.suffix [artifact_id {.#None} data] output)]
- value (\ host re_load context {.#None} directive)]
+ value (# host re_load context {.#None} directive)]
(in [definitions
[analysers
(dictionary.has extension (:as synthesis.Handler value) synthesizers)
@@ -283,7 +283,7 @@
{artifact.#Generator extension}
(do !
[.let [output (row.suffix [artifact_id {.#None} data] output)]
- value (\ host re_load context {.#None} directive)]
+ value (# host re_load context {.#None} directive)]
(in [definitions
[analysers
synthesizers
@@ -294,7 +294,7 @@
{artifact.#Directive extension}
(do !
[.let [output (row.suffix [artifact_id {.#None} data] output)]
- value (\ host re_load context {.#None} directive)]
+ value (# host re_load context {.#None} directive)]
(in [definitions
[analysers
synthesizers
@@ -305,7 +305,7 @@
{artifact.#Custom name}
(do !
[.let [output (row.suffix [artifact_id {.#Some name} data] output)]
- _ (\ host re_learn context {.#Some name} directive)]
+ _ (# host re_learn context {.#Some name} directive)]
(in [definitions
[analysers
synthesizers
@@ -334,7 +334,7 @@
(|> definitions
(dictionary.value def_name)
try.of_maybe
- (\ ! each (|>> [exported? type]
+ (# ! each (|>> [exported? type]
{.#Definition}
[def_name])))
@@ -342,7 +342,7 @@
(|> definitions
(dictionary.value def_name)
try.of_maybe
- (\ ! each (function (_ def_value)
+ (# ! each (function (_ def_value)
[def_name {.#Type [exported? (:as .Type def_value) labels]}])))))
(value@ .#definitions content))]
(in [(document.write $.key (with@ .#definitions definitions content))
@@ -357,7 +357,7 @@
(do (try.with async.monad)
[actual (cached_artifacts fs static module_id)
.let [expected (|> descriptor (value@ descriptor.#registry) artifact.artifacts)]
- [document bundles output] (async\in (loaded_document (value@ static.#artifact_extension static) host_environment module_id expected actual document))]
+ [document bundles output] (async#in (loaded_document (value@ static.#artifact_extension static) host_environment module_id expected actual document))]
(in [[descriptor document output] bundles])))
(def: (purge! fs static [module_name module_id])
@@ -365,16 +365,16 @@
(do [! (try.with async.monad)]
[.let [cache (..module fs static module_id)]
_ (|> cache
- (\ fs directory_files)
- (\ ! each (monad.each ! (\ fs delete)))
- (\ ! conjoint))]
- (\ fs delete cache)))
+ (# fs directory_files)
+ (# ! each (monad.each ! (# fs delete)))
+ (# ! conjoint))]
+ (# fs delete cache)))
(def: (valid_cache? expected actual)
(-> Descriptor Input Bit)
- (and (text\= (value@ descriptor.#name expected)
+ (and (text#= (value@ descriptor.#name expected)
(value@ ////.#module actual))
- (text\= (value@ descriptor.#file expected)
+ (text#= (value@ descriptor.#file expected)
(value@ ////.#file actual))
(n.= (value@ descriptor.#hash expected)
(value@ ////.#hash actual))))
@@ -395,7 +395,7 @@
(-> (List [Bit [Module [archive.ID [Descriptor (Document .Module)]]]])
dependency.Order
Purge)
- (list\mix (function (_ [module_name [module_id [descriptor document]]] purge)
+ (list#mix (function (_ [module_name [module_id [descriptor document]]] purge)
(let [purged? (: (Predicate Module)
(dictionary.key? purge))]
(if (purged? module_name)
@@ -423,8 +423,8 @@
(monad.each ! (function (_ [module_name module_id])
(do !
[data (..read_module_descriptor fs static module_id)
- [descriptor document] (async\in (<binary>.result ..parser data))]
- (if (text\= archive.runtime_module module_name)
+ [descriptor document] (async#in (<binary>.result ..parser data))]
+ (if (text#= archive.runtime_module module_name)
(in [true
[module_name [module_id [descriptor document]]]])
(do !
@@ -432,14 +432,14 @@
(in [(..valid_cache? descriptor input)
[module_name [module_id [descriptor document]]]])))))))
load_order (|> pre_loaded_caches
- (list\each product.right)
+ (list#each product.right)
(monad.mix try.monad
(function (_ [module [module_id [descriptor document]]] archive)
(archive.has module [descriptor document (: Output row.empty)] archive))
archive)
- (\ try.monad each (dependency.load_order $.key))
- (\ try.monad conjoint)
- async\in)
+ (# try.monad each (dependency.load_order $.key))
+ (# try.monad conjoint)
+ async#in)
.let [purge (..full_purge pre_loaded_caches load_order)]
_ (|> purge
dictionary.entries
@@ -451,7 +451,7 @@
[[descriptor,document,output bundles] (..load_definitions fs static module_id host_environment descriptor document)]
(in [[module_name descriptor,document,output]
bundles])))))]
- (async\in
+ (async#in
(do [! try.monad]
[archive (monad.mix !
(function (_ [[module descriptor,document,output] _bundle] archive)
@@ -461,7 +461,7 @@
analysis_state (..analysis_state (value@ static.#host static) archive)]
(in [archive
analysis_state
- (list\mix (function (_ [_ [+analysers +synthesizers +generators +directives]]
+ (list#mix (function (_ [_ [+analysers +synthesizers +generators +directives]]
[analysers synthesizers generators directives])
[(dictionary.merged +analysers analysers)
(dictionary.merged +synthesizers synthesizers)
@@ -475,11 +475,11 @@
(-> (generation.Host expression directive) (file.System Async) Static Import (List Context)
(Async (Try [Archive .Lux Bundles]))))
(do async.monad
- [binary (\ fs read (..general_descriptor fs static))]
+ [binary (# fs read (..general_descriptor fs static))]
(case binary
{try.#Success binary}
(do (try.with async.monad)
- [archive (async\in (archive.import ///.version binary))]
+ [archive (async#in (archive.import ///.version binary))]
(..load_every_reserved_module host_environment fs static import contexts archive))
{try.#Failure error}