aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-01-28 06:23:41 -0400
committerEduardo Julian2022-01-28 06:23:41 -0400
commit805309298575cef550749199374e853091f973b3 (patch)
treeaa6ab7e1f642a220b9bc1078018b98648452ea0d /stdlib/source/library
parentfe0d9fc74740f1b51e2f498d4516579d3e48ed02 (diff)
Better detection for "exec" optimization.
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux123
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux2
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux34
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux7
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux7
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux7
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux11
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux66
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux9
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux17
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/program.lux17
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux11
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux23
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux35
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux33
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux5
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager.lux9
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux8
18 files changed, 225 insertions, 199 deletions
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 6ee1bd38b..c4962a187 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -1,37 +1,37 @@
(.using
- [library
- [lux {"-" Mode and}
- [abstract
- [monad {"+" do}]]
- [control
- [pipe {"+" case>}]
- ["[0]" try {"+" Try}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser
- ["<[0]>" binary {"+" Parser}]]]
- [data
- ["[0]" product]
- ["[0]" binary {"+" Binary}]
- ["[0]" text {"+" Char}
- ["%" format {"+" format}]
- [encoding
- ["[0]" utf8]]]
- ["[0]" format "_"
- ["[1]" binary {"+" Writer} ("[1]#[0]" monoid)]]
- [collection
- ["[0]" list ("[1]#[0]" mix)]
- ["[0]" sequence {"+" Sequence} ("[1]#[0]" mix)]]]
- [math
- ["[0]" number
- ["n" nat]
- ["[0]" i64]]]
- [time
- ["[0]" instant {"+" Instant}]
- ["[0]" duration]]
- [world
- ["[0]" file]]
- [type
- abstract]]])
+ [library
+ [lux {"-" Mode and}
+ [abstract
+ [monad {"+" do}]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" try {"+" Try}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser
+ ["<[0]>" binary {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" binary {"+" Binary}]
+ ["[0]" text {"+" Char}
+ ["%" format {"+" format}]
+ [encoding
+ ["[0]" utf8]]]
+ ["[0]" format "_"
+ ["[1]" binary {"+" Writer} ("[1]#[0]" monoid)]]
+ [collection
+ ["[0]" list ("[1]#[0]" mix)]
+ ["[0]" sequence {"+" Sequence} ("[1]#[0]" mix)]]]
+ [math
+ ["[0]" number
+ ["n" nat]
+ ["[0]" i64]]]
+ [time
+ ["[0]" instant {"+" Instant}]
+ ["[0]" duration]]
+ [world
+ ["[0]" file]]
+ [type
+ abstract]]])
(type: Size
Nat)
@@ -425,8 +425,8 @@
(def: link_flag_parser
(Parser Link_Flag)
(do <>.monad
- [linkflag <binary>.bits/8]
- (case (.nat linkflag)
+ [it <binary>.bits/8]
+ (case (.nat it)
(^template [<value> <link_flag>]
[(^ <value>)
(in <link_flag>)])
@@ -434,7 +434,7 @@
_
(<>.lifted
- (exception.except ..invalid_link_flag [(.nat linkflag)]))))))
+ (exception.except ..invalid_link_flag [(.nat it)]))))))
)
(abstract: .public Mode
@@ -803,19 +803,10 @@
#major_device major_device
#minor_device minor_device])))
-(exception: .public (wrong_link_flag [expected Link_Flag
- actual Link_Flag])
- (exception.report
- ["Expected" (%.nat (..link_flag expected))]
- ["Actual" (%.nat (..link_flag actual))]))
-
-(def: (file_parser expected)
- (-> Link_Flag (Parser File))
+(def: (file_parser header)
+ (-> Header (Parser File))
(do <>.monad
- [header ..header_parser
- _ (<>.assertion (exception.error ..wrong_link_flag [expected (value@ #link_flag header)])
- (same? expected (value@ #link_flag header)))
- .let [size (value@ #size header)
+ [.let [size (value@ #size header)
rounded_size (..rounded_content_size size)]
content (<binary>.segment (..from_big size))
content (<>.lifted (..content content))
@@ -835,28 +826,22 @@
#id (value@ #group_id header)]]
content])))
-(def: (file_name_parser expected extractor)
- (-> Link_Flag (-> Header Path) (Parser Path))
- (do <>.monad
- [header ..header_parser
- _ (<>.lifted
- (exception.assertion ..wrong_link_flag [expected (value@ #link_flag header)]
- (n.= (..link_flag expected)
- (..link_flag (value@ #link_flag header)))))]
- (in (extractor header))))
-
(def: entry_parser
(Parser Entry)
- ($_ <>.either
- (# <>.monad each (|>> {..#Normal})
- (<>.either (..file_parser ..normal)
- (..file_parser ..old_normal)))
- (# <>.monad each (|>> {..#Symbolic_Link})
- (..file_name_parser ..symbolic_link (value@ #link_name)))
- (# <>.monad each (|>> {..#Directory})
- (..file_name_parser ..directory (value@ #path)))
- (# <>.monad each (|>> {..#Contiguous})
- (..file_parser ..contiguous))))
+ (do [! <>.monad]
+ [header ..header_parser]
+ (cond (same? ..contiguous (value@ #link_flag header))
+ (# ! each (|>> {..#Contiguous}) (..file_parser header))
+
+ (same? ..symbolic_link (value@ #link_flag header))
+ (in {..#Symbolic_Link (value@ #link_name header)})
+
+ (same? ..directory (value@ #link_flag header))
+ (in {..#Directory (value@ #path header)})
+
+ ... (or (same? ..normal (value@ #link_flag header))
+ ... (same? ..old_normal (value@ #link_flag header)))
+ (# ! each (|>> {..#Normal}) (..file_parser header)))))
... It's safe to implement the parser this way because the range of values for Nat is 2^64
... Whereas the maximum possible value for the checksum of a 512 block is (256 × 512) = 131,072
@@ -882,6 +867,6 @@
(def: .public parser
(Parser Tar)
- (|> (<>.some entry_parser)
+ (|> (<>.some ..entry_parser)
(# <>.monad each sequence.of_list)
(<>.before ..end_of_archive_parser)))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
index 218e9172d..0a7138dca 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux
@@ -23,7 +23,7 @@
["[0]P" analysis]
[//
["[0]" synthesis]
- ["[0]" generation {"+" Context}]
+ ["[0]" generation]
[///
["[0]" phase]
[meta
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
index b561975c1..74580074c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -34,10 +34,8 @@
["[0]" descriptor]
["[0]" module]
["[0]" artifact]
- ["[0]" registry {"+" Registry}]]]]])
-
-(type: .public Context
- [module.ID artifact.ID])
+ ["[0]" registry {"+" Registry}]
+ ["[0]" unit]]]]])
(type: .public (Buffer directive)
(Sequence [artifact.ID (Maybe Text) directive]))
@@ -57,18 +55,18 @@
(type: .public (Host expression directive)
(Interface
- (: (-> Context expression (Try Any))
+ (: (-> unit.ID expression (Try Any))
evaluate)
(: (-> directive (Try Any))
execute)
- (: (-> Context (Maybe Text) expression (Try [Text Any directive]))
+ (: (-> unit.ID (Maybe Text) expression (Try [Text Any directive]))
define)
- (: (-> Context Binary directive)
+ (: (-> unit.ID Binary directive)
ingest)
- (: (-> Context (Maybe Text) directive (Try Any))
+ (: (-> unit.ID (Maybe Text) directive (Try Any))
re_learn)
- (: (-> Context (Maybe Text) directive (Try Any))
+ (: (-> unit.ID (Maybe Text) directive (Try Any))
re_load)))
(type: .public (State anchor expression directive)
@@ -204,7 +202,7 @@
(def: .public (evaluate! label code)
(All (_ anchor expression directive)
- (-> Context expression (Operation anchor expression directive Any)))
+ (-> unit.ID expression (Operation anchor expression directive Any)))
(function (_ (^@ state+ [bundle state]))
(case (# (value@ #host state) evaluate label code)
{try.#Success output}
@@ -226,7 +224,7 @@
(def: .public (define! context custom code)
(All (_ anchor expression directive)
- (-> Context (Maybe Text) expression (Operation anchor expression directive [Text Any directive])))
+ (-> unit.ID (Maybe Text) expression (Operation anchor expression directive [Text Any directive])))
(function (_ (^@ stateE [bundle state]))
(case (# (value@ #host state) define context custom code)
{try.#Success output}
@@ -253,7 +251,7 @@
(template [<mandatory?> <inputs> <input_types> <name> <artifact>]
[(`` (def: .public (<name> name (~~ (template.spliced <inputs>)) dependencies)
(All (_ anchor expression directive)
- (-> Text (~~ (template.spliced <input_types>)) (Set artifact.Dependency) (Operation anchor expression directive artifact.ID)))
+ (-> Text (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID)))
(function (_ (^@ stateE [bundle state]))
(let [[id registry'] (<artifact> name <mandatory?> dependencies (value@ #registry state))]
{try.#Success [[bundle (with@ #registry registry' state)]
@@ -276,7 +274,7 @@
(def: .public (remember archive name)
(All (_ anchor expression directive)
- (-> Archive Symbol (Operation anchor expression directive Context)))
+ (-> Archive Symbol (Operation anchor expression directive unit.ID)))
(function (_ (^@ stateE [bundle state]))
(let [[_module _name] name]
(do try.monad
@@ -305,7 +303,7 @@
(def: .public (context archive)
(All (_ anchor expression directive)
- (-> Archive (Operation anchor expression directive Context)))
+ (-> Archive (Operation anchor expression directive unit.ID)))
(function (_ (^@ stateE [bundle state]))
(case (value@ #context state)
{.#None}
@@ -340,8 +338,8 @@
(def: .public (with_new_context archive dependencies body)
(All (_ anchor expression directive a)
- (-> Archive (Set artifact.Dependency) (Operation anchor expression directive a)
- (Operation anchor expression directive [Context a])))
+ (-> Archive (Set unit.ID) (Operation anchor expression directive a)
+ (Operation anchor expression directive [unit.ID a])))
(function (_ (^@ stateE [bundle state]))
(let [[id registry'] (registry.resource false dependencies (value@ #registry state))
id (n.+ id (value@ #registry_shift state))]
@@ -366,7 +364,7 @@
(def: .public (with_interim_artifacts archive body)
(All (_ anchor expression directive a)
(-> Archive (Operation anchor expression directive a)
- (Operation anchor expression directive [(Set Context) a])))
+ (Operation anchor expression directive [(Set unit.ID) a])))
(do phase.monad
[module (extension.read (value@ #module))]
(function (_ state+)
@@ -377,6 +375,6 @@
(with@ #interim_artifacts (list) state')]
[(list#mix (function (_ artifact_id dependencies)
(set.has [module_id artifact_id] dependencies))
- artifact.no_dependencies
+ unit.none
(value@ #interim_artifacts state'))
output]])))))
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
index 872b224b4..8d23b355c 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux
@@ -51,7 +51,8 @@
["[0]" phase]
[meta
[archive {"+" Archive}
- ["[0]" artifact]]]
+ ["[0]" artifact]
+ ["[0]" unit]]]
[language
[lux
["[0]" synthesis]
@@ -440,7 +441,7 @@
(directive.lifted_generation
(do [! phase.monad]
[.let [artifact [name bytecode]]
- artifact_id (generation.learn_custom name artifact.no_dependencies)
+ artifact_id (generation.learn_custom name unit.none)
_ (generation.execute! artifact)
_ (generation.save! artifact_id {.#Some name} artifact)
_ (generation.log! (format "JVM Class " name))]
@@ -555,7 +556,7 @@
(list)
(list#each ..method_declaration method_declarations)
sequence.empty))
- artifact_id (generation.learn_custom name artifact.no_dependencies)
+ artifact_id (generation.learn_custom name unit.none)
.let [artifact [name bytecode]]
_ (generation.execute! artifact)
_ (generation.save! artifact_id {.#Some name} artifact)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
index 73c67165f..99bcd7e85 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux
@@ -39,7 +39,7 @@
["[0]A" type]
["[0]A" module]]
["[1][0]" synthesis {"+" Synthesis}]
- ["[1][0]" generation {"+" Context}]
+ ["[1][0]" generation]
["[1][0]" directive {"+" Import Requirements Phase Operation Handler Bundle}]
["[1][0]" program {"+" Program}]
[///
@@ -47,7 +47,8 @@
[meta
["[0]" archive {"+" Archive}
["[0]" artifact]
- ["[0]" module]]
+ ["[0]" module]
+ ["[0]" unit]]
["[0]" cache "_"
["[1]/[0]" artifact]]]]]]])
@@ -69,7 +70,7 @@
(phase.except ///.invalid_syntax [extension_name %.code inputs]))))
(def: (context [module_id artifact_id])
- (-> Context Context)
+ (-> unit.ID unit.ID)
... TODO: Find a better way that doesn't rely on clever tricks.
[module_id (n.- (++ artifact_id) 0)])
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
index d8dc8d591..02cf2791f 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux
@@ -71,7 +71,8 @@
["[2][0]" variable {"+" Variable Register}]]
[meta
["[0]" archive {"+" Archive}
- ["[0]" artifact]]
+ ["[0]" artifact]
+ ["[0]" unit]]
["[0]" cache "_"
["[1]/[0]" artifact]]]]]]])
@@ -1068,7 +1069,7 @@
(unwrap_primitive _.dreturn type.double)))))))
(def: (method_dependencies archive method)
- (-> Archive (/.Overriden_Method Synthesis) (Operation (Set artifact.Dependency)))
+ (-> Archive (/.Overriden_Method Synthesis) (Operation (Set unit.ID)))
(let [[_super _name _strict_fp? _annotations
_t_vars _this _arguments _return _exceptions
bodyS] method]
@@ -1076,7 +1077,7 @@
(def: (anonymous_dependencies archive inputsTS overriden_methods)
(-> Archive (List Input) (List [(Environment Synthesis) (/.Overriden_Method Synthesis)])
- (Operation (Set artifact.Dependency)))
+ (Operation (Set unit.ID)))
(do [! //////.monad]
[all_input_dependencies (monad.each ! (|>> product.right (cache/artifact.dependencies archive)) inputsTS)
all_closure_dependencies (|> overriden_methods
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
index 0b14f240e..e232874c4 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux
@@ -40,10 +40,11 @@
[compiler
[language
[lux
- [version {"+" version}]
- [generation {"+" Context}]]]
+ [version {"+" version}]]]
[meta
- [io {"+" lux_context}]]]]]]
+ [io {"+" lux_context}]
+ [archive
+ ["[0]" unit]]]]]]]
["[0]" // "_"
["[1][0]" runtime {"+" Definition}]]
)
@@ -110,7 +111,7 @@
".")
(def: .public (class_name [module_id artifact_id])
- (-> Context Text)
+ (-> unit.ID Text)
(format lux_context
..class_path_separator (%.nat version)
..class_path_separator (%.nat module_id)
@@ -156,7 +157,7 @@
(loader.load class_name loader))))
(def: (define! library loader context custom valueG)
- (-> Library java/lang/ClassLoader Context (Maybe Text) (Bytecode Any) (Try [Text Any Definition]))
+ (-> Library java/lang/ClassLoader unit.ID (Maybe Text) (Bytecode Any) (Try [Text Any Definition]))
(let [class_name (maybe.else (..class_name context)
custom)]
(do try.monad
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
index 357922e6c..7f72697ca 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux
@@ -1,35 +1,37 @@
(.using
- [library
- [lux {"-" Definition}
- [abstract
- [monad {"+" do}]]
- [control
- ["[0]" try]]
- [data
- [collection
- ["[0]" sequence]]
- ["[0]" format "_"
- ["[1]" binary]]]
- [target
- [jvm
- ["_" bytecode {"+" Bytecode}]
- ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)]
- ["[0]" method {"+" Method}]
- ["[0]" version]
- ["[0]" class {"+" Class}]
- [encoding
- ["[0]" name]]
- ["[0]" type
- ["[0]" reflection]]]]
- [tool
- [compiler
- [language
- [lux
- [generation {"+" Context}]
- [program {"+" Program}]]]]]]]
- ["[0]" //
- ["[1][0]" runtime {"+" Definition}]
- ["[1][0]" function/abstract]])
+ [library
+ [lux {"-" Definition}
+ [abstract
+ [monad {"+" do}]]
+ [control
+ ["[0]" try]]
+ [data
+ [collection
+ ["[0]" sequence]]
+ ["[0]" format "_"
+ ["[1]" binary]]]
+ [target
+ [jvm
+ ["_" bytecode {"+" Bytecode}]
+ ["[0]" modifier {"+" Modifier} ("[1]#[0]" monoid)]
+ ["[0]" method {"+" Method}]
+ ["[0]" version]
+ ["[0]" class {"+" Class}]
+ [encoding
+ ["[0]" name]]
+ ["[0]" type
+ ["[0]" reflection]]]]
+ [tool
+ [compiler
+ [language
+ [lux
+ [program {"+" Program}]]]
+ [meta
+ [archive
+ ["[0]" unit]]]]]]]
+ ["[0]" //
+ ["[1][0]" runtime {"+" Definition}]
+ ["[1][0]" function/abstract]])
(def: ^Object
(type.class "java.lang.Object" (list)))
@@ -140,7 +142,7 @@
//runtime.apply))
(def: .public (program artifact_name context program)
- (-> (-> Context Text) (Program (Bytecode Any) Definition))
+ (-> (-> unit.ID Text) (Program (Bytecode Any) Definition))
(let [super_class (|> ..^Object type.reflection reflection.reflection name.internal)
main (method.method ..main::modifier "main" ..main::type
(list)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
index a812a0c31..55cbcdb67 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux
@@ -60,7 +60,8 @@
[io {"+" lux_context}]
[archive {"+" Output Archive}
["[0]" artifact]
- ["[0]" registry {"+" Registry}]]]]]]])
+ ["[0]" registry {"+" Registry}]
+ ["[0]" unit]]]]]]])
(type: .public Byte_Code
Binary)
@@ -89,7 +90,7 @@
(generation.Host (Bytecode Any) Definition))
(def: .public (class_name [module id])
- (-> generation.Context Text)
+ (-> unit.ID Text)
(format lux_context
"." (%.nat version.version)
"." (%.nat module)
@@ -633,9 +634,9 @@
... _ ..generate_function
]
(in [(|> registry.empty
- (registry.resource .true artifact.no_dependencies)
+ (registry.resource .true unit.none)
product.right
- ... (registry.resource .true artifact.no_dependencies)
+ ... (registry.resource .true unit.none)
... product.right
)
(sequence.sequence runtime_payload
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
index c4e0c5fad..6a7235ac0 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux
@@ -240,6 +240,12 @@
{///analysis.#Reference (///reference.local <output>)}]
(list)]])
+(def: .public (synthesize_exec synthesize archive before after)
+ (-> Phase Archive Synthesis Analysis (Operation Synthesis))
+ (do ///.monad
+ [after (synthesize archive after)]
+ (in (/.branch/exec [before after]))))
+
(def: .public (synthesize_let synthesize archive input @variable body)
(-> Phase Archive Synthesis Register Analysis (Operation Synthesis))
(do ///.monad
@@ -287,6 +293,17 @@
(^ (!masking @variable @output))
(..synthesize_masking synthesize^ archive inputS @variable @output)
+ (^ [[(///pattern.unit) body]
+ {.#End}])
+ (case inputA
+ (^or {///analysis.#Simple _}
+ {///analysis.#Structure _}
+ {///analysis.#Reference _})
+ (synthesize^ archive body)
+
+ _
+ (..synthesize_exec synthesize^ archive inputS body))
+
[[{///pattern.#Bind @variable} body]
{.#End}]
(..synthesize_let synthesize^ archive inputS @variable body)
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
index 6ca49597b..d8a683545 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
@@ -13,16 +13,15 @@
["%" format {"+" format}]]
[collection
["[0]" list ("[1]#[0]" functor)]]]]]
- [//
- [generation {"+" Context}]
- [///
- [meta
- ["[0]" archive {"+" Archive}
- ["[0]" descriptor]
- ["[0]" registry {"+" Registry}]]]]])
+ [////
+ [meta
+ ["[0]" archive {"+" Archive}
+ ["[0]" descriptor]
+ ["[0]" registry {"+" Registry}]
+ ["[0]" unit]]]])
(type: .public (Program expression directive)
- (-> Context expression directive))
+ (-> unit.ID expression directive))
(def: .public name
Text
@@ -33,7 +32,7 @@
["Modules" (exception.listing %.text modules)]))
(def: .public (context archive)
- (-> Archive (Try Context))
+ (-> Archive (Try unit.ID))
(do [! try.monad]
[registries (|> archive
archive.archived
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 3ff5019f9..bfe4e8fa3 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -6,7 +6,6 @@
[data
["[0]" product]
["[0]" bit]
- ["[0]" text ("[1]#[0]" equivalence)]
[collection
["[0]" set {"+" Set}]]]
[math
@@ -18,16 +17,6 @@
(type: .public ID
Nat)
-(type: .public Dependency
- [Nat ID])
-
-(def: .public dependency_hash
- (product.hash nat.hash nat.hash))
-
-(def: .public no_dependencies
- (Set Dependency)
- (set.empty dependency_hash))
-
(type: .public Artifact
(Record
[#id ID
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
index c289d9af0..7af5c105b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
@@ -22,12 +22,13 @@
[type
abstract]]]
["[0]" // "_"
- ["[1]" artifact {"+" Dependency Artifact ID}
+ ["[0]" unit]
+ ["[1]" artifact {"+" Artifact ID}
["[2][0]" category {"+" Category}]]])
(abstract: .public Registry
(Record
- [#artifacts (Sequence [Artifact (Set Dependency)])
+ [#artifacts (Sequence [Artifact (Set unit.ID)])
#resolver (Dictionary Text ID)])
(def: .public empty
@@ -36,7 +37,7 @@
#resolver (dictionary.empty text.hash)]))
(def: .public artifacts
- (-> Registry (Sequence [Artifact (Set Dependency)]))
+ (-> Registry (Sequence [Artifact (Set unit.ID)]))
(|>> :representation (value@ #artifacts)))
(def: next
@@ -44,7 +45,7 @@
(|>> ..artifacts sequence.size))
(def: .public (resource mandatory? dependencies registry)
- (-> Bit (Set Dependency) Registry [ID Registry])
+ (-> Bit (Set unit.ID) Registry [ID Registry])
(let [id (..next registry)]
[id
(|> registry
@@ -57,7 +58,7 @@
(template [<tag> <create> <fetch>]
[(def: .public (<create> name mandatory? dependencies registry)
- (-> Text Bit (Set Dependency) Registry [ID Registry])
+ (-> Text Bit (Set unit.ID) Registry [ID Registry])
(let [id (..next registry)]
[id
(|> registry
@@ -110,11 +111,11 @@
[5 //category.#Directive binary.text]
[6 //category.#Custom binary.text]))))
mandatory? binary.bit
- dependency (: (Writer Dependency)
+ dependency (: (Writer unit.ID)
(binary.and binary.nat binary.nat))
- dependencies (: (Writer (Set Dependency))
+ dependencies (: (Writer (Set unit.ID))
(binary.set dependency))
- artifacts (: (Writer (Sequence [Category Bit (Set Dependency)]))
+ artifacts (: (Writer (Sequence [Category Bit (Set unit.ID)]))
(binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
(|>> :representation
(value@ #artifacts)
@@ -147,10 +148,10 @@
_ (<>.failure (exception.error ..invalid_category [tag])))))
mandatory? <binary>.bit
- dependency (: (Parser Dependency)
+ dependency (: (Parser unit.ID)
(<>.and <binary>.nat <binary>.nat))
- dependencies (: (Parser (Set Dependency))
- (<binary>.set //.dependency_hash dependency))]
+ dependencies (: (Parser (Set unit.ID))
+ (<binary>.set unit.hash dependency))]
(|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies))
(# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry)
(product.right
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux
new file mode 100644
index 000000000..fb7cc745b
--- /dev/null
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux
@@ -0,0 +1,35 @@
+(.using
+ [library
+ [lux "*"
+ [abstract
+ [equivalence {"+" Equivalence}]
+ [hash {"+" Hash}]]
+ [data
+ ["[0]" product]
+ [collection
+ ["[0]" set {"+" Set}]]]
+ [math
+ [number
+ ["[0]" nat]]]]]
+ [//
+ ["[0]" module]
+ ["[0]" artifact]])
+
+(type: .public ID
+ (Record
+ [#module module.ID
+ #artifact artifact.ID]))
+
+(def: .public hash
+ (Hash ID)
+ ($_ product.hash
+ nat.hash
+ nat.hash))
+
+(def: .public equivalence
+ (Equivalence ID)
+ (# ..hash &equivalence))
+
+(def: .public none
+ (Set ID)
+ (set.empty ..hash))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
index 9971d71a1..327cae965 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux
@@ -24,13 +24,14 @@
[language
[lux
["[0]" synthesis {"+" Synthesis Path}]
- ["[0]" generation {"+" Context Operation}]
+ ["[0]" generation {"+" Operation}]
["[0]" analysis
["[1]/[0]" complex]]]]
[meta
["[0]" archive {"+" Archive}
["[0]" artifact]
- ["[0]" registry {"+" Registry}]]]]]]])
+ ["[0]" registry {"+" Registry}]
+ ["[0]" unit]]]]]]])
(def: (path_references references)
(-> (-> Synthesis (List Constant))
@@ -155,40 +156,36 @@
(list#each references)
list#conjoint)))
-(def: context_hash
- (Hash Context)
- (product.hash nat.hash nat.hash))
-
(def: .public (dependencies archive value)
(All (_ anchor expression directive)
- (-> Archive Synthesis (Operation anchor expression directive (Set artifact.Dependency))))
+ (-> Archive Synthesis (Operation anchor expression directive (Set unit.ID))))
(let [! phase.monad]
(|> value
..references
(set.of_list symbol.hash)
set.list
(monad.each ! (generation.remember archive))
- (# ! each (set.of_list context_hash)))))
+ (# ! each (set.of_list unit.hash)))))
(def: .public (path_dependencies archive value)
(All (_ anchor expression directive)
- (-> Archive Path (Operation anchor expression directive (Set artifact.Dependency))))
+ (-> Archive Path (Operation anchor expression directive (Set unit.ID))))
(let [! phase.monad]
(|> value
(..path_references ..references)
(set.of_list symbol.hash)
set.list
(monad.each ! (generation.remember archive))
- (# ! each (set.of_list context_hash)))))
+ (# ! each (set.of_list unit.hash)))))
(def: .public all
- (-> (List (Set artifact.Dependency))
- (Set artifact.Dependency))
- (list#mix set.union artifact.no_dependencies))
+ (-> (List (Set unit.ID))
+ (Set unit.ID))
+ (list#mix set.union unit.none))
(def: (immediate_dependencies archive)
- (-> Archive [(List artifact.Dependency)
- (Dictionary artifact.Dependency (Set artifact.Dependency))])
+ (-> Archive [(List unit.ID)
+ (Dictionary unit.ID (Set unit.ID))])
(|> archive
archive.entries
(list#each (function (_ [module [module_id [_module output registry]]])
@@ -208,13 +205,13 @@
mandatory_dependencies)
(dictionary.has artifact_id dependencies all_dependencies)])
[(list)
- (dictionary.empty context_hash)])))
+ (dictionary.empty unit.hash)])))
(def: .public (necessary_dependencies archive)
- (-> Archive (Set artifact.Dependency))
+ (-> Archive (Set unit.ID))
(let [[mandatory immediate] (immediate_dependencies archive)]
(loop [pending mandatory
- minimum artifact.no_dependencies]
+ minimum unit.none]
(case pending
{.#Item head tail}
(if (set.member? minimum head)
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 e89b45756..d0498a516 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -40,7 +40,8 @@
["[0]" module]
["[0]" descriptor {"+" Descriptor}]
["[0]" document {"+" Document}]
- ["[0]" artifact {"+" Artifact Dependency}
+ ["[0]" unit]
+ ["[0]" artifact {"+" Artifact}
["[0]" category {"+" Category}]]]
["[0]" cache "_"
["[1]/[0]" module]]
@@ -225,7 +226,7 @@
(def: (loaded_document extension host module_id expected actual document)
(All (_ expression directive)
- (-> Text (generation.Host expression directive) module.ID (Sequence [Artifact (Set Dependency)]) (Dictionary Text Binary) (Document .Module)
+ (-> Text (generation.Host expression directive) module.ID (Sequence [Artifact (Set unit.ID)]) (Dictionary Text Binary) (Document .Module)
(Try [(Document .Module) Bundles Output])))
(do [! try.monad]
[[definitions bundles] (: (Try [Definitions Bundles Output])
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
index 811739223..ea9e446e9 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
@@ -19,16 +19,13 @@
["[0]" artifact]
["[0]" registry]
["[0]" module]
- ["[0]" descriptor]]
- [//
- [language
- [lux
- [generation {"+" Context}]]]]])
+ ["[0]" descriptor]
+ ["[0]" unit]]])
(type: .public Packager
(-> (Dictionary file.Path Binary)
Archive
- Context
+ unit.ID
(Try (Either Binary
(List [Text Binary])))))
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 d056970b8..706db97ff 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux
@@ -34,7 +34,8 @@
["[0]" archive {"+" Output}
["[0]" module]
["[0]" descriptor {"+" Module}]
- ["[0]" artifact]]
+ ["[0]" artifact]
+ ["[0]" unit]]
["[0]" cache "_"
["[1]/[0]" module]
["[1]/[0]" artifact]]
@@ -43,7 +44,6 @@
[//
[language
["$" lux
- [generation {"+" Context}]
[phase
[generation
[jvm
@@ -132,7 +132,7 @@
"1.0")
(def: (manifest program)
- (-> Context java/util/jar/Manifest)
+ (-> unit.ID java/util/jar/Manifest)
(let [manifest (java/util/jar/Manifest::new)]
(exec (do_to (java/util/jar/Manifest::getMainAttributes manifest)
(java/util/jar/Attributes::put (java/util/jar/Attributes$Name::MAIN_CLASS) (|> program runtime.class_name name.internal name.external))
@@ -155,7 +155,7 @@
(java/util/zip/ZipOutputStream::closeEntry))))))
(def: (write_module static necessary_dependencies [module output] sink)
- (-> Static (Set Context) [module.ID Output] java/util/jar/JarOutputStream
+ (-> Static (Set unit.ID) [module.ID Output] java/util/jar/JarOutputStream
(Try java/util/jar/JarOutputStream))
(let [! try.monad]
(monad.mix try.monad