diff options
author | Eduardo Julian | 2022-06-16 00:48:19 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-06-16 00:48:19 -0400 |
commit | 9e2f1e76f2c8df01ed7687d934c3210fcf676bd6 (patch) | |
tree | 115fab5bd8a5f53dc0d13ce5453095324a83496f /stdlib/source/library/lux/tool/compiler | |
parent | f92c806ee8da63f04bbefbf558f6249bacdb47ea (diff) |
De-sigil-ification: suffix : [Part 13]
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
214 files changed, 2266 insertions, 2266 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/arity.lux b/stdlib/source/library/lux/tool/compiler/arity.lux index c1e2796c3..14e73f0c1 100644 --- a/stdlib/source/library/lux/tool/compiler/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/arity.lux @@ -9,7 +9,7 @@ Nat) (with_template [<comparison> <name>] - [(def: .public <name> (-> Arity Bit) (<comparison> 1))] + [(def .public <name> (-> Arity Bit) (<comparison> 1))] [n.< nullary?] [n.= unary?] diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 2f4f943f9..8ad59fc2e 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -53,7 +53,7 @@ ["[0]" descriptor] ["[0]" document]]]]]]) -(def: .public (state target module configuration expander host_analysis host generate generation_bundle) +(def .public (state target module configuration expander host_analysis host generate generation_bundle) (All (_ anchor expression directive) (-> Target descriptor.Module @@ -77,7 +77,7 @@ ///directive.#generation [///directive.#state generation_state ///directive.#phase generate]]])) -(def: .public (with_default_directives expander host_analysis program anchorT,expressionT,directiveT extender) +(def .public (with_default_directives expander host_analysis program anchorT,expressionT,directiveT extender) (All (_ anchor expression directive) (-> Expander ///analysis.Bundle @@ -94,13 +94,13 @@ (type: Reader (-> Source (Either [Source Text] [Source Code]))) -(def: (reader current_module aliases [location offset source_code]) +(def (reader current_module aliases [location offset source_code]) (-> descriptor.Module Aliases Source (///analysis.Operation Reader)) (function (_ [bundle state]) {try.#Success [[bundle state] (///syntax.parse current_module aliases ("lux text size" source_code))]})) -(def: (read source reader) +(def (read source reader) (-> Source Reader (///analysis.Operation [Source Code])) (function (_ [bundle compiler]) (case (reader source) @@ -122,7 +122,7 @@ [(///generation.Buffer directive) Registry]) -(def: (begin dependencies hash input) +(def (begin dependencies hash input) (-> (List descriptor.Module) Nat ///.Input (All (_ anchor expression directive) (///directive.Operation anchor expression directive @@ -139,7 +139,7 @@ (in [source [///generation.empty_buffer registry.empty]]))))) -(def: (end module) +(def (end module) (-> descriptor.Module (All (_ anchor expression directive) (///directive.Operation anchor expression directive [.Module (Payload directive)]))) @@ -158,7 +158,7 @@ final_registry]]))) ... TODO: Inline ASAP -(def: (get_current_payload _) +(def (get_current_payload _) (All (_ directive) (-> (Payload directive) (All (_ anchor expression) @@ -172,7 +172,7 @@ (in [buffer registry]))) ... TODO: Inline ASAP -(def: (process_directive wrapper archive expander pre_payoad code) +(def (process_directive wrapper archive expander pre_payoad code) (All (_ directive) (-> ///phase.Wrapper Archive Expander (Payload directive) Code (All (_ anchor expression) @@ -189,7 +189,7 @@ post_payload (..get_current_payload pre_payoad)] (in [requirements post_payload]))) -(def: (iteration' wrapper archive expander reader source pre_payload) +(def (iteration' wrapper archive expander reader source pre_payload) (All (_ directive) (-> ///phase.Wrapper Archive Expander Reader Source (Payload directive) (All (_ anchor expression) @@ -201,7 +201,7 @@ [requirements post_payload] (process_directive wrapper archive expander pre_payload code)] (in [source requirements post_payload]))) -(def: (iteration wrapper archive expander module source pre_payload aliases) +(def (iteration wrapper archive expander module source pre_payload aliases) (All (_ directive) (-> ///phase.Wrapper Archive Expander descriptor.Module Source (Payload directive) Aliases (All (_ anchor expression) @@ -220,18 +220,18 @@ {try.#Success [state {.#None}]} (exception.with ///.cannot_compile module {try.#Failure error})))))) -(def: (default_dependencies prelude input) +(def (default_dependencies prelude input) (-> descriptor.Module ///.Input (List descriptor.Module)) (list.partial descriptor.runtime (if (text#= prelude (the ///.#module input)) (list) (list prelude)))) -(def: module_aliases +(def module_aliases (-> .Module Aliases) (|>> (the .#module_aliases) (dictionary.of_list text.hash))) -(def: .public (compiler wrapper expander prelude write_directive) +(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))) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index e999ae79d..07a7b4c0f 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -87,7 +87,7 @@ (Async (Try a))) ... TODO: Get rid of this - (def: monad + (def monad (as (Monad Action) (try.with async.monad))) @@ -95,7 +95,7 @@ <State+> (these (///directive.State+ <type_vars>)) <Bundle> (these (///generation.Bundle <type_vars>))] - (def: (writer //) + (def (writer //) (All (_ a) (-> (Writer a) (Writer [(module.Module a) Registry]))) @@ -107,7 +107,7 @@ registry.writer )) - (def: (cache_module context platform @module key format entry) + (def (cache_module context platform @module key format entry) (All (_ <type_vars> document) (-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document) (Async (Try Any)))) @@ -141,20 +141,20 @@ (cache/module.cache! system context @module)))))) ... TODO: Inline ASAP - (def: initialize_buffer! + (def initialize_buffer! (All (_ <type_vars>) (///generation.Operation <type_vars> Any)) (///generation.set_buffer ///generation.empty_buffer)) ... TODO: Inline ASAP - (def: (compile_runtime! platform) + (def (compile_runtime! platform) (All (_ <type_vars>) (-> <Platform> (///generation.Operation <type_vars> [Registry Output]))) (do ///phase.monad [_ ..initialize_buffer!] (the #runtime platform))) - (def: runtime_descriptor + (def runtime_descriptor Descriptor [descriptor.#hash 0 descriptor.#name descriptor.runtime @@ -162,17 +162,17 @@ descriptor.#references (set.empty text.hash) descriptor.#state {.#Compiled}]) - (def: runtime_document + (def runtime_document (Document .Module) (document.document $.key (moduleA.empty 0))) - (def: runtime_module + (def runtime_module (module.Module .Module) [module.#id module.runtime module.#descriptor runtime_descriptor module.#document runtime_document]) - (def: (process_runtime archive platform) + (def (process_runtime archive platform) (All (_ <type_vars>) (-> Archive <Platform> (///directive.Operation <type_vars> @@ -188,7 +188,7 @@ (archive.has descriptor.runtime entry archive))))] (in [archive entry]))) - (def: (initialize_state extender + (def (initialize_state extender [analysers synthesizers generators @@ -222,7 +222,7 @@ (///phase.result' state) (at try.monad each product.left))) - (def: (phase_wrapper archive platform state) + (def (phase_wrapper archive platform state) (All (_ <type_vars>) (-> Archive <Platform> <State+> (Try [<State+> ///phase.Wrapper]))) (|> archive @@ -230,7 +230,7 @@ ///directive.lifted_generation (///phase.result' state))) - (def: (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives]) + (def (complete_extensions host_directive_bundle phase_wrapper [analysers synthesizers generators directives]) (All (_ <type_vars>) (-> (-> ///phase.Wrapper (///directive.Bundle <type_vars>)) ///phase.Wrapper @@ -247,7 +247,7 @@ generators (dictionary.composite directives (host_directive_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_directive_bundle program anchorT,expressionT,directiveT extender import compilation_sources compilation_configuration) (All (_ <type_vars>) (-> context.Context @@ -300,10 +300,10 @@ [phase_wrapper state] (with_missing_extensions platform program state)] (in [state archive phase_wrapper]))))) - (def: compilation_log_separator + (def compilation_log_separator (format text.new_line text.tab)) - (def: (module_compilation_log module) + (def (module_compilation_log module) (All (_ <type_vars>) (-> descriptor.Module <State+> Text)) (|>> (the [extension.#state @@ -315,7 +315,7 @@ (format left ..compilation_log_separator right)) module))) - (def: with_reset_log + (def with_reset_log (All (_ <type_vars>) (-> <State+> <State+>)) (has [extension.#state @@ -325,7 +325,7 @@ ///generation.#log] sequence.empty)) - (def: empty + (def empty (Set descriptor.Module) (set.empty text.hash)) @@ -337,13 +337,13 @@ [#depends_on Mapping #depended_by Mapping])) - (def: independence + (def independence Dependence (let [empty (dictionary.empty text.hash)] [#depends_on empty #depended_by empty])) - (def: (depend module import dependence) + (def (depend module import dependence) (-> descriptor.Module descriptor.Module Dependence Dependence) (let [transitive_dependency (is (-> (-> Dependence Mapping) descriptor.Module (Set descriptor.Module)) (function (_ lens module) @@ -375,7 +375,7 @@ [module transitive_depends_on] [import transitive_depended_by]))))) - (def: (circular_dependency? module import dependence) + (def (circular_dependency? module import dependence) (-> descriptor.Module descriptor.Module Dependence Bit) (let [dependence? (is (-> descriptor.Module (-> Dependence Mapping) descriptor.Module Bit) (function (_ from relationship to) @@ -403,7 +403,7 @@ "Importer" (%.text importer) "Duplicates" (%.list %.text (set.list duplicates)))) - (def: (verify_dependencies importer importee dependence) + (def (verify_dependencies importer importee dependence) (-> descriptor.Module descriptor.Module Dependence (Try Any)) (cond (text#= importer importee) (exception.except ..module_cannot_import_itself [importer]) @@ -418,7 +418,7 @@ (exception.report "Extension" (%.text extension))) - (def: (with_extensions from to) + (def (with_extensions from to) (All (_ state input output) (-> (extension.Bundle state input output) (extension.Bundle state input output) @@ -440,7 +440,7 @@ (dictionary.entries from)))) (with_template [<name> <path>] - [(def: (<name> from state) + [(def (<name> from state) (All (_ <type_vars>) (-> <State+> <State+> (Try <State+>))) (do try.monad @@ -453,7 +453,7 @@ [with_directive_extensions [extension.#bundle]] ) - (def: (with_all_extensions from state) + (def (with_all_extensions from state) (All (_ <type_vars>) (-> <State+> <State+> (Try <State+>))) (do try.monad @@ -490,7 +490,7 @@ Lux_Pending (..Pending <State+>) Lux_Importer (..Importer <State+>) Lux_Compiler (..Compiler <State+>)] - (def: (parallel initial) + (def (parallel initial) (All (_ <type_vars>) (-> Lux_Context (-> Lux_Compiler Lux_Importer))) @@ -582,7 +582,7 @@ return))))) ... TODO: Find a better way, as this only works for the Lux compiler. - (def: (updated_state archive extended_states state) + (def (updated_state archive extended_states state) (All (_ <type_vars>) (-> Archive (List <State+>) <State+> (Try <State+>))) (do [! try.monad] @@ -617,7 +617,7 @@ state (monad.mix ! with_all_extensions state extended_states)] (in (with_modules state)))) - (def: (set_current_module module state) + (def (set_current_module module state) (All (_ <type_vars>) (-> descriptor.Module <State+> <State+>)) (|> (///directive.set_current_module module) @@ -628,7 +628,7 @@ ... TODO: Come up with a less hacky way to prevent duplicate imports. ... This currently assumes that all imports will be specified once in a single .using form. ... This might not be the case in the future. - (def: (with_new_dependencies new_dependencies all_dependencies) + (def (with_new_dependencies new_dependencies all_dependencies) (-> (List descriptor.Module) (Set descriptor.Module) [(Set descriptor.Module) (Set descriptor.Module)]) (let [[all_dependencies duplicates _] (is [(Set descriptor.Module) (Set descriptor.Module) Bit] (list#mix (function (_ new [all duplicates seen_prelude?]) @@ -644,7 +644,7 @@ new_dependencies))] [all_dependencies duplicates])) - (def: (any|after_imports customs import! module duplicates new_dependencies archive) + (def (any|after_imports customs import! module duplicates new_dependencies archive) (All (_ <type_vars> state document object) (-> (List ///.Custom) (..Importer state) descriptor.Module (Set descriptor.Module) (List descriptor.Module) Archive @@ -667,7 +667,7 @@ (list#each product.right archive,state/*)]))) (async#in (exception.except ..cannot_import_twice [module duplicates]))))) - (def: (lux|after_imports customs import! module duplicates new_dependencies [archive state]) + (def (lux|after_imports customs import! module duplicates new_dependencies [archive state]) (All (_ <type_vars>) (-> (List ///.Custom) Lux_Importer descriptor.Module (Set descriptor.Module) (List descriptor.Module) Lux_Context Lux_Return)) (do (try.with async.monad) @@ -679,7 +679,7 @@ {.#Item _} (try.trusted (..updated_state archive state/* state)))]))) - (def: (next_compilation module [archive state] compilation) + (def (next_compilation module [archive state] compilation) (All (_ <type_vars>) (-> descriptor.Module Lux_Context (///.Compilation <State+> .Module Any) (Try [<State+> (Either (///.Compilation <State+> .Module Any) @@ -693,14 +693,14 @@ product.left) archive)) - (def: (compiler phase_wrapper expander platform) + (def (compiler phase_wrapper expander platform) (All (_ <type_vars>) (-> ///phase.Wrapper Expander <Platform> (///.Compiler <State+> .Module Any))) (let [instancer (//init.compiler phase_wrapper expander syntax.prelude (the #write platform))] (instancer $.key (list)))) - (def: (custom_compiler import context platform compilation_sources compiler + (def (custom_compiler import context platform compilation_sources compiler custom_key custom_format custom_compilation) (All (_ <type_vars> state document object) @@ -741,7 +741,7 @@ [_ (cache/archive.cache! (the #file_system platform) context archive)] (async#in {try.#Failure error}))))))) - (def: (lux_compiler import context platform compilation_sources compiler compilation) + (def (lux_compiler import context platform compilation_sources compiler compilation) (All (_ <type_vars>) (-> Import context.Context <Platform> (List _io.Context) (///.Compiler <State+> .Module Any) (///.Compilation <State+> .Module Any) @@ -791,20 +791,20 @@ [_ (cache/archive.cache! (the #file_system platform) context archive)] (async#in {try.#Failure error}))))))) - (for @.old (these (def: Fake_State + (for @.old (these (def Fake_State Type {.#Primitive (%.nat (static.random_nat)) (list)}) - (def: Fake_Document + (def Fake_Document Type {.#Primitive (%.nat (static.random_nat)) (list)}) - (def: Fake_Object + (def Fake_Object Type {.#Primitive (%.nat (static.random_nat)) (list)})) (these)) - (def: (serial_compiler import context platform compilation_sources compiler) + (def (serial_compiler import context platform compilation_sources compiler) (All (_ <type_vars>) (-> Import context.Context <Platform> (List _io.Context) (///.Compiler <State+> .Module Any) Lux_Compiler)) @@ -836,7 +836,7 @@ all_customs importer import! @module [archive custom_state] module)] (in [archive' lux_state])))))))) - (def: .public Custom + (def .public Custom Type (type (-> (List Text) (Try ///.Custom)))) @@ -847,7 +847,7 @@ "Expected Type" (%.type ..Custom) "Actual Type" (%.type type))) - (def: (custom import! it) + (def (custom import! it) (All (_ <type_vars>) (-> Lux_Importer compiler.Compiler (Async (Try [Lux_Context (List Text) Any])))) (let [/#definition (the compiler.#definition it) @@ -868,7 +868,7 @@ {try.#Success [context (the compiler.#parameters it) /#value]} (exception.except ..invalid_custom_compiler [/#definition /#type])))))) - (def: .public (compile lux_compiler phase_wrapper import file_context expander platform compilation context) + (def .public (compile lux_compiler phase_wrapper import file_context expander platform compilation context) (All (_ <type_vars>) (-> (-> Any ..Custom) ///phase.Wrapper Import context.Context Expander <Platform> Compilation Lux_Context Lux_Return)) (let [[host_dependencies libraries compilers sources target module configuration] compilation diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index 084348037..7f601efff 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux @@ -20,7 +20,7 @@ ... TODO: Remove #module_hash, #imports & #module_state ASAP. ... TODO: Not just from this parser, but from the lux.Module type. -(def: .public writer +(def .public writer (Writer .Module) (let [definition (is (Writer Definition) (all _.and _.bit _.type _.any)) @@ -52,7 +52,7 @@ ... #module_state _.any))) -(def: .public parser +(def .public parser (Parser .Module) (let [definition (is (Parser Definition) (all <>.and @@ -98,7 +98,7 @@ ... #module_state (at <>.monad in {.#Cached})))) -(def: .public key +(def .public key (Key .Module) (key.key [signature.#name (symbol ..compiler) signature.#version version.latest] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 471431654..0a1b71dab 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -72,17 +72,17 @@ (type: .public Match (Match' Analysis)) -(def: (branch_equivalence equivalence) +(def (branch_equivalence equivalence) (-> (Equivalence Analysis) (Equivalence Branch)) (implementation - (def: (= [reference_pattern reference_body] [sample_pattern sample_body]) + (def (= [reference_pattern reference_body] [sample_pattern sample_body]) (and (at /pattern.equivalence = reference_pattern sample_pattern) (at equivalence = reference_body sample_body))))) -(def: .public equivalence +(def .public equivalence (Equivalence Analysis) (implementation - (def: (= reference sample) + (def (= reference sample) (.case [reference sample] [{#Simple reference} {#Simple sample}] (at /simple.equivalence = reference sample) @@ -115,19 +115,19 @@ false)))) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [{<tag> content}]))] [case ..#Case] ) -(def: .public unit +(def .public unit (template (unit) [{..#Simple {/simple.#Unit}}])) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> value) [{..#Simple {<tag> value}}]))] @@ -145,7 +145,7 @@ (type: .public (Reification c) [c (List c)]) -(def: .public no_op +(def .public no_op (template (no_op value) [(|> 1 {variable.#Local} @@ -154,14 +154,14 @@ {..#Function (list)} {..#Apply value})])) -(def: .public (reified [abstraction inputs]) +(def .public (reified [abstraction inputs]) (-> (Reification Analysis) Analysis) (list#mix (function (_ input abstraction') {#Apply input abstraction'}) abstraction inputs)) -(def: .public (reification analysis) +(def .public (reification analysis) (-> Analysis (Reification Analysis)) (loop (again [abstraction analysis inputs (is (List Analysis) @@ -174,7 +174,7 @@ [abstraction inputs]))) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (syntax (_ [content <code>.any]) (in (list (` (.<| {..#Reference} <tag> @@ -188,7 +188,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Structure} {<tag>} @@ -198,7 +198,7 @@ [tuple /complex.#Tuple] ) -(def: .public (format analysis) +(def .public (format analysis) (Format Analysis) (.case analysis {#Simple it} @@ -255,7 +255,7 @@ [Bundle extension.Bundle] ) -(def: .public (with_source_code source action) +(def .public (with_source_code source action) (All (_ a) (-> Source (Operation a) (Operation a))) (function (_ [bundle state]) (let [old_source (the .#source state)] @@ -267,13 +267,13 @@ failure failure)))) -(def: .public (with_current_module name) +(def .public (with_current_module name) (All (_ a) (-> Text (Operation a) (Operation a))) (extension.localized (the .#current_module) (has .#current_module) (function.constant {.#Some name}))) -(def: .public (with_location location action) +(def .public (with_location location action) (All (_ a) (-> Location (Operation a) (Operation a))) (if (text#= "" (product.left location)) action @@ -287,17 +287,17 @@ failure failure))))) -(def: (located location error) +(def (located location error) (-> Location Text Text) (%.format (%.location location) text.new_line error)) -(def: .public (failure error) +(def .public (failure error) (-> Text Operation) (function (_ [bundle state]) {try.#Failure (located (the .#location state) error)})) -(def: .public (of_try it) +(def .public (of_try it) (All (_ a) (-> (Try a) (Operation a))) (function (_ [bundle state]) (.case it @@ -307,17 +307,17 @@ {try.#Success it} {try.#Success [[bundle state] it]}))) -(def: .public (except exception parameters) +(def .public (except exception parameters) (All (_ e) (-> (Exception e) e Operation)) (..failure (exception.error exception parameters))) -(def: .public (assertion exception parameters condition) +(def .public (assertion exception parameters condition) (All (_ e) (-> (Exception e) e Bit (Operation Any))) (if condition (at phase.monad in []) (..except exception parameters))) -(def: .public (with_exception exception message action) +(def .public (with_exception exception message action) (All (_ e o) (-> (Exception e) e (Operation o) (Operation o))) (function (_ bundle,state) (.case (exception.with exception message @@ -329,14 +329,14 @@ success success))) -(def: .public (set_state state) +(def .public (set_state state) (-> .Lux (Operation Any)) (function (_ [bundle _]) {try.#Success [[bundle state] []]})) (with_template [<name> <type> <field> <value>] - [(def: .public (<name> value) + [(def .public (<name> value) (-> <type> (Operation Any)) (extension.update (has <field> <value>)))] @@ -345,32 +345,32 @@ [set_location Location .#location value] ) -(def: .public (location file) +(def .public (location file) (-> Text Location) [file 1 0]) -(def: .public (source file code) +(def .public (source file code) (-> Text Text Source) [(location file) 0 code]) -(def: dummy_source +(def dummy_source Source [location.dummy 0 ""]) -(def: type_context +(def type_context Type_Context [.#ex_counter 0 .#var_counter 0 .#var_bindings (list)]) -(def: .public (info version host configuration) +(def .public (info version host configuration) (-> Version Text Configuration Info) [.#target host .#version (version.format version) .#mode {.#Build} .#configuration configuration]) -(def: .public (state info) +(def .public (state info) (-> Info Lux) [.#info info .#source ..dummy_source diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux index b2dbbbb79..bca0b70e3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux @@ -31,28 +31,28 @@ (type: .public Tag Nat) -(def: .public (tag right? lefts) +(def .public (tag right? lefts) (-> Bit Nat Tag) (if right? (++ lefts) lefts)) -(def: .public (lefts right? tag) +(def .public (lefts right? tag) (-> Bit Tag Nat) (if right? (-- tag) tag)) -(def: .public (choice multiplicity pick) +(def .public (choice multiplicity pick) (-> Nat Tag [Nat Bit]) (let [right? (n.= (-- multiplicity) pick)] [(..lefts right? pick) right?])) -(def: .public (equivalence (open "/#[0]")) +(def .public (equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Complex a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Variant [reference_lefts reference_right? reference_value]} {#Variant [sample_lefts sample_right? sample_value]}] @@ -66,13 +66,13 @@ _ false)))) -(def: .public (hash super) +(def .public (hash super) (All (_ a) (-> (Hash a) (Hash (Complex a)))) (implementation - (def: equivalence + (def equivalence (..equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value {#Variant [lefts right? value]} (all n.* 2 @@ -85,7 +85,7 @@ (at (list.hash super) hash members)) )))) -(def: .public (format %it it) +(def .public (format %it it) (All (_ a) (-> (Format a) (Format (Complex a)))) (case it {#Variant [lefts right? it]} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux index e37943c08..a54acd867 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -58,7 +58,7 @@ (type: .public Variant (Variant' Coverage)))) -(def: .public (minimum [max cases]) +(def .public (minimum [max cases]) (-> Variant Nat) (maybe.else (|> cases dictionary.keys @@ -66,11 +66,11 @@ ++) max)) -(def: .public (maximum [max cases]) +(def .public (maximum [max cases]) (-> Variant Nat) (maybe.else n#top max)) -(def: (alternatives coverage) +(def (alternatives coverage) (-> Coverage (List Coverage)) (case coverage {#Alt left right} @@ -79,10 +79,10 @@ _ (list coverage))) -(def: .public equivalence +(def .public equivalence (Equivalence Coverage) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Exhaustive} {#Exhaustive}] #1 @@ -120,7 +120,7 @@ (open: "/#[0]" ..equivalence) -(def: .public (format value) +(def .public (format value) (%.Format Coverage) (case value {#Bit it} @@ -162,7 +162,7 @@ "Expected size" ">= 2" "Actual size" (%.nat size))) -(def: .public (coverage pattern) +(def .public (coverage pattern) (-> Pattern (Try Coverage)) (case pattern (^.or {//pattern.#Simple {//simple.#Unit}} @@ -222,7 +222,7 @@ (|> (dictionary.empty n.hash) (dictionary.has idx value_coverage))})))) -(def: (xor left right) +(def (xor left right) (-> Bit Bit Bit) (or (and left (not right)) (and (not left) right))) @@ -245,7 +245,7 @@ "Expected cases" (%.nat expected) "Mismatched cases" (%.nat mismatched))) -(def: .public (exhaustive? coverage) +(def .public (exhaustive? coverage) (-> Coverage Bit) (case coverage {#Exhaustive} @@ -258,7 +258,7 @@ ... necessary to merge them all to figure out if the entire ... pattern-matching expression is exhaustive and whether it contains ... redundant patterns. -(def: .public (composite addition so_far) +(def .public (composite addition so_far) (-> Coverage Coverage (Try Coverage)) (with_expansions [<redundancy> (exception.except ..redundancy [so_far addition]) <alternatively> {try.#Success {#Alt addition so_far}} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index 2cc4503d9..69efc223d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux @@ -38,11 +38,11 @@ (type: .public Eval (-> Archive Type Code (Operation Any))) -(def: evals +(def evals (Atom (Dictionary module.ID Nat)) (atom.atom (dictionary.empty n.hash))) -(def: .public (evaluator expander synthesis_state generation_state generate) +(def .public (evaluator expander synthesis_state generation_state generate) (All (_ anchor expression artifact) (-> Expander synthesis.State+ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index 06489b706..cecf9c460 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -54,7 +54,7 @@ [invalid_type_application] ) -(def: .public (quantified @var @parameter :it:) +(def .public (quantified @var @parameter :it:) (-> check.Var Nat Type Type) (case :it: {.#Primitive name co_variant} @@ -93,7 +93,7 @@ ... tagged variants). ... But, so long as the type being used for the inference can be treated ... as a function type, this method of inference should work. -(def: (general' vars archive analyse inferT args) +(def (general' vars archive analyse inferT args) (-> (List check.Var) Archive Phase Type (List Code) (Operation [Type_Context (List check.Var) Type (List Analysis)])) (case args {.#End} @@ -154,7 +154,7 @@ (/.except ..cannot_infer [inferT args])) )) -(def: .public (general archive analyse inferT args) +(def .public (general archive analyse inferT args) (-> Archive Phase Type (List Code) (Operation [Type (List Analysis)])) (do [! phase.monad] [[just_before vars :inference: terms] (general' (list) archive analyse inferT args)] @@ -188,7 +188,7 @@ ... (in [:inference: terms]))) )) -(def: (with_recursion @self recursion) +(def (with_recursion @self recursion) (-> Nat Type Type Type) (function (again it) (case it @@ -216,14 +216,14 @@ _ it))) -(def: parameters +(def parameters (-> Nat (List Type)) (|>> list.indices (list#each (|>> (n.* 2) ++ {.#Parameter})) list.reversed)) (with_template [<name> <types> <inputs> <exception> <when> <then>] - [(`` (def: .public (<name> (~~ (template.spliced <inputs>)) complex) + [(`` (def .public (<name> (~~ (template.spliced <inputs>)) complex) (-> (~~ (template.spliced <types>)) Type (Operation Type)) (loop (again [depth 0 it complex]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux index 7ca7b9158..e66c897e9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux @@ -32,7 +32,7 @@ (type: .public Expander (-> Macro (List Code) Lux (Try (Try [Lux (List Code)])))) -(def: .public (expansion expander name macro inputs) +(def .public (expansion expander name macro inputs) (-> Expander Symbol Macro (List Code) (Meta (List Code))) (function (_ state) (do try.monad @@ -44,7 +44,7 @@ _ output)))) -(def: .public (single_expansion expander name macro inputs) +(def .public (single_expansion expander name macro inputs) (-> Expander Symbol Macro (List Code) (Meta Code)) (do meta.monad [expansion (..expansion expander name macro inputs)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux index 6c325986d..a2f23afd5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux @@ -69,7 +69,7 @@ {.#Compiled} "Compiled" {.#Cached} "Cached"))) -(def: .public (empty hash) +(def .public (empty hash) (-> Nat Module) [.#module_hash hash .#module_aliases (list) @@ -77,7 +77,7 @@ .#imports (list) .#module_state {.#Active}]) -(def: .public (import module) +(def .public (import module) (-> Text (Operation Any)) (///extension.lifted (do ///.monad @@ -92,7 +92,7 @@ state) []]})))) -(def: .public (alias alias module) +(def .public (alias alias module) (-> Text Text (Operation Any)) (///extension.lifted (do ///.monad @@ -104,7 +104,7 @@ state) []]})))) -(def: .public (exists? module) +(def .public (exists? module) (-> Text (Operation Bit)) (///extension.lifted (function (_ state) @@ -115,7 +115,7 @@ [state] {try.#Success})))) -(def: .public (define name definition) +(def .public (define name definition) (-> Text Global (Operation Any)) (///extension.lifted (do ///.monad @@ -137,7 +137,7 @@ ((///extension.up (/.except ..cannot_define_more_than_once [[self_name name] already_existing])) state)))))) -(def: .public (create hash name) +(def .public (create hash name) (-> Nat Text (Operation Any)) (///extension.lifted (function (_ state) @@ -146,7 +146,7 @@ state) []]}))) -(def: .public (with hash name action) +(def .public (with hash name action) (All (_ a) (-> Nat Text (Operation a) (Operation [Module a]))) (do ///.monad [_ (..create hash name) @@ -156,7 +156,7 @@ (in [module output]))) (with_template [<setter> <asker> <tag>] - [(def: .public (<setter> module_name) + [(def .public (<setter> module_name) (-> Text (Operation Any)) (///extension.lifted (function (_ state) @@ -177,7 +177,7 @@ ((///extension.up (/.except ..unknown_module module_name)) state))))) - (def: .public (<asker> module_name) + (def .public (<asker> module_name) (-> Text (Operation Bit)) (///extension.lifted (function (_ state) @@ -197,7 +197,7 @@ [set_cached cached? .#Cached] ) -(def: .public (declare_labels record? labels exported? type) +(def .public (declare_labels record? labels exported? type) (-> Bit (List Label) Bit Type (Operation Any)) (do [! ///.monad] [self_name (///extension.lifted meta.current_module_name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux index ef3350d56..841a39b77 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux @@ -23,10 +23,10 @@ {#Complex (Complex Pattern)} {#Bind Register}))) -(def: .public equivalence +(def .public equivalence (Equivalence Pattern) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Simple reference} {#Simple sample}] (at //simple.equivalence = reference sample) @@ -40,7 +40,7 @@ _ false)))) -(def: .public (format it) +(def .public (format it) (%.Format Pattern) (case it {#Simple it} @@ -53,7 +53,7 @@ (//variable.format {//variable.#Local it}))) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Complex} <tag> @@ -63,12 +63,12 @@ [tuple {//complex.#Tuple}] ) -(def: .public unit +(def .public unit (template (unit) [{..#Simple {//simple.#Unit}}])) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [{..#Simple {<tag> content}}]))] @@ -80,6 +80,6 @@ [text //simple.#Text] ) -(def: .public bind +(def .public bind (template (bind register) [{..#Bind register}])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux index 2fa60d94f..7491c9f00 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux @@ -29,13 +29,13 @@ (type: Foreign (Bindings Text [Type Variable])) -(def: (local? name scope) +(def (local? name scope) (-> Text Scope Bit) (|> scope (the [.#locals .#mappings]) (plist.contains? name))) -(def: (local name scope) +(def (local name scope) (-> Text Scope (Maybe [Type Variable])) (|> scope (the [.#locals .#mappings]) @@ -43,13 +43,13 @@ (maybe#each (function (_ [type value]) [type {variable.#Local value}])))) -(def: (captured? name scope) +(def (captured? name scope) (-> Text Scope Bit) (|> scope (the [.#captured .#mappings]) (plist.contains? name))) -(def: (captured name scope) +(def (captured name scope) (-> Text Scope (Maybe [Type Variable])) (loop (again [idx 0 mappings (the [.#captured .#mappings] scope)]) @@ -62,12 +62,12 @@ {.#End} {.#None}))) -(def: (reference? name scope) +(def (reference? name scope) (-> Text Scope Bit) (or (local? name scope) (captured? name scope))) -(def: (reference name scope) +(def (reference name scope) (-> Text Scope (Maybe [Type Variable])) (case (..local name scope) {.#Some type} @@ -76,7 +76,7 @@ _ (..captured name scope))) -(def: .public (variable name) +(def .public (variable name) (-> Text (Operation (Maybe [Type Variable]))) (extension.lifted (function (_ state) @@ -109,7 +109,7 @@ (exception: .public no_scope) (exception: .public drained) -(def: .public (with_local [name type] action) +(def .public (with_local [name type] action) (All (_ a) (-> [Text Type] (Operation a) (Operation a))) (function (_ [bundle state]) (case (the .#scopes state) @@ -140,7 +140,7 @@ _ (exception.except ..no_scope [])))) -(def: empty +(def empty Scope (let [bindings (is Bindings [.#counter 0 @@ -150,7 +150,7 @@ .#locals bindings .#captured bindings])) -(def: .public (reset action) +(def .public (reset action) (All (_ a) (-> (Operation a) (Operation a))) (function (_ [bundle state]) (case (action [bundle (has .#scopes (list ..empty) state)]) @@ -161,7 +161,7 @@ failure failure))) -(def: .public (with action) +(def .public (with action) (All (_ a) (-> (Operation a) (Operation [Scope a]))) (function (_ [bundle state]) (case (action [bundle (revised .#scopes (|>> {.#Item ..empty}) state)]) @@ -177,7 +177,7 @@ {try.#Failure error} {try.#Failure error}))) -(def: .public next +(def .public next (Operation Register) (extension.lifted (function (_ state) @@ -188,7 +188,7 @@ {.#End} (exception.except ..no_scope []))))) -(def: .public environment +(def .public environment (-> Scope (Environment Variable)) (|>> (the [.#captured .#mappings]) (list#each (function (_ [_ [_ ref]]) ref)))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux index 8a2fbd7d5..25ba7b1bd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux @@ -26,10 +26,10 @@ {#Frac Frac} {#Text Text})) -(def: .public equivalence +(def .public equivalence (Equivalence Simple) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Unit} {#Unit}] true @@ -47,7 +47,7 @@ _ false)))) -(def: .public (format it) +(def .public (format it) (Format Simple) (case it {#Unit} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux index dba3ad176..007289a0a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux @@ -26,7 +26,7 @@ [/// ["[0]" phase]]]]) -(def: .public (check action) +(def .public (check action) (All (_ a) (-> (Check a) (Operation a))) (function (_ (^.let stateE [bundle state])) (case (action (the .#type_context state)) @@ -37,10 +37,10 @@ {try.#Failure error} ((/.failure error) stateE)))) -(def: prefix +(def prefix (format (%.symbol (symbol ..type)) "#")) -(def: .public (existential? type) +(def .public (existential? type) (-> Type Bit) (case type {.#Primitive actual {.#End}} @@ -49,28 +49,28 @@ _ false)) -(def: (existential' module id) +(def (existential' module id) (-> Text Nat Type) {.#Primitive (format ..prefix module "#" (%.nat id)) (list)}) -(def: .public existential +(def .public existential (Operation Type) (do phase.monad [module (extension.lifted meta.current_module_name) id (extension.lifted meta.seed)] (in (..existential' module id)))) -(def: .public (expecting expected) +(def .public (expecting expected) (All (_ a) (-> Type (Operation a) (Operation a))) (extension.localized (the .#expected) (has .#expected) (function.constant {.#Some expected}))) -(def: .public fresh +(def .public fresh (All (_ a) (-> (Operation a) (Operation a))) (extension.localized (the .#type_context) (has .#type_context) (function.constant check.fresh_context))) -(def: .public (inference actualT) +(def .public (inference actualT) (-> Type (Operation Any)) (do phase.monad [module (extension.lifted meta.current_module_name) @@ -112,7 +112,7 @@ ... (in it))) ))) -(def: .public (with_var it) +(def .public (with_var it) (All (_ a) (-> (-> [check.Var Type] (Operation a)) (Operation a))) @@ -123,7 +123,7 @@ _ (..check (check.forget! @it))] (in it))) -(def: .public (inferring action) +(def .public (inferring action) (All (_ a) (-> (Operation a) (Operation [Type a]))) (<| ..with_var (function (_ [@it :it:])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux index afe5c1aa8..2682f80d8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -45,12 +45,12 @@ [#imports (List Import) #referrals (List Code)])) -(def: .public no_requirements +(def .public no_requirements Requirements [#imports (list) #referrals (list)]) -(def: .public (merge_requirements left right) +(def .public (merge_requirements left right) (-> Requirements Requirements Requirements) [#imports (list#composite (the #imports left) (the #imports right)) #referrals (list#composite (the #referrals left) (the #referrals right))]) @@ -67,7 +67,7 @@ ) (with_template [<name> <component> <phase>] - [(def: .public <name> + [(def .public <name> (All (_ anchor expression directive) (Operation anchor expression directive <phase>)) (function (_ [bundle state]) @@ -79,7 +79,7 @@ ) (with_template [<name> <component> <operation>] - [(def: .public <name> + [(def .public <name> (All (_ anchor expression directive output) (-> (<operation> output) (Operation anchor expression directive output))) @@ -92,7 +92,7 @@ [lifted_generation ..#generation (generation.Operation anchor expression directive)] ) -(def: .public (set_current_module module) +(def .public (set_current_module module) (All (_ anchor expression directive) (-> Module (Operation anchor expression directive Any))) (do phase.monad 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 a978ccd16..8bc9502fc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -96,7 +96,7 @@ [Extender extension.Extender] ) -(def: .public (state host module) +(def .public (state host module) (All (_ anchor expression directive) (-> (Host expression directive) descriptor.Module @@ -112,7 +112,7 @@ #log sequence.empty #interim_artifacts (list)]) -(def: .public empty_buffer +(def .public empty_buffer Buffer sequence.empty) @@ -121,7 +121,7 @@ <set> <get> <get_type> <exception>] [(exception: .public <exception>) - (def: .public <with_declaration> + (def .public <with_declaration> (All (_ anchor expression directive output) <with_type>) (function (_ body) (function (_ [bundle state]) @@ -133,7 +133,7 @@ {try.#Failure error} {try.#Failure error})))) - (def: .public <get> + (def .public <get> (All (_ anchor expression directive) (Operation anchor expression directive <get_type>)) (function (_ (^.let stateE [bundle state])) @@ -144,7 +144,7 @@ {.#None} (exception.except <exception> [])))) - (def: .public (<set> value) + (def .public (<set> value) (All (_ anchor expression directive) (-> <get_type> (Operation anchor expression directive Any))) (function (_ [bundle state]) @@ -166,20 +166,20 @@ set_buffer buffer (Buffer directive) no_active_buffer] ) -(def: .public get_registry +(def .public get_registry (All (_ anchor expression directive) (Operation anchor expression directive Registry)) (function (_ (^.let stateE [bundle state])) {try.#Success [stateE (the #registry state)]})) -(def: .public (set_registry value) +(def .public (set_registry value) (All (_ anchor expression directive) (-> Registry (Operation anchor expression directive Any))) (function (_ [bundle state]) {try.#Success [[bundle (has #registry value state)] []]})) -(def: .public next +(def .public next (All (_ anchor expression directive) (Operation anchor expression directive Nat)) (do phase.monad @@ -187,22 +187,22 @@ _ (extension.update (revised #counter ++))] (in count))) -(def: .public (symbol prefix) +(def .public (symbol prefix) (All (_ anchor expression directive) (-> Text (Operation anchor expression directive Text))) (at phase.monad each (|>> %.nat (format prefix)) ..next)) -(def: .public (enter_module module) +(def .public (enter_module module) (All (_ anchor expression directive) (-> descriptor.Module (Operation anchor expression directive Any))) (extension.update (has #module module))) -(def: .public module +(def .public module (All (_ anchor expression directive) (Operation anchor expression directive descriptor.Module)) (extension.read (the #module))) -(def: .public (evaluate! label code) +(def .public (evaluate! label code) (All (_ anchor expression directive) (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any))) (function (_ (^.let state+ [bundle state])) @@ -213,7 +213,7 @@ {try.#Failure error} (exception.except ..cannot_interpret [error])))) -(def: .public (execute! code) +(def .public (execute! code) (All (_ anchor expression directive) (-> directive (Operation anchor expression directive Any))) (function (_ (^.let state+ [bundle state])) @@ -224,7 +224,7 @@ {try.#Failure error} (exception.except ..cannot_interpret error)))) -(def: .public (define! context custom code) +(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]))) (function (_ (^.let stateE [bundle state])) @@ -235,7 +235,7 @@ {try.#Failure error} (exception.except ..cannot_interpret error)))) -(def: .public (save! artifact_id custom code) +(def .public (save! artifact_id custom code) (All (_ anchor expression directive) (-> artifact.ID (Maybe Text) directive (Operation anchor expression directive Any))) (do [! phase.monad] @@ -251,7 +251,7 @@ (phase.except ..no_buffer_for_saving_code [artifact_id])))) (with_template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>] - [(`` (def: .public (<name> it (~~ (template.spliced <inputs>)) dependencies) + [(`` (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))) (function (_ (^.let stateE [bundle state])) @@ -274,7 +274,7 @@ "Module" (symbol.module name) "Known Definitions" (exception.listing product.left known_definitions))) -(def: .public (remember archive name) +(def .public (remember archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive unit.ID))) (function (_ (^.let stateE [bundle state])) @@ -293,7 +293,7 @@ {.#Some id} {try.#Success [stateE [@module id]]}))))) -(def: .public (definition archive name) +(def .public (definition archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)]))) (function (_ (^.let stateE [bundle state])) @@ -314,7 +314,7 @@ (exception: .public no_context) -(def: .public (module_id module archive) +(def .public (module_id module archive) (All (_ anchor expression directive) (-> descriptor.Module Archive (Operation anchor expression directive module.ID))) (function (_ (^.let stateE [bundle state])) @@ -322,7 +322,7 @@ [@module (archive.id module archive)] (in [stateE @module])))) -(def: .public (context archive) +(def .public (context archive) (All (_ anchor expression directive) (-> Archive (Operation anchor expression directive unit.ID))) (function (_ (^.let stateE [bundle state])) @@ -335,7 +335,7 @@ [@module (archive.id (the #module state) archive)] (in [stateE [@module id]]))))) -(def: .public (with_context @artifact body) +(def .public (with_context @artifact body) (All (_ anchor expression directive a) (-> artifact.ID (Operation anchor expression directive a) @@ -346,7 +346,7 @@ (in [[bundle' (has #context (the #context state) state')] output])))) -(def: .public (with_registry_shift shift body) +(def .public (with_registry_shift shift body) (All (_ anchor expression directive a) (-> Nat (Operation anchor expression directive a) @@ -357,7 +357,7 @@ (in [[bundle' (has #registry_shift (the #registry_shift state) state')] output])))) -(def: .public (with_new_context archive dependencies body) +(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]))) @@ -374,7 +374,7 @@ [[@module @artifact] output]]))))) -(def: .public (log! message) +(def .public (log! message) (All (_ anchor expression directive a) (-> Text (Operation anchor expression directive Any))) (function (_ [bundle state]) @@ -382,7 +382,7 @@ (revised #log (sequence.suffix message) state)] []]})) -(def: .public (with_interim_artifacts archive body) +(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]))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index 83cf9fb35..1c621d0ff 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -40,7 +40,7 @@ (exception.report "Syntax" (%.code syntax))) -(def: variant_analysis +(def variant_analysis (template (_ analysis archive tag values) ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) [(case values @@ -50,7 +50,7 @@ _ (/complex.variant analysis tag archive (code.tuple values)))])) -(def: sum_analysis +(def sum_analysis (template (_ analysis archive lefts right? values) ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) [(case values @@ -60,7 +60,7 @@ _ (/complex.sum analysis lefts right? archive (code.tuple values)))])) -(def: case_analysis +(def case_analysis (template (_ analysis archive input branches code) ... (-> Phase Archive Code (List Code) Code (Operation Analysis)) [(case (list.pairs branches) @@ -70,7 +70,7 @@ {.#None} (//.except ..invalid [code]))])) -(def: apply_analysis +(def apply_analysis (template (_ expander analysis archive functionC argsC+) ... (-> Expander Phase Archive Code (List Code) (Operation Analysis)) [(do [! //.monad] @@ -92,7 +92,7 @@ _ (/function.apply analysis argsC+ functionT functionA archive functionC)))])) -(def: .public (phase expander) +(def .public (phase expander) (-> Expander Phase) (function (analysis archive code) (<| (let [[location code'] code]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index a16d7c410..728eb24ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -71,7 +71,7 @@ (exception: .public empty_branches) -(def: (quantified envs baseT) +(def (quantified envs baseT) (-> (List (List Type)) Type Type) (.case envs {.#End} @@ -87,7 +87,7 @@ ... type-variables or quantifications. ... This function makes it easier for "case" analysis to properly ... type-check the input with respect to the patterns. -(def: .public (tuple :it:) +(def .public (tuple :it:) (-> Type (Check [(List check.Var) Type])) (loop (again [envs (is (List (List Type)) (list)) @@ -149,7 +149,7 @@ _ (at check.monad in [(list) (..quantified envs :it:)])))) -(def: (simple_pattern_analysis type :input: location output next) +(def (simple_pattern_analysis type :input: location output next) (All (_ a) (-> Type Type Location Pattern (Operation a) (Operation [Pattern a]))) (/.with_location location (do ///.monad @@ -157,7 +157,7 @@ outputA next] (in [output outputA])))) -(def: (tuple_pattern_analysis pattern_analysis :input: sub_patterns next) +(def (tuple_pattern_analysis pattern_analysis :input: sub_patterns next) (All (_ a) (-> (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a])) Type (List Code) (Operation a) (Operation [Pattern a]))) @@ -224,7 +224,7 @@ ... body expressions. ... That is why the body must be analysed in the context of the ... pattern, and not separately. -(def: (pattern_analysis num_tags :input: pattern next) +(def (pattern_analysis num_tags :input: pattern next) (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) (.case pattern [location {.#Symbol ["" name]}] @@ -337,7 +337,7 @@ (/.except ..invalid [pattern]) )) -(def: .public (case analyse branches archive inputC) +(def .public (case analyse branches archive inputC) (-> Phase (List [Code Code]) Phase) (.case branches {.#Item [patternH bodyH] branchesT} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 231c3e374..e0c2a8b41 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -99,7 +99,7 @@ list#conjoint code.tuple)))) -(def: .public (sum analyse lefts right? archive) +(def .public (sum analyse lefts right? archive) (-> Phase Nat Bit Phase) (let [tag (/complex.tag right? lefts)] (function (again valueC) @@ -170,7 +170,7 @@ _ (/.except ..invalid_variant_type [expectedT lefts right? valueC]))))))) -(def: .public (variant analyse tag archive valueC) +(def .public (variant analyse tag archive valueC) (-> Phase Symbol Phase) (do [! ///.monad] [tag (///extension.lifted (meta.normal tag)) @@ -188,7 +188,7 @@ _ (..sum analyse lefts right? archive valueC)))) -(def: (typed_product analyse expectedT archive members) +(def (typed_product analyse expectedT archive members) (-> Phase Type Archive (List Code) (Operation Analysis)) (<| (let [! ///.monad]) (at ! each (|>> /.tuple)) @@ -219,7 +219,7 @@ _ (/.except ..cannot_analyse_tuple [expectedT members]))))) -(def: .public (product analyse archive membersC) +(def .public (product analyse archive membersC) (-> Phase Archive (List Code) (Operation Analysis)) (do [! ///.monad] [expectedT (///extension.lifted meta.expected_type)] @@ -290,7 +290,7 @@ ... records, so they must be normalized for further analysis. ... Normalization just means that all the tags get resolved to their ... canonical form (with their corresponding module identified). -(def: .public (normal pattern_matching? record) +(def .public (normal pattern_matching? record) (-> Bit (List Code) (Operation (Maybe (List [Symbol Code])))) (loop (again [input record output (is (List [Symbol Code]) @@ -314,7 +314,7 @@ _ (///#in {.#None})))) -(def: (local_binding? name) +(def (local_binding? name) (-> Text (Meta Bit)) (at meta.monad each (list.any? (list.any? (|>> product.left (text#= name)))) @@ -323,7 +323,7 @@ ... Lux already possesses the means to analyse tuples, so ... re-implementing the same functionality for records makes no sense. ... Records, thus, get transformed into tuples by ordering the elements. -(def: (order' head_k record) +(def (order' head_k record) (-> Symbol (List [Symbol Code]) (Operation (Maybe [Nat (List Code) Type]))) (do [! ///.monad] [slotH' (///extension.lifted @@ -363,7 +363,7 @@ {try.#Failure error} (in {.#None})))) -(def: .public (order pattern_matching? record) +(def .public (order pattern_matching? record) (-> Bit (List [Symbol Code]) (Operation (Maybe [Nat (List Code) Type]))) (case record ... empty_record = empty_tuple = unit/any = [] @@ -385,7 +385,7 @@ _ (order' head_k record)))) -(def: .public (record analyse archive members) +(def .public (record analyse archive members) (-> Phase Archive (List Code) (Operation Analysis)) (case members (pattern (list)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index 4cc07333a..3b3a319d3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -53,7 +53,7 @@ (format (%.nat idx) " " (%.code argC)))) (text.interposed text.new_line)))) -(def: .public (function analyse function_name arg_name archive body) +(def .public (function analyse function_name arg_name archive body) (-> Phase Text Text Phase) (do [! ///.monad] [expectedT (///extension.lifted meta.expected_type)] @@ -134,7 +134,7 @@ (/.failure "") ))))) -(def: .public (apply analyse argsC+ :function: functionA archive functionC) +(def .public (apply analyse argsC+ :function: functionA archive functionC) (-> Phase (List Code) Type Analysis Phase) (|> (/inference.general archive analyse :function: argsC+) (///#each (|>> product.right [functionA] /.reified)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux index 232954fff..cb4011c73 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -38,7 +38,7 @@ (exception.report "Label" (%.symbol definition))) -(def: (definition def_name) +(def (definition def_name) (-> Symbol (Operation Analysis)) (with_expansions [<return> (in (|> def_name ///reference.constant {/.#Reference}))] (do [! ///.monad] @@ -83,7 +83,7 @@ {.#Slot _} (/.except ..labels_are_not_definitions [def_name]))))) -(def: (variable var_name) +(def (variable var_name) (-> Text (Operation (Maybe Analysis))) (do [! ///.monad] [?var (/scope.variable var_name)] @@ -96,7 +96,7 @@ {.#None} (in {.#None})))) -(def: .public (reference it) +(def .public (reference it) (-> Symbol (Operation Analysis)) (case it ["" simple_name] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux index a5e7a9d08..416780c05 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux @@ -12,7 +12,7 @@ ["[1]" phase]]]]) (with_template [<name> <type> <tag>] - [(def: .public (<name> value) + [(def .public (<name> value) (-> <type> (Operation Analysis)) (do ///.monad [_ (/type.inference <type>)] @@ -26,7 +26,7 @@ [text .Text /simple.#Text] ) -(def: .public unit +(def .public unit (Operation Analysis) (do ///.monad [_ (/type.inference .Any)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux index 41f270408..6669776fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux @@ -43,7 +43,7 @@ (type: Eval (-> Type Code (Meta Any))) -(def: (meta_eval archive bundle compiler_eval) +(def (meta_eval archive bundle compiler_eval) (-> Archive ///analysis.Bundle evaluation.Eval Eval) (function (_ type code lux) @@ -54,7 +54,7 @@ {try.#Failure error} {try.#Failure error}))) -(def: (requiring phase archive expansion) +(def (requiring phase archive expansion) (All (_ anchor expression directive) (-> (Phase anchor expression directive) Archive (List Code) (Operation anchor expression directive /.Requirements))) @@ -75,7 +75,7 @@ {try.#Failure error}))))) (with_expansions [<lux_def_module> (these [|form_location| {.#Form (list.partial [|text_location| {.#Text "lux def module"}] annotations)}])] - (def: .public (phase wrapper expander) + (def .public (phase wrapper expander) (-> //.Wrapper Expander Phase) (let [analysis (//analysis.phase expander)] (function (again archive code) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index f04b95a6e..2f7e4ad0f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -29,12 +29,12 @@ (type: .public (Extension a) [Name (List a)]) -(def: .public equivalence +(def .public equivalence (All (_ a) (-> (Equivalence a) (Equivalence (Extension a)))) (|>> list.equivalence (product.equivalence text.equivalence))) -(def: .public hash +(def .public hash (All (_ a) (-> (Hash a) (Hash (Extension a)))) (|>> list.hash (product.hash text.hash))) @@ -48,7 +48,7 @@ (type: .public (Bundle s i o) <Bundle>)) -(def: .public empty +(def .public empty Bundle (dictionary.empty text.hash)) @@ -94,7 +94,7 @@ (type: .public (Extender s i o) (-> Any (Handler s i o))) -(def: .public (install extender name handler) +(def .public (install extender name handler) (All (_ s i o) (-> (Extender s i o) Name (Handler s i o) (Operation s i o Any))) (function (_ [bundle state]) @@ -106,7 +106,7 @@ {try.#Failure _} (exception.except ..cannot_overwrite name)))) -(def: .public (with extender extensions) +(def .public (with extender extensions) (All (_ s i o) (-> Extender (Bundle s i o) (Operation s i o Any))) (|> extensions @@ -116,7 +116,7 @@ (..install extender extension handle)) []))) -(def: .public (apply archive phase [name parameters]) +(def .public (apply archive phase [name parameters]) (All (_ s i o) (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) (function (_ (^.let stateE [bundle state])) @@ -128,7 +128,7 @@ {.#None} (exception.except ..unknown [name bundle])))) -(def: .public (localized get set transform) +(def .public (localized get set transform) (All (_ s s' i o v) (-> (-> s s') (-> s' s s) (-> s' s') (-> (Operation s i o v) (Operation s i o v)))) @@ -142,7 +142,7 @@ {try.#Failure error} {try.#Failure error}))))) -(def: .public (temporary transform) +(def .public (temporary transform) (All (_ s i o v) (-> (-> s s) (-> (Operation s i o v) (Operation s i o v)))) @@ -155,24 +155,24 @@ {try.#Failure error} {try.#Failure error})))) -(def: .public (with_state state) +(def .public (with_state state) (All (_ s i o v) (-> s (-> (Operation s i o v) (Operation s i o v)))) (..temporary (function.constant state))) -(def: .public (read get) +(def .public (read get) (All (_ s i o v) (-> (-> s v) (Operation s i o v))) (function (_ [bundle state]) {try.#Success [[bundle state] (get state)]})) -(def: .public (update transform) +(def .public (update transform) (All (_ s i o) (-> (-> s s) (Operation s i o Any))) (function (_ [bundle state]) {try.#Success [[bundle (transform state)] []]})) -(def: .public (lifted action) +(def .public (lifted action) (All (_ s i o v) (-> (//.Operation s v) (Operation s i o v))) (function (_ [bundle state]) @@ -183,7 +183,7 @@ {try.#Failure error} {try.#Failure error}))) -(def: .public (up it) +(def .public (up it) (All (_ s i o v) (-> (Operation s i o v) (//.Operation s v))) (function (_ state) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux index 24f8bc5bf..e11214c8b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis.lux @@ -10,7 +10,7 @@ ["[0]" / ["[1][0]" lux]]) -(def: .public (bundle eval host_specific) +(def .public (bundle eval host_specific) (-> Eval Bundle Bundle) (dictionary.composite host_specific (/lux.bundle eval))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux index 6ff29f42e..962ad9aea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/common_lisp.lux @@ -28,7 +28,7 @@ [/// ["[0]" phase]]]]]]) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "common_lisp") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux index 8342ce912..71082e284 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/js.lux @@ -26,7 +26,7 @@ [/// ["[0]" phase]]]]]) -(def: array::new +(def array::new Handler (custom [<code>.any @@ -41,7 +41,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<code>.any @@ -56,7 +56,7 @@ _ (analysis/type.inference Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <code>.any <code>.any) @@ -73,7 +73,7 @@ _ (analysis/type.inference :read:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <code>.any <code>.any <code>.any) @@ -92,7 +92,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <code>.any <code>.any) @@ -109,7 +109,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -120,7 +120,7 @@ (bundle.install "delete" array::delete) ))) -(def: object::new +(def object::new Handler (custom [(all <>.and <code>.any (<code>.tuple (<>.some <code>.any))) @@ -132,7 +132,7 @@ _ (analysis/type.inference .Any)] (in {analysis.#Extension extension (list.partial constructorA inputsA)})))])) -(def: object::get +(def object::get Handler (custom [(all <>.and <code>.text <code>.any) @@ -144,7 +144,7 @@ (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <code>.text <code>.any (<code>.tuple (<>.some <code>.any))) @@ -158,7 +158,7 @@ objectA inputsA)})))])) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -171,7 +171,7 @@ (bundle.install "undefined?" (/.unary Any Bit)) ))) -(def: js::constant +(def js::constant Handler (custom [<code>.text @@ -180,7 +180,7 @@ [_ (analysis/type.inference Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: js::apply +(def js::apply Handler (custom [(all <>.and <code>.any (<code>.tuple (<>.some <code>.any))) @@ -192,7 +192,7 @@ _ (analysis/type.inference Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: js::type_of +(def js::type_of Handler (custom [<code>.any @@ -203,7 +203,7 @@ _ (analysis/type.inference .Text)] (in {analysis.#Extension extension (list objectA)})))])) -(def: js::function +(def js::function Handler (custom [(all <>.and <code>.nat <code>.any) @@ -217,7 +217,7 @@ (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "js") (|> bundle.empty 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 e285ff15a..645d0366c 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 @@ -176,7 +176,7 @@ (exception.report "Class" (%.text class))) -(def: (ensure_fresh_class! class_loader name) +(def (ensure_fresh_class! class_loader name) (-> java/lang/ClassLoader External (Operation Any)) (do phase.monad [class (phase.lifted (reflection!.load class_loader name))] @@ -186,20 +186,20 @@ reflection!.deprecated? not)))) -(def: reflection +(def reflection (All (_ category) (-> (Type (<| Return' Value' category)) Text)) (|>> jvm.reflection reflection.reflection)) -(def: signature (|>> jvm.signature signature.signature)) +(def signature (|>> jvm.signature signature.signature)) -(def: object_class +(def object_class External "java.lang.Object") ... TODO: Get rid of this with_template block and use the definition in ... lux/ffi.jvm.lux ASAP (with_template [<name> <class>] - [(def: .public <name> + [(def .public <name> .Type {.#Primitive <class> {.#End}})] @@ -230,7 +230,7 @@ [#class External #member Text])) -(def: member +(def member (Parser Member) (all <>.and <code>.text <code>.text)) @@ -299,7 +299,7 @@ [unknown_type_var] ) -(def: bundle::conversion +(def bundle::conversion Bundle (<| (///bundle.prefix "conversion") (|> ///bundle.empty @@ -329,7 +329,7 @@ ))) (with_template [<name> <prefix> <type>] - [(def: <name> + [(def <name> Bundle (<| (///bundle.prefix (reflection.reflection <prefix>)) (|> ///bundle.empty @@ -353,7 +353,7 @@ ) (with_template [<name> <prefix> <type>] - [(def: <name> + [(def <name> Bundle (<| (///bundle.prefix (reflection.reflection <prefix>)) (|> ///bundle.empty @@ -370,7 +370,7 @@ [bundle::double reflection.double ..double] ) -(def: bundle::char +(def bundle::char Bundle (<| (///bundle.prefix (reflection.reflection reflection.char)) (|> ///bundle.empty @@ -378,7 +378,7 @@ (///bundle.install "<" (//lux.binary ..char ..char Bit)) ))) -(def: .public boxes +(def .public boxes (Dictionary External [External (Type Primitive)]) (|> (list [(reflection.reflection reflection.boolean) [box.boolean jvm.boolean]] [(reflection.reflection reflection.byte) [box.byte jvm.byte]] @@ -390,11 +390,11 @@ [(reflection.reflection reflection.char) [box.char jvm.char]]) (dictionary.of_list text.hash))) -(def: lux_array_type +(def lux_array_type (template (_ :read: :write:) [{.#Primitive (static array.type_name) (list {.#Apply :write: {.#Apply :read: _Mutable}})}])) -(def: (jvm_type luxT) +(def (jvm_type luxT) (-> .Type (Operation (Type Value))) (case luxT {.#Named name anonymousT} @@ -446,7 +446,7 @@ _ (/////analysis.except ..non_jvm_type luxT))) -(def: (jvm_array_type objectT) +(def (jvm_array_type objectT) (-> .Type (Operation (Type Array))) (do phase.monad [objectJ (jvm_type objectT)] @@ -455,7 +455,7 @@ (<text>.result parser.array) phase.lifted))) -(def: (primitive_array_length_handler primitive_type) +(def (primitive_array_length_handler primitive_type) (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args @@ -471,7 +471,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: array::length::object +(def array::length::object Handler (function (_ extension_name analyse archive args) (case args @@ -493,7 +493,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: (new_primitive_array_handler primitive_type) +(def (new_primitive_array_handler primitive_type) (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args @@ -508,7 +508,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: array::new::object +(def array::new::object Handler (function (_ extension_name analyse archive args) (case args @@ -530,7 +530,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: (check_parameter objectT) +(def (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT (pattern (lux_array_type elementT _)) @@ -591,7 +591,7 @@ _ (/////analysis.except ..non_parameter objectT))) -(def: (check_jvm objectT) +(def (check_jvm objectT) (-> .Type (Operation (Type Value))) (case objectT {.#Primitive name {.#End}} @@ -660,7 +660,7 @@ (check_parameter objectT))) (with_template [<name> <category> <parser>] - [(def: .public (<name> mapping typeJ) + [(def .public (<name> mapping typeJ) (-> Mapping (Type <category>) (Operation .Type)) (case (|> typeJ ..signature (<text>.result (<parser> mapping))) {try.#Success check} @@ -675,7 +675,7 @@ [reflection_return Return luxT.return] ) -(def: (check_object objectT) +(def (check_object objectT) (-> .Type (Operation [External .Type])) (do [! phase.monad] [:object: (check_jvm objectT) @@ -686,13 +686,13 @@ [:object: (reflection_type luxT.fresh :object:)] (phase#in [name :object:]))))) -(def: (check_return type) +(def (check_return type) (-> .Type (Operation (Type Return))) (if (same? .Any type) (phase#in jvm.void) (check_jvm type))) -(def: (read_primitive_array_handler lux_type jvm_type) +(def (read_primitive_array_handler lux_type jvm_type) (-> .Type (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args @@ -709,7 +709,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) -(def: array::read::object +(def array::read::object Handler (function (_ extension_name analyse archive args) (case args @@ -734,7 +734,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) -(def: (write_primitive_array_handler lux_type jvm_type) +(def (write_primitive_array_handler lux_type jvm_type) (-> .Type (Type Primitive) Handler) (let [array_type {.#Primitive (|> (jvm.array jvm_type) ..reflection) (list)}] @@ -756,7 +756,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)]))))) -(def: array::write::object +(def array::write::object Handler (function (_ extension_name analyse archive args) (case args @@ -784,7 +784,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)])))) -(def: bundle::array +(def bundle::array Bundle (<| (///bundle.prefix "array") (|> ///bundle.empty @@ -834,7 +834,7 @@ (///bundle.install "object" array::write::object)))) ))) -(def: object::null +(def object::null Handler (function (_ extension_name analyse archive args) (case args @@ -848,7 +848,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 0 (list.size args)])))) -(def: object::null? +(def object::null? Handler (function (_ extension_name analyse archive args) (case args @@ -863,7 +863,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: object::synchronized +(def object::synchronized Handler (function (_ extension_name analyse archive args) (case args @@ -878,7 +878,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) -(def: (object::throw class_loader) +(def (object::throw class_loader) (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args @@ -898,7 +898,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: (object::class class_loader) +(def (object::class class_loader) (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args @@ -917,7 +917,7 @@ _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: (object::instance? class_loader) +(def (object::instance? class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and <code>.text <code>.any) @@ -933,7 +933,7 @@ (in {/////analysis.#Extension extension_name (list (/////analysis.text sub_class) objectA)}) (/////analysis.except cannot_possibly_be_an_instance (format sub_class " !<= " object_class)))))])) -(def: (class_candidate_parents class_loader source_name fromT target_name target_class) +(def (class_candidate_parents class_loader source_name fromT target_name target_class) (-> java/lang/ClassLoader External .Type External (java/lang/Class java/lang/Object) (Operation (List [[Text .Type] Bit]))) (do [! phase.monad] [source_class (phase.lifted (reflection!.load class_loader source_name)) @@ -956,7 +956,7 @@ (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))} (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))))))) -(def: (inheritance_candidate_parents class_loader fromT target_class toT fromC) +(def (inheritance_candidate_parents class_loader fromT target_class toT fromC) (-> java/lang/ClassLoader .Type (java/lang/Class java/lang/Object) .Type Code (Operation (List [[Text .Type] Bit]))) (case fromT (pattern {.#Primitive _ (list.partial self_classT super_classT super_interfacesT+)}) @@ -972,7 +972,7 @@ _ (/////analysis.except ..cannot_cast [fromT toT fromC]))) -(def: (object::cast class_loader) +(def (object::cast class_loader) (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args @@ -1036,7 +1036,7 @@ _ (/////analysis.except ///.invalid_syntax [extension_name %.code args])))) -(def: (bundle::object class_loader) +(def (bundle::object class_loader) (-> java/lang/ClassLoader Bundle) (<| (///bundle.prefix "object") (|> ///bundle.empty @@ -1049,7 +1049,7 @@ (///bundle.install "cast" (object::cast class_loader)) ))) -(def: (get::static class_loader) +(def (get::static class_loader) (-> java/lang/ClassLoader Handler) (..custom [..member @@ -1069,7 +1069,7 @@ (/////analysis.text field) (/////analysis.text (..signature fieldJT)))))))])) -(def: (put::static class_loader) +(def (put::static class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..member <code>.any) @@ -1094,7 +1094,7 @@ (/////analysis.text (..signature fieldJT)) valueA)))))])) -(def: (get::virtual class_loader) +(def (get::virtual class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..member <code>.any) @@ -1119,7 +1119,7 @@ (/////analysis.text (..signature fieldJT)) objectA)))))])) -(def: (put::virtual class_loader) +(def (put::virtual class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..member <code>.any <code>.any) @@ -1157,7 +1157,7 @@ {#Special} {#Interface})) -(def: (de_aliased aliasing) +(def (de_aliased aliasing) (-> Aliasing (Type Value) (Type Value)) (function (again it) (`` (<| (case (parser.var? it) @@ -1185,7 +1185,7 @@ )) it)))) -(def: (check_method aliasing class method_name method_style inputsJT method) +(def (check_method aliasing class method_name method_style inputsJT method) (-> Aliasing (java/lang/Class java/lang/Object) Text Method_Style (List (Type Value)) java/lang/reflect/Method (Operation Bit)) (do phase.monad [parameters (|> (java/lang/reflect/Method::getGenericParameterTypes method) @@ -1219,7 +1219,7 @@ same_special? same_inputs?)))) -(def: (check_constructor aliasing class inputsJT constructor) +(def (check_constructor aliasing class inputsJT constructor) (-> Aliasing (java/lang/Class java/lang/Object) (List (Type Value)) (java/lang/reflect/Constructor java/lang/Object) (Operation Bit)) (do phase.monad [parameters (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor) @@ -1232,11 +1232,11 @@ (jvm#= expectedJC (de_aliased aliasing actualJC))) (list.zipped_2 parameters inputsJT)))))) -(def: index_parameter +(def index_parameter (-> Nat .Type) (|>> (n.* 2) ++ {.#Parameter})) -(def: (jvm_type_var_mapping owner_tvars method_tvars) +(def (jvm_type_var_mapping owner_tvars method_tvars) (-> (List Text) (List Text) [(List .Type) Mapping]) (let [jvm_tvars (list#composite owner_tvars method_tvars) lux_tvars (|> jvm_tvars @@ -1250,12 +1250,12 @@ mapping (dictionary.of_list text.hash lux_tvars)] [owner_tvarsT mapping])) -(def: (lux_class it) +(def (lux_class it) (-> (java/lang/Class java/lang/Object) (Type Class)) (jvm.class (java/lang/Class::getName it) (list))) (with_template [<name> <type> <params>] - [(`` (def: <name> + [(`` (def <name> (-> (<type> (~~ (template.spliced <params>))) (List (Type Class))) (|>> (~~ (template.symbol [<type> "::getExceptionTypes"])) (array.list {.#None}) @@ -1265,7 +1265,7 @@ [concrete_constructor_exceptions java/lang/reflect/Constructor [java/lang/Object]] ) -(def: (return_type it) +(def (return_type it) (-> java/lang/reflect/Method (Try (Type Return))) (reflection!.return (case (java/lang/reflect/Method::getGenericReturnType it) @@ -1275,7 +1275,7 @@ {.#None} (java/lang/reflect/Method::getReturnType it)))) -(def: (method_signature method_style method) +(def (method_signature method_style method) (-> Method_Style java/lang/reflect/Method (Operation Method_Signature)) (let [owner (java/lang/reflect/Method::getDeclaringClass method) owner_tvars (case method_style @@ -1323,7 +1323,7 @@ concrete_exceptions generic_exceptions)])))) -(def: (constructor_signature constructor) +(def (constructor_signature constructor) (-> (java/lang/reflect/Constructor java/lang/Object) (Operation Method_Signature)) (let [owner (java/lang/reflect/Constructor::getDeclaringClass constructor) owner_tvars (|> (java/lang/Class::getTypeParameters owner) @@ -1362,7 +1362,7 @@ {#Hint Method_Signature})) (with_template [<name> <tag>] - [(def: <name> + [(def <name> (-> Evaluation (Maybe Method_Signature)) (|>> (pipe.case {<tag> output} @@ -1376,7 +1376,7 @@ ) (with_template [<name> <type> <method>] - [(def: <name> + [(def <name> (-> <type> (List (Type Var))) (|>> <method> (array.list {.#None}) @@ -1387,13 +1387,13 @@ [method_type_variables java/lang/reflect/Method java/lang/reflect/Method::getTypeParameters] ) -(def: (aliasing expected actual) +(def (aliasing expected actual) (-> (List (Type Var)) (List (Type Var)) Aliasing) (|> (list.zipped_2 (list#each parser.name actual) (list#each parser.name expected)) (dictionary.of_list text.hash))) -(def: (family_tree' it) +(def (family_tree' it) (-> (java/lang/Class java/lang/Object) (List (java/lang/Class java/lang/Object))) (let [interfaces (array.list {.#None} (java/lang/Class::getInterfaces it)) @@ -1408,7 +1408,7 @@ list#conjoint (list.partial it)))) -(def: family_tree +(def family_tree (-> (java/lang/Class java/lang/Object) (List (java/lang/Class java/lang/Object))) (|>> ..family_tree' @@ -1418,7 +1418,7 @@ (dictionary.empty text.hash)) dictionary.values)) -(def: (all_declared_methods it) +(def (all_declared_methods it) (-> (java/lang/Class java/lang/Object) (List java/lang/reflect/Method)) (|> it @@ -1426,7 +1426,7 @@ (list#each (|>> java/lang/Class::getDeclaredMethods (array.list {.#None}))) list#conjoint)) -(def: (method_candidate allow_inheritance? class_loader actual_class_tvars class_name actual_method_tvars method_name method_style inputsJT) +(def (method_candidate allow_inheritance? class_loader actual_class_tvars class_name actual_method_tvars method_name method_style inputsJT) (-> Bit java/lang/ClassLoader (List (Type Var)) External (List (Type Var)) Text Method_Style (List (Type Value)) (Operation Method_Signature)) (do [! phase.monad] [class (phase.lifted (reflection!.load class_loader class_name)) @@ -1458,10 +1458,10 @@ (in method) (/////analysis.except ..too_many_candidates [actual_class_tvars class_name method_name actual_method_tvars inputsJT (list.partial method alternatives)]))))) -(def: constructor_method +(def constructor_method "<init>") -(def: (constructor_candidate class_loader actual_class_tvars class_name actual_method_tvars inputsJT) +(def (constructor_candidate class_loader actual_class_tvars class_name actual_method_tvars inputsJT) (-> java/lang/ClassLoader (List (Type Var)) External (List (Type Var)) (List (Type Value)) (Operation Method_Signature)) (do [! phase.monad] [class (phase.lifted (reflection!.load class_loader class_name)) @@ -1491,7 +1491,7 @@ (/////analysis.except ..too_many_candidates [actual_class_tvars class_name ..constructor_method actual_method_tvars inputsJT candidates])))) (with_template [<name> <category> <parser>] - [(def: .public <name> + [(def .public <name> (Parser (Type <category>)) (<text>.then <parser> <code>.text))] @@ -1501,21 +1501,21 @@ [return Return parser.return] ) -(def: input +(def input (Parser (Typed Code)) (<code>.tuple (<>.and ..type <code>.any))) -(def: (decorate_inputs typesT inputsA) +(def (decorate_inputs typesT inputsA) (-> (List (Type Value)) (List Analysis) (List Analysis)) (|> inputsA (list.zipped_2 (list#each (|>> ..signature /////analysis.text) typesT)) (list#each (function (_ [type value]) (/////analysis.tuple (list type value)))))) -(def: type_vars +(def type_vars (<code>.tuple (<>.some ..var))) -(def: (invoke::static class_loader) +(def (invoke::static class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..type_vars ..member ..type_vars (<>.some ..input)) @@ -1533,7 +1533,7 @@ (/////analysis.text (..signature outputJT)) (decorate_inputs argsT argsA))})))])) -(def: (invoke::virtual class_loader) +(def (invoke::virtual class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..type_vars ..member ..type_vars <code>.any (<>.some ..input)) @@ -1558,7 +1558,7 @@ objectA (decorate_inputs argsT argsA))})))])) -(def: (invoke::special class_loader) +(def (invoke::special class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..type_vars ..member ..type_vars <code>.any (<>.some ..input)) @@ -1583,7 +1583,7 @@ objectA (decorate_inputs argsT argsA))})))])) -(def: (invoke::interface class_loader) +(def (invoke::interface class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..type_vars ..member ..type_vars <code>.any (<>.some ..input)) @@ -1612,7 +1612,7 @@ objectA (decorate_inputs argsT argsA))})))])) -(def: (invoke::constructor class_loader) +(def (invoke::constructor class_loader) (-> java/lang/ClassLoader Handler) (..custom [(all <>.and ..type_vars <code>.text ..type_vars (<>.some ..input)) @@ -1627,7 +1627,7 @@ (in {/////analysis.#Extension extension_name (list.partial (/////analysis.text (..signature (jvm.class class (list)))) (decorate_inputs argsT argsA))})))])) -(def: (bundle::member class_loader) +(def (bundle::member class_loader) (-> java/lang/ClassLoader Bundle) (<| (///bundle.prefix "member") (|> ///bundle.empty @@ -1652,32 +1652,32 @@ (type: .public (Annotation_Parameter a) [Text a]) -(def: annotation_parameter +(def annotation_parameter (Parser (Annotation_Parameter Code)) (<code>.tuple (<>.and <code>.text <code>.any))) (type: .public (Annotation a) [Text (List (Annotation_Parameter a))]) -(def: .public annotation +(def .public annotation (Parser (Annotation Code)) (<code>.form (<>.and <code>.text (<>.some ..annotation_parameter)))) -(def: .public argument +(def .public argument (Parser Argument) (<code>.tuple (<>.and <code>.text ..type))) -(def: (annotation_parameter_analysis [name value]) +(def (annotation_parameter_analysis [name value]) (-> (Annotation_Parameter Analysis) Analysis) (/////analysis.tuple (list (/////analysis.text name) value))) -(def: (annotation_analysis [name parameters]) +(def (annotation_analysis [name parameters]) (-> (Annotation Analysis) Analysis) (/////analysis.tuple (list.partial (/////analysis.text name) (list#each annotation_parameter_analysis parameters)))) (with_template [<name> <category>] - [(def: <name> + [(def <name> (-> (Type <category>) Analysis) (|>> ..signature /////analysis.text))] @@ -1687,18 +1687,18 @@ [return_analysis Return] ) -(def: (typed_analysis [type term]) +(def (typed_analysis [type term]) (-> (Typed Analysis) Analysis) (/////analysis.tuple (list (value_analysis type) term))) -(def: (argument_analysis [argument argumentJT]) +(def (argument_analysis [argument argumentJT]) (-> Argument Analysis) (/////analysis.tuple (list (/////analysis.text argument) (value_analysis argumentJT)))) (with_template [<name> <only> <methods>] - [(def: (<name> [type class]) + [(def (<name> [type class]) (-> [(Type Class) (java/lang/Class java/lang/Object)] (Try (List [(Type Class) Text (Type Method)]))) (|> class @@ -1734,10 +1734,10 @@ ..all_declared_methods] ) -(def: jvm_package_separator ".") +(def jvm_package_separator ".") (with_template [<name> <methods>] - [(def: (<name> class_loader) + [(def (<name> class_loader) (-> java/lang/ClassLoader (List (Type Class)) (Try (List [(Type Class) Text (Type Method)]))) (|>> (monad.each try.monad (function (_ type) (|> type @@ -1776,12 +1776,12 @@ (type: .public Finality Bit) (type: .public Strictness Bit) -(def: .public public_tag "public") -(def: .public private_tag "private") -(def: .public protected_tag "protected") -(def: .public default_tag "default") +(def .public public_tag "public") +(def .public private_tag "private") +(def .public protected_tag "protected") +(def .public default_tag "default") -(def: .public visibility' +(def .public visibility' (<text>.Parser Visibility) (all <>.or (<text>.this ..public_tag) @@ -1790,11 +1790,11 @@ (<text>.this ..default_tag) )) -(def: .public visibility +(def .public visibility (Parser Visibility) (<text>.then ..visibility' <code>.text)) -(def: .public (visibility_analysis visibility) +(def .public (visibility_analysis visibility) (-> Visibility Analysis) (/////analysis.text (case visibility {#Public} ..public_tag @@ -1805,7 +1805,7 @@ (type: Exception (Type Class)) -(def: .public parameter_types +(def .public parameter_types (-> (List (Type Var)) (Check (List [(Type Var) .Type]))) (monad.each check.monad (function (_ parameterJ) @@ -1822,9 +1822,9 @@ (Type Return) (List Exception)]) -(def: .public abstract_tag "abstract") +(def .public abstract_tag "abstract") -(def: .public abstract_method_definition +(def .public abstract_method_definition (Parser (Abstract_Method Code)) (<| <code>.form (<>.after (<code>.this_text ..abstract_tag)) @@ -1837,7 +1837,7 @@ ..return (<code>.tuple (<>.some ..class))))) -(def: (method_mapping of_class parameters) +(def (method_mapping of_class parameters) (-> Mapping (List (Type Var)) (Check Mapping)) (|> parameters ..parameter_types @@ -1845,11 +1845,11 @@ (dictionary.has (parser.name parameterJ) parameterT mapping)) of_class)))) -(def: class_mapping +(def class_mapping (-> (List (Type Var)) (Check Mapping)) (..method_mapping luxT.fresh)) -(def: .public (analyse_abstract_method analyse archive method) +(def .public (analyse_abstract_method analyse archive method) (-> Phase Archive (Abstract_Method Code) (Operation Analysis)) (let [[method_name visibility annotations vars arguments return exceptions] method] (do [! phase.monad] @@ -1884,9 +1884,9 @@ (List (Typed a)) a]) -(def: .public constructor_tag "init") +(def .public constructor_tag "init") -(def: .public constructor_definition +(def .public constructor_definition (Parser (Constructor Code)) (<| <code>.form (<>.after (<code>.this_text ..constructor_tag)) @@ -1901,7 +1901,7 @@ (<code>.tuple (<>.some ..input)) <code>.any))) -(def: .public (analyse_constructor_method analyse archive selfT mapping method) +(def .public (analyse_constructor_method analyse archive selfT mapping method) (-> Phase Archive .Type Mapping (Constructor Code) (Operation Analysis)) (let [[visibility strict_fp? annotations vars exceptions @@ -1964,9 +1964,9 @@ (List Exception) a]) -(def: .public virtual_tag "virtual") +(def .public virtual_tag "virtual") -(def: .public virtual_method_definition +(def .public virtual_method_definition (Parser (Virtual_Method Code)) (<| <code>.form (<>.after (<code>.this_text ..virtual_tag)) @@ -1992,7 +1992,7 @@ #arguments (List (Type Value)) #return (Type Return)])) -(def: .public method_declaration +(def .public method_declaration (Parser (Method_Declaration Code)) (<code>.form (all <>.and @@ -2004,7 +2004,7 @@ ..return ))) -(def: .public (analyse_virtual_method analyse archive selfT mapping method) +(def .public (analyse_virtual_method analyse archive selfT mapping method) (-> Phase Archive .Type Mapping (Virtual_Method Code) (Operation Analysis)) (let [[method_name visibility final? strict_fp? annotations vars @@ -2062,9 +2062,9 @@ (List Exception) a]) -(def: .public static_tag "static") +(def .public static_tag "static") -(def: .public static_method_definition +(def .public static_method_definition (Parser (Static_Method Code)) (<| <code>.form (<>.after (<code>.this_text ..static_tag)) @@ -2079,7 +2079,7 @@ (<code>.tuple (<>.some ..class)) <code>.any))) -(def: .public (analyse_static_method analyse archive mapping method) +(def .public (analyse_static_method analyse archive mapping method) (-> Phase Archive Mapping (Static_Method Code) (Operation Analysis)) (let [[method_name visibility strict_fp? annotations vars @@ -2136,9 +2136,9 @@ (List (Type Class)) a]) -(def: .public overriden_tag "override") +(def .public overriden_tag "override") -(def: .public overriden_method_definition +(def .public overriden_method_definition (Parser (Overriden_Method Code)) (<| <code>.form (<>.after (<code>.this_text ..overriden_tag)) @@ -2169,7 +2169,7 @@ "Expected" (%.nat expected) "Actual" (%.nat actual))) -(def: (override_mapping mapping supers parent_type) +(def (override_mapping mapping supers parent_type) (-> Mapping (List (Type Class)) (Type Class) (Operation (List [Text .Type]))) (let [[parent_name parent_parameters] (parser.read_class parent_type)] (case (list.one (function (_ super) @@ -2195,7 +2195,7 @@ {.#None} (phase.lifted (exception.except ..unknown_super [parent_name supers]))))) -(def: .public (with_override_mapping supers parent_type mapping) +(def .public (with_override_mapping supers parent_type mapping) (-> (List (Type Class)) (Type Class) Mapping (Operation Mapping)) (do phase.monad [override_mapping (..override_mapping mapping supers parent_type)] @@ -2204,7 +2204,7 @@ mapping override_mapping)))) -(def: .public (hidden_method_body arity bodyA) +(def .public (hidden_method_body arity bodyA) (-> Nat Analysis Analysis) (<| /////analysis.tuple (list (/////analysis.unit)) @@ -2236,7 +2236,7 @@ (/////analysis.tuple (list forced_refencing bodyA))] (list)]})))) -(def: (with_fake_parameter#pattern it) +(def (with_fake_parameter#pattern it) (-> pattern.Pattern pattern.Pattern) (case it {pattern.#Simple _} @@ -2254,7 +2254,7 @@ {pattern.#Bind it} {pattern.#Bind (++ it)})) -(def: (with_fake_parameter it) +(def (with_fake_parameter it) (-> Analysis Analysis) (case it {/////analysis.#Simple _} @@ -2304,7 +2304,7 @@ {/////analysis.#Extension name (list#each with_fake_parameter parameters)})) -(def: .public (analyse_overriden_method analyse archive selfT mapping supers method) +(def .public (analyse_overriden_method analyse archive selfT mapping supers method) (-> Phase Archive .Type Mapping (List (Type Class)) (Overriden_Method Code) (Operation Analysis)) (let [[parent_type method_name strict_fp? annotations vars @@ -2356,13 +2356,13 @@ _ bodyA))} )))))) -(def: (matched? [sub sub_method subJT] [super super_method superJT]) +(def (matched? [sub sub_method subJT] [super super_method superJT]) (-> [(Type Class) Text (Type Method)] [(Type Class) Text (Type Method)] Bit) (and (at descriptor.equivalence = (jvm.descriptor super) (jvm.descriptor sub)) (text#= super_method sub_method) (jvm#= superJT subJT))) -(def: (mismatched_methods super_set sub_set) +(def (mismatched_methods super_set sub_set) (-> (List [(Type Class) Text (Type Method)]) (List [(Type Class) Text (Type Method)]) (List [(Type Class) Text (Type Method)])) @@ -2382,7 +2382,7 @@ "Actual (amount)" (%.nat (list.size actual)) "Actual (parameters)" (exception.listing ..signature actual))) -(def: (super_aliasing class_loader class) +(def (super_aliasing class_loader class) (-> java/lang/ClassLoader (Type Class) (Operation Aliasing)) (do phase.monad [.let [[name actual_parameters] (parser.read_class class)] @@ -2403,13 +2403,13 @@ mapping)) alias.fresh))))) -(def: (anonymous_class_name module id) +(def (anonymous_class_name module id) (-> Module Nat Text) (let [global (text.replaced .module_separator ..jvm_package_separator module) local (format "anonymous-class" (%.nat id))] (format global ..jvm_package_separator local))) -(def: .public (require_complete_method_concretion class_loader supers methods) +(def .public (require_complete_method_concretion class_loader supers methods) (-> java/lang/ClassLoader (List (Type Class)) (List (Overriden_Method Code)) (Operation Any)) (do [! phase.monad] [required_abstract_methods (phase.lifted (all_abstract_methods class_loader supers)) @@ -2457,10 +2457,10 @@ {#Overriden_Method (..Overriden_Method a)} {#Abstract_Method (..Abstract_Method a)})) -(def: class_name +(def class_name (|>> parser.read_class product.left name.internal)) -(def: (mock_class [name parameters] super interfaces fields methods modifier) +(def (mock_class [name parameters] super interfaces fields methods modifier) (-> Declaration (Type Class) (List (Type Class)) (List (Resource field.Field)) (List (Resource method.Method)) (Modifier class.Class) (Try [External Binary])) @@ -2481,7 +2481,7 @@ methods sequence.empty)))) -(def: constant::modifier +(def constant::modifier (Modifier field.Field) (all modifier#composite field.public @@ -2489,7 +2489,7 @@ field.final )) -(def: (field_definition field) +(def (field_definition field) (-> Field (Resource field.Field)) (case field ... TODO: Handle annotations. @@ -2521,7 +2521,7 @@ (field.field (modifier#composite visibility state) name #1 type sequence.empty))) -(def: method_privacy +(def method_privacy (-> ffi.Privacy (Modifier method.Method)) (|>> (pipe.case {ffi.#PublicP} method.public @@ -2529,10 +2529,10 @@ {ffi.#ProtectedP} method.protected {ffi.#DefaultP} modifier.empty))) -(def: constructor_name +(def constructor_name "<init>") -(def: (mock_value valueT) +(def (mock_value valueT) (-> (Type Value) (Bytecode Any)) (case (jvm.primitive? valueT) {.#Left classT} @@ -2551,7 +2551,7 @@ ... jvm.boolean jvm.byte jvm.short jvm.int jvm.char _.iconst_0))) -(def: (mock_return :return:) +(def (mock_return :return:) (-> (Type Return) (Bytecode Any)) (case (jvm.void? :return:) {.#Right :return:} @@ -2577,7 +2577,7 @@ ... jvm.boolean jvm.byte jvm.short jvm.int jvm.char _.ireturn))))) -(def: (mock_method super method) +(def (mock_method super method) (-> (Type Class) (Method_Definition Code) (Resource method.Method)) (case method {#Constructor [privacy strict_floating_point? annotations variables exceptions @@ -2655,7 +2655,7 @@ {.#None}) )) -(def: (mock declaration super interfaces inheritance fields methods) +(def (mock declaration super interfaces inheritance fields methods) (-> Declaration (Type Class) (List (Type Class)) (Modifier class.Class) (List ..Field) (List (Method_Definition Code)) @@ -2665,7 +2665,7 @@ (list#each (..mock_method super) methods) inheritance)) -(def: (class::anonymous class_loader host) +(def (class::anonymous class_loader host) (-> java/lang/ClassLoader runtime.Host Handler) (..custom [(all <>.and @@ -2720,14 +2720,14 @@ (/////analysis.tuple (list#each typed_analysis constructor_argsA+)) (/////analysis.tuple methodsA))})))])) -(def: (bundle::class class_loader host) +(def (bundle::class class_loader host) (-> java/lang/ClassLoader runtime.Host Bundle) (<| (///bundle.prefix "class") (|> ///bundle.empty (///bundle.install "anonymous" (class::anonymous class_loader host)) ))) -(def: .public (bundle class_loader host) +(def .public (bundle class_loader host) (-> java/lang/ClassLoader runtime.Host Bundle) (<| (///bundle.prefix "jvm") (|> ///bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux index fa08d5be0..3b58108c8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux @@ -26,19 +26,19 @@ [/// ["[0]" phase]]]]]) -(def: Nil +(def Nil (for @.lua ffi.Nil Any)) -(def: Object +(def Object (for @.lua (type (ffi.Object Any)) Any)) -(def: Function +(def Function (for @.lua ffi.Function Any)) -(def: array::new +(def array::new Handler (custom [<code>.any @@ -53,7 +53,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<code>.any @@ -68,7 +68,7 @@ _ (analysis/type.inference Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <code>.any <code>.any) @@ -85,7 +85,7 @@ _ (analysis/type.inference :read:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <code>.any <code>.any <code>.any) @@ -104,7 +104,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <code>.any <code>.any) @@ -121,7 +121,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -132,7 +132,7 @@ (bundle.install "delete" array::delete) ))) -(def: object::get +(def object::get Handler (custom [(all <>.and <code>.text <code>.any) @@ -144,7 +144,7 @@ (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <code>.text <code>.any (<code>.tuple (<>.some <code>.any))) @@ -158,7 +158,7 @@ objectA inputsA)})))])) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -169,7 +169,7 @@ ))) (with_template [<name> <fromT> <toT>] - [(def: <name> + [(def <name> Handler (custom [<code>.any @@ -184,7 +184,7 @@ [utf8::decode (array.Array (I64 Any)) Text] ) -(def: bundle::utf8 +(def bundle::utf8 Bundle (<| (bundle.prefix "utf8") (|> bundle.empty @@ -192,7 +192,7 @@ (bundle.install "decode" utf8::decode) ))) -(def: lua::constant +(def lua::constant Handler (custom [<code>.text @@ -201,7 +201,7 @@ [_ (analysis/type.inference Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: lua::apply +(def lua::apply Handler (custom [(all <>.and <code>.any (<code>.tuple (<>.some <code>.any))) @@ -213,7 +213,7 @@ _ (analysis/type.inference Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: lua::power +(def lua::power Handler (custom [(all <>.and <code>.any <code>.any) @@ -226,7 +226,7 @@ _ (analysis/type.inference Frac)] (in {analysis.#Extension extension (list powerA baseA)})))])) -(def: lua::import +(def lua::import Handler (custom [<code>.text @@ -235,7 +235,7 @@ [_ (analysis/type.inference ..Object)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: lua::function +(def lua::function Handler (custom [(all <>.and <code>.nat <code>.any) @@ -248,7 +248,7 @@ (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "lua") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index f261cbcad..f201ff72b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -35,7 +35,7 @@ [meta [archive (.only Archive)]]]]]]) -(def: .public (custom [syntax handler]) +(def .public (custom [syntax handler]) (All (_ s) (-> [(Parser s) (-> Text Phase Archive s (Operation Analysis))] @@ -48,7 +48,7 @@ {try.#Failure _} (////analysis.except ///.invalid_syntax [extension_name %.code args])))) -(def: (simple inputsT+ outputT) +(def (simple inputsT+ outputT) (-> (List Type) Type Handler) (let [num_expected (list.size inputsT+)] (function (_ extension_name analyse archive args) @@ -64,19 +64,19 @@ (in {////analysis.#Extension extension_name argsA})) (////analysis.except ///.incorrect_arity [extension_name num_expected num_actual])))))) -(def: .public (nullary valueT) +(def .public (nullary valueT) (-> Type Handler) (simple (list) valueT)) -(def: .public (unary inputT outputT) +(def .public (unary inputT outputT) (-> Type Type Handler) (simple (list inputT) outputT)) -(def: .public (binary subjectT paramT outputT) +(def .public (binary subjectT paramT outputT) (-> Type Type Type Handler) (simple (list subjectT paramT) outputT)) -(def: .public (trinary subjectT param0T param1T outputT) +(def .public (trinary subjectT param0T param1T outputT) (-> Type Type Type Type Handler) (simple (list subjectT param0T param1T) outputT)) @@ -86,7 +86,7 @@ (exception.report "Text" (%.text text))) - (def: text_char + (def text_char (Parser text.Char) (do <>.monad [raw <code>.text] @@ -94,7 +94,7 @@ 1 (in (|> raw (text.char 0) maybe.trusted)) _ (<>.failure (exception.error ..char_text_must_be_size_1 [raw]))))) - (def: lux::syntax_char_case! + (def lux::syntax_char_case! (..custom [(all <>.and <code>.any @@ -123,7 +123,7 @@ {////analysis.#Extension extension_name}))))]))) ... "lux is" represents reference/pointer equality. -(def: lux::is +(def lux::is Handler (function (_ extension_name analyse archive args) (<| typeA.with_var @@ -133,7 +133,7 @@ ... "lux try" provides a simple way to interact with the host platform's ... error_handling facilities. -(def: lux::try +(def lux::try Handler (function (_ extension_name analyse archive args) (case args @@ -150,7 +150,7 @@ _ (////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) -(def: lux::in_module +(def lux::in_module Handler (function (_ extension_name analyse archive argsC+) (case argsC+ @@ -161,7 +161,7 @@ _ (////analysis.except ///.invalid_syntax [extension_name %.code argsC+])))) -(def: (lux::type::check eval) +(def (lux::type::check eval) (-> Eval Handler) (function (_ extension_name analyse archive args) (case args @@ -176,7 +176,7 @@ _ (////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) -(def: (lux::type::as eval) +(def (lux::type::as eval) (-> Eval Handler) (function (_ extension_name analyse archive args) (case args @@ -192,7 +192,7 @@ _ (////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) -(def: (caster input output) +(def (caster input output) (-> Type Type Handler) (..custom [<code>.any @@ -206,7 +206,7 @@ (exception.report "Symbol" (%.symbol symbol))) -(def: lux::macro +(def lux::macro Handler (..custom [<code>.any @@ -230,7 +230,7 @@ (<| (typeA.expecting input_type) (phase archive valueC))))])) -(def: (bundle::lux eval) +(def (bundle::lux eval) (-> Eval Bundle) (|> ///bundle.empty (///bundle.install "syntax char case!" lux::syntax_char_case!) @@ -242,7 +242,7 @@ (///bundle.install "type check type" (..caster .Type .Type)) (///bundle.install "in-module" lux::in_module))) -(def: bundle::io +(def bundle::io Bundle (<| (///bundle.prefix "io") (|> ///bundle.empty @@ -250,10 +250,10 @@ (///bundle.install "error" (unary Text Nothing)) (///bundle.install "exit" (unary Int Nothing))))) -(def: I64* +(def I64* (type (I64 Any))) -(def: bundle::i64 +(def bundle::i64 Bundle (<| (///bundle.prefix "i64") (|> ///bundle.empty @@ -272,7 +272,7 @@ (///bundle.install "f64" (unary Int Frac)) (///bundle.install "char" (unary Int Text))))) -(def: bundle::f64 +(def bundle::f64 Bundle (<| (///bundle.prefix "f64") (|> ///bundle.empty @@ -287,7 +287,7 @@ (///bundle.install "encode" (unary Frac Text)) (///bundle.install "decode" (unary Text (type (Maybe Frac))))))) -(def: bundle::text +(def bundle::text Bundle (<| (///bundle.prefix "text") (|> ///bundle.empty @@ -300,7 +300,7 @@ (///bundle.install "clip" (trinary Nat Nat Text Text)) ))) -(def: .public (bundle eval) +(def .public (bundle eval) (-> Eval Bundle) (<| (///bundle.prefix "lux") (|> ///bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux index 5512587e7..d2f402d79 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/php.lux @@ -28,7 +28,7 @@ [/// ["[0]" phase]]]]]]) -(def: array::new +(def array::new Handler (custom [<c>.any @@ -41,7 +41,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<c>.any @@ -54,7 +54,7 @@ _ (analysis/type.infer Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <c>.any <c>.any) @@ -69,7 +69,7 @@ _ (analysis/type.infer :var:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <c>.any <c>.any <c>.any) @@ -86,7 +86,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <c>.any <c>.any) @@ -101,7 +101,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -112,19 +112,19 @@ (bundle.install "delete" array::delete) ))) -(def: Null +(def Null (for @.php ffi.Null Any)) -(def: Object +(def Object (for @.php (type (ffi.Object Any)) Any)) -(def: Function +(def Function (for @.php ffi.Function Any)) -(def: object::new +(def object::new Handler (custom [(all <>.and <c>.text (<>.some <c>.any)) @@ -134,7 +134,7 @@ _ (analysis/type.infer .Any)] (in {analysis.#Extension extension (list.partial (analysis.text constructor) inputsA)})))])) -(def: object::get +(def object::get Handler (custom [(all <>.and <c>.text <c>.any) @@ -146,7 +146,7 @@ (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <c>.text <c>.any (<>.some <c>.any)) @@ -160,7 +160,7 @@ objectA inputsA)})))])) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -171,7 +171,7 @@ (bundle.install "null?" (/.unary Any Bit)) ))) -(def: php::constant +(def php::constant Handler (custom [<c>.text @@ -180,7 +180,7 @@ [_ (analysis/type.infer Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: php::apply +(def php::apply Handler (custom [(all <>.and <c>.any (<>.some <c>.any)) @@ -192,7 +192,7 @@ _ (analysis/type.infer Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: php::pack +(def php::pack Handler (custom [(all <>.and <c>.any <c>.any) @@ -205,7 +205,7 @@ _ (analysis/type.infer Text)] (in {analysis.#Extension extension (list formatA dataA)})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "php") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux index aa2944967..96d175553 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/python.lux @@ -26,7 +26,7 @@ [/// ["[0]" phase]]]]]) -(def: array::new +(def array::new Handler (custom [<code>.any @@ -41,7 +41,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<code>.any @@ -56,7 +56,7 @@ _ (analysis/type.inference Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <code>.any <code>.any) @@ -73,7 +73,7 @@ _ (analysis/type.inference :read:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <code>.any <code>.any <code>.any) @@ -92,7 +92,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <code>.any <code>.any) @@ -109,7 +109,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -120,23 +120,23 @@ (bundle.install "delete" array::delete) ))) -(def: None +(def None (for @.python ffi.None Any)) -(def: Object +(def Object (for @.python (type (ffi.Object Any)) Any)) -(def: Function +(def Function (for @.python ffi.Function Any)) -(def: Dict +(def Dict (for @.python ffi.Dict Any)) -(def: object::get +(def object::get Handler (custom [(all <>.and <code>.text <code>.any) @@ -148,7 +148,7 @@ (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <code>.text <code>.any (<code>.tuple (<>.some <code>.any))) @@ -162,7 +162,7 @@ objectA inputsA)})))])) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -172,7 +172,7 @@ (bundle.install "none?" (/.unary Any Bit)) ))) -(def: python::constant +(def python::constant Handler (custom [<code>.text @@ -181,7 +181,7 @@ [_ (analysis/type.inference Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: python::import +(def python::import Handler (custom [<code>.text @@ -190,7 +190,7 @@ [_ (analysis/type.inference ..Object)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: python::apply +(def python::apply Handler (custom [(all <>.and <code>.any (<code>.tuple (<>.some <code>.any))) @@ -202,7 +202,7 @@ _ (analysis/type.inference Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: python::function +(def python::function Handler (custom [(all <>.and <code>.nat <code>.any) @@ -215,7 +215,7 @@ (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) -(def: python::exec +(def python::exec Handler (custom [(all <>.and <code>.any <code>.any) @@ -228,7 +228,7 @@ _ (analysis/type.inference .Any)] (in {analysis.#Extension extension (list codeA globalsA)})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "python") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux index c9e983ddd..5e2f27c47 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/r.lux @@ -28,7 +28,7 @@ [/// ["[0]" phase]]]]]]) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "r") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux index 01895a3e7..c75faf63a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/ruby.lux @@ -26,7 +26,7 @@ [/// ["[0]" phase]]]]]) -(def: array::new +(def array::new Handler (custom [<code>.any @@ -41,7 +41,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<code>.any @@ -56,7 +56,7 @@ _ (analysis/type.inference Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <code>.any <code>.any) @@ -73,7 +73,7 @@ _ (analysis/type.inference :read:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <code>.any <code>.any <code>.any) @@ -92,7 +92,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <code>.any <code>.any) @@ -109,7 +109,7 @@ _ (analysis/type.inference (type (array.Array' :read: :write:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -120,19 +120,19 @@ (bundle.install "delete" array::delete) ))) -(def: Nil +(def Nil (for @.ruby ffi.Nil Any)) -(def: Object +(def Object (for @.ruby (type (ffi.Object Any)) Any)) -(def: Function +(def Function (for @.ruby ffi.Function Any)) -(def: object::get +(def object::get Handler (custom [(all <>.and <code>.text <code>.any) @@ -144,7 +144,7 @@ (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <code>.text <code>.any (<code>.tuple (<>.some <code>.any))) @@ -158,7 +158,7 @@ objectA inputsA)})))])) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -168,7 +168,7 @@ (bundle.install "nil?" (/.unary Any Bit)) ))) -(def: ruby::constant +(def ruby::constant Handler (custom [<code>.text @@ -177,7 +177,7 @@ [_ (analysis/type.inference Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: ruby::apply +(def ruby::apply Handler (custom [(all <>.and <code>.any (<code>.tuple (<>.some <code>.any))) @@ -189,7 +189,7 @@ _ (analysis/type.inference Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: ruby::import +(def ruby::import Handler (custom [<code>.text @@ -198,7 +198,7 @@ [_ (analysis/type.inference Bit)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "ruby") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux index e0ba7f433..b76766cf7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/scheme.lux @@ -28,7 +28,7 @@ [/// ["[0]" phase]]]]]]) -(def: array::new +(def array::new Handler (custom [<c>.any @@ -41,7 +41,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list lengthA)}))))])) -(def: array::length +(def array::length Handler (custom [<c>.any @@ -54,7 +54,7 @@ _ (analysis/type.infer Nat)] (in {analysis.#Extension extension (list arrayA)}))))])) -(def: array::read +(def array::read Handler (custom [(<>.and <c>.any <c>.any) @@ -69,7 +69,7 @@ _ (analysis/type.infer :var:)] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: array::write +(def array::write Handler (custom [(all <>.and <c>.any <c>.any <c>.any) @@ -86,7 +86,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list indexA valueA arrayA)}))))])) -(def: array::delete +(def array::delete Handler (custom [(all <>.and <c>.any <c>.any) @@ -101,7 +101,7 @@ _ (analysis/type.infer (type (Array :var:)))] (in {analysis.#Extension extension (list indexA arrayA)}))))])) -(def: bundle::array +(def bundle::array Bundle (<| (bundle.prefix "array") (|> bundle.empty @@ -112,15 +112,15 @@ (bundle.install "delete" array::delete) ))) -(def: Nil +(def Nil (for @.scheme ffi.Nil Any)) -(def: Function +(def Function (for @.scheme ffi.Function Any)) -(def: bundle::object +(def bundle::object Bundle (<| (bundle.prefix "object") (|> bundle.empty @@ -128,7 +128,7 @@ (bundle.install "nil?" (/.unary Any Bit)) ))) -(def: scheme::constant +(def scheme::constant Handler (custom [<c>.text @@ -137,7 +137,7 @@ [_ (analysis/type.infer Any)] (in {analysis.#Extension extension (list (analysis.text name))})))])) -(def: scheme::apply +(def scheme::apply Handler (custom [(all <>.and <c>.any (<>.some <c>.any)) @@ -149,7 +149,7 @@ _ (analysis/type.infer Any)] (in {analysis.#Extension extension (list.partial abstractionA inputsA)})))])) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "scheme") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux index 3510a9f9e..1e2674dc4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/bundle.lux @@ -11,17 +11,17 @@ ["[0]" dictionary (.only Dictionary)]]]]] [// (.only Handler Bundle)]) -(def: .public empty +(def .public empty Bundle (dictionary.empty text.hash)) -(def: .public (install name anonymous) +(def .public (install name anonymous) (All (_ s i o) (-> Text (Handler s i o) (-> (Bundle s i o) (Bundle s i o)))) (dictionary.has name anonymous)) -(def: .public (prefix prefix) +(def .public (prefix prefix) (All (_ s i o) (-> Text (-> (Bundle s i o) (Bundle s i o)))) (|>> dictionary.entries diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index 41076ca66..960e51493 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -90,17 +90,17 @@ (type: Operation (directive.Operation Anchor (Bytecode Any) Definition)) -(def: signature (|>> type.signature signature.signature)) -(def: reflection (|>> type.reflection reflection.reflection)) +(def signature (|>> type.signature signature.signature)) +(def reflection (|>> type.reflection reflection.reflection)) (type: Declaration [Text (List (Type Var))]) -(def: declaration +(def declaration (Parser Declaration) (<code>.form (<>.and <code>.text (<>.some jvm.var)))) -(def: method_privacy +(def method_privacy (-> ffi.Privacy (Modifier method.Method)) (|>> (pipe.case {ffi.#PublicP} method.public @@ -108,7 +108,7 @@ {ffi.#ProtectedP} method.protected {ffi.#DefaultP} modifier.empty))) -(def: visibility' +(def visibility' (<text>.Parser (Modifier field.Field)) (`` (all <>.either (~~ (with_template [<label> <modifier>] @@ -119,11 +119,11 @@ ["protected" field.protected] ["default" modifier.empty]))))) -(def: visibility +(def visibility (Parser (Modifier field.Field)) (<text>.then ..visibility' <code>.text)) -(def: inheritance +(def inheritance (Parser (Modifier class.Class)) (`` (all <>.either (~~ (with_template [<label> <modifier>] @@ -133,7 +133,7 @@ ["abstract" class.abstract] ["default" modifier.empty]))))) -(def: state +(def state (Parser (Modifier field.Field)) (`` (all <>.either (~~ (with_template [<label> <modifier>] @@ -145,18 +145,18 @@ (type: Annotation Any) -(def: annotation +(def annotation (Parser Annotation) <code>.any) -(def: field_type +(def field_type (Parser (Type Value)) (<text>.then parser.value <code>.text)) (type: Constant [Text (List Annotation) (Type Value) Code]) -(def: constant +(def constant (Parser Constant) (<| <code>.form (<>.after (<code>.this_text "constant")) @@ -170,7 +170,7 @@ (type: Variable [Text (Modifier field.Field) (Modifier field.Field) Bit (List Annotation) (Type Value)]) -(def: variable +(def variable (Parser Variable) (<| <code>.form (<>.after (<code>.this_text "variable")) @@ -188,7 +188,7 @@ {#Constant Constant} {#Variable Variable})) -(def: field +(def field (Parser Field) (all <>.or ..constant @@ -203,7 +203,7 @@ {#Overriden_Method (jvm.Overriden_Method a)} {#Abstract_Method (jvm.Abstract_Method a)})) -(def: method +(def method (Parser (Method_Definition Code)) (all <>.or jvm.constructor_definition @@ -213,18 +213,18 @@ jvm.abstract_method_definition )) -(def: $Object +(def $Object (Type Class) (type.class "java.lang.Object" (list))) -(def: constant::modifier +(def constant::modifier (Modifier field.Field) (all modifier#composite field.public field.static field.final)) -(def: (field_definition field) +(def (field_definition field) (-> Field (Resource field.Field)) (case field ... TODO: Handle annotations. @@ -261,16 +261,16 @@ state) name #1 type sequence.empty))) -(def: annotation_parameter_synthesis +(def annotation_parameter_synthesis (<synthesis>.Parser (jvm.Annotation_Parameter Synthesis)) (<synthesis>.tuple (<>.and <synthesis>.text <synthesis>.any))) -(def: annotation_synthesis +(def annotation_synthesis (<synthesis>.Parser (jvm.Annotation Synthesis)) (<synthesis>.tuple (<>.and <synthesis>.text (<>.some ..annotation_parameter_synthesis)))) (with_template [<name> <type> <text>] - [(def: <name> + [(def <name> (<synthesis>.Parser (Type <type>)) (<text>.then <text> <synthesis>.text))] @@ -280,15 +280,15 @@ [return_type_synthesis Return parser.return] ) -(def: argument_synthesis +(def argument_synthesis (<synthesis>.Parser Argument) (<synthesis>.tuple (<>.and <synthesis>.text ..value_type_synthesis))) -(def: input_synthesis +(def input_synthesis (<synthesis>.Parser (Typed Synthesis)) (<synthesis>.tuple (<>.and ..value_type_synthesis <synthesis>.any))) -(def: (method_body arity) +(def (method_body arity) (-> Nat (<synthesis>.Parser Synthesis)) (<| (<>#each (function (_ [env offset inits it]) it)) (<synthesis>.function 1) @@ -300,7 +300,7 @@ <synthesis>.any) <synthesis>.any))) -(def: constructor_synthesis +(def constructor_synthesis (<synthesis>.Parser (jvm.Constructor Synthesis)) (<| <synthesis>.tuple (<>.after (<synthesis>.this_text jvm.constructor_tag)) @@ -319,7 +319,7 @@ (..method_body (list.size args)))) ))) -(def: overriden_method_synthesis +(def overriden_method_synthesis (<synthesis>.Parser (jvm.Overriden_Method Synthesis)) (<| <synthesis>.tuple (<>.after (<synthesis>.this_text jvm.overriden_tag)) @@ -339,7 +339,7 @@ (..method_body (list.size args)))) ))) -(def: virtual_method_synthesis +(def virtual_method_synthesis (<synthesis>.Parser (jvm.Virtual_Method Synthesis)) (<| <synthesis>.tuple (<>.after (<synthesis>.this_text jvm.virtual_tag)) @@ -360,7 +360,7 @@ (..method_body (list.size args)))) ))) -(def: static_method_synthesis +(def static_method_synthesis (<synthesis>.Parser (jvm.Static_Method Synthesis)) (<| <synthesis>.tuple (<>.after (<synthesis>.this_text jvm.static_tag)) @@ -379,7 +379,7 @@ (..method_body (list.size args)))) ))) -(def: abstract_method_synthesis +(def abstract_method_synthesis (<synthesis>.Parser (jvm.Abstract_Method Synthesis)) (<| <synthesis>.tuple (<>.after (<synthesis>.this_text jvm.abstract_tag)) @@ -393,7 +393,7 @@ (<synthesis>.tuple (<>.some ..class_type_synthesis)) ))) -(def: method_synthesis +(def method_synthesis (<synthesis>.Parser (Method_Definition Synthesis)) (all <>.or ..constructor_synthesis @@ -403,15 +403,15 @@ ..abstract_method_synthesis )) -(def: composite +(def composite (-> (List (Bytecode Any)) (Bytecode Any)) (|>> list.reversed (list#mix _.composite (_#in [])))) -(def: constructor_name +(def constructor_name "<init>") -(def: (method_argument lux_register argumentT jvm_register) +(def (method_argument lux_register argumentT jvm_register) (-> Register (Type Value) Register [Register (Bytecode Any)]) (case (type.primitive? argumentT) {.#Left argumentT} @@ -444,7 +444,7 @@ ... (at type.equivalence = type.double argumentT) (wrap_primitive 2 _.dload type.double)))))) -(def: .public (method_arguments offset types) +(def .public (method_arguments offset types) (-> Nat (List (Type Value)) (Bytecode Any)) (|> types list.enumeration @@ -454,7 +454,7 @@ (is [Register (Bytecode Any)] [offset (_#in [])])) product.right)) -(def: (constructor_method_generation archive super_class method) +(def (constructor_method_generation archive super_class method) (-> Archive (Type Class) (jvm.Constructor Synthesis) (Operation (Resource Method))) (<| (let [[privacy strict_floating_point? annotations method_tvars exceptions self arguments constructor_argumentsS @@ -489,7 +489,7 @@ _.return )}))))) -(def: (method_return returnT) +(def (method_return returnT) (-> (Type Return) (Bytecode Any)) (case (type.void? returnT) {.#Right returnT} @@ -527,7 +527,7 @@ ... (at type.equivalence = type.double returnT) (unwrap_primitive _.dreturn type.double))))))) -(def: (overriden_method_generation archive method) +(def (overriden_method_generation archive method) (-> Archive (jvm.Overriden_Method Synthesis) (Operation (Resource Method))) (do [! phase.monad] [.let [[super method_name strict_floating_point? annotations @@ -554,7 +554,7 @@ bodyG (method_return returnJ))})))))) -(def: (virtual_method_generation archive method) +(def (virtual_method_generation archive method) (-> Archive (jvm.Virtual_Method Synthesis) (Operation (Resource Method))) (do [! phase.monad] [.let [[method_name privacy final? strict_floating_point? annotations method_tvars @@ -581,7 +581,7 @@ bodyG (method_return returnJ))})))))) -(def: (static_method_generation archive method) +(def (static_method_generation archive method) (-> Archive (jvm.Static_Method Synthesis) (Operation (Resource Method))) (do [! phase.monad] [.let [[method_name privacy strict_floating_point? annotations method_tvars @@ -606,7 +606,7 @@ bodyG (method_return returnJ))})))))) -(def: (abstract_method_generation method) +(def (abstract_method_generation method) (-> (jvm.Abstract_Method Synthesis) (Resource Method)) (let [[name privacy annotations variables arguments return exceptions] method] @@ -618,7 +618,7 @@ (list) {.#None}))) -(def: (method_generation archive super_class method) +(def (method_generation archive super_class method) (-> Archive (Type Class) (Method_Definition Synthesis) (Operation (Resource Method))) (case method {#Constructor method} @@ -636,7 +636,7 @@ {#Abstract_Method method} (at phase.monad in (..abstract_method_generation method)))) -(def: (method_definition archive super interfaces [mapping selfT] [analyse synthesize generate]) +(def (method_definition archive super interfaces [mapping selfT] [analyse synthesize generate]) (-> Archive (Type Class) (List (Type Class)) @@ -676,10 +676,10 @@ methodG (method_generation archive super methodS')] (in [dependencies methodG])))) -(def: class_name +(def class_name (|>> parser.read_class product.left name.internal)) -(def: (mock_class [name parameters] super interfaces fields methods modifier) +(def (mock_class [name parameters] super interfaces fields methods modifier) (-> Declaration (Type Class) (List (Type Class)) (List (Resource field.Field)) (List (Resource method.Method)) (Modifier class.Class) (Try [External Binary])) @@ -700,7 +700,7 @@ methods sequence.empty)))) -(def: (mock_value valueT) +(def (mock_value valueT) (-> (Type Value) (Bytecode Any)) (case (type.primitive? valueT) {.#Left classT} @@ -719,7 +719,7 @@ ... type.boolean type.byte type.short type.int type.char _.iconst_0))) -(def: (mock_return returnT) +(def (mock_return returnT) (-> (Type Return) (Bytecode Any)) (case (type.void? returnT) {.#Right returnT} @@ -745,7 +745,7 @@ ... type.boolean type.byte type.short type.int type.char _.ireturn))))) -(def: (mock_method super method) +(def (mock_method super method) (-> (Type Class) (Method_Definition Code) (Resource method.Method)) (case method {#Constructor [privacy strict_floating_point? annotations variables exceptions @@ -823,7 +823,7 @@ {.#None}) )) -(def: (mock declaration super interfaces inheritance fields methods) +(def (mock declaration super interfaces inheritance fields methods) (-> Declaration (Type Class) (List (Type Class)) (Modifier class.Class) (List ..Field) (List (Method_Definition Code)) @@ -834,7 +834,7 @@ inheritance)) (with_template [<name> <type> <parser>] - [(def: <name> + [(def <name> (Parser <type>) (do [! <>.monad] [raw <code>.text] @@ -843,7 +843,7 @@ [class_declaration [External (List (Type Var))] parser.declaration'] ) -(def: (save_class! name bytecode dependencies) +(def (save_class! name bytecode dependencies) (-> Text Binary (Set unit.ID) (Operation Any)) (directive.lifted_generation (do [! phase.monad] @@ -854,7 +854,7 @@ _ (generation.log! (format "JVM Class " name))] (in [])))) -(def: jvm::class +(def jvm::class (Handler Anchor (Bytecode Any) Definition) (/.custom [(all <>.and @@ -919,7 +919,7 @@ _ (..save_class! name bytecode all_dependencies)] (in directive.no_requirements)))])) -(def: (method_declaration (open "/[0]")) +(def (method_declaration (open "/[0]")) (-> (jvm.Method_Declaration Code) (Resource Method)) (let [type (type.method [/#type_variables /#arguments /#return /#exceptions])] (method.method (all modifier#composite @@ -930,7 +930,7 @@ (list) {.#None}))) -(def: jvm::class::interface +(def jvm::class::interface (Handler Anchor (Bytecode Any) Definition) (/.custom [(all <>.and @@ -968,7 +968,7 @@ (import java/lang/ClassLoader "[1]::[0]") -(def: .public (bundle class_loader extender) +(def .public (bundle class_loader extender) (-> java/lang/ClassLoader Extender (Bundle Anchor (Bytecode Any) Definition)) (<| (bundle.prefix "jvm") (|> bundle.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 47b487dea..a8117080a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -56,7 +56,7 @@ [dependency ["[1]/[0]" artifact]]]]]]]]) -(def: .public (custom [syntax handler]) +(def .public (custom [syntax handler]) (All (_ anchor expression directive s) (-> [(Parser s) (-> Text @@ -73,13 +73,13 @@ {try.#Failure error} (phase.except ///.invalid_syntax [extension_name %.code inputs])))) -(def: (context [@module @artifact]) +(def (context [@module @artifact]) (-> unit.ID unit.ID) ... TODO: Find a better way that doesn't rely on clever tricks. [@module (n.- (++ @artifact) 0)]) ... TODO: Inline "evaluate!'" into "evaluate!" ASAP -(def: (evaluate!' archive generate code//type codeS) +(def (evaluate!' archive generate code//type codeS) (All (_ anchor expression directive) (-> Archive (/////generation.Phase anchor expression directive) @@ -95,7 +95,7 @@ codeV (/////generation.evaluate! (..context [@module id]) [{.#None} codeG])] (in [code//type codeG codeV])))) -(def: .public (evaluate! archive type codeC) +(def .public (evaluate! archive type codeC) (All (_ anchor expression directive) (-> Archive Type Code (Operation anchor expression directive [Type expression Any]))) (do phase.monad @@ -113,7 +113,7 @@ (evaluate!' archive generate type codeS))) ... TODO: Inline "definition'" into "definition" ASAP -(def: (definition' archive generate [module name] code//type codeS) +(def (definition' archive generate [module name] code//type codeS) (All (_ anchor expression directive) (-> Archive (/////generation.Phase anchor expression directive) @@ -140,7 +140,7 @@ _ (/////generation.save! @self {.#None} directive)] (in [code//type codeG value])))) -(def: (definition archive name expected codeC) +(def (definition archive name expected codeC) (All (_ anchor expression directive) (-> Archive Symbol (Maybe Type) Code (Operation anchor expression directive [Type expression Any]))) @@ -171,7 +171,7 @@ (with_template [<full> <partial> <learn>] [... TODO: Inline "<partial>" into "<full>" ASAP - (def: (<partial> archive generate extension codeT codeS) + (def (<partial> archive generate extension codeT codeS) (All (_ anchor expression directive) (-> Archive (/////generation.Phase anchor expression directive) @@ -193,7 +193,7 @@ _ (/////generation.save! @self {.#None} directive)] (in [codeG value]))))) - (def: .public (<full> archive extension codeT codeC) + (def .public (<full> archive extension codeT codeC) (All (_ anchor expression directive) (-> Archive Text Type Code (Operation anchor expression directive [expression Any]))) @@ -218,7 +218,7 @@ ) ... TODO: Get rid of this function ASAP. -(def: (refresh expander host_analysis) +(def (refresh expander host_analysis) (All (_ anchor expression directive) (-> Expander /////analysis.Bundle (Operation anchor expression directive Any))) (do phase.monad @@ -236,13 +236,13 @@ (dictionary.composite (///analysis.bundle eval host_analysis)))])) state)]))) -(def: (announce_definition! short type) +(def (announce_definition! short type) (All (_ anchor expression directive) (-> Text Type (Operation anchor expression directive Any))) (/////directive.lifted_generation (/////generation.log! (format short " : " (%.type type))))) -(def: (lux::def expander host_analysis) +(def (lux::def expander host_analysis) (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ @@ -262,7 +262,7 @@ _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+])))) -(def: (announce_labels! labels owner) +(def (announce_labels! labels owner) (All (_ anchor expression directive) (-> (List Text) Type (Operation anchor expression directive (List Any)))) (/////directive.lifted_generation @@ -271,7 +271,7 @@ (/////generation.log! (format tag " : Tag of " (%.type owner)))) labels))) -(def: (def::type_tagged expander host_analysis) +(def (deftype_tagged expander host_analysis) (-> Expander /////analysis.Bundle Handler) (..custom [(all <>.and <code>.local <code>.any @@ -309,13 +309,13 @@ _ (..announce_labels! labels (as Type value))] (in /////directive.no_requirements)))])) -(def: imports +(def imports (Parser (List Import)) (|> (<code>.tuple (<>.and <code>.text <code>.text)) <>.some <code>.tuple)) -(def: def::module +(def defmodule Handler (..custom [..imports @@ -346,7 +346,7 @@ "Alias" (%.symbol local) "Label" (%.symbol foreign))) -(def: (define_alias alias original) +(def (define_alias alias original) (-> Text Symbol (/////analysis.Operation Any)) (do phase.monad [current_module (///.lifted meta.current_module_name) @@ -363,7 +363,7 @@ {.#Slot _}) (phase.except ..cannot_alias_a_label [[current_module alias] original])))) -(def: def::alias +(def defalias Handler (..custom [(all <>.and <code>.local <code>.symbol) @@ -377,7 +377,7 @@ ... TODO: Stop requiring these types and the "swapped" function below to make types line-up. (with_template [<name> <anonymous>] - [(def: <name> + [(def <name> Type (with_expansions [<original> binary.Binary] (let [_ <original>] @@ -388,7 +388,7 @@ [Binary|DEFAULT (type (array.Array (I64 Any)))] ) -(def: (swapped original replacement) +(def (swapped original replacement) (-> Type Type Type Type) (function (again type) (if (type#= original type) @@ -420,7 +420,7 @@ {.#Named name (again anonymous)})))) (with_template [<description> <mame> <def_type> <type> <scope> <definer>] - [(def: (<mame> [anchorT expressionT directiveT] extender) + [(def (<mame> [anchorT expressionT directiveT] extender) (All (_ anchor expression directive) (-> [Type Type Type] Extender (Handler anchor expression directive))) @@ -459,22 +459,22 @@ (phase.except ///.invalid_syntax [extension_name %.code inputsC+]))))] ["Analysis" - def::analysis + defanalysis /////analysis.Handler /////analysis.Handler /////directive.lifted_analysis ..analyser] ["Synthesis" - def::synthesis + defsynthesis /////synthesis.Handler /////synthesis.Handler /////directive.lifted_synthesis ..synthesizer] ["Generation" - def::generation + defgeneration (/////generation.Handler anchorT expressionT directiveT) (/////generation.Handler anchor expression directive) /////directive.lifted_generation ..generator] ["Directive" - def::directive + defdirective (/////directive.Handler anchorT expressionT directiveT) (/////directive.Handler anchor expression directive) (<|) ..directive] @@ -482,8 +482,8 @@ ... TODO; Both "prepare-program" and "define-program" exist only ... because the old compiler couldn't handle a fully-inlined definition -... for "def::program". Inline them ASAP. -(def: (prepare_program archive analyse synthesize programC) +... for "defprogram". Inline them ASAP. +(def (prepare_program archive analyse synthesize programC) (All (_ anchor expression directive output) (-> Archive /////analysis.Phase @@ -499,7 +499,7 @@ (/////directive.lifted_synthesis (synthesize archive programA)))) -(def: (define_program archive @module generate program programS) +(def (define_program archive @module generate program programS) (All (_ anchor expression directive output) (-> Archive module.ID @@ -514,7 +514,7 @@ @self (/////generation.learn [/////program.name {.#None}] true (list#mix set.has dependencies interim_artifacts))] (/////generation.save! @self {.#None} (program [@module @self] programG)))) -(def: (def::program program) +(def (defprogram program) (All (_ anchor expression directive) (-> (Program expression directive) (Handler anchor expression directive))) (function (handler extension_name phase archive inputsC+) @@ -536,7 +536,7 @@ _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+])))) -(def: (bundle::def expander host_analysis program anchorT,expressionT,directiveT extender) +(def (bundle::def expander host_analysis program anchorT,expressionT,directiveT extender) (All (_ anchor expression directive) (-> Expander /////analysis.Bundle @@ -546,17 +546,17 @@ (Bundle anchor expression directive))) (<| (///bundle.prefix "def") (|> ///bundle.empty - (dictionary.has "module" def::module) - (dictionary.has "alias" def::alias) - (dictionary.has "type tagged" (def::type_tagged expander host_analysis)) - (dictionary.has "analysis" (def::analysis anchorT,expressionT,directiveT extender)) - (dictionary.has "synthesis" (def::synthesis anchorT,expressionT,directiveT extender)) - (dictionary.has "generation" (def::generation anchorT,expressionT,directiveT extender)) - (dictionary.has "directive" (def::directive anchorT,expressionT,directiveT extender)) - (dictionary.has "program" (def::program program)) + (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 "program" (defprogram program)) ))) -(def: .public (bundle expander host_analysis program anchorT,expressionT,directiveT extender) +(def .public (bundle expander host_analysis program anchorT,expressionT,directiveT extender) (All (_ anchor expression directive) (-> Expander /////analysis.Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux index 7ef89329d..246b7455e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp.lux @@ -12,7 +12,7 @@ [common_lisp [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index c0c04d708..51ed09e66 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -38,7 +38,7 @@ [/// ["[1]" phase]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -51,12 +51,12 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(def: !unary +(def !unary (template (_ function) (|>> list _.apply (|> (_.constant function))))) ... ... TODO: Get rid of this ASAP -... (def: lux::syntax_char_case! +... (def lux::syntax_char_case! ... (..custom [(all <>.and ... <s>.any ... <s>.any @@ -81,7 +81,7 @@ ... elseG ... conditionalsG))))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty ... (/.install "syntax char case!" lux::syntax_char_case!) @@ -89,12 +89,12 @@ ... (/.install "try" (unary //runtime.lux//try)) )) -... (def: (capped operation parameter subject) +... (def (capped operation parameter subject) ... (-> (-> Expression Expression Expression) ... (-> Expression Expression Expression)) ... (//runtime.i64//64 (operation parameter subject))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -114,7 +114,7 @@ (/.install "char" (unary (|>> _.code_char/1 _.string/1))) ))) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -130,19 +130,19 @@ ... (/.install "decode" (unary //runtime.f64//decode)) ))) -(def: (text//index [offset sub text]) +(def (text//index [offset sub text]) (Trinary (Expression Any)) (//runtime.text//index offset sub text)) -(def: (text//clip [offset length text]) +(def (text//clip [offset length text]) (Trinary (Expression Any)) (//runtime.text//clip offset length text)) -(def: (text//char [index text]) +(def (text//char [index text]) (Binary (Expression Any)) (_.char_code/1 (_.char/2 [text index]))) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -156,12 +156,12 @@ (/.install "clip" (trinary ..text//clip)) ))) -(def: (io//log! message) +(def (io//log! message) (Unary (Expression Any)) (_.progn (list (_.write_line/1 message) //runtime.unit))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty @@ -169,7 +169,7 @@ (/.install "error" (unary _.error/1)) ))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux index 79e422867..a68ac7532 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/host.lux @@ -8,7 +8,7 @@ [common_lisp [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "common_lisp") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux index 5b4f0979a..e3b3165e9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js.lux @@ -12,7 +12,7 @@ [js [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index f83d48372..8f07958c0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -39,7 +39,7 @@ [/// ["[1]" phase (.open: "[1]#[0]" monad)]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -55,7 +55,7 @@ ... [Procedures] ... [[Bits]] (with_template [<name> <op>] - [(def: (<name> [paramG subjectG]) + [(def (<name> [paramG subjectG]) (Binary Expression) (<op> subjectG (//runtime.i64::number paramG)))] @@ -64,7 +64,7 @@ ) ... [[Numbers]] -(def: f64//decode +(def f64//decode (Unary Expression) (|>> list (_.apply (_.var "parseFloat")) @@ -72,33 +72,33 @@ (_.closure (list)) //runtime.lux//try)) -(def: i64::char +(def i64::char (Unary Expression) (|>> //runtime.i64::number (list) (_.apply (_.var "String.fromCharCode")))) ... [[Text]] -(def: (text//concat [leftG rightG]) +(def (text//concat [leftG rightG]) (Binary Expression) (|> leftG (_.do "concat" (list rightG)))) -(def: (text//clip [startG endG subjectG]) +(def (text//clip [startG endG subjectG]) (Trinary Expression) (//runtime.text//clip startG endG subjectG)) -(def: (text//index [startG partG subjectG]) +(def (text//index [startG partG subjectG]) (Trinary Expression) (//runtime.text//index startG partG subjectG)) ... [[IO]] -(def: (io//log messageG) +(def (io//log messageG) (Unary Expression) (all _., (//runtime.io//log messageG) //runtime.unit)) -(def: .public (statement expression archive synthesis) +(def .public (statement expression archive synthesis) Phase! (case synthesis ... TODO: Get rid of this ASAP @@ -148,7 +148,7 @@ )) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <s>.any <s>.any @@ -179,14 +179,14 @@ {.#Some else!})))))])) ... [Bundles] -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) (/.install "is" (binary (product.uncurried _.=))) (/.install "try" (unary //runtime.lux//try)))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -206,7 +206,7 @@ (/.install "char" (unary i64::char)) ))) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -221,7 +221,7 @@ (/.install "encode" (unary (_.do "toString" (list)))) (/.install "decode" (unary f64//decode))))) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -234,14 +234,14 @@ (/.install "clip" (trinary text//clip)) ))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty (/.install "log" (unary io//log)) (/.install "error" (unary //runtime.io//error))))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 0c3a868ae..5d15df243 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -31,28 +31,28 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: array::new +(def array::new (Unary Expression) (|>> (_.the //runtime.i64_low_field) list (_.new (_.var "Array")))) -(def: array::length +(def array::length (Unary Expression) (|>> (_.the "length") //runtime.i64::of_number)) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary Expression) (_.at (_.the //runtime.i64_low_field indexG) arrayG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary Expression) (//runtime.array//write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary Expression) (//runtime.array//delete indexG arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -63,7 +63,7 @@ (/.install "delete" (binary array::delete)) ))) -(def: object::new +(def object::new (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [constructorS inputsS]) @@ -72,7 +72,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.new constructorG inputsG))))])) -(def: object::get +(def object::get Handler (custom [(all <>.and <s>.text <s>.any) @@ -81,7 +81,7 @@ [objectG (phase archive objectS)] (in (_.the fieldS objectG))))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <s>.text <s>.any (<>.some <s>.any)) @@ -92,14 +92,14 @@ (in (_.do methodS inputsG objectG))))])) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary Expression) (function.constant <unit>)) - (def: <?> (Unary Expression) (_.= <unit>))] + [(def <!> (Nullary Expression) (function.constant <unit>)) + (def <?> (Unary Expression) (_.= <unit>))] [object::null object::null? _.null] [object::undefined object::undefined? _.undefined] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -112,13 +112,13 @@ (/.install "undefined?" (unary object::undefined?)) ))) -(def: js::constant +(def js::constant (custom [<s>.text (function (_ extension phase archive name) (at ////////phase.monad in (_.var name)))])) -(def: js::apply +(def js::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -127,7 +127,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply abstractionG inputsG))))])) -(def: js::function +(def js::function (custom [(all <>.and <s>.i64 <s>.any) (function (_ extension phase archive [arity abstractionS]) @@ -147,7 +147,7 @@ 1 (_.apply g!abstraction g!inputs) _ (_.apply_1 g!abstraction (_.array g!inputs)))))))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "js") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux index f53409c26..8f05447f9 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm.lux @@ -12,7 +12,7 @@ [jvm [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (all dictionary.composite /common.bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index 44e2b7c41..febd59454 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -43,7 +43,7 @@ [meta [archive (.only Archive)]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text Phase Archive s (Operation (Bytecode Any)))] @@ -56,29 +56,29 @@ {try.#Failure error} (/////.except /////extension.invalid_syntax [extension_name synthesis.%synthesis input])))) -(def: $Boolean (type.class "java.lang.Boolean" (list))) -(def: $Double (type.class "java.lang.Double" (list))) -(def: $Character (type.class "java.lang.Character" (list))) -(def: $String (type.class "java.lang.String" (list))) -(def: $CharSequence (type.class "java.lang.CharSequence" (list))) -(def: $Object (type.class "java.lang.Object" (list))) -(def: $PrintStream (type.class "java.io.PrintStream" (list))) -(def: $System (type.class "java.lang.System" (list))) -(def: $Error (type.class "java.lang.Error" (list))) - -(def: lux_int +(def $Boolean (type.class "java.lang.Boolean" (list))) +(def $Double (type.class "java.lang.Double" (list))) +(def $Character (type.class "java.lang.Character" (list))) +(def $String (type.class "java.lang.String" (list))) +(def $CharSequence (type.class "java.lang.CharSequence" (list))) +(def $Object (type.class "java.lang.Object" (list))) +(def $PrintStream (type.class "java.io.PrintStream" (list))) +(def $System (type.class "java.lang.System" (list))) +(def $Error (type.class "java.lang.Error" (list))) + +(def lux_int (Bytecode Any) (all _.composite _.i2l (///value.wrap type.long))) -(def: jvm_int +(def jvm_int (Bytecode Any) (all _.composite (///value.unwrap type.long) _.l2i)) -(def: (predicate bytecode) +(def (predicate bytecode) (-> (-> Label (Bytecode Any)) (Bytecode Any)) (do _.monad @@ -94,7 +94,7 @@ ))) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <synthesis>.any <synthesis>.any @@ -138,21 +138,21 @@ (_.set_label @end)) )))))])) -(def: (lux::is [referenceG sampleG]) +(def (lux::is [referenceG sampleG]) (Binary (Bytecode Any)) (all _.composite referenceG sampleG (..predicate _.if_acmpeq))) -(def: (lux::try riskyG) +(def (lux::try riskyG) (Unary (Bytecode Any)) (all _.composite riskyG (_.checkcast ///function.class) ///runtime.try)) -(def: bundle::lux +(def bundle::lux Bundle (|> (is Bundle /////bundle.empty) (/////bundle.install "syntax char case!" ..lux::syntax_char_case!) @@ -160,7 +160,7 @@ (/////bundle.install "try" (unary ..lux::try)))) (with_template [<name> <op>] - [(def: (<name> [maskG inputG]) + [(def (<name> [maskG inputG]) (Binary (Bytecode Any)) (all _.composite inputG (///value.unwrap type.long) @@ -173,7 +173,7 @@ ) (with_template [<name> <op>] - [(def: (<name> [shiftG inputG]) + [(def (<name> [shiftG inputG]) (Binary (Bytecode Any)) (all _.composite inputG (///value.unwrap type.long) @@ -185,7 +185,7 @@ ) (with_template [<name> <type> <op>] - [(def: (<name> [paramG subjectG]) + [(def (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite subjectG (///value.unwrap <type>) @@ -207,7 +207,7 @@ (with_template [<eq> <lt> <type> <cmp>] [(with_template [<name> <reference>] - [(def: (<name> [paramG subjectG]) + [(def (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite subjectG (///value.unwrap <type>) @@ -223,12 +223,12 @@ [f64::= f64::< type.double _.dcmpg] ) -(def: (::toString class from) +(def (::toString class from) (-> (Type Class) (Type Primitive) (Bytecode Any)) (_.invokestatic class "toString" (type.method [(list) (list from) ..$String (list)]))) (with_template [<name> <prepare> <transform>] - [(def: (<name> inputG) + [(def (<name> inputG) (Unary (Bytecode Any)) (all _.composite inputG @@ -263,7 +263,7 @@ ///runtime.decode_frac] ) -(def: bundle::i64 +(def bundle::i64 Bundle (<| (/////bundle.prefix "i64") (|> (is Bundle /////bundle.empty) @@ -282,7 +282,7 @@ (/////bundle.install "f64" (unary ..i64::f64)) (/////bundle.install "char" (unary ..i64::char))))) -(def: bundle::f64 +(def bundle::f64 Bundle (<| (/////bundle.prefix "f64") (|> (is Bundle /////bundle.empty) @@ -297,7 +297,7 @@ (/////bundle.install "encode" (unary ..f64::encode)) (/////bundle.install "decode" (unary ..f64::decode))))) -(def: (text::size inputG) +(def (text::size inputG) (Unary (Bytecode Any)) (all _.composite inputG @@ -305,10 +305,10 @@ (_.invokevirtual ..$String "length" (type.method [(list) (list) type.int (list)])) ..lux_int)) -(def: no_op (Bytecode Any) (_#in [])) +(def no_op (Bytecode Any) (_#in [])) (with_template [<name> <pre_subject> <pre_param> <op> <post>] - [(def: (<name> [paramG subjectG]) + [(def (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite subjectG <pre_subject> @@ -326,14 +326,14 @@ ..lux_int] ) -(def: (text::concat [leftG rightG]) +(def (text::concat [leftG rightG]) (Binary (Bytecode Any)) (all _.composite leftG (_.checkcast $String) rightG (_.checkcast $String) (_.invokevirtual ..$String "concat" (type.method [(list) (list ..$String) ..$String (list)])))) -(def: (text::clip [offset! length! subject!]) +(def (text::clip [offset! length! subject!]) (Trinary (Bytecode Any)) (all _.composite subject! (_.checkcast $String) @@ -343,8 +343,8 @@ _.iadd (_.invokevirtual ..$String "substring" (type.method [(list) (list type.int type.int) ..$String (list)])))) -(def: index_method (type.method [(list) (list ..$String type.int) type.int (list)])) -(def: (text::index [startG partG textG]) +(def index_method (type.method [(list) (list ..$String type.int) type.int (list)])) +(def (text::index [startG partG textG]) (Trinary (Bytecode Any)) (do _.monad [@not_found _.new_label @@ -365,7 +365,7 @@ ///runtime.none_injection (_.set_label @end)))) -(def: bundle::text +(def bundle::text Bundle (<| (/////bundle.prefix "text") (|> (is Bundle /////bundle.empty) @@ -377,8 +377,8 @@ (/////bundle.install "char" (binary ..text::char)) (/////bundle.install "clip" (trinary ..text::clip))))) -(def: string_method (type.method [(list) (list ..$String) type.void (list)])) -(def: (io::log messageG) +(def string_method (type.method [(list) (list ..$String) type.void (list)])) +(def (io::log messageG) (Unary (Bytecode Any)) (all _.composite (_.getstatic ..$System "out" ..$PrintStream) @@ -387,7 +387,7 @@ (_.invokevirtual ..$PrintStream "println" ..string_method) ///runtime.unit)) -(def: (io::error messageG) +(def (io::error messageG) (Unary (Bytecode Any)) (all _.composite (_.new ..$Error) @@ -397,14 +397,14 @@ (_.invokespecial ..$Error "<init>" ..string_method) _.athrow)) -(def: bundle::io +(def bundle::io Bundle (<| (/////bundle.prefix "io") (|> (is Bundle /////bundle.empty) (/////bundle.install "log" (unary ..io::log)) (/////bundle.install "error" (unary ..io::error))))) -(def: .public bundle +(def .public bundle Bundle (<| (/////bundle.prefix "lux") (|> bundle::lux diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index e08b2aba8..a13cef376 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -81,7 +81,7 @@ ["[1]/[0]" artifact]]]]]]]]) (with_template [<name> <0>] - [(def: <name> + [(def <name> (Bytecode Any) (all _.composite _.l2i @@ -93,7 +93,7 @@ ) (with_template [<conversion> <name>] - [(def: (<name> inputG) + [(def (<name> inputG) (Unary (Bytecode Any)) (if (same? _.nop <conversion>) inputG @@ -133,7 +133,7 @@ [_.i2l conversion::short_to_long] ) -(def: bundle::conversion +(def bundle::conversion Bundle (<| (/////bundle.prefix "conversion") (|> (is Bundle /////bundle.empty) @@ -170,7 +170,7 @@ ))) (with_template [<name> <op>] - [(def: (<name> [parameter! subject!]) + [(def (<name> [parameter! subject!]) (Binary (Bytecode Any)) (all _.composite subject! @@ -214,12 +214,12 @@ [double::% _.drem] ) -(def: $Boolean (type.class box.boolean (list))) -(def: falseG (_.getstatic ..$Boolean "FALSE" ..$Boolean)) -(def: trueG (_.getstatic ..$Boolean "TRUE" ..$Boolean)) +(def $Boolean (type.class box.boolean (list))) +(def falseG (_.getstatic ..$Boolean "FALSE" ..$Boolean)) +(def trueG (_.getstatic ..$Boolean "TRUE" ..$Boolean)) (with_template [<name> <op>] - [(def: (<name> [reference subject]) + [(def (<name> [reference subject]) (Binary (Bytecode Any)) (do _.monad [@then _.new_label @@ -242,7 +242,7 @@ ) (with_template [<name> <op> <reference>] - [(def: (<name> [reference subject]) + [(def (<name> [reference subject]) (Binary (Bytecode Any)) (do _.monad [@then _.new_label @@ -269,7 +269,7 @@ [double::< _.dcmpg -1] ) -(def: bundle::int +(def bundle::int Bundle (<| (/////bundle.prefix (reflection.reflection reflection.int)) (|> (is Bundle /////bundle.empty) @@ -288,7 +288,7 @@ (/////bundle.install "ushr" (binary int::ushr)) ))) -(def: bundle::long +(def bundle::long Bundle (<| (/////bundle.prefix (reflection.reflection reflection.long)) (|> (is Bundle /////bundle.empty) @@ -307,7 +307,7 @@ (/////bundle.install "ushr" (binary long::ushr)) ))) -(def: bundle::float +(def bundle::float Bundle (<| (/////bundle.prefix (reflection.reflection reflection.float)) (|> (is Bundle /////bundle.empty) @@ -320,7 +320,7 @@ (/////bundle.install "<" (binary float::<)) ))) -(def: bundle::double +(def bundle::double Bundle (<| (/////bundle.prefix (reflection.reflection reflection.double)) (|> (is Bundle /////bundle.empty) @@ -333,7 +333,7 @@ (/////bundle.install "<" (binary double::<)) ))) -(def: bundle::char +(def bundle::char Bundle (<| (/////bundle.prefix (reflection.reflection reflection.char)) (|> (is Bundle /////bundle.empty) @@ -342,7 +342,7 @@ ))) (with_template [<name> <category> <parser>] - [(def: .public <name> + [(def .public <name> (Parser (Type <category>)) (<text>.then <parser> <synthesis>.text))] @@ -353,12 +353,12 @@ [return Return parser.return] ) -(def: reflection +(def reflection (All (_ category) (-> (Type (<| Return' Value' category)) Text)) (|>> type.reflection reflection.reflection)) -(def: signature +(def signature (All (_ category) (-> (Type category) Text)) (|>> type.signature signature.signature)) @@ -367,7 +367,7 @@ (exception.report "JVM Type" (..signature arrayJT))) -(def: .public object_array +(def .public object_array (Parser (Type Object)) (do <>.monad [arrayJT (<text>.then parser.array <synthesis>.text)] @@ -383,7 +383,7 @@ {.#None} (undefined)))) -(def: (primitive_array_length_handler jvm_primitive) +(def (primitive_array_length_handler jvm_primitive) (-> (Type Primitive) Handler) (..custom [<synthesis>.any @@ -395,7 +395,7 @@ (_.checkcast (type.array jvm_primitive)) _.arraylength))))])) -(def: array::length::object +(def array::length::object Handler (..custom [(all <>.and ..object_array <synthesis>.any) @@ -407,7 +407,7 @@ (_.checkcast (type.array elementJT)) _.arraylength))))])) -(def: (new_primitive_array_handler jvm_primitive) +(def (new_primitive_array_handler jvm_primitive) (-> Primitive_Array_Type Handler) (..custom [<synthesis>.any @@ -418,7 +418,7 @@ lengthG (_.newarray jvm_primitive)))))])) -(def: array::new::object +(def array::new::object Handler (..custom [(all <>.and ..object <synthesis>.any) @@ -429,7 +429,7 @@ lengthG (_.anewarray objectJT)))))])) -(def: (read_primitive_array_handler jvm_primitive loadG) +(def (read_primitive_array_handler jvm_primitive loadG) (-> (Type Primitive) (Bytecode Any) Handler) (..custom [(all <>.and <synthesis>.any <synthesis>.any) @@ -443,7 +443,7 @@ idxG loadG))))])) -(def: array::read::object +(def array::read::object Handler (..custom [(all <>.and ..object_array <synthesis>.any <synthesis>.any) @@ -457,7 +457,7 @@ idxG _.aaload))))])) -(def: (write_primitive_array_handler jvm_primitive storeG) +(def (write_primitive_array_handler jvm_primitive storeG) (-> (Type Primitive) (Bytecode Any) Handler) (..custom [(all <>.and <synthesis>.any <synthesis>.any <synthesis>.any) @@ -474,7 +474,7 @@ valueG storeG))))])) -(def: array::write::object +(def array::write::object Handler (..custom [(all <>.and ..object_array <synthesis>.any <synthesis>.any <synthesis>.any) @@ -491,7 +491,7 @@ valueG _.aastore))))])) -(def: bundle::array +(def bundle::array Bundle (<| (/////bundle.prefix "array") (|> /////bundle.empty @@ -541,11 +541,11 @@ (/////bundle.install "object" array::write::object)))) ))) -(def: (object::null _) +(def (object::null _) (Nullary (Bytecode Any)) _.aconst_null) -(def: (object::null? objectG) +(def (object::null? objectG) (Unary (Bytecode Any)) (do _.monad [@then _.new_label @@ -559,7 +559,7 @@ ..trueG (_.set_label @end)))) -(def: (object::synchronized [monitorG exprG]) +(def (object::synchronized [monitorG exprG]) (Binary (Bytecode Any)) (all _.composite monitorG @@ -569,16 +569,16 @@ _.swap _.monitorexit)) -(def: (object::throw exceptionG) +(def (object::throw exceptionG) (Unary (Bytecode Any)) (all _.composite exceptionG _.athrow)) -(def: $Class (type.class "java.lang.Class" (list))) -(def: $String (type.class "java.lang.String" (list))) +(def $Class (type.class "java.lang.Class" (list))) +(def $String (type.class "java.lang.String" (list))) -(def: object::class +(def object::class Handler (..custom [<synthesis>.text @@ -589,7 +589,7 @@ (_.string class) (_.invokestatic ..$Class "forName" (type.method [(list) (list ..$String) ..$Class (list)]))))))])) -(def: object::instance? +(def object::instance? Handler (..custom [(all <>.and <synthesis>.text <synthesis>.any) @@ -601,7 +601,7 @@ (_.instanceof (type.class class (list))) (///value.wrap type.boolean)))))])) -(def: object::cast +(def object::cast Handler (..custom [(all <>.and <synthesis>.text <synthesis>.text <synthesis>.any) @@ -632,7 +632,7 @@ ... else valueG)))))])) -(def: bundle::object +(def bundle::object Bundle (<| (/////bundle.prefix "object") (|> (is Bundle /////bundle.empty) @@ -645,17 +645,17 @@ (/////bundle.install "cast" object::cast) ))) -(def: get::static +(def get::static Handler (..custom [(all <>.and <synthesis>.text <synthesis>.text ..value) (function (_ extension_name generate archive [class field :unboxed:]) (at //////.monad in (_.getstatic (type.class class (list)) field :unboxed:)))])) -(def: unitG +(def unitG (_.string synthesis.unit)) -(def: put::static +(def put::static Handler (..custom [(all <>.and <synthesis>.text <synthesis>.text ..value <synthesis>.any) @@ -673,7 +673,7 @@ (_.putstatic (type.class class (list)) field :unboxed:) ..unitG))))])) -(def: get::virtual +(def get::virtual Handler (..custom [(all <>.and <synthesis>.text <synthesis>.text ..value <synthesis>.any) @@ -687,7 +687,7 @@ (_.checkcast :class:) getG))))])) -(def: put::virtual +(def put::virtual Handler (..custom [(all <>.and <synthesis>.text <synthesis>.text ..value <synthesis>.any <synthesis>.any) @@ -714,11 +714,11 @@ (type: Input (Typed Synthesis)) -(def: input +(def input (Parser Input) (<synthesis>.tuple (<>.and ..value <synthesis>.any))) -(def: (generate_input generate archive [valueT valueS]) +(def (generate_input generate archive [valueT valueS]) (-> Phase Archive Input (Operation (Typed (Bytecode Any)))) (do //////.monad [valueG (generate archive valueS)] @@ -731,7 +731,7 @@ valueG (_.checkcast valueT))])))) -(def: (prepare_output outputT) +(def (prepare_output outputT) (-> (Type Return) (Bytecode Any)) (case (type.void? outputT) {.#Right outputT} @@ -740,7 +740,7 @@ {.#Left outputT} (_#in []))) -(def: invoke::static +(def invoke::static Handler (..custom [(all <>.and ..class <synthesis>.text ..return (<>.some ..input)) @@ -753,7 +753,7 @@ (prepare_output outputT)))))])) (with_template [<check_cast?> <name> <invoke>] - [(def: <name> + [(def <name> Handler (..custom [(all <>.and ..class <synthesis>.text ..return <synthesis>.any (<>.some ..input)) @@ -775,7 +775,7 @@ [#1 invoke::interface _.invokeinterface] ) -(def: invoke::constructor +(def invoke::constructor Handler (..custom [(all <>.and ..class (<>.some ..input)) @@ -788,7 +788,7 @@ (monad.each _.monad product.right inputsTG) (_.invokespecial class "<init>" (type.method [(list) (list#each product.left inputsTG) type.void (list)]))))))])) -(def: bundle::member +(def bundle::member Bundle (<| (/////bundle.prefix "member") (|> (is Bundle /////bundle.empty) @@ -809,19 +809,19 @@ (/////bundle.install "constructor" invoke::constructor)))) ))) -(def: annotation_parameter +(def annotation_parameter (Parser (/.Annotation_Parameter Synthesis)) (<synthesis>.tuple (<>.and <synthesis>.text <synthesis>.any))) -(def: annotation +(def annotation (Parser (/.Annotation Synthesis)) (<synthesis>.tuple (<>.and <synthesis>.text (<>.some ..annotation_parameter)))) -(def: argument +(def argument (Parser Argument) (<synthesis>.tuple (<>.and <synthesis>.text ..value))) -(def: .public (hidden_method_body arity body) +(def .public (hidden_method_body arity body) (-> Nat Synthesis Synthesis) (with_expansions [<oops> (panic! (%.format (%.nat arity) " " (synthesis.%synthesis body)))] (case [arity body] @@ -847,7 +847,7 @@ _ <oops>))) -(def: (without_fake_parameter#path without_fake_parameter) +(def (without_fake_parameter#path without_fake_parameter) (-> (-> Synthesis Synthesis) (-> Path Path)) (function (again it) @@ -881,7 +881,7 @@ {synthesis.#Then it} {synthesis.#Then (without_fake_parameter it)}))) -(def: .public (without_fake_parameter it) +(def .public (without_fake_parameter it) (-> Synthesis Synthesis) (case it {synthesis.#Simple _} @@ -970,7 +970,7 @@ {synthesis.#Extension name parameters} {synthesis.#Extension name (list#each without_fake_parameter parameters)})) -(def: overriden_method_definition +(def overriden_method_definition (Parser [(Environment Synthesis) (/.Overriden_Method Synthesis)]) (<synthesis>.tuple (do <>.monad [_ (<synthesis>.this_text /.overriden_tag) @@ -998,7 +998,7 @@ 0 (without_fake_parameter body) _ body))]])))) -(def: (normalize_path normalize) +(def (normalize_path normalize) (-> (-> Synthesis Synthesis) (-> Path Path)) (function (again path) @@ -1035,7 +1035,7 @@ (type: Mapping (Dictionary Synthesis Variable)) -(def: (normalize_method_body mapping) +(def (normalize_method_body mapping) (-> Mapping Synthesis Synthesis) (function (again body) (case body @@ -1099,17 +1099,17 @@ {synthesis.#Extension [name inputsS+]} {synthesis.#Extension [name (list#each again inputsS+)]}))) -(def: $Object +(def $Object (type.class "java.lang.Object" (list))) -(def: (anonymous_init_method env inputsTI) +(def (anonymous_init_method env inputsTI) (-> (Environment Synthesis) (List (Typed (Bytecode Any))) (Type category.Method)) (type.method [(list) (list.repeated (n.+ (list.size inputsTI) (list.size env)) ..$Object) type.void (list)])) -(def: (with_anonymous_init class env super_class inputsTG) +(def (with_anonymous_init class env super_class inputsTG) (-> (Type category.Class) (Environment Synthesis) (Type category.Class) (List (Typed (Bytecode Any))) (Resource Method)) (let [inputs_offset (list.size inputsTG) inputs! (|> inputsTG @@ -1144,7 +1144,7 @@ store_captured! _.return)}))) -(def: (anonymous_instance generate archive class env inputsTI) +(def (anonymous_instance generate archive class env inputsTI) (-> Phase Archive (Type category.Class) (Environment Synthesis) (List (Typed (Bytecode Any))) (Operation (Bytecode Any))) (do [! //////.monad] [captureG+ (monad.each ! (generate archive) env)] @@ -1158,7 +1158,7 @@ (monad.all _.monad captureG+) (_.invokespecial class "<init>" (anonymous_init_method env inputsTI)))))) -(def: (returnG returnT) +(def (returnG returnT) (-> (Type Return) (Bytecode Any)) (case (type.void? returnT) {.#Right returnT} @@ -1196,14 +1196,14 @@ ... (at type.equivalence = type.double returnT) (unwrap_primitive _.dreturn type.double))))))) -(def: (method_dependencies archive method) +(def (method_dependencies archive method) (-> Archive (/.Overriden_Method Synthesis) (Operation (Set unit.ID))) (let [[_super _name _strict_fp? _annotations _t_vars _this _arguments _return _exceptions bodyS] method] (cache/artifact.dependencies archive bodyS))) -(def: (anonymous_dependencies archive inputsTS overriden_methods) +(def (anonymous_dependencies archive inputsTS overriden_methods) (-> Archive (List Input) (List [(Environment Synthesis) (/.Overriden_Method Synthesis)]) (Operation (Set unit.ID))) (do [! //////.monad] @@ -1218,7 +1218,7 @@ all_closure_dependencies all_method_dependencies))))) -(def: (prepare_argument lux_register argumentT jvm_register) +(def (prepare_argument lux_register argumentT jvm_register) (-> Register (Type Value) Register [Register (Bytecode Any)]) (case (type.primitive? argumentT) {.#Left argumentT} @@ -1251,7 +1251,7 @@ ... (at type.equivalence = type.double argumentT) (wrap_primitive 2 _.dload type.double)))))) -(def: .public (prepare_arguments offset types) +(def .public (prepare_arguments offset types) (-> Nat (List (Type Value)) (Bytecode Any)) (|> types list.enumeration @@ -1266,7 +1266,7 @@ (_#in [])])) product.right)) -(def: (normalized_method global_mapping [environment method]) +(def (normalized_method global_mapping [environment method]) (-> Mapping [(Environment Synthesis) (/.Overriden_Method Synthesis)] (/.Overriden_Method Synthesis)) (let [[ownerT name strict_fp? annotations vars self_name arguments returnT exceptionsT body] method @@ -1283,7 +1283,7 @@ self_name arguments returnT exceptionsT (normalize_method_body local_mapping body)])) -(def: (total_environment overriden_methods) +(def (total_environment overriden_methods) (-> (List [(Environment Synthesis) (/.Overriden_Method Synthesis)]) (List Synthesis)) (|> overriden_methods @@ -1295,7 +1295,7 @@ (set.of_list synthesis.hash) set.list)) -(def: (global_mapping total_environment) +(def (global_mapping total_environment) (-> (List Synthesis) Mapping) (|> total_environment ... Give them names as "foreign" variables. @@ -1304,7 +1304,7 @@ [capture {//////variable.#Foreign id}])) (dictionary.of_list synthesis.hash))) -(def: (method_definition phase archive artifact_id method) +(def (method_definition phase archive artifact_id method) (-> Phase Archive artifact.ID (/.Overriden_Method Synthesis) (Operation (Resource Method))) (let [[ownerT name strict_fp? annotations vars self_name arguments returnT exceptionsT bodyS] method] (do //////.monad @@ -1326,7 +1326,7 @@ bodyG (returnG returnT))}))))) -(def: class::anonymous +(def class::anonymous Handler (..custom [(all <>.and @@ -1366,14 +1366,14 @@ _ (//////generation.save! artifact_id {.#None} artifact)] (anonymous_instance generate archive class total_environment inputsTI)))])) -(def: bundle::class +(def bundle::class Bundle (<| (/////bundle.prefix "class") (|> (is Bundle /////bundle.empty) (/////bundle.install "anonymous" class::anonymous) ))) -(def: .public bundle +(def .public bundle Bundle (<| (/////bundle.prefix "jvm") (|> ..bundle::conversion diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux index bae90fe1b..8860a5568 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua.lux @@ -12,7 +12,7 @@ [lua [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index c454fc422..14c293e39 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -43,7 +43,7 @@ [/// ["[1]" phase (.open: "[1]#[0]" monad)]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -56,11 +56,11 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(def: !unary +(def !unary (template (_ function) [(|>> list _.apply (|> (_.var function)))])) -(def: .public (statement expression archive synthesis) +(def .public (statement expression archive synthesis) Phase! (case synthesis ... TODO: Get rid of this ASAP @@ -112,7 +112,7 @@ )) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <s>.any <s>.any @@ -141,14 +141,14 @@ (//case.case! statement phase archive) (at /////.monad each (|>> (as Expression)))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) (/.install "is" (binary (product.uncurried _.=))) (/.install "try" (unary //runtime.lux//try)))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -168,11 +168,11 @@ (/.install "char" (unary (function (_ it) (_.apply (list it) (_.var "utf8.char"))))) ))) -(def: f64//decode +(def f64//decode (Unary Expression) (|>> list _.apply (|> (_.var "tonumber")) _.return (_.closure (list)) //runtime.lux//try)) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -187,19 +187,19 @@ (/.install "encode" (unary (function (_ it) (_.apply (list (_.string "%.17g") it) (_.var "string.format"))))) (/.install "decode" (unary ..f64//decode))))) -(def: (text//char [paramO subjectO]) +(def (text//char [paramO subjectO]) (Binary Expression) (//runtime.text//char (_.+ (_.int +1) paramO) subjectO)) -(def: (text//clip [paramO extraO subjectO]) +(def (text//clip [paramO extraO subjectO]) (Trinary Expression) (//runtime.text//clip subjectO paramO extraO)) -(def: (text//index [startO partO textO]) +(def (text//index [startO partO textO]) (Trinary Expression) (//runtime.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -215,19 +215,19 @@ (/.install "clip" (trinary ..text//clip)) ))) -(def: (io//log! messageO) +(def (io//log! messageO) (Unary Expression) (|> (_.apply (list messageO) (_.var "print")) (_.or //runtime.unit))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty (/.install "log" (unary ..io//log!)) (/.install "error" (unary (!unary "error")))))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index 4ed8013ca..6d8a3bf73 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -34,27 +34,27 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: array::new +(def array::new (Unary Expression) (|>> ["n"] list _.table)) -(def: array::length +(def array::length (Unary Expression) (_.the "n")) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary Expression) (_.item (_.+ (_.int +1) indexG) arrayG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary Expression) (//runtime.array//write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary Expression) (//runtime.array//write indexG _.nil arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -65,7 +65,7 @@ (/.install "delete" (binary array::delete)) ))) -(def: object::get +(def object::get Handler (custom [(all <>.and <s>.text <s>.any) @@ -74,7 +74,7 @@ [objectG (phase archive objectS)] (in (_.the fieldS objectG))))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <s>.text <s>.any (<>.some <s>.any)) @@ -85,13 +85,13 @@ (in (_.do methodS inputsG objectG))))])) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary Expression) (function.constant <unit>)) - (def: <?> (Unary Expression) (_.= <unit>))] + [(def <!> (Nullary Expression) (function.constant <unit>)) + (def <?> (Unary Expression) (_.= <unit>))] [object::nil object::nil? _.nil] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -101,10 +101,10 @@ (/.install "nil?" (unary object::nil?)) ))) -(def: $input +(def $input (_.var "input")) -(def: utf8::encode +(def utf8::encode (custom [<s>.any (function (_ extension phase archive inputS) @@ -116,7 +116,7 @@ (_.var "string.byte"))) (_.var "table.pack")))))))])) -(def: utf8::decode +(def utf8::decode (custom [<s>.any (function (_ extension phase archive inputS) @@ -126,7 +126,7 @@ (_.var "table.unpack"))) (_.var "string.char")))))])) -(def: utf8 +(def utf8 Bundle (<| (/.prefix "utf8") (|> /.empty @@ -134,13 +134,13 @@ (/.install "decode" utf8::decode) ))) -(def: lua::constant +(def lua::constant (custom [<s>.text (function (_ extension phase archive name) (at ////////phase.monad in (_.var name)))])) -(def: lua::apply +(def lua::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -149,7 +149,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply inputsG abstractionG))))])) -(def: lua::power +(def lua::power (custom [(all <>.and <s>.any <s>.any) (function (_ extension phase archive [powerS baseS]) @@ -158,14 +158,14 @@ baseG (phase archive baseS)] (in (_.^ powerG baseG))))])) -(def: lua::import +(def lua::import (custom [<s>.text (function (_ extension phase archive module) (at ////////phase.monad in (_.require/1 (_.string module))))])) -(def: lua::function +(def lua::function (custom [(all <>.and <s>.i64 <s>.any) (function (_ extension phase archive [arity abstractionS]) @@ -184,7 +184,7 @@ 1 (_.apply g!inputs abstractionG) _ (_.apply (list (_.array g!inputs)) abstractionG))))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lua") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux index d36dc5557..4d9c8ab95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php.lux @@ -12,7 +12,7 @@ [php [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) 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 384736271..02ecee4d4 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 @@ -38,7 +38,7 @@ [/// ["[1]" phase]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -51,12 +51,12 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(def: !unary +(def !unary (template (_ function) (|>> list _.apply (|> (_.constant function))))) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <s>.any <s>.any @@ -98,7 +98,7 @@ _ (generation.save! context_artifact directive)] (in (_.apply (list.partial inputG foreigns) @expression))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) @@ -106,11 +106,11 @@ (/.install "try" (unary //runtime.lux//try)) )) -(def: (left_shifted [parameter subject]) +(def (left_shifted [parameter subject]) (Binary Expression) (_.bit_shl (_.% (_.int +64) parameter) subject)) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -131,15 +131,15 @@ (/.install "char" (unary //runtime.i64//char)) ))) -(def: (f64//% [parameter subject]) +(def (f64//% [parameter subject]) (Binary Expression) (_.fmod/2 [subject parameter])) -(def: (f64//encode subject) +(def (f64//encode subject) (Unary Expression) (_.number_format/2 [subject (_.int +17)])) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -154,15 +154,15 @@ (/.install "encode" (unary ..f64//encode)) (/.install "decode" (unary //runtime.f64//decode))))) -(def: (text//clip [paramO extraO subjectO]) +(def (text//clip [paramO extraO subjectO]) (Trinary Expression) (//runtime.text//clip paramO extraO subjectO)) -(def: (text//index [startO partO textO]) +(def (text//index [startO partO textO]) (Trinary Expression) (//runtime.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -175,14 +175,14 @@ (/.install "clip" (trinary ..text//clip)) ))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty (/.install "log" (unary //runtime.io//log!)) (/.install "error" (unary //runtime.io//throw!))))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux index 535f01072..d63c2c626 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux @@ -34,23 +34,23 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: (array::new size) +(def (array::new size) (Unary Expression) (//runtime.tuple//make size (_.array_fill/3 [(_.int +0) size _.null]))) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary Expression) (_.item indexG arrayG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary Expression) (//runtime.array//write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary Expression) (//runtime.array//write indexG _.null arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -61,7 +61,7 @@ (/.install "delete" (binary array::delete)) ))) -(def: object::new +(def object::new (custom [(all <>.and <s>.text (<>.some <s>.any)) (function (_ extension phase archive [constructor inputsS]) @@ -69,7 +69,7 @@ [inputsG (monad.each ! (phase archive) inputsS)] (in (_.new (_.constant constructor) inputsG))))])) -(def: object::get +(def object::get Handler (custom [(all <>.and <s>.text <s>.any) @@ -78,7 +78,7 @@ [objectG (phase archive objectS)] (in (_.the fieldS objectG))))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <s>.text <s>.any (<>.some <s>.any)) @@ -89,13 +89,13 @@ (in (_.do methodS inputsG objectG))))])) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary Expression) (function.constant <unit>)) - (def: <?> (Unary Expression) (_.=== <unit>))] + [(def <!> (Nullary Expression) (function.constant <unit>)) + (def <?> (Unary Expression) (_.=== <unit>))] [object::null object::null? _.null] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -106,13 +106,13 @@ (/.install "null?" (unary object::null?)) ))) -(def: php::constant +(def php::constant (custom [<s>.text (function (_ extension phase archive name) (at ////////phase.monad in (_.constant name)))])) -(def: php::apply +(def php::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -121,7 +121,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply inputsG abstractionG))))])) -(def: php::pack +(def php::pack (custom [(all <>.and <s>.any <s>.any) (function (_ extension phase archive [formatS dataS]) @@ -130,7 +130,7 @@ dataG (phase archive dataS)] (in (_.pack/2 [formatG (_.splat dataG)]))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "php") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux index 7b0c7cc9b..bb9e2638d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python.lux @@ -12,7 +12,7 @@ [python [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index ef6d301bc..3335bf992 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -45,7 +45,7 @@ [/// ["[1]" phase (.open: "[1]#[0]" monad)]]]]]) -(def: .public (statement expression archive synthesis) +(def .public (statement expression archive synthesis) Phase! (case synthesis ... TODO: Get rid of this ASAP @@ -88,7 +88,7 @@ (/////#each _.return (//function.function statement expression archive abstraction)) )) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -102,7 +102,7 @@ (/////.except extension.invalid_syntax [extension_name %synthesis input])))) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <synthesis>.any <synthesis>.any @@ -156,19 +156,19 @@ else! conditionals!))))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) (/.install "is" (binary (product.uncurried _.is))) (/.install "try" (unary //runtime.lux::try)))) -(def: (capped operation parameter subject) +(def (capped operation parameter subject) (-> (-> (Expression Any) (Expression Any) (Expression Any)) (-> (Expression Any) (Expression Any) (Expression Any))) (//runtime.i64::64 (operation parameter subject))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -189,7 +189,7 @@ (/.install "char" (unary //runtime.i64::char)) ))) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -206,15 +206,15 @@ (/.install "encode" (unary _.repr/1)) (/.install "decode" (unary //runtime.f64::decode))))) -(def: (text::clip [paramO extraO subjectO]) +(def (text::clip [paramO extraO subjectO]) (Trinary (Expression Any)) (//runtime.text::clip paramO extraO subjectO)) -(def: (text::index [startO partO textO]) +(def (text::index [startO partO textO]) (Trinary (Expression Any)) (//runtime.text::index startO partO textO)) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -227,14 +227,14 @@ (/.install "clip" (trinary ..text::clip)) ))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty (/.install "log" (unary //runtime.io::log!)) (/.install "error" (unary //runtime.io::throw!))))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index 7ec9d1083..1c1f170ce 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -33,29 +33,29 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: (array::new size) +(def (array::new size) (Unary (Expression Any)) (|> (list _.none) _.list (_.* size))) -(def: array::length +(def array::length (Unary (Expression Any)) (|>> _.len/1 //runtime.i64::64)) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary (Expression Any)) (_.item indexG arrayG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary (Expression Any)) (//runtime.array::write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary (Expression Any)) (//runtime.array::write indexG _.none arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -66,7 +66,7 @@ (/.install "delete" (binary array::delete)) ))) -(def: object::get +(def object::get Handler (custom [(all <>.and <s>.text <s>.any) @@ -75,7 +75,7 @@ [objectG (phase archive objectS)] (in (_.the fieldS objectG))))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <s>.text <s>.any (<>.some <s>.any)) @@ -86,13 +86,13 @@ (in (_.do methodS inputsG objectG))))])) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary (Expression Any)) (function.constant <unit>)) - (def: <?> (Unary (Expression Any)) (_.= <unit>))] + [(def <!> (Nullary (Expression Any)) (function.constant <unit>)) + (def <?> (Unary (Expression Any)) (_.= <unit>))] [object::none object::none? _.none] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -102,7 +102,7 @@ (/.install "none?" (unary object::none?)) ))) -(def: python::constant +(def python::constant (custom [<s>.text (function (_ extension phase archive name) @@ -110,7 +110,7 @@ [] (in (_.var name))))])) -(def: python::import +(def python::import (custom [<s>.text (function (_ extension phase archive module) @@ -118,7 +118,7 @@ [] (in (_.apply (list (_.string module)) (_.var "__import__")))))])) -(def: python::apply +(def python::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -127,7 +127,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply inputsG abstractionG))))])) -(def: python::function +(def python::function (custom [(all <>.and <s>.i64 <s>.any) (function (_ extension phase archive [arity abstractionS]) @@ -144,7 +144,7 @@ 1 (_.apply g!inputs abstractionG) _ (_.apply (list (_.list g!inputs)) abstractionG))))))])) -(def: python::exec +(def python::exec (custom [(all <>.and <s>.any <s>.any) (function (_ extension phase archive [codeS globalsS]) @@ -153,7 +153,7 @@ globalsG (phase archive globalsS)] (in (//runtime.lux::exec codeG globalsG))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "python") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux index 1fbf60948..487b9958b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r.lux @@ -12,7 +12,7 @@ [r [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index facbc2e58..cdcfb555b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -38,7 +38,7 @@ [/// ["[1]" phase]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -51,12 +51,12 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -... (def: !unary +... (def !unary ... (template (_ function) ... (|>> list _.apply (|> (_.constant function))))) ... ... ... TODO: Get rid of this ASAP -... ... (def: lux::syntax_char_case! +... ... (def lux::syntax_char_case! ... ... (..custom [(all <>.and ... ... <s>.any ... ... <s>.any @@ -81,7 +81,7 @@ ... ... elseG ... ... conditionalsG))))))])) -... (def: lux_procs +... (def lux_procs ... Bundle ... (|> /.empty ... ... (/.install "syntax char case!" lux::syntax_char_case!) @@ -89,12 +89,12 @@ ... ... (/.install "try" (unary //runtime.lux//try)) ... )) -... ... (def: (capped operation parameter subject) +... ... (def (capped operation parameter subject) ... ... (-> (-> Expression Expression Expression) ... ... (-> Expression Expression Expression)) ... ... (//runtime.i64//64 (operation parameter subject))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -114,7 +114,7 @@ (/.install "char" (unary (|>> //runtime.i64_low _.intToUtf8/1))) ))) -... (def: f64_procs +... (def f64_procs ... Bundle ... (<| (/.prefix "f64") ... (|> /.empty @@ -130,19 +130,19 @@ ... ... (/.install "decode" (unary //runtime.f64//decode)) ... ))) -... (def: (text//index [offset sub text]) +... (def (text//index [offset sub text]) ... (Trinary (Expression Any)) ... (//runtime.text//index offset sub text)) -... (def: (text//clip [offset length text]) +... (def (text//clip [offset length text]) ... (Trinary (Expression Any)) ... (//runtime.text//clip offset length text)) -... (def: (text//char [index text]) +... (def (text//char [index text]) ... (Binary (Expression Any)) ... (_.char_code/1 (_.char/2 [text index]))) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -155,12 +155,12 @@ ... (/.install "clip" (trinary ..text//clip)) ))) -... (def: (io//log! message) +... (def (io//log! message) ... (Unary (Expression Any)) ... (_.progn (list (_.write_line/1 message) ... //runtime.unit))) -... (def: io_procs +... (def io_procs ... Bundle ... (<| (/.prefix "io") ... (|> /.empty @@ -168,7 +168,7 @@ ... (/.install "error" (unary _.error/1)) ... ))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux index 8facd6a1a..3fa89672c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/host.lux @@ -34,7 +34,7 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "r") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux index aa8f8e7b3..180444525 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby.lux @@ -12,7 +12,7 @@ [ruby [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index 6cdacfa40..0537a3539 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -43,7 +43,7 @@ [/// ["[1]" phase (.open: "[1]#[0]" monad)]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -56,7 +56,7 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(def: .public (statement expression archive synthesis) +(def .public (statement expression archive synthesis) Phase! (case synthesis ... TODO: Get rid of this ASAP @@ -101,7 +101,7 @@ )) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <s>.any <s>.any @@ -142,7 +142,7 @@ else! conditionals!))))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) @@ -150,7 +150,7 @@ (_.do "equal?" (list reference) {.#None} subject)))) (/.install "try" (unary //runtime.lux//try)))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -173,7 +173,7 @@ (/.install "char" (unary //runtime.i64::char)) ))) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -189,19 +189,19 @@ (/.install "encode" (unary (_.do "to_s" (list) {.#None}))) (/.install "decode" (unary //runtime.f64//decode))))) -(def: (text//char [subjectO paramO]) +(def (text//char [subjectO paramO]) (Binary Expression) (//runtime.text//char subjectO paramO)) -(def: (text//clip [paramO extraO subjectO]) +(def (text//clip [paramO extraO subjectO]) (Trinary Expression) (//runtime.text//clip paramO extraO subjectO)) -(def: (text//index [startO partO textO]) +(def (text//index [startO partO textO]) (Trinary Expression) (//runtime.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -214,16 +214,16 @@ (/.install "clip" (trinary text//clip)) ))) -(def: (io//log! messageG) +(def (io//log! messageG) (Unary Expression) (|> (_.print/2 messageG (_.string text.new_line)) (_.or //runtime.unit))) -(def: io//error! +(def io//error! (Unary Expression) _.raise) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty @@ -231,7 +231,7 @@ (/.install "error" (unary ..io//error!)) ))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux index 89638f972..ce451a263 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux @@ -34,27 +34,27 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: (array::new [size]) +(def (array::new [size]) (Unary Expression) (_.do "new" (list size) {.#None} (is _.CVar (_.manual "Array")))) -(def: array::length +(def array::length (Unary Expression) (_.the "size")) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary Expression) (_.item indexG arrayG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary Expression) (//runtime.array//write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary Expression) (//runtime.array//write indexG _.nil arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -65,7 +65,7 @@ (/.install "delete" (binary array::delete)) ))) -(def: object::get +(def object::get Handler (custom [(all <>.and <s>.text <s>.any) @@ -74,7 +74,7 @@ [objectG (phase archive objectS)] (in (_.the fieldS objectG))))])) -(def: object::do +(def object::do Handler (custom [(all <>.and <s>.text <s>.any (<>.some <s>.any)) @@ -85,13 +85,13 @@ (in (_.do methodS inputsG {.#None} objectG))))])) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary Expression) (function.constant <unit>)) - (def: <?> (Unary Expression) (_.= <unit>))] + [(def <!> (Nullary Expression) (function.constant <unit>)) + (def <?> (Unary Expression) (_.= <unit>))] [object::nil object::nil? _.nil] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -101,13 +101,13 @@ (/.install "nil?" (unary object::nil?)) ))) -(def: ruby::constant +(def ruby::constant (custom [<s>.text (function (_ extension phase archive name) (at ////////phase.monad in (is _.CVar (_.manual name))))])) -(def: ruby::apply +(def ruby::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -116,14 +116,14 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply inputsG {.#None} abstractionG))))])) -(def: ruby::import +(def ruby::import (custom [<s>.text (function (_ extension phase archive module) (at ////////phase.monad in (_.require/1 (_.string module))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "ruby") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux index 7bca45f93..fdca305d2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme.lux @@ -12,7 +12,7 @@ [scheme [runtime (.only Bundle)]]]]]) -(def: .public bundle +(def .public bundle Bundle (dictionary.composite /common.bundle /host.bundle)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index 5d4801be1..20d9da33e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -38,7 +38,7 @@ [/// ["[1]" phase]]]]]) -(def: .public (custom [parser handler]) +(def .public (custom [parser handler]) (All (_ s) (-> [(Parser s) (-> Text (Generator s))] @@ -51,12 +51,12 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(def: !unary +(def !unary (template (_ function) (|>> list _.apply (|> (_.constant function))))) ... TODO: Get rid of this ASAP -(def: lux::syntax_char_case! +(def lux::syntax_char_case! (..custom [(all <>.and <s>.any <s>.any @@ -81,7 +81,7 @@ elseG conditionalsG)))))])) -(def: lux_procs +(def lux_procs Bundle (|> /.empty (/.install "syntax char case!" lux::syntax_char_case!) @@ -89,12 +89,12 @@ (/.install "try" (unary //runtime.lux//try)) )) -(def: (capped operation parameter subject) +(def (capped operation parameter subject) (-> (-> Expression Expression Expression) (-> Expression Expression Expression)) (//runtime.i64//64 (operation parameter subject))) -(def: i64_procs +(def i64_procs Bundle (<| (/.prefix "i64") (|> /.empty @@ -114,7 +114,7 @@ (/.install "char" (unary (|>> _.integer->char/1 (_.make_string/2 (_.int +1))))) ))) -(def: f64_procs +(def f64_procs Bundle (<| (/.prefix "f64") (|> /.empty @@ -129,15 +129,15 @@ (/.install "encode" (unary _.number->string/1)) (/.install "decode" (unary //runtime.f64//decode))))) -(def: (text//index [offset sub text]) +(def (text//index [offset sub text]) (Trinary Expression) (//runtime.text//index offset sub text)) -(def: (text//clip [paramO extraO subjectO]) +(def (text//clip [paramO extraO subjectO]) (Trinary Expression) (//runtime.text//clip paramO extraO subjectO)) -(def: text_procs +(def text_procs Bundle (<| (/.prefix "text") (|> /.empty @@ -150,13 +150,13 @@ (/.install "clip" (trinary ..text//clip)) ))) -(def: (io//log! message) +(def (io//log! message) (Unary Expression) (_.begin (list (_.display/1 message) (_.display/1 (_.string text.new_line)) //runtime.unit))) -(def: io_procs +(def io_procs Bundle (<| (/.prefix "io") (|> /.empty @@ -164,7 +164,7 @@ (/.install "error" (unary _.raise/1)) ))) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "lux") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux index 862df2607..a3989de9f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux @@ -34,27 +34,27 @@ ["//[1]" /// ["[1][0]" phase]]]]]]) -(def: (array::new size) +(def (array::new size) (Unary Expression) (_.make_vector/2 size _.nil)) -(def: array::length +(def array::length (Unary Expression) _.vector_length/1) -(def: (array::read [indexG arrayG]) +(def (array::read [indexG arrayG]) (Binary Expression) (_.vector_ref/2 arrayG indexG)) -(def: (array::write [indexG valueG arrayG]) +(def (array::write [indexG valueG arrayG]) (Trinary Expression) (//runtime.array//write indexG valueG arrayG)) -(def: (array::delete [indexG arrayG]) +(def (array::delete [indexG arrayG]) (Binary Expression) (//runtime.array//write indexG _.nil arrayG)) -(def: array +(def array Bundle (<| (/.prefix "array") (|> /.empty @@ -66,13 +66,13 @@ ))) (with_template [<!> <?> <unit>] - [(def: <!> (Nullary Expression) (function.constant <unit>)) - (def: <?> (Unary Expression) (_.eq?/2 <unit>))] + [(def <!> (Nullary Expression) (function.constant <unit>)) + (def <?> (Unary Expression) (_.eq?/2 <unit>))] [object::nil object::nil? _.nil] ) -(def: object +(def object Bundle (<| (/.prefix "object") (|> /.empty @@ -80,7 +80,7 @@ (/.install "nil?" (unary object::nil?)) ))) -(def: scheme::constant +(def scheme::constant (custom [<s>.text (function (_ extension phase archive name) @@ -88,7 +88,7 @@ [] (in (_.var name))))])) -(def: scheme::apply +(def scheme::apply (custom [(all <>.and <s>.any (<>.some <s>.any)) (function (_ extension phase archive [abstractionS inputsS]) @@ -97,7 +97,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.apply inputsG abstractionG))))])) -(def: .public bundle +(def .public bundle Bundle (<| (/.prefix "scheme") (|> /.empty diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux index dbaa7282b..fcfa9b7ea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/synthesis.lux @@ -6,6 +6,6 @@ [/// [synthesis (.only Bundle)]]]) -(def: .public bundle +(def .public bundle Bundle bundle.empty) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux index e016f9109..e31b13851 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp.lux @@ -25,7 +25,7 @@ [reference (.only) [variable (.only)]]]]]]]) -(def: .public (generate archive synthesis) +(def .public (generate archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux index 553bb6734..671b46045 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux @@ -37,15 +37,15 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register Var/1) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register Var/1) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueG (expression archive valueS) @@ -53,7 +53,7 @@ (in (_.let (list [(..register register) valueG]) (list bodyG))))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testG (expression archive testS) @@ -61,7 +61,7 @@ elseG (expression archive elseS)] (in (_.if testG thenG elseG)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueG (expression archive valueS)] @@ -76,38 +76,38 @@ valueG pathP)))) -(def: @savepoint (_.var "lux_pm_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) -(def: @variant (_.var "lux_pm_variant")) +(def @savepoint (_.var "lux_pm_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) +(def @variant (_.var "lux_pm_variant")) -(def: (push! value) +(def (push! value) (-> (Expression Any) (Expression Any)) (_.setq @cursor (_.cons/2 [value @cursor]))) -(def: pop! +(def pop! (Expression Any) (_.setq @cursor (_.cdr/1 @cursor))) -(def: peek +(def peek (Expression Any) (_.car/1 @cursor)) -(def: save! +(def save! (Expression Any) (_.setq @savepoint (_.cons/2 [@cursor @savepoint]))) -(def: restore! +(def restore! (List (Expression Any)) (list (_.setq @cursor (_.car/1 @savepoint)) (_.setq @savepoint (_.cdr/1 @savepoint)))) -(def: (multi_pop! pops) +(def (multi_pop! pops) (-> Nat (Expression Any)) (_.setq @cursor (_.nthcdr/2 [(_.int (.int pops)) @cursor]))) (with_template [<name> <flag> <prep>] - [(def: (<name> @fail simple? idx next!) + [(def (<name> @fail simple? idx next!) (-> _.Tag Bit Nat (Maybe (Expression Any)) (Expression Any)) (.let [<failure_condition> (_.eq/2 [@variant @temp])] (_.let (list [@variant ..peek]) @@ -129,7 +129,7 @@ [right_choice (_.string "") ++] ) -(def: (alternation @otherwise pre! post!) +(def (alternation @otherwise pre! post!) (-> _.Tag (Expression Any) (Expression Any) (Expression Any)) (_.tagbody (all list#composite (list ..save! @@ -138,7 +138,7 @@ ..restore! (list post!)))) -(def: (pattern_matching' expression archive) +(def (pattern_matching' expression archive) (Generator [Var/1 _.Tag _.Tag Path]) (function (again [$output @done @fail pathP]) (.case pathP @@ -230,7 +230,7 @@ post! (again [$output @done @fail postP])] (in (_.progn (list pre! post!))))))) -(def: (pattern_matching $output expression archive pathP) +(def (pattern_matching $output expression archive pathP) (-> Var/1 (Generator Path)) (do [! ///////phase.monad] [@done (at ! each (|>> %.nat (format "lux_case_done") _.tag) /////generation.next) @@ -242,7 +242,7 @@ (_.error/1 (_.string ////synthesis/case.pattern_matching_error)) @done))))) -(def: .public (case expression archive [valueS pathP]) +(def .public (case expression archive [valueS pathP]) (Generator [Synthesis Path]) (do [! ///////phase.monad] [initG (expression archive valueS) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux index 90acc3cef..eac649c9c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension.lux @@ -9,6 +9,6 @@ [/ ["[0]" common]]) -(def: .public bundle +(def .public bundle Bundle common.bundle) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux index 36e3a4a95..e0e2a756d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/extension/common.lux @@ -23,26 +23,26 @@ [extension ["[0]" bundle]]]]]) -(def: lux_procs +(def lux_procs Bundle (|> bundle.empty (bundle.install "is" (binary (product.uncurried _.eq))) (bundle.install "try" (unary ///runtime.lux//try)))) -(def: (i64//left_shifted [paramG subjectG]) +(def (i64//left_shifted [paramG subjectG]) (Binary (Expression Any)) (_.ash (_.rem (_.int +64) paramG) subjectG)) -(def: (i64//arithmetic_right_shifted [paramG subjectG]) +(def (i64//arithmetic_right_shifted [paramG subjectG]) (Binary (Expression Any)) (_.ash (|> paramG (_.rem (_.int +64)) (_.* (_.int -1))) subjectG)) -(def: (i64//logic_right_shifted [paramG subjectG]) +(def (i64//logic_right_shifted [paramG subjectG]) (Binary (Expression Any)) (///runtime.i64//logic_right_shifted (_.rem (_.int +64) paramG) subjectG)) -(def: i64_procs +(def i64_procs Bundle (<| (bundle.prefix "i64") (|> bundle.empty @@ -64,7 +64,7 @@ (bundle.install "char" (unary (|>> _.code_char/1 _.string/1))) ))) -(def: f64_procs +(def f64_procs Bundle (<| (bundle.prefix "f64") (|> bundle.empty @@ -85,21 +85,21 @@ (///runtime.some @temp) ///runtime.none))))))))) -(def: (text//< [paramG subjectG]) +(def (text//< [paramG subjectG]) (Binary (Expression Any)) (|> (_.string< paramG subjectG) _.null/1 _.not/1)) -(def: (text//clip [paramO extraO subjectO]) +(def (text//clip [paramO extraO subjectO]) (Trinary (Expression Any)) (///runtime.text//clip subjectO paramO extraO)) -(def: (text//index [startO partO textO]) +(def (text//index [startO partO textO]) (Trinary (Expression Any)) (///runtime.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (bundle.prefix "text") (|> bundle.empty @@ -112,13 +112,13 @@ (bundle.install "clip" (trinary text//clip)) ))) -(def: (void code) +(def (void code) (-> (Expression Any) (Expression Any)) (all _.progn code ///runtime.unit)) -(def: io_procs +(def io_procs Bundle (<| (bundle.prefix "io") (|> bundle.empty @@ -126,7 +126,7 @@ (bundle.install "error" (unary _.error/1)) ))) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index 29ed270dd..9029be0ed 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -29,18 +29,18 @@ [reference [variable (.only Register Variable)]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do [! ///////phase.monad] [functionG (expression archive functionS) argsG+ (monad.each ! (expression archive) argsS+)] (in (_.funcall/+ [functionG argsG+])))) -(def: capture +(def capture (-> Register Var/1) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure inits function_definition) +(def (with_closure inits function_definition) (-> (List (Expression Any)) (Expression Any) (Operation (Expression Any))) (case inits {.#End} @@ -55,10 +55,10 @@ function_definition]]) (_.funcall/+ [(_.function/1 @closure) inits])))))) -(def: input +(def input (|>> ++ //case.register)) -(def: .public (function expression archive [environment arity bodyS]) +(def .public (function expression archive [environment arity bodyS]) (Generator (Abstraction Synthesis)) (do [! ///////phase.monad] [@scope (at ! each (|>> %.nat (format "function_scope") _.tag) /////generation.next) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux index 7d6e7a6e7..f71d3e18b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/loop.lux @@ -32,7 +32,7 @@ [reference [variable (.only Register)]]]]]]]) -(def: .public (scope expression archive [start initsS+ bodyS]) +(def .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -58,7 +58,7 @@ (_.setq @output bodyG))) @output)))))) -(def: .public (again expression archive argsS+) +(def .public (again expression archive argsS+) (Generator (List Synthesis)) (do [! ///////phase.monad] [[tag offset] /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux index 43a98c287..419179137 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/primitive.lux @@ -4,18 +4,18 @@ [target ["_" common_lisp (.only Expression)]]]]) -(def: .public bit +(def .public bit (-> Bit (Expression Any)) _.bool) -(def: .public i64 +(def .public i64 (-> (I64 Any) (Expression Any)) (|>> .int _.int)) -(def: .public f64 +(def .public f64 (-> Frac (Expression Any)) _.double) -(def: .public text +(def .public text (-> Text (Expression Any)) _.string) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux index b64f9ecbb..7b2dcab79 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System (Expression Any)) (implementation - (def: constant _.var) - (def: variable _.var))) + (def constant _.var) + (def variable _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index e5b54688c..a924fbe8f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -38,7 +38,7 @@ [archive (.only Output Archive) ["[0]" artifact (.only Registry)]]]]]]) -(def: module_id +(def module_id 0) (with_template [<name> <base>] @@ -54,40 +54,40 @@ (type: .public (Generator i) (-> Phase Archive i (Operation (Expression Any)))) -(def: .public unit +(def .public unit (_.string /////synthesis.unit)) -(def: (flag value) +(def (flag value) (-> Bit Literal) (if value (_.string "") _.nil)) -(def: (variant' tag last? value) +(def (variant' tag last? value) (-> (Expression Any) (Expression Any) (Expression Any) (Computation Any)) (_.list/* (list tag last? value))) -(def: .public (variant [lefts right? value]) +(def .public (variant [lefts right? value]) (-> (Variant (Expression Any)) (Computation Any)) (variant' (_.int (.int lefts)) (flag right?) value)) -(def: .public none +(def .public none (Computation Any) (|> ..unit [0 #0] ..variant)) -(def: .public some +(def .public some (-> (Expression Any) (Computation Any)) (|>> [1 #1] ..variant)) -(def: .public left +(def .public left (-> (Expression Any) (Computation Any)) (|>> [0 #0] ..variant)) -(def: .public right +(def .public right (-> (Expression Any) (Computation Any)) (|>> [1 #1] ..variant)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -100,7 +100,7 @@ list.together))] (~ body)))))))) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -114,11 +114,11 @@ {.#Left name} (let [g!name (code.local name) code_nameC (code.local (format "@" name))] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) _.Var/1 (~ runtime_name))) - (` (def: (~ code_nameC) + (` (def (~ code_nameC) (_.Expression Any) (_.defparameter (~ runtime_name) (~ code))))))) @@ -129,11 +129,11 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) (_.Computation Any)) (_.call/* (~ runtime_name) (list (~+ inputsC))))) - (` (def: (~ code_nameC) + (` (def (~ code_nameC) (_.Expression Any) (..with_vars [(~+ inputsC)] (_.defun (~ runtime_name) (_.args (list (~+ inputsC))) @@ -159,18 +159,18 @@ (list (_.reverse/1 inputs) ..none)])))) -(def: runtime//lux +(def runtime//lux (List (Expression Any)) (list @lux//try @lux//program_args)) -(def: last_index +(def last_index (|>> _.length/1 [(_.int +1)] _.-/2)) (with_expansions [<recur> (these (all _.then (_.; (_.set lefts (_.-/2 [last_index_right lefts]))) (_.; (_.set tuple (_.nth last_index_right tuple)))))] - (def: !recur + (def !recur (template (_ <side>) (<side> (_.-/2 [last_index_right lefts]) (_.elt/2 [tuple last_index_right])))) @@ -223,7 +223,7 @@ no_match!))))))) -(def: runtime//adt +(def runtime//adt (List (Expression Any)) (list @tuple//left @tuple//right @@ -240,7 +240,7 @@ [(_.*/2 [(_.int -1) shift])] _.ash/2 [mask] _.logand/2)))) -(def: runtime//i64 +(def runtime//i64 (List (Expression Any)) (list @i64//right_shifted)) @@ -254,7 +254,7 @@ (..some index) ..none))))) -(def: runtime//text +(def runtime//text (List (Expression Any)) (list @text//index @text//clip)) @@ -270,11 +270,11 @@ (_.call/* (_.var "excl:exit") (list code))) (_.call/* (_.var "cl-user::quit") (list code))))) -(def: runtime//io +(def runtime//io (List (Expression Any)) (list @io//exit)) -(def: runtime +(def runtime (_.progn (all list#composite runtime//adt runtime//lux @@ -282,7 +282,7 @@ runtime//text runtime//io))) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux index b14e852b1..05ed5efea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/structure.lux @@ -14,7 +14,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple expression archive elemsS+) +(def .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -28,7 +28,7 @@ (monad.each ///////phase.monad (expression archive)) (///////phase#each _.vector/*)))) -(def: .public (variant expression archive [lefts right? valueS]) +(def .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (++ lefts) 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 78d2d4295..680957008 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 @@ -21,17 +21,17 @@ [/// ["[1]" phase]]]]) -(def: Vector +(def Vector (syntax (_ [size <code>.nat elemT <code>.any]) (in (list (` [(~+ (list.repeated size elemT))]))))) -(def: Arity +(def Arity (template (_ arity) [(All (_ of) (-> (Vector arity of) of))])) -(def: arity +(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] (do [! meta.monad] @@ -58,7 +58,7 @@ (with_template [<arity> <type> <term>] [(type: .public <type> (Arity <arity>)) - (def: .public <term> (arity <arity>))] + (def .public <term> (arity <arity>))] [0 Nullary nullary] [1 Unary unary] @@ -69,7 +69,7 @@ (type: .public (Variadic of) (-> (List of) of)) -(def: .public (variadic extension) +(def .public (variadic extension) (All (_ anchor expression directive) (-> (Variadic expression) (generation.Handler anchor expression directive))) (function (_ extension_name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux index a5471f9b6..5d6b92824 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js.lux @@ -34,7 +34,7 @@ (exception: .public cannot_recur_as_an_expression) -(def: (expression archive synthesis) +(def (expression archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] @@ -84,6 +84,6 @@ {synthesis.#Extension extension} (///extension.apply archive expression extension))) -(def: .public generate +(def .public generate Phase ..expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index aa18b4348..2e48dea7c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -36,11 +36,11 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register Var) (|>> (///reference.local //reference.system) as_expected)) -(def: .public (exec expression archive [this that]) +(def .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) (do ///////phase.monad [this (expression archive this) @@ -48,7 +48,7 @@ (in (|> (_.array (list this that)) (_.at (_.int +1)))))) -(def: .public (exec! statement expression archive [this that]) +(def .public (exec! statement expression archive [this that]) (Generator! [Synthesis Synthesis]) (do ///////phase.monad [this (expression archive this) @@ -57,7 +57,7 @@ (_.statement this) that)))) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -67,7 +67,7 @@ (_.return bodyO)) (list valueO))))) -(def: .public (let! statement expression archive [valueS register bodyS]) +(def .public (let! statement expression archive [valueS register bodyS]) (Generator! [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -76,7 +76,7 @@ (_.define (..register register) valueO) bodyO)))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -84,7 +84,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: .public (if! statement expression archive [testS thenS elseS]) +(def .public (if! statement expression archive [testS thenS elseS]) (Generator! [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -94,7 +94,7 @@ thenO elseO)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -106,51 +106,51 @@ valueO (list.reversed pathP))))) -(def: @savepoint (_.var "lux_pm_cursor_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) +(def @savepoint (_.var "lux_pm_cursor_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) -(def: (push_cursor! value) +(def (push_cursor! value) (-> Expression Statement) (_.statement (|> @cursor (_.do "push" (list value))))) -(def: peek_and_pop_cursor +(def peek_and_pop_cursor Expression (|> @cursor (_.do "pop" (list)))) -(def: pop_cursor! +(def pop_cursor! Statement (_.statement ..peek_and_pop_cursor)) -(def: length +(def length (|>> (_.the "length"))) -(def: last_index +(def last_index (|>> ..length (_.- (_.i32 +1)))) -(def: peek_cursor +(def peek_cursor Expression (|> @cursor (_.at (last_index @cursor)))) -(def: save_cursor! +(def save_cursor! Statement (.let [cursor (|> @cursor (_.do "slice" (list)))] (_.statement (|> @savepoint (_.do "push" (list cursor)))))) -(def: restore_cursor! +(def restore_cursor! Statement (_.set @cursor (|> @savepoint (_.do "pop" (list))))) -(def: fail_pm! _.break) +(def fail_pm! _.break) -(def: (multi_pop_cursor! pops) +(def (multi_pop_cursor! pops) (-> Nat Statement) (.let [popsJS (_.i32 (.int pops))] (_.statement (|> @cursor (_.do "splice" (list (|> @cursor ..length (_.- popsJS)) popsJS)))))) (with_template [<name> <flag>] - [(def: (<name> simple? idx) + [(def (<name> simple? idx) (-> Bit Nat Statement) (all _.then (_.set @temp (//runtime.sum//get ..peek_cursor <flag> @@ -166,7 +166,7 @@ [right_choice //runtime.unit] ) -(def: (alternation pre! post!) +(def (alternation pre! post!) (-> Statement Statement Statement) (all _.then (_.do_while (_.boolean false) @@ -177,7 +177,7 @@ ..restore_cursor! post!))) -(def: (optimized_pattern_matching again pathP) +(def (optimized_pattern_matching again pathP) (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP @@ -233,7 +233,7 @@ _ (///////phase#in {.#None}))) -(def: (pattern_matching' statement expression archive) +(def (pattern_matching' statement expression archive) (-> Phase! Phase Archive (-> Path (Operation Statement))) (function (again pathP) @@ -318,7 +318,7 @@ ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation])))))) -(def: (pattern_matching statement expression archive pathP) +(def (pattern_matching statement expression archive pathP) (-> Phase! Phase Archive Path (Operation Statement)) (do ///////phase.monad [pattern_matching! (pattern_matching' statement expression archive pathP)] @@ -327,7 +327,7 @@ pattern_matching!) (_.throw (_.string ////synthesis/case.pattern_matching_error)))))) -(def: .public (case! statement expression archive [valueS pathP]) +(def .public (case! statement expression archive [valueS pathP]) (Generator! [Synthesis Path]) (do ///////phase.monad [stack_init (expression archive valueS) @@ -338,7 +338,7 @@ (_.define @savepoint (_.array (list))) pattern_matching!)))) -(def: .public (case statement expression archive [valueS pathP]) +(def .public (case statement expression archive [valueS pathP]) (-> Phase! (Generator [Synthesis Path])) (do ///////phase.monad [pattern_matching! (..case! statement expression archive [valueS pathP])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index 58b0e104a..c7c5226ac 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -33,18 +33,18 @@ [dependency ["[1]" artifact]]]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Reification Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply functionO argsO+)))) -(def: capture +(def capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure @self inits body!) +(def (with_closure @self inits body!) (-> Var (List Expression) Statement [Statement Expression]) (case inits {.#End} @@ -58,20 +58,20 @@ (_.return (_.function @self (list) body!))) (_.apply @self inits)])) -(def: @curried +(def @curried (_.var "curried")) -(def: input +(def input (|>> ++ //case.register)) -(def: @@arguments +(def @@arguments (_.var "arguments")) -(def: (@scope function_name) +(def (@scope function_name) (-> unit.ID Text) (format (///reference.artifact function_name) "_scope")) -(def: .public (function statement expression archive [environment arity bodyS]) +(def .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do [! ///////phase.monad] [dependencies (cache.dependencies archive bodyS) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux index de5ee0616..eb9d60063 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux @@ -25,15 +25,15 @@ [reference [variable (.only Register)]]]]]) -(def: @scope +(def @scope (-> Nat Text) (|>> %.nat (format "scope"))) -(def: $iteration +(def $iteration (-> Nat Var) (|>> %.nat (format "iteration") _.var)) -(def: (setup $iteration initial? offset bindings body) +(def (setup $iteration initial? offset bindings body) (-> Var Bit Register (List Expression) Statement Statement) (case bindings (pattern (list)) @@ -60,7 +60,7 @@ (list#mix _.then body) (_.then (_.define $iteration (_.array bindings)))))) -(def: .public (scope! statement expression archive [start initsS+ bodyS]) +(def .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -82,7 +82,7 @@ (_.do_while (_.boolean true) body!))))))) -(def: .public (scope statement expression archive [start initsS+ bodyS]) +(def .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop @@ -95,10 +95,10 @@ [loop! (scope! statement expression archive [start initsS+ bodyS])] (in (_.apply (_.closure (list) loop!) (list)))))) -(def: @temp +(def @temp (_.var "lux_again_values")) -(def: .public (again! statement expression archive argsS+) +(def .public (again! statement expression archive argsS+) (Generator! (List Synthesis)) (do [! ///////phase.monad] [[offset @scope] /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux index aa45d7b64..19dd18af2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/primitive.lux @@ -6,16 +6,16 @@ ["[0]" // ["[1][0]" runtime]]) -(def: .public bit +(def .public bit _.boolean) -(def: .public (i64 value) +(def .public (i64 value) (-> (I64 Any) Computation) (//runtime.i64 (|> value //runtime.high .int _.i32) (|> value //runtime.low .int _.i32))) -(def: .public f64 +(def .public f64 _.number) -(def: .public text +(def .public text _.string) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux index 8a042db48..6cca81aeb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant' _.var) - (def: variable' _.var))) + (def constant' _.var) + (def variable' _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index 0bda3304e..41da758da 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -58,30 +58,30 @@ (type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: .public high +(def .public high (-> (I64 Any) (I64 Any)) (i64.right_shifted 32)) -(def: .public low +(def .public low (-> (I64 Any) (I64 Any)) (let [mask (-- (i64.left_shifted 32 1))] (|>> (i64.and mask)))) -(def: .public unit +(def .public unit Computation (_.string /////synthesis.unit)) -(def: .public (flag value) +(def .public (flag value) (-> Bit Computation) (if value (_.string "") _.null)) -(def: (feature name definition) +(def (feature name definition) (-> Var (-> Var Expression) Statement) (_.define name (definition name))) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -94,7 +94,7 @@ list.together))] (~ body)))))))) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -104,11 +104,11 @@ (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) Var (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!name)) @@ -118,11 +118,11 @@ (let [g!name (code.local name) inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply (~ runtime_name) (list (~+ inputsC))))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!_)) @@ -130,15 +130,15 @@ (_.function (~ g!_) (list (~+ inputsC)) (~ code))))))))))))))) -(def: length +(def length (-> Expression Computation) (_.the "length")) -(def: last_index +(def last_index (-> Expression Computation) (|>> ..length (_.- (_.i32 +1)))) -(def: (last_element tuple) +(def (last_element tuple) (_.at (..last_index tuple) tuple)) @@ -170,9 +170,9 @@ (_.return (_.do "slice" (list right_index) tuple))) ))))) -(def: .public variant_tag_field "_lux_tag") -(def: .public variant_flag_field "_lux_flag") -(def: .public variant_value_field "_lux_value") +(def .public variant_tag_field "_lux_tag") +(def .public variant_flag_field "_lux_flag") +(def .public variant_value_field "_lux_value") (runtime: variant//new (let [@this (_.var "this")] @@ -184,7 +184,7 @@ (_.set (_.the ..variant_value_field @this) value) ))))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Expression Expression Expression Computation) (_.new ..variant//new (list tag last? value))) @@ -216,23 +216,23 @@ actual::value))) mismatch!))) -(def: left +(def left (-> Expression Computation) (..variant (_.i32 +0) (flag #0))) -(def: right +(def right (-> Expression Computation) (..variant (_.i32 +0) (flag #1))) -(def: none +(def none Computation (..left ..unit)) -(def: some +(def some (-> Expression Computation) ..right) -(def: runtime//structure +(def runtime//structure Statement (all _.then @tuple//left @@ -258,15 +258,15 @@ output))))) (_.return output)))) -(def: runtime//lux +(def runtime//lux Statement (all _.then @lux//try @lux//program_args )) -(def: .public i64_low_field Text "_lux_low") -(def: .public i64_high_field Text "_lux_high") +(def .public i64_low_field Text "_lux_low") +(def .public i64_high_field Text "_lux_high") (runtime: i64::new (let [@this (_.var "this")] @@ -277,7 +277,7 @@ (_.set (_.the ..i64_low_field @this) low) ))))) -(def: .public (i64 high low) +(def .public (i64 high low) (-> Expression Expression Computation) (_.new ..i64::new (list high low))) @@ -297,16 +297,16 @@ (_.return (..i64 (_.bit_not (_.the ..i64_high_field value)) (_.bit_not (_.the ..i64_low_field value))))) -(def: (cap_shift! shift) +(def (cap_shift! shift) (-> Var Statement) (_.set shift (|> shift (_.bit_and (_.i32 +63))))) -(def: (no_shift! shift input) +(def (no_shift! shift input) (-> Var Var (-> Expression Expression)) (_.? (|> shift (_.= (_.i32 +0))) input)) -(def: small_shift? +(def small_shift? (-> Var Expression) (|>> (_.< (_.i32 +32)))) @@ -352,7 +352,7 @@ (..i64 (_.i32 +0) (|> input (_.the ..i64_high_field) (_.logic_right_shift (_.- (_.i32 +32) shift)))))))) -(def: runtime//bit +(def runtime//bit Statement (all _.then @i64::and @@ -536,12 +536,12 @@ (negative? (i64::- parameter subject)))) )))) -(def: (i64::<= param subject) +(def (i64::<= param subject) (-> Expression Expression Expression) (|> (i64::< param subject) (_.or (i64::= param subject)))) -(def: negative? +(def negative? (i64::< i64::zero)) (runtime: (i64::/ parameter subject) @@ -626,7 +626,7 @@ (i64::* parameter))] (_.return (i64::- flat subject)))) -(def: runtime//i64 +(def runtime//i64 Statement (all _.then ..runtime//bit @@ -675,7 +675,7 @@ (_.throw (_.string "[Lux Error] Cannot get char from text.")) (_.return (i64::of_number result)))))) -(def: runtime//text +(def runtime//text Statement (all _.then @text//index @@ -704,7 +704,7 @@ (runtime: (io//error message) (_.throw message)) -(def: runtime//io +(def runtime//io Statement (all _.then @io//log @@ -729,7 +729,7 @@ (_.statement (_.delete (_.at field object))) (_.return object))) -(def: runtime//js +(def runtime//js Statement (all _.then @js//get @@ -747,14 +747,14 @@ (_.statement (_.delete (_.at (_.the ..i64_low_field idx) array))) (_.return array))) -(def: runtime//array +(def runtime//array Statement (all _.then @array//write @array//delete )) -(def: runtime +(def runtime Statement (all _.then runtime//structure @@ -766,10 +766,10 @@ runtime//lux )) -(def: module_id +(def module_id 0) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux index 14e911912..9fdbc4592 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/structure.lux @@ -15,7 +15,7 @@ ["//[1]" /// (.only) ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple generate archive elemsS+) +(def .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -29,7 +29,7 @@ [elemsT+ (monad.each ! (generate archive) elemsS+)] (in (_.array elemsT+))))) -(def: .public (variant generate archive [lefts right? valueS]) +(def .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (///////phase#each (//runtime.variant (_.i32 (.int lefts)) (//runtime.flag right?)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux index a23f31e36..0a8c1c026 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm.lux @@ -21,7 +21,7 @@ ["[0]" reference] ["[1]" phase (.open: "[1]#[0]" monad)]]]]]) -(def: .public (generate archive synthesis) +(def .public (generate archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux index 73ec8260e..0ae4da146 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/case.lux @@ -39,7 +39,7 @@ [reference [variable (.only Register)]]]]]) -(def: (pop_alt stack_depth) +(def (pop_alt stack_depth) (-> Nat (Bytecode Any)) (.case stack_depth 0 (_#in []) @@ -50,27 +50,27 @@ _.pop2 (pop_alt (n.- 2 stack_depth))))) -(def: int +(def int (-> (I64 Any) (Bytecode Any)) (|>> .i64 i32.i32 _.int)) -(def: long +(def long (-> (I64 Any) (Bytecode Any)) (|>> .int _.long)) -(def: peek +(def peek (Bytecode Any) (all _.composite _.dup (//runtime.get //runtime.stack_head))) -(def: pop +(def pop (Bytecode Any) (all _.composite (//runtime.get //runtime.stack_tail) (_.checkcast //type.stack))) -(def: (left_projection lefts) +(def (left_projection lefts) (-> Nat (Bytecode Any)) (all _.composite (_.checkcast //type.tuple) @@ -82,25 +82,25 @@ lefts //runtime.left_projection))) -(def: (right_projection lefts) +(def (right_projection lefts) (-> Nat (Bytecode Any)) (all _.composite (_.checkcast //type.tuple) (..int lefts) //runtime.right_projection)) -(def: equals@Object +(def equals@Object (.let [class (type.class "java.lang.Object" (list)) method (type.method [(list) (list //type.value) type.boolean (list)])] (_.invokevirtual class "equals" method))) -(def: (path|bind register) +(def (path|bind register) (-> Register (Operation (Bytecode Any))) (operation#in (all _.composite ..peek (_.astore register)))) -(def: (path|bit_fork again @else [when thenP elseP]) +(def (path|bit_fork again @else [when thenP elseP]) (-> (-> Path (Operation (Bytecode Any))) Label [Bit Path (Maybe Path)] (Operation (Bytecode Any))) @@ -124,7 +124,7 @@ else!))))) (with_template [<name> <type> <unwrap> <dup> <pop> <test> <comparison> <if>] - [(def: (<name> again @else cons) + [(def (<name> again @else cons) (-> (-> Path (Operation (Bytecode Any))) Label (Fork <type> Path) (Operation (Bytecode Any))) @@ -157,7 +157,7 @@ [path|text_fork Text (at _.monad in []) _.dup _.pop _.string ..equals@Object _.ifeq] ) -(def: (path' stack_depth @else @end phase archive) +(def (path' stack_depth @else @end phase archive) (-> Nat Label Label (Generator Path)) (function (again path) (.case path @@ -242,7 +242,7 @@ right!))) ))) -(def: (path @end phase archive path) +(def (path @end phase archive path) (-> Label (Generator Path)) (do phase.monad [@else //runtime.forge_label @@ -257,7 +257,7 @@ )) )))) -(def: .public (if phase archive [testS thenS elseS]) +(def .public (if phase archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do phase.monad [test! (phase archive testS) @@ -277,7 +277,7 @@ (<| (_.when_acknowledged @end) (_.set_label @end))))))) -(def: .public (exec phase archive [this that]) +(def .public (exec phase archive [this that]) (Generator [Synthesis Synthesis]) (do phase.monad [this! (phase archive this) @@ -287,7 +287,7 @@ _.pop that!)))) -(def: .public (let phase archive [inputS register bodyS]) +(def .public (let phase archive [inputS register bodyS]) (Generator [Synthesis Register Synthesis]) (do phase.monad [input! (phase archive inputS) @@ -297,7 +297,7 @@ (_.astore register) body!)))) -(def: .public (get phase archive [path recordS]) +(def .public (get phase archive [path recordS]) (Generator [(List Member) Synthesis]) (do phase.monad [record! (phase archive recordS)] @@ -311,7 +311,7 @@ record! (list.reversed path))))) -(def: .public (case phase archive [valueS path]) +(def .public (case phase archive [valueS path]) (Generator [Synthesis Path]) (do phase.monad [@end //runtime.forge_label diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux index f86e61b14..5f07e5300 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux @@ -13,9 +13,9 @@ [world ["[0]" file (.only File)]]]]) -(def: extension ".class") +(def extension ".class") -(def: .public (write_class! name bytecode) +(def .public (write_class! name bytecode) (-> Text Binary (IO Text)) (let [file_path (format name ..extension)] (do io.monad diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index a87be42cc..a4147be81 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -67,7 +67,7 @@ [reference [variable (.only Register)]]]]]]) -(def: .public (with generate archive @begin class environment arity body) +(def .public (with generate archive @begin class environment arity body) (-> Phase Archive Label External (Environment Synthesis) Arity (Bytecode Any) (Operation [(List (Resource Field)) (List (Resource Method)) @@ -90,21 +90,21 @@ [instance (/new.instance generate archive classT environment arity)] (in [fields methods instance])))) -(def: modifier +(def modifier (Modifier Class) (all modifier#composite class.public class.final)) -(def: this_offset 1) +(def this_offset 1) -(def: internal +(def internal (All (_ category) (-> (Type (<| Return' Value' category)) Internal)) (|>> type.reflection reflection.reflection name.internal)) -(def: .public (abstraction generate archive [environment arity bodyS]) +(def .public (abstraction generate archive [environment arity bodyS]) (Generator Abstraction) (do phase.monad [dependencies (cache/artifact.dependencies archive bodyS) @@ -127,7 +127,7 @@ _ (generation.save! (product.right function_context) {.#None} bytecode)] (in instance))) -(def: (apply/?' generate archive [abstractionG inputsS]) +(def (apply/?' generate archive [abstractionG inputsS]) (Generator [(Bytecode Any) (List Synthesis)]) (do [! phase.monad] [inputsG (monad.each ! (generate archive) inputsS)] @@ -144,13 +144,13 @@ )))) )))) -(def: (apply/? generate archive [abstractionS inputsS]) +(def (apply/? generate archive [abstractionS inputsS]) (Generator Apply) (do [! phase.monad] [abstractionG (generate archive abstractionS)] (apply/?' generate archive [abstractionG inputsS]))) -(def: (apply/= generate archive [$abstraction @abstraction arity inputsS]) +(def (apply/= generate archive [$abstraction @abstraction arity inputsS]) (Generator [Symbol unit.ID Arity (List Synthesis)]) (do [! phase.monad] [.let [:abstraction: (type.class (//runtime.class_name @abstraction) (list))] @@ -162,13 +162,13 @@ (/implementation.call :abstraction: arity) )))) -(def: (apply/> generate archive [$abstraction @abstraction arity inputsS]) +(def (apply/> generate archive [$abstraction @abstraction arity inputsS]) (Generator [Symbol unit.ID Arity (List Synthesis)]) (do [! phase.monad] [=G (apply/= generate archive [$abstraction @abstraction arity (list.first arity inputsS)])] (apply/?' generate archive [=G (list.after arity inputsS)]))) -(def: .public (apply generate archive [abstractionS inputsS]) +(def .public (apply generate archive [abstractionS inputsS]) (Generator Apply) (case abstractionS (pattern (synthesis.constant $abstraction)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux index feebb5be2..cf462455e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/abstract.lux @@ -13,13 +13,13 @@ [constant ["[0]" arity]]]]) -... (def: .public artifact_id +... (def .public artifact_id ... 1) -(def: .public class +(def .public class ... (type.class (%.nat artifact_id) (list)) (type.class "library.lux.Function" (list))) -(def: .public init +(def .public init (Type Method) (type.method [(list) (list arity.type) type.void (list)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux index 4aea4dc4f..dcbaef747 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant.lux @@ -13,7 +13,7 @@ [constant [pool (.only Resource)]]]]]]) -(def: modifier +(def modifier (Modifier Field) (all modifier#composite field.public @@ -21,6 +21,6 @@ field.final )) -(def: .public (constant name type) +(def .public (constant name type) (-> Text (Type Value) (Resource Field)) (field.field ..modifier name #0 type (sequence.sequence))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux index 1edd1ce40..3892b9ef0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/constant/arity.lux @@ -10,7 +10,7 @@ [///////// [arity (.only Arity)]]]) -(def: .public minimum Arity 1) -(def: .public maximum Arity 8) +(def .public minimum Arity 1) +(def .public maximum Arity 8) -(def: .public type type.int) +(def .public type type.int) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux index 737c6ac4b..0ae3854a7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable.lux @@ -21,34 +21,34 @@ [reference [variable (.only Register)]]]]) -(def: .public type ////type.value) +(def .public type ////type.value) -(def: .public (get class name) +(def .public (get class name) (-> (Type Class) Text (Bytecode Any)) (all _.composite ////reference.this (_.getfield class name ..type) )) -(def: .public (put naming class register value) +(def .public (put naming class register value) (-> (-> Register Text) (Type Class) Register (Bytecode Any) (Bytecode Any)) (all _.composite ////reference.this value (_.putfield class (naming register) ..type))) -(def: modifier +(def modifier (Modifier Field) (all modifier#composite field.private field.final )) -(def: .public (variable name type) +(def .public (variable name type) (-> Text (Type Value) (Resource Field)) (field.field ..modifier name #0 type (sequence.sequence))) -(def: .public (variables naming amount) +(def .public (variables naming amount) (-> (-> Register Text) Nat (List (Resource Field))) (|> amount list.indices diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux index 90f8426d7..e84776579 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/count.lux @@ -13,20 +13,20 @@ ["[0]" //// ["[1][0]" abstract]]) -(def: .public field "partials") -(def: .public type type.int) +(def .public field "partials") +(def .public type type.int) -(def: .public initial +(def .public initial (Bytecode Any) (|> +0 signed.s1 try.trusted _.bipush)) -(def: this +(def this _.aload_0) -(def: .public value +(def .public value (Bytecode Any) (all _.composite ..this diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux index 545cf8396..f403f723c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux @@ -22,18 +22,18 @@ [reference [variable (.only Register)]]]]]]) -(def: .public (closure environment) +(def .public (closure environment) (-> (Environment Synthesis) (List (Type Value))) (list.repeated (list.size environment) //.type)) -(def: .public (get class register) +(def .public (get class register) (-> (Type Class) Register (Bytecode Any)) (//.get class (/////reference.foreign_name register))) -(def: .public (put class register value) +(def .public (put class register value) (-> (Type Class) Register (Bytecode Any) (Bytecode Any)) (//.put /////reference.foreign_name class register value)) -(def: .public variables +(def .public variables (-> (Environment Synthesis) (List (Resource Field))) (|>> list.size (//.variables /////reference.foreign_name))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux index 1684e6f8c..36d83b0f1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial.lux @@ -29,7 +29,7 @@ [reference [variable (.only Register)]]]]]]) -(def: .public (initial amount) +(def .public (initial amount) (-> Nat (Bytecode Any)) (all _.composite (|> _.aconst_null @@ -37,19 +37,19 @@ (monad.all _.monad)) (_#in []))) -(def: .public (get class register) +(def .public (get class register) (-> (Type Class) Register (Bytecode Any)) (//.get class (/////reference.partial_name register))) -(def: .public (put class register value) +(def .public (put class register value) (-> (Type Class) Register (Bytecode Any) (Bytecode Any)) (//.put /////reference.partial_name class register value)) -(def: .public variables +(def .public variables (-> Arity (List (Resource Field))) (|>> (n.- ///arity.minimum) (//.variables /////reference.partial_name))) -(def: .public (new arity) +(def .public (new arity) (-> Arity (Bytecode Any)) (if (arity.multiary? arity) (all _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux index 1301e055c..3e8e0e065 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method.lux @@ -6,7 +6,7 @@ ["[0]" modifier (.only Modifier) (.open: "[1]#[0]" monoid)] ["[0]" method (.only Method)]]]]]) -(def: .public modifier +(def .public modifier (Modifier Method) (all modifier#composite method.public diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index 69e7d5332..8b03c7ae8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux @@ -48,13 +48,13 @@ [reference [variable (.only Register)]]]]]]]) -(def: (increment by) +(def (increment by) (-> Nat (Bytecode Any)) (all _.composite (<| _.int .i64 by) _.iadd)) -(def: (inputs offset amount) +(def (inputs offset amount) (-> Register Nat (Bytecode Any)) (all _.composite (|> amount @@ -63,7 +63,7 @@ (_#in []) )) -(def: (apply offset amount) +(def (apply offset amount) (-> Register Nat (Bytecode Any)) (let [arity (n.min amount ///arity.maximum)] (all _.composite @@ -76,9 +76,9 @@ (_#in [])) ))) -(def: this_offset 1) +(def this_offset 1) -(def: .public (method class environment function_arity @begin body apply_arity) +(def .public (method class environment function_arity @begin body apply_arity) (-> (Type Class) (Environment Synthesis) Arity Label (Bytecode Any) Arity (Resource Method)) (let [num_partials (-- function_arity) over_extent (i.- (.int apply_arity) 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 5554117e6..84ad5a397 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 @@ -26,22 +26,22 @@ [archive ["[0]" unit]]]]]]) -(def: .public name "impl") +(def .public name "impl") -(def: .public (type :it: arity) +(def .public (type :it: arity) (-> (Type Class) Arity (Type category.Method)) (type.method [(list) (list.partial :it: (list.repeated arity ////type.value)) ////type.value (list)])) -(def: modifier +(def modifier (all modifier#composite method.static //.modifier )) -(def: .public (method :it: arity @begin body) +(def .public (method :it: arity @begin body) (-> (Type Class) Arity Label (Bytecode Any) (Resource Method)) (method.method ..modifier ..name @@ -53,6 +53,6 @@ (_.when_continuous _.areturn) )})) -(def: .public (call :it: arity) +(def .public (call :it: arity) (-> (Type Class) Arity (Bytecode Any)) (_.invokestatic :it: ..name (..type :it: arity))) 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 c3cea9bf2..934e7c561 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 @@ -42,13 +42,13 @@ [reference [variable (.only Register)]]]]]]]) -(def: .public name "<init>") +(def .public name "<init>") -(def: (partials arity) +(def (partials arity) (-> Arity (List (Type Value))) (list.repeated (-- arity) ////type.value)) -(def: .public (type environment arity) +(def .public (type environment arity) (-> (Environment Synthesis) Arity (Type category.Method)) (type.method [(list) (list#composite (///foreign.closure environment) @@ -58,13 +58,13 @@ type.void (list)])) -(def: no_partials +(def no_partials (|> +0 signed.s1 try.trusted _.bipush)) -(def: .public (super environment_size arity) +(def .public (super environment_size arity) (-> Nat Arity (Bytecode Any)) (let [arity_register (++ environment_size)] (all _.composite @@ -73,7 +73,7 @@ (_.iload arity_register)) (_.invokespecial ///abstract.class ..name ///abstract.init)))) -(def: (store_all amount put offset) +(def (store_all amount put offset) (-> Nat (-> Register (Bytecode Any) (Bytecode Any)) (-> Register Register) @@ -84,7 +84,7 @@ (_.aload (offset register))))) (monad.all _.monad))) -(def: .public (method class environment arity) +(def .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (let [environment_size (list.size environment) offset_foreign (is (-> Register Register) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux index b9b1e99a8..7cfe7943e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux @@ -43,7 +43,7 @@ ["[0]" arity (.only Arity)] ["[0]" phase]]]]]]) -(def: .public (instance' foreign_setup class environment arity) +(def .public (instance' foreign_setup class environment arity) (-> (List (Bytecode Any)) (Type Class) (Environment Synthesis) Arity (Bytecode Any)) (all _.composite (_.new class) @@ -52,13 +52,13 @@ (///partial.new arity) (_.invokespecial class //init.name (//init.type environment arity)))) -(def: .public (instance generate archive class environment arity) +(def .public (instance generate archive class environment arity) (-> Phase Archive (Type Class) (Environment Synthesis) Arity (Operation (Bytecode Any))) (do [! phase.monad] [foreign* (monad.each ! (generate archive) environment)] (in (instance' foreign* class environment arity)))) -(def: .public (method class environment arity) +(def .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (let [after_this (is (-> Nat Nat) (n.+ 1)) 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 51ceaf844..16909a692 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 @@ -26,19 +26,19 @@ [/// ["[0]" arity (.only Arity)]]]]]]) -(def: .public name "reset") +(def .public name "reset") -(def: .public (type class) +(def .public (type class) (-> (Type Class) (Type category.Method)) (type.method [(list) (list) class (list)])) -(def: (current_environment class) +(def (current_environment class) (-> (Type Class) (Environment Synthesis) (List (Bytecode Any))) (|>> list.size list.indices (list#each (///foreign.get class)))) -(def: .public (method class environment arity) +(def .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (method.method //.modifier ..name #0 (..type class) 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 eb8478a41..2196d5c3e 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 @@ -61,10 +61,10 @@ (import java/lang/ClassLoader "[1]::[0]") -(def: value::modifier (all modifier#composite field.public field.final field.static)) +(def value::modifier (all modifier#composite field.public field.final field.static)) -(def: init::type (type.method [(list) (list) type.void (list)])) -(def: init::modifier (all modifier#composite method.public method.static method.strict)) +(def init::type (type.method [(list) (list) type.void (list)])) +(def init::modifier (all modifier#composite method.public method.static method.strict)) (exception: .public (cannot_load [class Text error Text]) @@ -84,7 +84,7 @@ (exception.report "Class" class)) -(def: (class_value class_name class) +(def (class_value class_name class) (-> Text (java/lang/Class java/lang/Object) (Try Any)) (case (java/lang/Class::getField //value.field class) {try.#Success field} @@ -103,10 +103,10 @@ {try.#Failure error} (exception.except ..invalid_field [class_name //value.field error]))) -(def: class_path_separator +(def class_path_separator ".") -(def: (evaluate! library loader eval_class [@it valueG]) +(def (evaluate! library loader eval_class [@it valueG]) (-> Library java/lang/ClassLoader Text [(Maybe unit.ID) (Bytecode Any)] (Try [Any Definition])) (let [bytecode_name (text.replaced class_path_separator .module_separator eval_class) :value: (case @it @@ -139,7 +139,7 @@ (in [value [eval_class bytecode]]))))) -(def: (execute! library loader [class_name class_bytecode]) +(def (execute! library loader [class_name class_bytecode]) (-> Library java/lang/ClassLoader Definition (Try Any)) (io.run! (do (try.with io.monad) [existing_class? (|> (atom.read! library) @@ -152,7 +152,7 @@ (loader.store class_name class_bytecode library))] (loader.load class_name loader)))) -(def: (define! library loader context custom @it,valueG) +(def (define! library loader context custom @it,valueG) (-> Library java/lang/ClassLoader unit.ID (Maybe Text) [(Maybe unit.ID) (Bytecode Any)] (Try [Text Any Definition])) (let [class_name (maybe.else (//runtime.class_name context) custom)] @@ -160,30 +160,30 @@ [[value definition] (evaluate! library loader class_name @it,valueG)] (in [class_name value definition])))) -(def: .public host +(def .public host (IO [java/lang/ClassLoader //runtime.Host]) (io (let [library (loader.new_library []) loader (loader.memory library)] [loader (is //runtime.Host (implementation - (def: (evaluate context @it,valueG) + (def (evaluate context @it,valueG) (at try.monad each product.left (..evaluate! library loader (format "E" (//runtime.class_name context)) @it,valueG))) - (def: execute + (def execute (..execute! library loader)) - (def: define + (def define (..define! library loader)) - (def: (ingest context bytecode) + (def (ingest context bytecode) [(//runtime.class_name context) bytecode]) - (def: (re_learn context custom [_ bytecode]) + (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 [directive_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/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index f06d37da3..741098438 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -26,7 +26,7 @@ [reference [variable (.only Register)]]]]]) -(def: (invariant? register changeS) +(def (invariant? register changeS) (-> Register Synthesis Bit) (case changeS (pattern (synthesis.variable/local var)) @@ -35,10 +35,10 @@ _ false)) -(def: no_op +(def no_op (_#in [])) -(def: .public (again translate archive updatesS) +(def .public (again translate archive updatesS) (Generator (List Synthesis)) (do [! phase.monad] [[@begin offset] generation.anchor @@ -72,7 +72,7 @@ (monad.all _.monad)) (_.goto @begin))))) -(def: .public (scope translate archive [offset initsS+ iterationS]) +(def .public (scope translate archive [offset initsS+ iterationS]) (Generator [Nat (List Synthesis) Synthesis]) (do [! phase.monad] [@begin //runtime.forge_label diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index 90c3044ae..772482ec8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -20,18 +20,18 @@ ["[0]" // ["[1][0]" runtime]]) -(def: $Boolean (type.class "java.lang.Boolean" (list))) -(def: $Long (type.class "java.lang.Long" (list))) -(def: $Double (type.class "java.lang.Double" (list))) +(def $Boolean (type.class "java.lang.Boolean" (list))) +(def $Long (type.class "java.lang.Long" (list))) +(def $Double (type.class "java.lang.Double" (list))) -(def: .public (bit value) +(def .public (bit value) (-> Bit (Bytecode Any)) (_.getstatic $Boolean (if value "TRUE" "FALSE") $Boolean)) -(def: wrap_i64 +(def wrap_i64 (_.invokestatic $Long "valueOf" (type.method [(list) (list type.long) $Long (list)]))) -(def: .public (i64 value) +(def .public (i64 value) (-> (I64 Any) (Bytecode Any)) (case (.int value) (^.with_template [<int> <instruction>] @@ -77,18 +77,18 @@ [_ (_.long value)] ..wrap_i64))))) -(def: wrap_f64 +(def wrap_f64 (_.invokestatic $Double "valueOf" (type.method [(list) (list type.double) $Double (list)]))) (import java/lang/Double "[1]::[0]" ("static" doubleToRawLongBits "manual" [double] int)) -(def: d0_bits +(def d0_bits Int (java/lang/Double::doubleToRawLongBits +0.0)) -(def: .public (f64 value) +(def .public (f64 value) (-> Frac (Bytecode Any)) (case value (^.with_template [<int> <instruction>] @@ -129,5 +129,5 @@ [_ constantI] ..wrap_f64)))) -(def: .public text +(def .public text _.string) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux index a81896178..8a374a859 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux @@ -33,19 +33,19 @@ ["[1][0]" runtime (.only Definition)] ["[1][0]" function/abstract]]) -(def: ^Object +(def ^Object (type.class "java.lang.Object" (list))) -(def: ^String +(def ^String (type.class "java.lang.String" (list))) -(def: ^Args +(def ^Args (type.array ^String)) -(def: main::type +(def main::type (type.method [(list) (list ..^Args) type.void (list)])) -(def: main::modifier +(def main::modifier (Modifier Method) (all modifier#composite method.public @@ -53,29 +53,29 @@ method.strict )) -(def: program::modifier +(def program::modifier (Modifier Class) (all modifier#composite class.public class.final )) -(def: list:end +(def list:end //runtime.none_injection) -(def: amount_of_inputs +(def amount_of_inputs (Bytecode Any) (all _.composite _.aload_0 _.arraylength)) -(def: decrease +(def decrease (Bytecode Any) (all _.composite _.iconst_1 _.isub)) -(def: head +(def head (Bytecode Any) (all _.composite _.dup @@ -86,7 +86,7 @@ _.dup_x2 _.pop)) -(def: pair +(def pair (Bytecode Any) (let [empty_pair (all _.composite _.iconst_2 @@ -109,9 +109,9 @@ (set_side! _.iconst_1) ... P ))) -(def: list:item //runtime.right_injection) +(def list:item //runtime.right_injection) -(def: input_list +(def input_list (Bytecode Any) (do _.monad [@loop _.new_label @@ -131,17 +131,17 @@ (_.set_label @end) _.pop))) -(def: feed_inputs +(def feed_inputs //runtime.apply) -(def: run_io +(def run_io (Bytecode Any) (all _.composite (_.checkcast //function/abstract.class) //runtime.unit //runtime.apply)) -(def: .public (program artifact_name context program) +(def .public (program artifact_name context program) (-> (-> unit.ID Text) (Program (Bytecode Any) Definition)) (let [super_class (|> ..^Object type.reflection reflection.reflection name.internal) main (method.method ..main::modifier "main" diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux index b2c6f47ba..fe905d1bc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux @@ -26,12 +26,12 @@ [meta [archive (.only Archive)]]]]]]) -(def: .public this +(def .public this (Bytecode Any) _.aload_0) (with_template [<name> <prefix>] - [(def: .public <name> + [(def .public <name> (-> Register Text) (|>> %.nat (format <prefix>)))] @@ -39,7 +39,7 @@ [partial_name "p"] ) -(def: (foreign archive variable) +(def (foreign archive variable) (-> Archive Register (Operation (Bytecode Any))) (do [! ////.monad] [bytecode_name (at ! each //runtime.class_name @@ -50,7 +50,7 @@ (..foreign_name variable) //type.value))))) -(def: .public (variable archive variable) +(def .public (variable archive variable) (-> Archive Variable (Operation (Bytecode Any))) (case variable {variable.#Local variable} @@ -59,7 +59,7 @@ {variable.#Foreign variable} (..foreign archive variable))) -(def: .public (constant archive name) +(def .public (constant archive name) (-> Archive Symbol (Operation (Bytecode Any))) (do ////.monad [[@definition |abstraction|] (generation.definition archive name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 6331379f2..b52d18de3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -89,24 +89,24 @@ (type: .public Host (generation.Host (Bytecode Any) Definition)) -(def: .public (class_name [module id]) +(def .public (class_name [module id]) (-> unit.ID Text) (format lux_context "." (%.nat version.latest) "." (%.nat module) "." (%.nat id))) -(def: artifact_id +(def artifact_id 0) -(def: .public class +(def .public class (type.class (class_name [0 ..artifact_id]) (list))) -(def: procedure +(def procedure (-> Text (Type category.Method) (Bytecode Any)) (_.invokestatic ..class)) -(def: modifier +(def modifier (Modifier Method) (all modifier#composite method.public @@ -114,17 +114,17 @@ method.strict )) -(def: this +(def this (Bytecode Any) _.aload_0) -(def: .public (get index) +(def .public (get index) (-> (Bytecode Any) (Bytecode Any)) (all _.composite index _.aaload)) -(def: (set! index value) +(def (set! index value) (-> (Bytecode Any) (Bytecode Any) (Bytecode Any)) (all _.composite ... A @@ -134,17 +134,17 @@ _.aastore ... A )) -(def: .public unit (_.string synthesis.unit)) +(def .public unit (_.string synthesis.unit)) -(def: variant::name "variant") -(def: variant::type (type.method [(list) (list //type.lefts //type.right? //type.value) //type.variant (list)])) -(def: .public variant (..procedure ..variant::name ..variant::type)) +(def variant::name "variant") +(def variant::type (type.method [(list) (list //type.lefts //type.right? //type.value) //type.variant (list)])) +(def .public variant (..procedure ..variant::name ..variant::type)) -(def: variant_lefts _.iconst_0) -(def: variant_right? _.iconst_1) -(def: variant_value _.iconst_2) +(def variant_lefts _.iconst_0) +(def variant_right? _.iconst_1) +(def variant_value _.iconst_2) -(def: variant::method +(def variant::method (let [new_variant (all _.composite _.iconst_3 (_.anewarray //type.value)) @@ -163,10 +163,10 @@ (..set! ..variant_value $value) ... A[3] _.areturn)}))) -(def: .public left_right? _.aconst_null) -(def: .public right_right? ..unit) +(def .public left_right? _.aconst_null) +(def .public right_right? ..unit) -(def: .public left_injection +(def .public left_injection (Bytecode Any) (all _.composite _.iconst_0 @@ -175,7 +175,7 @@ _.pop2 ..variant)) -(def: .public right_injection +(def .public right_injection (Bytecode Any) (all _.composite _.iconst_0 @@ -184,9 +184,9 @@ _.pop2 ..variant)) -(def: .public some_injection ..right_injection) +(def .public some_injection ..right_injection) -(def: .public none_injection +(def .public none_injection (Bytecode Any) (all _.composite _.iconst_0 @@ -194,7 +194,7 @@ ..unit ..variant)) -(def: (risky $unsafe) +(def (risky $unsafe) (-> (Bytecode Any) (Bytecode Any)) (do _.monad [@try _.new_label @@ -210,11 +210,11 @@ _.areturn ))) -(def: decode_frac::name "decode_frac") -(def: decode_frac::type (type.method [(list) (list //type.text) //type.variant (list)])) -(def: .public decode_frac (..procedure ..decode_frac::name ..decode_frac::type)) +(def decode_frac::name "decode_frac") +(def decode_frac::type (type.method [(list) (list //type.text) //type.variant (list)])) +(def .public decode_frac (..procedure ..decode_frac::name ..decode_frac::type)) -(def: decode_frac::method +(def decode_frac::method (method.method ..modifier ..decode_frac::name #0 ..decode_frac::type (list) @@ -226,7 +226,7 @@ (//value.wrap type.double) ))})) -(def: .public log! +(def .public log! (Bytecode Any) (let [^PrintStream (type.class "java.io.PrintStream" (list)) ^System (type.class "java.lang.System" (list)) @@ -237,8 +237,8 @@ out (_.string "LUX LOG: ") (print! "print") out _.swap (print! "println")))) -(def: exception_constructor (type.method [(list) (list //type.text) type.void (list)])) -(def: (illegal_state_exception message) +(def exception_constructor (type.method [(list) (list //type.text) type.void (list)])) +(def (illegal_state_exception message) (-> Text (Bytecode Any)) (let [^IllegalStateException (type.class "java.lang.IllegalStateException" (list))] (all _.composite @@ -247,10 +247,10 @@ (_.string message) (_.invokespecial ^IllegalStateException "<init>" ..exception_constructor)))) -(def: failure::type +(def failure::type (type.method [(list) (list) type.void (list)])) -(def: (failure name message) +(def (failure name message) (-> Text Text (Resource Method)) (method.method ..modifier name #0 ..failure::type @@ -260,20 +260,20 @@ (..illegal_state_exception message) _.athrow)})) -(def: pm_failure::name "pm_failure") -(def: .public pm_failure (..procedure ..pm_failure::name ..failure::type)) +(def pm_failure::name "pm_failure") +(def .public pm_failure (..procedure ..pm_failure::name ..failure::type)) -(def: pm_failure::method +(def pm_failure::method (..failure ..pm_failure::name "Invalid expression for pattern-matching.")) -(def: .public stack_head _.iconst_0) -(def: .public stack_tail _.iconst_1) +(def .public stack_head _.iconst_0) +(def .public stack_tail _.iconst_1) -(def: push::name "push") -(def: push::type (type.method [(list) (list //type.stack //type.value) //type.stack (list)])) -(def: .public push (..procedure ..push::name ..push::type)) +(def push::name "push") +(def push::type (type.method [(list) (list //type.stack //type.value) //type.stack (list)])) +(def .public push (..procedure ..push::name ..push::type)) -(def: push::method +(def push::method (method.method ..modifier ..push::name #0 ..push::type (list) @@ -289,11 +289,11 @@ (..set! ..stack_tail $tail) _.areturn))})) -(def: case::name "case") -(def: case::type (type.method [(list) (list //type.variant //type.lefts //type.right?) //type.value (list)])) -(def: .public case (..procedure ..case::name ..case::type)) +(def case::name "case") +(def case::type (type.method [(list) (list //type.variant //type.lefts //type.right?) //type.value (list)])) +(def .public case (..procedure ..case::name ..case::type)) -(def: case::method +(def case::method (method.method ..modifier ..case::name #0 ..case::type (list) @@ -370,15 +370,15 @@ _.areturn ))})) -(def: projection_type (type.method [(list) (list //type.tuple //type.offset) //type.value (list)])) +(def projection_type (type.method [(list) (list //type.tuple //type.offset) //type.value (list)])) -(def: left_projection::name "left") -(def: .public left_projection (..procedure ..left_projection::name ..projection_type)) +(def left_projection::name "left") +(def .public left_projection (..procedure ..left_projection::name ..projection_type)) -(def: right_projection::name "right") -(def: .public right_projection (..procedure ..right_projection::name ..projection_type)) +(def right_projection::name "right") +(def .public right_projection (..procedure ..right_projection::name ..projection_type)) -(def: projection::method2 +(def projection::method2 [(Resource Method) (Resource Method)] (let [$tuple _.aload_0 $tuple::size (all _.composite @@ -465,23 +465,23 @@ [left_projection::method right_projection::method])) -(def: .public apply::name "apply") +(def .public apply::name "apply") -(def: .public (apply::type arity) +(def .public (apply::type arity) (-> Arity (Type category.Method)) (type.method [(list) (list.repeated arity //type.value) //type.value (list)])) -(def: .public apply +(def .public apply (_.invokevirtual //function.class ..apply::name (..apply::type 1))) -(def: try::name "try") -(def: try::type (type.method [(list) (list //function.class) //type.variant (list)])) -(def: .public try (..procedure ..try::name ..try::type)) +(def try::name "try") +(def try::type (type.method [(list) (list //function.class) //type.variant (list)])) +(def .public try (..procedure ..try::name ..try::type)) -(def: false _.iconst_0) -(def: true _.iconst_1) +(def false _.iconst_0) +(def true _.iconst_1) -(def: try::method +(def try::method (method.method ..modifier ..try::name #0 ..try::type (list) @@ -531,14 +531,14 @@ _.areturn ))})) -(def: reflection +(def reflection (All (_ category) (-> (Type (<| Return' Value' category)) Text)) (|>> type.reflection reflection.reflection)) -(def: ^Object (type.class "java.lang.Object" (list))) +(def ^Object (type.class "java.lang.Object" (list))) -(def: generate_runtime +(def generate_runtime (Operation [artifact.ID (Maybe Text) Binary]) (let [class (..reflection ..class) modifier (is (Modifier Class) @@ -571,7 +571,7 @@ _ (generation.save! ..artifact_id {.#None} [class bytecode])] (in [..artifact_id {.#None} bytecode])))) -(def: generate_function +(def generate_function (Operation Any) (let [apply::method+ (|> (enum.range n.enum (++ //function/arity.minimum) @@ -634,7 +634,7 @@ ] (in [])))) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ////.monad [runtime_payload ..generate_runtime @@ -650,7 +650,7 @@ ... function_payload )]))) -(def: .public forge_label +(def .public forge_label (Operation Label) (let [shift (n./ 4 i64.width)] ... This shift is done to avoid the possibility of forged labels diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux index f4b885825..ec2c60d9f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/structure.lux @@ -28,7 +28,7 @@ [/// ["[0]" phase]]]]) -(def: .public (tuple phase archive membersS) +(def .public (tuple phase archive membersS) (Generator (Tuple Synthesis)) (case membersS {.#End} @@ -54,7 +54,7 @@ _ (_.anewarray //type.value)] (monad.all ! membersI)))))) -(def: .public (lefts lefts) +(def .public (lefts lefts) (-> Nat (Bytecode Any)) (case lefts 0 _.iconst_0 @@ -75,13 +75,13 @@ {try.#Failure _} (_.int (.i64 lefts)))))) -(def: .public (right? right?) +(def .public (right? right?) (-> Bit (Bytecode Any)) (if right? //runtime.right_right? //runtime.left_right?)) -(def: .public (variant phase archive [lefts right? valueS]) +(def .public (variant phase archive [lefts right? valueS]) (Generator (Variant Synthesis)) (do phase.monad [valueI (phase archive valueS)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux index 2cf2cfe5e..974fa4925 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/type.lux @@ -5,19 +5,19 @@ [jvm ["[0]" type]]]]]) -(def: .public frac (type.class "java.lang.Double" (list))) -(def: .public text (type.class "java.lang.String" (list))) +(def .public frac (type.class "java.lang.Double" (list))) +(def .public text (type.class "java.lang.String" (list))) -(def: .public value (type.class "java.lang.Object" (list))) +(def .public value (type.class "java.lang.Object" (list))) -(def: .public lefts type.int) -(def: .public right? ..value) -(def: .public variant (type.array ..value)) +(def .public lefts type.int) +(def .public right? ..value) +(def .public variant (type.array ..value)) -(def: .public offset type.int) -(def: .public index ..offset) -(def: .public tuple (type.array ..value)) +(def .public offset type.int) +(def .public index ..offset) +(def .public tuple (type.array ..value)) -(def: .public stack (type.array ..value)) +(def .public stack (type.array ..value)) -(def: .public error (type.class "java.lang.Throwable" (list))) +(def .public error (type.class "java.lang.Throwable" (list))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux index 9cd5f6d93..d4f8b9a93 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux @@ -8,10 +8,10 @@ [category (.only Primitive)] ["[0]" box]]]]]]) -(def: .public field "value") +(def .public field "value") (with_template [<name> <boolean> <byte> <short> <int> <long> <float> <double> <char>] - [(def: (<name> type) + [(def (<name> type) (-> (Type Primitive) Text) (`` (cond (~~ (with_template [<type> <output>] [(type#= <type> type) <output>] @@ -35,13 +35,13 @@ "longValue" "floatValue" "doubleValue" "charValue"] ) -(def: .public (wrap type) +(def .public (wrap type) (-> (Type Primitive) (Bytecode Any)) (let [wrapper (type.class (primitive_wrapper type) (list))] (_.invokestatic wrapper "valueOf" (type.method [(list) (list type) wrapper (list)])))) -(def: .public (unwrap type) +(def .public (unwrap type) (-> (Type Primitive) (Bytecode Any)) (let [wrapper (type.class (primitive_wrapper type) (list))] (all _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux index 669e1667b..f0965920a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua.lux @@ -34,7 +34,7 @@ (exception: .public cannot_recur_as_an_expression) -(def: (expression archive synthesis) +(def (expression archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] @@ -84,6 +84,6 @@ {synthesis.#Extension extension} (///extension.apply archive expression extension))) -(def: .public generate +(def .public generate Phase ..expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index 7ade9486a..418694f74 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -34,15 +34,15 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register Var) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (exec expression archive [this that]) +(def .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) (do ///////phase.monad [this (expression archive this) @@ -50,7 +50,7 @@ (in (|> (_.array (list this that)) (_.item (_.int +2)))))) -(def: .public (exec! statement expression archive [this that]) +(def .public (exec! statement expression archive [this that]) (Generator! [Synthesis Synthesis]) (do [! ///////phase.monad] [this (expression archive this) @@ -60,7 +60,7 @@ (_.set (list $dummy) this) that)))) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -71,7 +71,7 @@ (_.closure (list (..register register))) (_.apply (list valueO)))))) -(def: .public (let! statement expression archive [valueS register bodyS]) +(def .public (let! statement expression archive [valueS register bodyS]) (Generator! [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -80,7 +80,7 @@ (_.local/1 (..register register) valueO) bodyO)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -92,7 +92,7 @@ valueO (list.reversed pathP))))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -104,7 +104,7 @@ (_.closure (list)) (_.apply (list)))))) -(def: .public (if! statement expression archive [testS thenS elseS]) +(def .public (if! statement expression archive [testS thenS elseS]) (Generator! [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -114,27 +114,27 @@ thenO elseO)))) -(def: @savepoint (_.var "lux_pm_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) +(def @savepoint (_.var "lux_pm_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) -(def: (push! value) +(def (push! value) (-> Expression Statement) (_.statement (|> (_.var "table.insert") (_.apply (list @cursor value))))) -(def: peek_and_pop +(def peek_and_pop Expression (|> (_.var "table.remove") (_.apply (list @cursor)))) -(def: pop! +(def pop! Statement (_.statement ..peek_and_pop)) -(def: peek +(def peek Expression (_.item (_.length @cursor) @cursor)) -(def: save! +(def save! Statement (_.statement (|> (_.var "table.insert") (_.apply (list @savepoint @@ -145,14 +145,14 @@ (_.table (list))) (_.var "table.move"))))))) -(def: restore! +(def restore! Statement (_.set (list @cursor) (|> (_.var "table.remove") (_.apply (list @savepoint))))) -(def: fail! _.break) +(def fail! _.break) (with_template [<name> <flag>] - [(def: (<name> simple? idx) + [(def (<name> simple? idx) (-> Bit Nat Statement) (all _.then (_.set (list @temp) (//runtime.sum//get ..peek <flag> @@ -168,7 +168,7 @@ [right_choice //runtime.unit] ) -(def: (alternation pre! post!) +(def (alternation pre! post!) (-> Statement Statement Statement) (all _.then (_.while (_.boolean true) @@ -179,7 +179,7 @@ ..restore! post!))) -(def: (pattern_matching' statement expression archive) +(def (pattern_matching' statement expression archive) (-> Phase! Phase Archive Path (Operation Statement)) (function (again pathP) (.case pathP @@ -261,7 +261,7 @@ ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation])))) -(def: (pattern_matching statement expression archive pathP) +(def (pattern_matching statement expression archive pathP) (-> Phase! Phase Archive Path (Operation Statement)) (do ///////phase.monad [pattern_matching! (pattern_matching' statement expression archive pathP)] @@ -270,7 +270,7 @@ pattern_matching!) (_.statement (|> (_.var "error") (_.apply (list (_.string ////synthesis/case.pattern_matching_error))))))))) -(def: .public dependencies +(def .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage (the ////synthesis/case.#dependencies) @@ -283,7 +283,7 @@ {///////variable.#Foreign register} (..capture register)))))) -(def: .public (case! statement expression archive [valueS pathP]) +(def .public (case! statement expression archive [valueS pathP]) (Generator! [Synthesis Path]) (do ///////phase.monad [stack_init (expression archive valueS) @@ -294,7 +294,7 @@ (_.local/1 @savepoint (_.array (list))) pattern_matching!)))) -(def: .public (case statement expression archive [valueS pathP]) +(def .public (case statement expression archive [valueS pathP]) (-> Phase! (Generator [Synthesis Path])) (|> [valueS pathP] (..case! statement expression archive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index 79bba0796..3454cfe52 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -33,18 +33,18 @@ [reference [variable (.only Register Variable)]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Reification Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply argsO+ functionO)))) -(def: capture +(def capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure inits @self @args body!) +(def (with_closure inits @self @args body!) (-> (List Expression) Var (List Var) Statement [Statement Expression]) (case inits {.#End} @@ -60,14 +60,14 @@ (_.return @self))) (_.apply inits @self)]))) -(def: input +(def input (|>> ++ //case.register)) -(def: (@scope function_name) +(def (@scope function_name) (-> unit.ID Label) (_.label (format (///reference.artifact function_name) "_scope"))) -(def: .public (function statement expression archive [environment arity bodyS]) +(def .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do [! ///////phase.monad] [dependencies (cache.dependencies archive bodyS) 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 71654a483..4878f0b72 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 @@ -33,11 +33,11 @@ [reference [variable (.only Register)]]]]]]) -(def: @scope +(def @scope (-> Nat Label) (|>> %.nat (format "scope") _.label)) -(def: (setup initial? offset bindings as_expression? body) +(def (setup initial? offset bindings as_expression? body) (-> Bit Register (List Expression) Bit Statement Statement) (let [variables (|> bindings list.enumeration @@ -50,7 +50,7 @@ (_.set variables (_.multi bindings))) body)))) -(def: .public (scope! statement expression archive as_expression? [start initsS+ bodyS]) +(def .public (scope! statement expression archive as_expression? [start initsS+ bodyS]) ... (Generator! (Scope Synthesis)) (-> Phase! Phase Archive Bit (Scope Synthesis) (Operation [(List Expression) Statement])) @@ -74,7 +74,7 @@ (_.set_label @scope) body!))])))) -(def: .public (scope statement expression archive [start initsS+ bodyS]) +(def .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop @@ -115,7 +115,7 @@ _ (/////generation.save! artifact_id {.#None} directive)] (in (_.apply initsO+ instantiation))))) -(def: .public (again! statement expression archive argsS+) +(def .public (again! statement expression archive argsS+) (Generator! (List Synthesis)) (do [! ///////phase.monad] [[offset @scope] /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux index ff40f0f26..d6104a879 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux @@ -5,7 +5,7 @@ ["_" lua (.only Literal)]]]]) (with_template [<name> <type> <implementation>] - [(def: .public <name> + [(def .public <name> (-> <type> Literal) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux index d98a16050..47df3bed5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant' _.var) - (def: variable' _.var))) + (def constant' _.var) + (def variable' _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index b97413f9b..a287bf380 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -58,52 +58,52 @@ (type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: .public unit +(def .public unit (_.string /////synthesis.unit)) -(def: (flag value) +(def (flag value) (-> Bit Literal) (if value ..unit _.nil)) -(def: .public variant_tag_field "_lux_tag") -(def: .public variant_flag_field "_lux_flag") -(def: .public variant_value_field "_lux_value") +(def .public variant_tag_field "_lux_tag") +(def .public variant_flag_field "_lux_flag") +(def .public variant_value_field "_lux_value") -(def: (variant' tag last? value) +(def (variant' tag last? value) (-> Expression Expression Expression Literal) (_.table (list [..variant_tag_field tag] [..variant_flag_field last?] [..variant_value_field value]))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Nat Bit Expression Literal) (variant' (_.int (.int tag)) (flag last?) value)) -(def: .public left +(def .public left (-> Expression Literal) (..variant 0 #0)) -(def: .public right +(def .public right (-> Expression Literal) (..variant 0 #1)) -(def: .public none +(def .public none Literal (..left ..unit)) -(def: .public some +(def .public some (-> Expression Literal) ..right) -(def: (feature name definition) +(def (feature name definition) (-> Var (-> Var Statement) Statement) (definition name)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -116,10 +116,10 @@ list.together))] (~ body)))))))) -(def: module_id +(def module_id 0) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -133,11 +133,11 @@ {.#Left name} (macro.with_symbols [g!_] (let [g!name (code.local name)] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) Var (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!name)) @@ -149,11 +149,11 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply (list (~+ inputsC)) (~ runtime_name)))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!_)) @@ -161,11 +161,11 @@ (_.function (~ g!_) (list (~+ inputsC)) (~ code))))))))))))))))) -(def: (item index table) +(def (item index table) (-> Expression Expression Location) (_.item (_.+ (_.int +1) index) table)) -(def: last_index +(def last_index (|>> _.length (_.- (_.int +1)))) (with_expansions [<recur> (these (all _.then @@ -228,7 +228,7 @@ actual::value))) mismatch!))) -(def: runtime//adt +(def runtime//adt Statement (all _.then @tuple//left @@ -255,14 +255,14 @@ tail))))) (_.return tail)))) -(def: runtime//lux +(def runtime//lux Statement (all _.then @lux//try @lux//program_args )) -(def: cap_shift +(def cap_shift (_.% (_.int +64))) (runtime: (i64//left_shifted param subject) @@ -296,7 +296,7 @@ (_.return (_.- (|> subject (..i64//division param) (_.* param)) subject))) -(def: runtime//i64 +(def runtime//i64 Statement (all _.then @i64//left_shifted @@ -305,26 +305,26 @@ @i64//remainder )) -(def: (find_byte_index subject param start) +(def (find_byte_index subject param start) (-> Expression Expression Expression Expression) (_.apply (list subject param start (_.boolean #1)) (_.var "string.find"))) -(def: (char_index subject byte_index) +(def (char_index subject byte_index) (-> Expression Expression Expression) (_.apply (list subject (_.int +1) byte_index) (_.var "utf8.len"))) -(def: (byte_index subject char_index) +(def (byte_index subject char_index) (-> Expression Expression Expression) (_.apply (list subject (_.+ (_.int +1) char_index)) (_.var "utf8.offset"))) -(def: lux_index +(def lux_index (-> Expression Expression) (_.- (_.int +1))) ... TODO: Remove this once the Lua compiler becomes self-hosted. -(def: on_rembulan? +(def on_rembulan? (_.= (_.string "Lua 5.3") (_.var "_VERSION"))) @@ -393,7 +393,7 @@ <rembulan> <normal>)))) -(def: runtime//text +(def runtime//text Statement (all _.then @text//index @@ -407,13 +407,13 @@ (_.set (list (..item idx array)) value) (_.return array))) -(def: runtime//array +(def runtime//array Statement (all _.then @array//write )) -(def: runtime +(def runtime Statement (all _.then ..runtime//adt @@ -423,7 +423,7 @@ ..runtime//array )) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux index 65ed33699..128bedbbe 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/structure.lux @@ -15,7 +15,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple phase archive elemsS+) +(def .public (tuple phase archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -29,7 +29,7 @@ (monad.each ///////phase.monad (phase archive)) (///////phase#each _.array)))) -(def: .public (variant phase archive [lefts right? valueS]) +(def .public (variant phase archive [lefts right? valueS]) (Generator (Variant Synthesis)) (///////phase#each (//runtime.variant lefts right?) (phase archive valueS))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux index dea69708f..5a1e5294c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php.lux @@ -29,7 +29,7 @@ [reference (.only) [variable (.only)]]]]]]]) -(def: (statement expression archive synthesis) +(def (statement expression archive synthesis) Phase! (case synthesis (^.with_template [<tag>] @@ -67,7 +67,7 @@ (exception: .public cannot_recur_as_an_expression) -(def: .public (expression archive synthesis) +(def .public (expression archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] @@ -104,6 +104,6 @@ {////synthesis.#Extension extension} (///extension.apply archive expression extension))) -(def: .public generate +(def .public generate Phase ..expression) 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 f9ea165c8..da294881a 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 @@ -36,15 +36,15 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register Var) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueG (expression archive valueS) @@ -54,7 +54,7 @@ _.array/* (_.item (_.int +1)))))) -(def: .public (let! statement expression archive [valueS register bodyS]) +(def .public (let! statement expression archive [valueS register bodyS]) (Generator! [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -63,7 +63,7 @@ (_.set! (..register register) valueO) body!)))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testG (expression archive testS) @@ -71,7 +71,7 @@ elseG (expression archive elseS)] (in (_.? testG thenG elseG)))) -(def: .public (if! statement expression archive [testS thenS elseS]) +(def .public (if! statement expression archive [testS thenS elseS]) (Generator! [Synthesis Synthesis Synthesis]) (do ///////phase.monad [test! (expression archive testS) @@ -81,7 +81,7 @@ then! else!)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueG (expression archive valueS)] @@ -96,46 +96,46 @@ valueG (list.reversed pathP))))) -(def: @savepoint (_.var "lux_pm_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) +(def @savepoint (_.var "lux_pm_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) -(def: (push! value) +(def (push! value) (-> Expression Statement) (_.; (_.array_push/2 [@cursor value]))) -(def: peek_and_pop +(def peek_and_pop Expression (_.array_pop/1 @cursor)) -(def: pop! +(def pop! Statement (_.; ..peek_and_pop)) -(def: peek +(def peek Expression (_.item (|> @cursor _.count/1 (_.- (_.int +1))) @cursor)) -(def: save! +(def save! Statement (.let [cursor (_.array_slice/2 [@cursor (_.int +0)])] (_.; (_.array_push/2 [@savepoint cursor])))) -(def: restore! +(def restore! Statement (_.set! @cursor (_.array_pop/1 @savepoint))) -(def: fail! _.break) +(def fail! _.break) -(def: (multi_pop! pops) +(def (multi_pop! pops) (-> Nat Statement) (_.; (_.array_splice/3 [@cursor (_.int +0) (_.int (i.* -1 (.int pops)))]))) (with_template [<name> <flag> <prep>] - [(def: (<name> simple? idx) + [(def (<name> simple? idx) (-> Bit Nat Statement) (all _.then (_.set! @temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek <flag>))) @@ -150,7 +150,7 @@ [right_choice (_.string "") ++] ) -(def: (alternation pre! post!) +(def (alternation pre! post!) (-> Statement Statement Statement) (all _.then (_.do_while (_.bool false) @@ -161,7 +161,7 @@ ..restore! post!))) -(def: (pattern_matching' statement expression archive) +(def (pattern_matching' statement expression archive) (Generator! Path) (function (again pathP) (.case pathP @@ -250,7 +250,7 @@ ([/////synthesis.path/seq _.then] [/////synthesis.path/alt ..alternation])))) -(def: (pattern_matching statement expression archive pathP) +(def (pattern_matching statement expression archive pathP) (Generator! Path) (do ///////phase.monad [iteration! (pattern_matching' statement expression archive pathP)] @@ -259,7 +259,7 @@ iteration!) (_.throw (_.new (_.constant "Exception") (list (_.string ////synthesis/case.pattern_matching_error)))))))) -(def: .public dependencies +(def .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage (the ////synthesis/case.#dependencies) @@ -272,7 +272,7 @@ {///////variable.#Foreign register} (..capture register)))))) -(def: .public (case! statement expression archive [valueS pathP]) +(def .public (case! statement expression archive [valueS pathP]) (Generator! [Synthesis Path]) (do ///////phase.monad [stack_init (expression archive valueS) @@ -282,7 +282,7 @@ (_.set! @savepoint (_.array/* (list))) pattern_matching!)))) -(def: .public (case statement expression archive [valueS pathP]) +(def .public (case statement expression archive [valueS pathP]) (-> Phase! (Generator [Synthesis Path])) (do [! ///////phase.monad] [[[case_module case_artifact] case!] (/////generation.with_new_context archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux index 90acc3cef..eac649c9c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension.lux @@ -9,6 +9,6 @@ [/ ["[0]" common]]) -(def: .public bundle +(def .public bundle Bundle common.bundle) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux index e569c80b2..fd5202409 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/extension/common.lux @@ -24,13 +24,13 @@ [extension ["[0]" bundle]]]]]) -(def: lux_procs +(def lux_procs Bundle (|> bundle.empty (bundle.install "is" (binary (product.uncurried _.=))) (bundle.install "try" (unary ///runtime.lux//try)))) -(def: i64_procs +(def i64_procs Bundle (<| (bundle.prefix "i64") (|> bundle.empty @@ -45,7 +45,7 @@ (bundle.install "-" (binary (product.uncurried _.-))) ))) -(def: int_procs +(def int_procs Bundle (<| (bundle.prefix "int") (|> bundle.empty @@ -56,7 +56,7 @@ (bundle.install "frac" (unary _.floatval/1)) (bundle.install "char" (unary _.chr/1))))) -(def: frac_procs +(def frac_procs Bundle (<| (bundle.prefix "frac") (|> bundle.empty @@ -72,11 +72,11 @@ (bundle.install "decode" (unary (|>> _.floatval/1 ///runtime.some))) ))) -(def: (text//index [startO partO textO]) +(def (text//index [startO partO textO]) (Trinary (Expression Any)) (///runtime.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (bundle.prefix "text") (|> bundle.empty @@ -91,7 +91,7 @@ (_.substr/3 [text from (_.- from to)])))) ))) -(def: io_procs +(def io_procs Bundle (<| (bundle.prefix "io") (|> bundle.empty @@ -100,7 +100,7 @@ (bundle.install "exit" (unary _.exit/1)) (bundle.install "current-time" (nullary (|>> _.time/0 (_.* (_.int +1,000)))))))) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux index b0c6a19a0..5a07d5032 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux @@ -29,25 +29,25 @@ [reference [variable (.only Register Variable)]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do [! ///////phase.monad] [functionG (expression archive functionS) argsG+ (monad.each ! (expression archive) argsS+)] (in (_.apply' argsG+ functionG)))) -(def: capture +(def capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: input +(def input (|>> ++ //case.register)) -(def: (@scope function_name) +(def (@scope function_name) (-> Context Label) (_.label (format (///reference.artifact function_name) "_scope"))) -(def: (with_closure inits @selfG @selfL body!) +(def (with_closure inits @selfG @selfL body!) (-> (List Expression) Global Var Statement [Statement Expression]) (case inits {.#End} @@ -67,7 +67,7 @@ (_.return @selfL)))) (_.apply inits @selfG)]))) -(def: .public (function statement expression archive [environment arity bodyS]) +(def .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do [! ///////phase.monad] [[function_name body!] (/////generation.with_new_context archive 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 f9798f4e6..c495d5a12 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 @@ -33,11 +33,11 @@ [reference [variable (.only Register)]]]]]]]) -(def: @scope +(def @scope (-> Nat Label) (|>> %.nat (format "scope") _.label)) -(def: (setup offset bindings body) +(def (setup offset bindings body) (-> Register (List Expression) Statement Statement) ... TODO: There is a bug in the way the variables are updated. Do it like it's done in either JS or Lua. (|> bindings @@ -48,7 +48,7 @@ list.reversed (list#mix _.then body))) -(def: .public (scope! statement expression archive [start initsS+ bodyS]) +(def .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -67,7 +67,7 @@ (_.set_label @scope) body!)))))) -(def: .public (scope statement expression archive [start initsS+ bodyS]) +(def .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop @@ -106,10 +106,10 @@ (in (_.apply (list) instantiation))))) ... TODO: Stop using a constant hard-coded variable. Generate a new one each time. -(def: @temp +(def @temp (_.var "lux_again_values")) -(def: .public (again! statement expression archive argsS+) +(def .public (again! statement expression archive argsS+) (Generator! (List Synthesis)) (do [! ///////phase.monad] [[offset @scope] /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux index df2ae080f..b88e520c8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/primitive.lux @@ -9,11 +9,11 @@ ["[0]" // ["[1][0]" runtime]]) -(def: .public bit +(def .public bit (-> Bit Literal) _.bool) -(def: .public (i64 value) +(def .public (i64 value) (-> (I64 Any) Expression) (let [h32 (|> value //runtime.high .int _.int) l32 (|> value //runtime.low .int _.int)] @@ -21,10 +21,10 @@ (_.bit_shl (_.int +32)) (_.bit_or l32)))) -(def: .public f64 +(def .public f64 (-> Frac Literal) _.float) -(def: .public text +(def .public text (-> Text Literal) _.string) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux index 1fb4ce3e2..8d723c451 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant _.global) - (def: variable _.var))) + (def constant _.global) + (def variable _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index a8a1229dd..425dee836 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -57,20 +57,20 @@ (type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: .public unit +(def .public unit (_.string /////synthesis.unit)) -(def: (flag value) +(def (flag value) (-> Bit Literal) (if value ..unit _.null)) -(def: (feature name definition) +(def (feature name definition) (-> Constant (-> Constant Statement) Statement) (definition name)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -83,10 +83,10 @@ list.together))] (~ body)))))))) -(def: module_id +(def module_id 0) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -100,11 +100,11 @@ {.#Left name} (macro.with_symbols [g!_] (let [g!name (code.local name)] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) Var (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!name)) @@ -116,11 +116,11 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply (list (~+ inputsC)) (~ runtime_name)))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..feature (~ runtime_name) (function ((~ g!_) (~ g!_)) @@ -140,20 +140,20 @@ (_.throw (_.new (_.constant "Exception") (list message))) (_.return ..unit))) -(def: runtime//io +(def runtime//io Statement (all _.then @io//log! @io//throw! )) -(def: .public tuple_size_field +(def .public tuple_size_field "_lux_size") -(def: tuple_size +(def tuple_size (_.item (_.string ..tuple_size_field))) -(def: jphp? +(def jphp? (_.=== (_.string "5.6.99") (_.phpversion/0 []))) (runtime: (array//length array) @@ -167,17 +167,17 @@ (_.set! (_.item idx array) value) (_.return array))) -(def: runtime//array +(def runtime//array Statement (all _.then @array//length @array//write )) -(def: jphp_last_index +(def jphp_last_index (|>> ..tuple_size (_.- (_.int +1)))) -(def: normal_last_index +(def normal_last_index (|>> _.count/1 (_.- (_.int +1)))) (with_expansions [<recur> (these (all _.then @@ -243,34 +243,34 @@ (_.array_slice/2 [(_.do "getArrayCopy" (list) tuple) right_index]))))) ))))) -(def: .public variant_tag_field "_lux_tag") -(def: .public variant_flag_field "_lux_flag") -(def: .public variant_value_field "_lux_value") +(def .public variant_tag_field "_lux_tag") +(def .public variant_flag_field "_lux_flag") +(def .public variant_value_field "_lux_value") (runtime: (sum//make tag last? value) (_.return (_.array/** (list [(_.string ..variant_tag_field) tag] [(_.string ..variant_flag_field) last?] [(_.string ..variant_value_field) value])))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Nat Bit Expression Computation) (sum//make (_.int (.int tag)) (..flag last?) value)) -(def: .public none +(def .public none Computation (..variant 0 #0 ..unit)) -(def: .public some +(def .public some (-> Expression Computation) (..variant 1 #1)) -(def: .public left +(def .public left (-> Expression Computation) (..variant 0 #0)) -(def: .public right +(def .public right (-> Expression Computation) (..variant 1 #1)) @@ -302,7 +302,7 @@ (_.return (sum//make (_.- wantedTag sum_tag) sum_flag sum_value))]) no_match!)))) -(def: runtime//adt +(def runtime//adt Statement (all _.then @tuple//make @@ -331,18 +331,18 @@ (_.set! tail (..some (_.array/* (list head tail))))) (_.return tail)))) -(def: runtime//lux +(def runtime//lux Statement (all _.then @lux//try @lux//program_args )) -(def: .public high +(def .public high (-> (I64 Any) (I64 Any)) (i64.right_shifted 32)) -(def: .public low +(def .public low (-> (I64 Any) (I64 Any)) (let [mask (-- (i64.left_shifted 32 1))] (|>> (i64.and mask)))) @@ -491,7 +491,7 @@ (_.bit_or low32)))) )))) -(def: runtime//i64 +(def runtime//i64 Statement (all _.then @i64//right_shifted @@ -523,7 +523,7 @@ (_.return ..none) (_.return (..some idx)))))))) -(def: (within? top value) +(def (within? top value) (-> Expression Expression Computation) (_.and (|> value (_.>= (_.int +0))) (|> value (_.< top)))) @@ -545,7 +545,7 @@ (_.item (_.int +1))))) (_.throw (_.new (_.constant "Exception") (list (_.string "[Lux Error] Cannot get char from text.")))))) -(def: runtime//text +(def runtime//text Statement (all _.then @text//size @@ -571,13 +571,13 @@ (_.return (..some output))) ))) -(def: runtime//f64 +(def runtime//f64 Statement (all _.then @f64//decode )) -(def: check_necessary_conditions! +(def check_necessary_conditions! Statement (let [i64_support? (_.=== (_.int +8) (_.constant "PHP_INT_SIZE")) i64_error (_.string (format "Cannot run program!" text.new_line @@ -585,7 +585,7 @@ (_.when (_.not i64_support?) (_.throw (_.new (_.constant "Exception") (list i64_error)))))) -(def: runtime +(def runtime Statement (all _.then check_necessary_conditions! @@ -598,7 +598,7 @@ runtime//io )) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux index d7a945e58..2cc580fe5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/structure.lux @@ -17,7 +17,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple expression archive elemsS+) +(def .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -33,7 +33,7 @@ (///////phase#each (|>> _.array/* (//runtime.tuple//make size))))))) -(def: .public (variant expression archive [lefts right? valueS]) +(def .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (++ lefts) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux index a0c15f71e..f51b79f96 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python.lux @@ -34,7 +34,7 @@ (exception: .public cannot_recur_as_an_expression) -(def: .public (expression archive synthesis) +(def .public (expression archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] @@ -74,6 +74,6 @@ {////synthesis.#Extension extension} (///extension.apply archive expression extension))) -(def: .public generate +(def .public generate Phase ..expression) 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 6b7d425f9..48ab895d4 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 @@ -41,20 +41,20 @@ [dependency ["[1]" artifact]]]]]]]]]) -(def: .public (symbol prefix) +(def .public (symbol prefix) (-> Text (Operation SVar)) (///////phase#each (|>> %.nat (format prefix) _.var) /////generation.next)) -(def: .public register +(def .public register (-> Register SVar) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -64,7 +64,7 @@ (_.lambda (list (..register register)) bodyO))))) -(def: .public (let! statement expression archive [valueS register bodyS]) +(def .public (let! statement expression archive [valueS register bodyS]) (Generator! [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -73,14 +73,14 @@ (_.set (list (..register register)) valueO) bodyO)))) -(def: .public (exec expression archive [pre post]) +(def .public (exec expression archive [pre post]) (Generator [Synthesis Synthesis]) (do ///////phase.monad [pre (expression archive pre) post (expression archive post)] (in (_.item (_.int +1) (_.tuple (list pre post)))))) -(def: .public (exec! statement expression archive [pre post]) +(def .public (exec! statement expression archive [pre post]) (Generator! [Synthesis Synthesis]) (do ///////phase.monad [pre (expression archive pre) @@ -89,7 +89,7 @@ (_.statement pre) post)))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -97,7 +97,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: .public (if! statement expression archive [testS thenS elseS]) +(def .public (if! statement expression archive [testS thenS elseS]) (Generator! [Synthesis Synthesis Synthesis]) (do ///////phase.monad [test! (expression archive testS) @@ -107,7 +107,7 @@ then! else!)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -120,43 +120,43 @@ valueO (list.reversed pathP))))) -(def: @savepoint (_.var "lux_pm_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) +(def @savepoint (_.var "lux_pm_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) -(def: (push! value) +(def (push! value) (-> (Expression Any) (Statement Any)) (_.statement (|> @cursor (_.do "append" (list value))))) -(def: peek_and_pop +(def peek_and_pop (Expression Any) (|> @cursor (_.do "pop" (list)))) -(def: pop! +(def pop! (Statement Any) (_.statement ..peek_and_pop)) -(def: peek +(def peek (Expression Any) (_.item (_.int -1) @cursor)) -(def: save! +(def save! (Statement Any) (.let [cursor (_.slice_from (_.int +0) @cursor)] (_.statement (|> @savepoint (_.do "append" (list cursor)))))) -(def: restore! +(def restore! (Statement Any) (_.set (list @cursor) (|> @savepoint (_.do "pop" (list))))) -(def: fail_pm! _.break) +(def fail_pm! _.break) -(def: (multi_pop! pops) +(def (multi_pop! pops) (-> Nat (Statement Any)) (_.delete (_.slice_from (_.int (i.* -1 (.int pops))) @cursor))) (with_template [<name> <flag>] - [(def: (<name> simple? idx) + [(def (<name> simple? idx) (-> Bit Nat (Statement Any)) (all _.then (_.set (list @temp) (//runtime.sum::get ..peek <flag> @@ -173,7 +173,7 @@ [right_choice //runtime.unit] ) -(def: (with_looping in_closure? g!once body!) +(def (with_looping in_closure? g!once body!) (-> Bit SVar (Statement Any) (Statement Any)) (.if in_closure? (_.while (_.bool true) @@ -187,7 +187,7 @@ body!) {.#Some _.continue})))) -(def: (alternation in_closure? g!once pre! post!) +(def (alternation in_closure? g!once pre! post!) (-> Bit SVar (Statement Any) (Statement Any) (Statement Any)) (all _.then (..with_looping in_closure? g!once @@ -197,7 +197,7 @@ ..restore! post!)) -(def: (primitive_pattern_matching again pathP) +(def (primitive_pattern_matching again pathP) (-> (-> Path (Operation (Statement Any))) (-> Path (Operation (Maybe (Statement Any))))) (.case pathP @@ -238,7 +238,7 @@ _ (at ///////phase.monad in {.#None}))) -(def: (pattern_matching' in_closure? statement expression archive) +(def (pattern_matching' in_closure? statement expression archive) (-> Bit Phase! Phase Archive Path (Operation (Statement Any))) (function (again pathP) (do [! ///////phase.monad] @@ -309,7 +309,7 @@ _ (undefined)))))) -(def: (pattern_matching in_closure? statement expression archive pathP) +(def (pattern_matching in_closure? statement expression archive pathP) (-> Bit Phase! Phase Archive Path (Operation (Statement Any))) (do ///////phase.monad [pattern_matching! (pattern_matching' in_closure? statement expression archive pathP) @@ -319,7 +319,7 @@ pattern_matching!) (_.raise (_.Exception/1 (_.string case.pattern_matching_error))))))) -(def: .public dependencies +(def .public dependencies (-> Path (List SVar)) (|>> case.storage (the case.#dependencies) @@ -332,7 +332,7 @@ {///////variable.#Foreign register} (..capture register)))))) -(def: .public (case! in_closure? statement expression archive [valueS pathP]) +(def .public (case! in_closure? statement expression archive [valueS pathP]) (-> Bit (Generator! [Synthesis Path])) (do ///////phase.monad [stack_init (expression archive valueS) @@ -343,7 +343,7 @@ pattern_matching! )))) -(def: .public (case statement expression archive [valueS pathP]) +(def .public (case statement expression archive [valueS pathP]) (-> Phase! (Generator [Synthesis Path])) (do ///////phase.monad [dependencies (cache.path_dependencies archive pathP) 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 abcc258a4..ca93b78d7 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 @@ -34,18 +34,18 @@ [dependency ["[1]" artifact]]]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Reification Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply argsO+ functionO)))) -(def: .public capture +(def .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure function_id @function inits function_definition) +(def (with_closure function_id @function inits function_definition) (-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any))) (case inits {.#End} @@ -66,10 +66,10 @@ _ (/////generation.save! function_id {.#None} directive)] (in (_.apply inits @function))))) -(def: input +(def input (|>> ++ //case.register)) -(def: .public (function statement expression archive [environment arity bodyS]) +(def .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do [! ///////phase.monad] [dependencies (cache.dependencies archive bodyS) 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 9dc509654..def965231 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 @@ -35,7 +35,7 @@ [reference ["[1][0]" variable (.only Register)]]]]]]]) -(def: (setup offset bindings body) +(def (setup offset bindings body) (-> Register (List (Expression Any)) (Statement Any) (Statement Any)) (let [variables (|> bindings list.enumeration @@ -44,13 +44,13 @@ (_.set variables (_.multi bindings)) body))) -(def: .public (set_scope body!) +(def .public (set_scope body!) (-> (Statement Any) (Statement Any)) (_.while (_.bool true) body! {.#None})) -(def: .public (scope! statement expression archive [start initsS+ bodyS]) +(def .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -67,7 +67,7 @@ ..set_scope body!))))) -(def: .public (scope statement expression archive [start initsS+ bodyS]) +(def .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop @@ -110,7 +110,7 @@ _ (/////generation.save! loop_artifact {.#None} directive)] (in (_.apply initsO+ instantiation))))) -(def: .public (again! statement expression archive argsS+) +(def .public (again! statement expression archive argsS+) (Generator! (List Synthesis)) (do [! ///////phase.monad] [offset /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux index 7afebeba8..7e565f3fe 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux @@ -7,7 +7,7 @@ ["[1][0]" runtime]]) (with_template [<type> <name> <implementation>] - [(def: .public <name> + [(def .public <name> (-> <type> (Expression Any)) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux index 47b64cd94..8786e5309 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System (Expression Any)) (implementation - (def: constant' _.var) - (def: variable' _.var))) + (def constant' _.var) + (def variable' _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 194f641ee..5c984981b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -60,56 +60,56 @@ (type: .public (Generator i) (-> Phase Archive i (Operation (Expression Any)))) -(def: prefix +(def prefix "LuxRuntime") -(def: .public unit +(def .public unit (_.unicode /////synthesis.unit)) -(def: (flag value) +(def (flag value) (-> Bit Literal) (if value ..unit _.none)) -(def: (variant' tag last? value) +(def (variant' tag last? value) (-> (Expression Any) (Expression Any) (Expression Any) Literal) (_.tuple (list tag last? value))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Nat Bit (Expression Any) Literal) (variant' (_.int (.int tag)) (flag last?) value)) -(def: .public left +(def .public left (-> (Expression Any) Literal) (..variant 0 #0)) -(def: .public right +(def .public right (-> (Expression Any) Literal) (..variant 0 #1)) -(def: .public none +(def .public none Literal (..left ..unit)) -(def: .public some +(def .public some (-> (Expression Any) Literal) ..right) -(def: (runtime_name name) +(def (runtime_name name) (-> Text SVar) (let [symbol (format ..prefix "_" (%.nat version.latest) "_" (%.nat (text#hash name)))] (_.var symbol))) -(def: (feature name definition) +(def (feature name definition) (-> SVar (-> SVar (Statement Any)) (Statement Any)) (definition name)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -122,7 +122,7 @@ list.together))] (~ body)))))))) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -133,8 +133,8 @@ (let [nameC (code.local name) code_nameC (code.local (format "@" name)) runtime_nameC (` (runtime_name (~ (code.text name))))] - (in (list (` (def: .public (~ nameC) SVar (~ runtime_nameC))) - (` (def: (~ code_nameC) + (in (list (` (def .public (~ nameC) SVar (~ runtime_nameC))) + (` (def (~ code_nameC) (Statement Any) (..feature (~ runtime_nameC) (function ((~ g!_) (~ g!_)) @@ -148,10 +148,10 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def: .public ((~ nameC) (~+ inputsC)) + (in (list (` (def .public ((~ nameC) (~+ inputsC)) (-> (~+ inputs_typesC) (Computation Any)) (_.apply (list (~+ inputsC)) (~ runtime_nameC)))) - (` (def: (~ code_nameC) + (` (def (~ code_nameC) (Statement Any) (..feature (~ runtime_nameC) (function ((~ g!_) (~ g!_)) @@ -179,7 +179,7 @@ (_.exec {.#Some globals} code) (_.return ..unit))) -(def: runtime::lux +(def runtime::lux (Statement Any) (all _.then @lux::try @@ -199,14 +199,14 @@ (runtime: (io::throw! message) (_.raise (_.Exception/1 message))) -(def: runtime::io +(def runtime::io (Statement Any) (all _.then @io::log! @io::throw! )) -(def: last_index +(def last_index (|>> _.len/1 (_.- (_.int +1)))) (with_expansions [<recur> (these (all _.then @@ -266,7 +266,7 @@ mismatch!) {.#None}))) -(def: runtime::adt +(def runtime::adt (Statement Any) (all _.then @tuple::left @@ -274,12 +274,12 @@ @sum::get )) -(def: i64::+limit (_.manual "+0x7FFFFFFFFFFFFFFF")) -(def: i64::-limit (_.manual "-0x8000000000000000")) -(def: i64::+iteration (_.manual "+0x10000000000000000")) -(def: i64::-iteration (_.manual "-0x10000000000000000")) -(def: i64::+cap (_.manual "+0x8000000000000000")) -(def: i64::-cap (_.manual "-0x8000000000000001")) +(def i64::+limit (_.manual "+0x7FFFFFFFFFFFFFFF")) +(def i64::-limit (_.manual "-0x8000000000000000")) +(def i64::+iteration (_.manual "+0x10000000000000000")) +(def i64::-iteration (_.manual "-0x10000000000000000")) +(def i64::+cap (_.manual "+0x8000000000000000")) +(def i64::-cap (_.manual "-0x8000000000000001")) (runtime: (i64::64 input) (with_vars [temp] @@ -298,7 +298,7 @@ ... This +- is only necessary to guarantee that values within the limits are always longs in Python 2 (|> input (_.+ ..i64::+limit) (_.- ..i64::+limit)))))))) -(def: as_nat +(def as_nat (_.% ..i64::+iteration)) (runtime: (i64::left_shifted param subject) @@ -345,7 +345,7 @@ [i64::xor _.bit_xor] ) -(def: python_version +(def python_version (Expression Any) (|> (_.__import__/1 (_.unicode "sys")) (_.the "version_info") @@ -356,7 +356,7 @@ (_.chr/1 value) (_.unichr/1 value)))) -(def: runtime::i64 +(def runtime::i64 (Statement Any) (all _.then @i64::64 @@ -385,7 +385,7 @@ (list [(list "Exception") ex (_.return ..none)])))) -(def: runtime::f64 +(def runtime::f64 (Statement Any) (all _.then @f64::/ @@ -400,10 +400,10 @@ ..none (..some (..i64::64 idx))))))) -(def: ++ +(def ++ (|>> (_.+ (_.int +1)))) -(def: (within? top value) +(def (within? top value) (-> (Expression Any) (Expression Any) (Computation Any)) (_.and (|> value (_.>= (_.int +0))) (|> value (_.< top)))) @@ -416,7 +416,7 @@ (_.return (|> text (_.slice idx (..++ idx)) _.ord/1 ..i64::64)) (_.raise (_.Exception/1 (_.unicode "[Lux Error] Cannot get char from text."))))) -(def: runtime::text +(def runtime::text (Statement Any) (all _.then @text::index @@ -429,13 +429,13 @@ (_.set (list (_.item idx array)) value) (_.return array))) -(def: runtime::array +(def runtime::array (Statement Any) (all _.then @array::write )) -(def: runtime +(def runtime (Statement Any) (all _.then runtime::lux @@ -447,10 +447,10 @@ runtime::array )) -(def: module_id +(def module_id 0) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux index 560fb1c49..cd9fe5bee 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/structure.lux @@ -15,7 +15,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple generate archive elemsS+) +(def .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -29,7 +29,7 @@ (monad.each ///////phase.monad (generate archive)) (///////phase#each _.list)))) -(def: .public (variant generate archive [lefts right? valueS]) +(def .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (///////phase#each (//runtime.variant lefts right?) (generate archive valueS))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux index 582d8dd42..b73d54264 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r.lux @@ -27,7 +27,7 @@ [reference (.only) [variable (.only)]]]]]]]) -(def: .public (generate archive synthesis) +(def .public (generate archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux index 6f41454c2..ff52e460e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux @@ -37,15 +37,15 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register SVar) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -55,7 +55,7 @@ (_.set! (..register register) valueO) bodyO))))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -63,7 +63,7 @@ elseO (expression archive elseS)] (in (_.if testO thenO elseO)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -78,61 +78,61 @@ valueO (list.reversed pathP))))) -(def: $savepoint (_.var "lux_pm_cursor_savepoint")) -(def: $cursor (_.var "lux_pm_cursor")) -(def: $temp (_.var "lux_pm_temp")) -(def: $alt_error (_.var "alt_error")) +(def $savepoint (_.var "lux_pm_cursor_savepoint")) +(def $cursor (_.var "lux_pm_cursor")) +(def $temp (_.var "lux_pm_temp")) +(def $alt_error (_.var "alt_error")) -(def: top +(def top _.length) -(def: next +(def next (|>> _.length (_.+ (_.int +1)))) -(def: (push! value var) +(def (push! value var) (-> Expression SVar Expression) (_.set_item! (next var) value var)) -(def: (pop! var) +(def (pop! var) (-> SVar Expression) (_.set_item! (top var) _.null var)) -(def: (push_cursor! value) +(def (push_cursor! value) (-> Expression Expression) (push! value $cursor)) -(def: save_cursor! +(def save_cursor! Expression (push! (_.slice (_.float +1.0) (_.length $cursor) $cursor) $savepoint)) -(def: restore_cursor! +(def restore_cursor! Expression (_.set! $cursor (_.item (top $savepoint) $savepoint))) -(def: peek +(def peek Expression (|> $cursor (_.item (top $cursor)))) -(def: pop_cursor! +(def pop_cursor! Expression (pop! $cursor)) -(def: error +(def error (_.string (template.with_locals [error] (template.text [error])))) -(def: fail! +(def fail! (_.stop ..error)) -(def: (catch handler) +(def (catch handler) (-> Expression Expression) (_.function (list $alt_error) (_.if (|> $alt_error (_.= ..error)) handler (_.stop $alt_error)))) -(def: (pattern_matching' expression archive) +(def (pattern_matching' expression archive) (Generator Path) (function (again pathP) (.case pathP @@ -221,7 +221,7 @@ {.#None}))) ))) -(def: (pattern_matching expression archive pathP) +(def (pattern_matching expression archive pathP) (Generator Path) (do ///////phase.monad [pattern_matching! (pattern_matching' expression archive pathP)] @@ -230,7 +230,7 @@ {.#Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))} {.#None})))) -(def: .public (case expression archive [valueS pathP]) +(def .public (case expression archive [valueS pathP]) (Generator [Synthesis Path]) (do [! ///////phase.monad] [valueO (expression archive valueS)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux index af38457a9..d0933505c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/function.lux @@ -32,14 +32,14 @@ [archive ["[0]" artifact]]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply argsO+ functionO)))) -(def: (with_closure function_id $function inits function_definition) +(def (with_closure function_id $function inits function_definition) (-> artifact.ID SVar (List Expression) Expression (Operation Expression)) (case inits {.#End} @@ -63,15 +63,15 @@ _ (/////generation.save! (%.nat function_id) closure_definition)] (in (_.apply inits $function))))) -(def: $curried (_.var "curried")) -(def: $missing (_.var "missing")) +(def $curried (_.var "curried")) +(def $missing (_.var "missing")) -(def: (input_declaration register) +(def (input_declaration register) (-> Register Expression) (_.set! (|> register ++ //case.register) (|> $curried (_.item (|> register ++ .int _.int))))) -(def: .public (function expression archive [environment arity bodyS]) +(def .public (function expression archive [environment arity bodyS]) (Generator (Abstraction Synthesis)) (do [! ///////phase.monad] [[[function_module function_artifact] bodyO] (/////generation.with_new_context archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux index 9c0a9cfa1..a3b660bd8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/loop.lux @@ -33,7 +33,7 @@ [reference [variable (.only Register)]]]]]]]) -(def: .public (scope expression archive [offset initsS+ bodyS]) +(def .public (scope expression archive [offset initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -57,7 +57,7 @@ bodyO)) (_.apply initsO+ $scope))))))) -(def: .public (again expression archive argsS+) +(def .public (again expression archive argsS+) (Generator (List Synthesis)) (do [! ///////phase.monad] [$scope /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux index ca30d7b84..1bbd9332c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux @@ -7,7 +7,7 @@ ["[1][0]" runtime]]) (with_template [<name> <type> <code>] - [(def: .public <name> + [(def .public <name> (-> <type> Expression) <code>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 23f19d400..62d2f235b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -35,12 +35,12 @@ (Dict Text Proc)) ... [Utils] -(def: .public (install name unnamed) +(def .public (install name unnamed) (-> Text (-> Text Proc) (-> Bundle Bundle)) (dict.has name (unnamed name))) -(def: .public (prefix prefix bundle) +(def .public (prefix prefix bundle) (-> Text Bundle Bundle) (|> bundle dict.entries @@ -49,28 +49,28 @@ ... [Procedures] ... [[Lux]] -(def: (lux//is [leftO rightO]) +(def (lux//is [leftO rightO]) Binary (r.apply (list leftO rightO) (r.global "identical"))) -(def: (lux//if [testO thenO elseO]) +(def (lux//if [testO thenO elseO]) Trinary (caseT.translate_if testO thenO elseO)) -(def: (lux//try riskyO) +(def (lux//try riskyO) Unary (runtimeT.lux//try riskyO)) (exception: .public (Wrong_Syntax [message Text]) message) -(def: .public (wrong_syntax procedure args) +(def .public (wrong_syntax procedure args) (-> Text (List ls.Synthesis) Text) (format "Procedure: " procedure "\n" "Arguments: " (%code (code.tuple args)))) -(def: lux//loop +(def lux//loop (-> Text Proc) (function (_ proc_name) (function (_ translate inputsS) @@ -82,13 +82,13 @@ (&.throw Wrong_Syntax (wrong_syntax proc_name inputsS))) ))) -(def: lux//again +(def lux//again (-> Text Proc) (function (_ proc_name) (function (_ translate inputsS) (loopT.translate_again translate inputsS)))) -(def: lux_procs +(def lux_procs Bundle (|> (dict.empty text.Hash<Text>) (install "is" (binary lux//is)) @@ -100,7 +100,7 @@ ... [[Bits]] (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -110,7 +110,7 @@ ) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<op> (runtimeT.int64_low paramO) subjectO))] @@ -119,7 +119,7 @@ [bit//logical_right_shifted runtimeT.bit//logical_right_shifted] ) -(def: bit_procs +(def bit_procs Bundle (<| (prefix "bit") (|> (dict.empty text.Hash<Text>) @@ -137,7 +137,7 @@ ("static" MAX_VALUE Double)) (with_template [<name> <const> <encode>] - [(def: (<name> _) + [(def (<name> _) Nullary (<encode> <const>))] @@ -147,7 +147,7 @@ ) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (|> subjectO (<op> paramO)))] @@ -159,7 +159,7 @@ ) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -176,7 +176,7 @@ ) (with_template [<name> <cmp>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<cmp> paramO subjectO))] @@ -184,14 +184,14 @@ [int//< runtimeT.int//<] ) -(def: (apply1 func) +(def (apply1 func) (-> Expression (-> Expression Expression)) (function (_ value) (r.apply (list value) func))) -(def: int//char (|>> runtimeT.int64_low (apply1 (r.global "intToUtf8")))) +(def int//char (|>> runtimeT.int64_low (apply1 (r.global "intToUtf8")))) -(def: int_procs +(def int_procs Bundle (<| (prefix "int") (|> (dict.empty text.Hash<Text>) @@ -205,11 +205,11 @@ (install "to-frac" (unary runtimeT.int//float)) (install "char" (unary int//char))))) -(def: (frac//encode value) +(def (frac//encode value) (-> Expression Expression) (r.apply (list (r.string "%f") value) (r.global "sprintf"))) -(def: frac_procs +(def frac_procs Bundle (<| (prefix "frac") (|> (dict.empty text.Hash<Text>) @@ -228,23 +228,23 @@ (install "decode" (unary runtimeT.frac//decode))))) ... [[Text]] -(def: (text//concat [subjectO paramO]) +(def (text//concat [subjectO paramO]) Binary (r.apply (list subjectO paramO) (r.global "paste0"))) -(def: (text//char [subjectO paramO]) +(def (text//char [subjectO paramO]) Binary (runtimeT.text//char subjectO paramO)) -(def: (text//clip [subjectO paramO extraO]) +(def (text//clip [subjectO paramO extraO]) Trinary (runtimeT.text//clip subjectO paramO extraO)) -(def: (text//index [textO partO startO]) +(def (text//index [textO partO startO]) Trinary (runtimeT.text//index textO partO startO)) -(def: text_procs +(def text_procs Bundle (<| (prefix "text") (|> (dict.empty text.Hash<Text>) @@ -258,17 +258,17 @@ ))) ... [[IO]] -(def: (io//exit input) +(def (io//exit input) Unary (r.apply_kw (list) (list ["status" (runtimeT.int//float input)]) (r.global "quit"))) -(def: (void code) +(def (void code) (-> Expression Expression) (r.block (r.then code runtimeT.unit))) -(def: io_procs +(def io_procs Bundle (<| (prefix "io") (|> (dict.empty text.Hash<Text>) @@ -279,7 +279,7 @@ (runtimeT.io//current_time! runtimeT.unit))))))) ... [Bundles] -(def: .public procedures +(def .public procedures Bundle (<| (prefix "lux") (|> lux_procs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux index d8f9eae7c..fcc48447c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux @@ -16,13 +16,13 @@ (// ["@" common])) ... (with_template [<name> <lua>] -... [(def: (<name> _) @.Nullary <lua>)] +... [(def (<name> _) @.Nullary <lua>)] ... [lua//nil "nil"] ... [lua//table "{}"] ... ) -... (def: (lua//global proc translate inputs) +... (def (lua//global proc translate inputs) ... (-> Text @.Proc) ... (case inputs ... (pattern (list [_ {.#Text name}])) @@ -33,7 +33,7 @@ ... _ ... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -... (def: (lua//call proc translate inputs) +... (def (lua//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs ... (pattern (list.partial functionS argsS+)) @@ -45,7 +45,7 @@ ... _ ... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -... (def: lua_procs +... (def lua_procs ... @.Bundle ... (|> (dict.empty text.Hash<Text>) ... (@.install "nil" (@.nullary lua//nil)) @@ -53,7 +53,7 @@ ... (@.install "global" lua//global) ... (@.install "call" lua//call))) -... (def: (table//call proc translate inputs) +... (def (table//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs ... (pattern (list.partial tableS [_ {.#Text field}] argsS+)) @@ -65,15 +65,15 @@ ... _ ... (&.throw @.Wrong_Syntax (@.wrong_syntax proc inputs)))) -... (def: (table//get [fieldO tableO]) +... (def (table//get [fieldO tableO]) ... @.Binary ... (runtimeT.lua//get tableO fieldO)) -... (def: (table//set [fieldO valueO tableO]) +... (def (table//set [fieldO valueO tableO]) ... @.Trinary ... (runtimeT.lua//set tableO fieldO valueO)) -... (def: table_procs +... (def table_procs ... @.Bundle ... (<| (@.prefix "table") ... (|> (dict.empty text.Hash<Text>) @@ -81,7 +81,7 @@ ... (@.install "get" (@.binary table//get)) ... (@.install "set" (@.trinary table//set))))) -(def: .public procedures +(def .public procedures @.Bundle (<| (@.prefix "lua") (dict.empty text.Hash<Text>) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux index 5a37d97b7..4cc1f49ba 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant _.var) - (def: variable _.var))) + (def constant _.var) + (def variable _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 20d9475a1..ff87c9113 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -41,7 +41,7 @@ [archive (.only Output Archive) ["[0]" artifact (.only Registry)]]]]]]) -(def: module_id +(def module_id 0) (with_template [<name> <base>] @@ -57,15 +57,15 @@ (type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(def: .public unit +(def .public unit Expression (_.string /////synthesis.unit)) -(def: full_32 (hex "FFFFFFFF")) -(def: half_32 (hex "7FFFFFFF")) -(def: post_32 (hex "100000000")) +(def full_32 (hex "FFFFFFFF")) +(def half_32 (hex "7FFFFFFF")) +(def post_32 (hex "100000000")) -(def: (cap_32 input) +(def (cap_32 input) (-> Nat Int) (cond (n.> full_32 input) (|> input (i64.and full_32) cap_32) @@ -76,7 +76,7 @@ ... else (.int input))) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -89,7 +89,7 @@ list.together))] (~ body)))))))) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -102,11 +102,11 @@ (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) _.SVar (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) _.Expression (_.set! (~ runtime_name) (~ code))))))) @@ -115,22 +115,22 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) _.Expression) (_.apply (list (~+ inputsC)) (~ runtime_name)))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) _.Expression (..with_vars [(~+ inputsC)] (_.set! (~ runtime_name) (_.function (list (~+ inputsC)) (~ code))))))))))))))) -(def: .public variant_tag_field "luxVT") -(def: .public variant_flag_field "luxVF") -(def: .public variant_value_field "luxVV") +(def .public variant_tag_field "luxVT") +(def .public variant_flag_field "luxVF") +(def .public variant_value_field "luxVV") -(def: .public (flag value) +(def .public (flag value) (-> Bit Expression) (if value (_.string "") @@ -141,29 +141,29 @@ [..variant_flag_field last?] [..variant_value_field value]))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Nat Bit Expression Expression) (adt::variant (_.int (.int tag)) (flag last?) value)) -(def: .public none +(def .public none Expression (variant 0 #0 ..unit)) -(def: .public some +(def .public some (-> Expression Expression) (variant 1 #1)) -(def: .public left +(def .public left (-> Expression Expression) (variant 0 #0)) -(def: .public right +(def .public right (-> Expression Expression) (variant 1 #1)) -(def: high_shift (_.bit_shl (_.int +32))) +(def high_shift (_.bit_shl (_.int +32))) (with_template [<name> <power>] [(runtime: <name> (|> (_.as::integer (_.int +2)) (_.** (_.as::integer (_.int <power>)))))] @@ -172,12 +172,12 @@ [f2^63 +63] ) -(def: (as_double value) +(def (as_double value) (-> Expression Expression) (_.apply (list value) (_.var "as.double"))) -(def: .public i64_high_field "luxIH") -(def: .public i64_low_field "luxIL") +(def .public i64_high_field "luxIH") +(def .public i64_low_field "luxIL") (runtime: (i64::unsigned_low input) (with_vars [low] @@ -199,21 +199,21 @@ (_.named_list (list [..i64_high_field (_.as::integer high)] [..i64_low_field (_.as::integer low)]))) -(def: high_32 +(def high_32 (-> Nat Nat) (i64.right_shifted 32)) -(def: low_32 +(def low_32 (-> Nat Nat) (|>> (i64.and (hex "FFFFFFFF")))) -(def: .public (i64 value) +(def .public (i64 value) (-> Int Expression) (let [value (.nat value)] (i64::new (|> value ..high_32 ..cap_32 _.int) (|> value ..low_32 ..cap_32 _.int)))) -(def: .public (lux_i64 high low) +(def .public (lux_i64 high low) (-> Int Int Int) (|> high (i64.left_shifted 32) @@ -229,8 +229,8 @@ [i64::max i#top] ) -(def: .public i64_high (_.item (_.string ..i64_high_field))) -(def: .public i64_low (_.item (_.string ..i64_low_field))) +(def .public i64_high (_.item (_.string ..i64_high_field))) +(def .public i64_low (_.item (_.string ..i64_low_field))) (runtime: (i64::not input) (i64::new (|> input i64_high _.bit_not) @@ -380,11 +380,11 @@ (new_half x16 x00))))) ))))))) -(def: (limit_shift! shift) +(def (limit_shift! shift) (-> SVar Expression) (_.set! shift (|> shift (_.bit_and (_.as::integer (_.int +63)))))) -(def: (no_shift_clause shift input) +(def (no_shift_clause shift input) (-> SVar SVar [Expression Expression]) [(|> shift (_.= (_.int +0))) input]) @@ -539,14 +539,14 @@ (_.set! inputs (..some (_.list (list value inputs))))) inputs))) -(def: runtime::lux +(def runtime::lux Expression (all _.then @lux::try @lux::program_args )) -(def: current_time_float +(def current_time_float Expression (let [raw_time (_.apply (list) (_.var "Sys.time"))] (_.apply (list raw_time) (_.var "as.numeric")))) @@ -556,25 +556,25 @@ (_.* (_.float +1,000.0)) i64::of_float)) -(def: runtime::io +(def runtime::io Expression (all _.then @io::current_time! )) -(def: minimum_index_length +(def minimum_index_length (-> SVar Expression) (|>> (_.+ (_.int +1)))) -(def: (product_element product index) +(def (product_element product index) (-> Expression Expression Expression) (|> product (_.item (|> index (_.+ (_.int +1)))))) -(def: (product_tail product) +(def (product_tail product) (-> SVar Expression) (|> product (_.item (_.length product)))) -(def: (updated_index min_length product) +(def (updated_index min_length product) (-> Expression Expression Expression) (|> min_length (_.- (_.length product)))) @@ -629,7 +629,7 @@ no_match))) -(def: runtime::adt +(def runtime::adt Expression (all _.then @tuple::left @@ -672,7 +672,7 @@ (let [low (|> (i64_high input) (_.bit_ushr (|> shift (_.- (_.int +32)))))] (i64::new (_.int +0) low))))) -(def: runtime::i64 +(def runtime::i64 Expression (all _.then @f2^32 @@ -715,22 +715,22 @@ ..none (..some output))))) -(def: runtime::frac +(def runtime::frac Expression (all _.then @frac::decode )) -(def: ++ +(def ++ (-> Expression Expression) (|>> (_.+ (_.int +1)))) -(def: (text_clip start end text) +(def (text_clip start end text) (-> Expression Expression Expression Expression) (_.apply (list text start end) (_.var "substr"))) -(def: (text_length text) +(def (text_length text) (-> Expression Expression) (_.apply (list text) (_.var "nchar"))) @@ -763,7 +763,7 @@ (..some (text_clip (++ minimum) (++ to) text)) ..none)))) -(def: (char_at idx text) +(def (char_at idx text) (-> Expression Expression Expression) (_.apply (list (text_clip idx idx text)) (_.var "utf8ToInt"))) @@ -775,7 +775,7 @@ (..some (i64::of_float (char_at idx text)))) ..none)) -(def: runtime::text +(def runtime::text Expression (all _.then @text::index @@ -783,7 +783,7 @@ @text::char )) -(def: (check_index_out_of_bounds array idx body) +(def (check_index_out_of_bounds array idx body) (-> Expression Expression Expression Expression) (_.if (_.> (_.length array) idx) (_.stop (_.string "Array index out of bounds!")) @@ -813,7 +813,7 @@ (_.set_item! (_.+ (_.int +1) idx) value array) array))) -(def: runtime::array +(def runtime::array Expression (all _.then @array::new @@ -821,7 +821,7 @@ @array::put )) -(def: runtime +(def runtime Expression (all _.then runtime::lux @@ -833,7 +833,7 @@ runtime::io )) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux index f41b3268d..5e376dd1f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/structure.lux @@ -17,7 +17,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple expression archive elemsS+) +(def .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -31,7 +31,7 @@ (monad.each ///////phase.monad (expression archive)) (///////phase#each _.list)))) -(def: .public (variant expression archive [lefts right? valueS]) +(def .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (++ lefts) 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 93183d209..5ee5957eb 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 @@ -19,7 +19,7 @@ ... This universe constant is for languages where one can't just turn all compiled definitions ... into the local variables of some scoping function. -(def: .public universe +(def .public universe (for @.lua ... In the case of Lua, there is a limit of 200 locals in a function's scope. (not ("lua script universe")) @@ -37,7 +37,7 @@ (not ("scheme script universe")) #0)) -(def: universe_label +(def universe_label Text (with_expansions [<label> (format "u" (%.nat (if ..universe 1 0)))] (for @.lua <label> @@ -46,7 +46,7 @@ @.scheme <label> ""))) -(def: .public (artifact [module artifact]) +(def .public (artifact [module artifact]) (-> unit.ID Text) (format "l" (%.nat version.latest) ..universe_label @@ -60,7 +60,7 @@ (is (-> Text expression) variable'))) -(def: .public (constant system archive name) +(def .public (constant system archive name) (All (_ anchor expression directive) (-> (System expression) Archive Symbol (////generation.Operation anchor expression directive expression))) @@ -68,7 +68,7 @@ (////generation.remember archive name))) (with_template [<sigil> <name>] - [(def: .public (<name> system) + [(def .public (<name> system) (All (_ expression) (-> (System expression) (-> Register expression))) @@ -78,7 +78,7 @@ ["l" local] ) -(def: .public (variable system variable) +(def .public (variable system variable) (All (_ expression) (-> (System expression) Variable expression)) (case variable @@ -88,7 +88,7 @@ {variable.#Foreign register} (..foreign system register))) -(def: .public (reference system archive reference) +(def .public (reference system archive reference) (All (_ anchor expression directive) (-> (System expression) Archive Reference (////generation.Operation anchor expression directive expression))) (case reference diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux index 6a11d8996..8cc7466cc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux @@ -34,7 +34,7 @@ (exception: .public cannot_recur_as_an_expression) -(def: (expression archive synthesis) +(def (expression archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] @@ -74,6 +74,6 @@ {////synthesis.#Extension extension} (///extension.apply archive expression extension))) -(def: .public generate +(def .public generate Phase ..expression) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index 3ddd687e1..bd9e27049 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -40,19 +40,19 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public (symbol prefix) +(def .public (symbol prefix) (-> Text (Operation LVar)) (///////phase#each (|>> %.nat (format prefix) _.local) /////generation.next)) -(def: .public register +(def .public register (-> Register LVar) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register LVar) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (exec expression archive [this that]) +(def .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) (do ///////phase.monad [this (expression archive this) @@ -60,7 +60,7 @@ (in (|> (_.array (list this that)) (_.item (_.int +1)))))) -(def: .public (exec! statement expression archive [this that]) +(def .public (exec! statement expression archive [this that]) (Generator! [Synthesis Synthesis]) (do ///////phase.monad [this (expression archive this) @@ -70,7 +70,7 @@ that )))) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -81,7 +81,7 @@ [(list (..register register))] (_.lambda {.#None}) (_.apply_lambda (list valueO)))))) -(def: .public (let! statement expression archive [valueS register bodyS]) +(def .public (let! statement expression archive [valueS register bodyS]) (Generator! [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -90,7 +90,7 @@ (_.set (list (..register register)) valueO) bodyO)))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -98,7 +98,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: .public (if! statement expression archive [testS thenS elseS]) +(def .public (if! statement expression archive [testS thenS elseS]) (Generator! [Synthesis Synthesis Synthesis]) (do ///////phase.monad [test! (expression archive testS) @@ -108,7 +108,7 @@ then! else!)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -120,38 +120,38 @@ valueO (list.reversed pathP))))) -(def: @savepoint (_.local "lux_pm_savepoint")) -(def: @cursor (_.local "lux_pm_cursor")) -(def: @temp (_.local "lux_pm_temp")) +(def @savepoint (_.local "lux_pm_savepoint")) +(def @cursor (_.local "lux_pm_cursor")) +(def @temp (_.local "lux_pm_temp")) -(def: (push! value) +(def (push! value) (-> Expression Statement) (_.statement (|> @cursor (_.do "push" (list value) {.#None})))) -(def: peek_and_pop +(def peek_and_pop Expression (|> @cursor (_.do "pop" (list) {.#None}))) -(def: pop! +(def pop! Statement (_.statement ..peek_and_pop)) -(def: peek +(def peek Expression (_.item (_.int -1) @cursor)) -(def: save! +(def save! Statement (.let [cursor (_.array_range (_.int +0) (_.int -1) @cursor)] (_.statement (|> @savepoint (_.do "push" (list cursor) {.#None}))))) -(def: restore! +(def restore! Statement (_.set (list @cursor) (|> @savepoint (_.do "pop" (list) {.#None})))) -(def: fail! _.break) +(def fail! _.break) -(def: (multi_pop! pops) +(def (multi_pop! pops) (-> Nat Statement) (_.statement (_.do "slice!" (list (_.int (i.* -1 (.int pops))) @@ -160,7 +160,7 @@ @cursor))) (with_template [<name> <flag>] - [(def: (<name> simple? idx) + [(def (<name> simple? idx) (-> Bit Nat Statement) (all _.then (_.set (list @temp) (//runtime.sum//get ..peek <flag> @@ -176,7 +176,7 @@ [right_choice //runtime.unit] ) -(def: (with_looping in_closure? g!once g!continue? body!) +(def (with_looping in_closure? g!once g!continue? body!) (-> Bit LVar LVar Statement Statement) (.if in_closure? (all _.then @@ -196,7 +196,7 @@ (_.when g!continue? _.next)))) -(def: (alternation in_closure? g!once g!continue? pre! post!) +(def (alternation in_closure? g!once g!continue? pre! post!) (-> Bit LVar LVar Statement Statement Statement) (all _.then (with_looping in_closure? g!once g!continue? @@ -206,7 +206,7 @@ ..restore! post!)) -(def: (primitive_pattern_matching again pathP) +(def (primitive_pattern_matching again pathP) (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP @@ -247,7 +247,7 @@ _ (at ///////phase.monad in {.#None}))) -(def: (pattern_matching' in_closure? statement expression archive) +(def (pattern_matching' in_closure? statement expression archive) (-> Bit (Generator! Path)) (function (again pathP) (do ///////phase.monad @@ -352,7 +352,7 @@ g!continue? (..symbol "continue")] (in (..alternation in_closure? g!once g!continue? pre! post!)))))))) -(def: (pattern_matching in_closure? statement expression archive pathP) +(def (pattern_matching in_closure? statement expression archive pathP) (-> Bit (Generator! Path)) (do ///////phase.monad [pattern_matching! (pattern_matching' in_closure? statement expression archive pathP) @@ -363,7 +363,7 @@ pattern_matching!) (_.statement (_.raise (_.string case.pattern_matching_error))))))) -(def: .public (case! in_closure? statement expression archive [valueS pathP]) +(def .public (case! in_closure? statement expression archive [valueS pathP]) (-> Bit (Generator! [Synthesis Path])) (do ///////phase.monad [stack_init (expression archive valueS) @@ -374,7 +374,7 @@ pattern_matching! )))) -(def: .public (case statement expression archive case) +(def .public (case statement expression archive case) (-> Phase! (Generator [Synthesis Path])) (|> case (case! true statement expression archive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 2ebe8edbb..67fd28d7b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -32,18 +32,18 @@ [dependency ["[1]/[0]" artifact]]]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Reification Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply_lambda argsO+ functionO)))) -(def: .public capture +(def .public capture (-> Register LVar) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure inits self function_definition) +(def (with_closure inits self function_definition) (-> (List Expression) Text Expression [Statement Expression]) (let [@self (_.global self)] (case inits @@ -61,10 +61,10 @@ (_.return @self)))])) (_.apply_lambda inits @self)]))) -(def: input +(def input (|>> ++ //case.register)) -(def: .public (function statement expression archive [environment arity bodyS]) +(def .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do [! ///////phase.monad] [dependencies (cache/artifact.dependencies archive bodyS) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux index 930206963..693f5a46d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/loop.lux @@ -31,7 +31,7 @@ [reference ["[1][0]" variable (.only Register)]]]]]]]) -(def: (setup offset bindings body) +(def (setup offset bindings body) (-> Register (List Expression) Statement Statement) (let [variables (|> bindings list.enumeration @@ -40,14 +40,14 @@ (_.set variables (_.multi bindings)) body))) -(def: symbol +(def symbol (_.symbol "lux_continue")) -(def: .public with_scope +(def .public with_scope (-> Statement Statement) (_.while (_.bool true))) -(def: .public (scope! statement expression archive [start initsS+ bodyS]) +(def .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -64,7 +64,7 @@ ..with_scope body!))))) -(def: .public (scope statement expression archive [start initsS+ bodyS]) +(def .public (scope statement expression archive [start initsS+ bodyS]) (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop @@ -79,7 +79,7 @@ [(list)] (_.lambda {.#None}) (_.apply_lambda (list))))))) -(def: .public (again! statement expression archive argsS+) +(def .public (again! statement expression archive argsS+) (Generator! (List Synthesis)) (do [! ///////phase.monad] [offset /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux index 162936972..eebaa01d5 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux @@ -5,7 +5,7 @@ ["_" ruby (.only Literal)]]]]) (with_template [<type> <name> <implementation>] - [(def: .public <name> + [(def .public <name> (-> <type> Literal) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux index b464719fc..b29560a21 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant' _.global) - (def: variable' _.local))) + (def constant' _.global) + (def variable' _.local))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 9552d15ac..7d5b9d6b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -59,16 +59,16 @@ (type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: .public unit +(def .public unit (_.string /////synthesis.unit)) -(def: (flag value) +(def (flag value) (-> Bit Literal) (if value ..unit _.nil)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -81,14 +81,14 @@ list.together))] (~ body)))))))) -(def: module_id +(def module_id 0) -(def: $Numeric +(def $Numeric _.CVar (_.manual "Numeric")) -(def: mruby? +(def mruby? _.Expression (_.and (|> $Numeric (_.do "method_defined?" (list (_.string "remainder")) {.#None}) @@ -96,14 +96,14 @@ (|> $Numeric (_.do "method_defined?" (list (_.string "remainder_of_divide")) {.#None})))) -(def: normal_ruby? +(def normal_ruby? _.Expression (_.not ..mruby?) ... (|> (_.local "Object") ... (_.do "const_defined?" (list (_.string "Encoding")) {.#None})) ) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -118,8 +118,8 @@ (let [runtime (code.local (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.constant (~ (code.text (%.code runtime))))) g!name (code.local name)] - (in (list (` (def: .public (~ g!name) _.CVar (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (in (list (` (def .public (~ g!name) _.CVar (~ runtime_name))) + (` (def (~ (code.local (format "@" name))) Statement (~ (list#mix (function (_ [when then] else) (` (_.if (~ when) @@ -136,12 +136,12 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply (list (~+ inputsC)) {.#None} (~ runtime_name)))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) Statement (..with_vars [(~+ inputsC)] (~ (list#mix (function (_ [when then] else) @@ -153,10 +153,10 @@ (~ default_implementation))) conditional_implementations)))))))))))))) -(def: tuple_size +(def tuple_size (_.the "length")) -(def: last_index +(def last_index (|>> ..tuple_size (_.- (_.int +1)))) (with_expansions [<recur> (these (all _.then @@ -187,32 +187,32 @@ (_.return (_.array_range right_index (..tuple_size tuple) tuple))) ))))) -(def: .public variant_tag_field "_lux_tag") -(def: .public variant_flag_field "_lux_flag") -(def: .public variant_value_field "_lux_value") +(def .public variant_tag_field "_lux_tag") +(def .public variant_flag_field "_lux_flag") +(def .public variant_value_field "_lux_value") (runtime: (sum//make tag last? value) (_.return (_.hash (list [(_.string ..variant_tag_field) tag] [(_.string ..variant_flag_field) last?] [(_.string ..variant_value_field) value])))) -(def: .public (variant tag last? value) +(def .public (variant tag last? value) (-> Nat Bit Expression Computation) (sum//make (_.int (.int tag)) (..flag last?) value)) -(def: .public left +(def .public left (-> Expression Computation) (..variant 0 #0)) -(def: .public right +(def .public right (-> Expression Computation) (..variant 0 #1)) -(def: .public none +(def .public none Computation (..left ..unit)) -(def: .public some +(def .public some (-> Expression Computation) ..right) @@ -243,7 +243,7 @@ actual::value))) mismatch!))) -(def: runtime//adt +(def runtime//adt Statement (all _.then @tuple//left @@ -268,17 +268,17 @@ (_.set (list tail) (..some (_.array (list head tail))))) (_.return tail)))) -(def: runtime//lux +(def runtime//lux Statement (all _.then @lux//try @lux//program_args )) -(def: i64::+limit (_.manual "+0x7FFFFFFFFFFFFFFF")) -(def: i64::-limit (_.manual "-0x8000000000000000")) -(def: i64::+cap (_.manual "+0x8000000000000000")) -(def: i64::-cap (_.manual "-0x8000000000000001")) +(def i64::+limit (_.manual "+0x7FFFFFFFFFFFFFFF")) +(def i64::-limit (_.manual "-0x8000000000000000")) +(def i64::+cap (_.manual "+0x8000000000000000")) +(def i64::-cap (_.manual "-0x8000000000000001")) (runtime: i64::+iteration (_.manual "(+1<<64)")) (runtime: i64::-iteration (_.manual "(-1<<64)")) @@ -299,21 +299,21 @@ )) (_.return input))))) -(def: i32::low +(def i32::low (|>> (_.bit_and (_.manual "+0xFFFFFFFF")))) -(def: i32::high +(def i32::high (|>> (_.bit_shr (_.int +32)) ..i32::low)) -(def: i32::positive? +(def i32::positive? (|>> (_.bit_and (_.manual "+0x80000000")) (_.= (_.int +0)))) -(def: i32::up +(def i32::up (_.bit_shl (_.int +32))) -(def: i64 +(def i64 (template (_ @high @low) [(|> (_.? (i32::positive? @high) @high @@ -323,7 +323,7 @@ i32::up (_.bit_or @low))])) -(def: as_nat +(def as_nat (_.% ..i64::+iteration)) (with_template [<runtime> <host>] @@ -340,16 +340,16 @@ [i64::xor _.bit_xor] ) -(def: (cap_shift! shift) +(def (cap_shift! shift) (-> LVar Statement) (_.set (list shift) (|> shift (_.bit_and (_.int +63))))) -(def: (handle_no_shift! shift input) +(def (handle_no_shift! shift input) (-> LVar LVar (-> Statement Statement)) (_.if (|> shift (_.= (_.int +0))) (_.return input))) -(def: small_shift? +(def small_shift? (-> LVar Expression) (|>> (_.< (_.int +32)))) @@ -419,10 +419,10 @@ (_.return (..i64 high (i32::low low))) ))) -(def: i64::min +(def i64::min (_.manual "-0x8000000000000000")) -(def: (i64::opposite value) +(def (i64::opposite value) (_.? (_.= i64::min value) i64::min (i64::+ (_.int +1) (_.bit_not value)))) @@ -431,13 +431,13 @@ [..normal_ruby? (_.return (i64::i64 (_.- parameter subject)))] (_.return (i64::+ (i64::opposite parameter) subject))) -(def: i16::high +(def i16::high (_.bit_shr (_.int +16))) -(def: i16::low +(def i16::low (_.bit_and (_.manual "+0xFFFF"))) -(def: i16::up +(def i16::up (_.bit_shl (_.int +16))) (runtime: (i64::* parameter subject) @@ -494,7 +494,7 @@ [..mruby? (_.return (_.do "chr" (list) {.#None} subject))] (_.return (_.do "chr" (list (_.string "UTF-8")) {.#None} subject))) -(def: runtime//i64 +(def runtime//i64 Statement (all _.then @i64::+iteration @@ -525,7 +525,7 @@ (_.return (..some @temp)) (_.return ..none))))) -(def: runtime//f64 +(def runtime//f64 Statement (all _.then @f64//decode @@ -539,7 +539,7 @@ (_.return ..none) (_.return (..some idx)))))) -(def: (within? top value) +(def (within? top value) (-> Expression Expression Computation) (_.and (|> value (_.>= (_.int +0))) (|> value (_.< top)))) @@ -554,7 +554,7 @@ (_.return (|> text (_.array_range idx idx) (_.do "ord" (list) {.#None}))) (_.statement (_.raise (_.string "[Lux Error] Cannot get char from text."))))) -(def: runtime//text +(def runtime//text Statement (all _.then @text//index @@ -567,13 +567,13 @@ (_.set (list (_.item idx array)) value) (_.return array))) -(def: runtime//array +(def runtime//array Statement (all _.then @array//write )) -(def: runtime +(def runtime Statement (all _.then (_.when ..mruby? @@ -592,7 +592,7 @@ runtime//array )) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux index 791f06d76..3cdbd9591 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/structure.lux @@ -15,7 +15,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple generate archive elemsS+) +(def .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -29,7 +29,7 @@ (monad.each ///////phase.monad (generate archive)) (///////phase#each _.array)))) -(def: .public (variant generate archive [lefts right? valueS]) +(def .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (///////phase#each (//runtime.variant lefts right?) (generate archive valueS))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux index 2702efa5e..b6a3a5842 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme.lux @@ -27,7 +27,7 @@ [reference (.only) [variable (.only)]]]]]]]) -(def: .public (generate archive synthesis) +(def .public (generate archive synthesis) Phase (case synthesis (^.with_template [<tag> <generator>] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index 7cbfc7bfe..f492d94df 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -37,15 +37,15 @@ [meta [archive (.only Archive)]]]]]]]) -(def: .public register +(def .public register (-> Register Var) (|>> (///reference.local //reference.system) as_expected)) -(def: .public capture +(def .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: .public (let expression archive [valueS register bodyS]) +(def .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) (do ///////phase.monad [valueO (expression archive valueS) @@ -53,7 +53,7 @@ (in (_.let (list [(..register register) valueO]) bodyO)))) -(def: .public (if expression archive [testS thenS elseS]) +(def .public (if expression archive [testS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do ///////phase.monad [testO (expression archive testS) @@ -61,7 +61,7 @@ elseO (expression archive elseS)] (in (_.if testO thenO elseO)))) -(def: .public (get expression archive [pathP valueS]) +(def .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -76,48 +76,48 @@ valueO (list.reversed pathP))))) -(def: @savepoint (_.var "lux_pm_cursor_savepoint")) -(def: @cursor (_.var "lux_pm_cursor")) -(def: @temp (_.var "lux_pm_temp")) -(def: @alt_error (_.var "alt_error")) +(def @savepoint (_.var "lux_pm_cursor_savepoint")) +(def @cursor (_.var "lux_pm_cursor")) +(def @temp (_.var "lux_pm_temp")) +(def @alt_error (_.var "alt_error")) -(def: (push! value var) +(def (push! value var) (-> Expression Var Computation) (_.set! var (_.cons/2 value var))) -(def: (push_cursor! value) +(def (push_cursor! value) (-> Expression Computation) (push! value @cursor)) -(def: (pop! var) +(def (pop! var) (-> Var Computation) (_.set! var (_.cdr/1 var))) -(def: save_cursor! +(def save_cursor! Computation (push! @cursor @savepoint)) -(def: restore_cursor! +(def restore_cursor! Computation (_.begin (list (_.set! @cursor (_.car/1 @savepoint)) (_.set! @savepoint (_.cdr/1 @savepoint))))) -(def: peek +(def peek Computation (_.car/1 @cursor)) -(def: pop_cursor! +(def pop_cursor! Computation (pop! @cursor)) -(def: pm_error +(def pm_error (_.string (template.with_locals [pm_error] (template.text [pm_error])))) -(def: fail! +(def fail! (_.raise/1 pm_error)) -(def: (try_pm on_failure happy_path) +(def (try_pm on_failure happy_path) (-> Expression Expression Computation) (_.guard @alt_error (list [(_.and (list (_.string?/1 @alt_error) @@ -126,7 +126,7 @@ {.#None} happy_path)) -(def: (pattern_matching' expression archive) +(def (pattern_matching' expression archive) (Generator Path) (function (again pathP) (.case pathP @@ -209,13 +209,13 @@ leftO))))) ))) -(def: (pattern_matching expression archive pathP) +(def (pattern_matching expression archive pathP) (Generator Path) (at ///////phase.monad each (try_pm (_.raise/1 (_.string "Invalid expression for pattern-matching."))) (pattern_matching' expression archive pathP))) -(def: .public (case expression archive [valueS pathP]) +(def .public (case expression archive [valueS pathP]) (Generator [Synthesis Path]) (do [! ///////phase.monad] [valueO (expression archive valueS)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux index 90acc3cef..eac649c9c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension.lux @@ -9,6 +9,6 @@ [/ ["[0]" common]]) -(def: .public bundle +(def .public bundle Bundle common.bundle) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index 2ed9653b5..815a712b3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -28,14 +28,14 @@ ["[1]/" // ["[1][0]" synthesis (.only Synthesis)]]]]) -(def: bundle::lux +(def bundle::lux Bundle (|> bundle.empty (bundle.install "is?" (binary (product.uncurried _.eq?/2))) (bundle.install "try" (unary ///runtime.lux//try)))) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -44,22 +44,22 @@ [i64::xor _.bit_xor/2] ) -(def: (i64::left_shifted [subjectO paramO]) +(def (i64::left_shifted [subjectO paramO]) Binary (_.arithmetic_shift/2 (_.remainder/2 (_.int +64) paramO) subjectO)) -(def: (i64::arithmetic_right_shifted [subjectO paramO]) +(def (i64::arithmetic_right_shifted [subjectO paramO]) Binary (_.arithmetic_shift/2 (|> paramO (_.remainder/2 (_.int +64)) (_.*/2 (_.int -1))) subjectO)) -(def: (i64::logical_right_shifted [subjectO paramO]) +(def (i64::logical_right_shifted [subjectO paramO]) Binary (///runtime.i64//logical_right_shifted (_.remainder/2 (_.int +64) paramO) subjectO)) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (|> subjectO (<op> paramO)))] @@ -71,7 +71,7 @@ ) (with_template [<name> <op>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -88,7 +88,7 @@ ) (with_template [<name> <cmp>] - [(def: (<name> [subjectO paramO]) + [(def (<name> [subjectO paramO]) Binary (<cmp> paramO subjectO))] @@ -96,9 +96,9 @@ [i64::< _.</2] ) -(def: i64::char (|>> _.integer->char/1 _.string/1)) +(def i64::char (|>> _.integer->char/1 _.string/1)) -(def: bundle::i64 +(def bundle::i64 Bundle (<| (bundle.prefix "i64") (|> bundle.empty @@ -118,7 +118,7 @@ (bundle.install "f64" (unary (|>> (_.//2 (_.float +1.0))))) (bundle.install "char" (unary i64::char))))) -(def: bundle::f64 +(def bundle::f64 Bundle (<| (bundle.prefix "f64") (|> bundle.empty @@ -133,15 +133,15 @@ (bundle.install "encode" (unary _.number->string/1)) (bundle.install "decode" (unary ///runtime.frac//decode))))) -(def: (text::char [subjectO paramO]) +(def (text::char [subjectO paramO]) Binary (_.string/1 (_.string_ref/2 subjectO paramO))) -(def: (text::clip [subjectO startO endO]) +(def (text::clip [subjectO startO endO]) Trinary (_.substring/3 subjectO startO endO)) -(def: bundle::text +(def bundle::text Bundle (<| (bundle.prefix "text") (|> bundle.empty @@ -152,16 +152,16 @@ (bundle.install "char" (binary text::char)) (bundle.install "clip" (trinary text::clip))))) -(def: (io::log input) +(def (io::log input) Unary (_.begin (list (_.display/1 input) _.newline/0))) -(def: (void code) +(def (void code) (-> Expression Computation) (_.begin (list code (_.string //////synthesis.unit)))) -(def: bundle::io +(def bundle::io Bundle (<| (bundle.prefix "io") (|> bundle.empty @@ -170,7 +170,7 @@ (bundle.install "exit" (unary _.exit/1)) (bundle.install "current-time" (nullary (function (_ _) (///runtime.io//current_time (_.string //////synthesis.unit)))))))) -(def: .public bundle +(def .public bundle Bundle (<| (bundle.prefix "lux") (|> bundle::lux diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index 47297cb47..8f07bec50 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -29,18 +29,18 @@ [reference [variable (.only Register Variable)]]]]]]) -(def: .public (apply expression archive [functionS argsS+]) +(def .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do [! ///////phase.monad] [functionO (expression archive functionS) argsO+ (monad.each ! (expression archive) argsS+)] (in (_.apply argsO+ functionO)))) -(def: capture +(def capture (-> Register Var) (|>> (///reference.foreign //reference.system) as_expected)) -(def: (with_closure inits function_definition) +(def (with_closure inits function_definition) (-> (List Expression) Computation (Operation Computation)) (///////phase#in (case inits @@ -54,13 +54,13 @@ {.#None}]) (_.apply inits))))) -(def: @curried (_.var "curried")) -(def: @missing (_.var "missing")) +(def @curried (_.var "curried")) +(def @missing (_.var "missing")) -(def: input +(def input (|>> ++ //case.register)) -(def: .public (function expression archive [environment arity bodyS]) +(def .public (function expression archive [environment arity bodyS]) (Generator (Abstraction Synthesis)) (do [! ///////phase.monad] [[function_name bodyO] (/////generation.with_new_context archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux index 8ca9af784..cd2ebc5af 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/loop.lux @@ -33,10 +33,10 @@ [reference [variable (.only Register)]]]]]]]) -(def: @scope +(def @scope (_.var "scope")) -(def: .public (scope expression archive [start initsS+ bodyS]) +(def .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop @@ -56,7 +56,7 @@ bodyO)]) (_.apply initsO+ @scope)))))) -(def: .public (again expression archive argsS+) +(def .public (again expression archive argsS+) (Generator (List Synthesis)) (do [! ///////phase.monad] [@scope /////generation.anchor diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux index 0772c64bc..cba7e79d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux @@ -5,7 +5,7 @@ ["_" scheme (.only Expression)]]]]) (with_template [<name> <type> <code>] - [(def: .public <name> + [(def .public <name> (-> <type> Expression) <code>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux index 7e0b61970..cef4fe09f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/reference.lux @@ -6,8 +6,8 @@ [/// [reference (.only System)]]) -(def: .public system +(def .public system (System Expression) (implementation - (def: constant _.var) - (def: variable _.var))) + (def constant _.var) + (def variable _.var))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index ecac319c2..8d145794e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -39,7 +39,7 @@ [archive (.only Output Archive) ["[0]" artifact (.only Registry)]]]]]]) -(def: module_id +(def module_id 0) (with_template [<name> <base>] @@ -55,10 +55,10 @@ (type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(def: .public unit +(def .public unit (_.string /////synthesis.unit)) -(def: .public with_vars +(def .public with_vars (syntax (_ [vars (<code>.tuple (<>.some <code>.local)) body <code>.any]) (do [! meta.monad] @@ -71,7 +71,7 @@ list.together))] (~ body)))))))) -(def: runtime: +(def runtime: (syntax (_ [declaration (<>.or <code>.local (<code>.form (<>.and <code>.local (<>.some <code>.local)))) @@ -84,11 +84,11 @@ (case declaration {.#Left name} (let [g!name (code.local name)] - (in (list (` (def: .public (~ g!name) + (in (list (` (def .public (~ g!name) Var (~ runtime_name))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) _.Computation (_.define_constant (~ runtime_name) (~ code))))))) @@ -97,17 +97,17 @@ inputsC (list#each code.local inputs) inputs_typesC (list#each (function.constant (` _.Expression)) inputs)] - (in (list (` (def: .public ((~ g!name) (~+ inputsC)) + (in (list (` (def .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) _.Computation) (_.apply (list (~+ inputsC)) (~ runtime_name)))) - (` (def: (~ (code.local (format "@" name))) + (` (def (~ (code.local (format "@" name))) _.Computation (..with_vars [(~+ inputsC)] (_.define_function (~ runtime_name) [(list (~+ inputsC)) {.#None}] (~ code)))))))))))))) -(def: last_index +(def last_index (-> Expression Computation) (|>> _.length/1 (_.-/2 (_.int +1)))) @@ -139,7 +139,7 @@ @slice)))) ))) -(def: (variant' tag last? value) +(def (variant' tag last? value) (-> Expression Expression Expression Computation) (all _.cons/2 tag @@ -149,7 +149,7 @@ (runtime: (sum//make tag last? value) (variant' tag last? value)) -(def: .public (variant [lefts right? value]) +(def .public (variant [lefts right? value]) (-> (Variant Expression) Computation) (..sum//make (_.int (.int lefts)) (_.bool right?) value)) @@ -176,26 +176,26 @@ (variant' (|> sum_tag (_.-/2 wanted_tag)) sum_flag sum_value)) no_match)))) -(def: runtime//adt +(def runtime//adt Computation (_.begin (list @tuple//left @tuple//right @sum//get @sum//make))) -(def: .public none +(def .public none Computation (|> ..unit [0 #0] variant)) -(def: .public some +(def .public some (-> Expression Computation) (|>> [1 #1] ..variant)) -(def: .public left +(def .public left (-> Expression Computation) (|>> [0 #0] ..variant)) -(def: .public right +(def .public right (-> Expression Computation) (|>> [1 #1] ..variant)) @@ -229,27 +229,27 @@ (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))]) (_.apply/2 @loop (_.reverse/1 program_args) ..none)))) -(def: runtime//lux +(def runtime//lux Computation (_.begin (list @lux//try @lux//program_args))) -(def: i64//+limit (_.manual "+9223372036854775807" +(def i64//+limit (_.manual "+9223372036854775807" ... "+0x7FFFFFFFFFFFFFFF" )) -(def: i64//-limit (_.manual "-9223372036854775808" +(def i64//-limit (_.manual "-9223372036854775808" ... "-0x8000000000000000" )) -(def: i64//+iteration (_.manual "+18446744073709551616" +(def i64//+iteration (_.manual "+18446744073709551616" ... "+0x10000000000000000" )) -(def: i64//-iteration (_.manual "-18446744073709551616" +(def i64//-iteration (_.manual "-18446744073709551616" ... "-0x10000000000000000" )) -(def: i64//+cap (_.manual "+9223372036854775808" +(def i64//+cap (_.manual "+9223372036854775808" ... "+0x8000000000000000" )) -(def: i64//-cap (_.manual "-9223372036854775809" +(def i64//-cap (_.manual "-9223372036854775809" ... "-0x8000000000000001" )) @@ -272,7 +272,7 @@ (_.arithmetic_shift/2 (_.remainder/2 (_.int +64) param)) ..i64//64)) -(def: as_nat +(def as_nat (_.remainder/2 ..i64//+iteration)) (runtime: (i64//right_shifted shift subject) @@ -295,7 +295,7 @@ (runtime: (i64//division param subject) (|> subject (_.//2 param) _.truncate/1 ..i64//64)) -(def: runtime//i64 +(def runtime//i64 Computation (_.begin (list @i64//64 @i64//left_shifted @@ -315,7 +315,7 @@ ..none (..some @output)))))) -(def: runtime//f64 +(def runtime//f64 Computation (_.begin (list @f64//decode))) @@ -332,7 +332,7 @@ (runtime: (text//char index text) (_.char->integer/1 (_.string_ref/2 text index))) -(def: runtime//text +(def runtime//text (_.begin (list @text//index @text//clip @text//char))) @@ -341,13 +341,13 @@ (_.begin (list (_.vector_set!/3 array idx value) array))) -(def: runtime//array +(def runtime//array Computation (all _.then @array//write )) -(def: runtime +(def runtime Computation (_.begin (list @slice runtime//lux @@ -358,7 +358,7 @@ runtime//array ))) -(def: .public generate +(def .public generate (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux index ec1611ddf..fec696893 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/structure.lux @@ -17,7 +17,7 @@ ["//[1]" /// ["[1][0]" phase (.open: "[1]#[0]" monad)]]]]) -(def: .public (tuple expression archive elemsS+) +(def .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ {.#End} @@ -31,7 +31,7 @@ (monad.each ///////phase.monad (expression archive)) (///////phase#each _.vector/*)))) -(def: .public (variant expression archive [lefts right? valueS]) +(def .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (++ lefts) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index de5d4c9e4..3e7102696 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux @@ -29,7 +29,7 @@ [reference (.only) [variable (.only)]]]]]]) -(def: (simple analysis) +(def (simple analysis) (-> ///simple.Simple /simple.Simple) (case analysis {///simple.#Unit} @@ -49,7 +49,7 @@ [///simple.#Int /simple.#I64] [///simple.#Rev /simple.#I64]))) -(def: (optimization archive) +(def (optimization archive) Phase (function (optimization' analysis) (case analysis @@ -102,7 +102,7 @@ (phase.result' state)))))) ))) -(def: .public (phase archive analysis) +(def .public (phase archive analysis) Phase (do phase.monad [synthesis (..optimization archive analysis)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux index 218ece022..4f772b16c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/case.lux @@ -37,11 +37,11 @@ [meta [archive (.only Archive)]]]]]) -(def: clean_up +(def clean_up (-> Path Path) (|>> {/.#Seq {/.#Pop}})) -(def: (path' pattern end? thenC) +(def (path' pattern end? thenC) (-> Pattern Bit (Operation Path) (Operation Path)) (case pattern {///pattern.#Simple simple} @@ -98,11 +98,11 @@ (list.reversed (list.enumeration tuple)))) )) -(def: (path archive synthesize pattern bodyA) +(def (path archive synthesize pattern bodyA) (-> Archive Phase Pattern Analysis (Operation Path)) (path' pattern true (///#each (|>> {/.#Then}) (synthesize archive bodyA)))) -(def: (weave_branch weave equivalence [new_test new_then] [[old_test old_then] old_tail]) +(def (weave_branch weave equivalence [new_test new_then] [[old_test old_then] old_tail]) (All (_ a) (-> (-> Path Path Path) (Equivalence a) [a Path] (/.Fork a Path) (/.Fork a Path))) @@ -116,13 +116,13 @@ {.#Item old_item} {.#Item (weave_branch weave equivalence [new_test new_then] old_item)})])) -(def: (weave_fork weave equivalence new_fork old_fork) +(def (weave_fork weave equivalence new_fork old_fork) (All (_ a) (-> (-> Path Path Path) (Equivalence a) (/.Fork a Path) (/.Fork a Path) (/.Fork a Path))) (list#mix (..weave_branch weave equivalence) old_fork {.#Item new_fork})) -(def: (weave new old) +(def (weave new old) (-> Path Path Path) (with_expansions [<default> (these {/.#Alt old new})] (case [new old] @@ -199,7 +199,7 @@ _ <default>))) -(def: (get patterns @selection) +(def (get patterns @selection) (-> (///complex.Tuple Pattern) Register (List Member)) (loop (again [lefts 0 patterns patterns]) @@ -236,52 +236,52 @@ _ <failure>))))) -(def: .public (synthesize_case synthesize archive input [[headP headA] tailPA+]) +(def .public (synthesize_case synthesize archive input [[headP headA] tailPA+]) (-> Phase Archive Synthesis Match (Operation Synthesis)) (do [! ///.monad] [headSP (path archive synthesize headP headA) tailSP+ (monad.each ! (product.uncurried (path archive synthesize)) tailPA+)] (in (/.branch/case [input (list#mix weave headSP tailSP+)])))) -(def: !masking +(def !masking (template (_ <variable> <output>) [[[{///pattern.#Bind <variable>} {///analysis.#Reference (///reference.local <output>)}] (list)]])) -(def: .public (synthesize_exec synthesize archive before after) +(def .public (synthesize_exec synthesize archive before after) (-> Phase Archive Synthesis Analysis (Operation Synthesis)) (do ///.monad [after (synthesize archive after)] (in (/.branch/exec [before after])))) -(def: .public (synthesize_let synthesize archive input @variable body) +(def .public (synthesize_let synthesize archive input @variable body) (-> Phase Archive Synthesis Register Analysis (Operation Synthesis)) (do ///.monad [body (/.with_new_local (synthesize archive body))] (in (/.branch/let [input @variable body])))) -(def: .public (synthesize_masking synthesize archive input @variable @output) +(def .public (synthesize_masking synthesize archive input @variable @output) (-> Phase Archive Synthesis Register Register (Operation Synthesis)) (if (n.= @variable @output) (///#in input) (..synthesize_let synthesize archive input @variable {///analysis.#Reference (///reference.local @output)}))) -(def: .public (synthesize_if synthesize archive test then else) +(def .public (synthesize_if synthesize archive test then else) (-> Phase Archive Synthesis Analysis Analysis (Operation Synthesis)) (do ///.monad [then (synthesize archive then) else (synthesize archive else)] (in (/.branch/if [test then else])))) -(def: !get +(def !get (template (_ <patterns> <output>) [[[(///pattern.tuple <patterns>) {///analysis.#Reference (///reference.local <output>)}] (.list)]])) -(def: .public (synthesize_get synthesize archive input patterns @member) +(def .public (synthesize_get synthesize archive input patterns @member) (-> Phase Archive Synthesis (///complex.Tuple Pattern) Register (Operation Synthesis)) (case (..get patterns @member) {.#End} @@ -295,7 +295,7 @@ _ (///#in (/.branch/get [path input]))))) -(def: .public (synthesize synthesize^ [headB tailB+] archive inputA) +(def .public (synthesize synthesize^ [headB tailB+] archive inputA) (-> Phase Match Phase) (do [! ///.monad] [inputS (synthesize^ archive inputA)] @@ -335,7 +335,7 @@ match (..synthesize_case synthesize^ archive inputS match)))) -(def: .public (count_pops path) +(def .public (count_pops path) (-> Path [Nat Path]) (case path (pattern (/.path/seq {/.#Pop} path')) @@ -345,7 +345,7 @@ _ [0 path])) -(def: .public pattern_matching_error +(def .public pattern_matching_error "Invalid expression for pattern-matching.") (type: .public Storage @@ -353,7 +353,7 @@ [#bindings (Set Register) #dependencies (Set Variable)])) -(def: empty +(def empty Storage [#bindings (set.empty n.hash) #dependencies (set.empty ///reference/variable.hash)]) @@ -364,7 +364,7 @@ ... since the variable will exist beforehand, so no closure will need ... to be created for it. ... Apply this trick to JS, Python et al. -(def: .public (storage path) +(def .public (storage path) (-> Path Storage) (loop (for_path [path path path_storage ..empty]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 8f29f5d0b..89af418b6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -36,21 +36,21 @@ "Foreign" (%.nat foreign) "Environment" (exception.listing /.%synthesis environment))) -(def: arity_arguments +(def arity_arguments (-> Arity (List Synthesis)) (|>> -- (enum.range n.enum 1) (list#each (|>> /.variable/local)))) -(def: .public self_reference +(def .public self_reference (template (self_reference) [(/.variable/local 0)])) -(def: (expanded_nested_self_reference arity) +(def (expanded_nested_self_reference arity) (-> Arity Synthesis) (/.function/apply [(..self_reference) (arity_arguments arity)])) -(def: .public (apply phase) +(def .public (apply phase) (-> Phase Phase) (function (_ archive exprA) (let [[funcA argsA] (////analysis.reification exprA)] @@ -86,7 +86,7 @@ _ (in <apply>))))))) -(def: (find_foreign environment register) +(def (find_foreign environment register) (-> (Environment Synthesis) Register (Operation Synthesis)) (case (list.item register environment) {.#Some aliased} @@ -95,7 +95,7 @@ {.#None} (phase.except ..cannot_find_foreign_variable_in_environment [register environment]))) -(def: (grow_path grow path) +(def (grow_path grow path) (-> (-> Synthesis (Operation Synthesis)) Path (Operation Path)) (case path {/.#Bind register} @@ -142,7 +142,7 @@ _ (phase#in path))) -(def: (grow environment expression) +(def (grow environment expression) (-> (Environment Synthesis) Synthesis (Operation Synthesis)) (case expression {/.#Structure structure} @@ -255,7 +255,7 @@ {/.#Simple _} (phase#in expression))) -(def: .public (abstraction phase environment archive bodyA) +(def .public (abstraction phase environment archive bodyA) (-> Phase (Environment Analysis) Phase) (do [! phase.monad] [environment (monad.each ! (phase archive) environment) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux index 778ba2900..f3c5fb252 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/loop.lux @@ -25,11 +25,11 @@ (type: .public (Transform a) (-> a (Maybe a))) -(def: .public (register_optimization offset) +(def .public (register_optimization offset) (-> Register (-> Register Register)) (|>> -- (n.+ offset))) -(def: (path_optimization body_optimization offset) +(def (path_optimization body_optimization offset) (-> (Transform Synthesis) Register (Transform Path)) (function (again path) (case path @@ -77,7 +77,7 @@ _ {.#Some path}))) -(def: (body_optimization true_loop? offset scope_environment arity expr) +(def (body_optimization true_loop? offset scope_environment arity expr) (-> Bit Register (Environment Synthesis) Arity (Transform Synthesis)) (loop (again [return? true expr expr]) @@ -211,7 +211,7 @@ (monad.each maybe.monad (again false)) (maybe#each (|>> [name] {/.#Extension})))))) -(def: .public (optimization true_loop? offset inits functionS) +(def .public (optimization true_loop? offset inits functionS) (-> Bit Register (List Synthesis) Abstraction (Maybe [Register (List Synthesis) Synthesis])) (|> (the /.#body functionS) (body_optimization true_loop? offset (the /.#environment functionS) (the /.#arity functionS)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 51de85771..1ca58edd0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -30,7 +30,7 @@ ["[0]" reference (.only) ["[0]" variable (.only Register Variable)]]]]) -(def: (prune redundant register) +(def (prune redundant register) (-> Register Register Register) (if (n.> redundant register) (-- register) @@ -39,7 +39,7 @@ (type: (Remover a) (-> Register (-> a a))) -(def: (remove_local_from_path remove_local redundant) +(def (remove_local_from_path remove_local redundant) (-> (Remover Synthesis) (Remover Path)) (function (again path) (case path @@ -98,7 +98,7 @@ {/.#Then (remove_local redundant then)} ))) -(def: (remove_local_from_variable redundant variable) +(def (remove_local_from_variable redundant variable) (Remover Variable) (case variable {variable.#Local register} @@ -107,7 +107,7 @@ {variable.#Foreign register} variable)) -(def: (remove_local redundant) +(def (remove_local redundant) (Remover Synthesis) (function (again synthesis) (case synthesis @@ -178,14 +178,14 @@ (type: Redundancy (Dictionary Register Bit)) -(def: initial +(def initial Redundancy (dictionary.empty n.hash)) -(def: redundant! true) -(def: necessary! false) +(def redundant! true) +(def necessary! false) -(def: (extended offset amount redundancy) +(def (extended offset amount redundancy) (-> Register Nat Redundancy [(List Register) Redundancy]) (let [extension (|> amount list.indices (list#each (n.+ offset)))] [extension @@ -194,14 +194,14 @@ redundancy extension)])) -(def: (default arity) +(def (default arity) (-> Arity Redundancy) (product.right (..extended 0 (++ arity) ..initial))) (type: (Optimization a) (-> [Redundancy a] (Try [Redundancy a]))) -(def: (list_optimization optimization) +(def (list_optimization optimization) (All (_ a) (-> (Optimization a) (Optimization (List a)))) (function (again [redundancy values]) (case values @@ -225,7 +225,7 @@ [unknown_register] ) -(def: (declare register redundancy) +(def (declare register redundancy) (-> Register Redundancy (Try Redundancy)) (case (dictionary.value register redundancy) {.#None} @@ -234,7 +234,7 @@ {.#Some _} (exception.except ..redundant_declaration [register]))) -(def: (observe register redundancy) +(def (observe register redundancy) (-> Register Redundancy (Try Redundancy)) (case (dictionary.value register redundancy) {.#None} @@ -243,7 +243,7 @@ {.#Some _} {try.#Success (dictionary.has register ..necessary! redundancy)})) -(def: (format redundancy) +(def (format redundancy) (%.Format Redundancy) (|> redundancy dictionary.entries @@ -251,7 +251,7 @@ (%.format (%.nat register) ": " (%.bit redundant?)))) (text.interposed ", "))) -(def: (path_optimization optimization) +(def (path_optimization optimization) (-> (Optimization Synthesis) (Optimization Path)) (function (again [redundancy path]) (case path @@ -329,7 +329,7 @@ (in [redundancy {/.#Then then}])) ))) -(def: (optimization' [redundancy synthesis]) +(def (optimization' [redundancy synthesis]) (Optimization Synthesis) (with_expansions [<no_op> (these {try.#Success [redundancy synthesis]})] @@ -449,7 +449,7 @@ (in [redundancy {/.#Extension name inputs}]))))) -(def: .public optimization +(def .public optimization (-> Synthesis (Try Synthesis)) (|>> [..initial] optimization' 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 fcf6e4cdc..625448c47 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -24,7 +24,7 @@ (type: .public (Program expression directive) (-> unit.ID expression directive)) -(def: .public name +(def .public name Text "") @@ -32,7 +32,7 @@ (exception.report "Modules" (exception.listing %.text modules))) -(def: .public (context archive) +(def .public (context archive) (-> Archive (Try unit.ID)) (do [! try.monad] [registries (|> archive diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index 3dcd579c9..054c8eeb2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -54,16 +54,16 @@ ["[0]" rev] ["[0]" frac]]]]]) -(def: declaration_name +(def declaration_name (syntax (_ [[name parameters] (<code>.form (<>.and <code>.any (<>.some <code>.any)))]) (in (list name)))) -(def: inline: +(def inlined (template (_ <declaration> <type> <body>) - [(for @.python (def: <declaration> <type> <body>) + [(for @.python (def <declaration> <type> <body>) ... TODO: No longer skip inlining Lua after Rembulan isn't being used anymore. - @.lua (def: <declaration> <type> <body>) - (`` (def: (~~ (..declaration_name <declaration>)) + @.lua (def <declaration> <type> <body>) + (`` (def (~~ (..declaration_name <declaration>)) (template <declaration> [<body>]))))])) @@ -84,7 +84,7 @@ Nat) (with_template [<extension> <diff> <name>] - [(def: <name> + [(def <name> (template (_ value) [(<extension> <diff> value)]))] @@ -93,12 +93,12 @@ ["lux i64 -" 1 !--] ) -(def: !clip +(def !clip (template (_ from to text) [("lux text clip" from (n.- from to) text)])) (with_template [<name> <extension>] - [(def: <name> + [(def <name> (template (_ reference subject) [(<extension> reference subject)]))] @@ -107,7 +107,7 @@ ) (with_template [<name> <extension>] - [(def: <name> + [(def <name> (template (_ param subject) [(<extension> param subject)]))] @@ -118,17 +118,17 @@ (type: .public Aliases (Dictionary Text Text)) -(def: .public no_aliases +(def .public no_aliases Aliases (dictionary.empty text.hash)) -(def: .public prelude +(def .public prelude .prelude) -(def: .public text_delimiter text.double_quote) +(def .public text_delimiter text.double_quote) (with_template [<char> <definition>] - [(def: .public <definition> <char>)] + [(def .public <definition> <char>)] ... Form delimiters ["(" open_form] @@ -165,9 +165,9 @@ (exception.report "Module" (%.text module))) -(def: amount_of_input_shown 64) +(def amount_of_input_shown 64) -(inline: (input_at start input) +(inlined (input_at start input) (-> Offset Text Text) (let [end (|> start (!n/+ amount_of_input_shown) (n.min ("lux text size" input)))] (!clip start end input))) @@ -187,12 +187,12 @@ (exception.report "Text" (%.text text))) -(def: !failure +(def !failure (template (_ parser where offset source_code) [{.#Left [[where offset source_code] (exception.error ..unrecognized_input [where (%.symbol (symbol parser)) source_code offset])]}])) -(def: !end_of_file +(def !end_of_file (template (_ where offset source_code current_module) [{.#Left [[where offset source_code] (exception.error ..end_of_file current_module)]}])) @@ -200,7 +200,7 @@ (type: (Parser a) (-> Source (Either [Source Text] [Source a]))) -(def: !with_char+ +(def !with_char+ (template (_ @source_code_size @source_code @offset @char @else @body) [(if (!i/< (as Int @source_code_size) (as Int @offset)) @@ -208,11 +208,11 @@ @body) @else)])) -(def: !with_char +(def !with_char (template (_ @source_code @offset @char @else @body) [(!with_char+ ("lux text size" @source_code) @source_code @offset @char @else @body)])) -(def: !letE +(def !letE (template (_ <binding> <computation> <body>) [(case <computation> {.#Right <binding>} @@ -222,30 +222,30 @@ <<otherwise>> (as_expected <<otherwise>>))])) -(def: !horizontal +(def !horizontal (template (_ where offset source_code) [[(revised .#column ++ where) (!++ offset) source_code]])) -(inline: (!new_line where) +(inlined (!new_line where) (-> Location Location) (let [[where::file where::line where::column] where] [where::file (!++ where::line) 0])) -(inline: (!forward length where) +(inlined (!forward length where) (-> Nat Location Location) (let [[where::file where::line where::column] where] [where::file where::line (!n/+ length where::column)])) -(def: !vertical +(def !vertical (template (_ where offset source_code) [[(!new_line where) (!++ offset) source_code]])) (with_template [<name> <close> <tag>] - [(inline: (<name> parse where offset source_code) + [(inlined (<name> parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) (loop (again [source (is Source [(!forward 1 where) offset source_code]) @@ -268,7 +268,7 @@ [tuple_parser ..close_tuple .#Tuple] ) -(def: !guarantee_no_new_lines +(def !guarantee_no_new_lines (template (_ where offset source_code content body) [(case ("lux text index" 0 (static text.new_line) content) {.#None} @@ -278,7 +278,7 @@ {.#Left [[where offset source_code] (exception.error ..text_cannot_contain_new_lines content)]})])) -(def: (text_parser where offset source_code) +(def (text_parser where offset source_code) (-> Location Offset Text (Either [Source Text] [Source Code])) (case ("lux text index" offset (static ..text_delimiter) source_code) {.#Some g!end} @@ -306,7 +306,7 @@ [..open_tuple] [..close_tuple] [..text_delimiter]) <digit_separator> (static ..digit_separator)] - (def: !if_digit? + (def !if_digit? (template (_ @char @then @else) [("lux syntax char case!" @char [[<digits>] @@ -315,7 +315,7 @@ ... else @else)])) - (def: !if_digit?+ + (def !if_digit?+ (template (_ @char @then @else_options @else) [(`` ("lux syntax char case!" @char [[<digits> <digit_separator>] @@ -326,7 +326,7 @@ ... else @else))])) - (`` (def: !if_symbol_char?|tail + (`` (def !if_symbol_char?|tail (template (_ @char @then @else) [("lux syntax char case!" @char [[<non_symbol_chars>] @@ -335,7 +335,7 @@ ... else @then)]))) - (`` (def: !if_symbol_char?|head + (`` (def !if_symbol_char?|head (template (_ @char @then @else) [("lux syntax char case!" @char [[<non_symbol_chars> <digits>] @@ -345,7 +345,7 @@ @then)]))) ) -(def: !number_output +(def !number_output (template (_ <source_code> <start> <end> <codec> <tag>) [(case (|> <source_code> (!clip <start> <end>) @@ -362,7 +362,7 @@ {.#Left [[where <start> <source_code>] error]})])) -(def: no_exponent +(def no_exponent Offset 0) @@ -375,7 +375,7 @@ [..positive_sign] [..negative_sign])] - (inline: (frac_parser source_code//size start where offset source_code) + (inlined (frac_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) (loop (again [end offset @@ -400,7 +400,7 @@ <frac_output>)))) - (inline: (signed_parser source_code//size start where offset source_code) + (inlined (signed_parser source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) (loop (again [end offset]) @@ -415,7 +415,7 @@ ) (with_template [<parser> <codec> <tag>] - [(inline: (<parser> source_code//size start where offset source_code) + [(inlined (<parser> source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) (loop (again [g!end offset]) @@ -429,7 +429,7 @@ [rev_parser rev.decimal .#Rev] ) -(def: !signed_parser +(def !signed_parser (template (_ source_code//size offset where source_code @aliases @end) [(<| (let [g!offset/1 (!++ offset)]) (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) @@ -441,7 +441,7 @@ end source_code] (!clip start end source_code)]}] - (inline: (symbol_part_parser start where offset source_code) + (inlined (symbol_part_parser start where offset source_code) (-> Nat Location Offset Text (Either [Source Text] [Source Text])) (let [source_code//size ("lux text size" source_code)] @@ -451,14 +451,14 @@ (again (!++ end)) <output>)))))) -(def: !half_symbol_parser +(def !half_symbol_parser (template (_ @offset @char @module) [(!if_symbol_char?|head @char (!letE [source' symbol] (..symbol_part_parser @offset (!forward 1 where) (!++ @offset) source_code) {.#Right [source' [@module symbol]]}) (!failure ..!half_symbol_parser where @offset source_code))])) -(`` (def: (short_symbol_parser source_code//size current_module [where offset/0 source_code]) +(`` (def (short_symbol_parser source_code//size current_module [where offset/0 source_code]) (-> Nat Text (Parser Symbol)) (<| (!with_char+ source_code//size source_code offset/0 char/0 (!end_of_file where offset/0 source_code current_module)) @@ -469,13 +469,13 @@ (!half_symbol_parser offset/1 char/1 current_module)) (!half_symbol_parser offset/0 char/0 (static ..prelude)))))) -(def: !short_symbol_parser +(def !short_symbol_parser (template (_ source_code//size @current_module @source @where @tag) [(!letE [source' symbol] (..short_symbol_parser source_code//size @current_module @source) {.#Right [source' [@where {@tag symbol}]]})])) (with_expansions [<simple> (these {.#Right [source' ["" simple]]})] - (`` (def: (full_symbol_parser aliases start source) + (`` (def (full_symbol_parser aliases start source) (-> Aliases Offset (Parser Symbol)) (<| (!letE [source' simple] (let [[where offset source_code] source] (..symbol_part_parser start where offset source_code))) @@ -493,13 +493,13 @@ complex]]})) <simple>))))) -(def: !full_symbol_parser +(def !full_symbol_parser (template (_ @offset @source @where @aliases @tag) [(!letE [source' full_symbol] (..full_symbol_parser @aliases @offset @source) {.#Right [source' [@where {@tag full_symbol}]]})])) ... TODO: Grammar macro for specifying syntax. -... (def: lux_grammar +... (def lux_grammar ... (grammar [expression "..."] ... [form "(" [#* expression] ")"])) @@ -508,18 +508,18 @@ <move_2> (these [(!forward 1 where) (!++/2 offset/0) source_code]) <again> (these (parse current_module aliases source_code//size))] - (def: !close + (def !close (template (_ closer) [{.#Left [<move_1> closer]}])) - (def: (bit_syntax value [where offset/0 source_code]) + (def (bit_syntax value [where offset/0 source_code]) (-> Bit (Parser Code)) {.#Right [[(revised .#column (|>> !++/2) where) (!++/2 offset/0) source_code] [where {.#Bit value}]]}) - (def: .public (parse current_module aliases source_code//size) + (def .public (parse current_module aliases source_code//size) (-> Text Aliases Nat (Parser Code)) ... The "exec []" is only there to avoid function fusion. ... This is to preserve the loop as much as possible and keep it tight. diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index c4a772695..722029eb2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -50,11 +50,11 @@ ... https://en.wikipedia.org/wiki/Currying #currying? Bit])) -(def: .public fresh_resolver +(def .public fresh_resolver Resolver (dictionary.empty variable.hash)) -(def: .public init +(def .public init State [#locals 0 #currying? false]) @@ -145,12 +145,12 @@ (type: .public Path (Path' Synthesis)) -(def: .public path/pop +(def .public path/pop Path {#Pop}) (with_template [<name> <kind>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Access} {<kind>} @@ -161,7 +161,7 @@ ) (with_template [<name> <access> <lefts> <right?>] - [(def: .public <name> + [(def .public <name> (template (<name> lefts right?) [(.<| {..#Access} {<access>} @@ -173,7 +173,7 @@ ) (with_template [<access> <side> <name>] - [(def: .public <name> + [(def .public <name> (template (<name> lefts) [(<access> lefts <side>)]))] @@ -185,7 +185,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [{<tag> content}]))] @@ -194,7 +194,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> left right) [{<tag> left right}]))] @@ -208,16 +208,16 @@ (type: .public Apply (Apply' Synthesis)) -(def: .public unit +(def .public unit Text "") (with_template [<with> <query> <tag> <type>] - [(def: .public (<with> value) + [(def .public (<with> value) (-> <type> (All (_ a) (-> (Operation a) (Operation a)))) (extension.temporary (has <tag> value))) - (def: .public <query> + (def .public <query> (Operation <type>) (extension.read (the <tag>)))] @@ -225,14 +225,14 @@ [with_currying? currying? #currying? Bit] ) -(def: .public with_new_local +(def .public with_new_local (All (_ a) (-> (Operation a) (Operation a))) (<<| (do phase.monad [locals ..locals]) (..with_locals (++ locals)))) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [{..#Simple {<tag> content}}]))] @@ -243,7 +243,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Structure} {<tag>} @@ -254,7 +254,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Reference} <tag> @@ -267,7 +267,7 @@ ) (with_template [<name> <family> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(.<| {..#Control} {<family>} @@ -287,7 +287,7 @@ [function/apply ..#Function ..#Apply] ) -(def: .public (%path' %then value) +(def .public (%path' %then value) (All (_ a) (-> (Format a) (Format (Path' a)))) (case value {#Pop} @@ -331,7 +331,7 @@ (|> (%then then) (text.enclosed ["(! " ")"])))) -(def: .public (%synthesis value) +(def .public (%synthesis value) (Format Synthesis) (case value {#Simple it} @@ -419,14 +419,14 @@ (format (%.text name) " ") (text.enclosed ["(" ")"])))) -(def: .public %path +(def .public %path (Format Path) (%path' %synthesis)) -(def: .public (path'_equivalence equivalence) +(def .public (path'_equivalence equivalence) (All (_ a) (-> (Equivalence a) (Equivalence (Path' a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Pop} {#Pop}] true @@ -466,13 +466,13 @@ _ false)))) -(def: (path'_hash super) +(def (path'_hash super) (All (_ a) (-> (Hash a) (Hash (Path' a)))) (implementation - (def: equivalence + (def equivalence (..path'_equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value {#Pop} 2 @@ -511,10 +511,10 @@ (n.* 29 (at super hash body)) )))) -(def: (branch_equivalence (open "#[0]")) +(def (branch_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Branch a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Let [reference_input reference_register reference_body]} {#Let [sample_input sample_register sample_body]}] @@ -541,13 +541,13 @@ _ false)))) -(def: (branch_hash super) +(def (branch_hash super) (All (_ a) (-> (Hash a) (Hash (Branch a)))) (implementation - (def: equivalence + (def equivalence (..branch_equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value {#Exec this that} (all n.* 2 @@ -577,10 +577,10 @@ (at (..path'_hash super) hash path)) )))) -(def: (loop_equivalence (open "/#[0]")) +(def (loop_equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Loop a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Scope [reference_start reference_inits reference_iteration]} {#Scope [sample_start sample_inits sample_iteration]}] @@ -594,13 +594,13 @@ _ false)))) -(def: (loop_hash super) +(def (loop_hash super) (All (_ a) (-> (Hash a) (Hash (Loop a)))) (implementation - (def: equivalence + (def equivalence (..loop_equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value {#Scope [start inits iteration]} (all n.* 2 @@ -613,10 +613,10 @@ (at (list.hash super) hash resets)) )))) -(def: (function_equivalence (open "#[0]")) +(def (function_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Function a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] [{#Abstraction [reference_environment reference_arity reference_body]} {#Abstraction [sample_environment sample_arity sample_body]}] @@ -632,13 +632,13 @@ _ false)))) -(def: (function_hash super) +(def (function_hash super) (All (_ a) (-> (Hash a) (Hash (Function a)))) (implementation - (def: equivalence + (def equivalence (..function_equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value {#Abstraction [environment arity body]} (all n.* 2 @@ -652,10 +652,10 @@ (at (list.hash super) hash arguments)) )))) -(def: (control_equivalence (open "#[0]")) +(def (control_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Control a)))) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] (^.with_template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] @@ -667,13 +667,13 @@ _ false)))) -(def: (control_hash super) +(def (control_hash super) (All (_ a) (-> (Hash a) (Hash (Control a)))) (implementation - (def: equivalence + (def equivalence (..control_equivalence (at super equivalence))) - (def: (hash value) + (def (hash value) (case value (^.with_template [<factor> <tag> <hash>] [{<tag> value} @@ -683,10 +683,10 @@ [5 #Function ..function_hash]) )))) -(def: .public equivalence +(def .public equivalence (Equivalence Synthesis) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] (^.with_template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] @@ -700,16 +700,16 @@ _ false)))) -(def: .public path_equivalence +(def .public path_equivalence (Equivalence Path) (path'_equivalence equivalence)) -(def: .public hash +(def .public hash (Hash Synthesis) (implementation - (def: equivalence ..equivalence) + (def equivalence ..equivalence) - (def: (hash value) + (def (hash value) (let [again_hash [..equivalence hash]] (case value (^.with_template [<tag> <hash>] @@ -721,14 +721,14 @@ [#Control (..control_hash again_hash)] [#Extension (extension.hash again_hash)])))))) -(def: .public !bind_top +(def .public !bind_top (template (!bind_top register thenP) [(all ..path/seq {..#Bind register} {..#Pop} thenP)])) -(def: .public !multi_pop +(def .public !multi_pop (template (!multi_pop nextP) [(all ..path/seq {..#Pop} @@ -743,7 +743,7 @@ ... pattern-optimizations again, since a lot of BINDs will become POPs ... and thus will result in useless code being generated. (with_template [<name> <side>] - [(def: .public <name> + [(def .public <name> (template (<name> idx nextP) [(all ..path/seq (<side> idx) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access.lux index dba26b8af..76c9a0400 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access.lux @@ -17,7 +17,7 @@ {#Side Side} {#Member Member})) -(def: .public (format it) +(def .public (format it) (Format Access) (case it {#Side it} @@ -26,13 +26,13 @@ {#Member it} (/member.format it))) -(def: .public hash +(def .public hash (Hash Access) (all sum.hash /side.hash /member.hash )) -(def: .public equivalence +(def .public equivalence (Equivalence Access) (at ..hash equivalence)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux index 24482862a..ec159b99a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/member.lux @@ -18,17 +18,17 @@ [#lefts Nat #right? Bit])) -(def: .public (format it) +(def .public (format it) (%.Format Member) (%.format "[" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "]")) -(def: .public hash +(def .public hash (Hash Member) (all product.hash nat.hash bit.hash )) -(def: .public equivalence +(def .public equivalence (Equivalence Member) (at ..hash equivalence)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux index 89dd5e86a..df1bda351 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/access/side.lux @@ -18,17 +18,17 @@ [#lefts Nat #right? Bit])) -(def: .public (format it) +(def .public (format it) (%.Format Side) (%.format "{" (%.nat (the #lefts it)) " " (%.bit (the #right? it)) "}")) -(def: .public hash +(def .public hash (Hash Side) (all product.hash nat.hash bit.hash )) -(def: .public equivalence +(def .public equivalence (Equivalence Side) (at ..hash equivalence)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux index 343619a25..3774c0319 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux @@ -26,7 +26,7 @@ {#F64 Frac} {#Text Text})) -(def: .public (format it) +(def .public (format it) (%.Format Simple) (case it (^.with_template [<pattern> <format>] @@ -39,10 +39,10 @@ {#I64 value} (%.int (.int value)))) -(def: .public equivalence +(def .public equivalence (Equivalence Simple) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] (^.with_template [<tag> <eq> <format>] [[{<tag> reference'} {<tag> sample'}] @@ -57,12 +57,12 @@ _ false)))) -(def: .public hash +(def .public hash (Hash Simple) (implementation - (def: equivalence ..equivalence) + (def equivalence ..equivalence) - (def: hash + (def hash (|>> (pipe.case (^.with_template [<factor> <tag> <hash>] [{<tag> value'} diff --git a/stdlib/source/library/lux/tool/compiler/meta.lux b/stdlib/source/library/lux/tool/compiler/meta.lux index 4034a23c8..ef6e71986 100644 --- a/stdlib/source/library/lux/tool/compiler/meta.lux +++ b/stdlib/source/library/lux/tool/compiler/meta.lux @@ -4,6 +4,6 @@ [// [version (.only Version)]]) -(def: .public version +(def .public version Version 00,02,00) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index bdb87cb95..b3b213099 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -76,16 +76,16 @@ [#next module.ID #resolver (Dictionary descriptor.Module [module.ID (Maybe (Entry Any))])]) - (def: next + (def next (-> Archive module.ID) (|>> representation (the #next))) - (def: .public empty + (def .public empty Archive (abstraction [#next 0 #resolver (dictionary.empty text.hash)])) - (def: .public (id module archive) + (def .public (id module archive) (-> descriptor.Module Archive (Try module.ID)) (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) @@ -96,7 +96,7 @@ (exception.except ..unknown_document [module (dictionary.keys /#resolver)])))) - (def: .public (reserve module archive) + (def .public (reserve module archive) (-> descriptor.Module Archive (Try [module.ID Archive])) (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) @@ -111,7 +111,7 @@ (revised #next ++) abstraction)]}))) - (def: .public (has module entry archive) + (def .public (has module entry archive) (-> descriptor.Module (Entry Any) Archive (Try Archive)) (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) @@ -131,7 +131,7 @@ {.#None} (exception.except ..module_must_be_reserved_before_it_can_be_added [module])))) - (def: .public entries + (def .public entries (-> Archive (List [descriptor.Module [module.ID (Entry Any)]])) (|>> representation (the #resolver) @@ -139,7 +139,7 @@ (list.all (function (_ [module [module_id entry]]) (at maybe.monad each (|>> [module_id] [module]) entry))))) - (def: .public (find module archive) + (def .public (find module archive) (-> descriptor.Module Archive (Try (Entry Any))) (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) @@ -152,7 +152,7 @@ {.#None} (exception.except ..unknown_document [module (dictionary.keys /#resolver)])))) - (def: .public (archived? archive module) + (def .public (archived? archive module) (-> Archive descriptor.Module Bit) (case (..find module archive) {try.#Success _} @@ -161,7 +161,7 @@ {try.#Failure _} false)) - (def: .public archived + (def .public archived (-> Archive (List descriptor.Module)) (|>> representation (the #resolver) @@ -171,7 +171,7 @@ {.#Some _} {.#Some module} {.#None} {.#None}))))) - (def: .public (reserved? archive module) + (def .public (reserved? archive module) (-> Archive descriptor.Module Bit) (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) @@ -181,13 +181,13 @@ {.#None} false))) - (def: .public reserved + (def .public reserved (-> Archive (List descriptor.Module)) (|>> representation (the #resolver) dictionary.keys)) - (def: .public reservations + (def .public reservations (-> Archive (List [descriptor.Module module.ID])) (|>> representation (the #resolver) @@ -195,7 +195,7 @@ (list#each (function (_ [module [id _]]) [module id])))) - (def: .public (composite additions archive) + (def .public (composite additions archive) (-> Archive Archive Archive) (let [[+next +resolver] (representation additions)] (|> archive @@ -219,21 +219,21 @@ (type: Frozen [Version module.ID (List Reservation)]) - (def: reader + (def reader (Parser ..Frozen) (all <>.and <binary>.nat <binary>.nat (<binary>.list (<>.and <binary>.text <binary>.nat)))) - (def: writer + (def writer (Writer ..Frozen) (all \\format.and \\format.nat \\format.nat (\\format.list (\\format.and \\format.text \\format.nat)))) - (def: .public (export version archive) + (def .public (export version archive) (-> Version Archive Binary) (let [(open "/[0]") (representation archive)] (|> /#resolver @@ -251,7 +251,7 @@ "Expected" (%.nat expected) "Actual" (%.nat actual))) - (def: .public (import expected binary) + (def .public (import expected binary) (-> Version Binary (Try Archive)) (do try.monad [[actual next reservations] (<binary>.result ..reader binary) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux index f66a0a42f..252776c37 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -23,7 +23,7 @@ #category Category #mandatory? Bit])) -(def: .public equivalence +(def .public equivalence (Equivalence Artifact) (all product.equivalence nat.equivalence 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 9e00a5b51..d9801694c 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 @@ -19,7 +19,7 @@ (type: .public Definition [Text (Maybe [Arity [Nat Nat]])]) -(def: .public definition_equivalence +(def .public definition_equivalence (Equivalence Definition) (all product.equivalence text.equivalence @@ -40,10 +40,10 @@ {#Directive Text} {#Custom Text})) -(def: .public equivalence +(def .public equivalence (Equivalence Category) (implementation - (def: (= left right) + (def (= left right) (case [left right] [{#Anonymous} {#Anonymous}] true diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux index 445e44c72..0e35d6528 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux @@ -9,11 +9,11 @@ (primitive .public (Key k) Signature - (def: .public signature + (def .public signature (All (_ ?) (-> (Key ?) Signature)) (|>> representation)) - (def: .public (key signature sample) + (def .public (key signature sample) (All (_ d) (-> Signature d (Key d))) (abstraction signature)) ) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module.lux index 868009871..4e2757bb8 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module.lux @@ -8,7 +8,7 @@ (type: .public ID Nat) -(def: .public runtime +(def .public runtime ID 0) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux index b661a1587..92e8dcc60 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux @@ -24,7 +24,7 @@ (type: .public Module Text) -(def: .public runtime +(def .public runtime Module "") @@ -36,10 +36,10 @@ #state Module_State #references (Set Module)])) -(def: module_state_equivalence +(def module_state_equivalence (Equivalence Module_State) (implementation - (def: (= left right) + (def (= left right) (case [left right] (^.with_template [<tag>] [[{<tag>} {<tag>}] @@ -51,7 +51,7 @@ _ false)))) -(def: .public equivalence +(def .public equivalence (Equivalence Descriptor) (all product.equivalence text.equivalence @@ -61,7 +61,7 @@ set.equivalence )) -(def: .public writer +(def .public writer (Writer Descriptor) (all \\format.and \\format.text @@ -71,7 +71,7 @@ (\\format.set \\format.text) )) -(def: .public parser +(def .public parser (Parser Descriptor) (all <>.and <binary>.text diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux index 56dd787be..fe4977e8d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux @@ -30,7 +30,7 @@ [#signature Signature #content d]) - (def: .public (content key document) + (def .public (content key document) (All (_ d) (-> (Key d) (Document Any) (Try d))) (let [[document//signature document//content] (representation document)] (if (at signature.equivalence = @@ -44,29 +44,29 @@ (exception.except ..invalid_signature [(key.signature key) document//signature])))) - (def: .public (document key content) + (def .public (document key content) (All (_ d) (-> (Key d) d (Document d))) (abstraction [#signature (key.signature key) #content content])) - (def: .public (marked? key document) + (def .public (marked? key document) (All (_ d) (-> (Key d) (Document Any) (Try (Document d)))) (do try.monad [_ (..content key document)] (in (as_expected document)))) - (def: .public signature + (def .public signature (-> (Document Any) Signature) (|>> representation (the #signature))) - (def: .public (writer content) + (def .public (writer content) (All (_ d) (-> (Writer d) (Writer (Document d)))) (let [writer (all binary.and signature.writer content)] (|>> representation writer))) - (def: .public (parser key it) + (def .public (parser key it) (All (_ d) (-> (Key d) (Parser d) (Parser (Document d)))) (do <>.monad [actual signature.parser diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux index 09cfc1190..9f23cad2e 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -34,20 +34,20 @@ [#artifacts (Sequence [Artifact (Set unit.ID)]) #resolver (Dictionary Text [ID (Maybe //category.Definition)])]) - (def: .public empty + (def .public empty Registry (abstraction [#artifacts sequence.empty #resolver (dictionary.empty text.hash)])) - (def: .public artifacts + (def .public artifacts (-> Registry (Sequence [Artifact (Set unit.ID)])) (|>> representation (the #artifacts))) - (def: next + (def next (-> Registry ID) (|>> ..artifacts sequence.size)) - (def: .public (resource mandatory? dependencies registry) + (def .public (resource mandatory? dependencies registry) (-> Bit (Set unit.ID) Registry [ID Registry]) (let [id (..next registry)] [id @@ -60,7 +60,7 @@ abstraction)])) (with_template [<tag> <create> <fetch> <type> <name> <+resolver>] - [(def: .public (<create> it mandatory? dependencies registry) + [(def .public (<create> it mandatory? dependencies registry) (-> <type> Bit (Set unit.ID) Registry [ID Registry]) (let [id (..next registry)] [id @@ -73,7 +73,7 @@ (revised #resolver (dictionary.has (<name> it) [id (is (Maybe //category.Definition) <+resolver>)])) abstraction)])) - (def: .public (<fetch> registry) + (def .public (<fetch> registry) (-> Registry (List <type>)) (|> registry representation @@ -94,17 +94,17 @@ [//category.#Custom custom customs Text |> {.#None}] ) - (def: .public (find_definition name registry) + (def .public (find_definition name registry) (-> Text Registry (Maybe [ID (Maybe //category.Definition)])) (|> (representation registry) (the #resolver) (dictionary.value name))) - (def: .public (id name registry) + (def .public (id name registry) (-> Text Registry (Maybe ID)) (maybe#each product.left (find_definition name registry))) - (def: .public writer + (def .public writer (Writer Registry) (let [definition (is (Writer //category.Definition) (all binary.and @@ -148,7 +148,7 @@ (exception.report "Tag" (%.nat tag))) - (def: .public parser + (def .public parser (Parser Registry) (let [definition (is (Parser //category.Definition) (all <>.and diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux index ac6a22c49..075e12c77 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux @@ -25,23 +25,23 @@ [#name Symbol #version Version])) -(def: .public equivalence +(def .public equivalence (Equivalence Signature) (all product.equivalence symbol.equivalence nat.equivalence)) -(def: .public (description signature) +(def .public (description signature) (-> Signature Text) (format (%.symbol (the #name signature)) " " (version.format (the #version signature)))) -(def: .public writer +(def .public writer (Writer Signature) (all binary.and (binary.and binary.text binary.text) binary.nat)) -(def: .public parser +(def .public parser (Parser Signature) (all <>.and (<>.and <binary>.text <binary>.text) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux index 9ce35e1b5..937f87043 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/unit.lux @@ -22,21 +22,21 @@ [#module module.ID #artifact artifact.ID])) -(def: .public hash +(def .public hash (Hash ID) (all product.hash nat.hash nat.hash)) -(def: .public equivalence +(def .public equivalence (Equivalence ID) (at ..hash equivalence)) -(def: .public none +(def .public none (Set ID) (set.empty ..hash)) -(def: .public (format it) +(def .public (format it) (%.Format ID) (%.format (%.nat (the #module it)) "." diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache.lux b/stdlib/source/library/lux/tool/compiler/meta/cache.lux index 15cdef528..0ebd1e7d5 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache.lux @@ -15,18 +15,18 @@ [// ["[0]" version]]]) -(def: .public (path fs context) +(def .public (path fs context) (All (_ !) (-> (file.System !) Context file.Path)) (let [/ (at fs separator)] (format (the context.#target context) / (the context.#host context) / (version.format //.version)))) -(def: .public (enabled? fs context) +(def .public (enabled? fs context) (All (_ !) (-> (file.System !) Context (! Bit))) (at fs directory? (..path fs context))) -(def: .public (enable! ! fs context) +(def .public (enable! ! fs context) (All (_ !) (-> (Monad !) (file.System !) Context (! (Try Any)))) (do ! [? (..enabled? fs context)] diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/archive.lux index 4710ce851..8876e3e77 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/archive.lux @@ -13,12 +13,12 @@ [context (.only Context)] ["[0]" archive (.only Archive)]]]) -(def: .public (descriptor fs context) +(def .public (descriptor fs context) (All (_ !) (-> (file.System !) Context file.Path)) (%.format (//.path fs context) (at fs separator) "descriptor")) -(def: .public (cache! fs context it) +(def .public (cache! fs context it) (All (_ !) (-> (file.System !) Context Archive (! (Try Any)))) (at fs write (..descriptor fs context) (archive.export ///.version it))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux index 8494dba2c..69c131082 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/artifact.lux @@ -20,7 +20,7 @@ ["[0]" module] ["[0]" artifact]]]]) -(def: .public (path fs context @module @artifact) +(def .public (path fs context @module @artifact) (All (_ !) (-> (file.System !) Context module.ID artifact.ID file.Path)) (format (//module.path fs context @module) @@ -28,12 +28,12 @@ (%.nat @artifact) (the context.#artifact_extension context))) -(def: .public (cache fs context @module @artifact) +(def .public (cache fs context @module @artifact) (All (_ !) (-> (file.System !) Context module.ID artifact.ID (! (Try Binary)))) (at fs read (..path fs context @module @artifact))) -(def: .public (cache! fs context @module @artifact content) +(def .public (cache! fs context @module @artifact content) (All (_ !) (-> (file.System !) Context module.ID artifact.ID Binary (! (Try Any)))) (at fs write (..path fs context @module @artifact) content)) 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 373696de2..5640bdd7e 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 @@ -35,7 +35,7 @@ ["[0]" registry (.only Registry)] ["[0]" unit]]]]]]]) -(def: (path_references references) +(def (path_references references) (-> (-> Synthesis (List Constant)) (-> Path (List Constant))) (function (again path) @@ -75,7 +75,7 @@ {synthesis.#Then then} (references then)))) -(def: (references value) +(def (references value) (-> Synthesis (List Constant)) (case value {synthesis.#Simple value} @@ -162,7 +162,7 @@ (list#each references) list#conjoint))) -(def: .public (dependencies archive value) +(def .public (dependencies archive value) (All (_ anchor expression directive) (-> Archive Synthesis (Operation anchor expression directive (Set unit.ID)))) (let [! phase.monad] @@ -173,7 +173,7 @@ (monad.each ! (generation.remember archive)) (at ! each (set.of_list unit.hash))))) -(def: .public (path_dependencies archive value) +(def .public (path_dependencies archive value) (All (_ anchor expression directive) (-> Archive Path (Operation anchor expression directive (Set unit.ID)))) (let [! phase.monad] @@ -184,12 +184,12 @@ (monad.each ! (generation.remember archive)) (at ! each (set.of_list unit.hash))))) -(def: .public all +(def .public all (-> (List (Set unit.ID)) (Set unit.ID)) (list#mix set.union unit.none)) -(def: (immediate_dependencies archive) +(def (immediate_dependencies archive) (-> Archive [(List unit.ID) (Dictionary unit.ID (Set unit.ID))]) (|> archive @@ -213,7 +213,7 @@ [(list) (dictionary.empty unit.hash)]))) -(def: .public (necessary_dependencies archive) +(def .public (necessary_dependencies archive) (-> Archive (Set unit.ID)) (let [[mandatory immediate] (immediate_dependencies archive)] (loop (again [pending mandatory diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux index 5cad8e963..bdb09274d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux @@ -26,18 +26,18 @@ (type: .public Ancestry (Set descriptor.Module)) -(def: fresh +(def fresh Ancestry (set.empty text.hash)) (type: .public Graph (Dictionary descriptor.Module Ancestry)) -(def: empty +(def empty Graph (dictionary.empty text.hash)) -(def: .public modules +(def .public modules (-> Graph (List descriptor.Module)) dictionary.keys) @@ -46,13 +46,13 @@ [#module descriptor.Module #imports Ancestry])) -(def: .public graph +(def .public graph (-> (List Dependency) Graph) (list#mix (function (_ [module imports] graph) (dictionary.has module imports graph)) ..empty)) -(def: (ancestry archive) +(def (ancestry archive) (-> Archive Graph) (let [memo (is (Memo descriptor.Module Ancestry) (function (_ again module) @@ -74,7 +74,7 @@ ..empty (archive.archived archive)))) -(def: (dependency? ancestry target source) +(def (dependency? ancestry target source) (-> Graph descriptor.Module descriptor.Module Bit) (let [target_ancestry (|> ancestry (dictionary.value target) @@ -84,7 +84,7 @@ (type: .public (Order a) (List [descriptor.Module [module.ID (archive.Entry a)]])) -(def: .public (load_order key archive) +(def .public (load_order key archive) (All (_ a) (-> (Key a) Archive (Try (Order a)))) (let [ancestry (..ancestry archive)] (|> ancestry diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux index 59c7f5b50..ea6c1a660 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux @@ -32,17 +32,17 @@ "Module ID" (%.nat @module) "Error" error)) -(def: .public (path fs context @module) +(def .public (path fs context @module) (All (_ !) (-> (file.System !) Context module.ID file.Path)) (format (//.path fs context) (at fs separator) (%.nat @module))) -(def: .public (enabled? fs context @module) +(def .public (enabled? fs context @module) (All (_ !) (-> (file.System !) Context module.ID (! Bit))) (at fs directory? (..path fs context @module))) -(def: .public (enable! ! fs context @module) +(def .public (enable! ! fs context @module) (All (_ !) (-> (Monad !) (file.System !) Context module.ID (! (Try Any)))) (do ! [.let [path (..path fs context @module)] @@ -68,25 +68,25 @@ success success)))))))))) -(def: file +(def file file.Path "descriptor") -(def: .public (descriptor fs context @module) +(def .public (descriptor fs context @module) (All (_ !) (-> (file.System !) Context module.ID file.Path)) (format (..path fs context @module) (at fs separator) ..file)) -(def: .public (cache! fs context @module content) +(def .public (cache! fs context @module content) (All (_ !) (-> (file.System !) Context module.ID Binary (! (Try Any)))) (at fs write (..descriptor fs context @module) content)) -(def: .public (cache fs context @module) +(def .public (cache fs context @module) (All (_ !) (-> (file.System !) Context module.ID (! (Try Binary)))) (at fs read (..descriptor fs context @module))) -(def: .public (artifacts ! fs context @module) +(def .public (artifacts ! fs context @module) (All (_ !) (-> (Monad !) (file.System !) Context module.ID (! (Try (Dictionary Text Binary))))) (do [! (try.with !)] [files (at fs directory_files (..path fs context @module)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux index addb97821..d538861e6 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux @@ -38,7 +38,7 @@ (Dictionary descriptor.Module module.ID)) ... TODO: Make the monad parameterizable. -(def: .public (purge! fs context @module) +(def .public (purge! fs context @module) (-> (file.System Async) Context module.ID (Async (Try Any))) (do [! (try.with async.monad)] [.let [cache (//module.path fs context @module)] @@ -48,7 +48,7 @@ (at ! conjoint))] (at fs delete cache))) -(def: .public (valid? expected actual) +(def .public (valid? expected actual) (-> Descriptor Input Bit) (and (text#= (the descriptor.#name expected) (the ////.#module actual)) @@ -57,7 +57,7 @@ (n.= (the descriptor.#hash expected) (the ////.#hash actual)))) -(def: initial +(def initial (-> (List Cache) Purge) (|>> (list.all (function (_ [valid? module_name @module _]) (if valid? @@ -65,7 +65,7 @@ {.#Some [module_name @module]}))) (dictionary.of_list text.hash))) -(def: .public (purge caches load_order) +(def .public (purge caches load_order) (-> (List Cache) (dependency.Order Any) Purge) (list#mix (function (_ [module_name [@module entry]] purge) (let [purged? (is (Predicate descriptor.Module) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux index ea10958bd..76c30f475 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux @@ -71,7 +71,7 @@ {#Export Export})) (with_template [<name> <long> <type> <parser>] - [(def: <name> + [(def <name> (Parser <type>) (<cli>.named <long> <parser>))] @@ -84,7 +84,7 @@ [configuration_parser "--configuration" Configuration (<text>.then configuration.parser <cli>.any)] ) -(def: .public service +(def .public service (Parser Service) (let [compilation (is (Parser Compilation) (all <>.and @@ -106,7 +106,7 @@ ..target_parser)) ))) -(def: .public target +(def .public target (-> Service Target) (|>> (pipe.case (^.or {#Compilation [host_dependencies libraries compilers sources target module]} diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux index 40ee7afe4..e8c4196dd 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux @@ -23,7 +23,7 @@ [#definition Symbol #parameters (List Text)])) -(def: .public equivalence +(def .public equivalence (Equivalence Compiler) (all product.equivalence symbol.equivalence @@ -31,7 +31,7 @@ )) (with_template [<ascii> <name>] - [(def: <name> + [(def <name> Text (text.of_char (hex <ascii>)))] @@ -39,16 +39,16 @@ ["03" end] ) -(def: parameter +(def parameter (-> Text Text) (text.enclosed [..start ..end])) -(def: .public (format [[module short] parameters]) +(def .public (format [[module short] parameters]) (%.Format Compiler) (%.format (..parameter module) (..parameter short) (text.together (list#each ..parameter parameters)))) -(def: .public parser +(def .public parser (Parser Compiler) (let [parameter (is (Parser Text) (<| (<>.after (<text>.this ..start)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/context.lux b/stdlib/source/library/lux/tool/compiler/meta/context.lux index cfacb3fe9..a2126c773 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/context.lux @@ -16,7 +16,7 @@ #artifact_extension Extension])) (with_template [<name> <host> <host_module_extension> <artifact_extension>] - [(def: .public (<name> target) + [(def .public (<name> target) (-> Path Context) [#host <host> #host_module_extension <host_module_extension> diff --git a/stdlib/source/library/lux/tool/compiler/meta/export.lux b/stdlib/source/library/lux/tool/compiler/meta/export.lux index 2871ecf8e..aab3dae55 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/export.lux @@ -28,16 +28,16 @@ [world ["[0]" file]]]]) -(def: .public file +(def .public file "library.tar") -(def: .public mode +(def .public mode (all tar.and tar.read_by_owner tar.write_by_owner tar.read_by_group tar.write_by_group tar.read_by_other)) -(def: .public ownership +(def .public ownership tar.Ownership (let [commons (is tar.Owner [tar.#name tar.anonymous @@ -45,7 +45,7 @@ [tar.#user commons tar.#group commons])) -(def: .public (library fs sources) +(def .public (library fs sources) (-> (file.System Async) (List Source) (Async (Try tar.Tar))) (|> sources (io.listing fs) @@ -65,7 +65,7 @@ (try#each sequence.of_list))) try#conjoint)))) -(def: .public (export fs [sources target]) +(def .public (export fs [sources target]) (-> (file.System Async) Export (Async (Try Any))) (do [! (try.with async.monad)] [tar (|> sources diff --git a/stdlib/source/library/lux/tool/compiler/meta/import.lux b/stdlib/source/library/lux/tool/compiler/meta/import.lux index dec6dde3b..d653afbac 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/import.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/import.lux @@ -26,7 +26,7 @@ [world ["[0]" file]]]]) -(def: Action +(def Action (type (All (_ a) (Async (Try a))))) (exception: .public useless_tar_entry) @@ -40,7 +40,7 @@ (type: .public Import (Dictionary file.Path Binary)) -(def: (import_library system library import) +(def (import_library system library import) (-> (file.System Async) Library Import (Action Import)) (let [! async.monad] (|> library @@ -65,7 +65,7 @@ import))) (at ! conjoint))))))) -(def: .public (import system libraries) +(def .public (import system libraries) (-> (file.System Async) (List Library) (Action Import)) (monad.mix (is (Monad Action) (try.with async.monad)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io.lux b/stdlib/source/library/lux/tool/compiler/meta/io.lux index efbdb599d..374e71ef3 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io.lux @@ -12,10 +12,10 @@ (type: .public Code Text) -(def: .public (safe system) +(def .public (safe system) (All (_ m) (-> (System m) Text Text)) (text.replaced "/" (at system separator))) -(def: .public lux_context +(def .public lux_context Context "lux") 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 a192cf58a..2cef8ada4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -56,7 +56,7 @@ ["[0]" directive] ["[1]/[0]" program]]]]]]) -(def: (module_parser key parser) +(def (module_parser key parser) (All (_ document) (-> (Key document) (Parser document) (Parser (module.Module document)))) (all <>.and @@ -64,18 +64,18 @@ descriptor.parser (document.parser key parser))) -(def: (parser key parser) +(def (parser key parser) (All (_ document) (-> (Key document) (Parser document) (Parser [(module.Module document) Registry]))) (all <>.and (..module_parser key parser) registry.parser)) -(def: (fresh_analysis_state host configuration) +(def (fresh_analysis_state host configuration) (-> Target Configuration .Lux) (analysis.state (analysis.info version.latest host configuration))) -(def: (analysis_state host configuration archive) +(def (analysis_state host configuration archive) (-> Target Configuration Archive (Try .Lux)) (do [! try.monad] [modules (is (Try (List [descriptor.Module .Module])) @@ -101,14 +101,14 @@ Generators Directives]) -(def: empty_bundles +(def empty_bundles Bundles [(dictionary.empty text.hash) (dictionary.empty text.hash) (dictionary.empty text.hash) (dictionary.empty text.hash)]) -(def: (loaded_document extension host @module expected actual document) +(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) (Try [(Document .Module) Bundles Output]))) @@ -246,7 +246,7 @@ (in [(document.document $.key (has .#definitions definitions content)) bundles]))) -(def: (load_definitions fs context @module host_environment entry) +(def (load_definitions fs context @module host_environment entry) (All (_ expression directive) (-> (file.System Async) Context module.ID (generation.Host expression directive) (archive.Entry .Module) @@ -263,11 +263,11 @@ (has archive.#output output)) bundles]))) -(def: pseudo_module +(def pseudo_module Text "(Lux Caching System)") -(def: (cache_parser customs) +(def (cache_parser customs) (-> (List Custom) (Parser [(module.Module Any) Registry])) (case (for @.old (as (List (Custom Any Any Any)) customs) @@ -281,7 +281,7 @@ (cache_parser tail) ))) -(def: (valid_cache customs fs context import contexts [module_name @module]) +(def (valid_cache customs fs context import contexts [module_name @module]) (-> (List Custom) (file.System Async) Context Import (List //.Context) [descriptor.Module module.ID] (Async (Try Cache))) @@ -296,7 +296,7 @@ [input (//context.read fs ..pseudo_module import contexts (the context.#host_module_extension context) module_name)] (in [(cache/purge.valid? (the module.#descriptor module) input) <cache>])))))) -(def: (pre_loaded_caches customs fs context import contexts archive) +(def (pre_loaded_caches customs fs context import contexts archive) (-> (List Custom) (file.System Async) Context Import (List //.Context) Archive (Async (Try (List Cache)))) (do [! (try.with async.monad)] @@ -306,7 +306,7 @@ (monad.each ! (..valid_cache customs fs context import contexts)))] (in it))) -(def: (load_order archive pre_loaded_caches) +(def (load_order archive pre_loaded_caches) (-> Archive (List Cache) (Try (dependency.Order .Module))) (|> pre_loaded_caches @@ -321,7 +321,7 @@ (at try.monad each (dependency.load_order $.key)) (at try.monad conjoint))) -(def: (loaded_caches host_environment fs context purge load_order) +(def (loaded_caches host_environment fs context purge load_order) (All (_ expression directive) (-> (generation.Host expression directive) (file.System Async) Context Purge (dependency.Order .Module) @@ -343,7 +343,7 @@ <it>)))))))] (in it))) -(def: (load_every_reserved_module customs configuration host_environment fs context import contexts archive) +(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 (Async (Try [Archive .Lux Bundles])))) @@ -374,7 +374,7 @@ ..empty_bundles loaded_caches)]))))) -(def: .public (thaw customs configuration host_environment fs context import contexts) +(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) (Async (Try [Archive .Lux Bundles])))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 6845f5cce..e79b60e7b 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -43,17 +43,17 @@ (type: .public Extension Text) -(def: .public lux_extension +(def .public lux_extension Extension ".lux") -(def: .public (path fs context module) +(def .public (path fs context module) (All (_ m) (-> (file.System m) Context Module file.Path)) (|> module (//.safe fs) (format context (at fs separator)))) -(def: (find_source_file fs importer contexts module extension) +(def (find_source_file fs importer contexts module extension) (-> (file.System Async) Module (List Context) Module Extension (Async (Try file.Path))) (case contexts @@ -68,11 +68,11 @@ (in {try.#Success path}) (find_source_file fs importer contexts' module extension)))))) -(def: (full_host_extension partial_host_extension) +(def (full_host_extension partial_host_extension) (-> Extension Extension) (format partial_host_extension ..lux_extension)) -(def: (find_local_source_file fs importer import contexts partial_host_extension module) +(def (find_local_source_file fs importer import contexts partial_host_extension module) (-> (file.System Async) Module Import (List Context) Extension Module (Async (Try [file.Path Binary]))) ... Preference is explicitly being given to Lux files that have a host extension. @@ -92,7 +92,7 @@ (at fs read) (at ! each (|>> [path]))))))) -(def: (find_library_source_file importer import partial_host_extension module) +(def (find_library_source_file importer import partial_host_extension module) (-> Module Import Extension Module (Try [file.Path Binary])) (let [path (format module (..full_host_extension partial_host_extension))] (case (dictionary.value path import) @@ -108,7 +108,7 @@ {.#None} (exception.except ..cannot_find_module [importer module])))))) -(def: (find_any_source_file fs importer import contexts partial_host_extension module) +(def (find_any_source_file fs importer import contexts partial_host_extension module) (-> (file.System Async) Module Import (List Context) Extension Module (Async (Try [file.Path Binary]))) ... Preference is explicitly being given to Lux files that have a host extension. @@ -122,7 +122,7 @@ {try.#Failure _} (in (..find_library_source_file importer import partial_host_extension module))))) -(def: .public (read fs importer import contexts partial_host_extension module) +(def .public (read fs importer import contexts partial_host_extension module) (-> (file.System Async) Module Import (List Context) Extension Module (Async (Try Input))) (do (try.with async.monad) @@ -140,7 +140,7 @@ (type: .public Enumeration (Dictionary file.Path Binary)) -(def: (context_listing fs context directory enumeration) +(def (context_listing fs context directory enumeration) (-> (file.System Async) Context file.Path Enumeration (Async (Try Enumeration))) (do [! (try.with async.monad)] [enumeration (|> directory @@ -158,10 +158,10 @@ (at ! each (monad.mix ! (context_listing fs context) enumeration)) (at ! conjoint)))) -(def: Action +(def Action (type (All (_ a) (Async (Try a))))) -(def: (canonical fs context) +(def (canonical fs context) (-> (file.System Async) Context (Action Context)) (do (try.with async.monad) [subs (at fs sub_directories context)] @@ -171,7 +171,7 @@ (file.parent fs) (maybe.else context))))) -(def: .public (listing fs contexts) +(def .public (listing fs contexts) (-> (file.System Async) (List Context) (Action Enumeration)) (let [! (is (Monad Action) (try.with async.monad))] diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux index 1543e082f..759cb26a5 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux @@ -33,7 +33,7 @@ (type: .public Order (List [module.ID (List artifact.ID)])) -(def: .public order +(def .public order (-> (cache/module.Order Any) Order) (list#each (function (_ [module [module_id entry]]) (|> entry diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index 47fb81088..ddc522426 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -118,21 +118,21 @@ (new [java/io/InputStream]) (getNextJarEntry [] "try" "?" java/util/jar/JarEntry)) -(def: byte +(def byte 1) ... https://en.wikipedia.org/wiki/Kibibyte -(def: kibi_byte +(def kibi_byte (n.* 1,024 byte)) ... https://en.wikipedia.org/wiki/Mebibyte -(def: mebi_byte +(def mebi_byte (n.* 1,024 kibi_byte)) -(def: manifest_version +(def manifest_version "1.0") -(def: (manifest program) +(def (manifest program) (-> (Maybe unit.ID) java/util/jar/Manifest) (let [manifest (java/util/jar/Manifest::new) attrs (do_to (java/util/jar/Manifest::getMainAttributes manifest) @@ -153,7 +153,7 @@ attrs) manifest))) -(def: (write_class static module artifact custom content sink) +(def (write_class static module artifact custom content sink) (-> Context module.ID artifact.ID (Maybe Text) Binary java/util/jar/JarOutputStream (Try java/util/jar/JarOutputStream)) (let [class_path (|> custom @@ -169,7 +169,7 @@ (java/io/Flushable::flush) (java/util/zip/ZipOutputStream::closeEntry)))))) -(def: (write_module static necessary_dependencies [module output] sink) +(def (write_module static necessary_dependencies [module output] sink) (-> Context (Set unit.ID) [module.ID Output] java/util/jar/JarOutputStream (Try java/util/jar/JarOutputStream)) (let [! try.monad] @@ -181,7 +181,7 @@ sink (sequence.list output)))) -(def: (read_jar_entry_with_unknown_size input) +(def (read_jar_entry_with_unknown_size input) (-> java/util/jar/JarInputStream [Nat Binary]) (let [chunk (binary.empty ..mebi_byte) chunk_size (.int ..mebi_byte) @@ -197,7 +197,7 @@ (java/io/OutputStream::write chunk (ffi.as_int +0) (ffi.as_int bytes_read) buffer) (again (|> bytes_read .nat (n.+ so_far)))))))) -(def: (read_jar_entry_with_known_size expected_size input) +(def (read_jar_entry_with_known_size expected_size input) (-> Nat java/util/jar/JarInputStream [Nat Binary]) (let [buffer (binary.empty expected_size)] (loop (again [so_far 0]) @@ -210,7 +210,7 @@ [expected_size buffer] (again so_far')))))) -(def: (read_jar_entry entry input) +(def (read_jar_entry entry input) (-> java/util/jar/JarEntry java/util/jar/JarInputStream [Nat Binary]) (case (ffi.of_long (java/util/zip/ZipEntry::getSize entry)) -1 @@ -219,7 +219,7 @@ entry_size (..read_jar_entry_with_known_size (.nat entry_size) input))) -(def: (write_host_dependency jar [entries duplicates sink]) +(def (write_host_dependency jar [entries duplicates sink]) (-> Binary [(Set file.Path) (Set file.Path) java/util/jar/JarOutputStream] (Try [(Set file.Path) (Set file.Path) java/util/jar/JarOutputStream])) @@ -267,7 +267,7 @@ duplicates sink)))))))) -(def: .public (package static) +(def .public (package static) (-> Context Packager) (function (_ host_dependencies archive program) (do [! try.monad] 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 0937615cc..cc5938094 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux @@ -44,7 +44,7 @@ [language ["$" lux]]]]]) -(def: (bundle_module module module_id necessary_dependencies output) +(def (bundle_module module module_id necessary_dependencies output) (-> descriptor.Module module.ID (Set unit.ID) Output (Try (Maybe _.Statement))) (do [! try.monad] [] @@ -73,11 +73,11 @@ artifacts)] (in {.#Some bundle}))))) -(def: module_file +(def module_file (-> module.ID file.Path) (|>> %.nat (text.suffix ".rb"))) -(def: (write_module mapping necessary_dependencies [module [module_id entry]] sink) +(def (write_module mapping necessary_dependencies [module [module_id entry]] sink) (-> (Dictionary descriptor.Module module.ID) (Set unit.ID) [descriptor.Module [module.ID (archive.Entry .Module)]] (List [module.ID [Text Binary]]) @@ -98,21 +98,21 @@ (in (list.partial [module_id [(..module_file module_id) entry_content]] sink)))))) -(def: .public main_file +(def .public main_file "main.rb") -(def: module_id_mapping +(def module_id_mapping (-> (Order .Module) (Dictionary descriptor.Module module.ID)) (|>> (list#each (function (_ [module [module_id entry]]) [module module_id])) (dictionary.of_list text.hash))) -(def: included_modules +(def included_modules (All (_ a) (-> (List [module.ID a]) (Set module.ID))) (|>> (list#each product.left) (list#mix set.has (set.empty nat.hash)))) -(def: .public (package host_dependencies archive program) +(def .public (package host_dependencies archive program) Packager (do [! try.monad] [.let [necessary_dependencies (cache/artifact.necessary_dependencies archive)] 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 1fed07990..70f595ff4 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -48,13 +48,13 @@ (type: (Action ! a) (! (Try a))) -(def: (then pre post) +(def (then pre post) (-> _.Expression _.Expression _.Expression) (_.manual (format (_.code pre) text.new_line (_.code post)))) -(def: bundle_module +(def bundle_module (-> Output (Try _.Expression)) (|>> sequence.list (list#each product.right) @@ -71,11 +71,11 @@ (..then so_far))))) (is _.Expression (_.manual ""))))) -(def: module_file +(def module_file (-> archive.ID file.Path) (|>> %.nat (text.suffix ".scm"))) -(def: mode +(def mode tar.Mode (all tar.and tar.read_by_group @@ -85,16 +85,16 @@ tar.write_by_group tar.write_by_owner)) -(def: owner +(def owner tar.Owner [tar.#name tar.anonymous tar.#id tar.no_id]) -(def: ownership +(def ownership [tar.#user ..owner tar.#group ..owner]) -(def: (write_module now mapping [module [module_id [descriptor document output]]]) +(def (write_module now mapping [module [module_id [descriptor document output]]]) (-> Instant (Dictionary Module archive.ID) [Module [archive.ID [Descriptor (Document .Module) Output]]] (Try tar.Entry)) @@ -115,7 +115,7 @@ module_file (tar.path (..module_file module_id))] (in {tar.#Normal [module_file now ..mode ..ownership entry_content]}))) -(def: .public (package now) +(def .public (package now) (-> Instant Packager) (function (package host_dependencies archive program) (do [! try.monad] 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 382536417..d68c344e5 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -34,7 +34,7 @@ [language ["$" lux]]]]]) -(def: (write_module necessary_dependencies sequence [module_id output] so_far) +(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))) @@ -57,7 +57,7 @@ (sequence so_far))))) so_far))) -(def: .public (package header code sequence scope) +(def .public (package header code sequence scope) (All (_ directive) (-> directive (-> directive Text) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index 97eb3944c..c2aa03feb 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -23,10 +23,10 @@ (type: .public (Operation s o) (state.+State Try s o)) -(def: .public functor +(def .public functor (All (_ s) (Functor (Operation s))) (implementation - (def: (each f it) + (def (each f it) (function (_ state) (case (it state) {try.#Success [state' output]} @@ -35,16 +35,16 @@ {try.#Failure error} {try.#Failure error}))))) -(def: .public monad +(def .public monad (All (_ s) (Monad (Operation s))) (implementation - (def: functor ..functor) + (def functor ..functor) - (def: (in it) + (def (in it) (function (_ state) {try.#Success [state it]})) - (def: (conjoint it) + (def (conjoint it) (function (_ state) (case (it state) {try.#Success [state' it']} @@ -59,31 +59,31 @@ (type: .public Wrapper (All (_ s i o) (-> (Phase s i o) Any))) -(def: .public (result' state operation) +(def .public (result' state operation) (All (_ s o) (-> s (Operation s o) (Try [s o]))) (operation state)) -(def: .public (result state operation) +(def .public (result state operation) (All (_ s o) (-> s (Operation s o) (Try o))) (|> state operation (at try.monad each product.right))) -(def: .public state +(def .public state (All (_ s o) (Operation s s)) (function (_ state) {try.#Success [state state]})) -(def: .public (with state) +(def .public (with state) (All (_ s o) (-> s (Operation s Any))) (function (_ _) {try.#Success [state []]})) -(def: .public (sub [get set] operation) +(def .public (sub [get set] operation) (All (_ s s' o) (-> [(-> s s') (-> s' s s)] (Operation s' o) @@ -93,31 +93,31 @@ [[state' output] (operation (get state))] (in [(set state' state) output])))) -(def: .public failure +(def .public failure (-> Text Operation) (|>> {try.#Failure} (state.lifted try.monad))) -(def: .public (except exception parameters) +(def .public (except exception parameters) (All (_ e) (-> (Exception e) e Operation)) (..failure (exception.error exception parameters))) -(def: .public (lifted error) +(def .public (lifted error) (All (_ s a) (-> (Try a) (Operation s a))) (function (_ state) (try#each (|>> [state]) error))) -(def: .public assertion +(def .public assertion (template (assertion exception message test) [(if test (at ..monad in []) (..except exception message))])) -(def: .public identity +(def .public identity (All (_ s a) (Phase s a a)) (function (_ archive input state) {try.#Success [state input]})) -(def: .public (composite pre post) +(def .public (composite pre post) (All (_ s0 s1 i t o) (-> (Phase s0 i t) (Phase s1 t o) diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 78539332c..9701fbf11 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -27,10 +27,10 @@ {#Variable Variable} {#Constant Constant})) -(def: .public equivalence +(def .public equivalence (Equivalence Reference) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] (^.with_template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] @@ -41,13 +41,13 @@ _ false)))) -(def: .public hash +(def .public hash (Hash Reference) (implementation - (def: equivalence + (def equivalence ..equivalence) - (def: (hash value) + (def (hash value) (case value (^.with_template [<factor> <tag> <hash>] [{<tag> value} @@ -59,7 +59,7 @@ )))) (with_template [<name> <family> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(<| {<family>} {<tag>} @@ -70,7 +70,7 @@ ) (with_template [<name> <tag>] - [(def: .public <name> + [(def .public <name> (template (<name> content) [(<| {<tag>} content)]))] @@ -79,11 +79,11 @@ [constant ..#Constant] ) -(`` (def: .public self +(`` (def .public self (template (self) [(..variable (~~ (/variable.self)))]))) -(def: .public format +(def .public format (Format Reference) (|>> (pipe.case {#Variable variable} diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 8dea1368a..7dd3cdc4c 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -24,10 +24,10 @@ {#Local Register} {#Foreign Register})) -(def: .public equivalence +(def .public equivalence (Equivalence Variable) (implementation - (def: (= reference sample) + (def (= reference sample) (case [reference sample] (^.with_template [<tag>] [[{<tag> reference'} {<tag> sample'}] @@ -37,13 +37,13 @@ _ #0)))) -(def: .public hash +(def .public hash (Hash Variable) (implementation - (def: equivalence + (def equivalence ..equivalence) - (def: hash + (def hash (|>> (pipe.case (^.with_template [<factor> <tag>] [{<tag> register} @@ -53,11 +53,11 @@ ([2 #Local] [3 #Foreign])))))) -(def: .public self +(def .public self (template (self) [{..#Local 0}])) -(def: .public self? +(def .public self? (-> Variable Bit) (|>> (pipe.case (pattern (..self)) @@ -66,7 +66,7 @@ _ false))) -(def: .public format +(def .public format (Format Variable) (|>> (pipe.case {#Local local} diff --git a/stdlib/source/library/lux/tool/compiler/version.lux b/stdlib/source/library/lux/tool/compiler/version.lux index 67fe69189..1c8b12785 100644 --- a/stdlib/source/library/lux/tool/compiler/version.lux +++ b/stdlib/source/library/lux/tool/compiler/version.lux @@ -11,36 +11,36 @@ (type: .public Version Nat) -(def: range +(def range 100) -(def: level +(def level (n.% ..range)) -(def: next +(def next (n./ ..range)) -(def: .public patch +(def .public patch (-> Version Nat) (|>> ..level)) -(def: .public minor +(def .public minor (-> Version Nat) (|>> ..next ..level)) -(def: .public major +(def .public major (-> Version Nat) (|>> ..next ..next ..level)) -(def: separator ".") +(def separator ".") -(def: (padded value) +(def (padded value) (-> Nat Text) (if (n.< 10 value) (%.format "0" (%.nat value)) (%.nat value))) -(def: .public (format version) +(def .public (format version) (%.Format Version) (%.format (%.nat (..major version)) ..separator |