diff options
author | Eduardo Julian | 2021-08-08 17:56:15 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-08-08 17:56:15 -0400 |
commit | f621a133e6e0a516c0586270fea8eaffb4829d82 (patch) | |
tree | 399396ee2f6a10df10cea9b78c51c76679b70e59 /stdlib/source/library/lux/tool/compiler | |
parent | 17e7566be51df5e428a6b10e6469201a8a9468da (diff) |
No more #export magic syntax.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
192 files changed, 1175 insertions, 1158 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/arity.lux b/stdlib/source/library/lux/tool/compiler/arity.lux index 61e0ea625..e0a3c06aa 100644 --- a/stdlib/source/library/lux/tool/compiler/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/arity.lux @@ -5,10 +5,10 @@ [number ["n" nat]]]]]) -(type: #export Arity Nat) +(type: .public Arity Nat) (template [<comparison> <name>] - [(def: #export <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 898f0edd3..e2fd13208 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -51,7 +51,7 @@ ["." document]]]] ]) -(def: #export (state target module expander host_analysis host generate generation_bundle) +(def: .public (state target module expander host_analysis host generate generation_bundle) (All [anchor expression directive] (-> Target Module @@ -74,7 +74,7 @@ #///directive.generation {#///directive.state generation_state #///directive.phase generate}}])) -(def: #export (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 @@ -228,7 +228,7 @@ (-> .Module Aliases) (|>> (get@ #.module_aliases) (dictionary.of_list text.hash))) -(def: #export (compiler expander prelude write_directive) +(def: .public (compiler expander prelude write_directive) (All [anchor expression directive] (-> Expander 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 9e54b2522..dac25756c 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -64,10 +64,10 @@ (with_expansions [<type_vars> (as_is anchor expression directive) <Operation> (as_is ///generation.Operation <type_vars>)] - (type: #export Phase_Wrapper + (type: .public Phase_Wrapper (All [s i o] (-> (Phase s i o) Any))) - (type: #export (Platform <type_vars>) + (type: .public (Platform <type_vars>) {#&file_system (file.System Async) #host (///generation.Host expression directive) #phase (///generation.Phase <type_vars>) @@ -221,7 +221,7 @@ generators (dictionary.merged directives (host_directive_bundle phase_wrapper))]) - (def: #export (initialize static module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender + (def: .public (initialize static module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender import compilation_sources) (All [<type_vars>] (-> Static @@ -356,17 +356,17 @@ (or (dependence? import (get@ #depends_on) module) (dependence? module (get@ #depended_by) import)))) - (exception: #export (module_cannot_import_itself {module Module}) + (exception: .public (module_cannot_import_itself {module Module}) (exception.report ["Module" (%.text module)])) - (exception: #export (cannot_import_circular_dependency {importer Module} + (exception: .public (cannot_import_circular_dependency {importer Module} {importee Module}) (exception.report ["Importer" (%.text importer)] ["importee" (%.text importee)])) - (exception: #export (cannot_import_twice {importer Module} + (exception: .public (cannot_import_twice {importer Module} {duplicates (Set Module)}) (exception.report ["Importer" (%.text importer)] @@ -523,7 +523,7 @@ try.assumed product.left)) - (def: #export (compile import static expander platform compilation context) + (def: .public (compile import static expander platform compilation context) (All [<type_vars>] (-> Import Static Expander <Platform> Compilation <Context> <Return>)) (let [[compilation_sources compilation_host_dependencies compilation_libraries compilation_target compilation_module] compilation diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index f8ddeff8e..34e1bbbb7 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: #export writer +(def: .public writer (Writer .Module) (let [definition (: (Writer Definition) ($_ _.and _.bit _.type _.code _.any)) @@ -60,7 +60,7 @@ ## #module_state _.any))) -(def: #export parser +(def: .public parser (Parser .Module) (let [definition (: (Parser Definition) ($_ <>.and <b>.bit <b>.type <b>.code <b>.any)) @@ -100,7 +100,7 @@ ## #module_state (\ <>.monad in #.Cached)))) -(def: #export key +(def: .public key (Key .Module) (key.key {#signature.name (name_of ..compiler) #signature.version /version.version} 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 7dc985749..c79f514c3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -35,7 +35,7 @@ ["." reference (#+ Reference) ["." variable (#+ Register Variable)]]]]) -(type: #export #rec Primitive +(type: .public #rec Primitive #Unit (#Bit Bit) (#Nat Nat) @@ -44,15 +44,15 @@ (#Frac Frac) (#Text Text)) -(type: #export Tag +(type: .public Tag Nat) -(type: #export (Variant a) +(type: .public (Variant a) {#lefts Nat #right? Bit #value a}) -(def: #export (tag lefts right?) +(def: .public (tag lefts right?) (-> Nat Bit Nat) (if right? (inc lefts) @@ -64,35 +64,35 @@ (dec tag) tag)) -(def: #export (choice options pick) +(def: .public (choice options pick) (-> Nat Nat [Nat Bit]) (let [right? (n.= (dec options) pick)] [(..lefts pick right?) right?])) -(type: #export (Tuple a) +(type: .public (Tuple a) (List a)) -(type: #export (Composite a) +(type: .public (Composite a) (#Variant (Variant a)) (#Tuple (Tuple a))) -(type: #export #rec Pattern +(type: .public #rec Pattern (#Simple Primitive) (#Complex (Composite Pattern)) (#Bind Register)) -(type: #export (Branch' e) +(type: .public (Branch' e) {#when Pattern #then e}) -(type: #export (Match' e) +(type: .public (Match' e) [(Branch' e) (List (Branch' e))]) -(type: #export (Environment a) +(type: .public (Environment a) (List a)) -(type: #export #rec Analysis +(type: .public #rec Analysis (#Primitive Primitive) (#Structure (Composite Analysis)) (#Reference Reference) @@ -101,10 +101,10 @@ (#Apply Analysis Analysis) (#Extension (Extension Analysis))) -(type: #export Branch +(type: .public Branch (Branch' Analysis)) -(type: #export Match +(type: .public Match (Match' Analysis)) (implementation: primitive_equivalence @@ -128,7 +128,7 @@ _ false))) -(implementation: #export (composite_equivalence (^open "/\.")) +(implementation: .public (composite_equivalence (^open "/\.")) (All [a] (-> (Equivalence a) (Equivalence (Composite a)))) (def: (= reference sample) @@ -145,7 +145,7 @@ _ false))) -(implementation: #export (composite_hash super) +(implementation: .public (composite_hash super) (All [a] (-> (Hash a) (Hash (Composite a)))) (def: &equivalence @@ -188,7 +188,7 @@ (and (\ pattern_equivalence = reference_pattern sample_pattern) (\ equivalence = reference_body sample_body)))) -(implementation: #export equivalence +(implementation: .public equivalence (Equivalence Analysis) (def: (= reference sample) @@ -224,18 +224,18 @@ false))) (template [<name> <tag>] - [(template: #export (<name> content) - (<tag> content))] + [(template: .public (<name> content) + [(<tag> content)])] [control/case #..Case] ) -(template: #export (unit) - (#..Primitive #..Unit)) +(template: .public (unit) + [(#..Primitive #..Unit)]) (template [<name> <tag>] - [(template: #export (<name> value) - (#..Primitive (<tag> value)))] + [(template: .public (<name> value) + [(#..Primitive (<tag> value))])] [bit #..Bit] [nat #..Nat] @@ -245,29 +245,29 @@ [text #..Text] ) -(type: #export (Abstraction c) +(type: .public (Abstraction c) [(Environment c) Arity c]) -(type: #export (Application c) +(type: .public (Application c) [c (List c)]) (def: (last? size tag) (-> Nat Tag Bit) (n.= (dec size) tag)) -(template: #export (no_op value) - (|> 1 #variable.Local #reference.Variable #..Reference - (#..Function (list)) - (#..Apply value))) +(template: .public (no_op value) + [(|> 1 #variable.Local #reference.Variable #..Reference + (#..Function (list)) + (#..Apply value))]) -(def: #export (apply [abstraction inputs]) +(def: .public (apply [abstraction inputs]) (-> (Application Analysis) Analysis) (list\fold (function (_ input abstraction') (#Apply input abstraction')) abstraction inputs)) -(def: #export (application analysis) +(def: .public (application analysis) (-> Analysis (Application Analysis)) (loop [abstraction analysis inputs (list)] @@ -279,10 +279,10 @@ [abstraction inputs]))) (template [<name> <tag>] - [(template: #export (<name> content) - (.<| #..Reference - <tag> - content))] + [(template: .public (<name> content) + [(.<| #..Reference + <tag> + content)])] [variable #reference.Variable] [constant #reference.Constant] @@ -292,31 +292,31 @@ ) (template [<name> <tag>] - [(template: #export (<name> content) - (.<| #..Complex - <tag> - content))] + [(template: .public (<name> content) + [(.<| #..Complex + <tag> + content)])] [pattern/variant #..Variant] [pattern/tuple #..Tuple] ) (template [<name> <tag>] - [(template: #export (<name> content) - (.<| #..Structure - <tag> - content))] + [(template: .public (<name> content) + [(.<| #..Structure + <tag> + content)])] [variant #..Variant] [tuple #..Tuple] ) -(template: #export (pattern/unit) - (#..Simple #..Unit)) +(template: .public (pattern/unit) + [(#..Simple #..Unit)]) (template [<name> <tag>] - [(template: #export (<name> content) - (#..Simple (<tag> content)))] + [(template: .public (<name> content) + [(#..Simple (<tag> content))])] [pattern/bit #..Bit] [pattern/nat #..Nat] @@ -326,10 +326,10 @@ [pattern/text #..Text] ) -(template: #export (pattern/bind register) - (#..Bind register)) +(template: .public (pattern/bind register) + [(#..Bind register)]) -(def: #export (%analysis analysis) +(def: .public (%analysis analysis) (Format Analysis) (case analysis (#Primitive primitive) @@ -389,7 +389,7 @@ (text.enclosed ["(" ")"])))) (template [<special> <general>] - [(type: #export <special> + [(type: .public <special> (<general> .Lux Code Analysis))] [State+ extension.State] @@ -399,7 +399,7 @@ [Bundle extension.Bundle] ) -(def: #export (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 (get@ #.source state)] @@ -423,7 +423,7 @@ #.locals fresh_bindings #.captured fresh_bindings}) -(def: #export (with_scope action) +(def: .public (with_scope action) (All [a] (-> (Operation a) (Operation [Scope a]))) (function (_ [bundle state]) (case (action [bundle (update@ #.scopes (|>> (#.Item fresh_scope)) state)]) @@ -439,13 +439,13 @@ (#try.Failure error) (#try.Failure error)))) -(def: #export (with_current_module name) +(def: .public (with_current_module name) (All [a] (-> Text (Operation a) (Operation a))) (extension.localized (get@ #.current_module) (set@ #.current_module) (function.constant (#.Some name)))) -(def: #export (with_location location action) +(def: .public (with_location location action) (All [a] (-> Location (Operation a) (Operation a))) (if (text\= "" (product.left location)) action @@ -464,31 +464,31 @@ (format (%.location location) text.new_line error)) -(def: #export (failure error) +(def: .public (failure error) (-> Text Operation) (function (_ [bundle state]) (#try.Failure (locate_error (get@ #.location state) error)))) -(def: #export (except exception parameters) +(def: .public (except exception parameters) (All [e] (-> (Exception e) e Operation)) (..failure (exception.error exception parameters))) -(def: #export (assertion exception parameters condition) +(def: .public (assertion exception parameters condition) (All [e] (-> (Exception e) e Bit (Operation Any))) (if condition (\ phase.monad in []) (..except exception parameters))) -(def: #export (failure' error) +(def: .public (failure' error) (-> Text (phase.Operation Lux)) (function (_ state) (#try.Failure (locate_error (get@ #.location state) error)))) -(def: #export (except' exception parameters) +(def: .public (except' exception parameters) (All [e] (-> (Exception e) e (phase.Operation Lux))) (..failure' (exception.error exception parameters))) -(def: #export (with_stack exception message action) +(def: .public (with_stack exception message action) (All [e o] (-> (Exception e) e (Operation o) (Operation o))) (function (_ bundle,state) (case (exception.with exception message @@ -500,14 +500,14 @@ (let [[bundle state] bundle,state] (#try.Failure (locate_error (get@ #.location state) error)))))) -(def: #export (install state) +(def: .public (install state) (-> .Lux (Operation Any)) (function (_ [bundle _]) (#try.Success [[bundle state] []]))) (template [<name> <type> <field> <value>] - [(def: #export (<name> value) + [(def: .public (<name> value) (-> <type> (Operation Any)) (extension.update (set@ <field> <value>)))] @@ -516,11 +516,11 @@ [set_location Location #.location value] ) -(def: #export (location file) +(def: .public (location file) (-> Text Location) [file 1 0]) -(def: #export (source file code) +(def: .public (source file code) (-> Text Text Source) [(location file) 0 code]) @@ -534,13 +534,13 @@ #.var_counter 0 #.var_bindings (list)}) -(def: #export (info version host) +(def: .public (info version host) (-> Version Text Info) {#.target host #.version (%.nat version) #.mode #.Build}) -(def: #export (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/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index 0895955dc..b099446ea 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 @@ -26,7 +26,7 @@ [archive (#+ Archive) [descriptor (#+ Module)]]]]]]]]) -(type: #export Eval +(type: .public Eval (-> Archive Nat Type Code (Operation Any))) (def: (context [module_id artifact_id]) @@ -34,7 +34,7 @@ ## TODO: Find a better way that doesn't rely on clever tricks. [(n.- module_id 0) artifact_id]) -(def: #export (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/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux index 95f38c760..800d3091e 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 @@ -13,22 +13,22 @@ [///// ["." phase]]) -(exception: #export (expansion_failed {macro Name} {inputs (List Code)} {error Text}) +(exception: .public (expansion_failed {macro Name} {inputs (List Code)} {error Text}) (exception.report ["Macro" (%.name macro)] ["Inputs" (exception.listing %.code inputs)] ["Error" error])) -(exception: #export (must_have_single_expansion {macro Name} {inputs (List Code)} {outputs (List Code)}) +(exception: .public (must_have_single_expansion {macro Name} {inputs (List Code)} {outputs (List Code)}) (exception.report ["Macro" (%.name macro)] ["Inputs" (exception.listing %.code inputs)] ["Outputs" (exception.listing %.code outputs)])) -(type: #export Expander +(type: .public Expander (-> Macro (List Code) Lux (Try (Try [Lux (List Code)])))) -(def: #export (expand expander name macro inputs) +(def: .public (expand expander name macro inputs) (-> Expander Name Macro (List Code) (Meta (List Code))) (function (_ state) (do try.monad @@ -40,7 +40,7 @@ (#try.Failure error) ((meta.failure (exception.error ..expansion_failed [name inputs error])) state))))) -(def: #export (expand_one expander name macro inputs) +(def: .public (expand_one expander name macro inputs) (-> Expander Name Macro (List Code) (Meta Code)) (do meta.monad [expansion (expand expander name macro inputs)] 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 bb8a578bd..5383d2ae4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -20,11 +20,11 @@ [archive [descriptor (#+ Module)]]]]]) -(type: #export (Component state phase) +(type: .public (Component state phase) {#state state #phase phase}) -(type: #export (State anchor expression directive) +(type: .public (State anchor expression directive) {#analysis (Component analysis.State+ analysis.Phase) #synthesis (Component synthesis.State+ @@ -32,26 +32,26 @@ #generation (Component (generation.State+ anchor expression directive) (generation.Phase anchor expression directive))}) -(type: #export Import +(type: .public Import {#module Module #alias Text}) -(type: #export Requirements +(type: .public Requirements {#imports (List Import) #referrals (List Code)}) -(def: #export no_requirements +(def: .public no_requirements Requirements {#imports (list) #referrals (list)}) -(def: #export (merge_requirements left right) +(def: .public (merge_requirements left right) (-> Requirements Requirements Requirements) {#imports (list\compose (get@ #imports left) (get@ #imports right)) #referrals (list\compose (get@ #referrals left) (get@ #referrals right))}) (template [<special> <general>] - [(type: #export (<special> anchor expression directive) + [(type: .public (<special> anchor expression directive) (<general> (..State anchor expression directive) Code Requirements))] [State+ extension.State] @@ -62,7 +62,7 @@ ) (template [<name> <component> <phase>] - [(def: #export <name> + [(def: .public <name> (All [anchor expression directive] (Operation anchor expression directive <phase>)) (function (_ [bundle state]) @@ -74,7 +74,7 @@ ) (template [<name> <component> <operation>] - [(def: #export <name> + [(def: .public <name> (All [anchor expression directive output] (-> (<operation> output) (Operation anchor expression directive output))) @@ -87,7 +87,7 @@ [lift_generation #..generation (generation.Operation anchor expression directive)] ) -(def: #export (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 856a044fb..f32b12865 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -30,18 +30,18 @@ ["." descriptor (#+ Module)] ["." artifact]]]]]) -(type: #export Context +(type: .public Context [archive.ID artifact.ID]) -(type: #export (Buffer directive) +(type: .public (Buffer directive) (Row [artifact.ID (Maybe Text) directive])) -(exception: #export (cannot_interpret {error Text}) +(exception: .public (cannot_interpret {error Text}) (exception.report ["Error" error])) (template [<name>] - [(exception: #export (<name> {artifact_id artifact.ID}) + [(exception: .public (<name> {artifact_id artifact.ID}) (exception.report ["Artifact ID" (%.nat artifact_id)]))] @@ -49,7 +49,7 @@ [no_buffer_for_saving_code] ) -(interface: #export (Host expression directive) +(interface: .public (Host expression directive) (: (-> Context expression (Try Any)) evaluate!) (: (-> directive (Try Any)) @@ -64,7 +64,7 @@ (: (-> Context (Maybe Text) directive (Try Any)) re_load)) -(type: #export (State anchor expression directive) +(type: .public (State anchor expression directive) {#module Module #anchor (Maybe anchor) #host (Host expression directive) @@ -75,7 +75,7 @@ #log (Row Text)}) (template [<special> <general>] - [(type: #export (<special> anchor expression directive) + [(type: .public (<special> anchor expression directive) (<general> (State anchor expression directive) Synthesis expression))] [State+ extension.State] @@ -86,7 +86,7 @@ [Extender extension.Extender] ) -(def: #export (state host module) +(def: .public (state host module) (All [anchor expression directive] (-> (Host expression directive) Module @@ -100,14 +100,14 @@ #context #.None #log row.empty}) -(def: #export empty_buffer Buffer row.empty) +(def: .public empty_buffer Buffer row.empty) (template [<tag> <with_declaration> <with_type> <with_value> <set> <get> <get_type> <exception>] - [(exception: #export <exception>) + [(exception: .public <exception>) - (def: #export <with_declaration> + (def: .public <with_declaration> (All [anchor expression directive output] <with_type>) (function (_ body) (function (_ [bundle state]) @@ -119,7 +119,7 @@ (#try.Failure error) (#try.Failure error))))) - (def: #export <get> + (def: .public <get> (All [anchor expression directive] (Operation anchor expression directive <get_type>)) (function (_ (^@ stateE [bundle state])) @@ -130,7 +130,7 @@ #.None (exception.except <exception> [])))) - (def: #export (<set> value) + (def: .public (<set> value) (All [anchor expression directive] (-> <get_type> (Operation anchor expression directive Any))) (function (_ [bundle state]) @@ -152,20 +152,20 @@ set_buffer buffer (Buffer directive) no_active_buffer] ) -(def: #export get_registry +(def: .public get_registry (All [anchor expression directive] (Operation anchor expression directive artifact.Registry)) (function (_ (^@ stateE [bundle state])) (#try.Success [stateE (get@ #registry state)]))) -(def: #export (set_registry value) +(def: .public (set_registry value) (All [anchor expression directive] (-> artifact.Registry (Operation anchor expression directive Any))) (function (_ [bundle state]) (#try.Success [[bundle (set@ #registry value state)] []]))) -(def: #export next +(def: .public next (All [anchor expression directive] (Operation anchor expression directive Nat)) (do phase.monad @@ -173,22 +173,22 @@ _ (extension.update (update@ #counter inc))] (in count))) -(def: #export (gensym prefix) +(def: .public (gensym prefix) (All [anchor expression directive] (-> Text (Operation anchor expression directive Text))) (\ phase.monad map (|>> %.nat (format prefix)) ..next)) -(def: #export (enter_module module) +(def: .public (enter_module module) (All [anchor expression directive] (-> Module (Operation anchor expression directive Any))) (extension.update (set@ #module module))) -(def: #export module +(def: .public module (All [anchor expression directive] (Operation anchor expression directive Module)) (extension.read (get@ #module))) -(def: #export (evaluate! label code) +(def: .public (evaluate! label code) (All [anchor expression directive] (-> Context expression (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) @@ -199,7 +199,7 @@ (#try.Failure error) (exception.except ..cannot_interpret error)))) -(def: #export (execute! code) +(def: .public (execute! code) (All [anchor expression directive] (-> directive (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) @@ -210,7 +210,7 @@ (#try.Failure error) (exception.except ..cannot_interpret error)))) -(def: #export (define! context custom code) +(def: .public (define! context custom code) (All [anchor expression directive] (-> Context (Maybe Text) expression (Operation anchor expression directive [Text Any directive]))) (function (_ (^@ stateE [bundle state])) @@ -221,7 +221,7 @@ (#try.Failure error) (exception.except ..cannot_interpret error)))) -(def: #export (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} @@ -237,7 +237,7 @@ (phase.except ..no_buffer_for_saving_code [artifact_id])))) (template [<name> <artifact>] - [(def: #export (<name> name) + [(def: .public (<name> name) (All [anchor expression directive] (-> Text (Operation anchor expression directive artifact.ID))) (function (_ (^@ stateE [bundle state])) @@ -253,14 +253,14 @@ [learn_directive artifact.directive] ) -(exception: #export (unknown_definition {name Name} +(exception: .public (unknown_definition {name Name} {known_definitions (List Text)}) (exception.report ["Definition" (name.short name)] ["Module" (name.module name)] ["Known Definitions" (exception.listing function.identity known_definitions)])) -(def: #export (remember archive name) +(def: .public (remember archive name) (All [anchor expression directive] (-> Archive Name (Operation anchor expression directive Context))) (function (_ (^@ stateE [bundle state])) @@ -279,9 +279,9 @@ (#.Some id) (#try.Success [stateE [module_id id]])))))) -(exception: #export no_context) +(exception: .public no_context) -(def: #export (module_id module archive) +(def: .public (module_id module archive) (All [anchor expression directive] (-> Module Archive (Operation anchor expression directive archive.ID))) (function (_ (^@ stateE [bundle state])) @@ -289,7 +289,7 @@ [module_id (archive.id module archive)] (in [stateE module_id])))) -(def: #export (context archive) +(def: .public (context archive) (All [anchor expression directive] (-> Archive (Operation anchor expression directive Context))) (function (_ (^@ stateE [bundle state])) @@ -302,7 +302,7 @@ [module_id (archive.id (get@ #module state) archive)] (in [stateE [module_id id]]))))) -(def: #export (with_context id body) +(def: .public (with_context id body) (All [anchor expression directive a] (-> artifact.ID (Operation anchor expression directive a) @@ -313,7 +313,7 @@ (in [[bundle' (set@ #context (get@ #context state) state')] output])))) -(def: #export (with_new_context archive body) +(def: .public (with_new_context archive body) (All [anchor expression directive a] (-> Archive (Operation anchor expression directive a) (Operation anchor expression directive [Context a]))) @@ -328,7 +328,7 @@ [[module_id id] output]]))))) -(def: #export (log! message) +(def: .public (log! message) (All [anchor expression directive a] (-> Text (Operation anchor expression directive Any))) (function (_ [bundle state]) 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 faa4089a1..d760db44f 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 @@ -28,7 +28,7 @@ [meta [archive (#+ Archive)]]]]]]) -(exception: #export (unrecognized_syntax {code Code}) +(exception: .public (unrecognized_syntax {code Code}) (exception.report ["Code" (%.code code)])) ## TODO: Had to split the 'compile' function due to compilation issues @@ -132,7 +132,7 @@ _ (//.except ..unrecognized_syntax [location.dummy code']))) -(def: #export (phase expander) +(def: .public (phase expander) (-> Expander Phase) (function (compile 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 7f539ae4e..0d106fe5a 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 @@ -34,29 +34,29 @@ [/// ["#" phase]]]]]]) -(exception: #export (cannot_match_with_pattern {type Type} {pattern Code}) +(exception: .public (cannot_match_with_pattern {type Type} {pattern Code}) (exception.report ["Type" (%.type type)] ["Pattern" (%.code pattern)])) -(exception: #export (sum_has_no_case {case Nat} {type Type}) +(exception: .public (sum_has_no_case {case Nat} {type Type}) (exception.report ["Case" (%.nat case)] ["Type" (%.type type)])) -(exception: #export (not_a_pattern {code Code}) +(exception: .public (not_a_pattern {code Code}) (exception.report ["Code" (%.code code)])) -(exception: #export (cannot_simplify_for_pattern_matching {type Type}) +(exception: .public (cannot_simplify_for_pattern_matching {type Type}) (exception.report ["Type" (%.type type)])) -(exception: #export (non_exhaustive_pattern_matching {input Code} {branches (List [Code Code])} {coverage Coverage}) +(exception: .public (non_exhaustive_pattern_matching {input Code} {branches (List [Code Code])} {coverage Coverage}) (exception.report ["Input" (%.code input)] ["Branches" (%.code (code.record branches))] ["Coverage" (/coverage.%coverage coverage)])) -(exception: #export (cannot_have_empty_branches {message Text}) +(exception: .public (cannot_have_empty_branches {message Text}) message) (def: (re_quantify envs baseT) @@ -298,7 +298,7 @@ (/.except ..not_a_pattern pattern) )) -(def: #export (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/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index 91052853b..6b949ea29 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -24,7 +24,7 @@ [/// ["#" phase ("#\." monad)]]]]) -(exception: #export (invalid_tuple_pattern) +(exception: .public (invalid_tuple_pattern) "Tuple size must be >= 2") (def: cases @@ -47,7 +47,7 @@ ## The #Partial tag covers arbitrary partial coverages in a general ## way, while the other tags cover more specific cases for bits ## and variants. -(type: #export #rec Coverage +(type: .public #rec Coverage #Partial (#Bit Bit) (#Variant (Maybe Nat) (Dictionary Nat Coverage)) @@ -55,7 +55,7 @@ (#Alt Coverage Coverage) #Exhaustive) -(def: #export (exhaustive? coverage) +(def: .public (exhaustive? coverage) (-> Coverage Bit) (case coverage (#Exhaustive _) @@ -64,7 +64,7 @@ _ #0)) -(def: #export (%coverage value) +(def: .public (%coverage value) (Format Coverage) (case value #Partial @@ -94,7 +94,7 @@ #Exhaustive "#Exhaustive")) -(def: #export (determine pattern) +(def: .public (determine pattern) (-> Pattern (Operation Coverage)) (case pattern (^or (#/.Simple #/.Unit) @@ -165,7 +165,7 @@ ## always be a pattern prior to them that would match the input. ## Because of that, the presence of redundant patterns is assumed to ## be a bug, likely due to programmer carelessness. -(exception: #export (redundant_pattern {so_far Coverage} {addition Coverage}) +(exception: .public (redundant_pattern {so_far Coverage} {addition Coverage}) (exception.report ["Coverage so-far" (%coverage so_far)] ["Coverage addition" (%coverage addition)])) @@ -210,7 +210,7 @@ (open: "coverage/." ..equivalence) -(exception: #export (variants_do_not_match {addition_cases Nat} {so_far_cases Nat}) +(exception: .public (variants_do_not_match {addition_cases Nat} {so_far_cases Nat}) (exception.report ["So-far Cases" (%.nat so_far_cases)] ["Addition Cases" (%.nat addition_cases)])) @@ -219,7 +219,7 @@ ## necessary to merge them all to figure out if the entire ## pattern-matching expression is exhaustive and whether it contains ## redundant patterns. -(def: #export (merged addition so_far) +(def: .public (merged addition so_far) (-> Coverage Coverage (Try Coverage)) (case [addition so_far] [#Partial #Partial] 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 0ebfb304f..3797288ae 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 @@ -27,13 +27,13 @@ [reference (#+) [variable (#+)]]]]]]) -(exception: #export (cannot_analyse {expected Type} {function Text} {argument Text} {body Code}) +(exception: .public (cannot_analyse {expected Type} {function Text} {argument Text} {body Code}) (ex.report ["Type" (%.type expected)] ["Function" function] ["Argument" argument] ["Body" (%.code body)])) -(exception: #export (cannot_apply {functionT Type} {functionC Code} {arguments (List Code)}) +(exception: .public (cannot_apply {functionT Type} {functionC Code} {arguments (List Code)}) (ex.report ["Function type" (%.type functionT)] ["Function" (%.code functionC)] ["Arguments" (|> arguments @@ -42,7 +42,7 @@ (format (%.nat idx) " " (%.code argC)))) (text.join_with text.new_line))])) -(def: #export (function analyse function_name arg_name archive body) +(def: .public (function analyse function_name arg_name archive body) (-> Phase Text Text Phase) (do {! ///.monad} [functionT (///extension.lift meta.expected_type)] @@ -105,7 +105,7 @@ (/.failure "") ))))) -(def: #export (apply analyse argsC+ functionT functionA archive functionC) +(def: .public (apply analyse argsC+ functionT functionA archive functionC) (-> Phase (List Code) Type Analysis Phase) (<| (/.with_stack ..cannot_apply [functionT functionC argsC+]) (do ///.monad diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux index 8daf5242f..f7980c7ec 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -28,29 +28,29 @@ [meta [archive (#+ Archive)]]]]]]) -(exception: #export (variant_tag_out_of_bounds {size Nat} {tag Tag} {type Type}) +(exception: .public (variant_tag_out_of_bounds {size Nat} {tag Tag} {type Type}) (exception.report ["Tag" (%.nat tag)] ["Variant size" (%.int (.int size))] ["Variant type" (%.type type)])) -(exception: #export (cannot_infer {type Type} {args (List Code)}) +(exception: .public (cannot_infer {type Type} {args (List Code)}) (exception.report ["Type" (%.type type)] ["Arguments" (exception.listing %.code args)])) -(exception: #export (cannot_infer_argument {inferred Type} {argument Code}) +(exception: .public (cannot_infer_argument {inferred Type} {argument Code}) (exception.report ["Inferred Type" (%.type inferred)] ["Argument" (%.code argument)])) -(exception: #export (smaller_variant_than_expected {expected Nat} {actual Nat}) +(exception: .public (smaller_variant_than_expected {expected Nat} {actual Nat}) (exception.report ["Expected" (%.int (.int expected))] ["Actual" (%.int (.int actual))])) (template [<name>] - [(exception: #export (<name> {type Type}) + [(exception: .public (<name> {type Type}) (%.type type))] [not_a_variant_type] @@ -107,7 +107,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: #export (general archive analyse inferT args) +(def: .public (general archive analyse inferT args) (-> Archive Phase Type (List Code) (Operation [Type (List Analysis)])) (case args #.End @@ -234,12 +234,12 @@ _ (/.except ..not_a_record_type inferT))) -(def: #export (record inferT) +(def: .public (record inferT) (-> Type (Operation Type)) (record' (n.- 2 0) inferT inferT)) ## Turns a variant type into the kind of function type suitable for inference. -(def: #export (variant tag expected_size inferT) +(def: .public (variant tag expected_size inferT) (-> Nat Nat Type (Operation Type)) (loop [depth 0 currentT inferT] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux index b0d9920df..4bdb708bd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux @@ -22,19 +22,19 @@ [/// ["#" phase]]]]) -(type: #export Tag Text) +(type: .public Tag Text) -(exception: #export (unknown_module {module Text}) +(exception: .public (unknown_module {module Text}) (exception.report ["Module" module])) -(exception: #export (cannot_declare_tag_twice {module Text} {tag Text}) +(exception: .public (cannot_declare_tag_twice {module Text} {tag Text}) (exception.report ["Module" module] ["Tag" tag])) (template [<name>] - [(exception: #export (<name> {tags (List Text)} {owner Type}) + [(exception: .public (<name> {tags (List Text)} {owner Type}) (exception.report ["Tags" (text.join_with " " tags)] ["Type" (%.type owner)]))] @@ -43,7 +43,7 @@ [cannot_declare_tags_for_foreign_type] ) -(exception: #export (cannot_define_more_than_once {name Name} {already_existing Global}) +(exception: .public (cannot_define_more_than_once {name Name} {already_existing Global}) (exception.report ["Definition" (%.name name)] ["Original" (case already_existing @@ -53,7 +53,7 @@ (#.Definition definition) (format "definition " (%.name name)))])) -(exception: #export (can_only_change_state_of_active_module {module Text} {state Module_State}) +(exception: .public (can_only_change_state_of_active_module {module Text} {state Module_State}) (exception.report ["Module" module] ["Desired state" (case state @@ -61,13 +61,13 @@ #.Compiled "Compiled" #.Cached "Cached")])) -(exception: #export (cannot_set_module_annotations_more_than_once {module Text} {old Code} {new Code}) +(exception: .public (cannot_set_module_annotations_more_than_once {module Text} {old Code} {new Code}) (exception.report ["Module" module] ["Old annotations" (%.code old)] ["New annotations" (%.code new)])) -(def: #export (empty hash) +(def: .public (empty hash) (-> Nat Module) {#.module_hash hash #.module_aliases (list) @@ -78,7 +78,7 @@ #.module_annotations #.None #.module_state #.Active}) -(def: #export (set_annotations annotations) +(def: .public (set_annotations annotations) (-> Code (Operation Any)) (///extension.lift (do ///.monad @@ -95,7 +95,7 @@ (#.Some old) (/.except' cannot_set_module_annotations_more_than_once [self_name old annotations]))))) -(def: #export (import module) +(def: .public (import module) (-> Text (Operation Any)) (///extension.lift (do ///.monad @@ -110,7 +110,7 @@ state) []]))))) -(def: #export (alias alias module) +(def: .public (alias alias module) (-> Text Text (Operation Any)) (///extension.lift (do ///.monad @@ -122,7 +122,7 @@ state) []]))))) -(def: #export (exists? module) +(def: .public (exists? module) (-> Text (Operation Bit)) (///extension.lift (function (_ state) @@ -132,7 +132,7 @@ (case> (#.Some _) #1 #.None #0) [state] #try.Success)))) -(def: #export (define name definition) +(def: .public (define name definition) (-> Text Global (Operation Any)) (///extension.lift (do ///.monad @@ -153,7 +153,7 @@ (#.Some already_existing) ((/.except' ..cannot_define_more_than_once [[self_name name] already_existing]) state)))))) -(def: #export (create hash name) +(def: .public (create hash name) (-> Nat Text (Operation Any)) (///extension.lift (function (_ state) @@ -162,7 +162,7 @@ state) []])))) -(def: #export (with_module hash name action) +(def: .public (with_module hash name action) (All [a] (-> Nat Text (Operation a) (Operation [Module a]))) (do ///.monad [_ (create hash name) @@ -172,7 +172,7 @@ (in [module output]))) (template [<setter> <asker> <tag>] - [(def: #export (<setter> module_name) + [(def: .public (<setter> module_name) (-> Text (Operation Any)) (///extension.lift (function (_ state) @@ -192,7 +192,7 @@ #.None ((/.except' unknown_module module_name) state))))) - (def: #export (<asker> module_name) + (def: .public (<asker> module_name) (-> Text (Operation Bit)) (///extension.lift (function (_ state) @@ -243,7 +243,7 @@ tags)] (in []))) -(def: #export (declare_tags tags exported? type) +(def: .public (declare_tags tags exported? type) (-> (List Tag) Bit Type (Operation Any)) (do ///.monad [self_name (///extension.lift meta.current_module_name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux index 4840dca2a..2b82d55a4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/primitive.lux @@ -12,7 +12,7 @@ ["#" phase]]]]]) (template [<name> <type> <tag>] - [(def: #export (<name> value) + [(def: .public (<name> value) (-> <type> (Operation Analysis)) (do ///.monad [_ (//type.infer <type>)] @@ -26,7 +26,7 @@ [text .Text #/.Text] ) -(def: #export unit +(def: .public unit (Operation Analysis) (do ///.monad [_ (//type.infer .Any)] 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 25f478f04..92e43368e 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 @@ -20,12 +20,12 @@ ["#." reference] ["#" phase]]]]]) -(exception: #export (foreign_module_has_not_been_imported {current Text} {foreign Text}) +(exception: .public (foreign_module_has_not_been_imported {current Text} {foreign Text}) (exception.report ["Current" current] ["Foreign" foreign])) -(exception: #export (definition_has_not_been_exported {definition Name}) +(exception: .public (definition_has_not_been_exported {definition Name}) (exception.report ["Definition" (%.name definition)])) @@ -66,7 +66,7 @@ #.None (in #.None)))) -(def: #export (reference reference) +(def: .public (reference reference) (-> Name (Operation Analysis)) (case reference ["" simple_name] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux index 3ccfd3551..2906b9fe8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/scope.lux @@ -73,7 +73,7 @@ _ (..captured name scope))) -(def: #export (find name) +(def: .public (find name) (-> Text (Operation (Maybe [Type Variable]))) (///extension.lift (function (_ state) @@ -103,10 +103,10 @@ (#.Some [ref_type ref])])) ))))) -(exception: #export cannot_create_local_binding_without_a_scope) -(exception: #export invalid_scope_alteration) +(exception: .public cannot_create_local_binding_without_a_scope) +(exception: .public invalid_scope_alteration) -(def: #export (with_local [name type] action) +(def: .public (with_local [name type] action) (All [a] (-> [Text Type] (Operation a) (Operation a))) (function (_ [bundle state]) (case (get@ #.scopes state) @@ -155,7 +155,7 @@ #.locals init_locals #.captured init_captured}) -(def: #export (with_scope name action) +(def: .public (with_scope name action) (All [a] (-> Text (Operation a) (Operation a))) (function (_ [bundle state]) (let [parent_name (case (get@ #.scopes state) @@ -177,9 +177,9 @@ (#try.Failure error))) )) -(exception: #export cannot_get_next_reference_when_there_is_no_scope) +(exception: .public cannot_get_next_reference_when_there_is_no_scope) -(def: #export next_local +(def: .public next_local (Operation Register) (///extension.lift (function (_ state) @@ -199,7 +199,7 @@ (#.Captured register) (#variable.Foreign register))) -(def: #export (environment scope) +(def: .public (environment scope) (-> Scope (List Variable)) (|> scope (get@ [#.captured #.mappings]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 5e3717c5b..50afd0eed 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -36,13 +36,13 @@ [meta [archive (#+ Archive)]]]]]]) -(exception: #export (invalid_variant_type {type Type} {tag Tag} {code Code}) +(exception: .public (invalid_variant_type {type Type} {tag Tag} {code Code}) (ex.report ["Type" (%.type type)] ["Tag" (%.nat tag)] ["Expression" (%.code code)])) (template [<name>] - [(exception: #export (<name> {type Type} {members (List Code)}) + [(exception: .public (<name> {type Type} {members (List Code)}) (ex.report ["Type" (%.type type)] ["Expression" (%.code (` [(~+ members)]))]))] @@ -50,11 +50,11 @@ [cannot_analyse_tuple] ) -(exception: #export (not_a_quantified_type {type Type}) +(exception: .public (not_a_quantified_type {type Type}) (%.type type)) (template [<name>] - [(exception: #export (<name> {type Type} {tag Tag} {code Code}) + [(exception: .public (<name> {type Type} {tag Tag} {code Code}) (ex.report ["Type" (%.type type)] ["Tag" (%.nat tag)] ["Expression" (%.code code)]))] @@ -63,12 +63,12 @@ [cannot_infer_numeric_tag] ) -(exception: #export (record_keys_must_be_tags {key Code} {record (List [Code Code])}) +(exception: .public (record_keys_must_be_tags {key Code} {record (List [Code Code])}) (ex.report ["Key" (%.code key)] ["Record" (%.code (code.record record))])) (template [<name>] - [(exception: #export (<name> {key Name} {record (List [Name Code])}) + [(exception: .public (<name> {key Name} {record (List [Name Code])}) (ex.report ["Tag" (%.code (code.tag key))] ["Record" (%.code (code.record (list\map (function (_ [keyI valC]) [(code.tag keyI) valC]) @@ -77,11 +77,11 @@ [cannot_repeat_tag] ) -(exception: #export (tag_does_not_belong_to_record {key Name} {type Type}) +(exception: .public (tag_does_not_belong_to_record {key Name} {type Type}) (ex.report ["Tag" (%.code (code.tag key))] ["Type" (%.type type)])) -(exception: #export (record_size_mismatch {expected Nat} {actual Nat} {type Type} {record (List [Name Code])}) +(exception: .public (record_size_mismatch {expected Nat} {actual Nat} {type Type} {record (List [Name Code])}) (ex.report ["Expected" (%.nat expected)] ["Actual" (%.nat actual)] ["Type" (%.type type)] @@ -90,7 +90,7 @@ [(code.tag keyI) valueC])) code.record))])) -(def: #export (sum analyse lefts right? archive) +(def: .public (sum analyse lefts right? archive) (-> Phase Nat Bit Phase) (let [tag (/.tag lefts right?)] (function (recur valueC) @@ -192,7 +192,7 @@ (/.except ..cannot_analyse_tuple [expectedT members]))))] (in (/.tuple membersA+)))) -(def: #export (product archive analyse membersC) +(def: .public (product archive analyse membersC) (-> Archive Phase (List Code) (Operation Analysis)) (do {! ///.monad} [expectedT (///extension.lift meta.expected_type)] @@ -259,7 +259,7 @@ (/.except ..invalid_tuple_type [expectedT membersC]) )))) -(def: #export (tagged_sum analyse tag archive valueC) +(def: .public (tagged_sum analyse tag archive valueC) (-> Phase Name Phase) (do {! ///.monad} [tag (///extension.lift (meta.normal tag)) @@ -281,7 +281,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: #export (normal record) +(def: .public (normal record) (-> (List [Code Code]) (Operation (List [Name Code]))) (monad.map ///.monad (function (_ [key val]) @@ -298,7 +298,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: #export (order record) +(def: .public (order record) (-> (List [Name Code]) (Operation [(List Code) Type])) (case record ## empty_record = empty_tuple = unit = [] @@ -336,7 +336,7 @@ (in [ordered_tuple recordT])) )) -(def: #export (record archive analyse members) +(def: .public (record archive analyse members) (-> Archive Phase (List [Code Code]) (Operation Analysis)) (case members (^ (list)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux index f530c80ae..374663c95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/type.lux @@ -16,12 +16,12 @@ [/// ["#" phase]]]]) -(def: #export (with_type expected) +(def: .public (with_type expected) (All [a] (-> Type (Operation a) (Operation a))) (///extension.localized (get@ #.expected) (set@ #.expected) (function.constant (#.Some expected)))) -(def: #export (with_env action) +(def: .public (with_env action) (All [a] (-> (Check a) (Operation a))) (function (_ (^@ stateE [bundle state])) (case (action (get@ #.type_context state)) @@ -32,19 +32,19 @@ (#try.Failure error) ((/.failure error) stateE)))) -(def: #export with_fresh_env +(def: .public with_fresh_env (All [a] (-> (Operation a) (Operation a))) (///extension.localized (get@ #.type_context) (set@ #.type_context) (function.constant check.fresh_context))) -(def: #export (infer actualT) +(def: .public (infer actualT) (-> Type (Operation Any)) (do ///.monad [expectedT (///extension.lift meta.expected_type)] (with_env (check.check expectedT actualT)))) -(def: #export (with_inference action) +(def: .public (with_inference action) (All [a] (-> (Operation a) (Operation [Type a]))) (do ///.monad [[_ varT] (..with_env 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 ef7cffba4..8bb5d475f 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 @@ -24,20 +24,20 @@ [reference (#+) [variable (#+)]]]]]) -(exception: #export (not_a_directive {code Code}) +(exception: .public (not_a_directive {code Code}) (exception.report ["Directive" (%.code code)])) -(exception: #export (invalid_macro_call {code Code}) +(exception: .public (invalid_macro_call {code Code}) (exception.report ["Code" (%.code code)])) -(exception: #export (macro_was_not_found {name Name}) +(exception: .public (macro_was_not_found {name Name}) (exception.report ["Name" (%.name name)])) (with_expansions [<lux_def_module> (as_is [|form_location| (#.Form (list& [|text_location| (#.Text "lux def module")] annotations))])] - (def: #export (phase expander) + (def: .public (phase expander) (-> Expander Phase) (let [analyze (//analysis.phase expander)] (function (recur 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 60f625250..0620b8c01 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 @@ -21,61 +21,61 @@ [meta [archive (#+ Archive)]]]) -(type: #export Name +(type: .public Name Text) -(type: #export (Extension a) +(type: .public (Extension a) [Name (List a)]) -(def: #export equivalence +(def: .public equivalence (All [a] (-> (Equivalence a) (Equivalence (Extension a)))) (|>> list.equivalence (product.equivalence text.equivalence))) -(def: #export hash +(def: .public hash (All [a] (-> (Hash a) (Hash (Extension a)))) (|>> list.hash (product.hash text.hash))) (with_expansions [<Bundle> (as_is (Dictionary Name (Handler s i o)))] - (type: #export (Handler s i o) + (type: .public (Handler s i o) (-> Name (//.Phase [<Bundle> s] i o) (//.Phase [<Bundle> s] (List i) o))) - (type: #export (Bundle s i o) + (type: .public (Bundle s i o) <Bundle>)) -(def: #export empty +(def: .public empty Bundle (dictionary.empty text.hash)) -(type: #export (State s i o) +(type: .public (State s i o) {#bundle (Bundle s i o) #state s}) -(type: #export (Operation s i o v) +(type: .public (Operation s i o v) (//.Operation (State s i o) v)) -(type: #export (Phase s i o) +(type: .public (Phase s i o) (//.Phase (State s i o) i o)) -(exception: #export (cannot_overwrite {name Name}) +(exception: .public (cannot_overwrite {name Name}) (exception.report ["Extension" (%.text name)])) -(exception: #export (incorrect_arity {name Name} {arity Nat} {args Nat}) +(exception: .public (incorrect_arity {name Name} {arity Nat} {args Nat}) (exception.report ["Extension" (%.text name)] ["Expected" (%.nat arity)] ["Actual" (%.nat args)])) -(exception: #export [a] (invalid_syntax {name Name} {%format (Format a)} {inputs (List a)}) +(exception: .public [a] (invalid_syntax {name Name} {%format (Format a)} {inputs (List a)}) (exception.report ["Extension" (%.text name)] ["Inputs" (exception.listing %format inputs)])) -(exception: #export [s i o] (unknown {name Name} {bundle (Bundle s i o)}) +(exception: .public [s i o] (unknown {name Name} {bundle (Bundle s i o)}) (exception.report ["Extension" (%.text name)] ["Available" (|> bundle @@ -83,10 +83,10 @@ (list.sort text\<) (exception.listing %.text))])) -(type: #export (Extender s i o) +(type: .public (Extender s i o) (-> Any (Handler s i o))) -(def: #export (install extender name handler) +(def: .public (install extender name handler) (All [s i o] (-> (Extender s i o) Text (Handler s i o) (Operation s i o Any))) (function (_ [bundle state]) @@ -98,7 +98,7 @@ _ (exception.except ..cannot_overwrite name)))) -(def: #export (with extender extensions) +(def: .public (with extender extensions) (All [s i o] (-> Extender (Bundle s i o) (Operation s i o Any))) (|> extensions @@ -108,7 +108,7 @@ (..install extender extension handle)) []))) -(def: #export (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 (_ (^@ stateE [bundle state])) @@ -120,7 +120,7 @@ #.None (exception.except ..unknown [name bundle])))) -(def: #export (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)))) @@ -134,7 +134,7 @@ (#try.Failure error) (#try.Failure error)))))) -(def: #export (temporary transform) +(def: .public (temporary transform) (All [s i o v] (-> (-> s s) (-> (Operation s i o v) (Operation s i o v)))) @@ -147,24 +147,24 @@ (#try.Failure error) (#try.Failure error))))) -(def: #export (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: #export (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: #export (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: #export (lift action) +(def: .public (lift action) (All [s i o v] (-> (//.Operation s v) (//.Operation [(Bundle s i o) s] v))) 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 0def3e75d..096b659a2 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 @@ ["." / #_ ["#." lux]]) -(def: #export (bundle eval host_specific) +(def: .public (bundle eval host_specific) (-> Eval Bundle Bundle) (dictionary.merged 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 348124448..ea770d3a9 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 @@ [/// ["." phase]]]]]]) -(def: #export 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 a0c430e81..b085da3c0 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 @@ -204,7 +204,7 @@ (in (#analysis.Extension extension (list (analysis.nat arity) abstractionA)))))])) -(def: #export 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 87dca360f..b98b2732a 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 @@ -115,7 +115,7 @@ (getDeclaredAnnotations [] [java/lang/annotation/Annotation])]) (template [<name>] - [(exception: #export (<name> {class External} {field Text}) + [(exception: .public (<name> {class External} {field Text}) (exception.report ["Class" (%.text class)] ["Field" (%.text field)]))] @@ -124,13 +124,13 @@ [deprecated_field] ) -(exception: #export (deprecated_method {class External} {method Text} {type .Type}) +(exception: .public (deprecated_method {class External} {method Text} {type .Type}) (exception.report ["Class" (%.text class)] ["Method" (%.text method)] ["Type" (%.type type)])) -(exception: #export (deprecated_class {class External}) +(exception: .public (deprecated_class {class External}) (exception.report ["Class" (%.text class)])) @@ -156,7 +156,7 @@ "java.lang.Object") (def: inheritance_relationship_type_name "_jvm_inheritance") -(def: #export (inheritance_relationship_type class super_class super_interfaces) +(def: .public (inheritance_relationship_type class super_class super_interfaces) (-> .Type .Type (List .Type) .Type) (#.Primitive ..inheritance_relationship_type_name (list& class super_class super_interfaces))) @@ -164,7 +164,7 @@ ## TODO: Get rid of this template block and use the definition in ## lux/ffi.jvm.lux ASAP (template [<name> <class>] - [(def: #export <name> .Type (#.Primitive <class> #.End))] + [(def: .public <name> .Type (#.Primitive <class> #.End))] ## Boxes [Boolean box.boolean] @@ -202,7 +202,7 @@ #exceptions (List .Type)}) (template [<name>] - [(exception: #export (<name> {type .Type}) + [(exception: .public (<name> {type .Type}) (exception.report ["Type" (%.type type)]))] @@ -213,7 +213,7 @@ ) (template [<name>] - [(exception: #export (<name> {class External}) + [(exception: .public (<name> {class External}) (exception.report ["Class/type" (%.text class)]))] @@ -223,7 +223,7 @@ ) (template [<name>] - [(exception: #export (<name> {class External} + [(exception: .public (<name> {class External} {method Text} {inputsJT (List (Type Value))} {hints (List Method_Signature)}) @@ -237,14 +237,14 @@ [too_many_candidates] ) -(exception: #export (cannot_cast {from .Type} {to .Type} {value Code}) +(exception: .public (cannot_cast {from .Type} {to .Type} {value Code}) (exception.report ["From" (%.type from)] ["To" (%.type to)] ["Value" (%.code value)])) (template [<name>] - [(exception: #export (<name> {message Text}) + [(exception: .public (<name> {message Text}) message)] [primitives_cannot_have_type_parameters] @@ -333,7 +333,7 @@ (///bundle.install "<" (//lux.binary ..char ..char Bit)) ))) -(def: #export 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]] @@ -843,7 +843,7 @@ (/////analysis.except cannot_possibly_be_an_instance (format sub_class " !<= " object_class)))))])) (template [<name> <category> <parser>] - [(def: #export (<name> mapping typeJ) + [(def: .public (<name> mapping typeJ) (-> Mapping (Type <category>) (Operation .Type)) (case (|> typeJ ..signature (<text>.run (<parser> mapping))) (#try.Success check) @@ -1343,7 +1343,7 @@ (/////analysis.except ..too_many_candidates [class_name ..constructor_method inputsJT candidates])))) (template [<name> <category> <parser>] - [(def: #export <name> + [(def: .public <name> (Parser (Type <category>)) (<text>.then <parser> <code>.text))] @@ -1494,21 +1494,21 @@ ))) ))) -(type: #export (Annotation_Parameter a) +(type: .public (Annotation_Parameter a) [Text a]) (def: annotation_parameter (Parser (Annotation_Parameter Code)) (<code>.tuple (<>.and <code>.text <code>.any))) -(type: #export (Annotation a) +(type: .public (Annotation a) [Text (List (Annotation_Parameter a))]) -(def: #export annotation +(def: .public annotation (Parser (Annotation Code)) (<code>.form (<>.and <code>.text (<>.some ..annotation_parameter)))) -(def: #export argument +(def: .public argument (Parser Argument) (<code>.tuple (<>.and <code>.text ..type))) @@ -1587,7 +1587,7 @@ ) (template [<name>] - [(exception: #export (<name> {methods (List [Text (Type Method)])}) + [(exception: .public (<name> {methods (List [Text (Type Method)])}) (exception.report ["Methods" (exception.listing (function (_ [name type]) @@ -1598,21 +1598,21 @@ [invalid_overriden_methods] ) -(type: #export Visibility +(type: .public Visibility #Public #Private #Protected #Default) -(type: #export Finality Bit) -(type: #export Strictness Bit) +(type: .public Finality Bit) +(type: .public Strictness Bit) -(def: #export public_tag "public") -(def: #export private_tag "private") -(def: #export protected_tag "protected") -(def: #export default_tag "default") +(def: .public public_tag "public") +(def: .public private_tag "private") +(def: .public protected_tag "protected") +(def: .public default_tag "default") -(def: #export visibility +(def: .public visibility (Parser Visibility) ($_ <>.or (<code>.text! ..public_tag) @@ -1620,7 +1620,7 @@ (<code>.text! ..protected_tag) (<code>.text! ..default_tag))) -(def: #export (visibility_analysis visibility) +(def: .public (visibility_analysis visibility) (-> Visibility Analysis) (/////analysis.text (case visibility #Public ..public_tag @@ -1628,7 +1628,7 @@ #Protected ..protected_tag #Default ..default_tag))) -(type: #export (Constructor a) +(type: .public (Constructor a) [Visibility Strictness (List (Annotation a)) @@ -1639,9 +1639,9 @@ (List (Typed a)) a]) -(def: #export constructor_tag "init") +(def: .public constructor_tag "init") -(def: #export constructor_definition +(def: .public constructor_definition (Parser (Constructor Code)) (<| <code>.form (<>.after (<code>.text! ..constructor_tag)) @@ -1656,7 +1656,7 @@ (<code>.tuple (<>.some ..input)) <code>.any))) -(def: #export (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 @@ -1705,7 +1705,7 @@ (/////analysis.tuple (list bodyA))) )))))) -(type: #export (Virtual_Method a) +(type: .public (Virtual_Method a) [Text Visibility Finality @@ -1720,7 +1720,7 @@ (def: virtual_tag "virtual") -(def: #export virtual_method_definition +(def: .public virtual_method_definition (Parser (Virtual_Method Code)) (<| <code>.form (<>.after (<code>.text! ..virtual_tag)) @@ -1737,7 +1737,7 @@ (<code>.tuple (<>.some ..class)) <code>.any))) -(def: #export (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 @@ -1783,7 +1783,7 @@ (/////analysis.tuple (list bodyA))) )))))) -(type: #export (Static_Method a) +(type: .public (Static_Method a) [Text Visibility Strictness @@ -1794,9 +1794,9 @@ (Type Return) a]) -(def: #export static_tag "static") +(def: .public static_tag "static") -(def: #export static_method_definition +(def: .public static_method_definition (Parser (Static_Method Code)) (<| <code>.form (<>.after (<code>.text! ..static_tag)) @@ -1811,7 +1811,7 @@ ..return <code>.any))) -(def: #export (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 exceptions @@ -1855,7 +1855,7 @@ (/////analysis.tuple (list bodyA))) )))))) -(type: #export (Overriden_Method a) +(type: .public (Overriden_Method a) [(Type Class) Text Bit @@ -1867,9 +1867,9 @@ (List (Type Class)) a]) -(def: #export overriden_tag "override") +(def: .public overriden_tag "override") -(def: #export overriden_method_definition +(def: .public overriden_method_definition (Parser (Overriden_Method Code)) (<| <code>.form (<>.after (<code>.text! ..overriden_tag)) @@ -1886,12 +1886,12 @@ <code>.any ))) -(exception: #export (unknown_super {name Text} {supers (List (Type Class))}) +(exception: .public (unknown_super {name Text} {supers (List (Type Class))}) (exception.report ["Name" (%.text name)] ["Available" (exception.listing (|>> jvm_parser.read_class product.left) supers)])) -(exception: #export (mismatched_super_parameters {name Text} {expected Nat} {actual Nat}) +(exception: .public (mismatched_super_parameters {name Text} {expected Nat} {actual Nat}) (exception.report ["Name" (%.text name)] ["Expected" (%.nat expected)] @@ -1923,7 +1923,7 @@ #.None (phase.lift (exception.except ..unknown_super [parent_name supers]))))) -(def: #export (with_fresh_type_vars vars mapping) +(def: .public (with_fresh_type_vars vars mapping) (-> (List (Type Var)) Mapping (Operation Mapping)) (do {! phase.monad} [pairings (monad.map ! (function (_ var) @@ -1937,7 +1937,7 @@ mapping pairings)))) -(def: #export (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)] @@ -1946,7 +1946,7 @@ mapping override_mapping)))) -(def: #export (hide_method_body arity bodyA) +(def: .public (hide_method_body arity bodyA) (-> Nat Analysis Analysis) (<| /////analysis.tuple (list (/////analysis.unit)) @@ -1975,7 +1975,7 @@ bodyA} (list)])))) -(def: #export (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 @@ -2023,10 +2023,10 @@ (..hide_method_body (list.size arguments) bodyA)) )))))) -(type: #export (Method_Definition a) +(type: .public (Method_Definition a) (#Overriden_Method (Overriden_Method a))) -(def: #export parameter_types +(def: .public parameter_types (-> (List (Type Var)) (Check (List [(Type Var) .Type]))) (monad.map check.monad (function (_ parameterJ) @@ -2048,7 +2048,7 @@ not)) sub_set)) -(exception: #export (class_parameter_mismatch {expected (List Text)} +(exception: .public (class_parameter_mismatch {expected (List Text)} {actual (List (Type Parameter))}) (exception.report ["Expected (amount)" (%.nat (list.size expected))] @@ -2083,7 +2083,7 @@ local (format "anonymous-class" (%.nat id))] (format global ..jvm_package_separator local))) -(def: #export (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.lift (all_abstract_methods class_loader supers)) @@ -2169,7 +2169,7 @@ (///bundle.install "anonymous" (class::anonymous class_loader)) ))) -(def: #export (bundle class_loader) +(def: .public (bundle class_loader) (-> java/lang/ClassLoader 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 50c8dfe2a..2fe863c2a 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 @@ -235,7 +235,7 @@ (in (#analysis.Extension extension (list (analysis.nat arity) abstractionA)))))])) -(def: #export 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 470078b0f..b3f48d4ce 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 @@ -34,7 +34,7 @@ [meta [archive (#+ Archive)]]]]]]) -(def: #export (custom [syntax handler]) +(def: .public (custom [syntax handler]) (All [s] (-> [(Parser s) (-> Text Phase Archive s (Operation Analysis))] @@ -63,25 +63,25 @@ (in (#////analysis.Extension extension_name argsA))) (////analysis.except ///.incorrect_arity [extension_name num_expected num_actual])))))) -(def: #export (nullary valueT) +(def: .public (nullary valueT) (-> Type Handler) (simple (list) valueT)) -(def: #export (unary inputT outputT) +(def: .public (unary inputT outputT) (-> Type Type Handler) (simple (list inputT) outputT)) -(def: #export (binary subjectT paramT outputT) +(def: .public (binary subjectT paramT outputT) (-> Type Type Type Handler) (simple (list subjectT paramT) outputT)) -(def: #export (trinary subjectT param0T param1T outputT) +(def: .public (trinary subjectT param0T param1T outputT) (-> Type Type Type Type Handler) (simple (list subjectT param0T param1T) outputT)) ## TODO: Get rid of this ASAP (as_is - (exception: #export (char_text_must_be_size_1 {text Text}) + (exception: .public (char_text_must_be_size_1 {text Text}) (exception.report ["Text" (%.text text)])) @@ -289,7 +289,7 @@ (///bundle.install "clip" (trinary Nat Nat Text Text)) ))) -(def: #export (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 0a7fc2d7d..306eb960e 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 @@ -200,7 +200,7 @@ _ (analysis/type.infer Text)] (in (#analysis.Extension extension (list formatA dataA)))))])) -(def: #export 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 00a5a803a..915933925 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 @@ -216,7 +216,7 @@ _ (analysis/type.infer .Any)] (in (#analysis.Extension extension (list codeA globalsA)))))])) -(def: #export 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 6dfbf707e..00e210a54 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 @@ [/// ["." phase]]]]]]) -(def: #export 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 a5328bc54..1cc151f14 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 @@ -185,7 +185,7 @@ [_ (analysis/type.infer Bit)] (in (#analysis.Extension extension (list (analysis.text name))))))])) -(def: #export 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 5a6776b13..2d729e701 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 @@ -145,7 +145,7 @@ _ (analysis/type.infer Any)] (in (#analysis.Extension extension (list& abstractionA inputsA)))))])) -(def: #export 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 1869c6ff4..a6ce28fc1 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 @@ ["." dictionary (#+ Dictionary)]]]]] [// (#+ Handler Bundle)]) -(def: #export empty +(def: .public empty Bundle (dictionary.empty text.hash)) -(def: #export (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.put name anonymous)) -(def: #export (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 446c63e08..00ed63ebf 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 @@ -298,7 +298,7 @@ (generation.log! (format "Class " name)))] (in directive.no_requirements)))])) -(def: #export bundle +(def: .public bundle (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 ce82ca51e..2861e1201 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 @@ -8,8 +8,8 @@ [io (#+ IO)] ["." try] ["." exception (#+ exception:)] - ["p" parser - ["s" code (#+ Parser)]]] + ["<>" parser + ["<.>" code (#+ Parser)]]] [data ["." product] ["." maybe] @@ -44,7 +44,7 @@ [meta ["." archive (#+ Archive)]]]]]]) -(def: #export (custom [syntax handler]) +(def: .public (custom [syntax handler]) (All [anchor expression directive s] (-> [(Parser s) (-> Text @@ -54,7 +54,7 @@ (Operation anchor expression directive Requirements))] (Handler anchor expression directive))) (function (_ extension_name phase archive inputs) - (case (s.run syntax inputs) + (case (<code>.run syntax inputs) (#try.Success inputs) (handler extension_name phase archive inputs) @@ -83,7 +83,7 @@ codeV (/////generation.evaluate! (..context [module_id id]) codeG)] (in [code//type codeG codeV])))) -(def: #export (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 @@ -170,7 +170,7 @@ _ (/////generation.save! id #.None directive)] (in [codeG value]))))) - (def: #export (<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]))) @@ -220,15 +220,16 @@ (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ - (^ (list [_ (#.Identifier ["" short_name])] valueC annotationsC [_ (#.Bit exported?)])) + (^ (list [_ (#.Identifier ["" short_name])] valueC annotationsC exported?C)) (do phase.monad [current_module (/////directive.lift_analysis (///.lift meta.current_module_name)) .let [full_name [current_module short_name]] [type valueT value] (..definition archive full_name #.None valueC) - [_ annotationsT annotations] (evaluate! archive Code annotationsC) + [_ _ exported?] (evaluate! archive Bit exported?C) + [_ _ annotations] (evaluate! archive Code annotationsC) _ (/////directive.lift_analysis - (module.define short_name (#.Right [exported? type (:as Code annotations) value]))) + (module.define short_name (#.Right [(:as Bit exported?) type (:as Code annotations) value]))) _ (..refresh expander host_analysis) _ (..announce_definition! short_name type)] (in /////directive.no_requirements)) @@ -239,14 +240,16 @@ (def: (def::type_tagged expander host_analysis) (-> Expander /////analysis.Bundle Handler) (..custom - [($_ p.and s.local_identifier s.any s.any (s.tuple (p.some s.text)) s.bit) - (function (_ extension_name phase archive [short_name valueC annotationsC tags exported?]) + [($_ <>.and <code>.local_identifier <code>.any <code>.any (<code>.tuple (<>.some <code>.text)) <code>.any) + (function (_ extension_name phase archive [short_name valueC annotationsC tags exported?C]) (do phase.monad [current_module (/////directive.lift_analysis (///.lift meta.current_module_name)) .let [full_name [current_module short_name]] - [_ annotationsT annotations] (evaluate! archive Code annotationsC) - .let [annotations (:as Code annotations)] + [_ _ exported?] (evaluate! archive Bit exported?C) + [_ _ annotations] (evaluate! archive Code annotationsC) + .let [exported? (:as Bit exported?) + annotations (:as Code annotations)] [type valueT value] (..definition archive full_name (#.Some .Type) valueC) _ (/////directive.lift_analysis (do phase.monad @@ -258,17 +261,17 @@ (def: imports (Parser (List Import)) - (|> (s.tuple (p.and s.text s.text)) - p.some - s.tuple)) + (|> (<code>.tuple (<>.and <code>.text <code>.text)) + <>.some + <code>.tuple)) (def: def::module Handler (..custom - [($_ p.and s.any ..imports) + [($_ <>.and <code>.any ..imports) (function (_ extension_name phase archive [annotationsC imports]) (do {! phase.monad} - [[_ annotationsT annotationsV] (evaluate! archive Code annotationsC) + [[_ _ annotationsV] (evaluate! archive Code annotationsC) .let [annotationsV (:as Code annotationsV)] _ (/////directive.lift_analysis (do ! @@ -283,7 +286,7 @@ (in {#/////directive.imports imports #/////directive.referrals (list)})))])) -(exception: #export (cannot_alias_an_alias {local Alias} {foreign Alias} {target Name}) +(exception: .public (cannot_alias_an_alias {local Alias} {foreign Alias} {target Name}) (exception.report ["Local alias" (%.name local)] ["Foreign alias" (%.name foreign)] @@ -304,7 +307,7 @@ (def: def::alias Handler (..custom - [($_ p.and s.local_identifier s.identifier) + [($_ <>.and <code>.local_identifier <code>.identifier) (function (_ extension_name phase archive [alias def_name]) (do phase.monad [_ (///.lift @@ -437,7 +440,7 @@ (dictionary.put "program" (def::program program)) ))) -(def: #export (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 740236dc8..6d5995330 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 4900dea03..13b4a40e4 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 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -168,7 +168,7 @@ (/.install "error" (unary _.error/1)) ))) -(def: #export 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 9895f051a..a4aa3e5e8 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 @@ -33,7 +33,7 @@ ["//#" /// #_ ["#." phase]]]]]]) -(def: #export 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 64db8196b..d4580215f 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 240bec8b5..af7b75366 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 @@ -32,7 +32,7 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -180,7 +180,7 @@ (/.install "log" (unary io//log)) (/.install "error" (unary //runtime.io//error))))) -(def: #export 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 ff601d308..9daf4b072 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 @@ -146,7 +146,7 @@ 1 (_.apply/* g!abstraction g!inputs) _ (_.apply/1 g!abstraction (_.array g!inputs)))))))))])) -(def: #export 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 16a34222e..43bc68142 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle ($_ dictionary.merged /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 61d56f794..b21b16ad4 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 @@ -42,7 +42,7 @@ [meta [archive (#+ Archive)]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text Phase Archive s (Operation (Bytecode Any)))] @@ -404,7 +404,7 @@ (/////bundle.install "log" (unary ..io::log)) (/////bundle.install "error" (unary ..io::error))))) -(def: #export 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 60e733c8a..b3f22b503 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 @@ -319,7 +319,7 @@ ))) (template [<name> <category> <parser>] - [(def: #export <name> + [(def: .public <name> (Parser (Type <category>)) (<t>.then <parser> <s>.text))] @@ -330,11 +330,11 @@ [return Return parser.return] ) -(exception: #export (not_an_object_array {arrayJT (Type Array)}) +(exception: .public (not_an_object_array {arrayJT (Type Array)}) (exception.report ["JVM Type" (|> arrayJT type.signature signature.signature)])) -(def: #export object_array +(def: .public object_array (Parser (Type Object)) (do <>.monad [arrayJT (<t>.then parser.array <s>.text)] @@ -1090,7 +1090,7 @@ (/////bundle.install "anonymous" class::anonymous) ))) -(def: #export 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 492f43b94..93062f68c 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 f1f6ccaa1..656ccac5c 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 @@ -35,7 +35,7 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -170,7 +170,7 @@ (/.install "log" (unary ..io//log!)) (/.install "error" (unary (!unary "error")))))) -(def: #export 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 873a37be7..1a633675d 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 @@ -183,7 +183,7 @@ 1 (_.apply/* g!inputs abstractionG) _ (_.apply/1 abstractionG (_.array g!inputs)))))))])) -(def: #export 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 6805ccc27..552a0756c 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 6cc7e61d0..11be7a215 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 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -181,7 +181,7 @@ (/.install "log" (unary //runtime.io//log!)) (/.install "error" (unary //runtime.io//throw!))))) -(def: #export 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 f7a42c5d2..3a294d06e 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 @@ -129,7 +129,7 @@ dataG (phase archive dataS)] (in (_.pack/2 [formatG (_.splat dataG)]))))])) -(def: #export 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 55e2e4756..b0bab688a 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 5be155ab3..4f6c64210 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 @@ -35,7 +35,7 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -160,7 +160,7 @@ (/.install "log" (unary //runtime.io::log!)) (/.install "error" (unary //runtime.io::throw!))))) -(def: #export 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 87f343233..349186b55 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 @@ -150,7 +150,7 @@ globalsG (phase archive globalsS)] (in (//runtime.lux::exec codeG globalsG))))])) -(def: #export 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 f137406ab..504e5d5e9 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 8604be023..f547703e3 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 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -167,7 +167,7 @@ ## (/.install "error" (unary _.error/1)) ## ))) -(def: #export 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 37390f799..f36b10e83 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 @@ -33,7 +33,7 @@ ["//#" /// #_ ["#." phase]]]]]]) -(def: #export 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 dfeee165e..42518bd79 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 c2119b731..c1f9be2b9 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 @@ -35,7 +35,7 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -175,7 +175,7 @@ (/.install "error" (unary ..io//error!)) ))) -(def: #export 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 cb2e4d28b..25d29d1a8 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 @@ -122,7 +122,7 @@ (\ ////////phase.monad in (_.require/1 (_.string module))))])) -(def: #export 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 9d74e5fc6..2fd37b5d7 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 (#+ Bundle)]]]]]) -(def: #export bundle +(def: .public bundle Bundle (dictionary.merged /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 e725c9b95..c04ee1e90 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 @@ [/// ["#" phase]]]]]) -(def: #export (custom [parser handler]) +(def: .public (custom [parser handler]) (All [s] (-> [(Parser s) (-> Text (Generator s))] @@ -163,7 +163,7 @@ (/.install "error" (unary _.raise/1)) ))) -(def: #export 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 0552946f9..680cec039 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 @@ -96,7 +96,7 @@ inputsG (monad.map ! (phase archive) inputsS)] (in (_.apply/* inputsG abstractionG))))])) -(def: #export 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 7e9e85d6e..557dac7ac 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 (#+ Bundle)]]]) -(def: #export 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 c7ef94ce9..3a0578db1 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 @@ -23,7 +23,7 @@ [reference (#+) [variable (#+)]]]]]]]) -(def: #export (generate archive synthesis) +(def: .public (generate archive synthesis) Phase (case synthesis (^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 43c2cab45..624915eed 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 @@ -35,15 +35,15 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register Var/1) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register Var/1) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -51,7 +51,7 @@ (in (_.let (list [(..register register) valueG]) (list bodyG))))) -(def: #export (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) @@ -59,7 +59,7 @@ elseG (expression archive elseS)] (in (_.if testG thenG elseG)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueG (expression archive valueS)] @@ -240,7 +240,7 @@ (_.error/1 (_.string ////synthesis/case.pattern_matching_error)) @done))))) -(def: #export (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 1880d7700..17052fb88 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 @@ [/ ["." common]]) -(def: #export 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 f5d416ee1..6cd07080a 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 @@ -126,7 +126,7 @@ (bundle.install "error" (unary _.error/1)) ))) -(def: #export 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 ad4bedbfa..2ca666bd4 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,7 +29,7 @@ [reference [variable (#+ Register Variable)]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionG (expression archive functionS) @@ -58,7 +58,7 @@ (def: input (|>> inc //case.register)) -(def: #export (function expression archive [environment arity bodyS]) +(def: .public (function expression archive [environment arity bodyS]) (Generator (Abstraction Synthesis)) (do {! ///////phase.monad} [@scope (\ ! map (|>> %.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 61b5cf216..b17b5fd09 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 (#+ Register)]]]]]]]) -(def: #export (scope expression archive [start initsS+ bodyS]) +(def: .public (scope expression archive [start initsS+ bodyS]) (Generator (Scope Synthesis)) (case initsS+ ## function/false/non-independent loop @@ -57,7 +57,7 @@ (_.setq @output bodyG))) @output)))))) -(def: #export (recur expression archive argsS+) +(def: .public (recur 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 82ab68128..c3417e461 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 (#+ Expression)]]]]) -(def: #export bit +(def: .public bit (-> Bit (Expression Any)) _.bool) -(def: #export i64 +(def: .public i64 (-> (I64 Any) (Expression Any)) (|>> .int _.int)) -(def: #export f64 +(def: .public f64 (-> Frac (Expression Any)) _.double) -(def: #export 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 83bbc6a95..a12a8c590 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System (Expression Any)) (def: constant _.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 b69836192..0c557720d 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 @@ -42,7 +42,7 @@ 0) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> [_.Tag Register] (Expression Any) (Expression Any)))] [Operation /////generation.Operation] @@ -51,10 +51,10 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation (Expression Any)))) -(def: #export unit +(def: .public unit (_.string /////synthesis.unit)) (def: (flag value) @@ -67,27 +67,27 @@ (-> (Expression Any) (Expression Any) (Expression Any) (Computation Any)) (_.list/* (list tag last? value))) -(def: #export (variant [lefts right? value]) +(def: .public (variant [lefts right? value]) (-> (Variant (Expression Any)) (Computation Any)) (variant' (_.int (.int lefts)) (flag right?) value)) -(def: #export none +(def: .public none (Computation Any) (|> ..unit [0 #0] ..variant)) -(def: #export some +(def: .public some (-> (Expression Any) (Computation Any)) (|>> [1 #1] ..variant)) -(def: #export left +(def: .public left (-> (Expression Any) (Computation Any)) (|>> [0 #0] ..variant)) -(def: #export right +(def: .public right (-> (Expression Any) (Computation Any)) (|>> [1 #1] ..variant)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -112,7 +112,7 @@ (#.Left name) (let [g!name (code.local_identifier name) code_nameC (code.local_identifier (format "@" name))] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) _.Var/1 (~ runtime_name))) @@ -127,7 +127,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) (_.Computation Any)) (_.call/* (~ runtime_name) (list (~+ inputsC))))) @@ -279,7 +279,7 @@ runtime//text runtime//io))) -(def: #export 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 a0b6b78e9..df957a3cd 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 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple expression archive elemsS+) +(def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -28,7 +28,7 @@ (monad.map ///////phase.monad (expression archive)) (///////phase\map _.vector/*)))) -(def: #export (variant expression archive [lefts right? valueS]) +(def: .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc 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 7c50630d7..95121edc4 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 @@ -24,17 +24,17 @@ (syntax: (Vector {size s.nat} elemT) (in (list (` [(~+ (list.repeat size elemT))])))) -(type: #export (Nullary of) (-> (Vector 0 of) of)) -(type: #export (Unary of) (-> (Vector 1 of) of)) -(type: #export (Binary of) (-> (Vector 2 of) of)) -(type: #export (Trinary of) (-> (Vector 3 of) of)) -(type: #export (Variadic of) (-> (List of) of)) +(type: .public (Nullary of) (-> (Vector 0 of) of)) +(type: .public (Unary of) (-> (Vector 1 of) of)) +(type: .public (Binary of) (-> (Vector 2 of) of)) +(type: .public (Trinary of) (-> (Vector 3 of) of)) +(type: .public (Variadic of) (-> (List of) of)) (syntax: (arity: {arity s.nat} {name s.local_identifier} type) (with_gensyms [g!_ g!extension g!name g!phase g!archive g!inputs g!of g!anchor g!expression g!directive] (do {! meta.monad} [g!input+ (monad.seq ! (list.repeat arity (macro.gensym "input")))] - (in (list (` (def: #export ((~ (code.local_identifier name)) (~ g!extension)) + (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (All [(~ g!anchor) (~ g!expression) (~ g!directive)] (-> ((~ type) (~ g!expression)) (generation.Handler (~ g!anchor) (~ g!expression) (~ g!directive)))) @@ -56,7 +56,7 @@ (arity: 2 binary ..Binary) (arity: 3 trinary ..Trinary) -(def: #export (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 e1c4dd247..608217f8f 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 @@ -63,7 +63,7 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot_recur_as_an_expression) +(exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase @@ -112,6 +112,6 @@ (#synthesis.Extension extension) (///extension.apply archive expression extension))) -(def: #export 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 7758725c1..51e58fb51 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 @@ -31,11 +31,11 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register Var) (|>> (///reference.local //reference.system) :assume)) -(def: #export (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) @@ -45,7 +45,7 @@ (_.return bodyO)) (list valueO))))) -(def: #export (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) @@ -54,7 +54,7 @@ (_.define (..register register) valueO) bodyO)))) -(def: #export (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) @@ -62,7 +62,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: #export (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) @@ -72,7 +72,7 @@ thenO elseO)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -304,7 +304,7 @@ pattern_matching!) (_.throw (_.string ////synthesis/case.pattern_matching_error)))))) -(def: #export (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) @@ -315,7 +315,7 @@ (_.define @savepoint (_.array (list))) pattern_matching!)))) -(def: #export (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 f2f326f8f..00ac84cf8 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 @@ -27,7 +27,7 @@ [reference [variable (#+ Register Variable)]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) @@ -65,7 +65,7 @@ (-> Context Text) (format (///reference.artifact function_name) "_scope")) -(def: #export (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/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux index dcb7daa43..602ef1191 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 @@ -41,7 +41,7 @@ list.reversed (list\fold _.then body))) -(def: #export (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 @@ -60,7 +60,7 @@ (_.do_while (_.boolean true) body!))))))) -(def: #export (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 @@ -76,7 +76,7 @@ (def: @temp (_.var "lux_recur_values")) -(def: #export (recur! statement expression archive argsS+) +(def: .public (recur! 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 ede743c5d..711a72275 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 @@ ["." // #_ ["#." runtime]]) -(def: #export bit +(def: .public bit _.boolean) -(def: #export (i64 value) +(def: .public (i64 value) (-> (I64 Any) Computation) (//runtime.i64 (|> value //runtime.high .int _.i32) (|> value //runtime.low .int _.i32))) -(def: #export f64 +(def: .public f64 _.number) -(def: #export 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 b21262192..646852129 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.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 350faeeec..5d09cbd16 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 @@ -44,7 +44,7 @@ ["." artifact (#+ Registry)]]]]]]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> [Register Text] Expression Statement))] [Operation /////generation.Operation] @@ -53,29 +53,29 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(type: #export Phase! +(type: .public Phase! (-> Phase Archive Synthesis (Operation Statement))) -(type: #export (Generator! i) +(type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: #export high +(def: .public high (-> (I64 Any) (I64 Any)) (i64.right_shifted 32)) -(def: #export low +(def: .public low (-> (I64 Any) (I64 Any)) (let [mask (dec (i64.left_shifted 32 1))] (|>> (i64.and mask)))) -(def: #export unit +(def: .public unit Computation (_.string /////synthesis.unit)) -(def: #export (flag value) +(def: .public (flag value) (-> Bit Computation) (if value (_.string "") @@ -85,7 +85,7 @@ (-> Var (-> Var Expression) Statement) (_.define name (definition name))) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -106,7 +106,7 @@ (case declaration (#.Left name) (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) Var (~ runtime_name))) @@ -120,7 +120,7 @@ (let [g!name (code.local_identifier name) inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply/* (~ runtime_name) (list (~+ inputsC))))) @@ -172,9 +172,9 @@ (_.return (_.do "slice" (list right_index) tuple))) ))))) -(def: #export variant_tag_field "_lux_tag") -(def: #export variant_flag_field "_lux_flag") -(def: #export 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")] @@ -186,7 +186,7 @@ (_.set (_.the ..variant_value_field @this) value) ))))) -(def: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Expression Expression Expression Computation) (_.new ..variant//new (list tag last? value))) @@ -264,8 +264,8 @@ @lux//program_args )) -(def: #export i64_low_field Text "_lux_low") -(def: #export 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")] @@ -276,7 +276,7 @@ (_.set (_.the ..i64_low_field @this) low) ))))) -(def: #export (i64 high low) +(def: .public (i64 high low) (-> Expression Expression Computation) (_.new ..i64//new (list high low))) @@ -771,7 +771,7 @@ (def: module_id 0) -(def: #export 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 5cbacf111..ebaaa7f49 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 @@ -14,7 +14,7 @@ ["//#" /// ["#." phase ("#\." monad)]]]]) -(def: #export (tuple generate archive elemsS+) +(def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -28,7 +28,7 @@ [elemsT+ (monad.map ! (generate archive) elemsS+)] (in (_.array elemsT+))))) -(def: #export (variant generate archive [lefts right? valueS]) +(def: .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc lefts) 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 629f7704e..bece6d582 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 @@ -19,7 +19,7 @@ ["." reference] ["#" phase ("#\." monad)]]]]]) -(def: #export (generate archive synthesis) +(def: .public (generate archive synthesis) Phase (case synthesis (^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 bdf4fb89c..37f9134fb 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 @@ -208,7 +208,7 @@ _.aconst_null (_.goto @end))))) -(def: #export (if phase archive [conditionS thenS elseS]) +(def: .public (if phase archive [conditionS thenS elseS]) (Generator [Synthesis Synthesis Synthesis]) (do phase.monad [conditionG (phase archive conditionS) @@ -227,7 +227,7 @@ elseG (_.set_label @end)))))) -(def: #export (let phase archive [inputS register bodyS]) +(def: .public (let phase archive [inputS register bodyS]) (Generator [Synthesis Register Synthesis]) (do phase.monad [inputG (phase archive inputS) @@ -237,7 +237,7 @@ (_.astore register) bodyG)))) -(def: #export (get phase archive [path recordS]) +(def: .public (get phase archive [path recordS]) (Generator [(List synthesis.Member) Synthesis]) (do phase.monad [recordG (phase archive recordS)] @@ -252,7 +252,7 @@ recordG (list.reversed path))))) -(def: #export (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 82f5b442b..d830d478f 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 @@ -15,7 +15,7 @@ (def: extension ".class") -(def: #export (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 d13e7ebed..7a8dd2860 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 @@ -58,7 +58,7 @@ [reference [variable (#+ Register)]]]]]]) -(def: #export (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)) @@ -95,7 +95,7 @@ Internal)) (|>> type.reflection reflection.reflection name.internal)) -(def: #export (abstraction generate archive [environment arity bodyS]) +(def: .public (abstraction generate archive [environment arity bodyS]) (Generator Abstraction) (do phase.monad [@begin //runtime.forge_label @@ -116,7 +116,7 @@ _ (generation.save! function_class #.None [function_class bytecode])] (in instance))) -(def: #export (apply generate archive [abstractionS inputsS]) +(def: .public (apply generate archive [abstractionS inputsS]) (Generator Apply) (do {! phase.monad} [abstractionG (generate archive abstractionS) 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 eb1f78ed9..04e3d4cda 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,12 +13,12 @@ [constant ["." arity]]]]) -(def: #export artifact_id +(def: .public artifact_id 1) -(def: #export class +(def: .public class (type.class (%.nat artifact_id) (list))) -(def: #export 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 d6bb70600..53d058584 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 @@ -21,6 +21,6 @@ field.final )) -(def: #export (constant name type) +(def: .public (constant name type) (-> Text (Type Value) (Resource Field)) (field.field ..modifier name type (row.row))) 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 a1e0a589d..7bb5a7f15 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 @@ -11,12 +11,12 @@ [///////// [arity (#+ Arity)]]]) -(def: #export name "arity") -(def: #export type type.int) +(def: .public name "arity") +(def: .public type type.int) -(def: #export minimum Arity 1) -(def: #export maximum Arity 8) +(def: .public minimum Arity 1) +(def: .public maximum Arity 8) -(def: #export constant +(def: .public constant (Resource Field) (//.constant ..name ..type)) 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 aa200182d..328921a19 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,16 +21,16 @@ [reference [variable (#+ Register)]]]]) -(def: #export type ////type.value) +(def: .public type ////type.value) -(def: #export (get class name) +(def: .public (get class name) (-> (Type Class) Text (Bytecode Any)) ($_ _.compose ////reference.this (_.getfield class name ..type) )) -(def: #export (put naming class register value) +(def: .public (put naming class register value) (-> (-> Register Text) (Type Class) Register (Bytecode Any) (Bytecode Any)) ($_ _.compose ////reference.this @@ -44,11 +44,11 @@ field.final )) -(def: #export (variable name type) +(def: .public (variable name type) (-> Text (Type Value) (Resource Field)) (field.field ..modifier name type (row.row))) -(def: #export (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/foreign.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/foreign.lux index ccfd84401..10dbc1bcc 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 @@ -23,18 +23,18 @@ [reference [variable (#+ Register)]]]]]]) -(def: #export (closure environment) +(def: .public (closure environment) (-> (Environment Synthesis) (List (Type Value))) (list.repeat (list.size environment) //.type)) -(def: #export (get class register) +(def: .public (get class register) (-> (Type Class) Register (Bytecode Any)) (//.get class (/////reference.foreign_name register))) -(def: #export (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: #export 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 7e5e8a6ca..adc3da6c8 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 @@ -30,7 +30,7 @@ [reference [variable (#+ Register)]]]]]]]) -(def: #export (initial amount) +(def: .public (initial amount) (-> Nat (Bytecode Any)) ($_ _.compose (|> _.aconst_null @@ -38,19 +38,19 @@ (monad.seq _.monad)) (_\in []))) -(def: #export (get class register) +(def: .public (get class register) (-> (Type Class) Register (Bytecode Any)) (//.get class (/////reference.partial_name register))) -(def: #export (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: #export variables +(def: .public variables (-> Arity (List (Resource Field))) (|>> (n.- ///arity.minimum) (//.variables /////reference.partial_name))) -(def: #export (new arity) +(def: .public (new arity) (-> Arity (Bytecode Any)) (if (arity.multiary? arity) ($_ _.compose diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux index a3e4fc738..4bc179078 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/field/variable/partial/count.lux @@ -13,17 +13,17 @@ ["." ///// #_ ["#." abstract]]) -(def: #export field "partials") -(def: #export type type.int) +(def: .public field "partials") +(def: .public type type.int) -(def: #export initial +(def: .public initial (Bytecode Any) (|> +0 signed.s1 try.assumed _.bipush)) (def: this _.aload_0) -(def: #export value +(def: .public value (Bytecode Any) ($_ _.compose ..this 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 9cbde4b63..4dbadacb0 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 @@ ["." modifier (#+ Modifier) ("#\." monoid)] ["." method (#+ Method)]]]]]) -(def: #export modifier +(def: .public modifier (Modifier Method) ($_ modifier\compose 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 46b871096..9f4bc4e13 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 @@ -77,7 +77,7 @@ (def: this_offset 1) -(def: #export (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 (dec 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 347ab1a8a..07473f901 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 @@ -18,15 +18,15 @@ [////// [arity (#+ Arity)]]]]) -(def: #export name "impl") +(def: .public name "impl") -(def: #export (type arity) +(def: .public (type arity) (-> Arity (Type category.Method)) (type.method [(list.repeat arity ////type.value) ////type.value (list)])) -(def: #export (method' name arity @begin body) +(def: .public (method' name arity @begin body) (-> Text Arity Label (Bytecode Any) (Resource Method)) (method.method //.modifier name (..type arity) @@ -37,6 +37,6 @@ _.areturn )))) -(def: #export method +(def: .public method (-> Arity Label (Bytecode Any) (Resource Method)) (method' ..name)) 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 f44d62118..b99f5661a 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 @@ -41,13 +41,13 @@ [reference [variable (#+ Register)]]]]]]]) -(def: #export name "<init>") +(def: .public name "<init>") (def: (partials arity) (-> Arity (List (Type Value))) (list.repeat (dec arity) ////type.value)) -(def: #export (type environment arity) +(def: .public (type environment arity) (-> (Environment Synthesis) Arity (Type category.Method)) (type.method [(list\compose (///foreign.closure environment) (if (arity.multiary? arity) @@ -58,7 +58,7 @@ (def: no_partials (|> 0 unsigned.u1 try.assumed _.bipush)) -(def: #export (super environment_size arity) +(def: .public (super environment_size arity) (-> Nat Arity (Bytecode Any)) (let [arity_register (inc environment_size)] ($_ _.compose @@ -78,7 +78,7 @@ (_.aload (offset register))))) (monad.seq _.monad))) -(def: #export (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 (: (-> 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 1707b1413..45ea0b010 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 @@ -42,7 +42,7 @@ ["." arity (#+ Arity)] ["." phase]]]]]]) -(def: #export (instance' foreign_setup class environment arity) +(def: .public (instance' foreign_setup class environment arity) (-> (List (Bytecode Any)) (Type Class) (Environment Synthesis) Arity (Bytecode Any)) ($_ _.compose (_.new class) @@ -51,13 +51,13 @@ (///partial.new arity) (_.invokespecial class //init.name (//init.type environment arity)))) -(def: #export (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.map ! (generate archive) environment)] (in (instance' foreign* class environment arity)))) -(def: #export (method class environment arity) +(def: .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (let [after_this (: (-> 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 8ad6fd92e..615cc0388 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,9 +26,9 @@ [/// ["." arity (#+ Arity)]]]]]]) -(def: #export name "reset") +(def: .public name "reset") -(def: #export (type class) +(def: .public (type class) (-> (Type Class) (Type category.Method)) (type.method [(list) class (list)])) @@ -38,7 +38,7 @@ list.indices (list\map (///foreign.get class)))) -(def: #export (method class environment arity) +(def: .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (method.method //.modifier ..name (..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 fc9f4d3ca..b58414fd9 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 @@ -60,18 +60,18 @@ (def: init::type (type.method [(list) type.void (list)])) (def: init::modifier ($_ modifier\compose method.public method.static method.strict)) -(exception: #export (cannot_load {class Text} {error Text}) +(exception: .public (cannot_load {class Text} {error Text}) (exception.report ["Class" class] ["Error" error])) -(exception: #export (invalid_field {class Text} {field Text} {error Text}) +(exception: .public (invalid_field {class Text} {field Text} {error Text}) (exception.report ["Class" class] ["Field" field] ["Error" error])) -(exception: #export (invalid_value {class Text}) +(exception: .public (invalid_value {class Text}) (exception.report ["Class" class])) @@ -144,7 +144,7 @@ [[value definition] (evaluate! library loader class_name valueG)] (in [class_name value definition])))) -(def: #export host +(def: .public host (IO //runtime.Host) (io (let [library (loader.new_library []) loader (loader.memory library)] 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 91c433788..857066e4b 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 @@ -37,7 +37,7 @@ (def: no_op (_\in [])) -(def: #export (recur translate archive updatesS) +(def: .public (recur translate archive updatesS) (Generator (List Synthesis)) (do {! phase.monad} [[@begin offset] generation.anchor @@ -71,7 +71,7 @@ (monad.seq _.monad)) (_.goto @begin))))) -(def: #export (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 42f9a24fa..7c35b11de 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 @@ -17,14 +17,14 @@ (def: $Long (type.class "java.lang.Long" (list))) (def: $Double (type.class "java.lang.Double" (list))) -(def: #export (bit value) +(def: .public (bit value) (-> Bit (Bytecode Any)) (_.getstatic $Boolean (if value "TRUE" "FALSE") $Boolean)) (def: wrap_i64 (_.invokestatic $Long "valueOf" (type.method [(list type.long) $Long (list)]))) -(def: #export (i64 value) +(def: .public (i64 value) (-> (I64 Any) (Bytecode Any)) (case (.int value) (^template [<int> <instruction>] @@ -76,7 +76,7 @@ (import: java/lang/Double (#static doubleToRawLongBits #manual [double] int)) -(def: #export (f64 value) +(def: .public (f64 value) (-> Frac (Bytecode Any)) (case value (^template [<int> <instruction>] @@ -117,5 +117,5 @@ [_ constantI] ..wrap_f64)))) -(def: #export 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 e87a3f0df..0a749f337 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 @@ -25,11 +25,17 @@ ["#." runtime (#+ Definition)] ["#." function/abstract]]) -(def: #export class "LuxProgram") +(def: .public class + "LuxProgram") -(def: ^Object (type.class "java.lang.Object" (list))) -(def: ^String (type.class "java.lang.String" (list))) -(def: ^Args (type.array ^String)) +(def: ^Object + (type.class "java.lang.Object" (list))) + +(def: ^String + (type.class "java.lang.String" (list))) + +(def: ^Args + (type.array ^String)) (def: main::type (type.method [(list ..^Args) type.void (list)])) @@ -121,7 +127,7 @@ _.aconst_null //runtime.apply)) -(def: #export (program program) +(def: .public (program program) (-> (Bytecode Any) Definition) (let [super_class (|> ..^Object type.reflection reflection.reflection name.internal) main (method.method ..main::modifier "main" ..main::type 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 2e3fe8618..d983068b9 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 (#+ Archive)]]]]]]) -(def: #export this +(def: .public this (Bytecode Any) _.aload_0) (template [<name> <prefix>] - [(def: #export <name> + [(def: .public <name> (-> Register Text) (|>> %.nat (format <prefix>)))] @@ -50,7 +50,7 @@ (..foreign_name variable) //type.value))))) -(def: #export (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: #export (constant archive name) +(def: .public (constant archive name) (-> Archive Name (Operation (Bytecode Any))) (do {! ////.monad} [bytecode_name (\ ! map //runtime.class_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 a1ae79528..757716fe7 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 @@ -60,14 +60,14 @@ [io (#+ lux_context)] [archive (#+ Archive)]]]]]]) -(type: #export Byte_Code Binary) +(type: .public Byte_Code Binary) -(type: #export Definition [Text Byte_Code]) +(type: .public Definition [Text Byte_Code]) -(type: #export Anchor [Label Register]) +(type: .public Anchor [Label Register]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> Anchor (Bytecode Any) Definition))] [Operation generation.Operation] @@ -76,13 +76,13 @@ [Bundle generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation (Bytecode Any)))) -(type: #export Host +(type: .public Host (generation.Host (Bytecode Any) Definition)) -(def: #export (class_name [module id]) +(def: .public (class_name [module id]) (-> generation.Context Text) (format lux_context "/" (%.nat version.version) @@ -92,7 +92,7 @@ (def: artifact_id 0) -(def: #export class +(def: .public class (type.class (%.nat ..artifact_id) (list))) (def: procedure @@ -111,7 +111,7 @@ (Bytecode Any) _.aload_0) -(def: #export (get index) +(def: .public (get index) (-> (Bytecode Any) (Bytecode Any)) ($_ _.compose index @@ -127,11 +127,11 @@ _.aastore ## A )) -(def: #export unit (_.string synthesis.unit)) +(def: .public unit (_.string synthesis.unit)) (def: variant::name "variant") (def: variant::type (type.method [(list) (list //type.tag //type.flag //type.value) //type.variant (list)])) -(def: #export variant (..procedure ..variant::name ..variant::type)) +(def: .public variant (..procedure ..variant::name ..variant::type)) (def: variant_tag _.iconst_0) (def: variant_last? _.iconst_1) @@ -156,10 +156,10 @@ (..set! ..variant_value $value) ## A[3] _.areturn))))) -(def: #export left_flag _.aconst_null) -(def: #export right_flag ..unit) +(def: .public left_flag _.aconst_null) +(def: .public right_flag ..unit) -(def: #export left_injection +(def: .public left_injection (Bytecode Any) ($_ _.compose _.iconst_0 @@ -168,7 +168,7 @@ _.pop2 ..variant)) -(def: #export right_injection +(def: .public right_injection (Bytecode Any) ($_ _.compose _.iconst_1 @@ -177,9 +177,9 @@ _.pop2 ..variant)) -(def: #export some_injection ..right_injection) +(def: .public some_injection ..right_injection) -(def: #export none_injection +(def: .public none_injection (Bytecode Any) ($_ _.compose _.iconst_0 @@ -205,7 +205,7 @@ (def: decode_frac::name "decode_frac") (def: decode_frac::type (type.method [(list) (list //type.text) //type.variant (list)])) -(def: #export decode_frac (..procedure ..decode_frac::name ..decode_frac::type)) +(def: .public decode_frac (..procedure ..decode_frac::name ..decode_frac::type)) (def: decode_frac::method (method.method ..modifier ..decode_frac::name @@ -219,7 +219,7 @@ (//value.wrap type.double) ))))) -(def: #export log! +(def: .public log! (Bytecode Any) (let [^PrintStream (type.class "java.io.PrintStream" (list)) ^System (type.class "java.lang.System" (list)) @@ -254,17 +254,17 @@ _.athrow)))) (def: pm_failure::name "pm_failure") -(def: #export pm_failure (..procedure ..pm_failure::name ..failure::type)) +(def: .public pm_failure (..procedure ..pm_failure::name ..failure::type)) (def: pm_failure::method (..failure ..pm_failure::name "Invalid expression for pattern-matching.")) -(def: #export stack_head _.iconst_0) -(def: #export 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: #export push (..procedure ..push::name ..push::type)) +(def: .public push (..procedure ..push::name ..push::type)) (def: push::method (method.method ..modifier ..push::name @@ -284,7 +284,7 @@ (def: case::name "case") (def: case::type (type.method [(list) (list //type.variant //type.tag //type.flag) //type.value (list)])) -(def: #export case (..procedure ..case::name ..case::type)) +(def: .public case (..procedure ..case::name ..case::type)) (def: case::method (method.method ..modifier ..case::name ..case::type @@ -361,10 +361,10 @@ (def: projection_type (type.method [(list) (list //type.tuple //type.offset) //type.value (list)])) (def: left_projection::name "left") -(def: #export left_projection (..procedure ..left_projection::name ..projection_type)) +(def: .public left_projection (..procedure ..left_projection::name ..projection_type)) (def: right_projection::name "right") -(def: #export right_projection (..procedure ..right_projection::name ..projection_type)) +(def: .public right_projection (..procedure ..right_projection::name ..projection_type)) (def: projection::method2 [(Resource Method) (Resource Method)] @@ -445,18 +445,18 @@ [left_projection::method right_projection::method])) -(def: #export apply::name "apply") +(def: .public apply::name "apply") -(def: #export (apply::type arity) +(def: .public (apply::type arity) (-> Arity (Type category.Method)) (type.method [(list) (list.repeat arity //type.value) //type.value (list)])) -(def: #export 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: #export try (..procedure ..try::name ..try::type)) +(def: .public try (..procedure ..try::name ..try::type)) (def: false _.iconst_0) (def: true _.iconst_1) @@ -596,13 +596,13 @@ [_ (generation.execute! [class bytecode])] (generation.save! //function.artifact_id #.None [class bytecode])))) -(def: #export generate +(def: .public generate (Operation Any) (do ////.monad [_ ..generate_runtime] ..generate_function)) -(def: #export 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 06b60b6c1..062708388 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 @@ -26,7 +26,7 @@ (def: $Object (type.class "java.lang.Object" (list))) -(def: #export (tuple generate archive membersS) +(def: .public (tuple generate archive membersS) (Generator (Tuple Synthesis)) (case membersS #.End @@ -52,7 +52,7 @@ _ (_.anewarray $Object)] (monad.seq ! membersI)))))) -(def: #export (tag lefts right?) +(def: .public (tag lefts right?) (-> Nat Bit (Bytecode Any)) (case (if right? (.inc lefts) @@ -75,13 +75,13 @@ (#try.Failure _) (_.int (.i64 tag)))))) -(def: #export (flag right?) +(def: .public (flag right?) (-> Bit (Bytecode Any)) (if right? //runtime.right_flag //runtime.left_flag)) -(def: #export (variant generate archive [lefts right? valueS]) +(def: .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (do phase.monad [valueI (generate 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 4c6f14a3f..2bc32f589 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 ["." type]]]]]) -(def: #export frac (type.class "java.lang.Double" (list))) -(def: #export 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: #export value (type.class "java.lang.Object" (list))) +(def: .public value (type.class "java.lang.Object" (list))) -(def: #export tag type.int) -(def: #export flag ..value) -(def: #export variant (type.array ..value)) +(def: .public tag type.int) +(def: .public flag ..value) +(def: .public variant (type.array ..value)) -(def: #export offset type.int) -(def: #export index ..offset) -(def: #export tuple (type.array ..value)) +(def: .public offset type.int) +(def: .public index ..offset) +(def: .public tuple (type.array ..value)) -(def: #export stack (type.array ..value)) +(def: .public stack (type.array ..value)) -(def: #export 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 36edc060a..138a9d2fb 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,7 +8,7 @@ [category (#+ Primitive)] ["." box]]]]]]) -(def: #export field "value") +(def: .public field "value") (template [<name> <boolean> <byte> <short> <int> <long> <float> <double> <char>] [(def: (<name> type) @@ -35,13 +35,13 @@ "longValue" "floatValue" "doubleValue" "charValue"] ) -(def: #export (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: #export (unwrap type) +(def: .public (unwrap type) (-> (Type Primitive) (Bytecode Any)) (let [wrapper (type.class (primitive_wrapper type) (list))] ($_ _.compose 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 b51cd2930..56860a588 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 @@ -65,7 +65,7 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot_recur_as_an_expression) +(exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase @@ -114,6 +114,6 @@ (#synthesis.Extension extension) (///extension.apply archive expression extension))) -(def: #export 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 273e1d0ae..db4de757c 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 @@ -30,15 +30,15 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register Var) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -49,7 +49,7 @@ (_.closure (list (..register register))) (_.apply/* (list valueO)))))) -(def: #export (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) @@ -58,7 +58,7 @@ (_.local/1 (..register register) valueO) bodyO)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -73,7 +73,7 @@ valueO (list.reversed pathP))))) -(def: #export (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) @@ -85,7 +85,7 @@ (_.closure (list)) (_.apply/* (list)))))) -(def: #export (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) @@ -247,7 +247,7 @@ pattern_matching!) (_.statement (|> (_.var "error") (_.apply/* (list (_.string ////synthesis/case.pattern_matching_error))))))))) -(def: #export dependencies +(def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage (get@ #////synthesis/case.dependencies) @@ -260,7 +260,7 @@ (#///////variable.Foreign register) (..capture register)))))) -(def: #export (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) @@ -271,7 +271,7 @@ (_.local/1 @savepoint (_.array (list))) pattern_matching!)))) -(def: #export (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 21c78c6f9..e26940c60 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 @@ -29,7 +29,7 @@ [reference [variable (#+ Register Variable)]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) @@ -63,7 +63,7 @@ (-> Context Label) (_.label (format (///reference.artifact function_name) "_scope"))) -(def: #export (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/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index d9ae9c51f..d19421620 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 @@ -47,7 +47,7 @@ (_.set variables (_.multi bindings))) body)))) -(def: #export (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])) @@ -71,7 +71,7 @@ (_.set_label @scope) body!))])))) -(def: #export (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 @@ -111,7 +111,7 @@ _ (/////generation.save! artifact_id #.None directive)] (in (|> instantiation (_.apply/* initsO+)))))) -(def: #export (recur! statement expression archive argsS+) +(def: .public (recur! 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 7d010b4cb..f819ca279 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 (#+ Literal)]]]]) (template [<name> <type> <implementation>] - [(def: #export <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 52bc69a29..b24890947 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.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 935caf949..d77a51d8a 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 @@ -39,7 +39,7 @@ ["." artifact (#+ Registry)]]]]]]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> [Register Label] Expression Statement))] [Operation /////generation.Operation] @@ -48,16 +48,16 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(type: #export Phase! +(type: .public Phase! (-> Phase Archive Synthesis (Operation Statement))) -(type: #export (Generator! i) +(type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: #export unit +(def: .public unit (_.string /////synthesis.unit)) (def: (flag value) @@ -66,9 +66,9 @@ ..unit _.nil)) -(def: #export variant_tag_field "_lux_tag") -(def: #export variant_flag_field "_lux_flag") -(def: #export 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) (-> Expression Expression Expression Literal) @@ -76,25 +76,25 @@ [..variant_flag_field last?] [..variant_value_field value]))) -(def: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Nat Bit Expression Literal) (variant' (_.int (.int tag)) (flag last?) value)) -(def: #export none +(def: .public none Literal (..variant 0 #0 ..unit)) -(def: #export some +(def: .public some (-> Expression Literal) (..variant 1 #1)) -(def: #export left +(def: .public left (-> Expression Literal) (..variant 0 #0)) -(def: #export right +(def: .public right (-> Expression Literal) (..variant 1 #1)) @@ -102,7 +102,7 @@ (-> Var (-> Var Statement) Statement) (definition name)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -130,7 +130,7 @@ (#.Left name) (macro.with_gensyms [g!_] (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) Var (~ runtime_name))) @@ -146,7 +146,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply/* (list (~+ inputsC)) (~ runtime_name)))) @@ -418,7 +418,7 @@ ..runtime//array )) -(def: #export 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 8b070c7a3..8c78dea65 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 @@ -14,7 +14,7 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple generate archive elemsS+) +(def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -28,7 +28,7 @@ (monad.map ///////phase.monad (generate archive)) (///////phase\map _.array)))) -(def: #export (variant generate archive [lefts right? valueS]) +(def: .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc lefts) 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 aad40560a..1366ae632 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 @@ -59,9 +59,9 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot_recur_as_an_expression) +(exception: .public cannot_recur_as_an_expression) -(def: #export (expression archive synthesis) +(def: .public (expression archive synthesis) Phase (case synthesis (^template [<tag> <generator>] @@ -98,6 +98,6 @@ (#////synthesis.Extension extension) (///extension.apply archive expression extension))) -(def: #export 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 3bbbd7d21..2906c63ed 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 @@ -34,15 +34,15 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register Var) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -52,7 +52,7 @@ _.array/* (_.item (_.int +1)))))) -(def: #export (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) @@ -61,7 +61,7 @@ (_.set! (..register register) valueO) body!)))) -(def: #export (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) @@ -69,7 +69,7 @@ elseG (expression archive elseS)] (in (_.? testG thenG elseG)))) -(def: #export (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) @@ -79,7 +79,7 @@ then! else!)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueG (expression archive valueS)] @@ -261,7 +261,7 @@ (-> Text (Operation Text)) (\ ///////phase.monad map (|>> %.nat (format prefix)) /////generation.next)) -(def: #export dependencies +(def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage (get@ #////synthesis/case.dependencies) @@ -274,7 +274,7 @@ (#///////variable.Foreign register) (..capture register)))))) -(def: #export (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) @@ -284,7 +284,7 @@ (_.set! @savepoint (_.array/* (list))) pattern_matching!)))) -(def: #export (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 1880d7700..17052fb88 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 @@ [/ ["." common]]) -(def: #export 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 f3ad84b3d..a630b31c3 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 @@ -100,7 +100,7 @@ (bundle.install "exit" (unary _.exit/1)) (bundle.install "current-time" (nullary (|>> _.time/0 (_.* (_.int +1,000)))))))) -(def: #export 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 93a099ce0..f4df9c34b 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,7 +29,7 @@ [reference [variable (#+ Register Variable)]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionG (expression archive functionS) @@ -67,7 +67,7 @@ (_.return @selfL)))) (_.apply/* inits @selfG)]))) -(def: #export (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 54a001a41..32e6346cf 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 @@ -47,7 +47,7 @@ list.reversed (list\fold _.then body))) -(def: #export (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 @@ -66,7 +66,7 @@ (_.set_label @scope) body!)))))) -(def: #export (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 @@ -107,7 +107,7 @@ (def: @temp (_.var "lux_recur_values")) -(def: #export (recur! statement expression archive argsS+) +(def: .public (recur! 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 9101ee48d..cc9af8550 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 @@ -11,11 +11,11 @@ ["." // #_ ["#." runtime]]) -(def: #export bit +(def: .public bit (-> Bit Literal) _.bool) -(def: #export (i64 value) +(def: .public (i64 value) (-> (I64 Any) Expression) (let [h32 (|> value //runtime.high .int _.int) l32 (|> value //runtime.low .int _.int)] @@ -23,10 +23,10 @@ (_.bit_shl (_.int +32)) (_.bit_or l32)))) -(def: #export f64 +(def: .public f64 (-> Frac Literal) _.float) -(def: #export 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 5dce15a26..487d08e32 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.global) 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 a18335967..4a5b7b5e0 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 @@ -39,7 +39,7 @@ ["." artifact (#+ Registry)]]]]]]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> [Nat Label] Expression Statement))] [Operation /////generation.Operation] @@ -48,16 +48,16 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(type: #export Phase! +(type: .public Phase! (-> Phase Archive Synthesis (Operation Statement))) -(type: #export (Generator! i) +(type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: #export unit +(def: .public unit (_.string /////synthesis.unit)) (def: (flag value) @@ -70,7 +70,7 @@ (-> Constant (-> Constant Statement) Statement) (definition name)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -98,7 +98,7 @@ (#.Left name) (macro.with_gensyms [g!_] (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) Var (~ runtime_name))) @@ -114,7 +114,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply/* (list (~+ inputsC)) (~ runtime_name)))) @@ -145,7 +145,7 @@ @io//throw! )) -(def: #export tuple_size_field +(def: .public tuple_size_field "_lux_size") (def: tuple_size @@ -241,34 +241,34 @@ (_.array_slice/2 [(_.do "getArrayCopy" (list) tuple) right_index]))))) ))))) -(def: #export variant_tag_field "_lux_tag") -(def: #export variant_flag_field "_lux_flag") -(def: #export 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: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Nat Bit Expression Computation) (sum//make (_.int (.int tag)) (..flag last?) value)) -(def: #export none +(def: .public none Computation (..variant 0 #0 ..unit)) -(def: #export some +(def: .public some (-> Expression Computation) (..variant 1 #1)) -(def: #export left +(def: .public left (-> Expression Computation) (..variant 0 #0)) -(def: #export right +(def: .public right (-> Expression Computation) (..variant 1 #1)) @@ -336,11 +336,11 @@ @lux//program_args )) -(def: #export high +(def: .public high (-> (I64 Any) (I64 Any)) (i64.right_shifted 32)) -(def: #export low +(def: .public low (-> (I64 Any) (I64 Any)) (let [mask (dec (i64.left_shifted 32 1))] (|>> (i64.and mask)))) @@ -596,7 +596,7 @@ runtime//io )) -(def: #export 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 601361f31..69979afd6 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 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple expression archive elemsS+) +(def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -33,7 +33,7 @@ (///////phase\map (|>> _.array/* (//runtime.tuple//make size))))))) -(def: #export (variant expression archive [lefts right? valueS]) +(def: .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc 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 1d01ba8b0..4426bc6c8 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 @@ -59,9 +59,9 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot_recur_as_an_expression) +(exception: .public cannot_recur_as_an_expression) -(def: #export (expression archive synthesis) +(def: .public (expression archive synthesis) Phase (case synthesis (^template [<tag> <generator>] @@ -108,6 +108,6 @@ (#////synthesis.Extension extension) (///extension.apply archive expression extension))) -(def: #export 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 59ccb6098..84bc0c2ca 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 @@ -34,20 +34,20 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export (gensym prefix) +(def: .public (gensym prefix) (-> Text (Operation SVar)) (///////phase\map (|>> %.nat (format prefix) _.var) /////generation.next)) -(def: #export register +(def: .public register (-> Register SVar) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -57,7 +57,7 @@ bodyO) (list valueO))))) -(def: #export (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) @@ -66,7 +66,7 @@ (_.set (list (..register register)) valueO) bodyO)))) -(def: #export (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) @@ -74,7 +74,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: #export (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) @@ -84,7 +84,7 @@ then! else!)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -295,7 +295,7 @@ pattern_matching!) (_.raise (_.Exception/1 (_.string case.pattern_matching_error))))))) -(def: #export dependencies +(def: .public dependencies (-> Path (List SVar)) (|>> case.storage (get@ #case.dependencies) @@ -308,7 +308,7 @@ (#///////variable.Foreign register) (..capture register)))))) -(def: #export (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) @@ -319,7 +319,7 @@ pattern_matching! )))) -(def: #export (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] pattern_matching!] (/////generation.with_new_context archive 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 c7ff46333..0b4ecc5e6 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 @@ -31,14 +31,14 @@ [archive (#+ Archive) ["." artifact]]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) argsO+ (monad.map ! (expression archive) argsS+)] (in (_.apply/* functionO argsO+)))) -(def: #export capture +(def: .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) :assume)) @@ -66,7 +66,7 @@ (def: input (|>> inc //case.register)) -(def: #export (function statement expression archive [environment arity bodyS]) +(def: .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do {! ///////phase.monad} [[[function_module function_artifact] body!] (/////generation.with_new_context archive 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 8f4386405..b627e5c44 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 @@ -41,13 +41,13 @@ list.reversed (list\fold _.then body))) -(def: #export (set_scope body!) +(def: .public (set_scope body!) (-> (Statement Any) (Statement Any)) (_.while (_.bool true) body! #.None)) -(def: #export (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 @@ ..set_scope body!))))) -(def: #export (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,7 +106,7 @@ _ (/////generation.save! loop_artifact #.None directive)] (in (_.apply/* instantiation initsO+))))) -(def: #export (recur! statement expression archive argsS+) +(def: .public (recur! 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 60175358f..9d02d3974 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 @@ ["#." runtime]]) (template [<type> <name> <implementation>] - [(def: #export <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 eeb4604a3..b53b3ff9d 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System (Expression Any)) (def: constant _.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 b653d67b7..49507ed33 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 @@ -41,7 +41,7 @@ ["." artifact (#+ Registry)]]]]]]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> Register (Expression Any) (Statement Any)))] [Operation /////generation.Operation] @@ -50,19 +50,19 @@ [Bundle /////generation.Bundle] ) -(type: #export Phase! +(type: .public Phase! (-> Phase Archive Synthesis (Operation (Statement Any)))) -(type: #export (Generator! i) +(type: .public (Generator! i) (-> Phase! Phase Archive i (Operation (Statement Any)))) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation (Expression Any)))) (def: prefix "LuxRuntime") -(def: #export +(def: .public unit (_.unicode /////synthesis.unit)) @@ -76,25 +76,25 @@ (-> (Expression Any) (Expression Any) (Expression Any) Literal) (_.tuple (list tag last? value))) -(def: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Nat Bit (Expression Any) Literal) (variant' (_.int (.int tag)) (flag last?) value)) -(def: #export none +(def: .public none Literal (..variant 0 #0 unit)) -(def: #export some +(def: .public some (-> (Expression Any) Literal) (..variant 1 #1)) -(def: #export left +(def: .public left (-> (Expression Any) Literal) (..variant 0 #0)) -(def: #export right +(def: .public right (-> (Expression Any) Literal) (..variant 1 #1)) @@ -109,7 +109,7 @@ (-> SVar (-> SVar (Statement Any)) (Statement Any)) (definition name)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -131,7 +131,7 @@ (let [nameC (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) runtime_nameC (` (runtime_name (~ (code.text name))))] - (in (list (` (def: #export (~ nameC) SVar (~ runtime_nameC))) + (in (list (` (def: .public (~ nameC) SVar (~ runtime_nameC))) (` (def: (~ code_nameC) (Statement Any) (..feature (~ runtime_nameC) @@ -146,7 +146,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` (_.Expression Any))) inputs)] - (in (list (` (def: #export ((~ nameC) (~+ inputsC)) + (in (list (` (def: .public ((~ nameC) (~+ inputsC)) (-> (~+ inputs_typesC) (Computation Any)) (_.apply/* (~ runtime_nameC) (list (~+ inputsC))))) (` (def: (~ code_nameC) @@ -445,7 +445,7 @@ (def: module_id 0) -(def: #export generate +(def: .public generate (Operation [Registry Output]) (/////generation.with_buffer (do ///////phase.monad 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 4e7bc841d..1ab751074 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 @@ -14,7 +14,7 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple generate archive elemsS+) +(def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -28,7 +28,7 @@ (monad.map ///////phase.monad (generate archive)) (///////phase\map _.list)))) -(def: #export (variant generate archive [lefts right? valueS]) +(def: .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc lefts) 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 80171bbfb..a87076394 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 @@ -25,7 +25,7 @@ [reference (#+) [variable (#+)]]]]]]]) -(def: #export (generate archive synthesis) +(def: .public (generate archive synthesis) Phase (case synthesis (^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 dcaf7f395..87cae6c43 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 @@ -36,15 +36,15 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register SVar) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register SVar) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -54,7 +54,7 @@ (_.set! (..register register) valueO) bodyO))))) -(def: #export (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) @@ -62,7 +62,7 @@ elseO (expression archive elseS)] (in (_.if testO thenO elseO)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -229,7 +229,7 @@ (#.Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))) #.None)))) -(def: #export (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 dfdec59ce..bbfa2e83d 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,7 +32,7 @@ [archive ["." artifact]]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) @@ -71,7 +71,7 @@ (_.set! (|> register inc //case.register) (|> $curried (_.item (|> register inc .int _.int))))) -(def: #export (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 47bb19e87..32ec3b041 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 (#+ Register)]]]]]]]) -(def: #export (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: #export (recur expression archive argsS+) +(def: .public (recur 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 9b7f40e86..1d4788f77 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 @@ ["#." runtime]]) (template [<name> <type> <code>] - [(def: #export <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 18157701d..037259b8a 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 @@ -25,31 +25,31 @@ [".T" loop])) ## [Types] -(type: #export Translator +(type: .public Translator (-> ls.Synthesis (Meta Expression))) -(type: #export Proc +(type: .public Proc (-> Translator (List ls.Synthesis) (Meta Expression))) -(type: #export Bundle +(type: .public Bundle (Dict Text Proc)) (syntax: (Vector {size s.nat} elemT) (in (list (` [(~+ (list.repeat size elemT))])))) -(type: #export Nullary (-> (Vector +0 Expression) Expression)) -(type: #export Unary (-> (Vector +1 Expression) Expression)) -(type: #export Binary (-> (Vector +2 Expression) Expression)) -(type: #export Trinary (-> (Vector +3 Expression) Expression)) -(type: #export Variadic (-> (List Expression) Expression)) +(type: .public Nullary (-> (Vector +0 Expression) Expression)) +(type: .public Unary (-> (Vector +1 Expression) Expression)) +(type: .public Binary (-> (Vector +2 Expression) Expression)) +(type: .public Trinary (-> (Vector +3 Expression) Expression)) +(type: .public Variadic (-> (List Expression) Expression)) ## [Utils] -(def: #export (install name unnamed) +(def: .public (install name unnamed) (-> Text (-> Text Proc) (-> Bundle Bundle)) (dict.put name (unnamed name))) -(def: #export (prefix prefix bundle) +(def: .public (prefix prefix bundle) (-> Text Bundle Bundle) (|> bundle dict.entries @@ -66,7 +66,7 @@ (with_gensyms [g!_ g!proc g!name g!translate g!inputs] (do {@ macro.monad} [g!input+ (monad.seq @ (list.repeat arity (macro.gensym "input")))] - (in (list (` (def: #export ((~ (code.local_identifier name)) (~ g!proc)) + (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!proc)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Expression) (-> Text ..Proc)) (function ((~ g!_) (~ g!name)) @@ -88,7 +88,7 @@ (arity: binary +2) (arity: trinary +3) -(def: #export (variadic proc) +(def: .public (variadic proc) (-> Variadic (-> Text Proc)) (function (_ proc_name) (function (_ translate inputsS) @@ -111,10 +111,10 @@ Unary (runtimeT.lux//try riskyO)) -(exception: #export (Wrong_Syntax {message Text}) +(exception: .public (Wrong_Syntax {message Text}) message) -(def: #export (wrong_syntax procedure args) +(def: .public (wrong_syntax procedure args) (-> Text (List ls.Synthesis) Text) (format "Procedure: " procedure "\n" "Arguments: " (%code (code.tuple args)))) @@ -328,7 +328,7 @@ (runtimeT.io//current_time! runtimeT.unit))))))) ## [Bundles] -(def: #export 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 f97ae27e0..c99ceb072 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 @@ -81,7 +81,7 @@ ## (@.install "get" (@.binary table//get)) ## (@.install "set" (@.trinary table//set))))) -(def: #export 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 bbdb06ba0..4e518e02a 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.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 824f53012..446f2ba72 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 @@ -45,7 +45,7 @@ 0) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> _.SVar _.Expression _.Expression))] [Operation /////generation.Operation] @@ -54,10 +54,10 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(def: #export unit +(def: .public unit Expression (_.string /////synthesis.unit)) @@ -76,7 +76,7 @@ ## else (.int input))) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -100,7 +100,7 @@ (case declaration (#.Left name) (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) _.SVar (~ runtime_name))) @@ -113,7 +113,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) _.Expression) (_.apply (list (~+ inputsC)) (~ runtime_name)))) @@ -124,11 +124,11 @@ (_.function (list (~+ inputsC)) (~ code)))))))))))))) -(def: #export variant_tag_field "luxVT") -(def: #export variant_flag_field "luxVF") -(def: #export variant_value_field "luxVV") +(def: .public variant_tag_field "luxVT") +(def: .public variant_flag_field "luxVF") +(def: .public variant_value_field "luxVV") -(def: #export (flag value) +(def: .public (flag value) (-> Bit Expression) (if value (_.string "") @@ -139,25 +139,25 @@ [..variant_flag_field last?] [..variant_value_field value]))) -(def: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Nat Bit Expression Expression) (adt::variant (_.int (.int tag)) (flag last?) value)) -(def: #export none +(def: .public none Expression (variant 0 #0 ..unit)) -(def: #export some +(def: .public some (-> Expression Expression) (variant 1 #1)) -(def: #export left +(def: .public left (-> Expression Expression) (variant 0 #0)) -(def: #export right +(def: .public right (-> Expression Expression) (variant 1 #1)) @@ -174,8 +174,8 @@ (-> Expression Expression) (_.apply (list value) (_.var "as.double"))) -(def: #export i64_high_field "luxIH") -(def: #export i64_low_field "luxIL") +(def: .public i64_high_field "luxIH") +(def: .public i64_low_field "luxIL") (runtime: (i64::unsigned_low input) (with_vars [low] @@ -205,13 +205,13 @@ (-> Nat Nat) (|>> (i64.and (hex "FFFFFFFF")))) -(def: #export (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: #export (lux_i64 high low) +(def: .public (lux_i64 high low) (-> Int Int Int) (|> high (i64.left_shifted 32) @@ -227,8 +227,8 @@ [i64::max i\top] ) -(def: #export i64_high (_.item (_.string ..i64_high_field))) -(def: #export 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) @@ -839,7 +839,7 @@ runtime::io )) -(def: #export 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 4ea0f31a2..3c74989df 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 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple expression archive elemsS+) +(def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -31,7 +31,7 @@ (monad.map ///////phase.monad (expression archive)) (///////phase\map _.list)))) -(def: #export (variant expression archive [lefts right? valueS]) +(def: .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc 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 f3643d685..7ae3e429a 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 @@ -17,7 +17,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: #export universe +(def: .public universe (for {## In the case of Lua, there is a limit of 200 locals in a function's scope. @.lua (not ("lua script universe")) ## Cannot make all definitions be local variables because of limitations with JRuby. @@ -37,20 +37,20 @@ @.scheme <label>} ""))) -(def: #export (artifact [module artifact]) +(def: .public (artifact [module artifact]) (-> Context Text) (format "l" (%.nat version.version) ..universe_label "m" (%.nat module) "a" (%.nat artifact))) -(interface: #export (System expression) +(interface: .public (System expression) (: (-> Text expression) constant) (: (-> Text expression) variable)) -(def: #export (constant system archive name) +(def: .public (constant system archive name) (All [anchor expression directive] (-> (System expression) Archive Name (////generation.Operation anchor expression directive expression))) @@ -58,7 +58,7 @@ (////generation.remember archive name))) (template [<sigil> <name>] - [(def: #export (<name> system) + [(def: .public (<name> system) (All [expression] (-> (System expression) (-> Register expression))) @@ -68,7 +68,7 @@ ["l" local] ) -(def: #export (variable system variable) +(def: .public (variable system variable) (All [expression] (-> (System expression) Variable expression)) (case variable @@ -78,7 +78,7 @@ (#variable.Foreign register) (..foreign system register))) -(def: #export (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 3a80031eb..0c56f55b1 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 @@ -59,7 +59,7 @@ (//////phase\map _.return (/function.function statement expression archive abstraction)) )) -(exception: #export cannot_recur_as_an_expression) +(exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase @@ -100,6 +100,6 @@ (#////synthesis.Extension extension) (///extension.apply archive expression extension))) -(def: #export 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 18185171c..0eca3ec0b 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 @@ -36,19 +36,19 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export (gensym prefix) +(def: .public (gensym prefix) (-> Text (Operation LVar)) (///////phase\map (|>> %.nat (format prefix) _.local) /////generation.next)) -(def: #export register +(def: .public register (-> Register LVar) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register LVar) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -59,7 +59,7 @@ (_.lambda #.None (list (..register register))) (_.apply_lambda/* (list valueO)))))) -(def: #export (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) @@ -68,7 +68,7 @@ (_.set (list (..register register)) valueO) bodyO)))) -(def: #export (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) @@ -76,7 +76,7 @@ elseO (expression archive elseS)] (in (_.? testO thenO elseO)))) -(def: #export (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) @@ -86,7 +86,7 @@ then! else!)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -340,7 +340,7 @@ pattern_matching!) (_.statement (_.raise (_.string case.pattern_matching_error))))))) -(def: #export (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) @@ -351,7 +351,7 @@ pattern_matching! )))) -(def: #export (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 281ea380a..11199e5b4 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 @@ -31,14 +31,14 @@ [archive (#+ Archive) ["." artifact]]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) argsO+ (monad.map ! (expression archive) argsS+)] (in (_.apply_lambda/* argsO+ functionO)))) -(def: #export capture +(def: .public capture (-> Register LVar) (|>> (///reference.foreign //reference.system) :assume)) @@ -63,7 +63,7 @@ (def: input (|>> inc //case.register)) -(def: #export (function statement expression archive [environment arity bodyS]) +(def: .public (function statement expression archive [environment arity bodyS]) (-> Phase! (Generator (Abstraction Synthesis))) (do {! ///////phase.monad} [[[function_module function_artifact] body!] (/////generation.with_new_context archive 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 2cf1506c7..89daa0b5f 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 @@ -44,11 +44,11 @@ (def: symbol (_.symbol "lux_continue")) -(def: #export with_scope +(def: .public with_scope (-> Statement Statement) (_.while (_.bool true))) -(def: #export (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 @@ -65,7 +65,7 @@ ..with_scope body!))))) -(def: #export (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 @@ -80,7 +80,7 @@ (_.lambda #.None (list)) (_.apply_lambda/* (list))))))) -(def: #export (recur! statement expression archive argsS+) +(def: .public (recur! 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 0f01d2455..38b35b7a6 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 (#+ Literal)]]]]) (template [<type> <name> <implementation>] - [(def: #export <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 a54e6da57..827cca197 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.global) 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 989fdf220..ed17f4d1d 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 @@ -40,7 +40,7 @@ ["." artifact (#+ Registry)]]]]]]) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> Register Expression Statement))] [Operation /////generation.Operation] @@ -49,16 +49,16 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(type: #export Phase! +(type: .public Phase! (-> Phase Archive Synthesis (Operation Statement))) -(type: #export (Generator! i) +(type: .public (Generator! i) (-> Phase! Phase Archive i (Operation Statement))) -(def: #export unit +(def: .public unit (_.string /////synthesis.unit)) (def: (flag value) @@ -71,7 +71,7 @@ (-> LVar (-> LVar Statement) Statement) (definition name)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -99,7 +99,7 @@ (#.Left name) (macro.with_gensyms [g!_] (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) LVar (~ runtime_name))) + (in (list (` (def: .public (~ g!name) LVar (~ runtime_name))) (` (def: (~ (code.local_identifier (format "@" name))) Statement (..feature (~ runtime_name) @@ -112,7 +112,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) Computation) (_.apply/* (list (~+ inputsC)) (~ runtime_name)))) @@ -158,32 +158,32 @@ (_.return (_.array_range right_index (..tuple_size tuple) tuple))) ))))) -(def: #export variant_tag_field "_lux_tag") -(def: #export variant_flag_field "_lux_flag") -(def: #export 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: #export (variant tag last? value) +(def: .public (variant tag last? value) (-> Nat Bit Expression Computation) (sum//make (_.int (.int tag)) (..flag last?) value)) -(def: #export none +(def: .public none Computation (..variant 0 #0 ..unit)) -(def: #export some +(def: .public some (-> Expression Computation) (..variant 1 #1)) -(def: #export left +(def: .public left (-> Expression Computation) (..variant 0 #0)) -(def: #export right +(def: .public right (-> Expression Computation) (..variant 1 #1)) @@ -389,7 +389,7 @@ runtime//array )) -(def: #export 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 eaf6add62..f51cad8bc 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 @@ -14,7 +14,7 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple generate archive elemsS+) +(def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -28,7 +28,7 @@ (monad.map ///////phase.monad (generate archive)) (///////phase\map _.array)))) -(def: #export (variant generate archive [lefts right? valueS]) +(def: .public (variant generate archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc lefts) 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 6292d9686..c2a62c407 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 @@ -25,7 +25,7 @@ [reference (#+) [variable (#+)]]]]]]]) -(def: #export (generate archive synthesis) +(def: .public (generate archive synthesis) Phase (case synthesis (^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 25da6b501..b09071726 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 @@ -36,15 +36,15 @@ [meta [archive (#+ Archive)]]]]]]]) -(def: #export register +(def: .public register (-> Register Var) (|>> (///reference.local //reference.system) :assume)) -(def: #export capture +(def: .public capture (-> Register Var) (|>> (///reference.foreign //reference.system) :assume)) -(def: #export (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) @@ -52,7 +52,7 @@ (in (_.let (list [(..register register) valueO]) bodyO)))) -(def: #export (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) @@ -60,7 +60,7 @@ elseO (expression archive elseS)] (in (_.if testO thenO elseO)))) -(def: #export (get expression archive [pathP valueS]) +(def: .public (get expression archive [pathP valueS]) (Generator [(List Member) Synthesis]) (do ///////phase.monad [valueO (expression archive valueS)] @@ -214,7 +214,7 @@ (try_pm (_.raise/1 (_.string "Invalid expression for pattern-matching."))) (pattern_matching' expression archive pathP))) -(def: #export (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 1880d7700..17052fb88 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 @@ [/ ["." common]]) -(def: #export 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 28cf31cc1..89acab685 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 @@ -31,17 +31,17 @@ (syntax: (Vector {size s.nat} elemT) (in (list (` [(~+ (list.repeat size elemT))])))) -(type: #export Nullary (-> (Vector 0 Expression) Computation)) -(type: #export Unary (-> (Vector 1 Expression) Computation)) -(type: #export Binary (-> (Vector 2 Expression) Computation)) -(type: #export Trinary (-> (Vector 3 Expression) Computation)) -(type: #export Variadic (-> (List Expression) Computation)) +(type: .public Nullary (-> (Vector 0 Expression) Computation)) +(type: .public Unary (-> (Vector 1 Expression) Computation)) +(type: .public Binary (-> (Vector 2 Expression) Computation)) +(type: .public Trinary (-> (Vector 3 Expression) Computation)) +(type: .public Variadic (-> (List Expression) Computation)) (syntax: (arity: {name s.local_identifier} {arity s.nat}) (with_gensyms [g!_ g!extension g!name g!phase g!inputs] (do {! macro.monad} [g!input+ (monad.seq ! (list.repeat arity (macro.gensym "input")))] - (in (list (` (def: #export ((~ (code.local_identifier name)) (~ g!extension)) + (in (list (` (def: .public ((~ (code.local_identifier name)) (~ g!extension)) (-> (-> (..Vector (~ (code.nat arity)) Expression) Computation) Handler) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!inputs)) @@ -62,7 +62,7 @@ (arity: binary 2) (arity: trinary 3) -(def: #export (variadic extension) +(def: .public (variadic extension) (-> Variadic Handler) (function (_ extension_name) (function (_ phase inputsS) @@ -212,7 +212,7 @@ (bundle.install "exit" (unary _.exit/1)) (bundle.install "current-time" (nullary (function (_ _) (///runtime.io//current_time (_.string //////synthesis.unit)))))))) -(def: #export 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 7feb087f2..9998edab9 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,7 +29,7 @@ [reference [variable (#+ Register Variable)]]]]]]) -(def: #export (apply expression archive [functionS argsS+]) +(def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) (do {! ///////phase.monad} [functionO (expression archive functionS) @@ -60,7 +60,7 @@ (def: input (|>> inc //case.register)) -(def: #export (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 25b0feb46..32da9a0de 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 @@ -36,7 +36,7 @@ (def: @scope (_.var "scope")) -(def: #export (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: #export (recur expression archive argsS+) +(def: .public (recur 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 a7c2b81b6..1cb915b8e 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 (#+ Expression)]]]]) (template [<name> <type> <code>] - [(def: #export <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 19d46ba19..b44d3f887 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,7 +6,7 @@ [/// [reference (#+ System)]]) -(implementation: #export system +(implementation: .public system (System Expression) (def: constant _.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 72ec2ef27..5e17c3324 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 @@ -43,7 +43,7 @@ 0) (template [<name> <base>] - [(type: #export <name> + [(type: .public <name> (<base> Var Expression Expression))] [Operation /////generation.Operation] @@ -52,13 +52,13 @@ [Bundle /////generation.Bundle] ) -(type: #export (Generator i) +(type: .public (Generator i) (-> Phase Archive i (Operation Expression))) -(def: #export unit +(def: .public unit (_.string /////synthesis.unit)) -(syntax: #export (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} +(syntax: .public (with_vars {vars (<code>.tuple (<>.some <code>.local_identifier))} body) (do {! meta.monad} [ids (monad.seq ! (list.repeat (list.size vars) meta.seed))] @@ -82,7 +82,7 @@ (case declaration (#.Left name) (let [g!name (code.local_identifier name)] - (in (list (` (def: #export (~ g!name) + (in (list (` (def: .public (~ g!name) Var (~ runtime_name))) @@ -95,7 +95,7 @@ inputsC (list\map code.local_identifier inputs) inputs_typesC (list\map (function.constant (` _.Expression)) inputs)] - (in (list (` (def: #export ((~ g!name) (~+ inputsC)) + (in (list (` (def: .public ((~ g!name) (~+ inputsC)) (-> (~+ inputs_typesC) _.Computation) (_.apply/* (list (~+ inputsC)) (~ runtime_name)))) @@ -147,7 +147,7 @@ (runtime: (sum//make tag last? value) (variant' tag last? value)) -(def: #export (variant [lefts right? value]) +(def: .public (variant [lefts right? value]) (-> (Variant Expression) Computation) (..sum//make (_.int (.int lefts)) (_.bool right?) value)) @@ -181,19 +181,19 @@ @sum//get @sum//make))) -(def: #export none +(def: .public none Computation (|> ..unit [0 #0] variant)) -(def: #export some +(def: .public some (-> Expression Computation) (|>> [1 #1] ..variant)) -(def: #export left +(def: .public left (-> Expression Computation) (|>> [0 #0] ..variant)) -(def: #export right +(def: .public right (-> Expression Computation) (|>> [1 #1] ..variant)) @@ -356,7 +356,7 @@ runtime//array ))) -(def: #export 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 3cf04831b..ebc933d4c 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 @@ ["//#" /// #_ ["#." phase ("#\." monad)]]]]) -(def: #export (tuple expression archive elemsS+) +(def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ #.End @@ -31,7 +31,7 @@ (monad.map ///////phase.monad (expression archive)) (///////phase\map _.vector/*)))) -(def: #export (variant expression archive [lefts right? valueS]) +(def: .public (variant expression archive [lefts right? valueS]) (Generator (Variant Synthesis)) (let [tag (if right? (inc 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 306dfc48a..4adb10f57 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 @@ -97,7 +97,7 @@ (phase.run' state)))))) ))) -(def: #export (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 f6f4d746c..aa9c0a757 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 @@ -223,7 +223,7 @@ _ <failure>))))) -(def: #export (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) @@ -235,20 +235,20 @@ (#///analysis.Reference (///reference.local <output>))] (list)]) -(def: #export (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: #export (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: #export (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) @@ -260,7 +260,7 @@ (#///analysis.Reference (///reference.local <output>))] (.list)]) -(def: #export (synthesize_get synthesize archive input patterns @member) +(def: .public (synthesize_get synthesize archive input patterns @member) (-> Phase Archive Synthesis (///analysis.Tuple ///analysis.Pattern) Register (Operation Synthesis)) (case (..get patterns @member) #.End @@ -274,7 +274,7 @@ _ (///\in (/.branch/get [path input]))))) -(def: #export (synthesize synthesize^ [headB tailB+] archive inputA) +(def: .public (synthesize synthesize^ [headB tailB+] archive inputA) (-> Phase Match Phase) (do {! ///.monad} [inputS (synthesize^ archive inputA)] @@ -303,7 +303,7 @@ match (..synthesize_case synthesize^ archive inputS match)))) -(def: #export (count_pops path) +(def: .public (count_pops path) (-> Path [Nat Path]) (case path (^ (/.path/seq #/.Pop path')) @@ -313,10 +313,10 @@ _ [0 path])) -(def: #export pattern_matching_error +(def: .public pattern_matching_error "Invalid expression for pattern-matching.") -(type: #export Storage +(type: .public Storage {#bindings (Set Register) #dependencies (Set Variable)}) @@ -331,7 +331,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: #export (storage path) +(def: .public (storage path) (-> Path Storage) (loop for_path [path path 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 b19403e90..39d934d96 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 @@ -27,7 +27,7 @@ ["#/." variable (#+ Register Variable)]] ["." phase ("#\." monad)]]]]) -(exception: #export (cannot_find_foreign_variable_in_environment {foreign Register} {environment (Environment Synthesis)}) +(exception: .public (cannot_find_foreign_variable_in_environment {foreign Register} {environment (Environment Synthesis)}) (exception.report ["Foreign" (%.nat foreign)] ["Environment" (exception.listing /.%synthesis environment)])) @@ -38,14 +38,14 @@ (enum.range n.enum 1) (list\map (|>> /.variable/local)))) -(template: #export (self_reference) +(template: .public (self_reference) (/.variable/local 0)) (def: (expanded_nested_self_reference arity) (-> Arity Synthesis) (/.function/apply [(..self_reference) (arity_arguments arity)])) -(def: #export (apply phase) +(def: .public (apply phase) (-> Phase Phase) (function (_ archive exprA) (let [[funcA argsA] (////analysis.application exprA)] @@ -243,7 +243,7 @@ (#/.Primitive _) (phase\in expression))) -(def: #export (abstraction phase environment archive bodyA) +(def: .public (abstraction phase environment archive bodyA) (-> Phase (Environment Analysis) Phase) (do {! phase.monad} [currying? /.currying? 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 6e83a6a6a..23227e4df 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 @@ -18,10 +18,10 @@ ["." reference ["." variable (#+ Register Variable)]]]]) -(type: #export (Transform a) +(type: .public (Transform a) (-> a (Maybe a))) -(def: #export (register_optimization offset) +(def: .public (register_optimization offset) (-> Register (-> Register Register)) (|>> dec (n.+ offset))) @@ -180,7 +180,7 @@ (monad.map maybe.monad (recur false)) (maybe\map (|>> [name] #/.Extension)))))) -(def: #export (optimization true_loop? offset inits functionS) +(def: .public (optimization true_loop? offset inits functionS) (-> Bit Register (List Synthesis) Abstraction (Maybe [Register (List Synthesis) Synthesis])) (|> (get@ #/.body functionS) (body_optimization true_loop? offset (get@ #/.environment functionS) (get@ #/.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 db9cbdc59..7f2f025f7 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 @@ -209,7 +209,7 @@ (#.Item head tail)]))))) (template [<name>] - [(exception: #export (<name> {register Register}) + [(exception: .public (<name> {register Register}) (exception.report ["Register" (%.nat register)]))] @@ -436,7 +436,7 @@ (in [redundancy (#/.Extension name inputs)]))))) -(def: #export 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 be1eead63..af17d9e15 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -21,18 +21,18 @@ ["." descriptor (#+ Module)] ["." artifact]]]]]) -(type: #export (Program expression directive) +(type: .public (Program expression directive) (-> Context expression directive)) -(def: #export name +(def: .public name Text "") -(exception: #export (cannot_find_program {modules (List Module)}) +(exception: .public (cannot_find_program {modules (List Module)}) (exception.report ["Modules" (exception.listing %.text modules)])) -(def: #export (context archive) +(def: .public (context archive) (-> Archive (Try Context)) (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 4c930475b..212181b2d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -51,8 +51,8 @@ ["." frac]]]]]) (template: (inline: <declaration> <type> <body>) - (for {@.python (def: <declaration> <type> <body>)} - (template: <declaration> <body>))) + [(for {@.python (def: <declaration> <type> <body>)} + (template: <declaration> [<body>]))]) ## TODO: Implement "lux syntax char case!" as a custom extension. ## That way, it should be possible to obtain the char without wrapping @@ -72,7 +72,7 @@ (template [<name> <extension> <diff>] [(template: (<name> value) - (<extension> <diff> value))] + [(<extension> <diff> value)])] [!inc "lux i64 +" 1] [!inc/2 "lux i64 +" 2] @@ -80,11 +80,11 @@ ) (template: (!clip from to text) - ("lux text clip" from (n.- from to) text)) + [("lux text clip" from (n.- from to) text)]) (template [<name> <extension>] [(template: (<name> reference subject) - (<extension> reference subject))] + [(<extension> reference subject)])] [!n/= "lux i64 ="] [!i/< "lux i64 <"] @@ -92,26 +92,26 @@ (template [<name> <extension>] [(template: (<name> param subject) - (<extension> param subject))] + [(<extension> param subject)])] [!n/+ "lux i64 +"] [!n/- "lux i64 -"] ) -(type: #export Aliases +(type: .public Aliases (Dictionary Text Text)) -(def: #export no_aliases +(def: .public no_aliases Aliases (dictionary.empty text.hash)) -(def: #export prelude +(def: .public prelude .prelude_module) -(def: #export text_delimiter text.double_quote) +(def: .public text_delimiter text.double_quote) (template [<char> <definition>] - [(def: #export <definition> <char>)] + [(def: .public <definition> <char>)] ## Form delimiters ["(" open_form] @@ -144,7 +144,7 @@ ["." name_separator] ) -(exception: #export (end_of_file {module Text}) +(exception: .public (end_of_file {module Text}) (exception.report ["Module" (%.text module)])) @@ -155,7 +155,7 @@ (let [end (|> start (!n/+ amount_of_input_shown) (n.min ("lux text size" input)))] (!clip start end input))) -(exception: #export (unrecognized_input {[file line column] Location} {context Text} {input Text} {offset Offset}) +(exception: .public (unrecognized_input {[file line column] Location} {context Text} {input Text} {offset Offset}) (exception.report ["File" file] ["Line" (%.nat line)] @@ -163,44 +163,44 @@ ["Context" (%.text context)] ["Input" (input_at offset input)])) -(exception: #export (text_cannot_contain_new_lines {text Text}) +(exception: .public (text_cannot_contain_new_lines {text Text}) (exception.report ["Text" (%.text text)])) (template: (!failure parser where offset source_code) - (#.Left [[where offset source_code] - (exception.error ..unrecognized_input [where (%.name (name_of parser)) source_code offset])])) + [(#.Left [[where offset source_code] + (exception.error ..unrecognized_input [where (%.name (name_of parser)) source_code offset])])]) (template: (!end_of_file where offset source_code current_module) - (#.Left [[where offset source_code] - (exception.error ..end_of_file current_module)])) + [(#.Left [[where offset source_code] + (exception.error ..end_of_file current_module)])]) (type: (Parser a) (-> Source (Either [Source Text] [Source a]))) (template: (!with_char+ @source_code_size @source_code @offset @char @else @body) - (if (!i/< (:as Int @source_code_size) - (:as Int @offset)) - (let [@char ("lux text char" @offset @source_code)] - @body) - @else)) + [(if (!i/< (:as Int @source_code_size) + (:as Int @offset)) + (let [@char ("lux text char" @offset @source_code)] + @body) + @else)]) (template: (!with_char @source_code @offset @char @else @body) - (!with_char+ ("lux text size" @source_code) @source_code @offset @char @else @body)) + [(!with_char+ ("lux text size" @source_code) @source_code @offset @char @else @body)]) (template: (!letE <binding> <computation> <body>) - (case <computation> - (#.Right <binding>) - <body> + [(case <computation> + (#.Right <binding>) + <body> - ## (#.Left error) - <<otherwise>> - (:assume <<otherwise>>))) + ## (#.Left error) + <<otherwise>> + (:assume <<otherwise>>))]) (template: (!horizontal where offset source_code) - [(update@ #.column inc where) - (!inc offset) - source_code]) + [[(update@ #.column inc where) + (!inc offset) + source_code]]) (inline: (!new_line where) (-> Location Location) @@ -213,9 +213,9 @@ [where::file where::line (!n/+ length where::column)])) (template: (!vertical where offset source_code) - [(!new_line where) - (!inc offset) - source_code]) + [[(!new_line where) + (!inc offset) + source_code]]) (template [<name> <close> <tag>] [(inline: (<name> parse where offset source_code) @@ -257,13 +257,13 @@ (#.Left [source' error]))))) (template: (!guarantee_no_new_lines where offset source_code content body) - (case ("lux text index" 0 (static text.new_line) content) - #.None - body + [(case ("lux text index" 0 (static text.new_line) content) + #.None + body - g!_ - (#.Left [[where offset source_code] - (exception.error ..text_cannot_contain_new_lines content)]))) + g!_ + (#.Left [[where offset source_code] + (exception.error ..text_cannot_contain_new_lines content)]))]) (def: (text_parser where offset source_code) (-> Location Offset Text (Either [Source Text] [Source Code])) @@ -295,55 +295,55 @@ [..sigil]) <digit_separator> (static ..digit_separator)] (template: (!if_digit? @char @then @else) - ("lux syntax char case!" @char - [[<digits>] - @then] + [("lux syntax char case!" @char + [[<digits>] + @then] - ## else - @else)) + ## else + @else)]) (template: (!if_digit?+ @char @then @else_options @else) - (`` ("lux syntax char case!" @char - [[<digits> <digit_separator>] - @then + [(`` ("lux syntax char case!" @char + [[<digits> <digit_separator>] + @then - (~~ (template.spliced @else_options))] + (~~ (template.spliced @else_options))] - ## else - @else))) + ## else + @else))]) (`` (template: (!if_name_char?|tail @char @then @else) - ("lux syntax char case!" @char - [[<non_name_chars>] - @else] + [("lux syntax char case!" @char + [[<non_name_chars>] + @else] - ## else - @then))) + ## else + @then)])) (`` (template: (!if_name_char?|head @char @then @else) - ("lux syntax char case!" @char - [[<non_name_chars> <digits>] - @else] + [("lux syntax char case!" @char + [[<non_name_chars> <digits>] + @else] - ## else - @then))) + ## else + @then)])) ) (template: (!number_output <source_code> <start> <end> <codec> <tag>) - (case (|> <source_code> - (!clip <start> <end>) - (text.replace_all ..digit_separator "") - (\ <codec> decode)) - (#.Right output) - (#.Right [[(let [[where::file where::line where::column] where] - [where::file where::line (!n/+ (!n/- <start> <end>) where::column)]) - <end> - <source_code>] - [where (<tag> output)]]) - - (#.Left error) - (#.Left [[where <start> <source_code>] - error]))) + [(case (|> <source_code> + (!clip <start> <end>) + (text.replace_all ..digit_separator "") + (\ <codec> decode)) + (#.Right output) + (#.Right [[(let [[where::file where::line where::column] where] + [where::file where::line (!n/+ (!n/- <start> <end>) where::column)]) + <end> + <source_code>] + [where (<tag> output)]]) + + (#.Left error) + (#.Left [[where <start> <source_code>] + error]))]) (def: no_exponent Offset @@ -413,11 +413,11 @@ ) (template: (!signed_parser source_code//size offset where source_code @aliases @end) - (<| (let [g!offset/1 (!inc offset)]) - (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) - (!if_digit? g!char/1 - (signed_parser source_code//size offset where (!inc/2 offset) source_code) - (!full_name_parser offset [where (!inc offset) source_code] where @aliases #.Identifier)))) + [(<| (let [g!offset/1 (!inc offset)]) + (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) + (!if_digit? g!char/1 + (signed_parser source_code//size offset where (!inc/2 offset) source_code) + (!full_name_parser offset [where (!inc offset) source_code] where @aliases #.Identifier)))]) (with_expansions [<output> (#.Right [[(update@ #.column (|>> (!n/+ (!n/- start end))) where) end @@ -434,10 +434,10 @@ <output>)))))) (template: (!half_name_parser @offset @char @module) - (!if_name_char?|head @char - (!letE [source' name] (..name_part_parser @offset where (!inc @offset) source_code) - (#.Right [source' [@module name]])) - (!failure ..!half_name_parser where @offset source_code))) + [(!if_name_char?|head @char + (!letE [source' name] (..name_part_parser @offset where (!inc @offset) source_code) + (#.Right [source' [@module name]])) + (!failure ..!half_name_parser where @offset source_code))]) (`` (def: (short_name_parser source_code//size current_module [where offset/0 source_code]) (-> Nat Text (Parser Name)) @@ -451,8 +451,8 @@ (!half_name_parser offset/0 char/0 (static ..prelude)))))) (template: (!short_name_parser source_code//size @current_module @source @where @tag) - (!letE [source' name] (..short_name_parser source_code//size @current_module @source) - (#.Right [source' [@where (@tag name)]]))) + [(!letE [source' name] (..short_name_parser source_code//size @current_module @source) + (#.Right [source' [@where (@tag name)]]))]) (with_expansions [<simple> (as_is (#.Right [source' ["" simple]]))] (`` (def: (full_name_parser aliases start source) @@ -474,8 +474,8 @@ <simple>))))) (template: (!full_name_parser @offset @source @where @aliases @tag) - (!letE [source' full_name] (..full_name_parser @aliases @offset @source) - (#.Right [source' [@where (@tag full_name)]]))) + [(!letE [source' full_name] (..full_name_parser @aliases @offset @source) + (#.Right [source' [@where (@tag full_name)]]))]) ## TODO: Grammar macro for specifying syntax. ## (grammar: lux_grammar @@ -488,7 +488,7 @@ <recur> (as_is (parse current_module aliases source_code//size))] (template: (!close closer) - (#.Left [<move_1> closer])) + [(#.Left [<move_1> closer])]) (def: (bit_syntax value [where offset/0 source_code]) (-> Bit (Parser Code)) @@ -497,7 +497,7 @@ source_code] [where (#.Bit value)]])) - (def: #export (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 d5a1e53a4..3112e5b74 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -34,43 +34,43 @@ ["." reference (#+ Reference) ["." variable (#+ Register Variable)]]]]) -(type: #export Resolver +(type: .public Resolver (Dictionary Variable Variable)) -(type: #export State +(type: .public State {#locals Nat ## https://en.wikipedia.org/wiki/Currying #currying? Bit}) -(def: #export fresh_resolver +(def: .public fresh_resolver Resolver (dictionary.empty variable.hash)) -(def: #export init +(def: .public init State {#locals 0 #currying? false}) -(type: #export Primitive +(type: .public Primitive (#Bit Bit) (#I64 (I64 Any)) (#F64 Frac) (#Text Text)) -(type: #export Side +(type: .public Side (Either Nat Nat)) -(type: #export Member +(type: .public Member (Either Nat Nat)) -(type: #export Access +(type: .public Access (#Side Side) (#Member Member)) -(type: #export (Fork value next) +(type: .public (Fork value next) [[value next] (List [value next])]) -(type: #export (Path' s) +(type: .public (Path' s) #Pop (#Access Access) (#Bind Register) @@ -82,40 +82,40 @@ (#Seq (Path' s) (Path' s)) (#Then s)) -(type: #export (Abstraction' s) +(type: .public (Abstraction' s) {#environment (Environment s) #arity Arity #body s}) -(type: #export (Apply' s) +(type: .public (Apply' s) {#function s #arguments (List s)}) -(type: #export (Branch s) +(type: .public (Branch s) (#Let s Register s) (#If s s s) (#Get (List Member) s) (#Case s (Path' s))) -(type: #export (Scope s) +(type: .public (Scope s) {#start Register #inits (List s) #iteration s}) -(type: #export (Loop s) +(type: .public (Loop s) (#Scope (Scope s)) (#Recur (List s))) -(type: #export (Function s) +(type: .public (Function s) (#Abstraction (Abstraction' s)) (#Apply s (List s))) -(type: #export (Control s) +(type: .public (Control s) (#Branch (Branch s)) (#Loop (Loop s)) (#Function (Function s))) -(type: #export #rec Synthesis +(type: .public #rec Synthesis (#Primitive Primitive) (#Structure (Composite Synthesis)) (#Reference Reference) @@ -123,7 +123,7 @@ (#Extension (Extension Synthesis))) (template [<special> <general>] - [(type: #export <special> + [(type: .public <special> (<general> ..State Analysis Synthesis))] [State+ extension.State] @@ -133,29 +133,29 @@ [Bundle extension.Bundle] ) -(type: #export Path +(type: .public Path (Path' Synthesis)) -(def: #export path/pop +(def: .public path/pop Path #Pop) (template [<name> <kind>] - [(template: #export (<name> content) - (.<| #..Access - <kind> - content))] + [(template: .public (<name> content) + [(.<| #..Access + <kind> + content)])] [path/side #..Side] [path/member #..Member] ) (template [<name> <kind> <side>] - [(template: #export (<name> content) - (.<| #..Access - <kind> - <side> - content))] + [(template: .public (<name> content) + [(.<| #..Access + <kind> + <side> + content)])] [side/left #..Side #.Left] [side/right #..Side #.Right] @@ -164,35 +164,35 @@ ) (template [<name> <tag>] - [(template: #export (<name> content) - (<tag> content))] + [(template: .public (<name> content) + [(<tag> content)])] [path/bind #..Bind] [path/then #..Then] ) (template [<name> <tag>] - [(template: #export (<name> left right) - (<tag> [left right]))] + [(template: .public (<name> left right) + [(<tag> [left right])])] [path/alt #..Alt] [path/seq #..Seq] ) -(type: #export Abstraction +(type: .public Abstraction (Abstraction' Synthesis)) -(type: #export Apply +(type: .public Apply (Apply' Synthesis)) -(def: #export unit Text "") +(def: .public unit Text "") (template [<with> <query> <tag> <type>] - [(def: #export (<with> value) + [(def: .public (<with> value) (-> <type> (All [a] (-> (Operation a) (Operation a)))) (extension.temporary (set@ <tag> value))) - (def: #export <query> + (def: .public <query> (Operation <type>) (extension.read (get@ <tag>)))] @@ -200,15 +200,15 @@ [with_currying? currying? #currying? Bit] ) -(def: #export with_new_local +(def: .public with_new_local (All [a] (-> (Operation a) (Operation a))) (<<| (do phase.monad [locals ..locals]) (..with_locals (inc locals)))) (template [<name> <tag>] - [(template: #export (<name> content) - (#..Primitive (<tag> content)))] + [(template: .public (<name> content) + [(#..Primitive (<tag> content))])] [bit #..Bit] [i64 #..I64] @@ -217,20 +217,20 @@ ) (template [<name> <tag>] - [(template: #export (<name> content) - (<| #..Structure - <tag> - content))] + [(template: .public (<name> content) + [(<| #..Structure + <tag> + content)])] [variant #analysis.Variant] [tuple #analysis.Tuple] ) (template [<name> <tag>] - [(template: #export (<name> content) - (.<| #..Reference - <tag> - content))] + [(template: .public (<name> content) + [(.<| #..Reference + <tag> + content)])] [variable reference.variable] [constant reference.constant] @@ -239,11 +239,11 @@ ) (template [<name> <family> <tag>] - [(template: #export (<name> content) - (.<| #..Control - <family> - <tag> - content))] + [(template: .public (<name> content) + [(.<| #..Control + <family> + <tag> + content)])] [branch/case #..Branch #..Case] [branch/let #..Branch #..Let] @@ -257,7 +257,7 @@ [function/apply #..Function #..Apply] ) -(def: #export (%path' %then value) +(def: .public (%path' %then value) (All [a] (-> (Format a) (Format (Path' a)))) (case value #Pop @@ -316,7 +316,7 @@ (|> (%then then) (text.enclosed ["(! " ")"])))) -(def: #export (%synthesis value) +(def: .public (%synthesis value) (Format Synthesis) (case value (#Primitive primitive) @@ -409,11 +409,11 @@ (format (%.text name) " ") (text.enclosed ["(" ")"])))) -(def: #export %path +(def: .public %path (Format Path) (%path' %synthesis)) -(implementation: #export primitive_equivalence +(implementation: .public primitive_equivalence (Equivalence Primitive) (def: (= reference sample) @@ -457,7 +457,7 @@ (Hash Member) (sum.hash n.hash n.hash)) -(implementation: #export access_equivalence +(implementation: .public access_equivalence (Equivalence Access) (def: (= reference sample) @@ -485,7 +485,7 @@ ([#Side] [#Member]))))) -(implementation: #export (path'_equivalence equivalence) +(implementation: .public (path'_equivalence equivalence) (All [a] (-> (Equivalence a) (Equivalence (Path' a)))) (def: (= reference sample) @@ -740,7 +740,7 @@ [5 #Function ..function_hash]) ))) -(implementation: #export equivalence +(implementation: .public equivalence (Equivalence Synthesis) (def: (= reference sample) @@ -757,11 +757,11 @@ _ false))) -(def: #export path_equivalence +(def: .public path_equivalence (Equivalence Path) (path'_equivalence equivalence)) -(implementation: #export hash +(implementation: .public hash (Hash Synthesis) (def: &equivalence ..equivalence) @@ -778,17 +778,17 @@ [#Control (..control_hash recur_hash)] [#Extension (extension.hash recur_hash)]))))) -(template: #export (!bind_top register thenP) - ($_ ..path/seq - (#..Bind register) - #..Pop - thenP)) +(template: .public (!bind_top register thenP) + [($_ ..path/seq + (#..Bind register) + #..Pop + thenP)]) -(template: #export (!multi_pop nextP) - ($_ ..path/seq - #..Pop - #..Pop - nextP)) +(template: .public (!multi_pop nextP) + [($_ ..path/seq + #..Pop + #..Pop + nextP)]) ## TODO: There are sister patterns to the simple side checks for tuples. ## These correspond to the situation where tuple members are accessed @@ -798,11 +798,11 @@ ## pattern-optimizations again, since a lot of BINDs will become POPs ## and thus will result in useless code being generated. (template [<name> <side>] - [(template: #export (<name> idx nextP) - ($_ ..path/seq - (<side> idx) - #..Pop - nextP))] + [(template: .public (<name> idx nextP) + [($_ ..path/seq + (<side> idx) + #..Pop + nextP)])] [simple_left_side ..side/left] [simple_right_side ..side/right] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux index dd3676068..1ad0a00b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/version.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/version.lux @@ -4,6 +4,6 @@ [//// [version (#+ Version)]]) -(def: #export version +(def: .public version Version 00,06,00) diff --git a/stdlib/source/library/lux/tool/compiler/meta.lux b/stdlib/source/library/lux/tool/compiler/meta.lux index 23cacb4aa..2d61d0c94 100644 --- a/stdlib/source/library/lux/tool/compiler/meta.lux +++ b/stdlib/source/library/lux/tool/compiler/meta.lux @@ -4,6 +4,6 @@ [// [version (#+ Version)]]) -(def: #export version +(def: .public version Version 00,01,00) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index cd6b245ee..8efda7f03 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -38,16 +38,16 @@ [/// [version (#+ Version)]]]) -(type: #export Output +(type: .public Output (Row [artifact.ID (Maybe Text) Binary])) -(exception: #export (unknown_document {module Module} +(exception: .public (unknown_document {module Module} {known_modules (List Module)}) (exception.report ["Module" (%.text module)] ["Known Modules" (exception.listing %.text known_modules)])) -(exception: #export (cannot_replace_document {module Module} +(exception: .public (cannot_replace_document {module Module} {old (Document Any)} {new (Document Any)}) (exception.report @@ -55,26 +55,28 @@ ["Old key" (signature.description (document.signature old))] ["New key" (signature.description (document.signature new))])) -(exception: #export (module_has_already_been_reserved {module Module}) +(exception: .public (module_has_already_been_reserved {module Module}) (exception.report ["Module" (%.text module)])) -(exception: #export (module_must_be_reserved_before_it_can_be_added {module Module}) +(exception: .public (module_must_be_reserved_before_it_can_be_added {module Module}) (exception.report ["Module" (%.text module)])) -(exception: #export (module_is_only_reserved {module Module}) +(exception: .public (module_is_only_reserved {module Module}) (exception.report ["Module" (%.text module)])) -(type: #export ID +(type: .public ID Nat) -(def: #export runtime_module +(def: .public runtime_module Module "") -(abstract: #export Archive +(abstract: .public Archive + {} + {#next ID #resolver (Dictionary Module [ID (Maybe [Descriptor (Document Any) Output])])} @@ -82,12 +84,12 @@ (-> Archive ID) (|>> :representation (get@ #next))) - (def: #export empty + (def: .public empty Archive (:abstraction {#next 0 #resolver (dictionary.empty text.hash)})) - (def: #export (id module archive) + (def: .public (id module archive) (-> Module Archive (Try ID)) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.get module resolver) @@ -98,7 +100,7 @@ (exception.except ..unknown_document [module (dictionary.keys resolver)])))) - (def: #export (reserve module archive) + (def: .public (reserve module archive) (-> Module Archive (Try [ID Archive])) (let [(^slots [#..next #..resolver]) (:representation archive)] (case (dictionary.get module resolver) @@ -113,7 +115,7 @@ (update@ #..next inc) :abstraction)])))) - (def: #export (add module [descriptor document output] archive) + (def: .public (add module [descriptor document output] archive) (-> Module [Descriptor (Document Any) Output] Archive (Try Archive)) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.get module resolver) @@ -132,7 +134,7 @@ #.None (exception.except ..module_must_be_reserved_before_it_can_be_added [module])))) - (def: #export (find module archive) + (def: .public (find module archive) (-> Module Archive (Try [Descriptor (Document Any) Output])) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.get module resolver) @@ -146,7 +148,7 @@ (exception.except ..unknown_document [module (dictionary.keys resolver)])))) - (def: #export (archived? archive module) + (def: .public (archived? archive module) (-> Archive Module Bit) (case (..find module archive) (#try.Success _) @@ -155,7 +157,7 @@ (#try.Failure _) bit.no)) - (def: #export archived + (def: .public archived (-> Archive (List Module)) (|>> :representation (get@ #resolver) @@ -165,7 +167,7 @@ (#.Some _) (#.Some module) #.None #.None))))) - (def: #export (reserved? archive module) + (def: .public (reserved? archive module) (-> Archive Module Bit) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.get module resolver) @@ -175,13 +177,13 @@ #.None bit.no))) - (def: #export reserved + (def: .public reserved (-> Archive (List Module)) (|>> :representation (get@ #resolver) dictionary.keys)) - (def: #export reservations + (def: .public reservations (-> Archive (List [Module ID])) (|>> :representation (get@ #resolver) @@ -189,7 +191,7 @@ (list\map (function (_ [module [id _]]) [module id])))) - (def: #export (merged additions archive) + (def: .public (merged additions archive) (-> Archive Archive Archive) (let [[+next +resolver] (:representation additions)] (|> archive @@ -227,7 +229,7 @@ binary.nat (binary.list (binary.and binary.text binary.nat)))) - (def: #export (export version archive) + (def: .public (export version archive) (-> Version Archive Binary) (let [(^slots [#..next #..resolver]) (:representation archive)] (|> resolver @@ -239,12 +241,12 @@ [version next] (binary.run ..writer)))) - (exception: #export (version_mismatch {expected Version} {actual Version}) + (exception: .public (version_mismatch {expected Version} {actual Version}) (exception.report ["Expected" (%.nat expected)] ["Actual" (%.nat actual)])) - (exception: #export corrupt_data) + (exception: .public corrupt_data) (def: (correct_modules? reservations) (-> (List Reservation) Bit) @@ -267,7 +269,7 @@ (and (correct_modules? reservations) (correct_ids? reservations))) - (def: #export (import expected binary) + (def: .public (import expected binary) (-> Version Binary (Try Archive)) (do try.monad [[actual next reservations] (<binary>.run ..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 cab4eb2d3..11aa363fd 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -21,10 +21,10 @@ [type abstract]]]) -(type: #export ID +(type: .public ID Nat) -(type: #export Category +(type: .public Category #Anonymous (#Definition Text) (#Analyser Text) @@ -33,20 +33,22 @@ (#Directive Text) (#Custom Text)) -(type: #export Artifact +(type: .public Artifact {#id ID #category Category}) -(abstract: #export Registry +(abstract: .public Registry + {} + {#artifacts (Row Artifact) #resolver (Dictionary Text ID)} - (def: #export empty + (def: .public empty Registry (:abstraction {#artifacts row.empty #resolver (dictionary.empty text.hash)})) - (def: #export artifacts + (def: .public artifacts (-> Registry (Row Artifact)) (|>> :representation (get@ #artifacts))) @@ -54,7 +56,7 @@ (-> Registry ID) (|>> ..artifacts row.size)) - (def: #export (resource registry) + (def: .public (resource registry) (-> Registry [ID Registry]) (let [id (..next registry)] [id @@ -65,7 +67,7 @@ :abstraction)])) (template [<tag> <create> <fetch>] - [(def: #export (<create> name registry) + [(def: .public (<create> name registry) (-> Text Registry [ID Registry]) (let [id (..next registry)] [id @@ -76,7 +78,7 @@ (update@ #resolver (dictionary.put name id)) :abstraction)])) - (def: #export (<fetch> registry) + (def: .public (<fetch> registry) (-> Registry (List Text)) (|> registry :representation @@ -94,13 +96,13 @@ [#Custom custom customs] ) - (def: #export (remember name registry) + (def: .public (remember name registry) (-> Text Registry (Maybe ID)) (|> (:representation registry) (get@ #resolver) (dictionary.get name))) - (def: #export writer + (def: .public writer (Writer Registry) (let [category (: (Writer Category) (function (_ value) @@ -121,11 +123,11 @@ (row\map (get@ #category)) artifacts))) - (exception: #export (invalid_category {tag Nat}) + (exception: .public (invalid_category {tag Nat}) (exception.report ["Tag" (%.nat tag)])) - (def: #export parser + (def: .public parser (Parser Registry) (let [category (: (Parser Category) (do {! <>.monad} diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux index 08d1af30f..59f1981bc 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux @@ -15,10 +15,10 @@ [// ["." artifact (#+ Registry)]]) -(type: #export Module +(type: .public Module Text) -(type: #export Descriptor +(type: .public Descriptor {#name Module #file Path #hash Nat @@ -26,7 +26,7 @@ #references (Set Module) #registry Registry}) -(def: #export writer +(def: .public writer (Writer Descriptor) ($_ binary.and binary.text @@ -37,7 +37,7 @@ artifact.writer )) -(def: #export parser +(def: .public parser (Parser Descriptor) ($_ <>.and <b>.text diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index b8af027c1..d9f12d482 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -20,16 +20,18 @@ ["." key (#+ Key)] [descriptor (#+ Module)]]) -(exception: #export (invalid_signature {expected Signature} {actual Signature}) +(exception: .public (invalid_signature {expected Signature} {actual Signature}) (exception.report ["Expected" (signature.description expected)] ["Actual" (signature.description actual)])) -(abstract: #export (Document d) +(abstract: .public (Document d) + {} + {#signature Signature #content d} - (def: #export (read key document) + (def: .public (read key document) (All [d] (-> (Key d) (Document Any) (Try d))) (let [[document//signature document//content] (:representation document)] (if (\ signature.equivalence = @@ -44,28 +46,28 @@ (exception.except ..invalid_signature [(key.signature key) document//signature])))) - (def: #export (write key content) + (def: .public (write key content) (All [d] (-> (Key d) d (Document d))) (:abstraction {#signature (key.signature key) #content content})) - (def: #export (check key document) + (def: .public (check key document) (All [d] (-> (Key d) (Document Any) (Try (Document d)))) (do try.monad [_ (..read key document)] (in (:assume document)))) - (def: #export signature + (def: .public signature (-> (Document Any) Signature) (|>> :representation (get@ #signature))) - (def: #export (writer content) + (def: .public (writer content) (All [d] (-> (Writer d) (Writer (Document d)))) (let [writer (binary.and signature.writer content)] (|>> :representation writer))) - (def: #export parser + (def: .public parser (All [d] (-> (Parser d) (Parser (Document d)))) (|>> (<>.and signature.parser) (\ <>.monad map (|>> :abstraction)))) 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 ec6439aa7..41de7eba0 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux @@ -6,14 +6,16 @@ [// [signature (#+ Signature)]]) -(abstract: #export (Key k) +(abstract: .public (Key k) + {} + Signature - (def: #export signature + (def: .public signature (-> (Key Any) Signature) (|>> :representation)) - (def: #export (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/signature.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux index e39bb2144..bc413b413 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/signature.lux @@ -19,24 +19,24 @@ [//// [version (#+ Version)]]) -(type: #export Signature +(type: .public Signature {#name Name #version Version}) -(def: #export equivalence +(def: .public equivalence (Equivalence Signature) (product.equivalence name.equivalence nat.equivalence)) -(def: #export (description signature) +(def: .public (description signature) (-> Signature Text) (format (%.name (get@ #name signature)) " " (%.nat (get@ #version signature)))) -(def: #export writer +(def: .public writer (Writer Signature) (binary.and (binary.and binary.text binary.text) binary.nat)) -(def: #export parser +(def: .public parser (Parser Signature) (<>.and (<>.and <b>.text <b>.text) <b>.nat)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux index ecce5c337..4a9773f6c 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -29,14 +29,14 @@ Ancestry (set.empty text.hash)) -(type: #export Graph +(type: .public Graph (Dictionary Module Ancestry)) (def: empty Graph (dictionary.empty text.hash)) -(def: #export modules +(def: .public modules (-> Graph (List Module)) dictionary.keys) @@ -44,7 +44,7 @@ {#module Module #imports Ancestry}) -(def: #export graph +(def: .public graph (-> (List Dependency) Graph) (list\fold (function (_ [module imports] graph) (dictionary.put module imports graph)) @@ -79,10 +79,10 @@ (maybe.else ..fresh))] (set.member? target_ancestry source))) -(type: #export Order +(type: .public Order (List [Module [archive.ID [Descriptor (Document .Module) Output]]])) -(def: #export (load_order key archive) +(def: .public (load_order key archive) (-> (Key .Module) Archive (Try Order)) (let [ancestry (..ancestry archive)] (|> ancestry diff --git a/stdlib/source/library/lux/tool/compiler/meta/io.lux b/stdlib/source/library/lux/tool/compiler/meta/io.lux index 8802d00bd..5aa0d7331 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io.lux @@ -6,15 +6,15 @@ [world [file (#+ Path System)]]]]) -(type: #export Context +(type: .public Context Path) -(type: #export Code +(type: .public Code Text) -(def: #export (safe system) +(def: .public (safe system) (All [m] (-> (System m) Text Text)) (text.replace_all "/" (\ system separator))) -(def: #export lux_context +(def: .public lux_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 125360e58..21d657352 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -51,7 +51,7 @@ ["." directive] ["#/." program]]]]]]) -(exception: #export (cannot_prepare {archive file.Path} +(exception: .public (cannot_prepare {archive file.Path} {module_id archive.ID} {error Text}) (exception.report @@ -83,7 +83,7 @@ (\ fs separator) (%.nat module_id))) -(def: #export (artifact fs static module_id artifact_id) +(def: .public (artifact fs static module_id artifact_id) (All [!] (-> (file.System !) Static archive.ID artifact.ID file.Path)) (format (..module fs static module_id) (\ fs separator) @@ -98,7 +98,7 @@ (in (#try.Success [])) (\ fs make_directory path)))) -(def: #export (prepare fs static module_id) +(def: .public (prepare fs static module_id) (-> (file.System Async) Static archive.ID (Async (Try Any))) (do {! async.monad} [.let [module (..module fs static module_id)] @@ -118,11 +118,11 @@ module_id error]))))))))) -(def: #export (write fs static module_id artifact_id content) +(def: .public (write fs static module_id artifact_id content) (-> (file.System Async) Static archive.ID artifact.ID Binary (Async (Try Any))) (\ fs write content (..artifact fs static module_id artifact_id))) -(def: #export (enable fs static) +(def: .public (enable fs static) (-> (file.System Async) Static (Async (Try Any))) (do (try.with async.monad) [_ (..ensure_directory fs (get@ #static.target static))] @@ -134,7 +134,7 @@ (\ fs separator) "general_descriptor")) -(def: #export (freeze fs static archive) +(def: .public (freeze fs static archive) (-> (file.System Async) Static Archive (Async (Try Any))) (\ fs write (archive.export ///.version archive) (..general_descriptor fs static))) @@ -147,7 +147,7 @@ (\ fs separator) ..module_descriptor_file)) -(def: #export (cache fs static module_id content) +(def: .public (cache fs static module_id content) (-> (file.System Async) Static archive.ID Binary (Async (Try Any))) (\ fs write content (..module_descriptor fs static module_id))) @@ -459,7 +459,7 @@ ..empty_bundles loaded_caches)]))))) -(def: #export (thaw host_environment fs static import contexts) +(def: .public (thaw host_environment fs static import contexts) (All [expression directive] (-> (generation.Host expression directive) (file.System Async) Static 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 e049ef8b5..81ac25578 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -29,23 +29,23 @@ [descriptor (#+ Module)]] ["/#" // (#+ Input)]]]) -(exception: #export (cannot_find_module {importer Module} {module Module}) +(exception: .public (cannot_find_module {importer Module} {module Module}) (exception.report ["Module" (%.text module)] ["Importer" (%.text importer)])) -(exception: #export (cannot_read_module {module Module}) +(exception: .public (cannot_read_module {module Module}) (exception.report ["Module" (%.text module)])) -(type: #export Extension +(type: .public Extension Text) (def: lux_extension Extension ".lux") -(def: #export (path fs context module) +(def: .public (path fs context module) (All [m] (-> (file.System m) Context Module file.Path)) (|> module (//.safe fs) @@ -120,7 +120,7 @@ (#try.Failure _) (in (..find_library_source_file importer import partial_host_extension module))))) -(def: #export (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) @@ -135,7 +135,7 @@ (#try.Failure _) (async\in (exception.except ..cannot_read_module [module]))))) -(type: #export Enumeration +(type: .public Enumeration (Dictionary file.Path Binary)) (def: (context_listing fs directory enumeration) @@ -159,7 +159,7 @@ (def: Action (type (All [a] (Async (Try a))))) -(def: #export (listing fs contexts) +(def: .public (listing fs contexts) (-> (file.System Async) (List Context) (Action Enumeration)) (monad.fold (: (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 07ac4be8c..21c15d551 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux @@ -22,16 +22,16 @@ [lux [generation (#+ Context)]]]]]) -(type: #export Packager +(type: .public Packager (-> (Dictionary file.Path Binary) Archive Context (Try Binary))) -(type: #export Order +(type: .public Order (List [archive.ID (List artifact.ID)])) -(def: #export order +(def: .public order (-> dependency.Order Order) (list\map (function (_ [module [module_id [descriptor document]]]) (|> descriptor 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 c138ef6ce..bf5ed12f9 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -242,7 +242,7 @@ duplicates sink)))))))) -(def: #export (package static) +(def: .public (package static) (-> Static Packager) (function (_ host_dependencies archive program) (do {! try.monad} 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 081a43829..ee2dd3415 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -116,7 +116,7 @@ module_file (tar.path (..module_file module_id))] (in (#tar.Normal [module_file now ..mode ..ownership entry_content])))) -(def: #export (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 0f3f33a29..28f8a3f28 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -54,7 +54,7 @@ (sequence so_far))))) so_far))) -(def: #export (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 cfae348ce..73aef8bcd 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -24,41 +24,41 @@ [meta [archive (#+ Archive)]]]) -(type: #export (Operation s o) +(type: .public (Operation s o) (state.+State Try s o)) -(def: #export monad +(def: .public monad (All [s] (Monad (Operation s))) (state.with try.monad)) -(type: #export (Phase s i o) +(type: .public (Phase s i o) (-> Archive i (Operation s o))) -(def: #export (run' state operation) +(def: .public (run' state operation) (All [s o] (-> s (Operation s o) (Try [s o]))) (operation state)) -(def: #export (run state operation) +(def: .public (run state operation) (All [s o] (-> s (Operation s o) (Try o))) (|> state operation (\ try.monad map product.right))) -(def: #export get_state +(def: .public get_state (All [s o] (Operation s s)) (function (_ state) (#try.Success [state state]))) -(def: #export (set_state state) +(def: .public (set_state state) (All [s o] (-> s (Operation s Any))) (function (_ _) (#try.Success [state []]))) -(def: #export (sub [get set] operation) +(def: .public (sub [get set] operation) (All [s s' o] (-> [(-> s s') (-> s' s s)] (Operation s' o) @@ -68,30 +68,30 @@ [[state' output] (operation (get state))] (in [(set state' state) output])))) -(def: #export failure +(def: .public failure (-> Text Operation) (|>> #try.Failure (state.lift try.monad))) -(def: #export (except exception parameters) +(def: .public (except exception parameters) (All [e] (-> (Exception e) e Operation)) (..failure (ex.error exception parameters))) -(def: #export (lift error) +(def: .public (lift error) (All [s a] (-> (Try a) (Operation s a))) (function (_ state) (try\map (|>> [state]) error))) -(syntax: #export (assertion exception message test) +(syntax: .public (assertion exception message test) (in (list (` (if (~ test) (\ ..monad (~' in) []) (..except (~ exception) (~ message))))))) -(def: #export identity +(def: .public identity (All [s a] (Phase s a a)) (function (_ archive input state) (#try.Success [state input]))) -(def: #export (compose pre post) +(def: .public (compose pre post) (All [s0 s1 i t o] (-> (Phase s0 i t) (Phase s1 t o) @@ -102,7 +102,7 @@ [post/state' output] (post archive temp post/state)] (in [[pre/state' post/state'] output])))) -(def: #export (timed definition description operation) +(def: .public (timed definition description operation) (All [s a] (-> Name Text (Operation s a) (Operation s a))) (do ..monad diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 8823b29e2..e8714bb2a 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -1,6 +1,6 @@ (.module: [library - [lux #* + [lux (#- local) [abstract [equivalence (#+ Equivalence)] [hash (#+ Hash)]] @@ -16,14 +16,14 @@ ["." / #_ ["#." variable (#+ Variable)]]) -(type: #export Constant +(type: .public Constant Name) -(type: #export Reference +(type: .public Reference (#Variable Variable) (#Constant Constant)) -(implementation: #export equivalence +(implementation: .public equivalence (Equivalence Reference) (def: (= reference sample) @@ -37,7 +37,7 @@ _ false))) -(implementation: #export hash +(implementation: .public hash (Hash Reference) (def: &equivalence @@ -54,29 +54,29 @@ ))) (template [<name> <family> <tag>] - [(template: #export (<name> content) - (<| <family> - <tag> - content))] + [(template: .public (<name> content) + [(<| <family> + <tag> + content)])] [local #..Variable #/variable.Local] [foreign #..Variable #/variable.Foreign] ) (template [<name> <tag>] - [(template: #export (<name> content) - (<| <tag> - content))] + [(template: .public (<name> content) + [(<| <tag> + content)])] [variable #..Variable] [constant #..Constant] ) -(def: #export self +(def: .public self Reference (..local 0)) -(def: #export format +(def: .public format (Format Reference) (|>> (case> (#Variable variable) (/variable.format variable) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index a8ce4c049..c45c5239b 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -14,14 +14,14 @@ ["n" nat] ["i" int]]]]]) -(type: #export Register +(type: .public Register Nat) -(type: #export Variable +(type: .public Variable (#Local Register) (#Foreign Register)) -(implementation: #export equivalence +(implementation: .public equivalence (Equivalence Variable) (def: (= reference sample) @@ -34,7 +34,7 @@ _ #0))) -(implementation: #export hash +(implementation: .public hash (Hash Variable) (def: &equivalence @@ -48,10 +48,10 @@ ([2 #Local] [3 #Foreign]))))) -(template: #export (self) - (#..Local 0)) +(template: .public (self) + [(#..Local 0)]) -(def: #export self? +(def: .public self? (-> Variable Bit) (|>> (case> (^ (..self)) true @@ -59,7 +59,7 @@ _ false))) -(def: #export format +(def: .public format (Format Variable) (|>> (case> (#Local local) (%.format "+" (%.nat local)) diff --git a/stdlib/source/library/lux/tool/compiler/version.lux b/stdlib/source/library/lux/tool/compiler/version.lux index 733b86477..4d34cab77 100644 --- a/stdlib/source/library/lux/tool/compiler/version.lux +++ b/stdlib/source/library/lux/tool/compiler/version.lux @@ -8,7 +8,7 @@ [number ["n" nat]]]]]) -(type: #export Version +(type: .public Version Nat) (def: range 100) @@ -23,15 +23,15 @@ (def: next (n./ ..range)) -(def: #export patch +(def: .public patch (-> Version Nat) (|>> ..current ..level)) -(def: #export minor +(def: .public minor (-> Version Nat) (|>> ..next ..level)) -(def: #export major +(def: .public major (-> Version Nat) (|>> ..next ..next ..level)) @@ -43,7 +43,7 @@ (%.format "0" (%.nat value)) (%.nat value))) -(def: #export (format version) +(def: .public (format version) (%.Format Version) (%.format (..padded (..major version)) ..separator |