aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-10-02 04:01:58 -0400
committerEduardo Julian2022-10-02 04:01:58 -0400
commitba150e8a206ffba1c5313c26fa88c6dcba6a08aa (patch)
tree62845871a0617e51ffd9a7cb8dcc66a1eeb04dd1 /stdlib/source/library
parentd82a9b1166902ecca9a9a6eb3e1bb2195c73d9b7 (diff)
New format for extensions [part 3]
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux1
-rw-r--r--stdlib/source/library/lux/control/function/inline.lux2
-rw-r--r--stdlib/source/library/lux/control/function/mutual.lux2
-rw-r--r--stdlib/source/library/lux/documentation.lux2
-rw-r--r--stdlib/source/library/lux/ffi.jvm.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/default/init.lux74
-rw-r--r--stdlib/source/library/lux/meta/compiler/default/platform.lux22
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux1
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/declaration.lux107
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux22
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux2
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/lux.lux60
-rw-r--r--stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/jvm.lux12
-rw-r--r--stdlib/source/library/lux/meta/extension.lux44
-rw-r--r--stdlib/source/library/lux/meta/macro/syntax/declaration.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/category.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/parser.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/reflection.lux2
-rw-r--r--stdlib/source/library/lux/meta/target/jvm/type/signature.lux2
22 files changed, 163 insertions, 206 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index 0d3c3c837..19cc619a2 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -5886,4 +5886,5 @@
[Analysis]
[Synthesis]
[Generation]
+ [Declaration]
)
diff --git a/stdlib/source/library/lux/control/function/inline.lux b/stdlib/source/library/lux/control/function/inline.lux
index a06d2daf7..bbdbdd434 100644
--- a/stdlib/source/library/lux/control/function/inline.lux
+++ b/stdlib/source/library/lux/control/function/inline.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except)
+ [lux (.except Declaration)
[abstract
["[0]" monad (.only do)]]
[control
diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux
index eab14d2ae..f834b94e6 100644
--- a/stdlib/source/library/lux/control/function/mutual.lux
+++ b/stdlib/source/library/lux/control/function/mutual.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Definition let def macro)
+ [lux (.except Definition Declaration let def macro)
[abstract
["[0]" monad (.only do)]]
[control
diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux
index ca27859fd..38ef6aa3f 100644
--- a/stdlib/source/library/lux/documentation.lux
+++ b/stdlib/source/library/lux/documentation.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Definition Module #Definition #module)
+ [lux (.except Definition Module Declaration #Definition #module)
[abstract
[monad (.only do)]
["[0]" enum]]
diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux
index 871f6afec..c585c45c7 100644
--- a/stdlib/source/library/lux/ffi.jvm.lux
+++ b/stdlib/source/library/lux/ffi.jvm.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive Type int char is as type)
+ [lux (.except Primitive Type Declaration int char is as type)
[abstract
["[0]" monad (.only do)]]
[control
diff --git a/stdlib/source/library/lux/meta/compiler/default/init.lux b/stdlib/source/library/lux/meta/compiler/default/init.lux
index b749ffdee..477ebd416 100644
--- a/stdlib/source/library/lux/meta/compiler/default/init.lux
+++ b/stdlib/source/library/lux/meta/compiler/default/init.lux
@@ -30,7 +30,7 @@
["[1][0]" program (.only Program)]
["[1][0]" syntax (.only Aliases)]
["[1][0]" synthesis]
- ["[1][0]" declaration (.only Requirements)]
+ ["[1][0]" declaration (.only Requirements Extender)]
["[1][0]" generation]
["[1][0]" analysis (.only)
[macro (.only Expander)]
@@ -40,7 +40,7 @@
["[0]P" analysis]
["[0]P" synthesis]
["[0]P" declaration]
- ["[0]" extension (.only Extender)
+ ["[0]" extension (.only)
["[0]E" analysis]
["[0]E" synthesis]
[declaration
@@ -58,11 +58,11 @@
(-> Target
descriptor.Module
Configuration
- Extender Expander
+ extension.Extender Expander
[Type Type Type]
///analysis.Bundle
(///generation.Host expression declaration)
- (-> Extender Lux (///generation.Phase anchor expression declaration))
+ (-> extension.Extender Lux (///generation.Phase anchor expression declaration))
(///generation.Bundle anchor expression declaration)
(///declaration.State+ anchor expression declaration)))
(let [synthesis_state [synthesisE.bundle ///synthesis.init]
@@ -87,7 +87,7 @@
(-> ///analysis.Bundle
(Program expression declaration)
[Type Type Type]
- Extender
+ (Extender anchor expression declaration)
(-> (///declaration.State+ anchor expression declaration)
(///declaration.State+ anchor expression declaration))))
(function (_ [declaration_extensions sub_state])
@@ -163,11 +163,10 @@
... TODO: Inline ASAP
(def (get_current_payload _)
- (All (_ declaration)
- (-> (Payload declaration)
- (All (_ anchor expression)
- (///declaration.Operation anchor expression declaration
- (Payload declaration)))))
+ (All (_ anchor expression declaration)
+ (-> (Extender anchor expression declaration)
+ (///declaration.Operation anchor expression declaration
+ (Payload declaration))))
(do ///phase.monad
[buffer (///declaration.lifted_generation
///generation.buffer)
@@ -176,46 +175,43 @@
(in [buffer registry])))
... TODO: Inline ASAP
-(def (process_declaration wrapper archive expander pre_payoad code)
- (All (_ declaration)
- (-> ///phase.Wrapper Archive Expander (Payload declaration) Code
- (All (_ anchor expression)
- (///declaration.Operation anchor expression declaration
- [Requirements (Payload declaration)]))))
+(def (process_declaration wrapper archive extender expander pre_payoad code)
+ (All (_ anchor expression declaration)
+ (-> ///phase.Wrapper Archive (Extender anchor expression declaration) Expander (Payload declaration) Code
+ (///declaration.Operation anchor expression declaration
+ [Requirements (Payload declaration)])))
(do ///phase.monad
[.let [[pre_buffer pre_registry] pre_payoad]
_ (///declaration.lifted_generation
(///generation.set_buffer pre_buffer))
_ (///declaration.lifted_generation
(///generation.set_registry pre_registry))
- requirements (let [execute! (declarationP.phase wrapper expander)]
+ requirements (let [execute! (declarationP.phase wrapper extender expander)]
(execute! archive code))
- post_payload (..get_current_payload pre_payoad)]
+ post_payload (..get_current_payload extender)]
(in [requirements post_payload])))
-(def (iteration' wrapper archive expander reader source pre_payload)
- (All (_ declaration)
- (-> ///phase.Wrapper Archive Expander Reader Source (Payload declaration)
- (All (_ anchor expression)
- (///declaration.Operation anchor expression declaration
- [Source Requirements (Payload declaration)]))))
+(def (iteration' wrapper archive extender expander reader source pre_payload)
+ (All (_ anchor expression declaration)
+ (-> ///phase.Wrapper Archive (Extender anchor expression declaration) Expander Reader Source (Payload declaration)
+ (///declaration.Operation anchor expression declaration
+ [Source Requirements (Payload declaration)])))
(do ///phase.monad
[[source code] (///declaration.lifted_analysis
(..read source reader))
- [requirements post_payload] (process_declaration wrapper archive expander pre_payload code)]
+ [requirements post_payload] (process_declaration wrapper archive extender expander pre_payload code)]
(in [source requirements post_payload])))
-(def (iteration wrapper archive expander module source pre_payload aliases)
- (All (_ declaration)
- (-> ///phase.Wrapper Archive Expander descriptor.Module Source (Payload declaration) Aliases
- (All (_ anchor expression)
- (///declaration.Operation anchor expression declaration
- (Maybe [Source Requirements (Payload declaration)])))))
+(def (iteration wrapper archive extender expander module source pre_payload aliases)
+ (All (_ anchor expression declaration)
+ (-> ///phase.Wrapper Archive (Extender anchor expression declaration) Expander descriptor.Module Source (Payload declaration) Aliases
+ (///declaration.Operation anchor expression declaration
+ (Maybe [Source Requirements (Payload declaration)]))))
(do ///phase.monad
[reader (///declaration.lifted_analysis
(..reader module aliases source))]
(function (_ state)
- (when (///phase.result' state (..iteration' wrapper archive expander reader source pre_payload))
+ (when (///phase.result' state (..iteration' wrapper archive extender expander reader source pre_payload))
{try.#Success [state source&requirements&buffer]}
{try.#Success [state {.#Some source&requirements&buffer}]}
@@ -250,13 +246,13 @@
@module (///phase.lifted (archive.id program_module archive))]
(///generation.save! @self {.#None} (program [@module @self] |program|))))
- (def .public (compiler program global wrapper expander prelude write_declaration program_module program_definition)
- (All (_ anchor expression declaration)
+ (def .public (compiler program global wrapper extender expander prelude write_declaration program_module program_definition)
+ (All (_ <parameters>)
(-> (Program expression declaration) (-> Archive Symbol (///generation.Operation <parameters> expression))
- ///phase.Wrapper Expander descriptor.Module (-> declaration Binary)
+ ///phase.Wrapper (Extender <parameters>) Expander descriptor.Module (-> declaration Binary)
descriptor.Module (Maybe Text)
(Instancer (///declaration.State+ <parameters>) .Module)))
- (let [execute! (declarationP.phase wrapper expander)]
+ (let [execute! (declarationP.phase wrapper extender expander)]
(function (_ key parameters input)
(let [dependencies (default_dependencies prelude input)]
[///.#dependencies dependencies
@@ -267,7 +263,7 @@
(..begin dependencies hash input))
.let [module (the ///.#module input)]]
(loop (again [iteration (<| (///phase.result' state)
- (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))])
+ (..iteration wrapper archive extender expander module source buffer ///syntax.no_aliases))])
(do !
[[state ?source&requirements&temporary_payload] iteration]
(when ?source&requirements&temporary_payload
@@ -321,7 +317,7 @@
_ (|> requirements
(the ///declaration.#referrals)
(monad.each ! (execute! archive)))
- temporary_payload (..get_current_payload temporary_payload)]
- (..iteration wrapper archive expander module source temporary_payload (..module_aliases analysis_module))))))]}]))
+ temporary_payload (..get_current_payload extender)]
+ (..iteration wrapper archive extender expander module source temporary_payload (..module_aliases analysis_module))))))]}]))
)))))]))))
)
diff --git a/stdlib/source/library/lux/meta/compiler/default/platform.lux b/stdlib/source/library/lux/meta/compiler/default/platform.lux
index 9b11c3348..732b86614 100644
--- a/stdlib/source/library/lux/meta/compiler/default/platform.lux
+++ b/stdlib/source/library/lux/meta/compiler/default/platform.lux
@@ -45,12 +45,12 @@
["[0]" syntax]
["[1][0]" synthesis]
["[1][0]" generation (.only Buffer)]
- ["[1][0]" declaration]
+ ["[1][0]" declaration (.only Extender)]
["[1][0]" analysis (.only)
[macro (.only Expander)]
["[0]A" module]]
[phase
- ["[0]" extension (.only Extender)]]]]
+ ["[0]" extension]]]]
[meta
[import (.only Import)]
["[0]" context]
@@ -78,7 +78,7 @@
(Record
[#file_system (file.System Async)
#host (///generation.Host expression declaration)
- #phase (-> Extender Lux (///generation.Phase <type_vars>))
+ #phase (-> extension.Extender Lux (///generation.Phase <type_vars>))
#runtime (<Operation> [Registry Output])
#phase_wrapper ///phase.Wrapper
#write (-> declaration Binary)]))
@@ -197,7 +197,7 @@
analysis_state
state)
(All (_ <type_vars>)
- (-> Extender
+ (-> extension.Extender
[(Dictionary Text ///analysis.Handler)
(Dictionary Text ///synthesis.Handler)
(Dictionary Text (///generation.Handler <type_vars>))
@@ -250,7 +250,7 @@
<Bundle>
(///declaration.Bundle <type_vars>)
(Program expression declaration)
- [Type Type Type] Extender
+ [Type Type Type] extension.Extender
Import (List _io.Context) Configuration
(Async (Try [<State+> Archive ///phase.Wrapper]))))
(do [! ..monad]
@@ -695,12 +695,12 @@
product.left)
archive))
- (def (compiler program global phase_wrapper expander platform program_module program_definition)
+ (def (compiler program global phase_wrapper extender expander platform program_module program_definition)
(All (_ <type_vars>)
(-> (Program expression declaration) (-> Archive Symbol (///generation.Operation <type_vars> expression))
- ///phase.Wrapper Expander <Platform> Text (Maybe Module)
+ ///phase.Wrapper (Extender <type_vars>) Expander <Platform> Text (Maybe Module)
(///.Compiler <State+> .Module Any)))
- (let [instancer (//init.compiler program global phase_wrapper expander syntax.prelude (the #write platform) program_module program_definition)]
+ (let [instancer (//init.compiler program global phase_wrapper extender expander syntax.prelude (the #write platform) program_module program_definition)]
(instancer $.key (list))))
(def (custom_compiler import context platform compilation_sources configuration
@@ -871,13 +871,13 @@
{try.#Success [context (the compiler.#parameters it) /#value]}
(exception.except ..invalid_custom_compiler [/#definition /#type]))))))
- (def .public (compile program global lux_compiler phase_wrapper import file_context expander platform compilation context)
+ (def .public (compile program global lux_compiler phase_wrapper import file_context extender expander platform compilation context)
(All (_ <type_vars>)
(-> (Program expression declaration) (-> Archive Symbol (///generation.Operation <type_vars> expression))
- (-> Any ..Custom) ///phase.Wrapper Import context.Context Expander <Platform> Compilation Lux_Context
+ (-> Any ..Custom) ///phase.Wrapper Import context.Context (Extender <type_vars>) Expander <Platform> Compilation Lux_Context
Lux_Return))
(let [[host_dependencies libraries compilers sources target program_module program_definition configuration] compilation
- import! (|> (..compiler program global phase_wrapper expander platform program_module program_definition)
+ import! (|> (..compiler program global phase_wrapper extender expander platform program_module program_definition)
(serial_compiler import file_context platform sources configuration)
(..parallel context))]
(do [! ..monad]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux b/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux
index 132df96b9..b75132497 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux
@@ -64,6 +64,7 @@
[Phase extension.Phase]
[Handler extension.Handler]
[Bundle extension.Bundle]
+ [Extender extension.Extender]
)
(with_template [<name> <component> <phase>]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/declaration.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/declaration.lux
index 5da3a891b..a88649369 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/declaration.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/declaration.lux
@@ -1,7 +1,6 @@
(.require
[library
[lux (.except)
- ["[0]" meta]
[abstract
["[0]" monad (.only do)]]
[control
@@ -11,12 +10,15 @@
[text
["%" \\format (.only format)]]
[collection
- ["[0]" list (.use "[1]#[0]" mix monoid)]]]]]
+ ["[0]" list (.use "[1]#[0]" mix monoid)]]]
+ ["[0]" meta (.only)
+ [type
+ ["[0]" check]]]]]
["[0]" //
["[1][0]" extension]
["[1][0]" analysis]
["/[1]" //
- ["/" declaration (.only Operation Phase)]
+ ["/" declaration (.only Operation Phase Extender)]
["[1][0]" analysis (.only)
["[0]" evaluation]
["[1]/[0]" macro (.only Expander)]
@@ -77,9 +79,38 @@
{try.#Failure error}
{try.#Failure error})))))
+(exception.def .public (not_an_extension [name expected actual])
+ (Exception [Symbol Type Type])
+ (exception.report
+ (list ["Name" (%.symbol name)]
+ ["Expected" (%.type expected)]
+ ["Actual" (%.type actual)])))
+
+(def (extension_application extender
+ phase archive
+ name parameters)
+ (All (_ anchor expression declaration)
+ (-> (Extender anchor expression declaration)
+ (Phase anchor expression declaration) Archive
+ Symbol (List Code)
+ (Operation anchor expression declaration /.Requirements)))
+ (do //.monad
+ [[exported? type value] (<| /.lifted_analysis
+ //extension.lifted
+ (meta.export name))]
+ (if (check.subsumes? .Declaration type)
+ ((extender value) "" phase archive parameters)
+ (//.except ..not_an_extension [name .Declaration type]))))
+
+(type Outcome
+ (Variant
+ {#More (List Code)}
+ {#Done /.Requirements}))
+
(with_expansions [<lux_def_module> (these [|form_location| {.#Form (list.partial [|text_location| {.#Text "lux def module"}] annotations)}])]
- (def .public (phase wrapper expander)
- (-> //.Wrapper Expander Phase)
+ (def .public (phase wrapper extender expander)
+ (All (_ anchor expression declaration)
+ (-> //.Wrapper (Extender anchor expression declaration) Expander (Phase anchor expression declaration)))
(function (again archive code)
(do [! //.monad]
[state //.state
@@ -98,33 +129,49 @@
[_ {.#Form (list.partial [_ {.#Text name}] inputs)}]
(//extension.apply archive again [name inputs])
- [_ {.#Form (list.partial macro inputs)}]
+ [_ {.#Form (list.partial macro|extension inputs)}]
(do !
- [expansion (/.lifted_analysis
- (do !
- [macroA (<| (///analysis/type.expecting Macro)
- (analysis archive macro))]
- (when macroA
- (///analysis.constant macro_name)
- (do !
- [?macro (//extension.lifted (meta.macro macro_name))
- macro (when ?macro
- {.#Some macro}
- (in macro)
-
- {.#None}
- (//.except ..macro_was_not_found macro_name))]
- (//extension.lifted (///analysis/macro.expansion expander macro_name macro inputs)))
-
- _
- (//.except ..invalid_macro_call code))))]
- (when expansion
- (list.partial <lux_def_module> referrals)
- (|> (again archive <lux_def_module>)
- (at ! each (revised /.#referrals (list#composite referrals))))
+ [expansion|requirements (do !
+ [[def_type def_analysis] (<| /.lifted_analysis
+ ///analysis/type.inferring
+ (analysis archive macro|extension))]
+ (when def_analysis
+ (///analysis.constant def_name)
+ (cond (check.subsumes? Macro def_type)
+ (/.lifted_analysis
+ (do !
+ [?macro (//extension.lifted (meta.macro def_name))
+ macro (when ?macro
+ {.#Some macro}
+ (in macro)
+
+ {.#None}
+ (//.except ..macro_was_not_found def_name))
+ expansion (//extension.lifted (///analysis/macro.expansion expander def_name macro inputs))]
+ (in {#More expansion})))
+
+ (check.subsumes? .Declaration def_type)
+ (do !
+ [requirements (extension_application extender again archive def_name inputs)]
+ (in {#Done requirements}))
+
+ ... else
+ (//.except ..invalid_macro_call [code]))
+
+ _
+ (//.except ..invalid_macro_call [code])))]
+ (when expansion|requirements
+ {.#Left expansion}
+ (when expansion
+ (list.partial <lux_def_module> referrals)
+ (|> (again archive <lux_def_module>)
+ (at ! each (revised /.#referrals (list#composite referrals))))
+
+ _
+ (..requiring again archive expansion))
- _
- (..requiring again archive expansion)))
+ {.#Right requirements}
+ (in requirements)))
_
(//.except ..not_a_declaration code))))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
index 75909c343..79e514a76 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/jvm.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Type Module Primitive Analysis char int type)
+ [lux (.except Type Module Primitive Analysis Declaration char int type)
["[0]" ffi (.only import)]
[abstract
["[0]" monad (.only do)]]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux
index e48295d6a..076b2c39b 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis/lux.lux
@@ -33,6 +33,7 @@
["[0]A" type]]
["[0]" synthesis]
["[0]" generation]
+ ["[0]" declaration]
[///
["[1]" phase]
[meta
@@ -275,35 +276,36 @@
(///bundle.install "clip" (trinary Nat Nat Text Text))
)))
-(def (simple_extension transparent_type opaque_type)
+(def (lux_extension handler_type extension_type)
(-> Type Type Handler)
(..custom
[<code>.any
(function (_ extension_name phase archive [it])
(do [! ////.monad]
- [it (<| (typeA.expecting transparent_type)
+ [it (<| (typeA.expecting handler_type)
(phase archive it))
- _ (typeA.inference opaque_type)]
+ _ (typeA.inference extension_type)]
(in it)))]))
-(def (generation_extension [anchor expression declaration])
- (-> [Type Type Type] Handler)
+(def (host_extension handler_type extension_type [anchor expression declaration])
+ (-> Type Type [Type Type Type] Handler)
(..custom
[<code>.any
(function (_ extension_name phase archive [it])
(do [! ////.monad]
- [it (<| (typeA.expecting (type_literal (generation.Handler anchor expression declaration)))
+ [it (<| (typeA.expecting (type_literal (handler_type anchor expression declaration)))
(phase archive it))
- _ (typeA.inference .Generation)]
+ _ (typeA.inference extension_type)]
(in it)))]))
(def (extension anchor,expression,declaration)
(-> [Type Type Type] Bundle)
(<| (///bundle.prefix "extension")
(|> ///bundle.empty
- (///bundle.install "analysis" (simple_extension analysis.Handler .Analysis))
- (///bundle.install "synthesis" (simple_extension synthesis.Handler .Synthesis))
- (///bundle.install "generation" (generation_extension anchor,expression,declaration))
+ (///bundle.install "analysis" (lux_extension analysis.Handler .Analysis))
+ (///bundle.install "synthesis" (lux_extension synthesis.Handler .Synthesis))
+ (///bundle.install "generation" (host_extension generation.Handler .Generation anchor,expression,declaration))
+ (///bundle.install "declaration" (host_extension declaration.Handler .Declaration anchor,expression,declaration))
)))
(def .public (bundle eval anchor,expression,declaration)
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
index 945dbb3ea..02f45f8e9 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/jvm.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Type Definition Primitive Analysis Synthesis)
+ [lux (.except Type Definition Primitive Analysis Synthesis Declaration)
["[0]" ffi (.only import)]
[abstract
["[0]" monad (.only do)]]
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/lux.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/lux.lux
index d138f22f2..0273d1a26 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/lux.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/declaration/lux.lux
@@ -30,7 +30,7 @@
["^" pattern]]
["[0]" type (.only sharing) (.use "[1]#[0]" equivalence)
["[0]" check]]]]]
- ["[0]" /// (.only Extender)
+ ["[0]" /// (.only)
["[1][0]" bundle]
["[1][0]" analysis]
["/[1]" //
@@ -43,7 +43,7 @@
["[0]" scope]]
["[1][0]" synthesis (.only Synthesis)]
["[1][0]" generation]
- ["[1][0]" declaration (.only Import Requirements Phase Operation Handler Bundle)]
+ ["[1][0]" declaration (.only Import Requirements Phase Operation Handler Extender Bundle)]
["[1][0]" program (.only Program)]
[///
["[0]" phase]
@@ -366,64 +366,16 @@
{.#Named name anonymous}
{.#Named name (again anonymous)}))))
-(with_template [<description> <mame> <def_type> <type> <scope> <definer>]
- [(def (<mame> [anchorT expressionT declarationT] extender)
- (All (_ anchor expression declaration)
- (-> [Type Type Type] Extender
- (Handler anchor expression declaration)))
- (function (handler extension_name phase archive inputsC+)
- (when inputsC+
- (list nameC valueC)
- (do phase.monad
- [target_platform (/////declaration.lifted_analysis
- (///.lifted meta.target))
- [_ _ name] (evaluate! archive Text nameC)
- [_ handlerV] (<definer> archive (as Text name)
- (let [raw_type (type_literal <def_type>)]
- (when target_platform
- (^.or @.jvm
- @.js)
- raw_type
-
- @.python
- (swapped binary.Binary Binary|Python raw_type)
-
- _
- (swapped binary.Binary Binary|DEFAULT raw_type)))
- valueC)
- _ (<| <scope>
- (///.install extender (as Text name))
- (sharing [anchor expression declaration]
- (is (Handler anchor expression declaration)
- handler)
- (is <type>
- (as_expected handlerV))))
- _ (/////declaration.lifted_generation
- (/////generation.log! (format <description> " " (%.text (as Text name)))))]
- (in /////declaration.no_requirements))
-
- _
- (phase.except ///.invalid_syntax [extension_name %.code inputsC+]))))]
-
- ["Declaration"
- def_declaration
- (/////declaration.Handler anchorT expressionT declarationT) (/////declaration.Handler anchor expression declaration)
- (<|)
- ..declaration]
- )
-
-(def (bundle::def host_analysis program anchor,expression,declaration extender)
+(def (bundle::def host_analysis program extender)
(All (_ anchor expression declaration)
(-> /////analysis.Bundle
(Program expression declaration)
- [Type Type Type]
- Extender
+ (Extender anchor expression declaration)
(Bundle anchor expression declaration)))
(<| (///bundle.prefix "def")
(|> ///bundle.empty
(dictionary.has "module" def_module)
(dictionary.has "alias" def_alias)
- (dictionary.has "declaration" (def_declaration anchor,expression,declaration extender))
)))
(def .public (bundle host_analysis program anchor,expression,declaration extender)
@@ -431,9 +383,9 @@
(-> /////analysis.Bundle
(Program expression declaration)
[Type Type Type]
- Extender
+ (Extender anchor expression declaration)
(Bundle anchor expression declaration)))
(<| (///bundle.prefix "lux")
(|> ///bundle.empty
(dictionary.has "def" (lux::def anchor,expression,declaration host_analysis))
- (dictionary.composite (..bundle::def host_analysis program anchor,expression,declaration extender)))))
+ (dictionary.composite (..bundle::def host_analysis program extender)))))
diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/jvm.lux
index 4272682cb..fc45197f5 100644
--- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/jvm.lux
+++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/jvm.lux
@@ -24,7 +24,7 @@
[dependency
["[1]/[0]" artifact]]]]]]]]
["[0]" /
- [runtime (.only Operation Phase Extender)]
+ [runtime (.only Operation Phase)]
["[1][0]" primitive]
["[1][0]" structure]
["[1][0]" reference]
@@ -32,7 +32,7 @@
["[1][0]" when]
["[1][0]" loop]
["//[1]" ///
- ["[1][0]" extension]
+ ["[0]" extension]
[//
["[0]" synthesis (.only Synthesis)]
[///
@@ -49,8 +49,8 @@
(def (extension_application extender lux
phase archive
name parameters)
- (-> Extender Lux
- (-> Extender Lux Phase) Archive
+ (-> extension.Extender Lux
+ (-> extension.Extender Lux Phase) Archive
Symbol (List Synthesis)
(Operation (Bytecode Any)))
(when (|> name
@@ -65,7 +65,7 @@
(///.failure error)))
(def .public (generate extender lux archive synthesis)
- (-> Extender Lux Phase)
+ (-> extension.Extender Lux Phase)
(when synthesis
(^.with_template [<tag> <generator>]
[(<tag> value)
@@ -117,7 +117,7 @@
(/function.apply (generate extender lux) archive application)
{synthesis.#Extension [["" name] parameters]}
- (///extension.apply archive (generate extender lux) [name parameters])
+ (extension.apply archive (generate extender lux) [name parameters])
{synthesis.#Extension [name parameters]}
(extension_application extender lux generate archive name parameters)
diff --git a/stdlib/source/library/lux/meta/extension.lux b/stdlib/source/library/lux/meta/extension.lux
index 18012001c..7fb2bf9c7 100644
--- a/stdlib/source/library/lux/meta/extension.lux
+++ b/stdlib/source/library/lux/meta/extension.lux
@@ -23,49 +23,6 @@
[synthesis
["<s>" \\parser]]]]]]]])
-(type Declaration
- (Record
- [#name Code
- #label Text
- #phase Text
- #archive Text
- #inputs (List Code)]))
-
-(def (declarationP default)
- (-> Code (Parser Declaration))
- (<c>.form (all <>.and
- <c>.any
- <c>.local
- <c>.local
- <c>.local
- (<c>.tuple (<>.some <c>.any)))))
-
-(with_template [<any> <end> <and> <result> <extension> <name>]
- [(def .public <name>
- (syntax (_ [[name extension phase archive inputs] (..declarationP (` <any>))
- body <c>.any])
- (let [g!name (code.local extension)
- g!phase (code.local phase)
- g!archive (code.local archive)]
- (with_symbols [g!handler g!inputs g!error g!_]
- (in (list (` (<extension> (, name)
- (.function ((, g!handler) (, g!name) (, g!phase) (, g!archive) (, g!inputs))
- (.when (<result>
- (monad.do <>.monad
- [(,* inputs)
- (, g!_) <end>]
- (.at <>.monad (,' in) (, body)))
- (, g!inputs))
- {.#Right (, g!_)}
- (, g!_)
-
- {.#Left (, g!error)}
- (phase.failure (, g!error)))
- )))))))))]
-
- [<c>.any <c>.end <c>.and <c>.result "lux def declaration" declaration]
- )
-
(with_template [<any> <end> <and> <result> <extension> <name> <type>]
[(def .public <name>
(syntax (_ [[handler extension phase archive inputs] (<c>.form (all <>.and
@@ -97,4 +54,5 @@
[<c>.any <c>.end <c>.and <c>.result "lux extension analysis" analysis .Analysis]
[<a>.any <a>.end <a>.and <a>.result "lux extension synthesis" synthesis .Synthesis]
[<s>.any <s>.end <s>.and <s>.result "lux extension generation" generation .Generation]
+ [<c>.any <c>.end <c>.and <c>.result "lux extension declaration" declaration .Declaration]
)
diff --git a/stdlib/source/library/lux/meta/macro/syntax/declaration.lux b/stdlib/source/library/lux/meta/macro/syntax/declaration.lux
index 511f10c30..e0ec8870b 100644
--- a/stdlib/source/library/lux/meta/macro/syntax/declaration.lux
+++ b/stdlib/source/library/lux/meta/macro/syntax/declaration.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except)
+ [lux (.except Declaration)
[abstract
[equivalence (.only Equivalence)]]
[control
diff --git a/stdlib/source/library/lux/meta/target/jvm/type.lux b/stdlib/source/library/lux/meta/target/jvm/type.lux
index aabf16518..3e5f0641f 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive Type int char)
+ [lux (.except Primitive Type Declaration int char)
[abstract
[equivalence (.only Equivalence)]
[hash (.only Hash)]]
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/category.lux b/stdlib/source/library/lux/meta/target/jvm/type/category.lux
index 7cae42458..fcd7e7dac 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/category.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/category.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive)
+ [lux (.except Primitive Declaration)
[meta
[macro
["[0]" template]]
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
index a3635d767..593c33e40 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/descriptor.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive int char)
+ [lux (.except Primitive Declaration int char)
[abstract
[equivalence (.only Equivalence)]]
[control
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/parser.lux b/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
index 15a46e8ec..ad41daeac 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/parser.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Type Primitive int char parameter)
+ [lux (.except Type Primitive Declaration int char parameter)
[abstract
[monad (.only do)]]
[control
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux b/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
index 4ea86a811..ae1e6c5cf 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/reflection.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive int char)
+ [lux (.except Primitive Declaration int char)
[abstract
[equivalence (.only Equivalence)]]
[data
diff --git a/stdlib/source/library/lux/meta/target/jvm/type/signature.lux b/stdlib/source/library/lux/meta/target/jvm/type/signature.lux
index 96a912cde..c24f1057d 100644
--- a/stdlib/source/library/lux/meta/target/jvm/type/signature.lux
+++ b/stdlib/source/library/lux/meta/target/jvm/type/signature.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Primitive int char)
+ [lux (.except Primitive Declaration int char)
[abstract
[equivalence (.only Equivalence)]
[hash (.only Hash)]]