From 53704218a3705132dbe807a8ef54f938809f84d5 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 1 Oct 2022 16:33:20 -0400 Subject: New format for extensions [part 0] --- stdlib/source/library/lux.lux | 3 + .../library/lux/meta/compiler/default/init.lux | 16 +- .../library/lux/meta/compiler/default/platform.lux | 51 ++-- .../lux/meta/compiler/language/lux/declaration.lux | 4 +- .../compiler/language/lux/phase/declaration.lux | 3 +- .../language/lux/phase/extension/analysis.lux | 8 +- .../language/lux/phase/extension/analysis/lux.lux | 24 +- .../lux/phase/extension/declaration/jvm.lux | 275 ++++++++++----------- .../lux/phase/extension/declaration/lux.lux | 48 ++-- .../compiler/language/lux/phase/generation/jvm.lux | 83 +++++-- .../meta/compiler/language/lux/phase/synthesis.lux | 10 +- .../compiler/language/lux/phase/synthesis/loop.lux | 4 +- .../lux/meta/compiler/language/lux/synthesis.lux | 25 +- stdlib/source/library/lux/meta/extension.lux | 33 ++- stdlib/source/library/lux/meta/type/check.lux | 12 +- stdlib/source/library/lux/meta/type/unit.lux | 1 + stdlib/source/program/compositor.lux | 4 +- stdlib/source/test/lux/meta/extension.lux | 43 ++-- 18 files changed, 379 insertions(+), 268 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 8a829ae10..62a51de98 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -5877,3 +5877,6 @@ _ (failure (..wrong_syntax_error (symbol ..Rec))))))) + +(def .public Generation + (Primitive "#Generation")) diff --git a/stdlib/source/library/lux/meta/compiler/default/init.lux b/stdlib/source/library/lux/meta/compiler/default/init.lux index 7cf349a43..128e66ae2 100644 --- a/stdlib/source/library/lux/meta/compiler/default/init.lux +++ b/stdlib/source/library/lux/meta/compiler/default/init.lux @@ -53,29 +53,31 @@ ["[0]" descriptor] ["[0]" document]]]]]]) -(def .public (state target module configuration expander host_analysis host generate generation_bundle) +(def .public (state target module configuration extender expander anchor,expression,declaration host_analysis host generate generation_bundle) (All (_ anchor expression declaration) (-> Target descriptor.Module Configuration - Expander + Extender Expander + [Type Type Type] ///analysis.Bundle (///generation.Host expression declaration) - (///generation.Phase anchor expression declaration) + (-> Extender Lux (///generation.Phase anchor expression declaration)) (///generation.Bundle anchor expression declaration) (///declaration.State+ anchor expression declaration))) (let [synthesis_state [synthesisE.bundle ///synthesis.init] generation_state [generation_bundle (///generation.state host module)] - eval (///analysis/evaluation.evaluator expander synthesis_state generation_state generate) - analysis_state [(analysisE.bundle eval host_analysis) - (///analysis.state (///analysis.info version.latest target configuration))]] + lux (///analysis.state (///analysis.info version.latest target configuration)) + eval (///analysis/evaluation.evaluator expander synthesis_state generation_state (generate extender lux)) + analysis_state [(analysisE.bundle eval anchor,expression,declaration host_analysis) + lux]] [extension.empty [///declaration.#analysis [///declaration.#state analysis_state ///declaration.#phase (analysisP.phase expander)] ///declaration.#synthesis [///declaration.#state synthesis_state ///declaration.#phase synthesisP.phase] ///declaration.#generation [///declaration.#state generation_state - ///declaration.#phase generate]]])) + ///declaration.#phase (generate extender)]]])) (def .public (with_default_declarations expander host_analysis program anchorT,expressionT,declarationT extender) (All (_ anchor expression declaration) diff --git a/stdlib/source/library/lux/meta/compiler/default/platform.lux b/stdlib/source/library/lux/meta/compiler/default/platform.lux index 427625283..af7fef44e 100644 --- a/stdlib/source/library/lux/meta/compiler/default/platform.lux +++ b/stdlib/source/library/lux/meta/compiler/default/platform.lux @@ -78,9 +78,9 @@ (Record [#file_system (file.System Async) #host (///generation.Host expression declaration) - #phase (///generation.Phase ) + #phase (-> Extender Lux (///generation.Phase )) #runtime ( [Registry Output]) - #phase_wrapper (-> Archive ( ///phase.Wrapper)) + #phase_wrapper ///phase.Wrapper #write (-> declaration Binary)])) ... TODO: Get rid of this @@ -223,18 +223,9 @@ (///phase.result' state) (at try.monad each product.left))) - (def (phase_wrapper archive platform state) + (def (complete_extensions host_declaration_bundle [analysers synthesizers generators declarations]) (All (_ ) - (-> Archive (Try [ ///phase.Wrapper]))) - (|> archive - ((the #phase_wrapper platform)) - ///declaration.lifted_generation - (///phase.result' state))) - - (def (complete_extensions host_declaration_bundle phase_wrapper [analysers synthesizers generators declarations]) - (All (_ ) - (-> (-> ///phase.Wrapper (///declaration.Bundle )) - ///phase.Wrapper + (-> (///declaration.Bundle ) [(Dictionary Text ///analysis.Handler) (Dictionary Text ///synthesis.Handler) (Dictionary Text (///generation.Handler )) @@ -246,9 +237,9 @@ [analysers synthesizers generators - (dictionary.composite declarations (host_declaration_bundle phase_wrapper))]) + (dictionary.composite declarations host_declaration_bundle)]) - (def .public (initialize context module expander host_analysis platform generation_bundle host_declaration_bundle program anchorT,expressionT,declarationT extender + (def .public (initialize context module expander host_analysis platform generation_bundle host_declaration_bundle program anchor,expression,declaration extender import compilation_sources compilation_configuration) (All (_ ) (-> context.Context @@ -257,16 +248,19 @@ ///analysis.Bundle - (-> ///phase.Wrapper (///declaration.Bundle )) + (///declaration.Bundle ) (Program expression declaration) - [Type Type Type] (-> ///phase.Wrapper Extender) + [Type Type Type] Extender Import (List _io.Context) Configuration (Async (Try [ Archive ///phase.Wrapper])))) (do [! ..monad] - [.let [state (//init.state (the context.#host context) + [.let [phase_wrapper (the #phase_wrapper platform) + state (//init.state (the context.#host context) module compilation_configuration + extender expander + anchor,expression,declaration host_analysis (the #host platform) (the #phase platform) @@ -277,20 +271,17 @@ .let [with_missing_extensions (is (All (_ ) (-> (Program expression declaration) - (Async (Try [///phase.Wrapper ])))) + (Async (Try )))) (function (_ platform program state) - (async#in - (do try.monad - [[state phase_wrapper] (..phase_wrapper archive platform state)] - (|> state - (initialize_state (extender phase_wrapper) - (as_expected (..complete_extensions host_declaration_bundle phase_wrapper (as_expected bundles))) - analysis_state) - (try#each (|>> (//init.with_default_declarations expander host_analysis program anchorT,expressionT,declarationT (extender phase_wrapper)) - [phase_wrapper])))))))]] + (|> state + (initialize_state extender + (as_expected (..complete_extensions host_declaration_bundle (as_expected bundles))) + analysis_state) + (try#each (//init.with_default_declarations expander host_analysis program anchor,expression,declaration extender)) + async#in)))]] (if (archive.archived? archive descriptor.runtime) (do ! - [[phase_wrapper state] (with_missing_extensions platform program state)] + [state (with_missing_extensions platform program state)] (in [state archive phase_wrapper])) (do ! [[state [archive payload]] (|> (..process_runtime archive platform) @@ -298,7 +289,7 @@ async#in) _ (..cache_module context platform 0 $.key $.format payload) - [phase_wrapper state] (with_missing_extensions platform program state)] + state (with_missing_extensions platform program state)] (in [state archive phase_wrapper]))))) (def compilation_log_separator 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 8eff3ed65..822c33d1d 100644 --- a/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux +++ b/stdlib/source/library/lux/meta/compiler/language/lux/declaration.lux @@ -33,7 +33,7 @@ #synthesis (Component synthesis.State+ synthesis.Phase) #generation (Component (generation.State+ anchor expression declaration) - (generation.Phase anchor expression declaration))])) + (-> Lux (generation.Phase anchor expression declaration)))])) (type .public Import (Record @@ -75,7 +75,7 @@ [analysis ..#analysis analysis.Phase] [synthesis ..#synthesis synthesis.Phase] - [generation ..#generation (generation.Phase anchor expression declaration)] + [generation ..#generation (-> Lux (generation.Phase anchor expression declaration))] ) (with_template [ ] 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 832944c9c..4cd838c6f 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 @@ -89,7 +89,8 @@ (evaluation.evaluator expander (the [//extension.#state /.#synthesis /.#state] state) (the [//extension.#state /.#generation /.#state] state) - (the [//extension.#state /.#generation /.#phase] state))) + ((the [//extension.#state /.#generation /.#phase] state) + (the [//extension.#state /.#analysis /.#state //extension.#state] state)))) extension_eval (as Eval (wrapper (as_expected compiler_eval)))] _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (when code diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis.lux index 2a887e12d..d74041df9 100644 --- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis.lux +++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/extension/analysis.lux @@ -10,7 +10,7 @@ ["[0]" / ["[1][0]" lux]]) -(def .public (bundle eval host_specific) - (-> Eval Bundle Bundle) - (dictionary.composite host_specific - (/lux.bundle eval))) +(def .public (bundle eval anchor,expression,declaration host_specific) + (-> Eval [Type Type Type] Bundle Bundle) + (|> (/lux.bundle eval anchor,expression,declaration) + (dictionary.composite host_specific))) 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 da97565c2..f2e202be9 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 @@ -31,6 +31,7 @@ ["[1][0]" analysis (.only Analysis Operation Phase Handler Bundle) [evaluation (.only Eval)] ["[0]A" type]] + ["[0]" generation] [/// ["[1]" phase] [meta @@ -273,8 +274,26 @@ (///bundle.install "clip" (trinary Nat Nat Text Text)) ))) -(def .public (bundle eval) - (-> Eval Bundle) +(def (generation_extension [anchor expression declaration]) + (-> [Type Type Type] Handler) + (..custom + [.any + (function (_ extension_name phase archive [it]) + (do [! ////.monad] + [it (<| (typeA.expecting (type_literal (generation.Handler anchor expression declaration))) + (phase archive it)) + _ (typeA.inference .Generation)] + (in it)))])) + +(def (extension anchor,expression,declaration) + (-> [Type Type Type] Bundle) + (<| (///bundle.prefix "extension") + (|> ///bundle.empty + (///bundle.install "generation" (generation_extension anchor,expression,declaration)) + ))) + +(def .public (bundle eval anchor,expression,declaration) + (-> Eval [Type Type Type] Bundle) (<| (///bundle.prefix "lux") (|> ///bundle.empty (dictionary.composite (bundle::lux eval)) @@ -282,4 +301,5 @@ (dictionary.composite bundle::f64) (dictionary.composite bundle::text) (dictionary.composite bundle::io) + (dictionary.composite (extension 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 942f931d8..1d4f70473 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 @@ -455,18 +455,16 @@ (is [Register (Bytecode Any)] [offset (_#in [])])) product.right)) -(def (constructor_method_generation archive super_class method) - (-> Archive (Type Class) (jvm.Constructor Synthesis) (Operation (Resource Method))) +(def (constructor_method_generation generate archive super_class method) + (-> (generation.Phase Anchor (Bytecode Any) Definition) Archive (Type Class) (jvm.Constructor Synthesis) (Operation (Resource Method))) (<| (let [[privacy strict_floating_point? annotations method_tvars exceptions self arguments constructor_argumentsS bodyS] method bodyS (when (list.size arguments) 0 (host.without_fake_parameter bodyS) _ bodyS)]) - (do [! phase.monad] - [generate declaration.generation]) declaration.lifted_generation - (do ! + (do [! phase.monad] [constructor_argumentsG (monad.each ! (|>> product.right (generate archive)) constructor_argumentsS) bodyG (generate archive bodyS) @@ -481,17 +479,17 @@ (if strict_floating_point? method.strict modifier.empty)) - ..constructor_name - true (type.method [method_tvars argumentsT type.void exceptions]) - (list) - {.#Some (all _.composite - (_.aload 0) - (..composite constructor_argumentsG) - (_.invokespecial super_class ..constructor_name super_constructorT) - (method_arguments 1 argumentsT) - bodyG - _.return - )}))))) + ..constructor_name + true (type.method [method_tvars argumentsT type.void exceptions]) + (list) + {.#Some (all _.composite + (_.aload 0) + (..composite constructor_argumentsG) + (_.invokespecial super_class ..constructor_name super_constructorT) + (method_arguments 1 argumentsT) + bodyG + _.return + )}))))) (def (method_return returnT) (-> (Type Return) (Bytecode Any)) @@ -531,87 +529,81 @@ ... (at type.equivalence = type.double returnT) (unwrap_primitive _.dreturn type.double))))))) -(def (overriden_method_generation archive method) - (-> Archive (jvm.Overriden_Method Synthesis) (Operation (Resource Method))) - (do [! phase.monad] - [.let [[super method_name strict_floating_point? annotations - method_tvars self arguments returnJ exceptionsJ - bodyS] method - bodyS (when (list.size arguments) - 0 (host.without_fake_parameter bodyS) - _ bodyS)] - generate declaration.generation] - (declaration.lifted_generation - (do ! - [bodyG (generate archive bodyS) - .let [argumentsT (list#each product.right arguments)]] - (in (method.method (all modifier#composite - method.public - (if strict_floating_point? - method.strict - modifier.empty)) - method_name - true (type.method [method_tvars argumentsT returnJ exceptionsJ]) - (list) - {.#Some (all _.composite - (method_arguments 1 argumentsT) - bodyG - (method_return returnJ))})))))) - -(def (virtual_method_generation archive method) - (-> Archive (jvm.Virtual_Method Synthesis) (Operation (Resource Method))) - (do [! phase.monad] - [.let [[method_name privacy final? strict_floating_point? annotations method_tvars - self arguments returnJ exceptionsJ - bodyS] method - bodyS (when (list.size arguments) - 0 (host.without_fake_parameter bodyS) - _ bodyS)] - generate declaration.generation] - (declaration.lifted_generation - (do ! - [bodyG (generate archive bodyS) - .let [argumentsT (list#each product.right arguments)]] - (in (method.method (all modifier#composite - (..method_privacy privacy) - (if strict_floating_point? - method.strict - modifier.empty) - (if final? - method.final - modifier.empty)) - method_name - true (type.method [method_tvars argumentsT returnJ exceptionsJ]) - (list) - {.#Some (all _.composite - (method_arguments 1 argumentsT) - bodyG - (method_return returnJ))})))))) - -(def (static_method_generation archive method) - (-> Archive (jvm.Static_Method Synthesis) (Operation (Resource Method))) - (do [! phase.monad] - [.let [[method_name privacy strict_floating_point? annotations method_tvars - arguments returnJ exceptionsJ - bodyS] method] - generate declaration.generation] - (declaration.lifted_generation - (do ! - [bodyG (generate archive bodyS) - .let [argumentsT (list#each product.right arguments)]] - (in (method.method (all modifier#composite - (..method_privacy privacy) - method.static - (if strict_floating_point? - method.strict - modifier.empty)) - method_name - true (type.method [method_tvars argumentsT returnJ exceptionsJ]) - (list) - {.#Some (all _.composite - (method_arguments 0 argumentsT) - bodyG - (method_return returnJ))})))))) +(def (overriden_method_generation generate archive method) + (-> (generation.Phase Anchor (Bytecode Any) Definition) Archive (jvm.Overriden_Method Synthesis) (Operation (Resource Method))) + (<| (let [[super method_name strict_floating_point? annotations + method_tvars self arguments returnJ exceptionsJ + bodyS] method + bodyS (when (list.size arguments) + 0 (host.without_fake_parameter bodyS) + _ bodyS)]) + declaration.lifted_generation + (do [! phase.monad] + [bodyG (generate archive bodyS) + .let [argumentsT (list#each product.right arguments)]] + (in (method.method (all modifier#composite + method.public + (if strict_floating_point? + method.strict + modifier.empty)) + method_name + true (type.method [method_tvars argumentsT returnJ exceptionsJ]) + (list) + {.#Some (all _.composite + (method_arguments 1 argumentsT) + bodyG + (method_return returnJ))}))))) + +(def (virtual_method_generation generate archive method) + (-> (generation.Phase Anchor (Bytecode Any) Definition) Archive (jvm.Virtual_Method Synthesis) (Operation (Resource Method))) + (<| (let [[method_name privacy final? strict_floating_point? annotations method_tvars + self arguments returnJ exceptionsJ + bodyS] method + bodyS (when (list.size arguments) + 0 (host.without_fake_parameter bodyS) + _ bodyS)]) + declaration.lifted_generation + (do [! phase.monad] + [bodyG (generate archive bodyS) + .let [argumentsT (list#each product.right arguments)]] + (in (method.method (all modifier#composite + (..method_privacy privacy) + (if strict_floating_point? + method.strict + modifier.empty) + (if final? + method.final + modifier.empty)) + method_name + true (type.method [method_tvars argumentsT returnJ exceptionsJ]) + (list) + {.#Some (all _.composite + (method_arguments 1 argumentsT) + bodyG + (method_return returnJ))}))))) + +(def (static_method_generation generate archive method) + (-> (generation.Phase Anchor (Bytecode Any) Definition) Archive (jvm.Static_Method Synthesis) (Operation (Resource Method))) + (<| (let [[method_name privacy strict_floating_point? annotations method_tvars + arguments returnJ exceptionsJ + bodyS] method]) + declaration.lifted_generation + (do [! phase.monad] + [bodyG (generate archive bodyS) + .let [argumentsT (list#each product.right arguments)]] + (in (method.method (all modifier#composite + (..method_privacy privacy) + method.static + (if strict_floating_point? + method.strict + modifier.empty)) + method_name + true (type.method [method_tvars argumentsT returnJ exceptionsJ]) + (list) + {.#Some (all _.composite + (method_arguments 0 argumentsT) + bodyG + (method_return returnJ))}))))) (def (abstract_method_generation method) (-> (jvm.Abstract_Method Synthesis) (Resource Method)) @@ -620,25 +612,25 @@ (method.method (all modifier#composite (..method_privacy privacy) method.abstract) - name - true (type.method [variables (list#each product.right arguments) return exceptions]) - (list) - {.#None}))) + name + true (type.method [variables (list#each product.right arguments) return exceptions]) + (list) + {.#None}))) -(def (method_generation archive super_class method) - (-> Archive (Type Class) (Method_Definition Synthesis) (Operation (Resource Method))) +(def (method_generation generate archive super_class method) + (-> (generation.Phase Anchor (Bytecode Any) Definition) Archive (Type Class) (Method_Definition Synthesis) (Operation (Resource Method))) (when method {#Constructor method} - (..constructor_method_generation archive super_class method) + (..constructor_method_generation generate archive super_class method) {#Overriden_Method method} - (..overriden_method_generation archive method) + (..overriden_method_generation generate archive method) {#Virtual_Method method} - (..virtual_method_generation archive method) + (..virtual_method_generation generate archive method) {#Static_Method method} - (..static_method_generation archive method) + (..static_method_generation generate archive method) {#Abstract_Method method} (at phase.monad in (..abstract_method_generation method)))) @@ -680,7 +672,7 @@ list (.result ..method_synthesis) phase.lifted) - methodG (method_generation archive super methodS')] + methodG (method_generation generate archive super methodS')] (in [dependencies methodG])))) (def class_name @@ -763,18 +755,18 @@ (if strict_floating_point? method.strict modifier.empty)) - ..constructor_name - true (type.method [variables (list#each product.right arguments) type.void exceptions]) - (list) - {.#Some (all _.composite - (_.aload 0) - (|> constructor_arguments - (list#each (|>> product.left ..mock_value)) - (monad.all _.monad)) - (|> (type.method [(list) (list#each product.left constructor_arguments) type.void (list)]) - (_.invokespecial super ..constructor_name)) - _.return - )}) + ..constructor_name + true (type.method [variables (list#each product.right arguments) type.void exceptions]) + (list) + {.#Some (all _.composite + (_.aload 0) + (|> constructor_arguments + (list#each (|>> product.left ..mock_value)) + (monad.all _.monad)) + (|> (type.method [(list) (list#each product.left constructor_arguments) type.void (list)]) + (_.invokespecial super ..constructor_name)) + _.return + )}) {#Overriden_Method [super name strict_floating_point? annotations variables self arguments return exceptions @@ -784,10 +776,10 @@ (if strict_floating_point? method.strict modifier.empty)) - name - true (type.method [variables (list#each product.right arguments) return exceptions]) - (list) - {.#Some (..mock_return return)}) + name + true (type.method [variables (list#each product.right arguments) return exceptions]) + (list) + {.#Some (..mock_return return)}) {#Virtual_Method [name privacy final? strict_floating_point? annotations variables self arguments return exceptions @@ -800,10 +792,10 @@ (if final? method.final modifier.empty)) - name - true (type.method [variables (list#each product.right arguments) return exceptions]) - (list) - {.#Some (..mock_return return)}) + name + true (type.method [variables (list#each product.right arguments) return exceptions]) + (list) + {.#Some (..mock_return return)}) {#Static_Method [name privacy strict_floating_point? annotations variables arguments return exceptions @@ -814,20 +806,20 @@ (if strict_floating_point? method.strict modifier.empty)) - name - true (type.method [variables (list#each product.right arguments) return exceptions]) - (list) - {.#Some (..mock_return return)}) + name + true (type.method [variables (list#each product.right arguments) return exceptions]) + (list) + {.#Some (..mock_return return)}) {#Abstract_Method [name privacy annotations variables arguments return exceptions]} (method.method (all modifier#composite method.abstract (..method_privacy privacy)) - name - true (type.method [variables (list#each product.right arguments) return exceptions]) - (list) - {.#None}) + name + true (type.method [variables (list#each product.right arguments) return exceptions]) + (list) + {.#None}) )) (def (mock declaration super interfaces inheritance fields methods) @@ -907,7 +899,8 @@ methods (monad.each ! (..method_definition archive super interfaces [mapping selfT] [(the [declaration.#analysis declaration.#phase] state) (the [declaration.#synthesis declaration.#phase] state) - (the [declaration.#generation declaration.#phase] state)]) + ((the [declaration.#generation declaration.#phase] state) + (the [declaration.#analysis declaration.#state extension.#state] state))]) methods) .let [all_dependencies (cache.all (list#each product.left methods))] bytecode (<| (at ! each (\\format.result class.format)) @@ -932,10 +925,10 @@ (method.method (all modifier#composite method.public method.abstract) - /#name - true type - (list) - {.#None}))) + /#name + true type + (list) + {.#None}))) (def jvm::class::interface (Handler Anchor (Bytecode Any) Definition) 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 2ea6deb7d..b88520b8d 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 @@ -102,7 +102,8 @@ [state (///.lifted phase.state) .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) - generate (the [/////declaration.#generation /////declaration.#phase] state)] + generate ((the [/////declaration.#generation /////declaration.#phase] state) + (the [/////declaration.#analysis /////declaration.#state ///.#state] state))] [_ codeA] (<| /////declaration.lifted_analysis scope.with typeA.fresh @@ -148,7 +149,8 @@ [state (///.lifted phase.state) .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) - generate (the [/////declaration.#generation /////declaration.#phase] state)] + generate ((the [/////declaration.#generation /////declaration.#phase] state) + (the [/////declaration.#analysis /////declaration.#state ///.#state] state))] [_ code//type codeA] (/////declaration.lifted_analysis (scope.with (typeA.fresh @@ -201,7 +203,8 @@ [state (///.lifted phase.state) .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) - generate (the [/////declaration.#generation /////declaration.#phase] state)] + generate ((the [/////declaration.#generation /////declaration.#phase] state) + (the [/////declaration.#analysis /////declaration.#state ///.#state] state))] [_ codeA] (<| /////declaration.lifted_analysis scope.with typeA.fresh @@ -218,22 +221,23 @@ ) ... TODO: Get rid of this function ASAP. -(def (refresh expander host_analysis) +(def (refresh expander anchor,expression,declaration host_analysis) (All (_ anchor expression declaration) - (-> Expander /////analysis.Bundle (Operation anchor expression declaration Any))) + (-> Expander [Type Type Type] /////analysis.Bundle (Operation anchor expression declaration Any))) (do phase.monad [[bundle state] phase.state .let [eval (/////analysis/evaluation.evaluator expander (the [/////declaration.#synthesis /////declaration.#state] state) (the [/////declaration.#generation /////declaration.#state] state) - (the [/////declaration.#generation /////declaration.#phase] state)) + ((the [/////declaration.#generation /////declaration.#phase] state) + (the [/////declaration.#analysis /////declaration.#state ///.#state] state))) previous_analysis_extensions (the [/////declaration.#analysis /////declaration.#state ///.#bundle] state)]] (phase.with [bundle (revised [/////declaration.#analysis /////declaration.#state] (is (-> /////analysis.State+ /////analysis.State+) (|>> product.right [(|> previous_analysis_extensions - (dictionary.composite (///analysis.bundle eval host_analysis)))])) + (dictionary.composite (///analysis.bundle eval anchor,expression,declaration host_analysis)))])) state)]))) (def (announce_definition! short type) @@ -242,8 +246,8 @@ (/////declaration.lifted_generation (/////generation.log! (format short " : " (%.type type))))) -(def (lux::def expander host_analysis) - (-> Expander /////analysis.Bundle Handler) +(def (lux::def expander anchor,expression,declaration host_analysis) + (-> Expander [Type Type Type] /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (when inputsC+ (list [_ {.#Symbol ["" short_name]}] valueC exported?C) @@ -255,7 +259,7 @@ [_ _ exported?] (evaluate! archive Bit exported?C) _ (/////declaration.lifted_analysis (moduleA.define short_name {.#Definition [(as Bit exported?) type value]})) - _ (..refresh expander host_analysis) + _ (..refresh expander anchor,expression,declaration host_analysis) _ (..announce_definition! short_name type)] (in /////declaration.no_requirements)) @@ -268,7 +272,7 @@ <>.some .tuple)) -(def defmodule +(def def_module Handler (..custom [..imports @@ -304,7 +308,7 @@ {.#Definition _} (moduleA.define alias {.#Alias original})))) -(def defalias +(def def_alias Handler (..custom [(all <>.and .local .symbol) @@ -421,7 +425,7 @@ ..declaration] ) -(def (bundle::def expander host_analysis program anchorT,expressionT,declarationT extender) +(def (bundle::def expander host_analysis program anchor,expression,declaration extender) (All (_ anchor expression declaration) (-> Expander /////analysis.Bundle @@ -431,15 +435,15 @@ (Bundle anchor expression declaration))) (<| (///bundle.prefix "def") (|> ///bundle.empty - (dictionary.has "module" defmodule) - (dictionary.has "alias" defalias) - (dictionary.has "analysis" (def_analysis anchorT,expressionT,declarationT extender)) - (dictionary.has "synthesis" (def_synthesis anchorT,expressionT,declarationT extender)) - (dictionary.has "generation" (def_generation anchorT,expressionT,declarationT extender)) - (dictionary.has "declaration" (def_declaration anchorT,expressionT,declarationT extender)) + (dictionary.has "module" def_module) + (dictionary.has "alias" def_alias) + (dictionary.has "analysis" (def_analysis anchor,expression,declaration extender)) + (dictionary.has "synthesis" (def_synthesis anchor,expression,declaration extender)) + (dictionary.has "generation" (def_generation anchor,expression,declaration extender)) + (dictionary.has "declaration" (def_declaration anchor,expression,declaration extender)) ))) -(def .public (bundle expander host_analysis program anchorT,expressionT,declarationT extender) +(def .public (bundle expander host_analysis program anchor,expression,declaration extender) (All (_ anchor expression declaration) (-> Expander /////analysis.Bundle @@ -449,5 +453,5 @@ (Bundle anchor expression declaration))) (<| (///bundle.prefix "lux") (|> ///bundle.empty - (dictionary.has "def" (lux::def expander host_analysis)) - (dictionary.composite (..bundle::def expander host_analysis program anchorT,expressionT,declarationT extender))))) + (dictionary.has "def" (lux::def expander anchor,expression,declaration host_analysis)) + (dictionary.composite (..bundle::def expander host_analysis program anchor,expression,declaration 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 0b9ec3dba..77274bc83 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 @@ -3,11 +3,28 @@ [lux (.except) [abstract [monad (.only do)]] - [meta + [control + ["[0]" try] + ["[0]" exception (.only Exception)]] + [data + [text + ["%" \\format]]] + ["[0]" meta (.only) [macro - ["^" pattern]]]]] + ["^" pattern]] + [target + [jvm + [bytecode (.only Bytecode)]]] + [type + ["[0]" check]] + [compiler + [meta + ["[0]" archive (.only Archive)] + ["[0]" cache + [dependency + ["[1]/[0]" artifact]]]]]]]] ["[0]" / - [runtime (.only Phase)] + [runtime (.only Operation Phase Extender)] ["[1][0]" primitive] ["[1][0]" structure] ["[1][0]" reference] @@ -17,13 +34,38 @@ ["//[1]" /// ["[1][0]" extension] [// - ["[0]" synthesis] + ["[0]" synthesis (.only Synthesis)] [/// ["[0]" reference] ["[1]" phase (.use "[1]#[0]" monad)]]]]]) -(def .public (generate archive synthesis) - Phase +(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 lux + phase archive + name parameters) + (-> Extender Lux + (-> Extender Lux Phase) Archive + Symbol (List Synthesis) + (Operation (Bytecode Any))) + (when (|> name + meta.export + (meta.result lux)) + {try.#Success [exported? type value]} + (if (check.subsumes? .Generation type) + ((extender value) "" (phase extender lux) archive parameters) + (///.except ..not_an_extension [name .Generation type])) + + {try.#Failure error} + (///.failure error))) + +(def .public (generate extender lux archive synthesis) + (-> Extender Lux Phase) (when synthesis (^.with_template [ ] [( value) @@ -34,10 +76,10 @@ [synthesis.text /primitive.text]) (synthesis.variant variantS) - (/structure.variant generate archive variantS) + (/structure.variant (generate extender lux) archive variantS) (synthesis.tuple members) - (/structure.tuple generate archive members) + (/structure.tuple (generate extender lux) archive members) {synthesis.#Reference reference} (when reference @@ -48,32 +90,35 @@ (/reference.constant archive constant)) (synthesis.branch/when [valueS pathS]) - (/when.when generate archive [valueS pathS]) + (/when.when (generate extender lux) archive [valueS pathS]) (synthesis.branch/exec [this that]) - (/when.exec generate archive [this that]) + (/when.exec (generate extender lux) archive [this that]) (synthesis.branch/let [inputS register bodyS]) - (/when.let generate archive [inputS register bodyS]) + (/when.let (generate extender lux) archive [inputS register bodyS]) (synthesis.branch/if [conditionS thenS elseS]) - (/when.if generate archive [conditionS thenS elseS]) + (/when.if (generate extender lux) archive [conditionS thenS elseS]) (synthesis.branch/get [path recordS]) - (/when.get generate archive [path recordS]) + (/when.get (generate extender lux) archive [path recordS]) (synthesis.loop/scope scope) - (/loop.scope generate archive scope) + (/loop.scope (generate extender lux) archive scope) (synthesis.loop/again updates) - (/loop.again generate archive updates) + (/loop.again (generate extender lux) archive updates) (synthesis.function/abstraction abstraction) - (/function.abstraction generate archive abstraction) + (/function.abstraction (generate extender lux) archive abstraction) (synthesis.function/apply application) - (/function.apply generate archive application) + (/function.apply (generate extender lux) archive application) + + {synthesis.#Extension [["" name] parameters]} + (///extension.apply archive (generate extender lux) [name parameters]) - {synthesis.#Extension extension} - (///extension.apply archive generate extension) + {synthesis.#Extension [name parameters]} + (extension_application extender lux generate archive name parameters) )) diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis.lux index fba249351..24c8189a3 100644 --- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis.lux @@ -93,14 +93,14 @@ (|> (//extension.apply archive optimization [name args]) (phase.result' state) (pipe.when - {try.#Success output} - {try.#Success output} - {try.#Failure _} (|> args (monad.each phase.monad optimization') - (phase#each (|>> [name] {/.#Extension})) - (phase.result' state)))))) + (phase#each (|>> [["" name]] {/.#Extension})) + (phase.result' state)) + + success + success)))) ))) (def .public (phase archive analysis) diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis/loop.lux index 0ae8912f8..99eddb022 100644 --- a/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/meta/compiler/language/lux/phase/synthesis/loop.lux @@ -187,7 +187,7 @@ ))) ... TODO: Stop relying on this custom code. - {/.#Extension ["lux syntax char case!" (list.partial input else matches)]} + {/.#Extension [["" "lux syntax char case!"] (list.partial input else matches)]} (if return? (do [! maybe.monad] [input (again false input) @@ -204,7 +204,7 @@ (again false match))) matches) else (again return? else)] - (in {/.#Extension ["lux syntax char case!" (list.partial input else matches)]})) + (in {/.#Extension [["" "lux syntax char case!"] (list.partial input else matches)]})) {.#None}) {/.#Extension [name args]} diff --git a/stdlib/source/library/lux/meta/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/meta/compiler/language/lux/synthesis.lux index 377e232b1..090832274 100644 --- a/stdlib/source/library/lux/meta/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/meta/compiler/language/lux/synthesis.lux @@ -23,6 +23,7 @@ ["i" int] ["f" frac]]] [meta + ["[0]" symbol] [macro ["^" pattern]]]]] ["[0]" / @@ -129,7 +130,7 @@ {#Structure (Complex Synthesis)} {#Reference Reference} {#Control (Control Synthesis)} - {#Extension (Extension Synthesis)}))) + {#Extension [Symbol (List Synthesis)]}))) (with_template [ ] [(type .public @@ -413,7 +414,7 @@ (text.interposed " ") (text.enclosed ["{#again " "}"])))) - {#Extension [name args]} + {#Extension [[_ name] args]} (|> (list#each %synthesis args) (text.interposed " ") (format (%.text name) " ") @@ -695,7 +696,9 @@ [#Structure (analysis/complex.equivalence =)] [#Reference reference.equivalence] [#Control (control_equivalence =)] - [#Extension (extension.equivalence =)]) + [#Extension (product.equivalence symbol.equivalence (list.equivalence =)) + ... (extension.equivalence =) + ]) _ false)))) @@ -712,14 +715,16 @@ (def (hash value) (let [again_hash [..equivalence hash]] (when value - (^.with_template [ ] + (^.with_template [ ] [{ value} - (at hash value)]) - ([#Simple /simple.hash] - [#Structure (analysis/complex.hash again_hash)] - [#Reference reference.hash] - [#Control (..control_hash again_hash)] - [#Extension (extension.hash again_hash)])))))) + (n.* (at hash value))]) + ([2 #Simple /simple.hash] + [3 #Structure (analysis/complex.hash again_hash)] + [5 #Reference reference.hash] + [7 #Control (..control_hash again_hash)] + [11 #Extension (product.hash symbol.hash (list.hash again_hash)) + ... (extension.hash again_hash) + ])))))) (def .public !bind_top (template (!bind_top register thenP) diff --git a/stdlib/source/library/lux/meta/extension.lux b/stdlib/source/library/lux/meta/extension.lux index 175b1143f..b8c707ddf 100644 --- a/stdlib/source/library/lux/meta/extension.lux +++ b/stdlib/source/library/lux/meta/extension.lux @@ -65,6 +65,37 @@ [.any .end .and .result "lux def analysis" analysis] [.any .end .and .result "lux def synthesis" synthesis] - [.any .end .and .result "lux def generation" generation] + ... [.any .end .and .result "lux def generation" generation] [.any .end .and .result "lux def declaration" declaration] ) + +(with_template [ ] + [(def .public + (syntax (_ [[handler extension phase archive inputs] (.form (all <>.and + .local + .local + .local + .local + (.tuple (<>.some .any)))) + body .any]) + (let [g!handler (code.local handler) + g!name (code.local extension) + g!phase (code.local phase) + g!archive (code.local archive)] + (with_symbols [g!inputs g!error g!_] + (in (list (` ( (.function ((, g!handler) (, g!name) (, g!phase) (, g!archive) (, g!inputs)) + (.when ( + (monad.do <>.monad + [(,* inputs) + (, g!_) ] + (.at <>.monad (,' in) (, body))) + (, g!inputs)) + {.#Right (, g!_)} + (, g!_) + + {.#Left (, g!error)} + (phase.failure (, g!error))) + )))))))))] + + [.any .end .and .result "lux extension generation" generation .Generation] + ) diff --git a/stdlib/source/library/lux/meta/type/check.lux b/stdlib/source/library/lux/meta/type/check.lux index 718f27931..b36b2b112 100644 --- a/stdlib/source/library/lux/meta/type/check.lux +++ b/stdlib/source/library/lux/meta/type/check.lux @@ -784,7 +784,9 @@ (monad.each ..monad (clean aliases)) (check#each (|>> {.#Primitive name}))) - (^.or {.#Parameter _} {.#Ex _} {.#Named _}) + (^.or {.#Parameter _} + {.#Ex _} + {.#Named _}) (check#in inputT) (^.with_template [] @@ -793,7 +795,10 @@ [leftT' (clean aliases leftT)] (|> (clean aliases rightT) (check#each (|>> { leftT'}))))]) - ([.#Sum] [.#Product] [.#Function] [.#Apply]) + ([.#Sum] + [.#Product] + [.#Function] + [.#Apply]) {.#Var @it} (when aliases @@ -828,5 +833,6 @@ [envT+' (monad.each ! (clean aliases) envT+) unquantifiedT' (clean aliases unquantifiedT)] (in { envT+' unquantifiedT'}))]) - ([.#UnivQ] [.#ExQ]) + ([.#UnivQ] + [.#ExQ]) )) diff --git a/stdlib/source/library/lux/meta/type/unit.lux b/stdlib/source/library/lux/meta/type/unit.lux index e95b261f0..823e300cd 100644 --- a/stdlib/source/library/lux/meta/type/unit.lux +++ b/stdlib/source/library/lux/meta/type/unit.lux @@ -1,3 +1,4 @@ +... https://en.wikipedia.org/wiki/Dimensional_analysis (.require [library [lux (.except type) diff --git a/stdlib/source/program/compositor.lux b/stdlib/source/program/compositor.lux index 99d36a8f9..4b12d65a9 100644 --- a/stdlib/source/program/compositor.lux +++ b/stdlib/source/program/compositor.lux @@ -143,10 +143,10 @@ analysis.Bundle (IO (Platform )) (generation.Bundle ) - (-> phase.Wrapper (declaration.Bundle )) + (declaration.Bundle ) (Program expression artifact) (-> Archive Symbol (generation.Operation expression)) [Type Type Type] - (-> phase.Wrapper Extender) + Extender Service [Packager file.Path] (Async Any))) diff --git a/stdlib/source/test/lux/meta/extension.lux b/stdlib/source/test/lux/meta/extension.lux index 66bf59e0e..419570970 100644 --- a/stdlib/source/test/lux/meta/extension.lux +++ b/stdlib/source/test/lux/meta/extension.lux @@ -20,7 +20,7 @@ ["[0]" random] [number ["n" nat]]] - [meta + ["[0]" meta (.only) ["[0]" code ["<[1]>" \\parser]] [macro @@ -54,6 +54,7 @@ ["[0]" synthesis (.only) ["<[1]>" \\parser]] [phase + ["[0]" extension] [generation (.,, (.for "JVM" (.,, (.these ["[0]" jvm ["[1]/[0]" runtime]])) @@ -103,6 +104,11 @@ (phase archive pass_through)) ... Generation + (def my_generation|generation + Generation + (generation (_ self phase archive [pass_through .any]) + (phase archive pass_through))) + (analysis (..my_generation self phase archive [parameters (<>.some .any)]) (let [! phase.monad] (|> parameters @@ -113,26 +119,26 @@ (let [! phase.monad] (|> parameters (monad.each ! (phase archive)) - (at ! each (|>> {synthesis.#Extension self}))))) - - (generation (..my_generation self phase archive [pass_through .any]) - (phase archive pass_through)) + (at ! each (|>> {synthesis.#Extension (symbol ..my_generation|generation)}))))) + + (def dummy_generation|generation + Generation + (generation (_ self phase archive []) + (let [self ..dummy_generation] + (at phase.monad in + (for @.jvm (jvm.string self) + @.js (js.string self) + @.python (python.unicode self) + @.lua (lua.string self) + @.ruby (ruby.string self) + @.php (php.string self) + @.scheme (scheme.string self)))))) (analysis (..dummy_generation self phase archive []) (at phase.monad in {analysis.#Extension self (list)})) (synthesis (..dummy_generation self phase archive []) - (at phase.monad in {synthesis.#Extension self (list)})) - - (generation (..dummy_generation self phase archive []) - (at phase.monad in - (for @.jvm (jvm.string self) - @.js (js.string self) - @.python (python.unicode self) - @.lua (lua.string self) - @.ruby (ruby.string self) - @.php (php.string self) - @.scheme (scheme.string self)))) + (at phase.monad in {synthesis.#Extension (symbol ..dummy_generation|generation) (list)})) ... Declaration (declaration (..my_declaration self phase archive [expression .any]) @@ -146,9 +152,12 @@ expressionS (declaration.lifted_synthesis (synthesis_phase archive expressionA)) + lux (<| declaration.lifted_analysis + extension.lifted + meta.compiler_state) generation_phase declaration.generation expressionG (declaration.lifted_generation - (generation_phase archive expressionS)) + (generation_phase lux archive expressionS)) _ (declaration.lifted_generation (generation.with_new_context archive unit.none -- cgit v1.2.3