aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler
diff options
context:
space:
mode:
authorEduardo Julian2022-01-18 05:06:21 -0400
committerEduardo Julian2022-01-18 05:06:21 -0400
commit4fb3c45f9d0e91cbfe5714c7de2189cddb0abad7 (patch)
tree540f4738865a4c7d2e4b0a309ceee482a4113156 /stdlib/source/library/lux/tool/compiler
parentfc854233d2af07ed44a063a75a6900cc02616c74 (diff)
Full implementation of console for Node.js.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/init.lux6
-rw-r--r--stdlib/source/library/lux/tool/compiler/default/platform.lux3
-rw-r--r--stdlib/source/library/lux/tool/compiler/language/lux/generation.lux29
-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/program.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux197
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/dependency.lux5
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux34
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux170
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux4
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/io/archive.lux3
-rw-r--r--stdlib/source/library/lux/tool/compiler/meta/packager.lux5
12 files changed, 259 insertions, 210 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux
index 59d7ce5e0..e7c3bae01 100644
--- a/stdlib/source/library/lux/tool/compiler/default/init.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/init.lux
@@ -47,7 +47,7 @@
[meta
["[0]" archive {"+" Archive}
["[0]" descriptor {"+" Module}]
- ["[0]" artifact]
+ ["[0]" registry {"+" Registry}]
["[0]" document]]]]
])
@@ -117,7 +117,7 @@
(type: (Payload directive)
[(///generation.Buffer directive)
- artifact.Registry])
+ Registry])
(def: (begin dependencies hash input)
(-> (List Module) Nat ///.Input
@@ -134,7 +134,7 @@
.let [source (///analysis.source (value@ ///.#module input) (value@ ///.#code input))]
_ (///analysis.set_source_code source)]
(in [source [///generation.empty_buffer
- artifact.empty]])))))
+ registry.empty]])))))
(def: (end module)
(-> Module
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux
index d78c5d4f7..fd852c4ce 100644
--- a/stdlib/source/library/lux/tool/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux
@@ -51,7 +51,8 @@
["[0]" module]]]]]
[meta
["[0]" archive {"+" Output Archive}
- ["[0]" artifact {"+" Registry}]
+ [registry {"+" Registry}]
+ ["[0]" artifact]
["[0]" descriptor {"+" Descriptor Module}]
["[0]" document {"+" Document}]]
[io {"+" Context}
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 ac37f48aa..a65131c3a 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux
@@ -32,7 +32,8 @@
[meta
["[0]" archive {"+" Archive}
["[0]" descriptor {"+" Module}]
- ["[0]" artifact]]]]])
+ ["[0]" artifact]
+ ["[0]" registry {"+" Registry}]]]]])
(type: .public Context
[archive.ID artifact.ID])
@@ -75,7 +76,7 @@
#anchor (Maybe anchor)
#host (Host expression directive)
#buffer (Maybe (Buffer directive))
- #registry artifact.Registry
+ #registry Registry
#counter Nat
#context (Maybe artifact.ID)
#log (Sequence Text)
@@ -102,7 +103,7 @@
#anchor {.#None}
#host host
#buffer {.#None}
- #registry artifact.empty
+ #registry registry.empty
#counter 0
#context {.#None}
#log sequence.empty
@@ -164,13 +165,13 @@
(def: .public get_registry
(All (_ anchor expression directive)
- (Operation anchor expression directive artifact.Registry))
+ (Operation anchor expression directive Registry))
(function (_ (^@ stateE [bundle state]))
{try.#Success [stateE (value@ #registry state)]}))
(def: .public (set_registry value)
(All (_ anchor expression directive)
- (-> artifact.Registry (Operation anchor expression directive Any)))
+ (-> Registry (Operation anchor expression directive Any)))
(function (_ [bundle state])
{try.#Success [[bundle (with@ #registry value state)]
[]]}))
@@ -255,12 +256,12 @@
{try.#Success [[bundle (with@ #registry registry' state)]
id]}))))]
- [mandatory? [mandatory?] [Bit] learn artifact.definition]
- [#1 [] [] learn_custom artifact.custom]
- [#0 [] [] learn_analyser artifact.analyser]
- [#0 [] [] learn_synthesizer artifact.synthesizer]
- [#0 [] [] learn_generator artifact.generator]
- [#0 [] [] learn_directive artifact.directive]
+ [mandatory? [mandatory?] [Bit] learn registry.definition]
+ [#1 [] [] learn_custom registry.custom]
+ [#0 [] [] learn_analyser registry.analyser]
+ [#0 [] [] learn_synthesizer registry.synthesizer]
+ [#0 [] [] learn_generator registry.generator]
+ [#0 [] [] learn_directive registry.directive]
)
(exception: .public (unknown_definition [name Symbol
@@ -282,9 +283,9 @@
(do try.monad
[[descriptor document] (archive.find _module archive)]
{try.#Success (value@ descriptor.#registry descriptor)}))]
- (case (artifact.remember _name registry)
+ (case (registry.remember _name registry)
{.#None}
- (exception.except ..unknown_definition [name (artifact.definitions registry)])
+ (exception.except ..unknown_definition [name (registry.definitions registry)])
{.#Some id}
{try.#Success [stateE [module_id id]]})))))
@@ -328,7 +329,7 @@
(-> Archive (Set artifact.Dependency) (Operation anchor expression directive a)
(Operation anchor expression directive [Context a])))
(function (_ (^@ stateE [bundle state]))
- (let [[id registry'] (artifact.resource false dependencies (value@ #registry state))]
+ (let [[id registry'] (registry.resource false dependencies (value@ #registry state))]
(do try.monad
[[[bundle' state'] output] (body [bundle (|> state
(with@ #registry registry')
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 b59f57dc5..e9f88652c 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
@@ -59,7 +59,8 @@
[meta
[io {"+" lux_context}]
[archive {"+" Output Archive}
- ["[0]" artifact {"+" Registry}]]]]]]])
+ ["[0]" artifact]
+ ["[0]" registry {"+" Registry}]]]]]]])
(type: .public Byte_Code
Binary)
@@ -629,10 +630,10 @@
[runtime_payload ..generate_runtime
... _ ..generate_function
]
- (in [(|> artifact.empty
- (artifact.resource .true artifact.no_dependencies)
+ (in [(|> registry.empty
+ (registry.resource .true artifact.no_dependencies)
product.right
- ... (artifact.resource .true artifact.no_dependencies)
+ ... (registry.resource .true artifact.no_dependencies)
... product.right
)
(sequence.sequence runtime_payload
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 6692af0d1..176ab28ed 100644
--- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
+++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux
@@ -19,7 +19,7 @@
[meta
["[0]" archive {"+" Archive}
["[0]" descriptor {"+" Module}]
- ["[0]" artifact]]]]])
+ ["[0]" registry {"+" Registry}]]]]])
(type: .public (Program expression directive)
(-> Context expression directive))
@@ -45,7 +45,7 @@
(in [[module id] (value@ descriptor.#registry descriptor)])))))]
(case (list.one (function (_ [[module module_id] registry])
(do maybe.monad
- [program_id (artifact.remember ..name registry)]
+ [program_id (registry.remember ..name registry)]
(in [module_id program_id])))
registries)
{.#Some program_context}
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 8f636a0b2..3c6a9638b 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux
@@ -2,28 +2,16 @@
[library
[lux "*"
[abstract
- [monad {"+" do}]]
- [control
- [pipe {"+" case>}]
- ["[0]" exception {"+" exception:}]
- ["<>" parser
- ["<[0]>" binary {"+" Parser}]]]
+ [equivalence {"+" Equivalence}]]
[data
["[0]" product]
- ["[0]" text
- ["%" format {"+" format}]]
+ ["[0]" bit]
+ ["[0]" text ("[1]#[0]" equivalence)]
[collection
- ["[0]" list]
- ["[0]" sequence {"+" Sequence} ("[1]#[0]" functor mix)]
- ["[0]" dictionary {"+" Dictionary}]
- ["[0]" set {"+" Set}]]
- [format
- ["[0]" binary {"+" Writer}]]]
+ ["[0]" set {"+" Set}]]]
[math
[number
- ["[0]" nat]]]
- [type
- abstract]]])
+ ["[0]" nat]]]]])
(type: .public ID
Nat)
@@ -38,10 +26,31 @@
{#Directive Text}
{#Custom Text}))
+(implementation: category_equivalence
+ (Equivalence Category)
+
+ (def: (= left right)
+ (case [left right]
+ [{#Anonymous} {#Anonymous}]
+ true
+
+ (^template [<tag>]
+ [[{<tag> left} {<tag> right}]
+ (text#= left right)])
+ ([#Definition]
+ [#Analyser]
+ [#Synthesizer]
+ [#Generator]
+ [#Directive]
+ [#Custom])
+
+ _
+ false)))
+
(type: .public Dependency
[Nat ID])
-(def: dependency_hash
+(def: .public dependency_hash
(product.hash nat.hash nat.hash))
(def: .public no_dependencies
@@ -55,147 +64,11 @@
#mandatory? Bit
#dependencies (Set Dependency)]))
-(abstract: .public Registry
- (Record
- [#artifacts (Sequence Artifact)
- #resolver (Dictionary Text ID)])
-
- (def: .public empty
- Registry
- (:abstraction [#artifacts sequence.empty
- #resolver (dictionary.empty text.hash)]))
-
- (def: .public artifacts
- (-> Registry (Sequence Artifact))
- (|>> :representation (value@ #artifacts)))
-
- (def: next
- (-> Registry ID)
- (|>> ..artifacts sequence.size))
-
- (def: .public (resource mandatory? dependencies registry)
- (-> Bit (Set Dependency) Registry [ID Registry])
- (let [id (..next registry)]
- [id
- (|> registry
- :representation
- (revised@ #artifacts (sequence.suffix [#id id
- #category {#Anonymous}
- #mandatory? mandatory?
- #dependencies dependencies]))
- :abstraction)]))
-
- (template [<tag> <create> <fetch>]
- [(def: .public (<create> name mandatory? dependencies registry)
- (-> Text Bit (Set Dependency) Registry [ID Registry])
- (let [id (..next registry)]
- [id
- (|> registry
- :representation
- (revised@ #artifacts (sequence.suffix [#id id
- #category {<tag> name}
- #mandatory? mandatory?
- #dependencies dependencies]))
- (revised@ #resolver (dictionary.has name id))
- :abstraction)]))
-
- (def: .public (<fetch> registry)
- (-> Registry (List Text))
- (|> registry
- :representation
- (value@ #artifacts)
- sequence.list
- (list.all (|>> (value@ #category)
- (case> {<tag> name} {.#Some name}
- _ {.#None})))))]
-
- [#Definition definition definitions]
- [#Analyser analyser analysers]
- [#Synthesizer synthesizer synthesizers]
- [#Generator generator generators]
- [#Directive directive directives]
- [#Custom custom customs]
- )
-
- (def: .public (remember name registry)
- (-> Text Registry (Maybe ID))
- (|> (:representation registry)
- (value@ #resolver)
- (dictionary.value name)))
-
- (def: .public writer
- (Writer Registry)
- (let [category (: (Writer Category)
- (function (_ value)
- (case value
- (^template [<nat> <tag> <writer>]
- [{<tag> value}
- ((binary.and binary.nat <writer>) [<nat> value])])
- ([0 #Anonymous binary.any]
- [1 #Definition binary.text]
- [2 #Analyser binary.text]
- [3 #Synthesizer binary.text]
- [4 #Generator binary.text]
- [5 #Directive binary.text]
- [6 #Custom binary.text]))))
- mandatory? binary.bit
- dependency (: (Writer Dependency)
- (binary.and binary.nat binary.nat))
- dependencies (: (Writer (Set Dependency))
- (binary.set dependency))
- artifacts (: (Writer (Sequence [Category Bit (Set Dependency)]))
- (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
- (|>> :representation
- (value@ #artifacts)
- (sequence#each (function (_ it)
- [(value@ #category it)
- (value@ #mandatory? it)
- (value@ #dependencies it)]))
- artifacts)))
-
- (exception: .public (invalid_category [tag Nat])
- (exception.report
- ["Tag" (%.nat tag)]))
-
- (def: .public parser
- (Parser Registry)
- (let [category (: (Parser Category)
- (do [! <>.monad]
- [tag <binary>.nat]
- (case tag
- (^template [<nat> <tag> <parser>]
- [<nat>
- (# ! each (|>> {<tag>}) <parser>)])
- ([0 #Anonymous <binary>.any]
- [1 #Definition <binary>.text]
- [2 #Analyser <binary>.text]
- [3 #Synthesizer <binary>.text]
- [4 #Generator <binary>.text]
- [5 #Directive <binary>.text]
- [6 #Custom <binary>.text])
-
- _ (<>.failure (exception.error ..invalid_category [tag])))))
- mandatory? <binary>.bit
- dependency (: (Parser Dependency)
- (<>.and <binary>.nat <binary>.nat))
- dependencies (: (Parser (Set Dependency))
- (<binary>.set ..dependency_hash dependency))]
- (|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies))
- (# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry)
- (product.right
- (case category
- {#Anonymous}
- (..resource mandatory? dependencies registry)
-
- (^template [<tag> <create>]
- [{<tag> name}
- (<create> name mandatory? dependencies registry)])
- ([#Definition ..definition]
- [#Analyser ..analyser]
- [#Synthesizer ..synthesizer]
- [#Generator ..generator]
- [#Directive ..directive]
- [#Custom ..custom])
- )))
- ..empty)))))
- )
+(def: .public equivalence
+ (Equivalence Artifact)
+ ($_ product.equivalence
+ nat.equivalence
+ ..category_equivalence
+ bit.equivalence
+ set.equivalence
+ ))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/dependency.lux
index 7b0065dc4..0962b5b61 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/dependency.lux
@@ -30,7 +30,8 @@
[meta
["[0]" archive {"+" Archive}
["[0]" artifact]
- ["[0]" descriptor]]]]]]])
+ ["[0]" descriptor]
+ ["[0]" registry {"+" Registry}]]]]]]])
(def: (path_references references)
(-> (-> Synthesis (List Constant))
@@ -194,7 +195,7 @@
(list#each (function (_ [module [module_id [descriptor document output]]])
(|> descriptor
(value@ descriptor.#registry)
- artifact.artifacts
+ registry.artifacts
sequence.list
(list#each (function (_ artifact)
[[module_id (value@ artifact.#id artifact)]
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 92327f924..11857d4be 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux
@@ -1,19 +1,19 @@
(.using
- [library
- [lux {"-" Module}
- [control
- ["<>" parser
- ["<b>" binary {"+" Parser}]]]
- [data
- ["[0]" text]
- [collection
- [set {"+" Set}]]
- [format
- ["[0]" binary {"+" Writer}]]]
- [world
- [file {"+" Path}]]]]
- [//
- ["[0]" artifact {"+" Registry}]])
+ [library
+ [lux {"-" Module}
+ [control
+ ["<>" parser
+ ["<b>" binary {"+" Parser}]]]
+ [data
+ ["[0]" text]
+ [collection
+ [set {"+" Set}]]
+ [format
+ ["[0]" binary {"+" Writer}]]]
+ [world
+ [file {"+" Path}]]]]
+ [//
+ ["[0]" registry {"+" Registry}]])
(type: .public Module
Text)
@@ -35,7 +35,7 @@
binary.nat
binary.any
(binary.set binary.text)
- artifact.writer
+ registry.writer
))
(def: .public parser
@@ -46,5 +46,5 @@
<b>.nat
(# <>.monad in {.#Cached})
(<b>.set text.hash <b>.text)
- artifact.parser
+ registry.parser
))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
new file mode 100644
index 000000000..3005c2e0d
--- /dev/null
+++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux
@@ -0,0 +1,170 @@
+(.using
+ [library
+ [lux "*"
+ [abstract
+ [monad {"+" do}]]
+ [control
+ [pipe {"+" case>}]
+ ["[0]" exception {"+" exception:}]
+ ["<>" parser
+ ["<[0]>" binary {"+" Parser}]]]
+ [data
+ ["[0]" product]
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ [set {"+" Set}]
+ ["[0]" list]
+ ["[0]" sequence {"+" Sequence} ("[1]#[0]" functor mix)]
+ ["[0]" dictionary {"+" Dictionary}]]
+ [format
+ ["[0]" binary {"+" Writer}]]]
+ [type
+ abstract]]]
+ ["[0]" // "_"
+ ["[1]" artifact {"+" Dependency Category Artifact ID}]])
+
+(abstract: .public Registry
+ (Record
+ [#artifacts (Sequence Artifact)
+ #resolver (Dictionary Text ID)])
+
+ (def: .public empty
+ Registry
+ (:abstraction [#artifacts sequence.empty
+ #resolver (dictionary.empty text.hash)]))
+
+ (def: .public artifacts
+ (-> Registry (Sequence Artifact))
+ (|>> :representation (value@ #artifacts)))
+
+ (def: next
+ (-> Registry ID)
+ (|>> ..artifacts sequence.size))
+
+ (def: .public (resource mandatory? dependencies registry)
+ (-> Bit (Set Dependency) Registry [ID Registry])
+ (let [id (..next registry)]
+ [id
+ (|> registry
+ :representation
+ (revised@ #artifacts (sequence.suffix [//.#id id
+ //.#category {//.#Anonymous}
+ //.#mandatory? mandatory?
+ //.#dependencies dependencies]))
+ :abstraction)]))
+
+ (template [<tag> <create> <fetch>]
+ [(def: .public (<create> name mandatory? dependencies registry)
+ (-> Text Bit (Set Dependency) Registry [ID Registry])
+ (let [id (..next registry)]
+ [id
+ (|> registry
+ :representation
+ (revised@ #artifacts (sequence.suffix [//.#id id
+ //.#category {<tag> name}
+ //.#mandatory? mandatory?
+ //.#dependencies dependencies]))
+ (revised@ #resolver (dictionary.has name id))
+ :abstraction)]))
+
+ (def: .public (<fetch> registry)
+ (-> Registry (List Text))
+ (|> registry
+ :representation
+ (value@ #artifacts)
+ sequence.list
+ (list.all (|>> (value@ //.#category)
+ (case> {<tag> name} {.#Some name}
+ _ {.#None})))))]
+
+ [//.#Definition definition definitions]
+ [//.#Analyser analyser analysers]
+ [//.#Synthesizer synthesizer synthesizers]
+ [//.#Generator generator generators]
+ [//.#Directive directive directives]
+ [//.#Custom custom customs]
+ )
+
+ (def: .public (remember name registry)
+ (-> Text Registry (Maybe ID))
+ (|> (:representation registry)
+ (value@ #resolver)
+ (dictionary.value name)))
+
+ (def: .public writer
+ (Writer Registry)
+ (let [category (: (Writer Category)
+ (function (_ value)
+ (case value
+ (^template [<nat> <tag> <writer>]
+ [{<tag> value}
+ ((binary.and binary.nat <writer>) [<nat> value])])
+ ([0 //.#Anonymous binary.any]
+ [1 //.#Definition binary.text]
+ [2 //.#Analyser binary.text]
+ [3 //.#Synthesizer binary.text]
+ [4 //.#Generator binary.text]
+ [5 //.#Directive binary.text]
+ [6 //.#Custom binary.text]))))
+ mandatory? binary.bit
+ dependency (: (Writer Dependency)
+ (binary.and binary.nat binary.nat))
+ dependencies (: (Writer (Set Dependency))
+ (binary.set dependency))
+ artifacts (: (Writer (Sequence [Category Bit (Set Dependency)]))
+ (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))]
+ (|>> :representation
+ (value@ #artifacts)
+ (sequence#each (function (_ it)
+ [(value@ //.#category it)
+ (value@ //.#mandatory? it)
+ (value@ //.#dependencies it)]))
+ artifacts)))
+
+ (exception: .public (invalid_category [tag Nat])
+ (exception.report
+ ["Tag" (%.nat tag)]))
+
+ (def: .public parser
+ (Parser Registry)
+ (let [category (: (Parser Category)
+ (do [! <>.monad]
+ [tag <binary>.nat]
+ (case tag
+ (^template [<nat> <tag> <parser>]
+ [<nat>
+ (# ! each (|>> {<tag>}) <parser>)])
+ ([0 //.#Anonymous <binary>.any]
+ [1 //.#Definition <binary>.text]
+ [2 //.#Analyser <binary>.text]
+ [3 //.#Synthesizer <binary>.text]
+ [4 //.#Generator <binary>.text]
+ [5 //.#Directive <binary>.text]
+ [6 //.#Custom <binary>.text])
+
+ _ (<>.failure (exception.error ..invalid_category [tag])))))
+ mandatory? <binary>.bit
+ dependency (: (Parser Dependency)
+ (<>.and <binary>.nat <binary>.nat))
+ dependencies (: (Parser (Set Dependency))
+ (<binary>.set //.dependency_hash dependency))]
+ (|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies))
+ (# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry)
+ (product.right
+ (case category
+ {//.#Anonymous}
+ (..resource mandatory? dependencies registry)
+
+ (^template [<tag> <create>]
+ [{<tag> name}
+ (<create> name mandatory? dependencies registry)])
+ ([//.#Definition ..definition]
+ [//.#Analyser ..analyser]
+ [//.#Synthesizer ..synthesizer]
+ [//.#Generator ..generator]
+ [//.#Directive ..directive]
+ [//.#Custom ..custom])
+ )))
+ ..empty)))))
+ )
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 dd4b64aa4..7b8a98a61 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux
@@ -22,7 +22,7 @@
["[0]" descriptor {"+" Module Descriptor}]
["[0]" document {"+" Document}]]])
-(type: Ancestry
+(type: .public Ancestry
(Set Module))
(def: fresh
@@ -40,7 +40,7 @@
(-> Graph (List Module))
dictionary.keys)
-(type: Dependency
+(type: .public Dependency
(Record
[#module Module
#imports Ancestry]))
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 55c03a050..46d3d65cf 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux
@@ -37,6 +37,7 @@
["/[1]" //
["[0]" archive {"+" Output Archive}
["[0]" artifact {"+" Artifact}]
+ ["[0]" registry]
["[0]" descriptor {"+" Module Descriptor}]
["[0]" document {"+" Document}]]
[cache
@@ -356,7 +357,7 @@
Bundles]))))
(do (try.with async.monad)
[actual (cached_artifacts fs static module_id)
- .let [expected (|> descriptor (value@ descriptor.#registry) artifact.artifacts)]
+ .let [expected (|> descriptor (value@ descriptor.#registry) registry.artifacts)]
[document bundles output] (async#in (loaded_document (value@ static.#artifact_extension static) host_environment module_id expected actual document))]
(in [[descriptor document output] bundles])))
diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
index 5d6fe712e..b8319015f 100644
--- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux
+++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux
@@ -16,7 +16,8 @@
["[0]" dependency]]
["[0]" archive {"+" Archive}
["[0]" descriptor]
- ["[0]" artifact]]
+ ["[0]" artifact]
+ ["[0]" registry]]
[//
[language
[lux
@@ -37,7 +38,7 @@
(list#each (function (_ [module [module_id [descriptor document]]])
(|> descriptor
(value@ descriptor.#registry)
- artifact.artifacts
+ registry.artifacts
sequence.list
(list#each (|>> (value@ artifact.#id)))
[module_id]))))