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.lux162
1 files changed, 81 insertions, 81 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 ba2cec5c2..ee2e507e8 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -95,7 +95,7 @@
(do async.monad
[? (\ fs directory? path)]
(if ?
- (wrap (#try.Success []))
+ (in (#try.Success []))
(\ fs make_directory path))))
(def: #export (prepare fs static module_id)
@@ -104,7 +104,7 @@
[#let [module (..module fs static module_id)]
module_exists? (\ fs directory? module)]
(if module_exists?
- (wrap (#try.Success []))
+ (in (#try.Success []))
(do (try.with !)
[_ (ensure_directory fs (..unversioned_lux_archive fs static))
_ (ensure_directory fs (..versioned_lux_archive fs static))]
@@ -114,9 +114,9 @@
(#try.Success [])
(#try.Failure error)
- (exception.throw ..cannot_prepare [(..archive fs static)
- module_id
- error])))))))))
+ (exception.except ..cannot_prepare [(..archive fs static)
+ module_id
+ error])))))))))
(def: #export (write fs static module_id artifact_id content)
(-> (file.System Async) Static archive.ID artifact.ID Binary (Async (Try Any)))
@@ -172,9 +172,9 @@
(do !
[[descriptor document output] (archive.find module archive)
content (document.read $.key document)]
- (wrap [module content])))
+ (in [module content])))
(archive.archived archive)))]
- (wrap (set@ #.modules modules (fresh_analysis_state host)))))
+ (in (set@ #.modules modules (fresh_analysis_state host)))))
(def: (cached_artifacts fs static module_id)
(-> (file.System Async) Static archive.ID (Async (Try (Dictionary Text Binary))))
@@ -233,85 +233,85 @@
(do !
[#let [output (row.add [artifact_id #.None data] output)]
_ (\ host re_learn context #.None directive)]
- (wrap [definitions
- [analysers
- synthesizers
- generators
- directives]
- output]))
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output]))
(#artifact.Definition name)
(let [output (row.add [artifact_id #.None data] output)]
(if (text\= $/program.name name)
- (wrap [definitions
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output])
+ (do !
+ [value (\ host re_load context #.None directive)]
+ (in [(dictionary.put name value definitions)
[analysers
synthesizers
generators
directives]
- output])
- (do !
- [value (\ host re_load context #.None directive)]
- (wrap [(dictionary.put name value definitions)
- [analysers
- synthesizers
- generators
- directives]
- output]))))
+ output]))))
(#artifact.Analyser extension)
(do !
[#let [output (row.add [artifact_id #.None data] output)]
value (\ host re_load context #.None directive)]
- (wrap [definitions
- [(dictionary.put extension (:as analysis.Handler value) analysers)
- synthesizers
- generators
- directives]
- output]))
+ (in [definitions
+ [(dictionary.put extension (:as analysis.Handler value) analysers)
+ synthesizers
+ generators
+ directives]
+ output]))
(#artifact.Synthesizer extension)
(do !
[#let [output (row.add [artifact_id #.None data] output)]
value (\ host re_load context #.None directive)]
- (wrap [definitions
- [analysers
- (dictionary.put extension (:as synthesis.Handler value) synthesizers)
- generators
- directives]
- output]))
+ (in [definitions
+ [analysers
+ (dictionary.put extension (:as synthesis.Handler value) synthesizers)
+ generators
+ directives]
+ output]))
(#artifact.Generator extension)
(do !
[#let [output (row.add [artifact_id #.None data] output)]
value (\ host re_load context #.None directive)]
- (wrap [definitions
- [analysers
- synthesizers
- (dictionary.put extension (:as generation.Handler value) generators)
- directives]
- output]))
+ (in [definitions
+ [analysers
+ synthesizers
+ (dictionary.put extension (:as generation.Handler value) generators)
+ directives]
+ output]))
(#artifact.Directive extension)
(do !
[#let [output (row.add [artifact_id #.None data] output)]
value (\ host re_load context #.None directive)]
- (wrap [definitions
- [analysers
- synthesizers
- generators
- (dictionary.put extension (:as directive.Handler value) directives)]
- output]))
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ (dictionary.put extension (:as directive.Handler value) directives)]
+ output]))
(#artifact.Custom name)
(do !
[#let [output (row.add [artifact_id (#.Some name) data] output)]
_ (\ host re_learn context (#.Some name) directive)]
- (wrap [definitions
- [analysers
- synthesizers
- generators
- directives]
- output]))))
+ (in [definitions
+ [analysers
+ synthesizers
+ generators
+ directives]
+ output]))))
(#try.Success [definitions' bundles' output'])
(recur input' definitions' bundles' output')
@@ -324,7 +324,7 @@
definitions (monad.map ! (function (_ [def_name def_global])
(case def_global
(#.Alias alias)
- (wrap [def_name (#.Alias alias)])
+ (in [def_name (#.Alias alias)])
(#.Definition [exported? type annotations _])
(|> definitions
@@ -334,8 +334,8 @@
#.Definition
[def_name])))))
(get@ #.definitions content))]
- (wrap [(document.write $.key (set@ #.definitions definitions content))
- bundles])))
+ (in [(document.write $.key (set@ #.definitions definitions content))
+ bundles])))
(def: (load_definitions fs static module_id host_environment descriptor document)
(All [expression directive]
@@ -346,8 +346,8 @@
(do (try.with async.monad)
[actual (cached_artifacts fs static module_id)
#let [expected (|> descriptor (get@ #descriptor.registry) artifact.artifacts)]
- [document bundles output] (async\wrap (loaded_document (get@ #static.artifact_extension static) host_environment module_id expected actual document))]
- (wrap [[descriptor document output] bundles])))
+ [document bundles output] (async\in (loaded_document (get@ #static.artifact_extension static) host_environment module_id expected actual document))]
+ (in [[descriptor document output] bundles])))
(def: (purge! fs static [module_name module_id])
(-> (file.System Async) Static [Module archive.ID] (Async (Try Any)))
@@ -412,14 +412,14 @@
(monad.map ! (function (_ [module_name module_id])
(do !
[data (..read_module_descriptor fs static module_id)
- [descriptor document] (async\wrap (<binary>.run ..parser data))]
+ [descriptor document] (async\in (<binary>.run ..parser data))]
(if (text\= archive.runtime_module module_name)
- (wrap [true
- [module_name [module_id [descriptor document]]]])
+ (in [true
+ [module_name [module_id [descriptor document]]]])
(do !
[input (//context.read fs ..pseudo_module import contexts (get@ #static.host_module_extension static) module_name)]
- (wrap [(..valid_cache? descriptor input)
- [module_name [module_id [descriptor document]]]])))))))
+ (in [(..valid_cache? descriptor input)
+ [module_name [module_id [descriptor document]]]])))))))
load_order (|> pre_loaded_caches
(list\map product.right)
(monad.fold try.monad
@@ -428,7 +428,7 @@
archive)
(\ try.monad map (dependency.load_order $.key))
(\ try.monad join)
- async\wrap)
+ async\in)
#let [purge (..full_purge pre_loaded_caches load_order)]
_ (|> purge
dictionary.entries
@@ -438,9 +438,9 @@
(monad.map ! (function (_ [module_name [module_id [descriptor document _]]])
(do !
[[descriptor,document,output bundles] (..load_definitions fs static module_id host_environment descriptor document)]
- (wrap [[module_name descriptor,document,output]
- bundles])))))]
- (async\wrap
+ (in [[module_name descriptor,document,output]
+ bundles])))))]
+ (async\in
(do {! try.monad}
[archive (monad.fold !
(function (_ [[module descriptor,document,output] _bundle] archive)
@@ -448,16 +448,16 @@
archive
loaded_caches)
analysis_state (..analysis_state (get@ #static.host static) archive)]
- (wrap [archive
- analysis_state
- (list\fold (function (_ [_ [+analysers +synthesizers +generators +directives]]
- [analysers synthesizers generators directives])
- [(dictionary.merge +analysers analysers)
- (dictionary.merge +synthesizers synthesizers)
- (dictionary.merge +generators generators)
- (dictionary.merge +directives directives)])
- ..empty_bundles
- loaded_caches)])))))
+ (in [archive
+ analysis_state
+ (list\fold (function (_ [_ [+analysers +synthesizers +generators +directives]]
+ [analysers synthesizers generators directives])
+ [(dictionary.merge +analysers analysers)
+ (dictionary.merge +synthesizers synthesizers)
+ (dictionary.merge +generators generators)
+ (dictionary.merge +directives directives)])
+ ..empty_bundles
+ loaded_caches)])))))
(def: #export (thaw host_environment fs static import contexts)
(All [expression directive]
@@ -468,10 +468,10 @@
(case binary
(#try.Success binary)
(do (try.with async.monad)
- [archive (async\wrap (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)
- (wrap (#try.Success [archive.empty
- (fresh_analysis_state (get@ #static.host static))
- ..empty_bundles])))))
+ (in (#try.Success [archive.empty
+ (fresh_analysis_state (get@ #static.host static))
+ ..empty_bundles])))))