diff options
author | Eduardo Julian | 2022-06-26 19:37:45 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-06-26 19:37:45 -0400 |
commit | 853d28f803e75d125915a81dcdcd140513efe3d2 (patch) | |
tree | 41d24b6cb5593b631793efa77f53359e8229ea37 /stdlib/source/library | |
parent | 9f6505491e8a5c8a159ce094fe0af6f4fef0c5cf (diff) |
Re-named directives to declarations.
Diffstat (limited to '')
37 files changed, 735 insertions, 734 deletions
diff --git a/stdlib/source/library/lux/extension.lux b/stdlib/source/library/lux/extension.lux index 9c3946a30..cfa13af9b 100644 --- a/stdlib/source/library/lux/extension.lux +++ b/stdlib/source/library/lux/extension.lux @@ -31,7 +31,7 @@ #archive Text #inputs (List Code)])) -(def (declaration default) +(def (declarationP default) (-> Code (Parser Declaration)) (<c>.form (all <>.and <c>.any @@ -42,7 +42,7 @@ (with_template [<any> <end> <and> <result> <extension> <name>] [(def .public <name> - (syntax (_ [[name extension phase archive inputs] (..declaration (` <any>)) + (syntax (_ [[name extension phase archive inputs] (..declarationP (` <any>)) body <c>.any]) (let [g!name (code.local extension) g!phase (code.local phase) @@ -66,5 +66,5 @@ [<c>.any <c>.end <c>.and <c>.result "lux def analysis" analysis] [<a>.any <a>.end <a>.and <a>.result "lux def synthesis" synthesis] [<s>.any <s>.end <s>.and <s>.result "lux def generation" generation] - [<c>.any <c>.end <c>.and <c>.result "lux def directive" directive] + [<c>.any <c>.end <c>.and <c>.result "lux def declaration" declaration] ) diff --git a/stdlib/source/library/lux/ffi/export.js.lux b/stdlib/source/library/lux/ffi/export.js.lux index e40ea1964..a887d9f84 100644 --- a/stdlib/source/library/lux/ffi/export.js.lux +++ b/stdlib/source/library/lux/ffi/export.js.lux @@ -1,7 +1,7 @@ (.require [library [lux (.except) - [extension (.only directive)] + [extension (.only declaration)] ["[0]" meta] ["[0]" static] [abstract @@ -32,7 +32,7 @@ [language [lux ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] [analysis ["[0]" type]]]]]]]]) @@ -49,41 +49,41 @@ (with_expansions [<extension> (static.random (|>> %.nat (%.format "lua export ") code.text) random.nat)] - (directive (<extension> self phase archive [name <code>.text - term <code>.any]) - (do [! phase.monad] - [next directive.analysis - [_ term] (<| directive.lifted_analysis - type.inferring - (next archive term)) + (declaration (<extension> self phase archive [name <code>.text + term <code>.any]) + (do [! phase.monad] + [next declaration.analysis + [_ term] (<| declaration.lifted_analysis + type.inferring + (next archive term)) - next directive.synthesis - term (directive.lifted_synthesis - (next archive term)) + next declaration.synthesis + term (declaration.lifted_synthesis + (next archive term)) - dependencies (directive.lifted_generation - (dependency.dependencies archive term)) + dependencies (declaration.lifted_generation + (dependency.dependencies archive term)) - next directive.generation - [interim_artifacts term] (directive.lifted_generation - (generation.with_interim_artifacts archive - (next archive term))) + next declaration.generation + [interim_artifacts term] (declaration.lifted_generation + (generation.with_interim_artifacts archive + (next archive term))) - _ (directive.lifted_generation - (do ! - [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) - .let [$module (/.var "module") - $exports (/.the "exports" $module) - definition (/.define (/.var name) term) - export (/.when (/.not (/.= (/.string "undefined") (/.type_of $module))) - (/.set (/.the name $exports) (/.var name))) - code (all /.then - definition - export)] - _ (generation.execute! definition) - _ (generation.save! @self {.#None} code)] - (generation.log! (%.format "Export " (%.text name)))))] - (in directive.no_requirements))) + _ (declaration.lifted_generation + (do ! + [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) + .let [$module (/.var "module") + $exports (/.the "exports" $module) + definition (/.define (/.var name) term) + export (/.when (/.not (/.= (/.string "undefined") (/.type_of $module))) + (/.set (/.the name $exports) (/.var name))) + code (all /.then + definition + export)] + _ (generation.execute! definition) + _ (generation.save! @self {.#None} code)] + (generation.log! (%.format "Export " (%.text name)))))] + (in declaration.no_requirements))) (def .public export (syntax (_ [exports (<>.many <code>.any)]) diff --git a/stdlib/source/library/lux/ffi/export.lua.lux b/stdlib/source/library/lux/ffi/export.lua.lux index 66b98998d..c38eaf711 100644 --- a/stdlib/source/library/lux/ffi/export.lua.lux +++ b/stdlib/source/library/lux/ffi/export.lua.lux @@ -1,7 +1,7 @@ (.require [library [lux (.except) - [extension (.only directive)] + [extension (.only declaration)] ["[0]" meta] ["[0]" static] [abstract @@ -32,7 +32,7 @@ [language [lux ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] [analysis ["[0]" type]]]]]]]]) @@ -53,53 +53,53 @@ (with_expansions [<extension> (static.random (|>> %.nat (%.format "lua export ") code.text) random.nat)] - (directive (<extension> self phase archive [name <code>.text - term <code>.any]) - (do [! phase.monad] - [next directive.analysis - [_ term] (<| directive.lifted_analysis - type.inferring - (next archive term)) + (declaration (<extension> self phase archive [name <code>.text + term <code>.any]) + (do [! phase.monad] + [next declaration.analysis + [_ term] (<| declaration.lifted_analysis + type.inferring + (next archive term)) - next directive.synthesis - term (directive.lifted_synthesis - (next archive term)) + next declaration.synthesis + term (declaration.lifted_synthesis + (next archive term)) - dependencies (directive.lifted_generation - (dependency.dependencies archive term)) + dependencies (declaration.lifted_generation + (dependency.dependencies archive term)) - next directive.generation - [interim_artifacts term] (directive.lifted_generation - (generation.with_interim_artifacts archive - (next archive term))) + next declaration.generation + [interim_artifacts term] (declaration.lifted_generation + (generation.with_interim_artifacts archive + (next archive term))) - _ (directive.lifted_generation - (do ! - [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) - .let [$exports (/.var "_REQUIREDNAME") - $global (/.var "_G") - exporting? (/.not (/.= /.nil $exports)) - no_exports? (/.= /.nil (/.item $exports $global)) - initialize_exports! (/.set (list (/.item $exports $global)) (/.table (list))) - export_definition! (/.set (|> $global - (/.item $exports) - (/.item (/.string name)) - (list)) - (/.var name)) - export! (/.when exporting? - (all /.then - (/.when no_exports? - initialize_exports!) - export_definition! - ))] - _ (generation.execute! (all /.then - (/.set (list (/.var name)) term) - export!)) - _ (generation.save! @self {.#None} (all /.then - (/.local/1 (/.var name) term) - export!))] - (generation.log! (%.format "Export " (%.text name)))))] - (in directive.no_requirements))) + _ (declaration.lifted_generation + (do ! + [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) + .let [$exports (/.var "_REQUIREDNAME") + $global (/.var "_G") + exporting? (/.not (/.= /.nil $exports)) + no_exports? (/.= /.nil (/.item $exports $global)) + initialize_exports! (/.set (list (/.item $exports $global)) (/.table (list))) + export_definition! (/.set (|> $global + (/.item $exports) + (/.item (/.string name)) + (list)) + (/.var name)) + export! (/.when exporting? + (all /.then + (/.when no_exports? + initialize_exports!) + export_definition! + ))] + _ (generation.execute! (all /.then + (/.set (list (/.var name)) term) + export!)) + _ (generation.save! @self {.#None} (all /.then + (/.local/1 (/.var name) term) + export!))] + (generation.log! (%.format "Export " (%.text name)))))] + (in declaration.no_requirements))) (def .public export (syntax (_ [exports (<>.many <code>.any)]) diff --git a/stdlib/source/library/lux/ffi/export.py.lux b/stdlib/source/library/lux/ffi/export.py.lux index 42309927e..be61ff11e 100644 --- a/stdlib/source/library/lux/ffi/export.py.lux +++ b/stdlib/source/library/lux/ffi/export.py.lux @@ -1,7 +1,7 @@ (.require [library [lux (.except) - [extension (.only directive)] + [extension (.only declaration)] ["[0]" meta] ["[0]" static] [abstract @@ -32,7 +32,7 @@ [language [lux ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] [analysis ["[0]" type]]]]]]]]) @@ -49,34 +49,34 @@ (with_expansions [<extension> (static.random (|>> %.nat (%.format "python export ") code.text) random.nat)] - (directive (<extension> self phase archive [name <code>.text - term <code>.any]) - (do [! phase.monad] - [next directive.analysis - [_ term] (<| directive.lifted_analysis - type.inferring - (next archive term)) + (declaration (<extension> self phase archive [name <code>.text + term <code>.any]) + (do [! phase.monad] + [next declaration.analysis + [_ term] (<| declaration.lifted_analysis + type.inferring + (next archive term)) - next directive.synthesis - term (directive.lifted_synthesis - (next archive term)) + next declaration.synthesis + term (declaration.lifted_synthesis + (next archive term)) - dependencies (directive.lifted_generation - (dependency.dependencies archive term)) + dependencies (declaration.lifted_generation + (dependency.dependencies archive term)) - next directive.generation - [interim_artifacts term] (directive.lifted_generation - (generation.with_interim_artifacts archive - (next archive term))) + next declaration.generation + [interim_artifacts term] (declaration.lifted_generation + (generation.with_interim_artifacts archive + (next archive term))) - _ (directive.lifted_generation - (do ! - [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) - .let [code (/.set (list (/.item (/.string name) /.globals/0)) term)] - _ (generation.execute! code) - _ (generation.save! @self {.#None} code)] - (generation.log! (%.format "Export " (%.text name)))))] - (in directive.no_requirements))) + _ (declaration.lifted_generation + (do ! + [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) + .let [code (/.set (list (/.item (/.string name) /.globals/0)) term)] + _ (generation.execute! code) + _ (generation.save! @self {.#None} code)] + (generation.log! (%.format "Export " (%.text name)))))] + (in declaration.no_requirements))) (def .public export (syntax (_ [exports (<>.many <code>.any)]) diff --git a/stdlib/source/library/lux/ffi/export.rb.lux b/stdlib/source/library/lux/ffi/export.rb.lux index 6777bfa86..b29982a1c 100644 --- a/stdlib/source/library/lux/ffi/export.rb.lux +++ b/stdlib/source/library/lux/ffi/export.rb.lux @@ -1,7 +1,7 @@ (.require [library [lux (.except global) - [extension (.only directive)] + [extension (.only declaration)] ["[0]" meta] ["[0]" static] ["[0]" type] @@ -34,7 +34,7 @@ [language [lux ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] ["[0]" analysis ["[1]" type]]]]]]]]) @@ -87,45 +87,45 @@ (with_expansions [<extension> (static.random (|>> %.nat (%.format "ruby export ") code.text) random.nat)] - (directive (<extension> self phase archive [global? <code>.bit - name <code>.text - term <code>.any]) - (do [! phase.monad] - [next directive.analysis - [type term] (<| directive.lifted_analysis - analysis.inferring - (next archive term)) + (declaration (<extension> self phase archive [global? <code>.bit + name <code>.text + term <code>.any]) + (do [! phase.monad] + [next declaration.analysis + [type term] (<| declaration.lifted_analysis + analysis.inferring + (next archive term)) - next directive.synthesis - term (directive.lifted_synthesis - (next archive term)) + next declaration.synthesis + term (declaration.lifted_synthesis + (next archive term)) - dependencies (directive.lifted_generation - (dependency.dependencies archive term)) + dependencies (declaration.lifted_generation + (dependency.dependencies archive term)) - next directive.generation - [interim_artifacts term] (directive.lifted_generation - (generation.with_interim_artifacts archive - (next archive term))) + next declaration.generation + [interim_artifacts term] (declaration.lifted_generation + (generation.with_interim_artifacts archive + (next archive term))) - _ (directive.lifted_generation - (do ! - [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) - .let [[:input:/* :output:] (type.flat_function type) - code (if global? - (/.set (list (/.manual name)) term) - (case :input:/* - {.#End} - (/.function (/.manual name) (list) - (/.return term)) + _ (declaration.lifted_generation + (do ! + [@self (generation.learn_custom name (list#mix set.has dependencies interim_artifacts)) + .let [[:input:/* :output:] (type.flat_function type) + code (if global? + (/.set (list (/.manual name)) term) + (case :input:/* + {.#End} + (/.function (/.manual name) (list) + (/.return term)) - _ - (/.statement (/.apply (list (/.string name) term) {.#None} - (/.manual "define_method")))))] - _ (generation.execute! code) - _ (generation.save! @self {.#None} code)] - (generation.log! (%.format "Export " (%.text name)))))] - (in directive.no_requirements))) + _ + (/.statement (/.apply (list (/.string name) term) {.#None} + (/.manual "define_method")))))] + _ (generation.execute! code) + _ (generation.save! @self {.#None} code)] + (generation.log! (%.format "Export " (%.text name)))))] + (in declaration.no_requirements))) (def .public export (syntax (_ [exports (<>.many <code>.any)]) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index 4922fd23e..7a5bdebc0 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Primitive parameter) + [lux (.except Primitive parameter type) ["[0]" ffi (.only import)] ["[0]" type] [abstract diff --git a/stdlib/source/library/lux/target/jvm/type/lux.lux b/stdlib/source/library/lux/target/jvm/type/lux.lux index b68215990..6f2ab6b47 100644 --- a/stdlib/source/library/lux/target/jvm/type/lux.lux +++ b/stdlib/source/library/lux/target/jvm/type/lux.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Primitive int char parameter) + [lux (.except Primitive int char parameter type) [abstract ["[0]" monad (.only do)]] [control @@ -16,7 +16,7 @@ ["[0]" array] ["[0]" dictionary (.only Dictionary)]]] [type - [primitive (.except)] + [":" primitive] ["[0]" check (.only Check) (.use "[1]#[0]" monad)]]]] ["[0]" // (.only) [category (.only Void Value Return Method Primitive Object Class Array Var Parameter)] @@ -30,12 +30,13 @@ ["[1][0]" name]]]]) (with_template [<name>] - [(primitive .public (<name> class) Any)] + [(:.primitive .public (<name> class) Any)] - [Lower] [Upper] + [Lower] + [Upper] ) -(type .public Mapping +(.type .public Mapping (Dictionary Text Type)) (def .public fresh @@ -186,10 +187,10 @@ [//reflection.double] [//reflection.char])))) {.#Primitive (|> name //reflection.class //reflection.array //reflection.reflection) {.#End}} - (|> elementT array.Array .type)) + (|> elementT array.Array type_literal)) _ - (|> elementT array.Array .type))))) + (|> elementT array.Array type_literal))))) (<>.after (<text>.this //descriptor.array_prefix)))) (def .public (type mapping) diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index f9c201df1..f966f9b63 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -31,7 +31,7 @@ [program (.only Program)] ["[1][0]" syntax (.only Aliases)] ["[1][0]" synthesis] - ["[1][0]" directive (.only Requirements)] + ["[1][0]" declaration (.only Requirements)] ["[1][0]" generation] ["[1][0]" analysis (.only) [macro (.only Expander)] @@ -40,11 +40,11 @@ [phase ["[0]P" analysis] ["[0]P" synthesis] - ["[0]P" directive] + ["[0]P" declaration] ["[0]" extension (.only Extender) ["[0]E" analysis] ["[0]E" synthesis] - [directive + [declaration ["[0]D" lux]]]]]] [meta ["[0]" archive (.only Archive) @@ -54,41 +54,41 @@ ["[0]" document]]]]]]) (def .public (state target module configuration expander host_analysis host generate generation_bundle) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Target descriptor.Module Configuration Expander ///analysis.Bundle - (///generation.Host expression directive) - (///generation.Phase anchor expression directive) - (///generation.Bundle anchor expression directive) - (///directive.State+ anchor expression directive))) + (///generation.Host expression declaration) + (///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))]] [extension.empty - [///directive.#analysis [///directive.#state analysis_state - ///directive.#phase (analysisP.phase expander)] - ///directive.#synthesis [///directive.#state synthesis_state - ///directive.#phase synthesisP.phase] - ///directive.#generation [///directive.#state generation_state - ///directive.#phase generate]]])) + [///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]]])) -(def .public (with_default_directives expander host_analysis program anchorT,expressionT,directiveT extender) - (All (_ anchor expression directive) +(def .public (with_default_declarations expander host_analysis program anchorT,expressionT,declarationT extender) + (All (_ anchor expression declaration) (-> Expander ///analysis.Bundle - (Program expression directive) + (Program expression declaration) [Type Type Type] Extender - (-> (///directive.State+ anchor expression directive) - (///directive.State+ anchor expression directive)))) - (function (_ [directive_extensions sub_state]) - [(dictionary.composite directive_extensions - (luxD.bundle expander host_analysis program anchorT,expressionT,directiveT extender)) + (-> (///declaration.State+ anchor expression declaration) + (///declaration.State+ anchor expression declaration)))) + (function (_ [declaration_extensions sub_state]) + [(dictionary.composite declaration_extensions + (luxD.bundle expander host_analysis program anchorT,expressionT,declarationT extender)) sub_state])) (type Reader @@ -115,22 +115,22 @@ [source' output]]})))) (type (Operation a) - (All (_ anchor expression directive) - (///directive.Operation anchor expression directive a))) + (All (_ anchor expression declaration) + (///declaration.Operation anchor expression declaration a))) -(type (Payload directive) - [(///generation.Buffer directive) +(type (Payload declaration) + [(///generation.Buffer declaration) Registry]) (def (begin dependencies hash input) (-> (List descriptor.Module) Nat ///.Input - (All (_ anchor expression directive) - (///directive.Operation anchor expression directive - [Source (Payload directive)]))) + (All (_ anchor expression declaration) + (///declaration.Operation anchor expression declaration + [Source (Payload declaration)]))) (do ///phase.monad [.let [module (the ///.#module input)] - _ (///directive.set_current_module module)] - (///directive.lifted_analysis + _ (///declaration.set_current_module module)] + (///declaration.lifted_analysis (do [! ///phase.monad] [_ (moduleA.create hash module) _ (monad.each ! moduleA.import dependencies) @@ -141,74 +141,74 @@ (def (end module) (-> descriptor.Module - (All (_ anchor expression directive) - (///directive.Operation anchor expression directive [.Module (Payload directive)]))) + (All (_ anchor expression declaration) + (///declaration.Operation anchor expression declaration [.Module (Payload declaration)]))) (do ///phase.monad - [_ (///directive.lifted_analysis + [_ (///declaration.lifted_analysis (moduleA.set_compiled module)) analysis_module (<| (is (Operation .Module)) - ///directive.lifted_analysis + ///declaration.lifted_analysis extension.lifted meta.current_module) - final_buffer (///directive.lifted_generation + final_buffer (///declaration.lifted_generation ///generation.buffer) - final_registry (///directive.lifted_generation + final_registry (///declaration.lifted_generation ///generation.get_registry)] (in [analysis_module [final_buffer final_registry]]))) ... TODO: Inline ASAP (def (get_current_payload _) - (All (_ directive) - (-> (Payload directive) + (All (_ declaration) + (-> (Payload declaration) (All (_ anchor expression) - (///directive.Operation anchor expression directive - (Payload directive))))) + (///declaration.Operation anchor expression declaration + (Payload declaration))))) (do ///phase.monad - [buffer (///directive.lifted_generation + [buffer (///declaration.lifted_generation ///generation.buffer) - registry (///directive.lifted_generation + registry (///declaration.lifted_generation ///generation.get_registry)] (in [buffer registry]))) ... TODO: Inline ASAP -(def (process_directive wrapper archive expander pre_payoad code) - (All (_ directive) - (-> ///phase.Wrapper Archive Expander (Payload directive) Code +(def (process_declaration wrapper archive expander pre_payoad code) + (All (_ declaration) + (-> ///phase.Wrapper Archive Expander (Payload declaration) Code (All (_ anchor expression) - (///directive.Operation anchor expression directive - [Requirements (Payload directive)])))) + (///declaration.Operation anchor expression declaration + [Requirements (Payload declaration)])))) (do ///phase.monad [.let [[pre_buffer pre_registry] pre_payoad] - _ (///directive.lifted_generation + _ (///declaration.lifted_generation (///generation.set_buffer pre_buffer)) - _ (///directive.lifted_generation + _ (///declaration.lifted_generation (///generation.set_registry pre_registry)) - requirements (let [execute! (directiveP.phase wrapper expander)] + requirements (let [execute! (declarationP.phase wrapper expander)] (execute! archive code)) post_payload (..get_current_payload pre_payoad)] (in [requirements post_payload]))) (def (iteration' wrapper archive expander reader source pre_payload) - (All (_ directive) - (-> ///phase.Wrapper Archive Expander Reader Source (Payload directive) + (All (_ declaration) + (-> ///phase.Wrapper Archive Expander Reader Source (Payload declaration) (All (_ anchor expression) - (///directive.Operation anchor expression directive - [Source Requirements (Payload directive)])))) + (///declaration.Operation anchor expression declaration + [Source Requirements (Payload declaration)])))) (do ///phase.monad - [[source code] (///directive.lifted_analysis + [[source code] (///declaration.lifted_analysis (..read source reader)) - [requirements post_payload] (process_directive wrapper archive expander pre_payload code)] + [requirements post_payload] (process_declaration wrapper archive expander pre_payload code)] (in [source requirements post_payload]))) (def (iteration wrapper archive expander module source pre_payload aliases) - (All (_ directive) - (-> ///phase.Wrapper Archive Expander descriptor.Module Source (Payload directive) Aliases + (All (_ declaration) + (-> ///phase.Wrapper Archive Expander descriptor.Module Source (Payload declaration) Aliases (All (_ anchor expression) - (///directive.Operation anchor expression directive - (Maybe [Source Requirements (Payload directive)]))))) + (///declaration.Operation anchor expression declaration + (Maybe [Source Requirements (Payload declaration)]))))) (do ///phase.monad - [reader (///directive.lifted_analysis + [reader (///declaration.lifted_analysis (..reader module aliases source))] (function (_ state) (case (///phase.result' state (..iteration' wrapper archive expander reader source pre_payload)) @@ -231,11 +231,11 @@ (-> .Module Aliases) (|>> (the .#module_aliases) (dictionary.of_list text.hash))) -(def .public (compiler wrapper expander prelude write_directive) - (All (_ anchor expression directive) - (-> ///phase.Wrapper Expander descriptor.Module (-> directive Binary) - (Instancer (///directive.State+ anchor expression directive) .Module))) - (let [execute! (directiveP.phase wrapper expander)] +(def .public (compiler wrapper expander prelude write_declaration) + (All (_ anchor expression declaration) + (-> ///phase.Wrapper Expander descriptor.Module (-> declaration Binary) + (Instancer (///declaration.State+ anchor expression declaration) .Module))) + (let [execute! (declarationP.phase wrapper expander)] (function (_ key parameters input) (let [dependencies (default_dependencies prelude input)] [///.#dependencies dependencies @@ -262,8 +262,8 @@ {.#Right [[module.#id (try.else module.runtime (archive.id module archive)) module.#descriptor descriptor module.#document (document.document key analysis_module)] - (sequence#each (function (_ [artifact_id custom directive]) - [artifact_id custom (write_directive directive)]) + (sequence#each (function (_ [artifact_id custom declaration]) + [artifact_id custom (write_declaration declaration)]) final_buffer) final_registry]}])) @@ -271,21 +271,21 @@ (let [[temporary_buffer temporary_registry] temporary_payload] (in [state {.#Left [///.#dependencies (|> requirements - (the ///directive.#imports) + (the ///declaration.#imports) (list#each product.left)) ///.#process (function (_ state archive) (again (<| (///phase.result' state) (do [! ///phase.monad] [analysis_module (<| (is (Operation .Module)) - ///directive.lifted_analysis + ///declaration.lifted_analysis extension.lifted meta.current_module) - _ (///directive.lifted_generation + _ (///declaration.lifted_generation (///generation.set_buffer temporary_buffer)) - _ (///directive.lifted_generation + _ (///declaration.lifted_generation (///generation.set_registry temporary_registry)) _ (|> requirements - (the ///directive.#referrals) + (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))))))]}])) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 0f893a1dc..492644edc 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -20,7 +20,7 @@ ["[0]" binary (.only Binary) ["_" \\format (.only Format)]] ["[0]" text (.use "[1]#[0]" equivalence) - ["%" \\format (.only format)]] + ["%" \\format]] [collection ["[0]" dictionary (.only Dictionary)] ["[0]" sequence (.only Sequence) (.use "[1]#[0]" mix)] @@ -44,7 +44,7 @@ ["[0]" syntax] ["[1][0]" synthesis] ["[1][0]" generation (.only Buffer)] - ["[1][0]" directive] + ["[1][0]" declaration] ["[1][0]" analysis (.only) [macro (.only Expander)] ["[0]A" module]] @@ -71,16 +71,16 @@ ["[1]" context] ["ioW" archive]]]]]) -(with_expansions [<type_vars> (these anchor expression directive) +(with_expansions [<type_vars> (these anchor expression declaration) <Operation> (these ///generation.Operation <type_vars>)] (type .public (Platform <type_vars>) (Record [#file_system (file.System Async) - #host (///generation.Host expression directive) + #host (///generation.Host expression declaration) #phase (///generation.Phase <type_vars>) #runtime (<Operation> [Registry Output]) #phase_wrapper (-> Archive (<Operation> ///phase.Wrapper)) - #write (-> directive Binary)])) + #write (-> declaration Binary)])) ... TODO: Get rid of this (type (Action a) @@ -92,7 +92,7 @@ (try.with async.monad))) (with_expansions [<Platform> (these (Platform <type_vars>)) - <State+> (these (///directive.State+ <type_vars>)) + <State+> (these (///declaration.State+ <type_vars>)) <Bundle> (these (///generation.Bundle <type_vars>))] (def (format //) @@ -175,10 +175,10 @@ (def (process_runtime archive platform) (All (_ <type_vars>) (-> Archive <Platform> - (///directive.Operation <type_vars> - [Archive (archive.Entry .Module)]))) + (///declaration.Operation <type_vars> + [Archive (archive.Entry .Module)]))) (do ///phase.monad - [[registry payload] (///directive.lifted_generation + [[registry payload] (///declaration.lifted_generation (..compile_runtime! platform)) .let [entry [..runtime_module payload registry]] archive (///phase.lifted (if (archive.reserved? archive descriptor.runtime) @@ -192,7 +192,7 @@ [analysers synthesizers generators - directives] + declarations] analysis_state state) (All (_ <type_vars>) @@ -200,24 +200,24 @@ [(Dictionary Text ///analysis.Handler) (Dictionary Text ///synthesis.Handler) (Dictionary Text (///generation.Handler <type_vars>)) - (Dictionary Text (///directive.Handler <type_vars>))] + (Dictionary Text (///declaration.Handler <type_vars>))] .Lux <State+> (Try <State+>))) (|> (sharing [<type_vars>] (is <State+> state) - (is (///directive.Operation <type_vars> Any) + (is (///declaration.Operation <type_vars> Any) (do [! ///phase.monad] - [_ (///directive.lifted_analysis + [_ (///declaration.lifted_analysis (do ! [_ (///analysis.set_state analysis_state)] (extension.with extender analysers))) - _ (///directive.lifted_synthesis + _ (///declaration.lifted_synthesis (extension.with extender synthesizers)) - _ (///directive.lifted_generation + _ (///declaration.lifted_generation (extension.with extender (as_expected generators))) - _ (extension.with extender (as_expected directives))] + _ (extension.with extender (as_expected declarations))] (in [])))) (///phase.result' state) (at try.monad each product.left))) @@ -227,27 +227,27 @@ (-> Archive <Platform> <State+> (Try [<State+> ///phase.Wrapper]))) (|> archive ((the #phase_wrapper platform)) - ///directive.lifted_generation + ///declaration.lifted_generation (///phase.result' state))) - (def (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives]) + (def (complete_extensions host_declaration_bundle phase_wrapper [analysers synthesizers generators declarations]) (All (_ <type_vars>) - (-> (-> ///phase.Wrapper (///directive.Bundle <type_vars>)) + (-> (-> ///phase.Wrapper (///declaration.Bundle <type_vars>)) ///phase.Wrapper [(Dictionary Text ///analysis.Handler) (Dictionary Text ///synthesis.Handler) (Dictionary Text (///generation.Handler <type_vars>)) - (Dictionary Text (///directive.Handler <type_vars>))] + (Dictionary Text (///declaration.Handler <type_vars>))] [(Dictionary Text ///analysis.Handler) (Dictionary Text ///synthesis.Handler) (Dictionary Text (///generation.Handler <type_vars>)) - (Dictionary Text (///directive.Handler <type_vars>))])) + (Dictionary Text (///declaration.Handler <type_vars>))])) [analysers synthesizers generators - (dictionary.composite directives (host_directive_bundle phase_wrapper))]) + (dictionary.composite declarations (host_declaration_bundle phase_wrapper))]) - (def .public (initialize context module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender + (def .public (initialize context module expander host_analysis platform generation_bundle host_declaration_bundle program anchorT,expressionT,declarationT extender import compilation_sources compilation_configuration) (All (_ <type_vars>) (-> context.Context @@ -256,8 +256,8 @@ ///analysis.Bundle <Platform> <Bundle> - (-> ///phase.Wrapper (///directive.Bundle <type_vars>)) - (Program expression directive) + (-> ///phase.Wrapper (///declaration.Bundle <type_vars>)) + (Program expression declaration) [Type Type Type] (-> ///phase.Wrapper Extender) Import (List _io.Context) Configuration (Async (Try [<State+> Archive ///phase.Wrapper])))) @@ -275,7 +275,7 @@ [archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (the #host platform) (the #file_system platform) context import compilation_sources) .let [with_missing_extensions (is (All (_ <type_vars>) - (-> <Platform> (Program expression directive) <State+> + (-> <Platform> (Program expression declaration) <State+> (Async (Try [///phase.Wrapper <State+>])))) (function (_ platform program state) (async#in @@ -283,9 +283,9 @@ [[state phase_wrapper] (..phase_wrapper archive platform state)] (|> state (initialize_state (extender phase_wrapper) - (as_expected (..complete_extensions host_directive_bundle phase_wrapper (as_expected bundles))) + (as_expected (..complete_extensions host_declaration_bundle phase_wrapper (as_expected bundles))) analysis_state) - (try#each (|>> (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper)) + (try#each (|>> (//init.with_default_declarations expander host_analysis program anchorT,expressionT,declarationT (extender phase_wrapper)) [phase_wrapper])))))))]] (if (archive.archived? archive descriptor.runtime) (do ! @@ -301,26 +301,26 @@ (in [state archive phase_wrapper]))))) (def compilation_log_separator - (format text.new_line text.tab)) + (%.format text.new_line text.tab)) (def (module_compilation_log module) (All (_ <type_vars>) (-> descriptor.Module <State+> Text)) (|>> (the [extension.#state - ///directive.#generation - ///directive.#state + ///declaration.#generation + ///declaration.#state extension.#state ///generation.#log]) (sequence#mix (function (_ right left) - (format left ..compilation_log_separator right)) + (%.format left ..compilation_log_separator right)) module))) (def with_reset_log (All (_ <type_vars>) (-> <State+> <State+>)) (has [extension.#state - ///directive.#generation - ///directive.#state + ///declaration.#generation + ///declaration.#state extension.#state ///generation.#log] sequence.empty)) @@ -447,10 +447,10 @@ [inherited (with_extensions (the <path> from) (the <path> state))] (in (has <path> inherited state))))] - [with_analysis_extensions [extension.#state ///directive.#analysis ///directive.#state extension.#bundle]] - [with_synthesis_extensions [extension.#state ///directive.#synthesis ///directive.#state extension.#bundle]] - [with_generation_extensions [extension.#state ///directive.#generation ///directive.#state extension.#bundle]] - [with_directive_extensions [extension.#bundle]] + [with_analysis_extensions [extension.#state ///declaration.#analysis ///declaration.#state extension.#bundle]] + [with_synthesis_extensions [extension.#state ///declaration.#synthesis ///declaration.#state extension.#bundle]] + [with_generation_extensions [extension.#state ///declaration.#generation ///declaration.#state extension.#bundle]] + [with_declaration_extensions [extension.#bundle]] ) (def (with_all_extensions from state) @@ -460,7 +460,7 @@ [state (with_analysis_extensions from state) state (with_synthesis_extensions from state) state (with_generation_extensions from state)] - (with_directive_extensions from state))) + (with_declaration_extensions from state))) (type (Context state) [Archive state]) @@ -600,8 +600,8 @@ with_modules (is (All (_ <type_vars>) (-> <State+> <State+>)) (revised [extension.#state - ///directive.#analysis - ///directive.#state + ///declaration.#analysis + ///declaration.#state extension.#state] (is (All (_ a) (-> a a)) (function (_ analysis_state) @@ -620,7 +620,7 @@ (def (set_current_module module state) (All (_ <type_vars>) (-> descriptor.Module <State+> <State+>)) - (|> (///directive.set_current_module module) + (|> (///declaration.set_current_module module) (///phase.result' state) try.trusted product.left)) @@ -685,9 +685,9 @@ (Try [<State+> (Either (///.Compilation <State+> .Module Any) (archive.Entry Any))]))) ((the ///.#process compilation) - ... TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. + ... TODO: The "///declaration.set_current_module" below shouldn't be necessary. Remove it ASAP. ... TODO: The context shouldn't need to be re-set either. - (|> (///directive.set_current_module module) + (|> (///declaration.set_current_module module) (///phase.result' state) try.trusted product.left) @@ -856,8 +856,8 @@ [context (import! (list) descriptor.runtime /#module) .let [[archive state] context meta_state (the [extension.#state - ///directive.#analysis - ///directive.#state + ///declaration.#analysis + ///declaration.#state extension.#state] state)] [_ /#type /#value] (|> /#definition diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/declaration.lux index 380e48d63..1f2b4505a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/declaration.lux @@ -26,14 +26,14 @@ [#state state #phase phase])) -(type .public (State anchor expression directive) +(type .public (State anchor expression declaration) (Record [#analysis (Component analysis.State+ analysis.Phase) #synthesis (Component synthesis.State+ synthesis.Phase) - #generation (Component (generation.State+ anchor expression directive) - (generation.Phase anchor expression directive))])) + #generation (Component (generation.State+ anchor expression declaration) + (generation.Phase anchor expression declaration))])) (type .public Import (Record @@ -56,8 +56,8 @@ #referrals (list#composite (the #referrals left) (the #referrals right))]) (with_template [<special> <general>] - [(type .public (<special> anchor expression directive) - (<general> (..State anchor expression directive) Code Requirements))] + [(type .public (<special> anchor expression declaration) + (<general> (..State anchor expression declaration) Code Requirements))] [State+ extension.State] [Operation extension.Operation] @@ -68,33 +68,33 @@ (with_template [<name> <component> <phase>] [(def .public <name> - (All (_ anchor expression directive) - (Operation anchor expression directive <phase>)) + (All (_ anchor expression declaration) + (Operation anchor expression declaration <phase>)) (function (_ [bundle state]) {try.#Success [[bundle state] (the [<component> ..#phase] state)]}))] [analysis ..#analysis analysis.Phase] [synthesis ..#synthesis synthesis.Phase] - [generation ..#generation (generation.Phase anchor expression directive)] + [generation ..#generation (generation.Phase anchor expression declaration)] ) (with_template [<name> <component> <operation>] [(def .public <name> - (All (_ anchor expression directive output) + (All (_ anchor expression declaration output) (-> (<operation> output) - (Operation anchor expression directive output))) + (Operation anchor expression declaration output))) (|>> (phase.sub [(the [<component> ..#state]) (has [<component> ..#state])]) extension.lifted))] [lifted_analysis ..#analysis analysis.Operation] [lifted_synthesis ..#synthesis synthesis.Operation] - [lifted_generation ..#generation (generation.Operation anchor expression directive)] + [lifted_generation ..#generation (generation.Operation anchor expression declaration)] ) (def .public (set_current_module module) - (All (_ anchor expression directive) - (-> Module (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> Module (Operation anchor expression declaration Any))) (do phase.monad [_ (..lifted_analysis (analysis.set_current_module module))] 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 67bc8b4c1..b8067a964 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -39,8 +39,8 @@ ["[0]" module (.only) ["[0]" descriptor]]]]]]) -(type .public (Buffer directive) - (Sequence [artifact.ID (Maybe Text) directive])) +(type .public (Buffer declaration) + (Sequence [artifact.ID (Maybe Text) declaration])) (exception .public (cannot_interpret [error Text]) (exception.report @@ -55,28 +55,28 @@ [no_buffer_for_saving_code] ) -(type .public (Host expression directive) +(type .public (Host expression declaration) (Interface (is (-> unit.ID [(Maybe unit.ID) expression] (Try Any)) evaluate) - (is (-> directive (Try Any)) + (is (-> declaration (Try Any)) execute) - (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive])) + (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any declaration])) define) - (is (-> unit.ID Binary directive) + (is (-> unit.ID Binary declaration) ingest) - (is (-> unit.ID (Maybe Text) directive (Try Any)) + (is (-> unit.ID (Maybe Text) declaration (Try Any)) re_learn) - (is (-> unit.ID (Maybe Text) directive (Try Any)) + (is (-> unit.ID (Maybe Text) declaration (Try Any)) re_load))) -(type .public (State anchor expression directive) +(type .public (State anchor expression declaration) (Record [#module descriptor.Module #anchor (Maybe anchor) - #host (Host expression directive) - #buffer (Maybe (Buffer directive)) + #host (Host expression declaration) + #buffer (Maybe (Buffer declaration)) #registry Registry #registry_shift Nat #counter Nat @@ -85,8 +85,8 @@ #interim_artifacts (List artifact.ID)])) (with_template [<special> <general>] - [(type .public (<special> anchor expression directive) - (<general> (State anchor expression directive) Synthesis expression))] + [(type .public (<special> anchor expression declaration) + (<general> (State anchor expression declaration) Synthesis expression))] [State+ extension.State] [Operation extension.Operation] @@ -97,10 +97,10 @@ ) (def .public (state host module) - (All (_ anchor expression directive) - (-> (Host expression directive) + (All (_ anchor expression declaration) + (-> (Host expression declaration) descriptor.Module - (..State anchor expression directive))) + (..State anchor expression declaration))) [#module module #anchor {.#None} #host host @@ -122,7 +122,7 @@ [(exception .public <exception>) (def .public <with_declaration> - (All (_ anchor expression directive output) <with_type>) + (All (_ anchor expression declaration output) <with_type>) (function (_ body) (function (_ [bundle state]) (case (body [bundle (has <tag> {.#Some <with_value>} state)]) @@ -134,8 +134,8 @@ {try.#Failure error})))) (def .public <get> - (All (_ anchor expression directive) - (Operation anchor expression directive <get_type>)) + (All (_ anchor expression declaration) + (Operation anchor expression declaration <get_type>)) (function (_ (^.let stateE [bundle state])) (case (the <tag> state) {.#Some output} @@ -145,66 +145,66 @@ (exception.except <exception> [])))) (def .public (<set> value) - (All (_ anchor expression directive) - (-> <get_type> (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> <get_type> (Operation anchor expression declaration Any))) (function (_ [bundle state]) {try.#Success [[bundle (has <tag> {.#Some value} state)] []]}))] [#anchor (with_anchor anchor) - (-> anchor (Operation anchor expression directive output) - (Operation anchor expression directive output)) + (-> anchor (Operation anchor expression declaration output) + (Operation anchor expression declaration output)) anchor set_anchor anchor anchor no_anchor] [#buffer with_buffer - (-> (Operation anchor expression directive output) - (Operation anchor expression directive output)) + (-> (Operation anchor expression declaration output) + (Operation anchor expression declaration output)) ..empty_buffer - set_buffer buffer (Buffer directive) no_active_buffer] + set_buffer buffer (Buffer declaration) no_active_buffer] ) (def .public get_registry - (All (_ anchor expression directive) - (Operation anchor expression directive Registry)) + (All (_ anchor expression declaration) + (Operation anchor expression declaration Registry)) (function (_ (^.let stateE [bundle state])) {try.#Success [stateE (the #registry state)]})) (def .public (set_registry value) - (All (_ anchor expression directive) - (-> Registry (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> Registry (Operation anchor expression declaration Any))) (function (_ [bundle state]) {try.#Success [[bundle (has #registry value state)] []]})) (def .public next - (All (_ anchor expression directive) - (Operation anchor expression directive Nat)) + (All (_ anchor expression declaration) + (Operation anchor expression declaration Nat)) (do phase.monad [count (extension.read (the #counter)) _ (extension.update (revised #counter ++))] (in count))) (def .public (symbol prefix) - (All (_ anchor expression directive) - (-> Text (Operation anchor expression directive Text))) + (All (_ anchor expression declaration) + (-> Text (Operation anchor expression declaration Text))) (at phase.monad each (|>> %.nat (format prefix)) ..next)) (def .public (enter_module module) - (All (_ anchor expression directive) - (-> descriptor.Module (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> descriptor.Module (Operation anchor expression declaration Any))) (extension.update (has #module module))) (def .public module - (All (_ anchor expression directive) - (Operation anchor expression directive descriptor.Module)) + (All (_ anchor expression declaration) + (Operation anchor expression declaration descriptor.Module)) (extension.read (the #module))) (def .public (evaluate! label code) - (All (_ anchor expression directive) - (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression declaration Any))) (function (_ (^.let state+ [bundle state])) (case (at (the #host state) evaluate label code) {try.#Success output} @@ -214,8 +214,8 @@ (exception.except ..cannot_interpret [error])))) (def .public (execute! code) - (All (_ anchor expression directive) - (-> directive (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> declaration (Operation anchor expression declaration Any))) (function (_ (^.let state+ [bundle state])) (case (at (the #host state) execute code) {try.#Success output} @@ -225,8 +225,8 @@ (exception.except ..cannot_interpret error)))) (def .public (define! context custom code) - (All (_ anchor expression directive) - (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive]))) + (All (_ anchor expression declaration) + (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression declaration [Text Any declaration]))) (function (_ (^.let stateE [bundle state])) (case (at (the #host state) define context custom code) {try.#Success output} @@ -236,8 +236,8 @@ (exception.except ..cannot_interpret error)))) (def .public (save! artifact_id custom code) - (All (_ anchor expression directive) - (-> artifact.ID (Maybe Text) directive (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> artifact.ID (Maybe Text) declaration (Operation anchor expression declaration Any))) (do [! phase.monad] [?buffer (extension.read (the #buffer))] (case ?buffer @@ -252,8 +252,8 @@ (with_template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>] [(`` (def .public (<name> it (~~ (template.spliced <inputs>)) dependencies) - (All (_ anchor expression directive) - (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID))) + (All (_ anchor expression declaration) + (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression declaration artifact.ID))) (function (_ (^.let stateE [bundle state])) (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))] {try.#Success [[bundle (has #registry registry' state)] @@ -264,7 +264,7 @@ [Text #0 [] [] learn_analyser registry.analyser] [Text #0 [] [] learn_synthesizer registry.synthesizer] [Text #0 [] [] learn_generator registry.generator] - [Text #0 [] [] learn_directive registry.directive] + [Text #0 [] [] learn_declaration registry.declaration] ) (exception .public (unknown_definition [name Symbol @@ -275,8 +275,8 @@ "Known Definitions" (exception.listing product.left known_definitions))) (def .public (remember archive name) - (All (_ anchor expression directive) - (-> Archive Symbol (Operation anchor expression directive unit.ID))) + (All (_ anchor expression declaration) + (-> Archive Symbol (Operation anchor expression declaration unit.ID))) (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad @@ -294,8 +294,8 @@ {try.#Success [stateE [@module id]]}))))) (def .public (definition archive name) - (All (_ anchor expression directive) - (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)]))) + (All (_ anchor expression declaration) + (-> Archive Symbol (Operation anchor expression declaration [unit.ID (Maybe category.Definition)]))) (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad @@ -315,16 +315,16 @@ (exception .public no_context) (def .public (module_id module archive) - (All (_ anchor expression directive) - (-> descriptor.Module Archive (Operation anchor expression directive module.ID))) + (All (_ anchor expression declaration) + (-> descriptor.Module Archive (Operation anchor expression declaration module.ID))) (function (_ (^.let stateE [bundle state])) (do try.monad [@module (archive.id module archive)] (in [stateE @module])))) (def .public (context archive) - (All (_ anchor expression directive) - (-> Archive (Operation anchor expression directive unit.ID))) + (All (_ anchor expression declaration) + (-> Archive (Operation anchor expression declaration unit.ID))) (function (_ (^.let stateE [bundle state])) (case (the #context state) {.#None} @@ -336,10 +336,10 @@ (in [stateE [@module id]]))))) (def .public (with_context @artifact body) - (All (_ anchor expression directive a) + (All (_ anchor expression declaration a) (-> artifact.ID - (Operation anchor expression directive a) - (Operation anchor expression directive a))) + (Operation anchor expression declaration a) + (Operation anchor expression declaration a))) (function (_ [bundle state]) (do try.monad [[[bundle' state'] output] (body [bundle (has #context {.#Some @artifact} state)])] @@ -347,10 +347,10 @@ output])))) (def .public (with_registry_shift shift body) - (All (_ anchor expression directive a) + (All (_ anchor expression declaration a) (-> Nat - (Operation anchor expression directive a) - (Operation anchor expression directive a))) + (Operation anchor expression declaration a) + (Operation anchor expression declaration a))) (function (_ [bundle state]) (do try.monad [[[bundle' state'] output] (body [bundle (has #registry_shift shift state)])] @@ -358,9 +358,9 @@ output])))) (def .public (with_new_context archive dependencies body) - (All (_ anchor expression directive a) - (-> Archive (Set unit.ID) (Operation anchor expression directive a) - (Operation anchor expression directive [unit.ID a]))) + (All (_ anchor expression declaration a) + (-> Archive (Set unit.ID) (Operation anchor expression declaration a) + (Operation anchor expression declaration [unit.ID a]))) (function (_ (^.let stateE [bundle state])) (let [[@artifact registry'] (registry.resource false dependencies (the #registry state)) @artifact (n.+ @artifact (the #registry_shift state))] @@ -375,17 +375,17 @@ output]]))))) (def .public (log! message) - (All (_ anchor expression directive a) - (-> Text (Operation anchor expression directive Any))) + (All (_ anchor expression declaration a) + (-> Text (Operation anchor expression declaration Any))) (function (_ [bundle state]) {try.#Success [[bundle (revised #log (sequence.suffix message) state)] []]})) (def .public (with_interim_artifacts archive body) - (All (_ anchor expression directive a) - (-> Archive (Operation anchor expression directive a) - (Operation anchor expression directive [(List unit.ID) a]))) + (All (_ anchor expression declaration a) + (-> Archive (Operation anchor expression declaration a) + (Operation anchor expression declaration [(List unit.ID) a]))) (do phase.monad [module (extension.read (the #module))] (function (_ state+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/declaration.lux index cffe0d681..806308519 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/declaration.lux @@ -16,7 +16,7 @@ ["[1][0]" extension] ["[1][0]" analysis] ["/[1]" // - ["/" directive (.only Operation Phase)] + ["/" declaration (.only Operation Phase)] ["[1][0]" analysis (.only) ["[0]" evaluation] ["[1]/[0]" macro (.only Expander)] @@ -28,9 +28,9 @@ [meta [archive (.only Archive)]]]]]) -(exception .public (not_a_directive [code Code]) +(exception .public (not_a_declaration [code Code]) (exception.report - "Directive" (%.code code))) + "Declaration" (%.code code))) (exception .public (invalid_macro_call [code Code]) (exception.report @@ -55,9 +55,9 @@ {try.#Failure error}))) (def (requiring phase archive expansion) - (All (_ anchor expression directive) - (-> (Phase anchor expression directive) Archive (List Code) - (Operation anchor expression directive /.Requirements))) + (All (_ anchor expression declaration) + (-> (Phase anchor expression declaration) Archive (List Code) + (Operation anchor expression declaration /.Requirements))) (function (_ state) (loop (again [state state input expansion @@ -122,4 +122,4 @@ (..requiring again archive expansion))) _ - (//.except ..not_a_directive code))))))) + (//.except ..not_a_declaration code))))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 4696b3104..eb523d7e0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Type Module Primitive char int) + [lux (.except Type Module Primitive char int type) ["[0]" ffi (.only import)] ["[0]" meta] [abstract @@ -70,7 +70,7 @@ ["[1]" abstract]]]] ["/[1]" // ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] ["[1][0]" analysis (.only Analysis Operation Phase Handler Bundle) ["[0]" complex] ["[0]" pattern] @@ -226,7 +226,7 @@ [char (reflection.reflection reflection.char)] ) -(type Member +(.type Member (Record [#class External #member Text])) @@ -235,7 +235,7 @@ (Parser Member) (all <>.and <code>.text <code>.text)) -(type Method_Signature +(.type Method_Signature (Record [#method .Type #deprecated? Bit @@ -1150,7 +1150,7 @@ valueA objectA)))))])) -(type Method_Style +(.type Method_Style (Variant {#Static} {#Abstract} @@ -1357,7 +1357,7 @@ concrete_exceptions generic_exceptions)])))) -(type Evaluation +(.type Evaluation (Variant {#Pass Method_Signature} {#Hint Method_Signature})) @@ -1650,14 +1650,14 @@ ))) ))) -(type .public (Annotation_Parameter a) +(.type .public (Annotation_Parameter a) [Text a]) (def annotation_parameter (Parser (Annotation_Parameter Code)) (<code>.tuple (<>.and <code>.text <code>.any))) -(type .public (Annotation a) +(.type .public (Annotation a) [Text (List (Annotation_Parameter a))]) (def .public annotation @@ -1767,15 +1767,15 @@ [invalid_overriden_methods] ) -(type .public Visibility +(.type .public Visibility (Variant {#Public} {#Private} {#Protected} {#Default})) -(type .public Finality Bit) -(type .public Strictness Bit) +(.type .public Finality Bit) +(.type .public Strictness Bit) (def .public public_tag "public") (def .public private_tag "private") @@ -1803,7 +1803,7 @@ {#Protected} ..protected_tag {#Default} ..default_tag))) -(type Exception +(.type Exception (Type Class)) (def .public parameter_types @@ -1814,7 +1814,7 @@ [[_ parameterT] check.existential] (in [parameterJ parameterT]))))) -(type .public (Abstract_Method a) +(.type .public (Abstract_Method a) [Text Visibility (List (Annotation a)) @@ -1874,7 +1874,7 @@ (/////analysis.tuple (list#each class_analysis exceptions)) )))))) -(type .public (Constructor a) +(.type .public (Constructor a) [Visibility Strictness (List (Annotation a)) @@ -1952,7 +1952,7 @@ (/////analysis.tuple (list bodyA))} )))))) -(type .public (Virtual_Method a) +(.type .public (Virtual_Method a) [Text Visibility Finality @@ -1984,7 +1984,7 @@ (<code>.tuple (<>.some ..class)) <code>.any))) -(type .public (Method_Declaration a) +(.type .public (Method_Declaration a) (Record [#name Text #annotations (List (Annotation a)) @@ -2052,7 +2052,7 @@ (/////analysis.tuple (list bodyA))} )))))) -(type .public (Static_Method a) +(.type .public (Static_Method a) [Text Visibility Strictness @@ -2125,7 +2125,7 @@ (/////analysis.tuple (list bodyA))} )))))) -(type .public (Overriden_Method a) +(.type .public (Overriden_Method a) [(Type Class) Text Bit @@ -2436,21 +2436,21 @@ (list.empty? invalid_overriden_methods))] (in []))) -(type Declaration +(.type Declaration [Text (List (Type Var))]) -(type Constant +(.type Constant [Text (List Annotation) (Type Value) Code]) -(type Variable +(.type Variable [Text (Modifier field.Field) (Modifier field.Field) (List Annotation) (Type Value)]) -(type Field +(.type Field (Variant {#Constant Constant} {#Variable Variable})) -(type (Method_Definition a) +(.type (Method_Definition a) (Variant {#Constructor (..Constructor a)} {#Virtual_Method (..Virtual_Method a)} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux index 39104d42d..9fdfb4d7c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/jvm.lux @@ -65,7 +65,7 @@ [language [lux ["[0]" generation] - ["[0]" directive (.only Handler Bundle)] + ["[0]" declaration (.only Handler Bundle)] ["[0]" analysis (.only Analysis) ["[0]A" type] ["[0]A" scope]] @@ -83,13 +83,13 @@ [generation [jvm ["[0]" host]]] - [directive + [declaration ["/" lux]]]]]]]] [type ["[0]" check (.only Check)]]]]) (type Operation - (directive.Operation Anchor (Bytecode Any) Definition)) + (declaration.Operation Anchor (Bytecode Any) Definition)) (def signature (|>> type.signature signature.signature)) (def reflection (|>> type.reflection reflection.reflection)) @@ -461,8 +461,8 @@ self arguments constructor_argumentsS bodyS] method]) (do [! phase.monad] - [generate directive.generation]) - directive.lifted_generation + [generate declaration.generation]) + declaration.lifted_generation (do ! [constructor_argumentsG (monad.each ! (|>> product.right (generate archive)) constructor_argumentsS) @@ -537,8 +537,8 @@ bodyS (case (list.size arguments) 0 (host.without_fake_parameter bodyS) _ bodyS)] - generate directive.generation] - (directive.lifted_generation + generate declaration.generation] + (declaration.lifted_generation (do ! [bodyG (generate archive bodyS) .let [argumentsT (list#each product.right arguments)]] @@ -561,8 +561,8 @@ [.let [[method_name privacy final? strict_floating_point? annotations method_tvars self arguments returnJ exceptionsJ bodyS] method] - generate directive.generation] - (directive.lifted_generation + generate declaration.generation] + (declaration.lifted_generation (do ! [bodyG (generate archive bodyS) .let [argumentsT (list#each product.right arguments)]] @@ -588,8 +588,8 @@ [.let [[method_name privacy strict_floating_point? annotations method_tvars arguments returnJ exceptionsJ bodyS] method] - generate directive.generation] - (directive.lifted_generation + generate declaration.generation] + (declaration.lifted_generation (do ! [bodyG (generate archive bodyS) .let [argumentsT (list#each product.right arguments)]] @@ -649,7 +649,7 @@ (function (_ methodC) (do phase.monad [methodA (is (Operation Analysis) - (directive.lifted_analysis + (declaration.lifted_analysis (case methodC {#Constructor method} (jvm.analyse_constructor_method analyse archive selfT mapping method) @@ -666,9 +666,9 @@ {#Abstract_Method method} (jvm.analyse_abstract_method analyse archive method)))) methodS (is (Operation Synthesis) - (directive.lifted_synthesis + (declaration.lifted_synthesis (synthesize archive methodA))) - dependencies (directive.lifted_generation + dependencies (declaration.lifted_generation (cache.dependencies archive methodS)) methodS' (|> methodS list @@ -846,7 +846,7 @@ (def (save_class! name bytecode dependencies) (-> Text Binary (Set unit.ID) (Operation Any)) - (directive.lifted_generation + (declaration.lifted_generation (do [! phase.monad] [.let [artifact [name bytecode]] artifact_id (generation.learn_custom name dependencies) @@ -888,9 +888,9 @@ fields methods)) ... Necessary for reflection to work properly during analysis. - _ (directive.lifted_generation + _ (declaration.lifted_generation (generation.execute! mock)) - parameters (directive.lifted_analysis + parameters (declaration.lifted_analysis (typeA.check (jvm.parameter_types parameters))) .let [mapping (list#mix (function (_ [parameterJ parameterT] mapping) (dictionary.has (parser.name parameterJ) parameterT mapping)) @@ -899,9 +899,9 @@ selfT {.#Primitive name (list#each product.right parameters)}] state (extension.lifted phase.state) methods (monad.each ! (..method_definition archive super interfaces [mapping selfT] - [(the [directive.#analysis directive.#phase] state) - (the [directive.#synthesis directive.#phase] state) - (the [directive.#generation directive.#phase] state)]) + [(the [declaration.#analysis declaration.#phase] state) + (the [declaration.#synthesis declaration.#phase] state) + (the [declaration.#generation declaration.#phase] state)]) methods) .let [all_dependencies (cache.all (list#each product.left methods))] bytecode (<| (at ! each (\\format.result class.format)) @@ -918,7 +918,7 @@ (list#each product.right methods) sequence.empty)) _ (..save_class! name bytecode all_dependencies)] - (in directive.no_requirements)))])) + (in declaration.no_requirements)))])) (def (method_declaration (open "/[0]")) (-> (jvm.Method_Declaration Code) (Resource Method)) @@ -941,7 +941,7 @@ (<code>.tuple (<>.some ..annotation)) (<>.some jvm.method_declaration)) (function (_ extension_name phase archive [[name parameters] supers annotations method_declarations]) - (directive.lifted_generation + (declaration.lifted_generation (do [! phase.monad] [bytecode (<| (at ! each (\\format.result class.format)) phase.lifted @@ -964,7 +964,7 @@ _ (generation.execute! artifact) _ (generation.save! artifact_id {.#Some name} artifact) _ (generation.log! (format "JVM Interface " (%.text name)))] - (in directive.no_requirements))))])) + (in declaration.no_requirements))))])) (import java/lang/ClassLoader "[1]::[0]") diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux index 0d02b109f..d2d4592e6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux @@ -43,7 +43,7 @@ ["[0]" scope]] ["[1][0]" synthesis (.only Synthesis)] ["[1][0]" generation] - ["[1][0]" directive (.only Import Requirements Phase Operation Handler Bundle)] + ["[1][0]" declaration (.only Import Requirements Phase Operation Handler Bundle)] ["[1][0]" program (.only Program)] [/// ["[0]" phase] @@ -57,14 +57,14 @@ ["[1]/[0]" artifact]]]]]]]]) (def .public (custom [syntax handler]) - (All (_ anchor expression directive s) + (All (_ anchor expression declaration s) (-> [(Parser s) (-> Text - (Phase anchor expression directive) + (Phase anchor expression declaration) Archive s - (Operation anchor expression directive Requirements))] - (Handler anchor expression directive))) + (Operation anchor expression declaration Requirements))] + (Handler anchor expression declaration))) (function (_ extension_name phase archive inputs) (case (<code>.result syntax inputs) {try.#Success inputs} @@ -80,13 +80,13 @@ ... TODO: Inline "evaluate!'" into "evaluate!" ASAP (def (evaluate!' archive generate code//type codeS) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Archive - (/////generation.Phase anchor expression directive) + (/////generation.Phase anchor expression declaration) Type Synthesis - (Operation anchor expression directive [Type expression Any]))) - (/////directive.lifted_generation + (Operation anchor expression declaration [Type expression Any]))) + (/////declaration.lifted_generation (do phase.monad [module /////generation.module id /////generation.next @@ -96,32 +96,32 @@ (in [code//type codeG codeV])))) (def .public (evaluate! archive type codeC) - (All (_ anchor expression directive) - (-> Archive Type Code (Operation anchor expression directive [Type expression Any]))) + (All (_ anchor expression declaration) + (-> Archive Type Code (Operation anchor expression declaration [Type expression Any]))) (do phase.monad [state (///.lifted phase.state) - .let [analyse (the [/////directive.#analysis /////directive.#phase] state) - synthesize (the [/////directive.#synthesis /////directive.#phase] state) - generate (the [/////directive.#generation /////directive.#phase] state)] - [_ codeA] (<| /////directive.lifted_analysis + .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) + synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) + generate (the [/////declaration.#generation /////declaration.#phase] state)] + [_ codeA] (<| /////declaration.lifted_analysis scope.with typeA.fresh (typeA.expecting type) (analyse archive codeC)) - codeS (/////directive.lifted_synthesis + codeS (/////declaration.lifted_synthesis (synthesize archive codeA))] (evaluate!' archive generate type codeS))) ... TODO: Inline "definition'" into "definition" ASAP (def (definition' archive generate [module name] code//type codeS) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Archive - (/////generation.Phase anchor expression directive) + (/////generation.Phase anchor expression declaration) Symbol Type Synthesis - (Operation anchor expression directive [Type expression Any]))) - (/////directive.lifted_generation + (Operation anchor expression declaration [Type expression Any]))) + (/////declaration.lifted_generation (do phase.monad [dependencies (cache/artifact.dependencies archive codeS) [interim_artifacts codeG] (/////generation.with_interim_artifacts archive @@ -136,20 +136,20 @@ {.#None})] @module (phase.lifted (archive.id module archive)) @self (/////generation.learn [name @abstraction] false (list#mix set.has dependencies interim_artifacts)) - [target_name value directive] (/////generation.define! [@module @self] {.#None} [(maybe#each product.right @abstraction) codeG]) - _ (/////generation.save! @self {.#None} directive)] + [target_name value declaration] (/////generation.define! [@module @self] {.#None} [(maybe#each product.right @abstraction) codeG]) + _ (/////generation.save! @self {.#None} declaration)] (in [code//type codeG value])))) (def (definition archive name expected codeC) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Archive Symbol (Maybe Type) Code - (Operation anchor expression directive [Type expression Any]))) + (Operation anchor expression declaration [Type expression Any]))) (do [! phase.monad] [state (///.lifted phase.state) - .let [analyse (the [/////directive.#analysis /////directive.#phase] state) - synthesize (the [/////directive.#synthesis /////directive.#phase] state) - generate (the [/////directive.#generation /////directive.#phase] state)] - [_ code//type codeA] (/////directive.lifted_analysis + .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) + synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) + generate (the [/////declaration.#generation /////declaration.#phase] state)] + [_ code//type codeA] (/////declaration.lifted_analysis (scope.with (typeA.fresh (case expected @@ -165,71 +165,71 @@ [codeA (<| (typeA.expecting expected) (analyse archive codeC))] (in [expected codeA])))))) - codeS (/////directive.lifted_synthesis + codeS (/////declaration.lifted_synthesis (synthesize archive codeA))] (definition' archive generate name code//type codeS))) (with_template [<full> <partial> <learn>] [... TODO: Inline "<partial>" into "<full>" ASAP (def (<partial> archive generate extension codeT codeS) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Archive - (/////generation.Phase anchor expression directive) + (/////generation.Phase anchor expression declaration) Text Type Synthesis - (Operation anchor expression directive [expression Any]))) + (Operation anchor expression declaration [expression Any]))) (do phase.monad - [current_module (/////directive.lifted_analysis + [current_module (/////declaration.lifted_analysis (///.lifted meta.current_module_name))] - (/////directive.lifted_generation + (/////declaration.lifted_generation (do phase.monad [dependencies (cache/artifact.dependencies archive codeS) [interim_artifacts codeG] (/////generation.with_interim_artifacts archive (generate archive codeS)) @module (phase.lifted (archive.id current_module archive)) @self (<learn> extension (list#mix set.has dependencies interim_artifacts)) - [target_name value directive] (/////generation.define! [@module @self] {.#None} [{.#None} codeG]) - _ (/////generation.save! @self {.#None} directive)] + [target_name value declaration] (/////generation.define! [@module @self] {.#None} [{.#None} codeG]) + _ (/////generation.save! @self {.#None} declaration)] (in [codeG value]))))) (def .public (<full> archive extension codeT codeC) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Archive Text Type Code - (Operation anchor expression directive [expression Any]))) + (Operation anchor expression declaration [expression Any]))) (do phase.monad [state (///.lifted phase.state) - .let [analyse (the [/////directive.#analysis /////directive.#phase] state) - synthesize (the [/////directive.#synthesis /////directive.#phase] state) - generate (the [/////directive.#generation /////directive.#phase] state)] - [_ codeA] (<| /////directive.lifted_analysis + .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) + synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) + generate (the [/////declaration.#generation /////declaration.#phase] state)] + [_ codeA] (<| /////declaration.lifted_analysis scope.with typeA.fresh (typeA.expecting codeT) (analyse archive codeC)) - codeS (/////directive.lifted_synthesis + codeS (/////declaration.lifted_synthesis (synthesize archive codeA))] (<partial> archive generate extension codeT codeS)))] [analyser analyser' /////generation.learn_analyser] [synthesizer synthesizer' /////generation.learn_synthesizer] [generator generator' /////generation.learn_generator] - [directive directive' /////generation.learn_directive] + [declaration declaration' /////generation.learn_declaration] ) ... TODO: Get rid of this function ASAP. (def (refresh expander host_analysis) - (All (_ anchor expression directive) - (-> Expander /////analysis.Bundle (Operation anchor expression directive Any))) + (All (_ anchor expression declaration) + (-> Expander /////analysis.Bundle (Operation anchor expression declaration Any))) (do phase.monad [[bundle state] phase.state .let [eval (/////analysis/evaluation.evaluator expander - (the [/////directive.#synthesis /////directive.#state] state) - (the [/////directive.#generation /////directive.#state] state) - (the [/////directive.#generation /////directive.#phase] state)) - previous_analysis_extensions (the [/////directive.#analysis /////directive.#state ///.#bundle] state)]] + (the [/////declaration.#synthesis /////declaration.#state] state) + (the [/////declaration.#generation /////declaration.#state] state) + (the [/////declaration.#generation /////declaration.#phase] state)) + previous_analysis_extensions (the [/////declaration.#analysis /////declaration.#state ///.#bundle] state)]] (phase.with [bundle - (revised [/////directive.#analysis /////directive.#state] + (revised [/////declaration.#analysis /////declaration.#state] (is (-> /////analysis.State+ /////analysis.State+) (|>> product.right [(|> previous_analysis_extensions @@ -237,9 +237,9 @@ state)]))) (def (announce_definition! short type) - (All (_ anchor expression directive) - (-> Text Type (Operation anchor expression directive Any))) - (/////directive.lifted_generation + (All (_ anchor expression declaration) + (-> Text Type (Operation anchor expression declaration Any))) + (/////declaration.lifted_generation (/////generation.log! (format short " : " (%.type type))))) (def (lux::def expander host_analysis) @@ -248,24 +248,24 @@ (case inputsC+ (pattern (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) (do phase.monad - [current_module (/////directive.lifted_analysis + [current_module (/////declaration.lifted_analysis (///.lifted meta.current_module_name)) .let [full_name [current_module short_name]] [type valueT value] (..definition archive full_name {.#None} valueC) [_ _ exported?] (evaluate! archive Bit exported?C) - _ (/////directive.lifted_analysis + _ (/////declaration.lifted_analysis (moduleA.define short_name {.#Definition [(as Bit exported?) type value]})) _ (..refresh expander host_analysis) _ (..announce_definition! short_name type)] - (in /////directive.no_requirements)) + (in /////declaration.no_requirements)) _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+])))) (def (announce_labels! labels owner) - (All (_ anchor expression directive) - (-> (List Text) Type (Operation anchor expression directive (List Any)))) - (/////directive.lifted_generation + (All (_ anchor expression declaration) + (-> (List Text) Type (Operation anchor expression declaration (List Any)))) + (/////declaration.lifted_generation (monad.each phase.monad (function (_ tag) (/////generation.log! (format tag " : Tag of " (%.type owner)))) @@ -280,13 +280,13 @@ <code>.any) (function (_ extension_name phase archive [short_name valueC labels exported?C]) (do phase.monad - [current_module (/////directive.lifted_analysis + [current_module (/////declaration.lifted_analysis (///.lifted meta.current_module_name)) .let [full_name [current_module short_name]] [_ _ exported?] (evaluate! archive Bit exported?C) .let [exported? (as Bit exported?)] [type valueT value] (..definition archive full_name {.#Some .Type} valueC) - labels (/////directive.lifted_analysis + labels (/////declaration.lifted_analysis (do phase.monad [.let [[record? labels] (case labels {.#Left tags} @@ -307,7 +307,7 @@ _ (..refresh expander host_analysis) _ (..announce_definition! short_name type) _ (..announce_labels! labels (as Type value))] - (in /////directive.no_requirements)))])) + (in /////declaration.no_requirements)))])) (def imports (Parser (List Import)) @@ -321,7 +321,7 @@ [..imports (function (_ extension_name phase archive imports) (do [! phase.monad] - [_ (/////directive.lifted_analysis + [_ (/////declaration.lifted_analysis (monad.each ! (function (_ [module alias]) (do ! [_ (moduleA.import module)] @@ -329,8 +329,8 @@ "" (in []) _ (moduleA.alias alias module)))) imports))] - (in [/////directive.#imports imports - /////directive.#referrals (list)])))])) + (in [/////declaration.#imports imports + /////declaration.#referrals (list)])))])) (exception .public (cannot_alias_an_alias [local Alias foreign Alias @@ -370,10 +370,10 @@ (function (_ extension_name phase archive [alias def_name]) (do phase.monad [_ (///.lifted - (phase.sub [(the [/////directive.#analysis /////directive.#state]) - (has [/////directive.#analysis /////directive.#state])] + (phase.sub [(the [/////declaration.#analysis /////declaration.#state]) + (has [/////declaration.#analysis /////declaration.#state])] (define_alias alias def_name)))] - (in /////directive.no_requirements)))])) + (in /////declaration.no_requirements)))])) ... TODO: Stop requiring these types and the "swapped" function below to make types line-up. (with_template [<name> <anonymous>] @@ -420,15 +420,15 @@ {.#Named name (again anonymous)})))) (with_template [<description> <mame> <def_type> <type> <scope> <definer>] - [(def (<mame> [anchorT expressionT directiveT] extender) - (All (_ anchor expression directive) + [(def (<mame> [anchorT expressionT declarationT] extender) + (All (_ anchor expression declaration) (-> [Type Type Type] Extender - (Handler anchor expression directive))) + (Handler anchor expression declaration))) (function (handler extension_name phase archive inputsC+) (case inputsC+ (pattern (list nameC valueC)) (do phase.monad - [target_platform (/////directive.lifted_analysis + [target_platform (/////declaration.lifted_analysis (///.lifted meta.target)) [_ _ name] (evaluate! archive Text nameC) [_ handlerV] (<definer> archive (as Text name) @@ -446,14 +446,14 @@ valueC) _ (<| <scope> (///.install extender (as Text name)) - (sharing [anchor expression directive] - (is (Handler anchor expression directive) + (sharing [anchor expression declaration] + (is (Handler anchor expression declaration) handler) (is <type> (as_expected handlerV)))) - _ (/////directive.lifted_generation + _ (/////declaration.lifted_generation (/////generation.log! (format <description> " " (%.text (as Text name)))))] - (in /////directive.no_requirements)) + (in /////declaration.no_requirements)) _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+]))))] @@ -461,52 +461,52 @@ ["Analysis" defanalysis /////analysis.Handler /////analysis.Handler - /////directive.lifted_analysis + /////declaration.lifted_analysis ..analyser] ["Synthesis" defsynthesis /////synthesis.Handler /////synthesis.Handler - /////directive.lifted_synthesis + /////declaration.lifted_synthesis ..synthesizer] ["Generation" defgeneration - (/////generation.Handler anchorT expressionT directiveT) (/////generation.Handler anchor expression directive) - /////directive.lifted_generation + (/////generation.Handler anchorT expressionT declarationT) (/////generation.Handler anchor expression declaration) + /////declaration.lifted_generation ..generator] - ["Directive" - defdirective - (/////directive.Handler anchorT expressionT directiveT) (/////directive.Handler anchor expression directive) + ["Declaration" + defdeclaration + (/////declaration.Handler anchorT expressionT declarationT) (/////declaration.Handler anchor expression declaration) (<|) - ..directive] + ..declaration] ) ... TODO; Both "prepare-program" and "define-program" exist only ... because the old compiler couldn't handle a fully-inlined definition ... for "defprogram". Inline them ASAP. (def (prepare_program archive analyse synthesize programC) - (All (_ anchor expression directive output) + (All (_ anchor expression declaration output) (-> Archive /////analysis.Phase /////synthesis.Phase Code - (Operation anchor expression directive Synthesis))) + (Operation anchor expression declaration Synthesis))) (do phase.monad - [[_ programA] (<| /////directive.lifted_analysis + [[_ programA] (<| /////declaration.lifted_analysis scope.with typeA.fresh (typeA.expecting (type_literal (-> (List Text) (IO Any)))) (analyse archive programC))] - (/////directive.lifted_synthesis + (/////declaration.lifted_synthesis (synthesize archive programA)))) (def (define_program archive @module generate program programS) - (All (_ anchor expression directive output) + (All (_ anchor expression declaration output) (-> Archive module.ID - (/////generation.Phase anchor expression directive) - (Program expression directive) + (/////generation.Phase anchor expression declaration) + (Program expression declaration) Synthesis - (/////generation.Operation anchor expression directive Any))) + (/////generation.Operation anchor expression declaration Any))) (do phase.monad [dependencies (cache/artifact.dependencies archive programS) [interim_artifacts programG] (/////generation.with_interim_artifacts archive @@ -515,56 +515,56 @@ (/////generation.save! @self {.#None} (program [@module @self] programG)))) (def (defprogram program) - (All (_ anchor expression directive) - (-> (Program expression directive) (Handler anchor expression directive))) + (All (_ anchor expression declaration) + (-> (Program expression declaration) (Handler anchor expression declaration))) (function (handler extension_name phase archive inputsC+) (case inputsC+ (pattern (list programC)) (do phase.monad [state (///.lifted phase.state) - .let [analyse (the [/////directive.#analysis /////directive.#phase] state) - synthesize (the [/////directive.#synthesis /////directive.#phase] state) - generate (the [/////directive.#generation /////directive.#phase] state)] + .let [analyse (the [/////declaration.#analysis /////declaration.#phase] state) + synthesize (the [/////declaration.#synthesis /////declaration.#phase] state) + generate (the [/////declaration.#generation /////declaration.#phase] state)] programS (prepare_program archive analyse synthesize programC) - current_module (/////directive.lifted_analysis + current_module (/////declaration.lifted_analysis (///.lifted meta.current_module_name)) @module (phase.lifted (archive.id current_module archive)) - _ (/////directive.lifted_generation + _ (/////declaration.lifted_generation (define_program archive @module generate program programS))] - (in /////directive.no_requirements)) + (in /////declaration.no_requirements)) _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+])))) -(def (bundle::def expander host_analysis program anchorT,expressionT,directiveT extender) - (All (_ anchor expression directive) +(def (bundle::def expander host_analysis program anchorT,expressionT,declarationT extender) + (All (_ anchor expression declaration) (-> Expander /////analysis.Bundle - (Program expression directive) + (Program expression declaration) [Type Type Type] Extender - (Bundle anchor expression directive))) + (Bundle anchor expression declaration))) (<| (///bundle.prefix "def") (|> ///bundle.empty (dictionary.has "module" defmodule) (dictionary.has "alias" defalias) (dictionary.has "type tagged" (deftype_tagged expander host_analysis)) - (dictionary.has "analysis" (defanalysis anchorT,expressionT,directiveT extender)) - (dictionary.has "synthesis" (defsynthesis anchorT,expressionT,directiveT extender)) - (dictionary.has "generation" (defgeneration anchorT,expressionT,directiveT extender)) - (dictionary.has "directive" (defdirective anchorT,expressionT,directiveT extender)) + (dictionary.has "analysis" (defanalysis anchorT,expressionT,declarationT extender)) + (dictionary.has "synthesis" (defsynthesis anchorT,expressionT,declarationT extender)) + (dictionary.has "generation" (defgeneration anchorT,expressionT,declarationT extender)) + (dictionary.has "declaration" (defdeclaration anchorT,expressionT,declarationT extender)) (dictionary.has "program" (defprogram program)) ))) -(def .public (bundle expander host_analysis program anchorT,expressionT,directiveT extender) - (All (_ anchor expression directive) +(def .public (bundle expander host_analysis program anchorT,expressionT,declarationT extender) + (All (_ anchor expression declaration) (-> Expander /////analysis.Bundle - (Program expression directive) + (Program expression declaration) [Type Type Type] Extender - (Bundle anchor expression directive))) + (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,directiveT extender))))) + (dictionary.composite (..bundle::def expander host_analysis program anchorT,expressionT,declarationT extender))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index d908ed1a3..073eac767 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -89,13 +89,13 @@ (set.of_list _.hash) set.list) @expression (_.constant (reference.artifact [context_module context_artifact])) - directive (_.define_function @expression (list.partial (_.parameter @input) (list#each _.reference foreigns)) - (list#mix (function (_ [test then] else) - (_.if test (_.return then) else)) - (_.return elseG) - conditionalsG))] - _ (generation.execute! directive) - _ (generation.save! context_artifact directive)] + declaration (_.define_function @expression (list.partial (_.parameter @input) (list#each _.reference foreigns)) + (list#mix (function (_ [test then] else) + (_.if test (_.return then) else)) + (_.return elseG) + conditionalsG))] + _ (generation.execute! declaration) + _ (generation.save! context_artifact declaration)] (in (_.apply (list.partial inputG foreigns) @expression))))])) (def lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 75cb5a86e..501587da2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -31,12 +31,12 @@ (def arity (syntax (_ [arity <code>.nat]) - (with_symbols [g!_ g!extension g!name g!phase g!archive g!inputs g!anchor g!expression g!directive] + (with_symbols [g!_ g!extension g!name g!phase g!archive g!inputs g!anchor g!expression g!declaration] (do [! meta.monad] [g!input+ (monad.all ! (list.repeated arity (macro.symbol "input")))] - (in (list (` (is (All ((~ g!_) (~ g!anchor) (~ g!expression) (~ g!directive)) + (in (list (` (is (All ((~ g!_) (~ g!anchor) (~ g!expression) (~ g!declaration)) (-> ((Arity (~ (code.nat arity))) (~ g!expression)) - (generation.Handler (~ g!anchor) (~ g!expression) (~ g!directive)))) + (generation.Handler (~ g!anchor) (~ g!expression) (~ g!declaration)))) (function ((~ g!_) (~ g!extension)) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!archive) (~ g!inputs)) (case (~ g!inputs) @@ -68,8 +68,8 @@ (-> (List of) of)) (def .public (variadic extension) - (All (_ anchor expression directive) - (-> (Variadic expression) (generation.Handler anchor expression directive))) + (All (_ anchor expression declaration) + (-> (Variadic expression) (generation.Handler anchor expression declaration))) (function (_ extension_name) (function (_ phase archive inputsS) (let [! ///.monad] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux index 81c42a003..86965220b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/implementation.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Type Label) + [lux (.except Type Label type) [data [collection ["[0]" list]]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index d8ba5543d..d60aad8a3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Type) + [lux (.except Type type) [abstract ["[0]" monad]] [control diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux index f592a3aba..faff66f47 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/reset.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Type) + [lux (.except Type type) [data [collection ["[0]" list (.use "[1]#[0]" functor)]]] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index 9e33db858..c8d769e87 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -183,7 +183,7 @@ (def (re_learn context custom [_ bytecode]) (io.run! (loader.store (maybe.else (//runtime.class_name context) custom) bytecode library))) - (def (re_load context custom [directive_name bytecode]) + (def (re_load context custom [declaration_name bytecode]) (io.run! (do (try.with io.monad) [.let [class_name (maybe.else (//runtime.class_name context) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index 53ab302e9..5c44eb15b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -91,28 +91,28 @@ locals (|> initsO+ list.enumeration (list#each (|>> product.left (n.+ start) //case.register))) - [directive instantiation] (is [Statement Expression] - (case (|> (synthesis.path/then bodyS) - //case.dependencies - (set.of_list _.hash) - (set.difference (set.of_list _.hash locals)) - set.list) - {.#End} - [(_.function @loop locals - scope!) - @loop] + [declaration instantiation] (is [Statement Expression] + (case (|> (synthesis.path/then bodyS) + //case.dependencies + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) + set.list) + {.#End} + [(_.function @loop locals + scope!) + @loop] - foreigns - (let [@context (_.var (format (_.code @loop) "_context"))] - [(_.function @context foreigns - (all _.then - (<| (_.local_function @loop locals) - scope!) - (_.return @loop) - )) - (_.apply foreigns @context)])))] - _ (/////generation.execute! directive) - _ (/////generation.save! artifact_id {.#None} directive)] + foreigns + (let [@context (_.var (format (_.code @loop) "_context"))] + [(_.function @context foreigns + (all _.then + (<| (_.local_function @loop locals) + scope!) + (_.return @loop) + )) + (_.apply foreigns @context)])))] + _ (/////generation.execute! declaration) + _ (/////generation.save! artifact_id {.#None} declaration)] (in (_.apply initsO+ instantiation))))) (def .public (again! statement expression archive argsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 8fdaeabc9..2b015ee7f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -290,7 +290,7 @@ .let [@case (_.constant (///reference.artifact [case_module case_artifact])) @dependencies+ (..dependencies (/////synthesis.path/seq (/////synthesis.path/then valueS) pathP)) - directive (_.define_function @case (list#each _.parameter @dependencies+) case!)] - _ (/////generation.execute! directive) - _ (/////generation.save! case_artifact directive)] + declaration (_.define_function @case (list#each _.parameter @dependencies+) case!)] + _ (/////generation.execute! declaration) + _ (/////generation.save! case_artifact declaration)] (in (_.apply @dependencies+ @case)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux index 4a80287a7..009dd0271 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux @@ -88,21 +88,21 @@ (|>> synthesis.path/then //case.dependencies (set.of_list _.hash))) - [directive instantiation] (is [Statement Expression] - (case (|> (list#each referenced_variables initsS+) - (list#mix set.union (referenced_variables bodyS)) - (set.difference loop_variables) - set.list) - {.#End} - [(_.define_function @loop (list) scope!) - @loop] + [declaration instantiation] (is [Statement Expression] + (case (|> (list#each referenced_variables initsS+) + (list#mix set.union (referenced_variables bodyS)) + (set.difference loop_variables) + set.list) + {.#End} + [(_.define_function @loop (list) scope!) + @loop] - foreigns - [(<| (_.define_function @loop (list#each _.parameter foreigns)) - (_.return (_.closure (list#each _.parameter foreigns) (list) scope!))) - (_.apply foreigns @loop)]))] - _ (/////generation.execute! directive) - _ (/////generation.save! loop_artifact directive)] + foreigns + [(<| (_.define_function @loop (list#each _.parameter foreigns)) + (_.return (_.closure (list#each _.parameter foreigns) (list) scope!))) + (_.apply foreigns @loop)]))] + _ (/////generation.execute! declaration) + _ (/////generation.save! loop_artifact declaration)] (in (_.apply (list) instantiation))))) ... TODO: Stop using a constant hard-coded variable. Generate a new one each time. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index 9b7ad5575..b79dc468b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -354,8 +354,8 @@ .let [@case (_.var (///reference.artifact [case_module case_artifact])) @dependencies+ (..dependencies (/////synthesis.path/seq (/////synthesis.path/then valueS) pathP)) - directive (_.def @case @dependencies+ - pattern_matching!)] - _ (/////generation.execute! directive) - _ (/////generation.save! case_artifact {.#None} directive)] + declaration (_.def @case @dependencies+ + pattern_matching!)] + _ (/////generation.execute! declaration) + _ (/////generation.save! case_artifact {.#None} declaration)] (in (_.apply @dependencies+ @case)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux index efbc2ca8c..e7ee5d68f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux @@ -56,14 +56,14 @@ _ (do [! ///////phase.monad] - [.let [directive (_.def @function - (|> (list.enumeration inits) - (list#each (|>> product.left ..capture))) - (all _.then - function_definition - (_.return @function)))] - _ (/////generation.execute! directive) - _ (/////generation.save! function_id {.#None} directive)] + [.let [declaration (_.def @function + (|> (list.enumeration inits) + (list#each (|>> product.left ..capture))) + (all _.then + function_definition + (_.return @function)))] + _ (/////generation.execute! declaration) + _ (/////generation.save! function_id {.#None} declaration)] (in (_.apply inits @function))))) (def input @@ -92,25 +92,25 @@ (list.indices arity))]] (with_closure function_artifact @self environment (_.def @self (list (_.poly @curried)) - (all _.then - (_.set (list @num_args) (_.len/1 @curried)) - (<| (_.if (|> @num_args (_.= arityO)) - (<| (_.then initialize!) - //loop.set_scope - body!)) - (_.if (|> @num_args (_.> arityO)) - (let [arity_inputs (_.slice (_.int +0) arityO @curried) - extra_inputs (_.slice arityO @num_args @curried)] - (_.return (|> @self - (apply_poly arity_inputs) - (apply_poly extra_inputs))))) - ... (|> @num_args (_.< arityO)) - (let [@next (_.var "next") - @missing (_.var "missing")] - (all _.then - (_.def @next (list (_.poly @missing)) - (_.return (|> @self (apply_poly (|> @curried (_.+ @missing)))))) - (_.return @next) - ))) - ))) + (all _.then + (_.set (list @num_args) (_.len/1 @curried)) + (<| (_.if (|> @num_args (_.= arityO)) + (<| (_.then initialize!) + //loop.set_scope + body!)) + (_.if (|> @num_args (_.> arityO)) + (let [arity_inputs (_.slice (_.int +0) arityO @curried) + extra_inputs (_.slice arityO @num_args @curried)] + (_.return (|> @self + (apply_poly arity_inputs) + (apply_poly extra_inputs))))) + ... (|> @num_args (_.< arityO)) + (let [@next (_.var "next") + @missing (_.var "missing")] + (all _.then + (_.def @next (list (_.poly @missing)) + (_.return (|> @self (apply_poly (|> @curried (_.+ @missing)))))) + (_.return @next) + ))) + ))) )) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux index 6ef7dd75d..6ac83864b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux @@ -89,25 +89,25 @@ actual_loop (<| (_.def @loop locals) ..set_scope body!) - [directive instantiation] (is [(Statement Any) (Expression Any)] - (case (|> (synthesis.path/then bodyS) - //case.dependencies - (set.of_list _.hash) - (set.difference (set.of_list _.hash locals)) - set.list) - {.#End} - [actual_loop - @loop] + [declaration instantiation] (is [(Statement Any) (Expression Any)] + (case (|> (synthesis.path/then bodyS) + //case.dependencies + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) + set.list) + {.#End} + [actual_loop + @loop] - foreigns - [(_.def @loop foreigns - (all _.then - actual_loop - (_.return @loop) - )) - (_.apply foreigns @loop)]))] - _ (/////generation.execute! directive) - _ (/////generation.save! loop_artifact {.#None} directive)] + foreigns + [(_.def @loop foreigns + (all _.then + actual_loop + (_.return @loop) + )) + (_.apply foreigns @loop)]))] + _ (/////generation.execute! declaration) + _ (/////generation.save! loop_artifact {.#None} declaration)] (in (_.apply initsO+ instantiation))))) (def .public (again! statement expression archive argsS+) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux index 2ef7aa07e..97dbdfe82 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux @@ -61,9 +61,9 @@ variable'))) (def .public (constant system archive name) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> (System expression) Archive Symbol - (////generation.Operation anchor expression directive expression))) + (////generation.Operation anchor expression declaration expression))) (phase#each (|>> ..artifact (at system constant')) (////generation.remember archive name))) @@ -89,8 +89,8 @@ (..foreign system register))) (def .public (reference system archive reference) - (All (_ anchor expression directive) - (-> (System expression) Archive Reference (////generation.Operation anchor expression directive expression))) + (All (_ anchor expression declaration) + (-> (System expression) Archive Reference (////generation.Operation anchor expression declaration expression))) (case reference {reference.#Constant value} (..constant system archive value) 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 162f4c147..9b9c15e3f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -21,8 +21,8 @@ [module ["[0]" descriptor]]]]]) -(type .public (Program expression directive) - (-> unit.ID expression directive)) +(type .public (Program expression declaration) + (-> unit.ID expression declaration)) (def .public name Text diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux index a8317290c..665894617 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux @@ -37,7 +37,7 @@ {#Analyser Text} {#Synthesizer Text} {#Generator Text} - {#Directive Text} + {#Declaration Text} {#Custom Text})) (def .public equivalence @@ -57,7 +57,7 @@ ([#Analyser] [#Synthesizer] [#Generator] - [#Directive] + [#Declaration] [#Custom]) _ diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux index f93624fbc..ec61e4b79 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -90,7 +90,7 @@ [//category.#Analyser analyser analysers Text |> {.#None}] [//category.#Synthesizer synthesizer synthesizers Text |> {.#None}] [//category.#Generator generator generators Text |> {.#None}] - [//category.#Directive directive directives Text |> {.#None}] + [//category.#Declaration declaration declarations Text |> {.#None}] [//category.#Custom custom customs Text |> {.#None}] ) @@ -127,7 +127,7 @@ [2 //category.#Analyser binary.text] [3 //category.#Synthesizer binary.text] [4 //category.#Generator binary.text] - [5 //category.#Directive binary.text] + [5 //category.#Declaration binary.text] [6 //category.#Custom binary.text])))) mandatory? binary.bit dependency (is (Format unit.ID) @@ -172,7 +172,7 @@ [2 //category.#Analyser <binary>.text] [3 //category.#Synthesizer <binary>.text] [4 //category.#Generator <binary>.text] - [5 //category.#Directive <binary>.text] + [5 //category.#Declaration <binary>.text] [6 //category.#Custom <binary>.text]) _ (<>.failure (exception.error ..invalid_category [tag]))))) @@ -195,7 +195,7 @@ [//category.#Analyser ..analyser] [//category.#Synthesizer ..synthesizer] [//category.#Generator ..generator] - [//category.#Directive ..directive] + [//category.#Declaration ..declaration] [//category.#Custom ..custom]) ))) ..empty))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index 4a1572890..11fa0a54f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -163,8 +163,8 @@ list#conjoint))) (def .public (dependencies archive value) - (All (_ anchor expression directive) - (-> Archive Synthesis (Operation anchor expression directive (Set unit.ID)))) + (All (_ anchor expression declaration) + (-> Archive Synthesis (Operation anchor expression declaration (Set unit.ID)))) (let [! phase.monad] (|> value ..references @@ -174,8 +174,8 @@ (at ! each (set.of_list unit.hash))))) (def .public (path_dependencies archive value) - (All (_ anchor expression directive) - (-> Archive Path (Operation anchor expression directive (Set unit.ID)))) + (All (_ anchor expression declaration) + (-> Archive Path (Operation anchor expression declaration (Set unit.ID)))) (let [! phase.monad] (|> value (..path_references ..references) 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 2c7b14da6..3a89e09eb 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -53,7 +53,7 @@ ["[0]" analysis] ["[0]" synthesis] ["[0]" generation] - ["[0]" directive] + ["[0]" declaration] ["[1]/[0]" program]]]]]]) (def (module_parser key parser) @@ -93,13 +93,13 @@ (type Analysers (Dictionary Text analysis.Handler)) (type Synthesizers (Dictionary Text synthesis.Handler)) (type Generators (Dictionary Text generation.Handler)) -(type Directives (Dictionary Text directive.Handler)) +(type Declarations (Dictionary Text declaration.Handler)) (type Bundles [Analysers Synthesizers Generators - Directives]) + Declarations]) (def empty_bundles Bundles @@ -109,8 +109,8 @@ (dictionary.empty text.hash)]) (def (loaded_document extension host @module expected actual document) - (All (_ expression directive) - (-> Text (generation.Host expression directive) module.ID (Sequence [Artifact (Set unit.ID)]) (Dictionary Text Binary) (Document .Module) + (All (_ expression declaration) + (-> Text (generation.Host expression declaration) module.ID (Sequence [Artifact (Set unit.ID)]) (Dictionary Text Binary) (Document .Module) (Try [(Document .Module) Bundles Output]))) (do [! try.monad] [[definitions bundles] (is (Try [Definitions Bundles Output]) @@ -119,23 +119,23 @@ (dictionary.empty text.hash)) bundles ..empty_bundles output (is Output sequence.empty)]) - (let [[analysers synthesizers generators directives] bundles] + (let [[analysers synthesizers generators declarations] bundles] (case input {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']} (case (do ! [data (try.of_maybe (dictionary.value (format (%.nat @artifact) extension) actual)) .let [context [@module @artifact] - directive (at host ingest context data)]] + declaration (at host ingest context data)]] (case artifact_category {category.#Anonymous} (do ! [.let [output (sequence.suffix [@artifact {.#None} data] output)] - _ (at host re_learn context {.#None} directive)] + _ (at host re_learn context {.#None} declaration)] (in [definitions [analysers synthesizers generators - directives] + declarations] output])) {category.#Definition [name function_artifact]} @@ -145,70 +145,70 @@ [analysers synthesizers generators - directives] + declarations] output]) (do ! - [value (at host re_load context {.#None} directive)] + [value (at host re_load context {.#None} declaration)] (in [(dictionary.has name value definitions) [analysers synthesizers generators - directives] + declarations] output])))) {category.#Analyser extension} (do ! [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (at host re_load context {.#None} directive)] + value (at host re_load context {.#None} declaration)] (in [definitions [(dictionary.has extension (as analysis.Handler value) analysers) synthesizers generators - directives] + declarations] output])) {category.#Synthesizer extension} (do ! [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (at host re_load context {.#None} directive)] + value (at host re_load context {.#None} declaration)] (in [definitions [analysers (dictionary.has extension (as synthesis.Handler value) synthesizers) generators - directives] + declarations] output])) {category.#Generator extension} (do ! [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (at host re_load context {.#None} directive)] + value (at host re_load context {.#None} declaration)] (in [definitions [analysers synthesizers (dictionary.has extension (as generation.Handler value) generators) - directives] + declarations] output])) - {category.#Directive extension} + {category.#Declaration extension} (do ! [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (at host re_load context {.#None} directive)] + value (at host re_load context {.#None} declaration)] (in [definitions [analysers synthesizers generators - (dictionary.has extension (as directive.Handler value) directives)] + (dictionary.has extension (as declaration.Handler value) declarations)] output])) {category.#Custom name} (do ! [.let [output (sequence.suffix [@artifact {.#Some name} data] output)] - _ (at host re_learn context {.#Some name} directive)] + _ (at host re_learn context {.#Some name} declaration)] (in [definitions [analysers synthesizers generators - directives] + declarations] output])))) {try.#Success [definitions' bundles' output']} (again input' definitions' bundles' output') @@ -247,8 +247,8 @@ bundles]))) (def (load_definitions fs context @module host_environment entry) - (All (_ expression directive) - (-> (file.System Async) Context module.ID (generation.Host expression directive) + (All (_ expression declaration) + (-> (file.System Async) Context module.ID (generation.Host expression declaration) (archive.Entry .Module) (Async (Try [(archive.Entry .Module) Bundles])))) (do (try.with async.monad) @@ -322,8 +322,8 @@ (at try.monad conjoint))) (def (loaded_caches host_environment fs context purge load_order) - (All (_ expression directive) - (-> (generation.Host expression directive) (file.System Async) Context + (All (_ expression declaration) + (-> (generation.Host expression declaration) (file.System Async) Context Purge (dependency.Order .Module) (Async (Try (List [[descriptor.Module (archive.Entry .Module)] Bundles]))))) (do [! (try.with async.monad)] @@ -344,8 +344,8 @@ (in it))) (def (load_every_reserved_module customs configuration host_environment fs context import contexts archive) - (All (_ expression directive) - (-> (List Custom) Configuration (generation.Host expression directive) (file.System Async) Context Import (List //.Context) Archive + (All (_ expression declaration) + (-> (List Custom) Configuration (generation.Host expression declaration) (file.System Async) Context Import (List //.Context) Archive (Async (Try [Archive .Lux Bundles])))) (do [! (try.with async.monad)] [pre_loaded_caches (..pre_loaded_caches customs fs context import contexts archive) @@ -365,18 +365,18 @@ analysis_state (..analysis_state (the context.#host context) configuration archive)] (in [archive analysis_state - (list#mix (function (_ [_ [+analysers +synthesizers +generators +directives]] - [analysers synthesizers generators directives]) + (list#mix (function (_ [_ [+analysers +synthesizers +generators +declarations]] + [analysers synthesizers generators declarations]) [(dictionary.composite +analysers analysers) (dictionary.composite +synthesizers synthesizers) (dictionary.composite +generators generators) - (dictionary.composite +directives directives)]) + (dictionary.composite +declarations declarations)]) ..empty_bundles loaded_caches)]))))) (def .public (thaw customs configuration host_environment fs context import contexts) - (All (_ expression directive) - (-> (List Custom) Configuration (generation.Host expression directive) (file.System Async) Context Import (List //.Context) + (All (_ expression declaration) + (-> (List Custom) Configuration (generation.Host expression declaration) (file.System Async) Context Import (List //.Context) (Async (Try [Archive .Lux Bundles])))) (do async.monad [binary (at fs read (cache/archive.descriptor fs context))] diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux index c59a31672..ee78db247 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux @@ -63,9 +63,9 @@ (at utf8.codec decoded) (at ! each (|>> as_expected - (is directive) - (sharing [directive] - (is directive + (is declaration) + (sharing [declaration] + (is declaration so_far)) (_.then so_far))))) (_.comment "Lux module" diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index 86960acb0..8d0f233b4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -64,9 +64,9 @@ (at encoding.utf8 decoded) (at try.monad each (|>> as_expected - (is directive) - (sharing [directive] - (is directive + (is declaration) + (sharing [declaration] + (is declaration so_far)) (..then so_far))))) (is _.Expression (_.manual ""))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux index 042b0fcdb..92975f25e 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -35,9 +35,9 @@ ["$" lux]]]]]) (def (write_module necessary_dependencies sequence [module_id output] so_far) - (All (_ directive) - (-> (Set unit.ID) (-> directive directive directive) [module.ID Output] directive - (Try directive))) + (All (_ declaration) + (-> (Set unit.ID) (-> declaration declaration declaration) [module.ID Output] declaration + (Try declaration))) (|> output sequence.list (list.all (function (_ [artifact_id custom content]) @@ -50,19 +50,19 @@ (at utf8.codec decoded) (at try.monad each (|>> as_expected - (is directive) - (sharing [directive] - (is directive + (is declaration) + (sharing [declaration] + (is declaration so_far)) (sequence so_far))))) so_far))) (def .public (package header code sequence scope) - (All (_ directive) - (-> directive - (-> directive Text) - (-> directive directive directive) - (-> directive directive) + (All (_ declaration) + (-> declaration + (-> declaration Text) + (-> declaration declaration declaration) + (-> declaration declaration) Packager)) (function (package host_dependencies archive program) (do [! try.monad] diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux index ed08ed73f..c6e9c5de3 100644 --- a/stdlib/source/library/lux/tool/interpreter.lux +++ b/stdlib/source/library/lux/tool/interpreter.lux @@ -16,7 +16,7 @@ ["[0]" module] ["[0]" type]] ["[0]" generation] - ["[0]" directive (.only State+ Operation) + ["[0]" declaration (.only State+ Operation) ["[0]" total]] ["[0]" extension]] ["[0]" default @@ -58,26 +58,26 @@ "Till next time...") (def enter_module - (All (_ anchor expression directive) - (Operation anchor expression directive Any)) - (directive.lifted_analysis + (All (_ anchor expression declaration) + (Operation anchor expression declaration Any)) + (declaration.lifted_analysis (do phase.monad [_ (module.create 0 ..module)] (analysis.set_current_module ..module)))) (def (initialize Monad<!> Console<!> platform configuration generation_bundle) - (All (_ ! anchor expression directive) + (All (_ ! anchor expression declaration) (-> (Monad !) - (Console !) (Platform ! anchor expression directive) + (Console !) (Platform ! anchor expression declaration) Configuration - (generation.Bundle anchor expression directive) - (! (State+ anchor expression directive)))) + (generation.Bundle anchor expression declaration) + (! (State+ anchor expression declaration)))) (do Monad<!> [state (platform.initialize platform generation_bundle) state (platform.compile platform (has cli.#module syntax.prelude configuration) (has [extension.#state - directive.#analysis directive.#state + declaration.#analysis declaration.#state extension.#state .#info .#mode] {.#Interpreter} @@ -87,10 +87,10 @@ _ (at Console<!> write ..welcome_message)] (in state))) -(with_expansions [<Interpretation> (these (Operation anchor expression directive [Type Any]))] +(with_expansions [<Interpretation> (these (Operation anchor expression declaration [Type Any]))] - (def (interpret_directive code) - (All (_ anchor expression directive) + (def (interpret_declaration code) + (All (_ anchor expression declaration) (-> Code <Interpretation>)) (do phase.monad [_ (total.phase code) @@ -98,14 +98,14 @@ (in [Any []]))) (def (interpret_expression code) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Code <Interpretation>)) (do [! phase.monad] [state (extension.lifted phase.state) - .let [analyse (the [directive.#analysis directive.#phase] state) - synthesize (the [directive.#synthesis directive.#phase] state) - generate (the [directive.#generation directive.#phase] state)] - [_ codeT codeA] (directive.lifted_analysis + .let [analyse (the [declaration.#analysis declaration.#phase] state) + synthesize (the [declaration.#synthesis declaration.#phase] state) + generate (the [declaration.#generation declaration.#phase] state)] + [_ codeT codeA] (declaration.lifted_analysis (analysis.with_scope (type.with_fresh_env (do ! @@ -114,9 +114,9 @@ codeT (type.with_env (check.clean codeT))] (in [codeT codeA]))))) - codeS (directive.lifted_synthesis + codeS (declaration.lifted_synthesis (synthesize codeA))] - (directive.lifted_generation + (declaration.lifted_generation (generation.with_buffer (do ! [codeH (generate codeS) @@ -125,23 +125,23 @@ (in [codeT codeV])))))) (def (interpret configuration code) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> Configuration Code <Interpretation>)) (function (_ state) (case (<| (phase.result' state) - (sharing [anchor expression directive] - (is (State+ anchor expression directive) + (sharing [anchor expression declaration] + (is (State+ anchor expression declaration) state) (is <Interpretation> - (interpret_directive code)))) + (interpret_declaration code)))) {try.#Success [state' output]} {try.#Success [state' output]} {try.#Failure error} - (if (ex.match? total.not_a_directive error) + (if (ex.match? total.not_a_declaration error) (<| (phase.result' state) - (sharing [anchor expression directive] - (is (State+ anchor expression directive) + (sharing [anchor expression declaration] + (is (State+ anchor expression declaration) state) (is <Interpretation> (interpret_expression code)))) @@ -149,43 +149,43 @@ ) (def (execute configuration code) - (All (_ anchor expression directive) - (-> Configuration Code (Operation anchor expression directive Text))) + (All (_ anchor expression declaration) + (-> Configuration Code (Operation anchor expression declaration Text))) (do phase.monad [[codeT codeV] (interpret configuration code) state phase.state] (in (/type.represent (the [extension.#state - directive.#analysis directive.#state + declaration.#analysis declaration.#state extension.#state] state) codeT codeV)))) -(type (Context anchor expression directive) +(type (Context anchor expression declaration) (Record [#configuration Configuration - #state (State+ anchor expression directive) + #state (State+ anchor expression declaration) #source Source])) -(with_expansions [<Context> (these (Context anchor expression directive))] +(with_expansions [<Context> (these (Context anchor expression declaration))] (def (read_eval_print context) - (All (_ anchor expression directive) + (All (_ anchor expression declaration) (-> <Context> (Try [<Context> Text]))) (do try.monad [.let [[_where _offset _code] (the #source context)] [source' input] (syntax.parse ..module syntax.no_aliases (text.size _code) (the #source context)) [state' representation] (let [... TODO: Simplify ASAP - state (sharing [anchor expression directive] + state (sharing [anchor expression declaration] (is <Context> context) - (is (State+ anchor expression directive) + (is (State+ anchor expression declaration) (the #state context)))] (<| (phase.result' state) ... TODO: Simplify ASAP - (sharing [anchor expression directive] + (sharing [anchor expression declaration] (is <Context> context) - (is (Operation anchor expression directive Text) + (is (Operation anchor expression declaration Text) (execute (the #configuration context) input)))))] (in [(|> context (has #state state') @@ -193,11 +193,11 @@ representation])))) (def .public (run! Monad<!> Console<!> platform configuration generation_bundle) - (All (_ ! anchor expression directive) + (All (_ ! anchor expression declaration) (-> (Monad !) - (Console !) (Platform ! anchor expression directive) + (Console !) (Platform ! anchor expression declaration) Configuration - (generation.Bundle anchor expression directive) + (generation.Bundle anchor expression declaration) (! Any))) (do [! Monad<!>] [state (initialize Monad<!> Console<!> platform configuration)] |