aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/meta
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/document.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux10
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux110
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/context.lux44
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux8
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux16
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/script.lux12
12 files changed, 119 insertions, 119 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
index 2c5b688a2..16486e75b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux
@@ -20,13 +20,13 @@
[format
["[0]" binary {"+" [Writer]}]]
[collection
- ["[0]" list ("[1]\[0]" functor mix)]
+ ["[0]" list ("[1]#[0]" functor mix)]
["[0]" dictionary {"+" [Dictionary]}]
["[0]" set]
["[0]" row {"+" [Row]}]]]
[math
[number
- ["n" nat ("[1]\[0]" equivalence)]]]
+ ["n" nat ("[1]#[0]" equivalence)]]]
[type
abstract]]]
[/
@@ -187,7 +187,7 @@
(|>> :representation
(value@ #resolver)
dictionary.entries
- (list\each (function (_ [module [id _]])
+ (list#each (function (_ [module [id _]])
[module id]))))
(def: .public (merged additions archive)
@@ -197,7 +197,7 @@
:representation
(revised@ #next (n.max +next))
(revised@ #resolver (function (_ resolver)
- (list\mix (function (_ [module [id entry]] resolver)
+ (list#mix (function (_ [module [id entry]] resolver)
(case entry
{.#Some _}
(dictionary.has module [id entry] resolver)
@@ -252,7 +252,7 @@
(-> (List Reservation) Bit)
(n.= (list.size reservations)
(|> reservations
- (list\each product.left)
+ (list#each product.left)
(set.of_list text.hash)
set.size)))
@@ -260,7 +260,7 @@
(-> (List Reservation) Bit)
(n.= (list.size reservations)
(|> reservations
- (list\each product.right)
+ (list#each product.right)
(set.of_list n.hash)
set.size)))
@@ -274,12 +274,12 @@
(do try.monad
[[actual next reservations] (<binary>.result ..reader binary)
_ (exception.assertion ..version_mismatch [expected actual]
- (n\= expected actual))
+ (n#= expected actual))
_ (exception.assertion ..corrupt_data []
(correct_reservations? reservations))]
(in (:abstraction
[#next next
- #resolver (list\mix (function (_ [module id] archive)
+ #resolver (list#mix (function (_ [module id] archive)
(dictionary.has module [id {.#None}] archive))
(value@ #resolver (:representation ..empty))
reservations)]))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
index 9681197b8..5295241d4 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -14,7 +14,7 @@
["%" format {"+" [format]}]]
[collection
["[0]" list]
- ["[0]" row {"+" [Row]} ("[1]\[0]" functor mix)]
+ ["[0]" row {"+" [Row]} ("[1]#[0]" functor mix)]
["[0]" dictionary {"+" [Dictionary]}]]
[format
["[0]" binary {"+" [Writer]}]]]
@@ -122,7 +122,7 @@
(binary.row/64 category))]
(|>> :representation
(value@ #artifacts)
- (row\each (value@ #category))
+ (row#each (value@ #category))
artifacts)))
(exception: .public (invalid_category [tag Nat])
@@ -137,7 +137,7 @@
(case tag
(^template [<nat> <tag> <parser>]
[<nat>
- (\ ! each (|>> {<tag>}) <parser>)])
+ (# ! each (|>> {<tag>}) <parser>)])
([0 #Anonymous <binary>.any]
[1 #Definition <binary>.text]
[2 #Analyser <binary>.text]
@@ -148,7 +148,7 @@
_ (<>.failure (exception.error ..invalid_category [tag])))))]
(|> (<binary>.row/64 category)
- (\ <>.monad each (row\mix (function (_ artifact registry)
+ (# <>.monad each (row#mix (function (_ artifact registry)
(product.right
(case artifact
{#Anonymous}
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux
index f1f68d434..622cf2d59 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux
@@ -44,7 +44,7 @@
<b>.text
<b>.text
<b>.nat
- (\ <>.monad in {.#Cached})
+ (# <>.monad in {.#Cached})
(<b>.set text.hash <b>.text)
artifact.parser
))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
index 3207e7b8f..bbb14191a 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux
@@ -34,7 +34,7 @@
(def: .public (read key document)
(All (_ d) (-> (Key d) (Document Any) (Try d)))
(let [[document//signature document//content] (:representation document)]
- (if (\ signature.equivalence =
+ (if (# signature.equivalence =
(key.signature key)
document//signature)
{try.#Success (:sharing [e]
@@ -70,5 +70,5 @@
(def: .public parser
(All (_ d) (-> (Parser d) (Parser (Document d))))
(|>> (<>.and signature.parser)
- (\ <>.monad each (|>> :abstraction))))
+ (# <>.monad each (|>> :abstraction))))
)
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
index a7acc969b..a7bc82364 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
@@ -4,7 +4,7 @@
[abstract
["[0]" monad {"+" [do]}]]
[control
- ["[0]" maybe ("[1]\[0]" functor)]
+ ["[0]" maybe ("[1]#[0]" functor)]
["[0]" try {"+" [Try]}]
["[0]" state]
["[0]" function
@@ -13,7 +13,7 @@
["[0]" text
["%" format {"+" [format]}]]
[collection
- ["[0]" list ("[1]\[0]" functor mix)]
+ ["[0]" list ("[1]#[0]" functor mix)]
["[0]" dictionary {"+" [Dictionary]}]
["[0]" set {"+" [Set]}]]]]]
[///
@@ -47,7 +47,7 @@
(def: .public graph
(-> (List Dependency) Graph)
- (list\mix (function (_ [module imports] graph)
+ (list#mix (function (_ [module imports] graph)
(dictionary.has module imports graph))
..empty))
@@ -63,9 +63,9 @@
{try.#Failure error}
..fresh)]
ancestors (monad.each ! recur (set.list parents))]
- (in (list\mix set.union parents ancestors)))))
+ (in (list#mix set.union parents ancestors)))))
ancestry (memo.open memo)]
- (list\mix (function (_ module memory)
+ (list#mix (function (_ module memory)
(if (dictionary.key? memory module)
memory
(let [[memory _] (ancestry [memory module])]
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io.lux b/stdlib/source/library/lux/tool/compiler/meta/io.lux
index 0d7ab9698..0dc406820 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io.lux
@@ -14,7 +14,7 @@
(def: .public (safe system)
(All (_ m) (-> (System m) Text Text))
- (text.replaced "/" (\ system separator)))
+ (text.replaced "/" (# system separator)))
(def: .public lux_context
"lux")
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}
diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
index 59d06a9fd..95a122edd 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux
@@ -10,10 +10,10 @@
["[0]" try {"+" [Try]}]
["[0]" exception {"+" [exception:]}]
[concurrency
- ["[0]" async {"+" [Async]} ("[1]\[0]" monad)]]]
+ ["[0]" async {"+" [Async]} ("[1]#[0]" monad)]]]
[data
[binary {"+" [Binary]}]
- ["[0]" text ("[1]\[0]" hash)
+ ["[0]" text ("[1]#[0]" hash)
["%" format {"+" [format]}]
[encoding
["[0]" utf8]]]
@@ -52,19 +52,19 @@
(All (_ m) (-> (file.System m) Context Module file.Path))
(|> module
(//.safe fs)
- (format context (\ fs separator))))
+ (format context (# fs separator))))
(def: (find_source_file fs importer contexts module extension)
(-> (file.System Async) Module (List Context) Module Extension
(Async (Try file.Path)))
(case contexts
{.#End}
- (async\in (exception.except ..cannot_find_module [importer module]))
+ (async#in (exception.except ..cannot_find_module [importer module]))
{.#Item context contexts'}
(let [path (format (..path fs context module) extension)]
(do async.monad
- [? (\ fs file? path)]
+ [? (# fs file? path)]
(if ?
(in {try.#Success path})
(find_source_file fs importer contexts' module extension))))))
@@ -83,15 +83,15 @@
(case outcome
{try.#Success path}
(|> path
- (\ fs read)
- (\ (try.with !) each (|>> [path])))
+ (# fs read)
+ (# (try.with !) each (|>> [path])))
{try.#Failure _}
(do [! (try.with !)]
[path (..find_source_file fs importer contexts module ..lux_extension)]
(|> path
- (\ fs read)
- (\ ! each (|>> [path])))))))
+ (# fs read)
+ (# ! each (|>> [path])))))))
(def: (find_library_source_file importer import partial_host_extension module)
(-> Module Import Extension Module (Try [file.Path Binary]))
@@ -128,15 +128,15 @@
(Async (Try Input)))
(do (try.with async.monad)
[[path binary] (..find_any_source_file fs importer import contexts partial_host_extension module)]
- (case (\ utf8.codec decoded binary)
+ (case (# utf8.codec decoded binary)
{try.#Success code}
(in [////.#module module
////.#file path
- ////.#hash (text\hash code)
+ ////.#hash (text#hash code)
////.#code code])
{try.#Failure _}
- (async\in (exception.except ..cannot_read_module [module])))))
+ (async#in (exception.except ..cannot_read_module [module])))))
(type: .public Enumeration
(Dictionary file.Path Binary))
@@ -145,19 +145,19 @@
(-> (file.System Async) Context file.Path Enumeration (Async (Try Enumeration)))
(do [! (try.with async.monad)]
[enumeration (|> directory
- (\ fs directory_files)
- (\ ! each (monad.mix ! (function (_ file enumeration)
+ (# fs directory_files)
+ (# ! each (monad.mix ! (function (_ file enumeration)
(if (text.ends_with? ..lux_extension file)
(do !
- [source_code (\ fs read file)]
- (async\in (dictionary.has' (text.replaced context "" file) source_code enumeration)))
+ [source_code (# fs read file)]
+ (async#in (dictionary.has' (text.replaced context "" file) source_code enumeration)))
(in enumeration)))
enumeration))
- (\ ! conjoint))]
+ (# ! conjoint))]
(|> directory
- (\ fs sub_directories)
- (\ ! each (monad.mix ! (context_listing fs context) enumeration))
- (\ ! conjoint))))
+ (# fs sub_directories)
+ (# ! each (monad.mix ! (context_listing fs context) enumeration))
+ (# ! conjoint))))
(def: Action
(type (All (_ a) (Async (Try a)))))
@@ -165,7 +165,7 @@
(def: (canonical fs context)
(-> (file.System Async) Context (Action Context))
(do (try.with async.monad)
- [subs (\ fs sub_directories context)]
+ [subs (# fs sub_directories context)]
(in (|> subs
list.head
(maybe.else context)
@@ -181,7 +181,7 @@
(do !
[context (..canonical fs context)]
(..context_listing fs
- (format context (\ fs separator))
+ (format context (# fs separator))
context
enumeration)))
(: Enumeration
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
index 73d919175..86e5af12b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
@@ -8,7 +8,7 @@
[collection
[dictionary {"+" [Dictionary]}]
["[0]" row]
- ["[0]" list ("[1]\[0]" functor)]]]
+ ["[0]" list ("[1]#[0]" functor)]]]
[world
["[0]" file]]]]
[//
@@ -33,10 +33,10 @@
(def: .public order
(-> dependency.Order Order)
- (list\each (function (_ [module [module_id [descriptor document]]])
+ (list#each (function (_ [module [module_id [descriptor document]]])
(|> descriptor
(value@ descriptor.#registry)
artifact.artifacts
row.list
- (list\each (|>> (value@ artifact.#id)))
+ (list#each (|>> (value@ artifact.#id)))
[module_id]))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
index 9faeb3b47..10433ddf5 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -5,7 +5,7 @@
[abstract
["[0]" monad {"+" [Monad do]}]]
[control
- ["[0]" maybe ("[1]\[0]" functor)]
+ ["[0]" maybe ("[1]#[0]" functor)]
["[0]" try {"+" [Try]}]]
[data
["[0]" binary {"+" [Binary]}]
@@ -13,7 +13,7 @@
["%" format {"+" [format]}]]
[collection
["[0]" row]
- ["[0]" list ("[1]\[0]" functor)]
+ ["[0]" list ("[1]#[0]" functor)]
["[0]" dictionary]
["[0]" set {"+" [Set]}]]]
[math
@@ -141,7 +141,7 @@
(-> Static archive.ID artifact.ID (Maybe Text) Binary java/util/jar/JarOutputStream
(Try java/util/jar/JarOutputStream))
(let [class_path (|> custom
- (maybe\each (|>> name.internal name.read))
+ (maybe#each (|>> name.internal name.read))
(maybe.else (runtime.class_name [module artifact]))
(text.suffix (value@ static.#artifact_extension static)))]
(do try.monad
@@ -249,7 +249,7 @@
[order (dependency.load_order $.key archive)
.let [buffer (java/io/ByteArrayOutputStream::new (.int ..mebi_byte))]
sink (|> order
- (list\each (function (_ [module [module_id [descriptor document output]]])
+ (list#each (function (_ [module [module_id [descriptor document output]]])
[module_id output]))
(monad.mix ! (..write_module static)
(java/util/jar/JarOutputStream::new buffer (..manifest program))))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
index b5d364a3d..0b7857b58 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux
@@ -14,7 +14,7 @@
["[0]" encoding]]
[collection
["[0]" row]
- ["[0]" list ("[1]\[0]" functor mix)]
+ ["[0]" list ("[1]#[0]" functor mix)]
["[0]" dictionary {"+" [Dictionary]}]
["[0]" set]]
[format
@@ -57,12 +57,12 @@
(def: bundle_module
(-> Output (Try _.Expression))
(|>> row.list
- (list\each product.right)
+ (list#each product.right)
(monad.mix try.monad
(function (_ content so_far)
(|> content
- (\ encoding.utf8 decoded)
- (\ try.monad each
+ (# encoding.utf8 decoded)
+ (# try.monad each
(|>> :expected
(:sharing [directive]
directive
@@ -107,11 +107,11 @@
(value@ descriptor.#references)
set.list
(list.all (function (_ module) (dictionary.value module mapping)))
- (list\each (|>> ..module_file _.string _.load_relative/1))
- (list\mix ..then bundle)
+ (list#each (|>> ..module_file _.string _.load_relative/1))
+ (list#mix ..then bundle)
(: _.Expression)
_.code
- (\ encoding.utf8 encoded)
+ (# encoding.utf8 encoded)
tar.content))
module_file (tar.path (..module_file module_id))]
(in {tar.#Normal [module_file now ..mode ..ownership entry_content]})))
@@ -122,7 +122,7 @@
(do [! try.monad]
[order (dependency.load_order $.key archive)
.let [mapping (|> order
- (list\each (function (_ [module [module_id [descriptor document output]]])
+ (list#each (function (_ [module [module_id [descriptor document output]]])
[module module_id]))
(dictionary.of_list text.hash)
(: (Dictionary Module archive.ID)))]
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
index aa79bf5b5..8399ce409 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux
@@ -15,7 +15,7 @@
["[0]" utf8]]]
[collection
["[0]" row]
- ["[0]" list ("[1]\[0]" functor)]]]]]
+ ["[0]" list ("[1]#[0]" functor)]]]]]
[program
[compositor
["[0]" static {"+" [Static]}]]]
@@ -39,12 +39,12 @@
(Try directive)))
(|> output
row.list
- (list\each (|>> product.right product.right))
+ (list#each (|>> product.right product.right))
(monad.mix try.monad
(function (_ content so_far)
(|> content
- (\ utf8.codec decoded)
- (\ try.monad each
+ (# utf8.codec decoded)
+ (# try.monad each
(|>> :expected
(:sharing [directive]
directive
@@ -65,7 +65,7 @@
(do [! try.monad]
[order (dependency.load_order $.key archive)]
(|> order
- (list\each (function (_ [module [module_id [descriptor document output]]])
+ (list#each (function (_ [module [module_id [descriptor document output]]])
[module_id output]))
(monad.mix ! (..write_module sequence) header)
- (\ ! each (|>> scope code (\ utf8.codec encoded)))))))
+ (# ! each (|>> scope code (# utf8.codec encoded)))))))