diff options
author | Eduardo Julian | 2021-09-12 00:07:08 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-09-12 00:07:08 -0400 |
commit | dda05bca0956af5e5b3875c4cc36e61aa04772e4 (patch) | |
tree | 0f8b27697d58ab5c8e41aba7c7c9f769d3800767 /stdlib/source/library/lux/tool/compiler | |
parent | d48270f43c404ba19ca04da2553455ecaaf2caba (diff) |
Made the "#" character great again!
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
127 files changed, 2003 insertions, 2003 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index a43b9a4d9..d583a072a 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -67,12 +67,12 @@ analysis_state [(analysisE.bundle eval host_analysis) (///analysis.state (///analysis.info ///version.version target))]] [extension.empty - [#///directive.analysis [#///directive.state analysis_state - #///directive.phase (analysisP.phase expander)] - #///directive.synthesis [#///directive.state synthesis_state - #///directive.phase synthesisP.phase] - #///directive.generation [#///directive.state generation_state - #///directive.phase generate]]])) + [///directive.#analysis [///directive.#state analysis_state + ///directive.#phase (analysisP.phase expander)] + ///directive.#synthesis [///directive.#state synthesis_state + ///directive.#phase synthesisP.phase] + ///directive.#generation [///directive.#state generation_state + ///directive.#phase generate]]])) (def: .public (with_default_directives expander host_analysis program anchorT,expressionT,directiveT extender) (All (_ anchor expression directive) @@ -94,21 +94,21 @@ (def: (reader current_module aliases [location offset source_code]) (-> Module Aliases Source (///analysis.Operation Reader)) (function (_ [bundle state]) - {#try.Success [[bundle state] + {try.#Success [[bundle state] (///syntax.parse current_module aliases ("lux text size" source_code))]})) (def: (read source reader) (-> Source Reader (///analysis.Operation [Source Code])) (function (_ [bundle compiler]) (case (reader source) - {#.Left [source' error]} - {#try.Failure error} + {.#Left [source' error]} + {try.#Failure error} - {#.Right [source' output]} + {.#Right [source' output]} (let [[location _] output] - {#try.Success [[bundle (|> compiler - (with@ #.source source') - (with@ #.location location))] + {try.#Success [[bundle (|> compiler + (with@ .#source source') + (with@ .#location location))] [source' output]]})))) (type: (Operation a) @@ -125,13 +125,13 @@ (///directive.Operation anchor expression directive [Source (Payload directive)]))) (do ///phase.monad - [.let [module (value@ #///.module input)] + [.let [module (value@ ///.#module input)] _ (///directive.set_current_module module)] (///directive.lifted_analysis (do [! ///phase.monad] [_ (module.create hash module) _ (monad.each ! module.import dependencies) - .let [source (///analysis.source (value@ #///.module input) (value@ #///.code input))] + .let [source (///analysis.source (value@ ///.#module input) (value@ ///.#code input))] _ (///analysis.set_source_code source)] (in [source [///generation.empty_buffer artifact.empty]]))))) @@ -209,24 +209,24 @@ (..reader module aliases source))] (function (_ state) (case (///phase.result' state (..iteration' wrapper archive expander reader source pre_payload)) - {#try.Success [state source&requirements&buffer]} - {#try.Success [state {#.Some source&requirements&buffer}]} + {try.#Success [state source&requirements&buffer]} + {try.#Success [state {.#Some source&requirements&buffer}]} - {#try.Failure error} + {try.#Failure error} (if (exception.match? ///syntax.end_of_file error) - {#try.Success [state #.None]} - (exception.with ///.cannot_compile module {#try.Failure error})))))) + {try.#Success [state {.#None}]} + (exception.with ///.cannot_compile module {try.#Failure error})))))) (def: (default_dependencies prelude input) (-> Module ///.Input (List Module)) (list& archive.runtime_module - (if (text\= prelude (value@ #///.module input)) + (if (text\= prelude (value@ ///.#module input)) (list) (list prelude)))) (def: module_aliases (-> .Module Aliases) - (|>> (value@ #.module_aliases) (dictionary.of_list text.hash))) + (|>> (value@ .#module_aliases) (dictionary.of_list text.hash))) (def: .public (compiler wrapper expander prelude write_directive) (All (_ anchor expression directive) @@ -235,41 +235,41 @@ (let [execute! (directiveP.phase wrapper expander)] (function (_ key parameters input) (let [dependencies (default_dependencies prelude input)] - [#///.dependencies dependencies - #///.process (function (_ state archive) + [///.#dependencies dependencies + ///.#process (function (_ state archive) (do [! try.monad] - [.let [hash (text\hash (value@ #///.code input))] + [.let [hash (text\hash (value@ ///.#code input))] [state [source buffer]] (<| (///phase.result' state) (..begin dependencies hash input)) - .let [module (value@ #///.module input)]] + .let [module (value@ ///.#module input)]] (loop [iteration (<| (///phase.result' state) (..iteration wrapper archive expander module source buffer ///syntax.no_aliases))] (do ! [[state ?source&requirements&temporary_payload] iteration] (case ?source&requirements&temporary_payload - #.None + {.#None} (do ! [[state [analysis_module [final_buffer final_registry]]] (///phase.result' state (..end module)) - .let [descriptor [#descriptor.hash hash - #descriptor.name module - #descriptor.file (value@ #///.file input) - #descriptor.references (set.of_list text.hash dependencies) - #descriptor.state #.Compiled - #descriptor.registry final_registry]]] + .let [descriptor [descriptor.#hash hash + descriptor.#name module + descriptor.#file (value@ ///.#file input) + descriptor.#references (set.of_list text.hash dependencies) + descriptor.#state {.#Compiled} + descriptor.#registry final_registry]]] (in [state - {#.Right [descriptor + {.#Right [descriptor (document.write key analysis_module) (row\each (function (_ [artifact_id custom directive]) [artifact_id custom (write_directive directive)]) final_buffer)]}])) - {#.Some [source requirements temporary_payload]} + {.#Some [source requirements temporary_payload]} (let [[temporary_buffer temporary_registry] temporary_payload] (in [state - {#.Left [#///.dependencies (|> requirements - (value@ #///directive.imports) + {.#Left [///.#dependencies (|> requirements + (value@ ///directive.#imports) (list\each product.left)) - #///.process (function (_ state archive) + ///.#process (function (_ state archive) (recur (<| (///phase.result' state) (do [! ///phase.monad] [analysis_module (<| (: (Operation .Module)) @@ -281,7 +281,7 @@ _ (///directive.lifted_generation (///generation.set_registry temporary_registry)) _ (|> requirements - (value@ #///directive.referrals) + (value@ ///directive.#referrals) (monad.each ! (execute! archive))) temporary_payload (..get_current_payload temporary_payload)] (..iteration wrapper archive expander module source temporary_payload (..module_aliases analysis_module))))))]}])) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index f884282eb..eda9c6147 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -131,12 +131,12 @@ (def: (runtime_descriptor registry) (-> Registry Descriptor) - [#descriptor.hash 0 - #descriptor.name archive.runtime_module - #descriptor.file "" - #descriptor.references (set.empty text.hash) - #descriptor.state #.Compiled - #descriptor.registry registry]) + [descriptor.#hash 0 + descriptor.#name archive.runtime_module + descriptor.#file "" + descriptor.#references (set.empty text.hash) + descriptor.#state {.#Compiled} + descriptor.#registry registry]) (def: runtime_document (Document .Module) @@ -234,7 +234,7 @@ Import (List Context) (Async (Try [<State+> Archive ///phase.Wrapper])))) (do [! (try.with async.monad)] - [.let [state (//init.state (value@ #static.host static) + [.let [state (//init.state (value@ static.#host static) module expander host_analysis @@ -276,11 +276,11 @@ (def: (module_compilation_log module) (All (_ <type_vars>) (-> Module <State+> Text)) - (|>> (value@ [#extension.state - #///directive.generation - #///directive.state - #extension.state - #///generation.log]) + (|>> (value@ [extension.#state + ///directive.#generation + ///directive.#state + extension.#state + ///generation.#log]) (row\mix (function (_ right left) (format left ..compilation_log_separator right)) module))) @@ -288,11 +288,11 @@ (def: with_reset_log (All (_ <type_vars>) (-> <State+> <State+>)) - (with@ [#extension.state - #///directive.generation - #///directive.state - #extension.state - #///generation.log] + (with@ [extension.#state + ///directive.#generation + ///directive.#state + extension.#state + ///generation.#log] row.empty)) (def: empty @@ -382,7 +382,7 @@ (exception.except ..cannot_import_circular_dependency [importer importee]) ... else - {#try.Success []})) + {try.#Success []})) (with_expansions [<Context> (as_is [Archive <State+>]) <Result> (as_is (Try <Context>)) @@ -423,30 +423,30 @@ [[_ dependence] (stm.update (..depend importer module) dependence)] (in dependence)))] (case (..verify_dependencies importer module dependence) - {#try.Failure error} - (in [(async.resolved {#try.Failure error}) - #.None]) + {try.#Failure error} + (in [(async.resolved {try.#Failure error}) + {.#None}]) - {#try.Success _} + {try.#Success _} (do ! [[archive state] (stm.read current)] (if (archive.archived? archive module) - (in [(async\in {#try.Success [archive state]}) - #.None]) + (in [(async\in {try.#Success [archive state]}) + {.#None}]) (do ! [@pending (stm.read pending)] (case (dictionary.value module @pending) - {#.Some [return signal]} + {.#Some [return signal]} (in [return - #.None]) + {.#None}]) - #.None + {.#None} (case (if (archive.reserved? archive module) (do try.monad [module_id (archive.id module archive)] (in [module_id archive])) (archive.reserve module archive)) - {#try.Success [module_id archive]} + {try.#Success [module_id archive]} (do ! [_ (stm.write [archive state] current) .let [[return signal] (:sharing [<type_vars>] @@ -457,31 +457,31 @@ (async.async []))] _ (stm.update (dictionary.has module [return signal]) pending)] (in [return - {#.Some [[archive state] + {.#Some [[archive state] module_id signal]}])) - {#try.Failure error} - (in [(async\in {#try.Failure error}) - #.None]))))))))))) + {try.#Failure error} + (in [(async\in {try.#Failure error}) + {.#None}]))))))))))) _ (case signal - #.None + {.#None} (in []) - {#.Some [context module_id resolver]} + {.#Some [context module_id resolver]} (do ! [result (compile importer import! module_id context module) result (case result - {#try.Failure error} + {try.#Failure error} (in result) - {#try.Success [resulting_archive resulting_state]} + {try.#Success [resulting_archive resulting_state]} (stm.commit! (do stm.monad [[_ [merged_archive _]] (stm.update (function (_ [archive state]) [(archive.merged resulting_archive archive) state]) current)] - (in {#try.Success [merged_archive resulting_state]})))) + (in {try.#Success [merged_archive resulting_state]})))) _ (async.future (resolver result))] (in [])))] return))))) @@ -500,14 +500,14 @@ .let [additions (|> modules (list\each product.left) (set.of_list text.hash))]] - (in (revised@ [#extension.state - #///directive.analysis - #///directive.state - #extension.state] + (in (revised@ [extension.#state + ///directive.#analysis + ///directive.#state + extension.#state] (function (_ analysis_state) (|> analysis_state (:as .Lux) - (revised@ #.modules (function (_ current) + (revised@ .#modules (function (_ current) (list\composite (list.only (|>> product.left (set.member? additions) not) @@ -544,14 +544,14 @@ importer import compilation_sources - (value@ #static.host_module_extension static) + (value@ static.#host_module_extension static) module)] (loop [[archive state] [archive state] compilation (base_compiler (:as ///.Input input)) all_dependencies (: (Set Module) (set.of_list text.hash (list)))] (do ! - [.let [new_dependencies (value@ #///.dependencies compilation) + [.let [new_dependencies (value@ ///.#dependencies compilation) continue! (:sharing [<type_vars>] <Platform> platform @@ -576,10 +576,10 @@ new_dependencies))] [archive state] (if (set.empty? duplicates) (case new_dependencies - #.End + {.#End} (in [archive state]) - {#.Item _} + {.#Item _} (do ! [archive,document+ (|> new_dependencies (list\each (import! module)) @@ -590,7 +590,7 @@ (in [archive (try.trusted (..updated_state archive state))]))) (async\in (exception.except ..cannot_import_twice [module duplicates])))] - (case ((value@ #///.process compilation) + (case ((value@ ///.#process compilation) ... TODO: The "///directive.set_current_module" below shouldn't be necessary. Remove it ASAP. ... TODO: The context shouldn't need to be re-set either. (|> (///directive.set_current_module module) @@ -598,27 +598,27 @@ try.trusted product.left) archive) - {#try.Success [state more|done]} + {try.#Success [state more|done]} (case more|done - {#.Left more} + {.#Left more} (continue! [archive state] more all_dependencies) - {#.Right [descriptor document output]} + {.#Right [descriptor document output]} (do ! [.let [_ (debug.log! (..module_compilation_log module state)) - descriptor (with@ #descriptor.references all_dependencies descriptor)] + descriptor (with@ descriptor.#references all_dependencies descriptor)] _ (..cache_module static platform module_id [descriptor document output])] (case (archive.has module [descriptor document output] archive) - {#try.Success archive} + {try.#Success archive} (in [archive (..with_reset_log state)]) - {#try.Failure error} - (async\in {#try.Failure error})))) + {try.#Failure error} + (async\in {try.#Failure error})))) - {#try.Failure error} + {try.#Failure error} (do ! [_ (ioW.freeze (value@ #&file_system platform) static archive)] - (async\in {#try.Failure error}))))))))] + (async\in {try.#Failure error}))))))))] (compiler archive.runtime_module compilation_module))) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index 251a543a3..39714d1c0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux @@ -86,10 +86,10 @@ ... #imports (<b>.list <b>.text) ... #module_state - (\ <>.monad in #.Cached)))) + (\ <>.monad in {.#Cached})))) (def: .public key (Key .Module) - (key.key [#signature.name (name_of ..compiler) - #signature.version /version.version] + (key.key [signature.#name (name_of ..compiler) + signature.#version /version.version] (module.empty 0))) 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 fb9566948..1fd1fe2b4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -37,7 +37,7 @@ (type: .public Primitive (.Variant - #Unit + {#Unit} {#Bit Bit} {#Nat Nat} {#Int Int} @@ -120,7 +120,7 @@ (def: (= reference sample) (case [reference sample] - [#Unit #Unit] + [{#Unit} {#Unit}] true (^template [<tag> <=>] @@ -213,7 +213,7 @@ [{#Case [reference_analysis reference_match]} {#Case [sample_analysis sample_match]}] (and (= reference_analysis sample_analysis) - (\ (list.equivalence (branch_equivalence =)) = {#.Item reference_match} {#.Item sample_match})) + (\ (list.equivalence (branch_equivalence =)) = {.#Item reference_match} {.#Item sample_match})) [{#Function [reference_environment reference_analysis]} {#Function [sample_environment sample_analysis]}] @@ -233,24 +233,24 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(<tag> content)])] + [{<tag> content}])] - [control/case #..Case] + [control/case ..#Case] ) (template: .public (unit) - [{#..Primitive #..Unit}]) + [{..#Primitive {..#Unit}}]) (template [<name> <tag>] [(template: .public (<name> value) - [{#..Primitive {<tag> value}}])] - - [bit #..Bit] - [nat #..Nat] - [int #..Int] - [rev #..Rev] - [frac #..Frac] - [text #..Text] + [{..#Primitive {<tag> value}}])] + + [bit ..#Bit] + [nat ..#Nat] + [int ..#Int] + [rev ..#Rev] + [frac ..#Frac] + [text ..#Text] ) (type: .public (Abstraction c) @@ -265,11 +265,11 @@ (template: .public (no_op value) [(|> 1 - {#variable.Local} - {#reference.Variable} - {#..Reference} - {#..Function (list)} - {#..Apply value})]) + {variable.#Local} + {reference.#Variable} + {..#Reference} + {..#Function (list)} + {..#Apply value})]) (def: .public (apply [abstraction inputs]) (-> (Application Analysis) Analysis) @@ -284,19 +284,19 @@ inputs (list)] (case abstraction {#Apply input next} - (recur next {#.Item input inputs}) + (recur next {.#Item input inputs}) _ [abstraction inputs]))) (template [<name> <tag>] [(template: .public (<name> content) - [(.<| {#..Reference} + [(.<| {..#Reference} <tag> content)])] - [variable {#reference.Variable}] - [constant {#reference.Constant}] + [variable {reference.#Variable}] + [constant {reference.#Constant}] [variable/local (reference.local)] [variable/foreign (reference.foreign)] @@ -304,48 +304,48 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(.<| {#..Complex} + [(.<| {..#Complex} <tag> content)])] - [pattern/variant {#..Variant}] - [pattern/tuple {#..Tuple}] + [pattern/variant {..#Variant}] + [pattern/tuple {..#Tuple}] ) (template [<name> <tag>] [(template: .public (<name> content) - [(.<| {#..Structure} + [(.<| {..#Structure} {<tag>} content)])] - [variant #..Variant] - [tuple #..Tuple] + [variant ..#Variant] + [tuple ..#Tuple] ) (template: .public (pattern/unit) - [{#..Simple #..Unit}]) + [{..#Simple {..#Unit}}]) (template [<name> <tag>] [(template: .public (<name> content) - [{#..Simple {<tag> content}}])] + [{..#Simple {<tag> content}}])] - [pattern/bit #..Bit] - [pattern/nat #..Nat] - [pattern/int #..Int] - [pattern/rev #..Rev] - [pattern/frac #..Frac] - [pattern/text #..Text] + [pattern/bit ..#Bit] + [pattern/nat ..#Nat] + [pattern/int ..#Int] + [pattern/rev ..#Rev] + [pattern/frac ..#Frac] + [pattern/text ..#Text] ) (template: .public (pattern/bind register) - [{#..Bind register}]) + [{..#Bind register}]) (def: .public (%analysis analysis) (Format Analysis) (case analysis {#Primitive primitive} (case primitive - #Unit + {#Unit} "[]" (^template [<tag> <format>] @@ -387,7 +387,7 @@ {#Apply _} (|> analysis ..application - {#.Item} + {.#Item} (list\each %analysis) (text.interposed " ") (text.enclosed ["(" ")"])) @@ -413,42 +413,42 @@ (def: .public (with_source_code source action) (All (_ a) (-> Source (Operation a) (Operation a))) (function (_ [bundle state]) - (let [old_source (value@ #.source state)] - (case (action [bundle (with@ #.source source state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (with@ #.source old_source state')] + (let [old_source (value@ .#source state)] + (case (action [bundle (with@ .#source source state)]) + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (with@ .#source old_source state')] output]} - {#try.Failure error} - {#try.Failure error})))) + {try.#Failure error} + {try.#Failure error})))) (def: fresh_bindings (All (_ k v) (Bindings k v)) - [#.counter 0 - #.mappings (list)]) + [.#counter 0 + .#mappings (list)]) (def: fresh_scope Scope - [#.name (list) - #.inner 0 - #.locals fresh_bindings - #.captured fresh_bindings]) + [.#name (list) + .#inner 0 + .#locals fresh_bindings + .#captured fresh_bindings]) (def: .public (with_scope action) (All (_ a) (-> (Operation a) (Operation [Scope a]))) (function (_ [bundle state]) - (case (action [bundle (revised@ #.scopes (|>> {#.Item fresh_scope}) state)]) - {#try.Success [[bundle' state'] output]} - (case (value@ #.scopes state') - {#.Item head tail} - {#try.Success [[bundle' (with@ #.scopes tail state')] + (case (action [bundle (revised@ .#scopes (|>> {.#Item fresh_scope}) state)]) + {try.#Success [[bundle' state'] output]} + (case (value@ .#scopes state') + {.#Item head tail} + {try.#Success [[bundle' (with@ .#scopes tail state')] [head output]]} - #.End - {#try.Failure "Impossible error: Drained scopes!"}) + {.#End} + {try.#Failure "Impossible error: Drained scopes!"}) - {#try.Failure error} - {#try.Failure error}))) + {try.#Failure error} + {try.#Failure error}))) (def: scope_reset (List Scope) @@ -457,33 +457,33 @@ (def: .public (without_scopes action) (All (_ a) (-> (Operation a) (Operation a))) (function (_ [bundle state]) - (case (action [bundle (with@ #.scopes ..scope_reset state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (with@ #.scopes (value@ #.scopes state) state')] + (case (action [bundle (with@ .#scopes ..scope_reset state)]) + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (with@ .#scopes (value@ .#scopes state) state')] output]} - {#try.Failure error} - {#try.Failure error}))) + {try.#Failure error} + {try.#Failure error}))) (def: .public (with_current_module name) (All (_ a) (-> Text (Operation a) (Operation a))) - (extension.localized (value@ #.current_module) - (with@ #.current_module) - (function.constant {#.Some name}))) + (extension.localized (value@ .#current_module) + (with@ .#current_module) + (function.constant {.#Some name}))) (def: .public (with_location location action) (All (_ a) (-> Location (Operation a) (Operation a))) (if (text\= "" (product.left location)) action (function (_ [bundle state]) - (let [old_location (value@ #.location state)] - (case (action [bundle (with@ #.location location state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (with@ #.location old_location state')] + (let [old_location (value@ .#location state)] + (case (action [bundle (with@ .#location location state)]) + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (with@ .#location old_location state')] output]} - {#try.Failure error} - {#try.Failure error}))))) + {try.#Failure error} + {try.#Failure error}))))) (def: (locate_error location error) (-> Location Text Text) @@ -493,7 +493,7 @@ (def: .public (failure error) (-> Text Operation) (function (_ [bundle state]) - {#try.Failure (locate_error (value@ #.location state) error)})) + {try.#Failure (locate_error (value@ .#location state) error)})) (def: .public (except exception parameters) (All (_ e) (-> (Exception e) e Operation)) @@ -508,7 +508,7 @@ (def: .public (failure' error) (-> Text (phase.Operation Lux)) (function (_ state) - {#try.Failure (locate_error (value@ #.location state) error)})) + {try.#Failure (locate_error (value@ .#location state) error)})) (def: .public (except' exception parameters) (All (_ e) (-> (Exception e) e (phase.Operation Lux))) @@ -519,17 +519,17 @@ (function (_ bundle,state) (case (exception.with exception message (action bundle,state)) - {#try.Success output} - {#try.Success output} + {try.#Success output} + {try.#Success output} - {#try.Failure error} + {try.#Failure error} (let [[bundle state] bundle,state] - {#try.Failure (locate_error (value@ #.location state) error)})))) + {try.#Failure (locate_error (value@ .#location state) error)})))) (def: .public (install state) (-> .Lux (Operation Any)) (function (_ [bundle _]) - {#try.Success [[bundle state] + {try.#Success [[bundle state] []]})) (template [<name> <type> <field> <value>] @@ -537,9 +537,9 @@ (-> <type> (Operation Any)) (extension.update (with@ <field> <value>)))] - [set_source_code Source #.source value] - [set_current_module Text #.current_module {#.Some value}] - [set_location Location #.location value] + [set_source_code Source .#source value] + [set_current_module Text .#current_module {.#Some value}] + [set_location Location .#location value] ) (def: .public (location file) @@ -556,28 +556,28 @@ (def: type_context Type_Context - [#.ex_counter 0 - #.var_counter 0 - #.var_bindings (list)]) + [.#ex_counter 0 + .#var_counter 0 + .#var_bindings (list)]) (def: .public (info version host) (-> Version Text Info) - [#.target host - #.version (%.nat version) - #.mode #.Build]) + [.#target host + .#version (%.nat version) + .#mode {.#Build}]) (def: .public (state info) (-> Info Lux) - [#.info info - #.source ..dummy_source - #.location location.dummy - #.current_module #.None - #.modules (list) - #.scopes (list) - #.type_context ..type_context - #.expected #.None - #.seed 0 - #.scope_type_vars (list) - #.extensions [] - #.eval (:as (-> Type Code (Meta Any)) []) - #.host []]) + [.#info info + .#source ..dummy_source + .#location location.dummy + .#current_module {.#None} + .#modules (list) + .#scopes (list) + .#type_context ..type_context + .#expected {.#None} + .#seed 0 + .#scope_type_vars (list) + .#extensions [] + .#eval (:as (-> Type Code (Meta Any)) []) + .#host []]) 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 ed5983d14..428e8011a 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 @@ -38,10 +38,10 @@ (do try.monad [output (expander macro inputs state)] (case output - {#try.Success output} - {#try.Success output} + {try.#Success output} + {try.#Success output} - {#try.Failure error} + {try.#Failure error} ((meta.failure (exception.error ..expansion_failed [name inputs error])) state))))) (def: .public (expand_one 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 cd74d94f4..d11fa82cc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -70,11 +70,11 @@ (All (_ anchor expression directive) (Operation anchor expression directive <phase>)) (function (_ [bundle state]) - {#try.Success [[bundle state] (value@ [<component> #..phase] state)]}))] + {try.#Success [[bundle state] (value@ [<component> ..#phase] state)]}))] - [analysis #..analysis analysis.Phase] - [synthesis #..synthesis synthesis.Phase] - [generation #..generation (generation.Phase anchor expression directive)] + [analysis ..#analysis analysis.Phase] + [synthesis ..#synthesis synthesis.Phase] + [generation ..#generation (generation.Phase anchor expression directive)] ) (template [<name> <component> <operation>] @@ -82,13 +82,13 @@ (All (_ anchor expression directive output) (-> (<operation> output) (Operation anchor expression directive output))) - (|>> (phase.sub [(value@ [<component> #..state]) - (with@ [<component> #..state])]) + (|>> (phase.sub [(value@ [<component> ..#state]) + (with@ [<component> ..#state])]) extension.lifted))] - [lifted_analysis #..analysis analysis.Operation] - [lifted_synthesis #..synthesis synthesis.Operation] - [lifted_generation #..generation (generation.Operation anchor expression directive)] + [lifted_analysis ..#analysis analysis.Operation] + [lifted_synthesis ..#synthesis synthesis.Operation] + [lifted_generation ..#generation (generation.Operation anchor expression directive)] ) (def: .public (set_current_module module) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index 72a086650..ab139fc04 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -52,11 +52,11 @@ (type: .public (Host expression directive) (Interface (: (-> Context expression (Try Any)) - evaluate!) + evaluate) (: (-> directive (Try Any)) - execute!) + execute) (: (-> Context (Maybe Text) expression (Try [Text Any directive])) - define!) + define) (: (-> Context Binary directive) ingest) @@ -94,12 +94,12 @@ Module (..State anchor expression directive))) [#module module - #anchor #.None + #anchor {.#None} #host host - #buffer #.None + #buffer {.#None} #registry artifact.empty #counter 0 - #context #.None + #context {.#None} #log row.empty]) (def: .public empty_buffer @@ -115,30 +115,30 @@ (All (_ anchor expression directive output) <with_type>) (function (_ body) (function (_ [bundle state]) - (case (body [bundle (with@ <tag> {#.Some <with_value>} state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (with@ <tag> (value@ <tag> state) state')] + (case (body [bundle (with@ <tag> {.#Some <with_value>} state)]) + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (with@ <tag> (value@ <tag> state) state')] output]} - {#try.Failure error} - {#try.Failure error})))) + {try.#Failure error} + {try.#Failure error})))) (def: .public <get> (All (_ anchor expression directive) (Operation anchor expression directive <get_type>)) (function (_ (^@ stateE [bundle state])) (case (value@ <tag> state) - {#.Some output} - {#try.Success [stateE output]} + {.#Some output} + {try.#Success [stateE output]} - #.None + {.#None} (exception.except <exception> [])))) (def: .public (<set> value) (All (_ anchor expression directive) (-> <get_type> (Operation anchor expression directive Any))) (function (_ [bundle state]) - {#try.Success [[bundle (with@ <tag> {#.Some value} state)] + {try.#Success [[bundle (with@ <tag> {.#Some value} state)] []]}))] [#anchor @@ -160,13 +160,13 @@ (All (_ anchor expression directive) (Operation anchor expression directive artifact.Registry)) (function (_ (^@ stateE [bundle state])) - {#try.Success [stateE (value@ #registry state)]})) + {try.#Success [stateE (value@ #registry state)]})) (def: .public (set_registry value) (All (_ anchor expression directive) (-> artifact.Registry (Operation anchor expression directive Any))) (function (_ [bundle state]) - {#try.Success [[bundle (with@ #registry value state)] + {try.#Success [[bundle (with@ #registry value state)] []]})) (def: .public next @@ -196,33 +196,33 @@ (All (_ anchor expression directive) (-> Context expression (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) - (case (\ (value@ #host state) evaluate! label code) - {#try.Success output} - {#try.Success [state+ output]} + (case (\ (value@ #host state) evaluate label code) + {try.#Success output} + {try.#Success [state+ output]} - {#try.Failure error} - (exception.except ..cannot_interpret error)))) + {try.#Failure error} + (exception.except ..cannot_interpret [error])))) (def: .public (execute! code) (All (_ anchor expression directive) (-> directive (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) - (case (\ (value@ #host state) execute! code) - {#try.Success output} - {#try.Success [state+ output]} + (case (\ (value@ #host state) execute code) + {try.#Success output} + {try.#Success [state+ output]} - {#try.Failure error} + {try.#Failure error} (exception.except ..cannot_interpret error)))) (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])) - (case (\ (value@ #host state) define! context custom code) - {#try.Success output} - {#try.Success [stateE output]} + (case (\ (value@ #host state) define context custom code) + {try.#Success output} + {try.#Success [stateE output]} - {#try.Failure error} + {try.#Failure error} (exception.except ..cannot_interpret error)))) (def: .public (save! artifact_id custom code) @@ -231,13 +231,13 @@ (do [! phase.monad] [?buffer (extension.read (value@ #buffer))] (case ?buffer - {#.Some buffer} + {.#Some buffer} ... TODO: Optimize by no longer checking for overwrites... (if (row.any? (|>> product.left (n.= artifact_id)) buffer) (phase.except ..cannot_overwrite_output [artifact_id]) - (extension.update (with@ #buffer {#.Some (row.suffix [artifact_id custom code] buffer)}))) + (extension.update (with@ #buffer {.#Some (row.suffix [artifact_id custom code] buffer)}))) - #.None + {.#None} (phase.except ..no_buffer_for_saving_code [artifact_id])))) (template [<name> <artifact>] @@ -246,7 +246,7 @@ (-> Text (Operation anchor expression directive artifact.ID))) (function (_ (^@ stateE [bundle state])) (let [[id registry'] (<artifact> name (value@ #registry state))] - {#try.Success [[bundle (with@ #registry registry' state)] + {try.#Success [[bundle (with@ #registry registry' state)] id]})))] [learn artifact.definition] @@ -272,16 +272,16 @@ (do try.monad [module_id (archive.id _module archive) registry (if (text\= (value@ #module state) _module) - {#try.Success (value@ #registry state)} + {try.#Success (value@ #registry state)} (do try.monad [[descriptor document] (archive.find _module archive)] - {#try.Success (value@ #descriptor.registry descriptor)}))] + {try.#Success (value@ descriptor.#registry descriptor)}))] (case (artifact.remember _name registry) - #.None + {.#None} (exception.except ..unknown_definition [name (artifact.definitions registry)]) - {#.Some id} - {#try.Success [stateE [module_id id]]}))))) + {.#Some id} + {try.#Success [stateE [module_id id]]}))))) (exception: .public no_context) @@ -298,10 +298,10 @@ (-> Archive (Operation anchor expression directive Context))) (function (_ (^@ stateE [bundle state])) (case (value@ #context state) - #.None + {.#None} (exception.except ..no_context []) - {#.Some id} + {.#Some id} (do try.monad [module_id (archive.id (value@ #module state) archive)] (in [stateE [module_id id]]))))) @@ -313,7 +313,7 @@ (Operation anchor expression directive a))) (function (_ [bundle state]) (do try.monad - [[[bundle' state'] output] (body [bundle (with@ #context {#.Some id} state)])] + [[[bundle' state'] output] (body [bundle (with@ #context {.#Some id} state)])] (in [[bundle' (with@ #context (value@ #context state) state')] output])))) @@ -326,7 +326,7 @@ (do try.monad [[[bundle' state'] output] (body [bundle (|> state (with@ #registry registry') - (with@ #context {#.Some id}))]) + (with@ #context {.#Some id}))]) module_id (archive.id (value@ #module state) archive)] (in [[bundle' (with@ #context (value@ #context state) state')] [[module_id id] @@ -336,6 +336,6 @@ (All (_ anchor expression directive a) (-> Text (Operation anchor expression directive Any))) (function (_ [bundle state]) - {#try.Success [[bundle + {try.#Success [[bundle (revised@ #log (row.suffix message) 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 5bebbcde9..c3b6434d2 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 @@ -49,35 +49,32 @@ (^template [<tag> <analyser>] [{<tag> value} (<analyser> value)]) - ([#.Bit /primitive.bit] - [#.Nat /primitive.nat] - [#.Int /primitive.int] - [#.Rev /primitive.rev] - [#.Frac /primitive.frac] - [#.Text /primitive.text]) - - (^ {#.Variant (list& [_ {#.Tag tag}] + ([.#Bit /primitive.bit] + [.#Nat /primitive.nat] + [.#Int /primitive.int] + [.#Rev /primitive.rev] + [.#Frac /primitive.frac] + [.#Text /primitive.text]) + + (^ {.#Variant (list& [_ {.#Identifier tag}] values)}) (case values - {#.Item value #.End} + {.#Item value {.#End}} (/structure.tagged_sum compile tag archive value) _ (/structure.tagged_sum compile tag archive (` [(~+ values)]))) - (^ {#.Variant (list& [_ {#.Nat lefts}] [_ {#.Bit right?}] + (^ {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}) (case values - {#.Item value #.End} + {.#Item value .#End} (/structure.sum compile lefts right? archive value) _ (/structure.sum compile lefts right? archive (` [(~+ values)]))) - {#.Tag tag} - (/structure.tagged_sum compile tag archive (' [])) - - (^ {#.Tuple elems}) + (^ {.#Tuple elems}) (/structure.record archive compile elems) _ @@ -86,32 +83,32 @@ (def: (compile|others expander archive compile code') (-> Expander Archive Phase (-> (Code' (Ann Location)) (Operation Analysis))) (case code' - {#.Identifier reference} + {.#Identifier reference} (/reference.reference reference) - (^ {#.Form (list [_ {#.Variant branches}] input)}) + (^ {.#Form (list [_ {.#Variant branches}] input)}) (if (n.even? (list.size branches)) (/case.case compile (list.pairs branches) archive input) (//.except ..unrecognized_syntax [location.dummy code'])) - (^ {#.Form (list& [_ {#.Text extension_name}] extension_args)}) + (^ {.#Form (list& [_ {.#Text extension_name}] extension_args)}) (//extension.apply archive compile [extension_name extension_args]) - (^ {#.Form (list [_ {#.Tuple (list [_ {#.Identifier ["" function_name]}] - [_ {#.Identifier ["" arg_name]}])}] + (^ {.#Form (list [_ {.#Tuple (list [_ {.#Identifier ["" function_name]}] + [_ {.#Identifier ["" arg_name]}])}] body)}) (/function.function compile function_name arg_name archive body) - (^ {#.Form (list& functionC argsC+)}) + (^ {.#Form (list& functionC argsC+)}) (do [! //.monad] [[functionT functionA] (/type.with_inference (compile archive functionC))] (case functionA - {#/.Reference {#reference.Constant def_name}} + {/.#Reference {reference.#Constant def_name}} (do ! [?macro (//extension.lifted (meta.macro def_name))] (case ?macro - {#.Some macro} + {.#Some macro} (do ! [expansion (//extension.lifted (/macro.expand_one expander def_name macro argsC+))] (compile archive expansion)) 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 69307c2ac..5d6489898 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 @@ -69,11 +69,11 @@ (def: (re_quantify envs baseT) (-> (List (List Type)) Type Type) (.case envs - #.End + {.#End} baseT - {#.Item head tail} - (re_quantify tail {#.UnivQ head baseT}))) + {.#Item head tail} + (re_quantify tail {.#UnivQ head baseT}))) ... Type-checking on the input value is done during the analysis of a ... "case" expression, to ensure that the patterns being used make @@ -88,53 +88,53 @@ (list)) caseT caseT] (.case caseT - {#.Var id} + {.#Var id} (do ///.monad [?caseT' (//type.with_env (check.peek id))] (.case ?caseT' - {#.Some caseT'} + {.#Some caseT'} (recur envs caseT') _ (/.except ..cannot_simplify_for_pattern_matching caseT))) - {#.Named name unnamedT} + {.#Named name unnamedT} (recur envs unnamedT) - {#.UnivQ env unquantifiedT} - (recur {#.Item env envs} unquantifiedT) + {.#UnivQ env unquantifiedT} + (recur {.#Item env envs} unquantifiedT) - {#.ExQ _} + {.#ExQ _} (do ///.monad [[var_id varT] (//type.with_env check.var)] (recur envs (maybe.trusted (type.applied (list varT) caseT)))) - {#.Apply inputT funcT} + {.#Apply inputT funcT} (.case funcT - {#.Var funcT_id} + {.#Var funcT_id} (do ///.monad [funcT' (//type.with_env (do check.monad [?funct' (check.peek funcT_id)] (.case ?funct' - {#.Some funct'} + {.#Some funct'} (in funct') _ (check.except ..cannot_simplify_for_pattern_matching caseT))))] - (recur envs {#.Apply inputT funcT'})) + (recur envs {.#Apply inputT funcT'})) _ (.case (type.applied (list inputT) funcT) - {#.Some outputT} + {.#Some outputT} (recur envs outputT) - #.None + {.#None} (/.except ..cannot_simplify_for_pattern_matching caseT))) - {#.Product _} + {.#Product _} (|> caseT type.flat_tuple (list\each (re_quantify envs)) @@ -172,75 +172,75 @@ (def: (analyse_pattern num_tags inputT pattern next) (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) (.case pattern - [location {#.Identifier ["" name]}] + [location {.#Identifier ["" name]}] (/.with_location location (do ///.monad [outputA (//scope.with_local [name inputT] next) idx //scope.next_local] - (in [{#/.Bind idx} outputA]))) + (in [{/.#Bind idx} outputA]))) (^template [<type> <input> <output>] [[location <input>] - (analyse_primitive <type> inputT location {#/.Simple <output>} next)]) - ([Bit {#.Bit pattern_value} {#/.Bit pattern_value}] - [Nat {#.Nat pattern_value} {#/.Nat pattern_value}] - [Int {#.Int pattern_value} {#/.Int pattern_value}] - [Rev {#.Rev pattern_value} {#/.Rev pattern_value}] - [Frac {#.Frac pattern_value} {#/.Frac pattern_value}] - [Text {#.Text pattern_value} {#/.Text pattern_value}] - [Any {#.Tuple #.End} #/.Unit]) + (analyse_primitive <type> inputT location {/.#Simple <output>} next)]) + ([Bit {.#Bit pattern_value} {/.#Bit pattern_value}] + [Nat {.#Nat pattern_value} {/.#Nat pattern_value}] + [Int {.#Int pattern_value} {/.#Int pattern_value}] + [Rev {.#Rev pattern_value} {/.#Rev pattern_value}] + [Frac {.#Frac pattern_value} {/.#Frac pattern_value}] + [Text {.#Text pattern_value} {/.#Text pattern_value}] + [Any {.#Tuple {.#End}} {/.#Unit}]) - (^ [location {#.Tuple (list singleton)}]) - (analyse_pattern #.None inputT singleton next) + (^ [location {.#Tuple (list singleton)}]) + (analyse_pattern {.#None} inputT singleton next) - [location {#.Tuple sub_patterns}] + [location {.#Tuple sub_patterns}] (do [! ///.monad] [record (//structure.normal sub_patterns) record_size,members,recordT (: (Operation (Maybe [Nat (List Code) Type])) (.case record - {#.Some record} + {.#Some record} (//structure.order record) - #.None - (in #.None)))] + {.#None} + (in {.#None})))] (.case record_size,members,recordT - {#.Some [record_size members recordT]} + {.#Some [record_size members recordT]} (do ! [_ (.case inputT - {#.Var _id} + {.#Var _id} (//type.with_env (check.check inputT recordT)) _ (in []))] - (analyse_pattern {#.Some record_size} inputT [location {#.Tuple members}] next)) + (analyse_pattern {.#Some record_size} inputT [location {.#Tuple members}] next)) - #.None + {.#None} (/.with_location location (do [! ///.monad] [inputT' (simplify_case inputT)] (.case inputT' - {#.Product _} + {.#Product _} (let [matches (loop [types (type.flat_tuple inputT') patterns sub_patterns output (: (List [Type Code]) - #.End)] + {.#End})] (.case [types patterns] - [#.End #.End] + [{.#End} {.#End}] output - [{#.Item headT #.End} {#.Item headP #.End}] - {#.Item [headT headP] output} + [{.#Item headT {.#End}} {.#Item headP {.#End}}] + {.#Item [headT headP] output} - [remainingT {#.Item headP #.End}] - {#.Item [(type.tuple remainingT) headP] output} + [remainingT {.#Item headP {.#End}}] + {.#Item [(type.tuple remainingT) headP] output} - [{#.Item headT #.End} remainingP] - {#.Item [headT (code.tuple remainingP)] output} + [{.#Item headT {.#End}} remainingP] + {.#Item [headT (code.tuple remainingP)] output} - [{#.Item headT tailT} {#.Item headP tailP}] - (recur tailT tailP {#.Item [headT headP] output}) + [{.#Item headT tailT} {.#Item headP tailP}] + (recur tailT tailP {.#Item [headT headP] output}) _ (undefined)))] @@ -252,7 +252,7 @@ (do ! [[memberP [memberP+ thenA]] ((:as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) analyse_pattern) - #.None memberT memberC then)] + {.#None} memberT memberC then)] (in [(list& memberP memberP+) thenA])))) (do ! [nextA next] @@ -264,38 +264,38 @@ _ (/.except ..cannot_match_with_pattern [inputT' pattern])))))) - [location {#.Tag tag}] + [location {.#Tag tag}] (/.with_location location - (analyse_pattern #.None inputT (` {(~ pattern)}) next)) + (analyse_pattern {.#None} inputT (` {(~ pattern)}) next)) - (^ [location {#.Variant (list& [_ {#.Nat lefts}] [_ {#.Bit right?}] values)}]) + (^ [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) (/.with_location location (do ///.monad [inputT' (simplify_case inputT)] (.case inputT' - {#.Sum _} + {.#Sum _} (let [flat_sum (type.flat_variant inputT') size_sum (list.size flat_sum) num_cases (maybe.else size_sum num_tags) idx (/.tag lefts right?)] (.case (list.item idx flat_sum) - (^multi {#.Some caseT} + (^multi {.#Some caseT} (n.< num_cases idx)) (do ///.monad [[testP nextA] (if (and (n.> num_cases size_sum) (n.= (-- num_cases) idx)) - (analyse_pattern #.None + (analyse_pattern {.#None} (type.variant (list.after (-- num_cases) flat_sum)) (` [(~+ values)]) next) - (analyse_pattern #.None caseT (` [(~+ values)]) next))] + (analyse_pattern {.#None} caseT (` [(~+ values)]) next))] (in [(/.pattern/variant [lefts right? testP]) nextA])) _ (/.except ..sum_has_no_case [idx inputT]))) - {#.UnivQ _} + {.#UnivQ _} (do ///.monad [[ex_id exT] (//type.with_env check.existential)] @@ -307,7 +307,7 @@ _ (/.except ..cannot_match_with_pattern [inputT' pattern])))) - (^ [location {#.Variant (list& [_ {#.Tag tag}] values)}]) + (^ [location {.#Variant (list& [_ {.#Tag tag}] values)}]) (/.with_location location (do ///.monad [tag (///extension.lifted (meta.normal tag)) @@ -315,7 +315,7 @@ _ (//type.with_env (check.check inputT variantT)) .let [[lefts right?] (/.choice (list.size group) idx)]] - (analyse_pattern {#.Some (list.size group)} inputT (` {(~ (code.nat lefts)) (~ (code.bit right?)) (~+ values)}) next))) + (analyse_pattern {.#Some (list.size group)} inputT (` {(~ (code.nat lefts)) (~ (code.bit right?)) (~+ values)}) next))) _ (/.except ..not_a_pattern pattern) @@ -324,25 +324,25 @@ (def: .public (case analyse branches archive inputC) (-> Phase (List [Code Code]) Phase) (.case branches - {#.Item [patternH bodyH] branchesT} + {.#Item [patternH bodyH] branchesT} (do [! ///.monad] [[inputT inputA] (//type.with_inference (analyse archive inputC)) - outputH (analyse_pattern #.None inputT patternH (analyse archive bodyH)) + outputH (analyse_pattern {.#None} inputT patternH (analyse archive bodyH)) outputT (monad.each ! (function (_ [patternT bodyT]) - (analyse_pattern #.None inputT patternT (analyse archive bodyT))) + (analyse_pattern {.#None} inputT patternT (analyse archive bodyT))) branchesT) outputHC (|> outputH product.left /coverage.determine) outputTC (monad.each ! (|>> product.left /coverage.determine) outputT) _ (.case (monad.mix try.monad /coverage.merged outputHC outputTC) - {#try.Success coverage} + {try.#Success coverage} (///.assertion non_exhaustive_pattern_matching [inputC branches coverage] (/coverage.exhaustive? coverage)) - {#try.Failure error} + {try.#Failure error} (/.failure error))] - (in {#/.Case inputA [outputH outputT]})) + (in {/.#Case inputA [outputH outputT]})) - #.End + {.#End} (/.except ..cannot_have_empty_branches ""))) 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 59ecb1717..813324061 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 @@ -50,12 +50,12 @@ (type: .public Coverage (Rec Coverage (.Variant - #Partial + {#Partial} {#Bit Bit} {#Variant (Maybe Nat) (Dictionary Nat Coverage)} {#Seq Coverage Coverage} {#Alt Coverage Coverage} - #Exhaustive))) + {#Exhaustive}))) (def: .public (exhaustive? coverage) (-> Coverage Bit) @@ -69,7 +69,7 @@ (def: .public (%coverage value) (Format Coverage) (case value - #Partial + {#Partial} "#Partial" {#Bit value'} @@ -93,41 +93,41 @@ {#Alt left right} (format "{#Alt " (%coverage left) " " (%coverage right) "}") - #Exhaustive + {#Exhaustive} "#Exhaustive")) (def: .public (determine pattern) (-> Pattern (Operation Coverage)) (case pattern - (^or {#/.Simple #/.Unit} - {#/.Bind _}) - (////\in #Exhaustive) + (^or {/.#Simple {/.#Unit}} + {/.#Bind _}) + (////\in {#Exhaustive}) ... Primitive patterns always have partial coverage because there ... are too many possibilities as far as values go. (^template [<tag>] - [{#/.Simple {<tag> _}} - (////\in #Partial)]) - ([#/.Nat] - [#/.Int] - [#/.Rev] - [#/.Frac] - [#/.Text]) + [{/.#Simple {<tag> _}} + (////\in {#Partial})]) + ([/.#Nat] + [/.#Int] + [/.#Rev] + [/.#Frac] + [/.#Text]) ... Bits are the exception, since there is only "#1" and ... "#0", which means it is possible for bit ... pattern-matching to become exhaustive if complementary parts meet. - {#/.Simple {#/.Bit value}} + {/.#Simple {/.#Bit value}} (////\in {#Bit value}) ... Tuple patterns can be exhaustive if there is exhaustiveness for all of ... their sub-patterns. - {#/.Complex {#/.Tuple membersP+}} + {/.#Complex {/.#Tuple membersP+}} (case (list.reversed membersP+) - (^or #.End {#.Item _ #.End}) + (^or {.#End} {.#Item _ {.#End}}) (/.except ..invalid_tuple_pattern []) - {#.Item lastP prevsP+} + {.#Item lastP prevsP+} (do ////.monad [lastC (determine lastP)] (monad.mix ////.monad @@ -135,7 +135,7 @@ (do ////.monad [leftC (determine leftP)] (case rightC - #Exhaustive + {#Exhaustive} (in leftC) _ @@ -144,15 +144,15 @@ ... Variant patterns can be shown to be exhaustive if all the possible ... cases are handled exhaustively. - {#/.Complex {#/.Variant [lefts right? value]}} + {/.#Complex {/.#Variant [lefts right? value]}} (do ////.monad [value_coverage (determine value) .let [idx (if right? (++ lefts) lefts)]] (in {#Variant (if right? - {#.Some idx} - #.None) + {.#Some idx} + {.#None}) (|> (dictionary.empty n.hash) (dictionary.has idx value_coverage))})))) @@ -185,7 +185,7 @@ (implementation: equivalence (Equivalence Coverage) (def: (= reference sample) (case [reference sample] - [#Exhaustive #Exhaustive] + [{#Exhaustive} {#Exhaustive}] #1 [{#Bit sideR} {#Bit sideS}] @@ -226,13 +226,13 @@ (def: .public (merged addition so_far) (-> Coverage Coverage (Try Coverage)) (case [addition so_far] - [#Partial #Partial] - (try\in #Partial) + [{#Partial} {#Partial}] + (try\in {#Partial}) ... 2 bit coverages are exhaustive if they complement one another. (^multi [{#Bit sideA} {#Bit sideSF}] (xor sideA sideSF)) - (try\in #Exhaustive) + (try\in {#Exhaustive}) [{#Variant allA casesA} {#Variant allSF casesSF}] (let [addition_cases (cases allSF) @@ -250,12 +250,12 @@ [casesM (monad.mix ! (function (_ [tagA coverageA] casesSF') (case (dictionary.value tagA casesSF') - {#.Some coverageSF} + {.#Some coverageSF} (do ! [coverageM (merged coverageA coverageSF)] (in (dictionary.has tagA coverageM casesSF'))) - #.None + {.#None} (in (dictionary.has tagA coverageA casesSF')))) casesSF (dictionary.entries casesA))] (in (if (and (or (known_cases? addition_cases) @@ -263,9 +263,9 @@ (n.= (++ (n.max addition_cases so_far_cases)) (dictionary.size casesM)) (list.every? exhaustive? (dictionary.values casesM))) - #Exhaustive + {#Exhaustive} {#Variant (case allSF - {#.Some _} + {.#Some _} allSF _ @@ -300,12 +300,12 @@ (exception.except ..redundant_pattern [so_far addition])) ... The addition cannot possibly improve the coverage. - [_ #Exhaustive] + [_ {#Exhaustive}] (exception.except ..redundant_pattern [so_far addition]) ... The addition completes the coverage. - [#Exhaustive _] - (try\in #Exhaustive) + [{#Exhaustive} _] + (try\in {#Exhaustive}) ... The left part will always match, so the addition is redundant. (^multi [{#Seq left right} single] @@ -334,41 +334,41 @@ (function (_ coverageA possibilitiesSF) (loop [altsSF possibilitiesSF] (case altsSF - #.End - (in [#.None (list coverageA)]) + {.#End} + (in [{.#None} (list coverageA)]) - {#.Item altSF altsSF'} + {.#Item altSF altsSF'} (case (merged coverageA altSF) - {#try.Success altMSF} + {try.#Success altMSF} (case altMSF {#Alt _} (do ! [[success altsSF+] (recur altsSF')] - (in [success {#.Item altSF altsSF+}])) + (in [success {.#Item altSF altsSF+}])) _ - (in [{#.Some altMSF} altsSF'])) + (in [{.#Some altMSF} altsSF'])) - {#try.Failure error} - {#try.Failure error}) + {try.#Failure error} + {try.#Failure error}) ))))] [successA possibilitiesSF] (fuse_once addition (flat_alt so_far))] (loop [successA successA possibilitiesSF possibilitiesSF] (case successA - {#.Some coverageA'} + {.#Some coverageA'} (do ! [[successA' possibilitiesSF'] (fuse_once coverageA' possibilitiesSF)] (recur successA' possibilitiesSF')) - #.None + {.#None} (case (list.reversed possibilitiesSF) - {#.Item last prevs} + {.#Item last prevs} (in (list\mix (function (_ left right) {#Alt left right}) last prevs)) - #.End + {.#End} (undefined))))) _ 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 5b1ba0a7b..ab080a2b8 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 @@ -54,15 +54,15 @@ (loop [expectedT functionT] (/.with_stack ..cannot_analyse [expectedT function_name arg_name body] (case expectedT - {#.Named name unnamedT} + {.#Named name unnamedT} (recur unnamedT) - {#.Apply argT funT} + {.#Apply argT funT} (case (type.applied (list argT) funT) - {#.Some value} + {.#Some value} (recur value) - #.None + {.#None} (/.failure (ex.error cannot_analyse [expectedT function_name arg_name body]))) (^template [<tag> <instancer>] @@ -70,15 +70,15 @@ (do ! [[_ instanceT] (//type.with_env <instancer>)] (recur (maybe.trusted (type.applied (list instanceT) expectedT))))]) - ([#.UnivQ check.existential] - [#.ExQ check.var]) + ([.#UnivQ check.existential] + [.#ExQ check.var]) - {#.Var id} + {.#Var id} (do ! [?expectedT' (//type.with_env (check.peek id))] (case ?expectedT' - {#.Some expectedT'} + {.#Some expectedT'} (recur expectedT') ... Inference @@ -86,15 +86,15 @@ (do ! [[input_id inputT] (//type.with_env check.var) [output_id outputT] (//type.with_env check.var) - .let [functionT {#.Function inputT outputT}] + .let [functionT {.#Function inputT outputT}] functionA (recur functionT) _ (//type.with_env (check.check expectedT functionT))] (in functionA)))) - {#.Function inputT outputT} + {.#Function inputT outputT} (<| (\ ! each (.function (_ [scope bodyA]) - {#/.Function (list\each (|>> /.variable) + {/.#Function (list\each (|>> /.variable) (//scope.environment scope)) bodyA})) /.with_scope 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 68fafe17f..e377fedb0 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 @@ -66,20 +66,20 @@ (def: (replace parameter_idx replacement type) (-> Nat Type Type Type) (case type - {#.Primitive name params} - {#.Primitive name (list\each (replace parameter_idx replacement) params)} + {.#Primitive name params} + {.#Primitive name (list\each (replace parameter_idx replacement) params)} (^template [<tag>] [{<tag> left right} {<tag> (replace parameter_idx replacement left) (replace parameter_idx replacement right)}]) - ([#.Sum] - [#.Product] - [#.Function] - [#.Apply]) + ([.#Sum] + [.#Product] + [.#Function] + [.#Apply]) - {#.Parameter idx} + {.#Parameter idx} (if (n.= parameter_idx idx) replacement type) @@ -88,8 +88,8 @@ [{<tag> env quantified} {<tag> (list\each (replace parameter_idx replacement) env) (replace (n.+ 2 parameter_idx) replacement quantified)}]) - ([#.UnivQ] - [#.ExQ]) + ([.#UnivQ] + [.#ExQ]) _ type)) @@ -97,7 +97,7 @@ (def: (named_type location id) (-> Location Nat Type) (let [name (format "{New Type " (%.location location) " " (%.nat id) "}")] - {#.Primitive name (list)})) + {.#Primitive name (list)})) (def: new_named_type (Operation Type) @@ -116,22 +116,22 @@ (def: .public (general archive analyse inferT args) (-> Archive Phase Type (List Code) (Operation [Type (List Analysis)])) (case args - #.End + {.#End} (do ///.monad [_ (//type.infer inferT)] (in [inferT (list)])) - {#.Item argC args'} + {.#Item argC args'} (case inferT - {#.Named name unnamedT} + {.#Named name unnamedT} (general archive analyse unnamedT args) - {#.UnivQ _} + {.#UnivQ _} (do ///.monad [[var_id varT] (//type.with_env check.var)] (general archive analyse (maybe.trusted (type.applied (list varT) inferT)) args)) - {#.ExQ _} + {.#ExQ _} (do [! ///.monad] [[var_id varT] (//type.with_env check.var) output (general archive analyse @@ -147,12 +147,12 @@ (check.check varT newT))))] (in output)) - {#.Apply inputT transT} + {.#Apply inputT transT} (case (type.applied (list inputT) transT) - {#.Some outputT} + {.#Some outputT} (general archive analyse outputT args) - #.None + {.#None} (/.except ..invalid_type_application inferT)) ... Arguments are inferred back-to-front because, by convention, @@ -162,7 +162,7 @@ ... By inferring back-to-front, a lot of type-annotations can be ... avoided in Lux code, since the inference algorithm can piece ... things together more easily. - {#.Function inputT outputT} + {.#Function inputT outputT} (do ///.monad [[outputT' args'A] (general archive analyse outputT args') argA (<| (/.with_stack ..cannot_infer_argument [inputT argC]) @@ -170,12 +170,12 @@ (analyse archive argC))] (in [outputT' (list& argA args'A)])) - {#.Var infer_id} + {.#Var infer_id} (do ///.monad [?inferT' (//type.with_env (check.peek infer_id))] (case ?inferT' - {#.Some inferT'} + {.#Some inferT'} (general archive analyse inferT' args) _ @@ -189,15 +189,15 @@ (-> Nat Type Type Type) (function (recur base) (case base - {#.Primitive name parameters} - {#.Primitive name (list\each recur parameters)} + {.#Primitive name parameters} + {.#Primitive name (list\each recur parameters)} (^template [<tag>] [{<tag> left right} {<tag> (recur left) (recur right)}]) - ([#.Sum] [#.Product] [#.Function] [#.Apply]) + ([.#Sum] [.#Product] [.#Function] [.#Apply]) - {#.Parameter index} + {.#Parameter index} (if (n.= target index) sub base) @@ -205,7 +205,7 @@ (^template [<tag>] [{<tag> environment quantified} {<tag> (list\each recur environment) quantified}]) - ([#.UnivQ] [#.ExQ]) + ([.#UnivQ] [.#ExQ]) _ base))) @@ -214,7 +214,7 @@ (def: (record' record_size target originalT inferT) (-> Nat Nat Type Type (Operation Type)) (case inferT - {#.Named name unnamedT} + {.#Named name unnamedT} (record' record_size target originalT unnamedT) (^template [<tag>] @@ -222,18 +222,18 @@ (do ///.monad [bodyT+ (record' record_size (n.+ 2 target) originalT bodyT)] (in {<tag> env bodyT+}))]) - ([#.UnivQ] - [#.ExQ]) + ([.#UnivQ] + [.#ExQ]) - {#.Apply inputT funcT} + {.#Apply inputT funcT} (case (type.applied (list inputT) funcT) - {#.Some outputT} + {.#Some outputT} (record' record_size target originalT outputT) - #.None + {.#None} (/.except ..invalid_type_application inferT)) - {#.Product _} + {.#Product _} (let [[lefts right] (list.split_at (-- record_size) (type.flat_tuple inferT))] (///\in (|> inferT (type.function (list\composite lefts (list (type.tuple right)))) @@ -252,7 +252,7 @@ (loop [depth 0 currentT inferT] (case currentT - {#.Named name unnamedT} + {.#Named name unnamedT} (do ///.monad [unnamedT+ (recur depth unnamedT)] (in unnamedT+)) @@ -262,10 +262,10 @@ (do ///.monad [bodyT+ (recur (++ depth) bodyT)] (in {<tag> env bodyT+}))]) - ([#.UnivQ] - [#.ExQ]) + ([.#UnivQ] + [.#ExQ]) - {#.Sum _} + {.#Sum _} (let [cases (type.flat_variant currentT) actual_size (list.size cases) boundary (-- expected_size)] @@ -273,14 +273,14 @@ (and (n.> expected_size actual_size) (n.< boundary tag))) (case (list.item tag cases) - {#.Some caseT} + {.#Some caseT} (///\in (if (n.= 0 depth) (type.function (list caseT) currentT) (let [replace' (replace (|> depth -- (n.* 2)) inferT)] (type.function (list (replace' caseT)) (replace' currentT))))) - #.None + {.#None} (/.except ..variant_tag_out_of_bounds [expected_size tag inferT])) (n.< expected_size actual_size) @@ -297,12 +297,12 @@ ... else (/.except ..variant_tag_out_of_bounds [expected_size tag inferT]))) - {#.Apply inputT funcT} + {.#Apply inputT funcT} (case (type.applied (list inputT) funcT) - {#.Some outputT} + {.#Some outputT} (variant tag expected_size outputT) - #.None + {.#None} (/.except ..invalid_type_application 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 84124d32f..dde8eb173 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 @@ -44,19 +44,19 @@ (exception.report ["Definition" (%.name name)] ["Original" (case already_existing - {#.Alias alias} + {.#Alias alias} (format "alias " (%.name alias)) - {#.Definition definition} + {.#Definition definition} (format "definition " (%.name name)) - {#.Type _} + {.#Type _} (format "type " (%.name name)) - {#.Label _} + {.#Label _} (format "tag " (%.name name)) - {#.Slot _} + {.#Slot _} (format "slot " (%.name name)))])) (exception: .public (can_only_change_state_of_active_module [module Text @@ -64,17 +64,17 @@ (exception.report ["Module" module] ["Desired state" (case state - #.Active "Active" - #.Compiled "Compiled" - #.Cached "Cached")])) + {.#Active} "Active" + {.#Compiled} "Compiled" + {.#Cached} "Cached")])) (def: .public (empty hash) (-> Nat Module) - [#.module_hash hash - #.module_aliases (list) - #.definitions (list) - #.imports (list) - #.module_state #.Active]) + [.#module_hash hash + .#module_aliases (list) + .#definitions (list) + .#imports (list) + .#module_state {.#Active}]) (def: .public (import module) (-> Text (Operation Any)) @@ -82,12 +82,12 @@ (do ///.monad [self_name meta.current_module_name] (function (_ state) - {#try.Success [(revised@ #.modules - (plist.revised self_name (revised@ #.imports (function (_ current) + {try.#Success [(revised@ .#modules + (plist.revised self_name (revised@ .#imports (function (_ current) (if (list.any? (text\= module) current) current - {#.Item module current})))) + {.#Item module current})))) state) []]})))) @@ -97,9 +97,9 @@ (do ///.monad [self_name meta.current_module_name] (function (_ state) - {#try.Success [(revised@ #.modules - (plist.revised self_name (revised@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text])) - (|>> {#.Item [alias module]})))) + {try.#Success [(revised@ .#modules + (plist.revised self_name (revised@ .#module_aliases (: (-> (List [Text Text]) (List [Text Text])) + (|>> {.#Item [alias module]})))) state) []]})))) @@ -108,10 +108,10 @@ (///extension.lifted (function (_ state) (|> state - (value@ #.modules) + (value@ .#modules) (plist.value module) - (case> {#.Some _} #1 #.None #0) - [state] {#try.Success})))) + (case> {.#Some _} #1 {.#None} #0) + [state] {try.#Success})))) (def: .public (define name definition) (-> Text Global (Operation Any)) @@ -120,25 +120,25 @@ [self_name meta.current_module_name self meta.current_module] (function (_ state) - (case (plist.value name (value@ #.definitions self)) - #.None - {#try.Success [(revised@ #.modules + (case (plist.value name (value@ .#definitions self)) + {.#None} + {try.#Success [(revised@ .#modules (plist.has self_name - (revised@ #.definitions + (revised@ .#definitions (: (-> (List [Text Global]) (List [Text Global])) - (|>> {#.Item [name definition]})) + (|>> {.#Item [name definition]})) self)) state) []]} - {#.Some already_existing} + {.#Some already_existing} ((/.except' ..cannot_define_more_than_once [[self_name name] already_existing]) state)))))) (def: .public (create hash name) (-> Nat Text (Operation Any)) (///extension.lifted (function (_ state) - {#try.Success [(revised@ #.modules + {try.#Success [(revised@ .#modules (plist.has name (..empty hash)) state) []]}))) @@ -157,50 +157,50 @@ (-> Text (Operation Any)) (///extension.lifted (function (_ state) - (case (|> state (value@ #.modules) (plist.value module_name)) - {#.Some module} - (let [active? (case (value@ #.module_state module) - #.Active #1 - _ #0)] + (case (|> state (value@ .#modules) (plist.value module_name)) + {.#Some module} + (let [active? (case (value@ .#module_state module) + {.#Active} #1 + _ #0)] (if active? - {#try.Success [(revised@ #.modules - (plist.has module_name (with@ #.module_state <tag> module)) + {try.#Success [(revised@ .#modules + (plist.has module_name (with@ .#module_state {<tag>} module)) state) []]} - ((/.except' can_only_change_state_of_active_module [module_name <tag>]) + ((/.except' can_only_change_state_of_active_module [module_name {<tag>}]) state))) - #.None + {.#None} ((/.except' unknown_module module_name) state))))) (def: .public (<asker> module_name) (-> Text (Operation Bit)) (///extension.lifted (function (_ state) - (case (|> state (value@ #.modules) (plist.value module_name)) - {#.Some module} - {#try.Success [state - (case (value@ #.module_state module) + (case (|> state (value@ .#modules) (plist.value module_name)) + {.#Some module} + {try.#Success [state + (case (value@ .#module_state module) <tag> #1 _ #0)]} - #.None + {.#None} ((/.except' unknown_module module_name) state)))))] - [set_active active? #.Active] - [set_compiled compiled? #.Compiled] - [set_cached cached? #.Cached] + [set_active active? .#Active] + [set_compiled compiled? .#Compiled] + [set_cached cached? .#Cached] ) (def: (hash module_name) (-> Text (Operation Nat)) (///extension.lifted (function (_ state) - (case (|> state (value@ #.modules) (plist.value module_name)) - {#.Some module} - {#try.Success [state (value@ #.module_hash module)]} + (case (|> state (value@ .#modules) (plist.value module_name)) + {.#Some module} + {try.#Success [state (value@ .#module_hash module)]} - #.None + {.#None} ((/.except' unknown_module module_name) state))))) (def: .public (declare_tags record? tags exported? type) @@ -208,7 +208,7 @@ (do [! ///.monad] [self_name (///extension.lifted meta.current_module_name) [type_module type_name] (case type - {#.Named type_name _} + {.#Named type_name _} (in type_name) _ @@ -216,8 +216,8 @@ _ (///.assertion cannot_declare_tags_for_foreign_type [tags type] (text\= self_name type_module))] (monad.each ! (function (_ [index short]) - (..define (format "#" short) + (..define short (if record? - {#.Slot [exported? type tags index]} - {#.Label [exported? type tags index]}))) + {.#Slot [exported? type tags index]} + {.#Label [exported? type tags index]}))) (list.enumeration tags)))) 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 ad481b931..fe8c61096 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 @@ -16,18 +16,18 @@ (-> <type> (Operation Analysis)) (do ///.monad [_ (//type.infer <type>)] - (in {#/.Primitive {<tag> value}})))] + (in {/.#Primitive {<tag> value}})))] - [bit .Bit #/.Bit] - [nat .Nat #/.Nat] - [int .Int #/.Int] - [rev .Rev #/.Rev] - [frac .Frac #/.Frac] - [text .Text #/.Text] + [bit .Bit /.#Bit] + [nat .Nat /.#Nat] + [int .Int /.#Int] + [rev .Rev /.#Rev] + [frac .Frac /.#Frac] + [text .Text /.#Text] ) (def: .public unit (Operation Analysis) (do ///.monad [_ (//type.infer .Any)] - (in {#/.Primitive #/.Unit}))) + (in {/.#Primitive {/.#Unit}}))) 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 26946da08..05495f98d 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 @@ -36,14 +36,14 @@ (def: (definition def_name) (-> Name (Operation Analysis)) - (with_expansions [<return> (in (|> def_name ///reference.constant #/.Reference))] + (with_expansions [<return> (in (|> def_name ///reference.constant {/.#Reference}))] (do [! ///.monad] [constant (///extension.lifted (meta.definition def_name))] (case constant - {#.Alias real_def_name} + {.#Alias real_def_name} (definition real_def_name) - {#.Definition [exported? actualT _]} + {.#Definition [exported? actualT _]} (do ! [_ (//type.infer actualT) (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) @@ -58,7 +58,7 @@ (/.except foreign_module_has_not_been_imported [current ::module]))) (/.except definition_has_not_been_exported def_name)))) - {#.Type [exported? value labels]} + {.#Type [exported? value labels]} (do ! [_ (//type.infer .Type) (^@ def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) @@ -73,10 +73,10 @@ (/.except foreign_module_has_not_been_imported [current ::module]))) (/.except definition_has_not_been_exported def_name)))) - {#.Label _} + {.#Label _} (/.except labels_are_not_definitions [def_name]) - {#.Slot _} + {.#Slot _} (/.except labels_are_not_definitions [def_name]))))) (def: (variable var_name) @@ -84,13 +84,13 @@ (do [! ///.monad] [?var (//scope.find var_name)] (case ?var - {#.Some [actualT ref]} + {.#Some [actualT ref]} (do ! [_ (//type.infer actualT)] - (in {#.Some (|> ref ///reference.variable #/.Reference)})) + (in {.#Some (|> ref ///reference.variable {/.#Reference})})) - #.None - (in #.None)))) + {.#None} + (in {.#None})))) (def: .public (reference reference) (-> Name (Operation Analysis)) @@ -99,10 +99,10 @@ (do [! ///.monad] [?var (variable simple_name)] (case ?var - {#.Some varA} + {.#Some varA} (in varA) - #.None + {.#None} (do ! [this_module (///extension.lifted meta.current_module_name)] (definition [this_module 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 cb737d36d..d14adf09f 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 @@ -32,35 +32,35 @@ (def: (local? name scope) (-> Text Scope Bit) (|> scope - (value@ [#.locals #.mappings]) + (value@ [.#locals .#mappings]) (plist.contains? name))) (def: (local name scope) (-> Text Scope (Maybe [Type Variable])) (|> scope - (value@ [#.locals #.mappings]) + (value@ [.#locals .#mappings]) (plist.value name) (maybe\each (function (_ [type value]) - [type {#variable.Local value}])))) + [type {variable.#Local value}])))) (def: (captured? name scope) (-> Text Scope Bit) (|> scope - (value@ [#.captured #.mappings]) + (value@ [.#captured .#mappings]) (plist.contains? name))) (def: (captured name scope) (-> Text Scope (Maybe [Type Variable])) (loop [idx 0 - mappings (value@ [#.captured #.mappings] scope)] + mappings (value@ [.#captured .#mappings] scope)] (case mappings - {#.Item [_name [_source_type _source_ref]] mappings'} + {.#Item [_name [_source_type _source_ref]] mappings'} (if (text\= name _name) - {#.Some [_source_type {#variable.Foreign idx}]} + {.#Some [_source_type {variable.#Foreign idx}]} (recur (++ idx) mappings')) - #.End - #.None))) + {.#End} + {.#None}))) (def: (reference? name scope) (-> Text Scope Bit) @@ -70,8 +70,8 @@ (def: (reference name scope) (-> Text Scope (Maybe [Type Variable])) (case (..local name scope) - {#.Some type} - {#.Some type} + {.#Some type} + {.#Some type} _ (..captured name scope))) @@ -81,29 +81,29 @@ (///extension.lifted (function (_ state) (let [[inner outer] (|> state - (value@ #.scopes) + (value@ .#scopes) (list.split_when (|>> (reference? name))))] (case outer - #.End - {#.Right [state #.None]} + {.#End} + {.#Right [state {.#None}]} - {#.Item top_outer _} + {.#Item top_outer _} (let [[ref_type init_ref] (maybe.else (undefined) (..reference name top_outer)) [ref inner'] (list\mix (: (-> Scope [Variable (List Scope)] [Variable (List Scope)]) (function (_ scope ref+inner) - [{#variable.Foreign (value@ [#.captured #.counter] scope)} - {#.Item (revised@ #.captured + [{variable.#Foreign (value@ [.#captured .#counter] scope)} + {.#Item (revised@ .#captured (: (-> Foreign Foreign) - (|>> (revised@ #.counter ++) - (revised@ #.mappings (plist.has name [ref_type (product.left ref+inner)])))) + (|>> (revised@ .#counter ++) + (revised@ .#mappings (plist.has name [ref_type (product.left ref+inner)])))) scope) (product.right ref+inner)}])) - [init_ref #.End] + [init_ref {.#End}] (list.reversed inner)) scopes (list\composite inner' outer)] - {#.Right [(with@ #.scopes scopes state) - {#.Some [ref_type ref]}]}) + {.#Right [(with@ .#scopes scopes state) + {.#Some [ref_type ref]}]}) ))))) (exception: .public cannot_create_local_binding_without_a_scope) @@ -112,30 +112,30 @@ (def: .public (with_local [name type] action) (All (_ a) (-> [Text Type] (Operation a) (Operation a))) (function (_ [bundle state]) - (case (value@ #.scopes state) - {#.Item head tail} - (let [old_mappings (value@ [#.locals #.mappings] head) - new_var_id (value@ [#.locals #.counter] head) - new_head (revised@ #.locals + (case (value@ .#scopes state) + {.#Item head tail} + (let [old_mappings (value@ [.#locals .#mappings] head) + new_var_id (value@ [.#locals .#counter] head) + new_head (revised@ .#locals (: (-> Local Local) - (|>> (revised@ #.counter ++) - (revised@ #.mappings (plist.has name [type new_var_id])))) + (|>> (revised@ .#counter ++) + (revised@ .#mappings (plist.has name [type new_var_id])))) head)] - (case (///.result' [bundle (with@ #.scopes {#.Item new_head tail} state)] + (case (///.result' [bundle (with@ .#scopes {.#Item new_head tail} state)] action) - {#try.Success [[bundle' state'] output]} - (case (value@ #.scopes state') - {#.Item head' tail'} - (let [scopes' {#.Item (with@ #.locals (value@ #.locals head) head') + {try.#Success [[bundle' state'] output]} + (case (value@ .#scopes state') + {.#Item head' tail'} + (let [scopes' {.#Item (with@ .#locals (value@ .#locals head) head') tail'}] - {#try.Success [[bundle' (with@ #.scopes scopes' state')] + {try.#Success [[bundle' (with@ .#scopes scopes' state')] output]}) _ (exception.except ..invalid_scope_alteration [])) - {#try.Failure error} - {#try.Failure error})) + {try.#Failure error} + {try.#Failure error})) _ (exception.except ..cannot_create_local_binding_without_a_scope [])) @@ -144,8 +144,8 @@ (template [<name> <val_type>] [(def: <name> (Bindings Text [Type <val_type>]) - [#.counter 0 - #.mappings (list)])] + [.#counter 0 + .#mappings (list)])] [init_locals Nat] [init_captured Variable] @@ -153,31 +153,31 @@ (def: (scope parent_name child_name) (-> (List Text) Text Scope) - [#.name (list& child_name parent_name) - #.inner 0 - #.locals init_locals - #.captured init_captured]) + [.#name (list& child_name parent_name) + .#inner 0 + .#locals init_locals + .#captured init_captured]) (def: .public (with_scope name action) (All (_ a) (-> Text (Operation a) (Operation a))) (function (_ [bundle state]) - (let [parent_name (case (value@ #.scopes state) - #.End + (let [parent_name (case (value@ .#scopes state) + {.#End} (list) - {#.Item top _} - (value@ #.name top))] - (case (action [bundle (revised@ #.scopes - (|>> {#.Item (scope parent_name name)}) + {.#Item top _} + (value@ .#name top))] + (case (action [bundle (revised@ .#scopes + (|>> {.#Item (scope parent_name name)}) state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (revised@ #.scopes + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (revised@ .#scopes (|>> list.tail (maybe.else (list))) state')] output]} - {#try.Failure error} - {#try.Failure error})))) + {try.#Failure error} + {try.#Failure error})))) (exception: .public cannot_get_next_reference_when_there_is_no_scope) @@ -185,24 +185,24 @@ (Operation Register) (///extension.lifted (function (_ state) - (case (value@ #.scopes state) - {#.Item top _} - {#try.Success [state (value@ [#.locals #.counter] top)]} + (case (value@ .#scopes state) + {.#Item top _} + {try.#Success [state (value@ [.#locals .#counter] top)]} - #.End + {.#End} (exception.except ..cannot_get_next_reference_when_there_is_no_scope []))))) (def: (ref_variable ref) (-> Ref Variable) (case ref - {#.Local register} - {#variable.Local register} + {.#Local register} + {variable.#Local register} - {#.Captured register} - {#variable.Foreign register})) + {.#Captured register} + {variable.#Foreign register})) (def: .public (environment scope) (-> Scope (List Variable)) (|> scope - (value@ [#.captured #.mappings]) + (value@ [.#captured .#mappings]) (list\each (function (_ [_ [_ ref]]) (ref_variable ref))))) 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 0ccb8f1e0..188d8f7b8 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 @@ -115,28 +115,28 @@ (check.clean expectedT))] (/.with_stack ..cannot_analyse_variant [expectedT' tag valueC] (case expectedT - {#.Sum _} + {.#Sum _} (let [flat (type.flat_variant expectedT)] (case (list.item tag flat) - {#.Some variant_type} + {.#Some variant_type} (do ! [valueA (//type.with_type variant_type (analyse archive valueC))] (in (/.variant [lefts right? valueA]))) - #.None + {.#None} (/.except //inference.variant_tag_out_of_bounds [(list.size flat) tag expectedT]))) - {#.Named name unnamedT} + {.#Named name unnamedT} (//type.with_type unnamedT (recur valueC)) - {#.Var id} + {.#Var id} (do ! [?expectedT' (//type.with_env (check.peek id))] (case ?expectedT' - {#.Some expectedT'} + {.#Some expectedT'} (//type.with_type expectedT' (recur valueC)) @@ -152,18 +152,18 @@ [[instance_id instanceT] (//type.with_env <instancer>)] (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT)) (recur valueC)))]) - ([#.UnivQ check.existential] - [#.ExQ check.var]) + ([.#UnivQ check.existential] + [.#ExQ check.var]) - {#.Apply inputT funT} + {.#Apply inputT funT} (case funT - {#.Var funT_id} + {.#Var funT_id} (do ! [?funT' (//type.with_env (check.peek funT_id))] (case ?funT' - {#.Some funT'} - (//type.with_type {#.Apply inputT funT'} + {.#Some funT'} + (//type.with_type {.#Apply inputT funT'} (recur valueC)) _ @@ -171,11 +171,11 @@ _ (case (type.applied (list inputT) funT) - {#.Some outputT} + {.#Some outputT} (//type.with_type outputT (recur valueC)) - #.None + {.#None} (/.except ..not_a_quantified_type funT))) _ @@ -189,26 +189,26 @@ (loop [membersT+ (type.flat_tuple expectedT) membersC+ members] (case [membersT+ membersC+] - [{#.Item memberT #.End} {#.Item memberC #.End}] + [{.#Item memberT {.#End}} {.#Item memberC {.#End}}] (do ! [memberA (//type.with_type memberT (analyse archive memberC))] (in (list memberA))) - [{#.Item memberT #.End} _] + [{.#Item memberT {.#End}} _] (//type.with_type memberT (\ ! each (|>> list) (analyse archive (code.tuple membersC+)))) - [_ {#.Item memberC #.End}] + [_ {.#Item memberC {.#End}}] (//type.with_type (type.tuple membersT+) (\ ! each (|>> list) (analyse archive memberC))) - [{#.Item memberT membersT+'} {#.Item memberC membersC+'}] + [{.#Item memberT membersT+'} {.#Item memberC membersC+'}] (do ! [memberA (//type.with_type memberT (analyse archive memberC)) memberA+ (recur membersT+' membersC+')] - (in {#.Item memberA memberA+})) + (in {.#Item memberA memberA+})) _ (/.except ..cannot_analyse_tuple [expectedT members]))))] @@ -220,19 +220,19 @@ [expectedT (///extension.lifted meta.expected_type)] (/.with_stack ..cannot_analyse_tuple [expectedT membersC] (case expectedT - {#.Product _} + {.#Product _} (..typed_product archive analyse membersC) - {#.Named name unnamedT} + {.#Named name unnamedT} (//type.with_type unnamedT (product archive analyse membersC)) - {#.Var id} + {.#Var id} (do ! [?expectedT' (//type.with_env (check.peek id))] (case ?expectedT' - {#.Some expectedT'} + {.#Some expectedT'} (//type.with_type expectedT' (product archive analyse membersC)) @@ -252,18 +252,18 @@ [[instance_id instanceT] (//type.with_env <instancer>)] (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT)) (product archive analyse membersC)))]) - ([#.UnivQ check.existential] - [#.ExQ check.var]) + ([.#UnivQ check.existential] + [.#ExQ check.var]) - {#.Apply inputT funT} + {.#Apply inputT funT} (case funT - {#.Var funT_id} + {.#Var funT_id} (do ! [?funT' (//type.with_env (check.peek funT_id))] (case ?funT' - {#.Some funT'} - (//type.with_type {#.Apply inputT funT'} + {.#Some funT'} + (//type.with_type {.#Apply inputT funT'} (product archive analyse membersC)) _ @@ -271,11 +271,11 @@ _ (case (type.applied (list inputT) funT) - {#.Some outputT} + {.#Some outputT} (//type.with_type outputT (product archive analyse membersC)) - #.None + {.#None} (/.except ..not_a_quantified_type funT))) _ @@ -291,7 +291,7 @@ [lefts right?] (/.choice case_size idx)] expectedT (///extension.lifted meta.expected_type)] (case expectedT - {#.Var _} + {.#Var _} (do ! [inferenceT (//inference.variant idx case_size variantT) [inferredT valueA+] (//inference.general archive analyse inferenceT (list valueC))] @@ -308,18 +308,18 @@ (-> (List Code) (Operation (Maybe (List [Name Code])))) (loop [input record output (: (List [Name Code]) - #.End)] + {.#End})] (case input - (^ (list& [_ {#.Tag slotH}] valueH tail)) + (^ (list& [_ {.#Tag slotH}] valueH tail)) (do ///.monad [slotH (///extension.lifted (meta.normal slotH))] - (recur tail {#.Item [slotH valueH] output})) + (recur tail {.#Item [slotH valueH] output})) - #.End - (\ ///.monad in {#.Some output}) + {.#End} + (\ ///.monad in {.#Some output}) _ - (\ ///.monad in #.None)))) + (\ ///.monad in {.#None})))) ... Lux already possesses the means to analyse tuples, so ... re-implementing the same functionality for records makes no sense. @@ -328,17 +328,17 @@ (-> (List [Name Code]) (Operation (Maybe [Nat (List Code) Type]))) (case record ... empty_record = empty_tuple = unit/any = [] - #.End - (\ ///.monad in {#.Some [0 (list) Any]}) + {.#End} + (\ ///.monad in {.#Some [0 (list) Any]}) - {#.Item [head_k head_v] _} + {.#Item [head_k head_v] _} (do [! ///.monad] [slotH' (///extension.lifted (do meta.monad [head_k (meta.normal head_k)] (meta.try (meta.slot head_k))))] (case slotH' - {#try.Success [_ slot_set recordT]} + {try.#Success [_ slot_set recordT]} (do ! [.let [size_record (list.size record) size_ts (list.size slot_set)] @@ -352,12 +352,12 @@ (do ! [key (///extension.lifted (meta.normal key))] (case (dictionary.value key tag->idx) - {#.Some idx} + {.#Some idx} (if (dictionary.key? idx->val idx) (/.except ..cannot_repeat_tag [key record]) (in (dictionary.has idx val idx->val))) - #.None + {.#None} (/.except ..slot_does_not_belong_to_record [key recordT])))) (: (Dictionary Nat Code) (dictionary.empty n.hash)) @@ -365,10 +365,10 @@ .let [ordered_tuple (list\each (function (_ idx) (maybe.trusted (dictionary.value idx idx->val))) tuple_range)]] - (in {#.Some [size_ts ordered_tuple recordT]})) + (in {.#Some [size_ts ordered_tuple recordT]})) - {#try.Failure error} - (in #.None))) + {try.#Failure error} + (in {.#None}))) )) (def: .public (record archive analyse members) @@ -380,12 +380,12 @@ (^ (list singletonC)) (analyse archive singletonC) - (^ (list [_ {#.Tag pseudo_slot}] singletonC)) + (^ (list [_ {.#Tag pseudo_slot}] singletonC)) (do [! ///.monad] [head_k (///extension.lifted (meta.normal pseudo_slot)) slot (///extension.lifted (meta.try (meta.slot head_k)))] (case slot - {#try.Success [_ slot_set recordT]} + {try.#Success [_ slot_set recordT]} (case (list.size slot_set) 1 (analyse archive singletonC) _ (..product archive analyse members)) @@ -397,21 +397,21 @@ (do [! ///.monad] [?members (normal members)] (case ?members - #.None + {.#None} (..product archive analyse members) - {#.Some slots} + {.#Some slots} (do ! [record_size,membersC,recordT (..order slots)] (case record_size,membersC,recordT - #.None + {.#None} (..product archive analyse members) - {#.Some [record_size membersC recordT]} + {.#Some [record_size membersC recordT]} (do ! [expectedT (///extension.lifted meta.expected_type)] (case expectedT - {#.Var _} + {.#Var _} (do ! [inferenceT (//inference.record record_size recordT) [inferredT membersA] (//inference.general archive analyse inferenceT membersC)] 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 33a8715d5..1f53c1154 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 @@ -18,23 +18,23 @@ (def: .public (with_type expected) (All (_ a) (-> Type (Operation a) (Operation a))) - (///extension.localized (value@ #.expected) (with@ #.expected) - (function.constant {#.Some expected}))) + (///extension.localized (value@ .#expected) (with@ .#expected) + (function.constant {.#Some expected}))) (def: .public (with_env action) (All (_ a) (-> (Check a) (Operation a))) (function (_ (^@ stateE [bundle state])) - (case (action (value@ #.type_context state)) - {#try.Success [context' output]} - {#try.Success [[bundle (with@ #.type_context context' state)] + (case (action (value@ .#type_context state)) + {try.#Success [context' output]} + {try.#Success [[bundle (with@ .#type_context context' state)] output]} - {#try.Failure error} + {try.#Failure error} ((/.failure error) stateE)))) (def: .public with_fresh_env (All (_ a) (-> (Operation a) (Operation a))) - (///extension.localized (value@ #.type_context) (with@ #.type_context) + (///extension.localized (value@ .#type_context) (with@ .#type_context) (function.constant check.fresh_context))) (def: .public (infer actualT) 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 dc47f7039..0d95f2262 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 @@ -48,13 +48,13 @@ Eval) (function (_ type code lux) (case (compiler_eval archive type code [bundle lux]) - {#try.Success [[_bundle lux'] value]} - {#try.Success [lux' value]} + {try.#Success [[_bundle lux'] value]} + {try.#Success [lux' value]} - {#try.Failure error} - {#try.Failure error}))) + {try.#Failure error} + {try.#Failure error}))) -(with_expansions [<lux_def_module> (as_is [|form_location| {#.Form (list& [|text_location| {#.Text "lux def module"}] annotations)}])] +(with_expansions [<lux_def_module> (as_is [|form_location| {.#Form (list& [|text_location| {.#Text "lux def module"}] annotations)}])] (def: .public (phase wrapper expander) (-> //.Wrapper Expander Phase) (let [analysis (//analysis.phase expander)] @@ -62,18 +62,18 @@ (do [! //.monad] [state //.get_state .let [compiler_eval (meta_eval archive - (value@ [#//extension.state #/.analysis #/.state #//extension.bundle] state) + (value@ [//extension.#state /.#analysis /.#state //extension.#bundle] state) (evaluation.evaluator expander - (value@ [#//extension.state #/.synthesis #/.state] state) - (value@ [#//extension.state #/.generation #/.state] state) - (value@ [#//extension.state #/.generation #/.phase] state))) + (value@ [//extension.#state /.#synthesis /.#state] state) + (value@ [//extension.#state /.#generation /.#state] state) + (value@ [//extension.#state /.#generation /.#phase] state))) extension_eval (:as Eval (wrapper (:expected compiler_eval)))] - _ (//.set_state (with@ [#//extension.state #/.analysis #/.state #//extension.state #.eval] extension_eval state))] + _ (//.set_state (with@ [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code - (^ [_ {#.Form (list& [_ {#.Text name}] inputs)}]) + (^ [_ {.#Form (list& [_ {.#Text name}] inputs)}]) (//extension.apply archive recur [name inputs]) - (^ [_ {#.Form (list& macro inputs)}]) + (^ [_ {.#Form (list& macro inputs)}]) (do ! [expansion (/.lifted_analysis (do ! @@ -84,10 +84,10 @@ (do ! [?macro (//extension.lifted (meta.macro macro_name)) macro (case ?macro - {#.Some macro} + {.#Some macro} (in macro) - #.None + {.#None} (//.except ..macro_was_not_found macro_name))] (//extension.lifted (///analysis/macro.expand expander macro_name macro inputs))) @@ -96,7 +96,7 @@ (case expansion (^ (list& <lux_def_module> referrals)) (|> (recur archive <lux_def_module>) - (\ ! each (revised@ #/.referrals (list\composite referrals)))) + (\ ! each (revised@ /.#referrals (list\composite referrals)))) _ (|> expansion 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 2fd695eef..7f3481817 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 @@ -97,8 +97,8 @@ (-> (Extender s i o) Text (Handler s i o) (Operation s i o Any))) (function (_ [bundle state]) (case (dictionary.value name bundle) - #.None - {#try.Success [[(dictionary.has name (extender handler) bundle) state] + {.#None} + {try.#Success [[(dictionary.has name (extender handler) bundle) state] []]} _ @@ -119,11 +119,11 @@ (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) (function (_ (^@ stateE [bundle state])) (case (dictionary.value name bundle) - {#.Some handler} + {.#Some handler} (((handler name phase) archive parameters) stateE) - #.None + {.#None} (exception.except ..unknown [name bundle])))) (def: .public (localized get set transform) @@ -134,11 +134,11 @@ (function (_ [bundle state]) (let [old (get state)] (case (operation [bundle (set (transform old) state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' (set old state')] output]} + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' (set old state')] output]} - {#try.Failure error} - {#try.Failure error}))))) + {try.#Failure error} + {try.#Failure error}))))) (def: .public (temporary transform) (All (_ s i o v) @@ -147,11 +147,11 @@ (function (_ operation) (function (_ [bundle state]) (case (operation [bundle (transform state)]) - {#try.Success [[bundle' state'] output]} - {#try.Success [[bundle' state] output]} + {try.#Success [[bundle' state'] output]} + {try.#Success [[bundle' state] output]} - {#try.Failure error} - {#try.Failure error})))) + {try.#Failure error} + {try.#Failure error})))) (def: .public (with_state state) (All (_ s i o v) @@ -162,13 +162,13 @@ (All (_ s i o v) (-> (-> s v) (Operation s i o v))) (function (_ [bundle state]) - {#try.Success [[bundle state] (get state)]})) + {try.#Success [[bundle state] (get state)]})) (def: .public (update transform) (All (_ s i o) (-> (-> s s) (Operation s i o Any))) (function (_ [bundle state]) - {#try.Success [[bundle (transform state)] []]})) + {try.#Success [[bundle (transform state)] []]})) (def: .public (lifted action) (All (_ s i o v) @@ -176,8 +176,8 @@ (//.Operation [(Bundle s i o) s] v))) (function (_ [bundle state]) (case (action state) - {#try.Success [state' output]} - {#try.Success [[bundle state'] output]} + {try.#Success [state' output]} + {try.#Success [[bundle state'] output]} - {#try.Failure error} - {#try.Failure error}))) + {try.#Failure error} + {try.#Failure error}))) 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 36578eb15..6de21c89b 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 @@ -38,7 +38,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -50,7 +50,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -64,7 +64,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -80,7 +80,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -94,7 +94,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -117,7 +117,7 @@ (phase archive constructorC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& constructorA inputsA)})))])) + (in {analysis.#Extension extension (list& constructorA inputsA)})))])) (def: object::get Handler @@ -128,7 +128,7 @@ [objectA (analysis/type.with_type Any (phase archive objectC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list (analysis.text fieldC) + (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) (def: object::do @@ -141,7 +141,7 @@ (phase archive objectC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text methodC) + (in {analysis.#Extension extension (list& (analysis.text methodC) objectA inputsA)})))])) @@ -165,7 +165,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: js::apply Handler @@ -177,7 +177,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: js::type_of Handler @@ -188,7 +188,7 @@ [objectA (analysis/type.with_type Any (phase archive objectC)) _ (analysis/type.infer .Text)] - (in {#analysis.Extension extension (list objectA)})))])) + (in {analysis.#Extension extension (list objectA)})))])) (def: js::function Handler @@ -201,7 +201,7 @@ (phase archive abstractionC)) _ (analysis/type.infer (for [@.js ffi.Function] Any))] - (in {#analysis.Extension extension (list (analysis.nat arity) + (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) (def: .public bundle 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 f9cf0b336..88b935e35 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 @@ -161,13 +161,13 @@ (def: inheritance_relationship_type_name "_jvm_inheritance") (def: .public (inheritance_relationship_type class super_class super_interfaces) (-> .Type .Type (List .Type) .Type) - {#.Primitive ..inheritance_relationship_type_name + {.#Primitive ..inheritance_relationship_type_name (list& class super_class super_interfaces)}) ... TODO: Get rid of this template block and use the definition in ... lux/ffi.jvm.lux ASAP (template [<name> <class>] - [(def: .public <name> .Type {#.Primitive <class> #.End})] + [(def: .public <name> .Type {.#Primitive <class> {.#End}})] ... Boxes [Boolean box.boolean] @@ -355,31 +355,31 @@ (def: (jvm_type luxT) (-> .Type (Operation (Type Value))) (case luxT - {#.Named name anonymousT} + {.#Named name anonymousT} (jvm_type anonymousT) - {#.Apply inputT abstractionT} + {.#Apply inputT abstractionT} (case (type.applied (list inputT) abstractionT) - {#.Some outputT} + {.#Some outputT} (jvm_type outputT) - #.None + {.#None} (/////analysis.except ..non_jvm_type luxT)) - (^ {#.Primitive (static array.type_name) (list elemT)}) + (^ {.#Primitive (static array.type_name) (list elemT)}) (phase\each jvm.array (jvm_type elemT)) - {#.Primitive class parametersT} + {.#Primitive class parametersT} (case (dictionary.value class ..boxes) - {#.Some [_ primitive_type]} + {.#Some [_ primitive_type]} (case parametersT - #.End + {.#End} (phase\in primitive_type) _ (/////analysis.except ..primitives_cannot_have_type_parameters class)) - #.None + {.#None} (do [! phase.monad] [parametersJT (: (Operation (List (Type Parameter))) (monad.each ! @@ -387,15 +387,15 @@ (do phase.monad [parameterJT (jvm_type parameterT)] (case (jvm_parser.parameter? parameterJT) - {#.Some parameterJT} + {.#Some parameterJT} (in parameterJT) - #.None + {.#None} (/////analysis.except ..non_parameter parameterT)))) parametersT))] (in (jvm.class class parametersJT)))) - {#.Ex _} + {.#Ex _} (phase\in (jvm.class ..object_class (list))) _ @@ -417,11 +417,11 @@ (^ (list arrayC)) (do phase.monad [_ (typeA.infer ..int) - arrayA (typeA.with_type {#.Primitive (|> (jvm.array primitive_type) + arrayA (typeA.with_type {.#Primitive (|> (jvm.array primitive_type) ..reflection) (list)} (analyse archive arrayC))] - (in {#/////analysis.Extension extension_name (list arrayA)})) + (in {/////analysis.#Extension extension_name (list arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -438,7 +438,7 @@ (analyse archive arrayC)) varT (typeA.with_env (check.clean varT)) arrayJT (jvm_array_type (.type (array.Array varT)))] - (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature arrayJT)) + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) arrayA)})) _ @@ -452,9 +452,9 @@ (do phase.monad [lengthA (typeA.with_type ..int (analyse archive lengthC)) - _ (typeA.infer {#.Primitive (|> (jvm.array primitive_type) ..reflection) + _ (typeA.infer {.#Primitive (|> (jvm.array primitive_type) ..reflection) (list)})] - (in {#/////analysis.Extension extension_name (list lengthA)})) + (in {/////analysis.#Extension extension_name (list lengthA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -470,12 +470,12 @@ expectedT (///.lifted meta.expected_type) expectedJT (jvm_array_type expectedT) elementJT (case (jvm_parser.array? expectedJT) - {#.Some elementJT} + {.#Some elementJT} (in elementJT) - #.None + {.#None} (/////analysis.except ..non_array expectedT))] - (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature elementJT)) + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature elementJT)) lengthA)})) _ @@ -484,11 +484,11 @@ (def: (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT - (^ {#.Primitive (static array.type_name) + (^ {.#Primitive (static array.type_name) (list elementT)}) (/////analysis.except ..non_parameter objectT) - {#.Primitive name parameters} + {.#Primitive name parameters} (`` (cond (or (~~ (template [<type>] [(text\= (..reflection <type>) name)] @@ -506,27 +506,27 @@ ... else (phase\in (jvm.class name (list))))) - {#.Named name anonymous} + {.#Named name anonymous} (check_parameter anonymous) (^template [<tag>] [{<tag> id} (phase\in (jvm.class ..object_class (list)))]) - ([#.Var] - [#.Ex]) + ([.#Var] + [.#Ex]) (^template [<tag>] [{<tag> env unquantified} (check_parameter unquantified)]) - ([#.UnivQ] - [#.ExQ]) + ([.#UnivQ] + [.#ExQ]) - {#.Apply inputT abstractionT} + {.#Apply inputT abstractionT} (case (type.applied (list inputT) abstractionT) - {#.Some outputT} + {.#Some outputT} (check_parameter outputT) - #.None + {.#None} (/////analysis.except ..non_parameter objectT)) _ @@ -535,7 +535,7 @@ (def: (check_jvm objectT) (-> .Type (Operation (Type Value))) (case objectT - {#.Primitive name #.End} + {.#Primitive name {.#End}} (`` (cond (~~ (template [<type>] [(text\= (..reflection <type>) name) (phase\in <type>)] @@ -565,37 +565,37 @@ (text.starts_with? descriptor.array_prefix name) (let [[_ unprefixed] (maybe.trusted (text.split_by descriptor.array_prefix name))] (\ phase.monad each jvm.array - (check_jvm {#.Primitive unprefixed (list)}))) + (check_jvm {.#Primitive unprefixed (list)}))) ... else (phase\in (jvm.class name (list))))) - (^ {#.Primitive (static array.type_name) + (^ {.#Primitive (static array.type_name) (list elementT)}) (|> elementT check_jvm (phase\each jvm.array)) - {#.Primitive name parameters} + {.#Primitive name parameters} (do [! phase.monad] [parameters (monad.each ! check_parameter parameters)] (phase\in (jvm.class name parameters))) - {#.Named name anonymous} + {.#Named name anonymous} (check_jvm anonymous) (^template [<tag>] [{<tag> env unquantified} (check_jvm unquantified)]) - ([#.UnivQ] - [#.ExQ]) + ([.#UnivQ] + [.#ExQ]) - {#.Apply inputT abstractionT} + {.#Apply inputT abstractionT} (case (type.applied (list inputT) abstractionT) - {#.Some outputT} + {.#Some outputT} (check_jvm outputT) - #.None + {.#None} (/////analysis.except ..non_object objectT)) _ @@ -624,10 +624,10 @@ [_ (typeA.infer lux_type) idxA (typeA.with_type ..int (analyse archive idxC)) - arrayA (typeA.with_type {#.Primitive (|> (jvm.array jvm_type) ..reflection) + arrayA (typeA.with_type {.#Primitive (|> (jvm.array jvm_type) ..reflection) (list)} (analyse archive arrayC))] - (in {#/////analysis.Extension extension_name (list idxA arrayA)})) + (in {/////analysis.#Extension extension_name (list idxA arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) @@ -647,7 +647,7 @@ arrayJT (jvm_array_type (.type (array.Array varT))) idxA (typeA.with_type ..int (analyse archive idxC))] - (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature arrayJT)) + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) idxA arrayA)})) @@ -656,7 +656,7 @@ (def: (write_primitive_array_handler lux_type jvm_type) (-> .Type (Type Primitive) Handler) - (let [array_type {#.Primitive (|> (jvm.array jvm_type) ..reflection) + (let [array_type {.#Primitive (|> (jvm.array jvm_type) ..reflection) (list)}] (function (_ extension_name analyse archive args) (case args @@ -669,7 +669,7 @@ (analyse archive valueC)) arrayA (typeA.with_type array_type (analyse archive arrayC))] - (in {#/////analysis.Extension extension_name (list idxA + (in {/////analysis.#Extension extension_name (list idxA valueA arrayA)})) @@ -693,7 +693,7 @@ (analyse archive idxC)) valueA (typeA.with_type varT (analyse archive valueC))] - (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature arrayJT)) + (in {/////analysis.#Extension extension_name (list (/////analysis.text (..signature arrayJT)) idxA valueA arrayA)})) @@ -759,7 +759,7 @@ (do phase.monad [expectedT (///.lifted meta.expected_type) _ (check_object expectedT)] - (in {#/////analysis.Extension extension_name (list)})) + (in {/////analysis.#Extension extension_name (list)})) _ (/////analysis.except ///.incorrect_arity [extension_name 0 (list.size args)])))) @@ -774,7 +774,7 @@ [objectT objectA] (typeA.with_inference (analyse archive objectC)) _ (check_object objectT)] - (in {#/////analysis.Extension extension_name (list objectA)})) + (in {/////analysis.#Extension extension_name (list objectA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -789,7 +789,7 @@ (analyse archive monitorC)) _ (check_object monitorT) exprA (analyse archive exprC)] - (in {#/////analysis.Extension extension_name (list monitorA exprA)})) + (in {/////analysis.#Extension extension_name (list monitorA exprA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) @@ -809,7 +809,7 @@ (if ? (in []) (/////analysis.except non_throwable exception_class)))] - (in {#/////analysis.Extension extension_name (list exceptionA)})) + (in {/////analysis.#Extension extension_name (list exceptionA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -820,12 +820,12 @@ (case args (^ (list classC)) (case classC - [_ {#.Text class}] + [_ {.#Text class}] (do phase.monad [_ (..ensure_fresh_class! class_loader class) - _ (typeA.infer {#.Primitive "java.lang.Class" (list {#.Primitive class (list)})}) + _ (typeA.infer {.#Primitive "java.lang.Class" (list {.#Primitive class (list)})}) _ (phase.lifted (reflection!.load class_loader class))] - (in {#/////analysis.Extension extension_name (list (/////analysis.text class))})) + (in {/////analysis.#Extension extension_name (list (/////analysis.text class))})) _ (/////analysis.except ///.invalid_syntax [extension_name %.code args])) @@ -846,18 +846,18 @@ object_class (check_object objectT) ? (phase.lifted (reflection!.sub? class_loader object_class sub_class))] (if ? - (in {#/////analysis.Extension extension_name (list (/////analysis.text sub_class) objectA)}) + (in {/////analysis.#Extension extension_name (list (/////analysis.text sub_class) objectA)}) (/////analysis.except cannot_possibly_be_an_instance (format sub_class " !<= " object_class)))))])) (template [<name> <category> <parser>] [(def: .public (<name> mapping typeJ) (-> Mapping (Type <category>) (Operation .Type)) (case (|> typeJ ..signature (<text>.result (<parser> mapping))) - {#try.Success check} + {try.#Success check} (typeA.with_env check) - {#try.Failure error} + {try.#Failure error} (phase.failure error)))] [boxed_reflection_type Value luxT.boxed_type] @@ -880,19 +880,19 @@ superT (reflection_type mapping superJT)] (in [[super_name superT] (java/lang/Class::isAssignableFrom super_class target_class)]))) (case (java/lang/Class::getGenericSuperclass source_class) - {#.Some super} - (list& super (array.list #.None (java/lang/Class::getGenericInterfaces source_class))) + {.#Some super} + (list& super (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))) - #.None + {.#None} (if (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers source_class)) - {#.Item (:as java/lang/reflect/Type (ffi.class_for java/lang/Object)) - (array.list #.None (java/lang/Class::getGenericInterfaces source_class))} - (array.list #.None (java/lang/Class::getGenericInterfaces source_class))))))) + {.#Item (:as java/lang/reflect/Type (ffi.class_for java/lang/Object)) + (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))} + (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))))))) (def: (inheritance_candidate_parents class_loader fromT target_class toT fromC) (-> java/lang/ClassLoader .Type (java/lang/Class java/lang/Object) .Type Code (Operation (List [[Text .Type] Bit]))) (case fromT - (^ {#.Primitive _ (list& self_classT super_classT super_interfacesT+)}) + (^ {.#Primitive _ (list& self_classT super_classT super_interfacesT+)}) (monad.each phase.monad (function (_ superT) (do [! phase.monad] @@ -959,13 +959,13 @@ (case (|> candidate_parents (list.only product.right) (list\each product.left)) - {#.Item [next_name nextT] _} + {.#Item [next_name nextT] _} (recur [next_name nextT]) - #.End + {.#End} (in false)))))))))] (if can_cast? - (in {#/////analysis.Extension extension_name (list (/////analysis.text source_name) + (in {/////analysis.#Extension extension_name (list (/////analysis.text source_name) (/////analysis.text target_name) fromA)}) (/////analysis.except ..cannot_cast [fromT toT fromC]))) @@ -1001,7 +1001,7 @@ (not deprecated?)) fieldT (reflection_type luxT.fresh fieldJT) _ (typeA.infer fieldT)] - (in (<| {#/////analysis.Extension extension_name} + (in (<| {/////analysis.#Extension extension_name} (list (/////analysis.text class) (/////analysis.text field) (/////analysis.text (|> fieldJT ..reflection)))))))])) @@ -1025,7 +1025,7 @@ fieldT (reflection_type luxT.fresh fieldJT) valueA (typeA.with_type fieldT (analyse archive valueC))] - (in (<| {#/////analysis.Extension extension_name} + (in (<| {/////analysis.#Extension extension_name} (list (/////analysis.text class) (/////analysis.text field) valueA)))))])) @@ -1049,7 +1049,7 @@ (not deprecated?)) fieldT (reflection_type mapping fieldJT) _ (typeA.infer fieldT)] - (in (<| {#/////analysis.Extension extension_name} + (in (<| {/////analysis.#Extension extension_name} (list (/////analysis.text class) (/////analysis.text field) (/////analysis.text (..reflection fieldJT)) @@ -1078,7 +1078,7 @@ fieldT (reflection_type mapping fieldJT) valueA (typeA.with_type fieldT (analyse archive valueC))] - (in (<| {#/////analysis.Extension extension_name} + (in (<| {/////analysis.#Extension extension_name} (list (/////analysis.text class) (/////analysis.text field) (/////analysis.text (..reflection fieldJT)) @@ -1087,30 +1087,30 @@ (type: Method_Style (Variant - #Static - #Abstract - #Virtual - #Special - #Interface)) + {#Static} + {#Abstract} + {#Virtual} + {#Special} + {#Interface})) (def: (check_method aliasing class method_name method_style inputsJT method) (-> Aliasing (java/lang/Class java/lang/Object) Text Method_Style (List (Type Value)) java/lang/reflect/Method (Operation Bit)) (do phase.monad [parameters (|> (java/lang/reflect/Method::getGenericParameterTypes method) - (array.list #.None) + (array.list {.#None}) (monad.each try.monad reflection!.type) phase.lifted) .let [modifiers (java/lang/reflect/Method::getModifiers method) correct_class? (java/lang/Object::equals class (java/lang/reflect/Method::getDeclaringClass method)) correct_method? (text\= method_name (java/lang/reflect/Method::getName method)) static_matches? (case method_style - #Static + {#Static} (java/lang/reflect/Modifier::isStatic modifiers) _ true) special_matches? (case method_style - #Special + {#Special} (not (or (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class)) (java/lang/reflect/Modifier::isAbstract modifiers))) @@ -1122,13 +1122,13 @@ (and prev (jvm\= expectedJC (: (Type Value) (case (jvm_parser.var? actualJC) - {#.Some name} + {.#Some name} (|> aliasing (dictionary.value name) (maybe.else name) jvm.var) - #.None + {.#None} actualJC))))) true (list.zipped/2 parameters inputsJT)))]] @@ -1143,7 +1143,7 @@ (-> Aliasing (java/lang/Class java/lang/Object) (List (Type Value)) (java/lang/reflect/Constructor java/lang/Object) (Operation Bit)) (do phase.monad [parameters (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor) - (array.list #.None) + (array.list {.#None}) (monad.each try.monad reflection!.type) phase.lifted)] (in (and (java/lang/Object::equals class (java/lang/reflect/Constructor::getDeclaringClass constructor)) @@ -1151,19 +1151,19 @@ (list.every? (function (_ [expectedJC actualJC]) (jvm\= expectedJC (: (Type Value) (case (jvm_parser.var? actualJC) - {#.Some name} + {.#Some name} (|> aliasing (dictionary.value name) (maybe.else name) jvm.var) - #.None + {.#None} actualJC)))) (list.zipped/2 parameters inputsJT)))))) (def: index_parameter (-> Nat .Type) - (|>> (n.* 2) ++ #.Parameter)) + (|>> (n.* 2) ++ {.#Parameter})) (def: (jvm_type_var_mapping owner_tvars method_tvars) (-> (List Text) (List Text) [(List .Type) Mapping]) @@ -1183,20 +1183,20 @@ (-> Method_Style java/lang/reflect/Method (Operation Method_Signature)) (let [owner (java/lang/reflect/Method::getDeclaringClass method) owner_tvars (case method_style - #Static + {#Static} (list) _ (|> (java/lang/Class::getTypeParameters owner) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName)))) method_tvars (|> (java/lang/reflect/Method::getTypeParameters method) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName))) [owner_tvarsT mapping] (jvm_type_var_mapping owner_tvars method_tvars)] (do [! phase.monad] [inputsT (|> (java/lang/reflect/Method::getGenericParameterTypes method) - (array.list #.None) + (array.list {.#None}) (monad.each ! (|>> reflection!.type phase.lifted)) (phase\each (monad.each ! (..reflection_type mapping))) phase\conjoint) @@ -1207,17 +1207,17 @@ (phase\each (..reflection_return mapping)) phase\conjoint) exceptionsT (|> (java/lang/reflect/Method::getGenericExceptionTypes method) - (array.list #.None) + (array.list {.#None}) (monad.each ! (|>> reflection!.type phase.lifted)) (phase\each (monad.each ! (..reflection_type mapping))) phase\conjoint) .let [methodT (<| (type.univ_q (dictionary.size mapping)) (type.function (case method_style - #Static + {#Static} inputsT _ - (list& {#.Primitive (java/lang/Class::getName owner) owner_tvarsT} + (list& {.#Primitive (java/lang/Class::getName owner) owner_tvarsT} inputsT))) outputT)]] (in [methodT @@ -1228,24 +1228,24 @@ (-> (java/lang/reflect/Constructor java/lang/Object) (Operation Method_Signature)) (let [owner (java/lang/reflect/Constructor::getDeclaringClass constructor) owner_tvars (|> (java/lang/Class::getTypeParameters owner) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName))) method_tvars (|> (java/lang/reflect/Constructor::getTypeParameters constructor) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName))) [owner_tvarsT mapping] (jvm_type_var_mapping owner_tvars method_tvars)] (do [! phase.monad] [inputsT (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor) - (array.list #.None) + (array.list {.#None}) (monad.each ! (|>> reflection!.type phase.lifted)) (phase\each (monad.each ! (reflection_type mapping))) phase\conjoint) exceptionsT (|> (java/lang/reflect/Constructor::getGenericExceptionTypes constructor) - (array.list #.None) + (array.list {.#None}) (monad.each ! (|>> reflection!.type phase.lifted)) (phase\each (monad.each ! (reflection_type mapping))) phase\conjoint) - .let [objectT {#.Primitive (java/lang/Class::getName owner) owner_tvarsT} + .let [objectT {.#Primitive (java/lang/Class::getName owner) owner_tvarsT} constructorT (<| (type.univ_q (dictionary.size mapping)) (type.function inputsT) objectT)]] @@ -1262,10 +1262,10 @@ [(def: <name> (-> Evaluation (Maybe Method_Signature)) (|>> (case> {<tag> output} - {#.Some output} + {.#Some output} _ - #.None)))] + {.#None})))] [pass! #Pass] [hint! #Hint] @@ -1275,7 +1275,7 @@ [(def: <name> (-> <type> (List (Type Var))) (|>> <method> - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName jvm.var))))] [class_type_variables (java/lang/Class java/lang/Object) java/lang/Class::getTypeParameters] @@ -1296,7 +1296,7 @@ .let [expected_class_tvars (class_type_variables class)] candidates (|> class java/lang/Class::getDeclaredMethods - (array.list #.None) + (array.list {.#None}) (list.only (|>> java/lang/reflect/Method::getName (text\= method_name))) (monad.each ! (: (-> java/lang/reflect/Method (Operation Evaluation)) (function (_ method) @@ -1306,14 +1306,14 @@ (..aliasing expected_method_tvars actual_method_tvars))] passes? (check_method aliasing class method_name method_style inputsJT method)] (\ ! each (if passes? - (|>> #Pass) - (|>> #Hint)) + (|>> {#Pass}) + (|>> {#Hint})) (method_signature method_style method)))))))] (case (list.all pass! candidates) - {#.Item method #.End} + {.#Item method {.#End}} (in method) - #.End + {.#End} (/////analysis.except ..no_candidates [class_name method_name inputsJT (list.all hint! candidates)]) candidates @@ -1329,7 +1329,7 @@ .let [expected_class_tvars (class_type_variables class)] candidates (|> class java/lang/Class::getConstructors - (array.list #.None) + (array.list {.#None}) (monad.each ! (function (_ constructor) (do ! [.let [expected_method_tvars (constructor_type_variables constructor) @@ -1337,13 +1337,15 @@ (..aliasing expected_method_tvars actual_method_tvars))] passes? (check_constructor aliasing class inputsJT constructor)] (\ ! each - (if passes? (|>> #Pass) (|>> #Hint)) + (if passes? + (|>> {#Pass}) + (|>> {#Hint})) (constructor_signature constructor))))))] (case (list.all pass! candidates) - {#.Item constructor #.End} + {.#Item constructor {.#End}} (in constructor) - #.End + {.#End} (/////analysis.except ..no_candidates [class_name ..constructor_method inputsJT (list.all hint! candidates)]) candidates @@ -1382,12 +1384,12 @@ (do phase.monad [_ (..ensure_fresh_class! class_loader class) .let [argsT (list\each product.left argsTC)] - [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Static argsT) + [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method {#Static} argsT) _ (phase.assertion ..deprecated_method [class method methodT] (not deprecated?)) [outputT argsA] (inferenceA.general archive analyse methodT (list\each product.right argsTC)) outputJT (check_return outputT)] - (in {#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) + (in {/////analysis.#Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) (/////analysis.text method) (/////analysis.text (..signature outputJT)) (decorate_inputs argsT argsA))})))])) @@ -1400,18 +1402,18 @@ (do phase.monad [_ (..ensure_fresh_class! class_loader class) .let [argsT (list\each product.left argsTC)] - [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Virtual argsT) + [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method {#Virtual} argsT) _ (phase.assertion ..deprecated_method [class method methodT] (not deprecated?)) [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\each product.right argsTC))) .let [[objectA argsA] (case allA - {#.Item objectA argsA} + {.#Item objectA argsA} [objectA argsA] _ (undefined))] outputJT (check_return outputT)] - (in {#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) + (in {/////analysis.#Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) (/////analysis.text method) (/////analysis.text (..signature outputJT)) objectA @@ -1425,12 +1427,12 @@ (do phase.monad [_ (..ensure_fresh_class! class_loader class) .let [argsT (list\each product.left argsTC)] - [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method #Special argsT) + [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class method_tvars method {#Special} argsT) _ (phase.assertion ..deprecated_method [class method methodT] (not deprecated?)) [outputT argsA] (inferenceA.general archive analyse methodT (list& objectC (list\each product.right argsTC))) outputJT (check_return outputT)] - (in {#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) + (in {/////analysis.#Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) (/////analysis.text method) (/////analysis.text (..signature outputJT)) (decorate_inputs argsT argsA))})))])) @@ -1446,18 +1448,18 @@ class (phase.lifted (reflection!.load class_loader class_name)) _ (phase.assertion non_interface class_name (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers class))) - [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class_name method_tvars method #Interface argsT) + [methodT deprecated? exceptionsT] (..method_candidate class_loader class_tvars class_name method_tvars method {#Interface} argsT) _ (phase.assertion ..deprecated_method [class_name method methodT] (not deprecated?)) [outputT allA] (inferenceA.general archive analyse methodT (list& objectC (list\each product.right argsTC))) .let [[objectA argsA] (case allA - {#.Item objectA argsA} + {.#Item objectA argsA} [objectA argsA] _ (undefined))] outputJT (check_return outputT)] - (in {#/////analysis.Extension extension_name + (in {/////analysis.#Extension extension_name (list& (/////analysis.text (..signature (jvm.class class_name (list)))) (/////analysis.text method) (/////analysis.text (..signature outputJT)) @@ -1476,7 +1478,7 @@ _ (phase.assertion ..deprecated_method [class ..constructor_method methodT] (not deprecated?)) [outputT argsA] (inferenceA.general archive analyse methodT (list\each product.right argsTC))] - (in {#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) + (in {/////analysis.#Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) (decorate_inputs argsT argsA))})))])) (def: (bundle::member class_loader) @@ -1554,23 +1556,23 @@ (-> (java/lang/Class java/lang/Object) (Try (List [Text (Type Method)]))) (|>> java/lang/Class::getDeclaredMethods - (array.list #.None) + (array.list {.#None}) <only> (monad.each try.monad (function (_ method) (do [! try.monad] [.let [type_variables (|> (java/lang/reflect/Method::getTypeParameters method) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName jvm.var)))] inputs (|> (java/lang/reflect/Method::getGenericParameterTypes method) - (array.list #.None) + (array.list {.#None}) (monad.each ! reflection!.type)) return (|> method java/lang/reflect/Method::getGenericReturnType reflection!.return) exceptions (|> (java/lang/reflect/Method::getGenericExceptionTypes method) - (array.list #.None) + (array.list {.#None}) (monad.each ! reflection!.class))] (in [(java/lang/reflect/Method::getName method) (jvm.method [type_variables inputs return exceptions])]))))))] @@ -1607,10 +1609,10 @@ (type: .public Visibility (Variant - #Public - #Private - #Protected - #Default)) + {#Public} + {#Private} + {#Protected} + {#Default})) (type: .public Finality Bit) (type: .public Strictness Bit) @@ -1631,10 +1633,10 @@ (def: .public (visibility_analysis visibility) (-> Visibility Analysis) (/////analysis.text (case visibility - #Public ..public_tag - #Private ..private_tag - #Protected ..protected_tag - #Default ..default_tag))) + {#Public} ..public_tag + {#Private} ..private_tag + {#Protected} ..protected_tag + {#Default} ..default_tag))) (type: .public (Constructor a) [Visibility @@ -1693,7 +1695,7 @@ (in [name luxT]))) arguments) [scope bodyA] (|> arguments' - {#.Item [self_name selfT]} + {.#Item [self_name selfT]} list.reversed (list\mix scope.with_local (analyse archive body)) (typeA.with_type .Any) @@ -1707,7 +1709,7 @@ (/////analysis.tuple (list\each ..argument_analysis arguments)) (/////analysis.tuple (list\each class_analysis exceptions)) (/////analysis.tuple (list\each typed_analysis super_arguments)) - {#/////analysis.Function + {/////analysis.#Function (list\each (|>> /////analysis.variable) (scope.environment scope)) (/////analysis.tuple (list bodyA))} @@ -1769,7 +1771,7 @@ (in [name luxT]))) arguments) [scope bodyA] (|> arguments' - {#.Item [self_name selfT]} + {.#Item [self_name selfT]} list.reversed (list\mix scope.with_local (analyse archive body)) (typeA.with_type returnT) @@ -1785,7 +1787,7 @@ (/////analysis.tuple (list\each ..argument_analysis arguments)) (return_analysis return) (/////analysis.tuple (list\each class_analysis exceptions)) - {#/////analysis.Function + {/////analysis.#Function (list\each (|>> /////analysis.variable) (scope.environment scope)) (/////analysis.tuple (list bodyA))} @@ -1857,7 +1859,7 @@ (return_analysis return) (/////analysis.tuple (list\each class_analysis exceptions)) - {#/////analysis.Function + {/////analysis.#Function (list\each (|>> /////analysis.variable) (scope.environment scope)) (/////analysis.tuple (list bodyA))} @@ -1914,10 +1916,10 @@ (case (list.one (function (_ super) (let [[super_name super_parameters] (jvm_parser.read_class super)] (if (text\= parent_name super_name) - {#.Some super_parameters} - #.None))) + {.#Some super_parameters} + {.#None}))) supers) - {#.Some super_parameters} + {.#Some super_parameters} (let [expected_count (list.size parent_parameters) actual_count (list.size super_parameters)] (if (n.= expected_count actual_count) @@ -1931,7 +1933,7 @@ (\ ! each (|>> (list.zipped/2 parent_parameters))))) (phase.lifted (exception.except ..mismatched_super_parameters [parent_name expected_count actual_count])))) - #.None + {.#None} (phase.lifted (exception.except ..unknown_super [parent_name supers]))))) (def: .public (with_fresh_type_vars vars mapping) @@ -1966,23 +1968,23 @@ bodyA 2 - {#/////analysis.Case (/////analysis.unit) - [[#/////analysis.when - {#/////analysis.Bind 2} + {/////analysis.#Case (/////analysis.unit) + [[/////analysis.#when + {/////analysis.#Bind 2} - #/////analysis.then + /////analysis.#then bodyA] (list)]} _ - {#/////analysis.Case (/////analysis.unit) - [[#/////analysis.when - {#/////analysis.Complex - {#/////analysis.Tuple (|> arity + {/////analysis.#Case (/////analysis.unit) + [[/////analysis.#when + {/////analysis.#Complex + {/////analysis.#Tuple (|> arity list.indices - (list\each (|>> (n.+ 2) #/////analysis.Bind)))}} + (list\each (|>> (n.+ 2) {/////analysis.#Bind})))}} - #/////analysis.then + /////analysis.#then bodyA] (list)]}))) @@ -2012,7 +2014,7 @@ arguments) returnT (boxed_reflection_return mapping return) [scope bodyA] (|> arguments' - {#.Item [self_name selfT]} + {.#Item [self_name selfT]} list.reversed (list\mix scope.with_local (analyse archive body)) (typeA.with_type returnT) @@ -2028,7 +2030,7 @@ (return_analysis return) (/////analysis.tuple (list\each class_analysis exceptions)) - {#/////analysis.Function + {/////analysis.#Function (list\each (|>> /////analysis.variable) (scope.environment scope)) (..hide_method_body (list.size arguments) bodyA)} @@ -2074,7 +2076,7 @@ [.let [[name actual_parameters] (jvm_parser.read_class class)] class (phase.lifted (reflection!.load class_loader name)) .let [expected_parameters (|> (java/lang/Class::getTypeParameters class) - (array.list #.None) + (array.list {.#None}) (list\each (|>> java/lang/reflect/TypeVariable::getName)))] _ (phase.assertion ..class_parameter_mismatch [expected_parameters actual_parameters] (n.= (list.size expected_parameters) @@ -2082,10 +2084,10 @@ (in (|> (list.zipped/2 expected_parameters actual_parameters) (list\mix (function (_ [expected actual] mapping) (case (jvm_parser.var? actual) - {#.Some actual} + {.#Some actual} (dictionary.has actual expected mapping) - #.None + {.#None} mapping)) jvm_alias.fresh))))) @@ -2154,7 +2156,7 @@ selfT (///.lifted (do meta.monad [where meta.current_module_name id meta.seed] - (in (inheritance_relationship_type {#.Primitive (..anonymous_class_name where id) (list)} + (in (inheritance_relationship_type {.#Primitive (..anonymous_class_name where id) (list)} super_classT super_interfaceT+)))) _ (typeA.infer selfT) @@ -2165,10 +2167,10 @@ (analyse archive term))] (in [type termA]))) constructor_args) - .let [supers {#.Item super_class super_interfaces}] + .let [supers {.#Item super_class super_interfaces}] _ (..require_complete_method_concretion class_loader supers methods) methodsA (monad.each ! (analyse_overriden_method analyse archive selfT mapping supers) methods)] - (in {#/////analysis.Extension extension_name + (in {/////analysis.#Extension extension_name (list (class_analysis super_class) (/////analysis.tuple (list\each class_analysis super_interfaces)) (/////analysis.tuple (list\each typed_analysis constructor_argsA+)) 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 c9c1dfb0b..beb9ac7c4 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 @@ -50,7 +50,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -62,7 +62,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -76,7 +76,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -92,7 +92,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -106,7 +106,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -128,7 +128,7 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list (analysis.text fieldC) + (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) (def: object::do @@ -141,7 +141,7 @@ (phase archive objectC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text methodC) + (in {analysis.#Extension extension (list& (analysis.text methodC) objectA inputsA)})))])) @@ -165,7 +165,7 @@ [inputA (analysis/type.with_type (type <fromT>) (phase archive inputC)) _ (analysis/type.infer (type <toT>))] - (in {#analysis.Extension extension (list inputA)})))]))] + (in {analysis.#Extension extension (list inputA)})))]))] [utf8::encode Text (array.Array (I64 Any))] [utf8::decode (array.Array (I64 Any)) Text] @@ -186,7 +186,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: lua::apply Handler @@ -198,7 +198,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: lua::power Handler @@ -211,7 +211,7 @@ baseA (analysis/type.with_type Frac (phase archive baseC)) _ (analysis/type.infer Frac)] - (in {#analysis.Extension extension (list powerA baseA)})))])) + (in {analysis.#Extension extension (list powerA baseA)})))])) (def: lua::import Handler @@ -220,7 +220,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer ..Object)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: lua::function Handler @@ -232,7 +232,7 @@ abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] - (in {#analysis.Extension extension (list (analysis.nat arity) + (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) (def: .public bundle 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 0609bee0a..e1c23ed0d 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 @@ -41,10 +41,10 @@ Handler)) (function (_ extension_name analyse archive args) (case (<code>.result syntax args) - {#try.Success inputs} + {try.#Success inputs} (handler extension_name analyse archive inputs) - {#try.Failure _} + {try.#Failure _} (////analysis.except ///.invalid_syntax [extension_name %.code args])))) (def: (simple inputsT+ outputT) @@ -60,7 +60,7 @@ (typeA.with_type argT (analyse archive argC))) (list.zipped/2 inputsT+ args))] - (in {#////analysis.Extension extension_name argsA})) + (in {////analysis.#Extension extension_name argsA})) (////analysis.except ///.incorrect_arity [extension_name num_expected num_actual])))))) (def: .public (nullary valueT) @@ -119,7 +119,7 @@ (list (////analysis.tuple (list\each (|>> ////analysis.nat) cases)) branch)))) (list& input else) - {#////analysis.Extension extension_name}))))]))) + {////analysis.#Extension extension_name}))))]))) ... "lux is" represents reference/pointer equality. (def: lux::is @@ -142,7 +142,7 @@ _ (typeA.infer (type (Either Text varT))) opA (typeA.with_type (type (-> .Any varT)) (analyse archive opC))] - (in {#////analysis.Extension extension_name (list opA)})) + (in {////analysis.#Extension extension_name (list opA)})) _ (////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -151,7 +151,7 @@ Handler (function (_ extension_name analyse archive argsC+) (case argsC+ - (^ (list [_ {#.Text module_name}] exprC)) + (^ (list [_ {.#Text module_name}] exprC)) (////analysis.with_current_module module_name (analyse archive exprC)) @@ -214,15 +214,15 @@ (do ! [input_type (///.lifted (meta.definition (name_of .Macro')))] (case input_type - (^or {#.Definition [exported? def_type def_value]} - {#.Type [exported? def_value labels]}) + (^or {.#Definition [exported? def_type def_value]} + {.#Type [exported? def_value labels]}) (in (:as Type def_value)) - (^or {#.Label _} - {#.Slot _}) + (^or {.#Label _} + {.#Slot _}) (////.failure (exception.error ..not_a_type [(name_of .Macro')])) - {#.Alias real_name} + {.#Alias real_name} (recur real_name))))] (typeA.with_type input_type (phase archive valueC))))])) 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 16717539b..0aa12b4be 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 @@ -38,7 +38,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -50,7 +50,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -64,7 +64,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -80,7 +80,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -94,7 +94,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -127,7 +127,7 @@ (do [! phase.monad] [inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text constructor) inputsA)})))])) + (in {analysis.#Extension extension (list& (analysis.text constructor) inputsA)})))])) (def: object::get Handler @@ -138,7 +138,7 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list (analysis.text fieldC) + (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) (def: object::do @@ -151,7 +151,7 @@ (phase archive objectC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text methodC) + (in {analysis.#Extension extension (list& (analysis.text methodC) objectA inputsA)})))])) @@ -173,7 +173,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: php::apply Handler @@ -185,7 +185,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: php::pack Handler @@ -198,7 +198,7 @@ dataA (analysis/type.with_type (type (Array (I64 Any))) (phase archive dataC)) _ (analysis/type.infer Text)] - (in {#analysis.Extension extension (list formatA dataA)})))])) + (in {analysis.#Extension extension (list formatA dataA)})))])) (def: .public bundle Bundle 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 ec21b45bc..385150e03 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 @@ -38,7 +38,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -50,7 +50,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -64,7 +64,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -80,7 +80,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -94,7 +94,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -136,7 +136,7 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list (analysis.text fieldC) + (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) (def: object::do @@ -149,7 +149,7 @@ (phase archive objectC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text methodC) + (in {analysis.#Extension extension (list& (analysis.text methodC) objectA inputsA)})))])) @@ -170,7 +170,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: python::import Handler @@ -179,7 +179,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer ..Object)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: python::apply Handler @@ -191,7 +191,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: python::function Handler @@ -203,7 +203,7 @@ abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] - (in {#analysis.Extension extension (list (analysis.nat arity) + (in {analysis.#Extension extension (list (analysis.nat arity) abstractionA)})))])) (def: python::exec @@ -217,7 +217,7 @@ globalsA (analysis/type.with_type ..Dict (phase archive globalsC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list codeA globalsA)})))])) + (in {analysis.#Extension extension (list codeA globalsA)})))])) (def: .public bundle Bundle 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 525458cdd..7a8eda597 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 @@ -38,7 +38,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -50,7 +50,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -64,7 +64,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -80,7 +80,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -94,7 +94,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -128,7 +128,7 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list (analysis.text fieldC) + (in {analysis.#Extension extension (list (analysis.text fieldC) objectA)})))])) (def: object::do @@ -141,7 +141,7 @@ (phase archive objectC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer .Any)] - (in {#analysis.Extension extension (list& (analysis.text methodC) + (in {analysis.#Extension extension (list& (analysis.text methodC) objectA inputsA)})))])) @@ -162,7 +162,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: ruby::apply Handler @@ -174,7 +174,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: ruby::import Handler @@ -183,7 +183,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Bit)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: .public bundle Bundle 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 a0df81d93..1dd6d0ca0 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 @@ -38,7 +38,7 @@ (phase archive lengthC)) [var_id varT] (analysis/type.with_env check.var) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list lengthA)})))])) + (in {analysis.#Extension extension (list lengthA)})))])) (def: array::length Handler @@ -50,7 +50,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer Nat)] - (in {#analysis.Extension extension (list arrayA)})))])) + (in {analysis.#Extension extension (list arrayA)})))])) (def: array::read Handler @@ -64,7 +64,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer varT)] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: array::write Handler @@ -80,7 +80,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA valueA arrayA)})))])) + (in {analysis.#Extension extension (list indexA valueA arrayA)})))])) (def: array::delete Handler @@ -94,7 +94,7 @@ arrayA (analysis/type.with_type (type (Array varT)) (phase archive arrayC)) _ (analysis/type.infer (type (Array varT)))] - (in {#analysis.Extension extension (list indexA arrayA)})))])) + (in {analysis.#Extension extension (list indexA arrayA)})))])) (def: bundle::array Bundle @@ -131,7 +131,7 @@ (function (_ extension phase archive name) (do phase.monad [_ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list (analysis.text name))})))])) + (in {analysis.#Extension extension (list (analysis.text name))})))])) (def: scheme::apply Handler @@ -143,7 +143,7 @@ (phase archive abstractionC)) inputsA (monad.each ! (|>> (phase archive) (analysis/type.with_type Any)) inputsC) _ (analysis/type.infer Any)] - (in {#analysis.Extension extension (list& abstractionA inputsA)})))])) + (in {analysis.#Extension extension (list& abstractionA inputsA)})))])) (def: .public bundle Bundle 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 76c66e37d..a4c026cb4 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 @@ -171,9 +171,9 @@ (def: (constraint name) (-> Text Constraint) - [#type.name name - #type.super_class (type.class "java.lang.Object" (list)) - #type.super_interfaces (list)]) + [type.#name name + type.#super_class (type.class "java.lang.Object" (list)) + type.#super_interfaces (list)]) (def: constant::modifier (Modifier field.Field) @@ -194,15 +194,15 @@ [constant (`` (|> value (~~ (template.spliced <constant>)))) attribute (attribute.constant constant)] (field.field ..constant::modifier name <type> (row.row attribute)))]) - ([#.Bit type.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] - [#.Int type.byte [.i64 i32.i32 constant.integer pool.integer]] - [#.Int type.short [.i64 i32.i32 constant.integer pool.integer]] - [#.Int type.int [.i64 i32.i32 constant.integer pool.integer]] - [#.Int type.long [constant.long pool.long]] - [#.Frac type.float [host.double_to_float constant.float pool.float]] - [#.Frac type.double [constant.double pool.double]] - [#.Nat type.char [.i64 i32.i32 constant.integer pool.integer]] - [#.Text (type.class "java.lang.String" (list)) [pool.string]] + ([.#Bit type.boolean [(case> #0 +0 #1 +1) .i64 i32.i32 constant.integer pool.integer]] + [.#Int type.byte [.i64 i32.i32 constant.integer pool.integer]] + [.#Int type.short [.i64 i32.i32 constant.integer pool.integer]] + [.#Int type.int [.i64 i32.i32 constant.integer pool.integer]] + [.#Int type.long [constant.long pool.long]] + [.#Frac type.float [host.double_to_float constant.float pool.float]] + [.#Frac type.double [constant.double pool.double]] + [.#Nat type.char [.i64 i32.i32 constant.integer pool.integer]] + [.#Text (type.class "java.lang.String" (list)) [pool.string]] ) ... TODO: Tighten this pattern-matching so this catch-all clause isn't necessary. @@ -275,13 +275,13 @@ (monad.each check.monad (|>> ..signature (luxT.check (luxT.class mapping))) super_interfaces))) - .let [selfT (jvm.inheritance_relationship_type {#.Primitive name (list\each product.right parameters)} + .let [selfT (jvm.inheritance_relationship_type {.#Primitive name (list\each product.right parameters)} super_classT super_interfaceT+)] state (extension.lifted phase.get_state) - .let [analyse (value@ [#directive.analysis #directive.phase] state) - synthesize (value@ [#directive.synthesis #directive.phase] state) - generate (value@ [#directive.generation #directive.phase] state)] + .let [analyse (value@ [directive.#analysis directive.#phase] state) + synthesize (value@ [directive.#synthesis directive.#phase] state) + generate (value@ [directive.#generation directive.#phase] state)] methods (monad.each ! (..method_definition [mapping selfT] [analyse synthesize generate]) methods) ... _ (directive.lifted_generation 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 95775c22a..fdd576cdc 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 @@ -54,10 +54,10 @@ (Handler anchor expression directive))) (function (_ extension_name phase archive inputs) (case (<code>.result syntax inputs) - {#try.Success inputs} + {try.#Success inputs} (handler extension_name phase archive inputs) - {#try.Failure error} + {try.#Failure error} (phase.except ///.invalid_syntax [extension_name %.code inputs])))) (def: (context [module_id artifact_id]) @@ -87,9 +87,9 @@ (-> Archive Type Code (Operation anchor expression directive [Type expression Any]))) (do phase.monad [state (///.lifted phase.get_state) - .let [analyse (value@ [#/////directive.analysis #/////directive.phase] state) - synthesize (value@ [#/////directive.synthesis #/////directive.phase] state) - generate (value@ [#/////directive.generation #/////directive.phase] state)] + .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) + synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) + generate (value@ [/////directive.#generation /////directive.#phase] state)] [_ codeA] (/////directive.lifted_analysis (/////analysis.with_scope (typeA.with_fresh_env @@ -113,8 +113,8 @@ [codeG (generate archive codeS) id (/////generation.learn name) module_id (phase.lifted (archive.id module archive)) - [target_name value directive] (/////generation.define! [module_id id] #.None codeG) - _ (/////generation.save! id #.None directive)] + [target_name value directive] (/////generation.define! [module_id id] {.#None} codeG) + _ (/////generation.save! id {.#None} directive)] (in [code//type codeG value])))) (def: (definition archive name expected codeC) @@ -123,14 +123,14 @@ (Operation anchor expression directive [Type expression Any]))) (do [! phase.monad] [state (///.lifted phase.get_state) - .let [analyse (value@ [#/////directive.analysis #/////directive.phase] state) - synthesize (value@ [#/////directive.synthesis #/////directive.phase] state) - generate (value@ [#/////directive.generation #/////directive.phase] state)] + .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) + synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) + generate (value@ [/////directive.#generation /////directive.#phase] state)] [_ code//type codeA] (/////directive.lifted_analysis (/////analysis.with_scope (typeA.with_fresh_env (case expected - #.None + {.#None} (do ! [[code//type codeA] (typeA.with_inference (analyse archive codeC)) @@ -138,7 +138,7 @@ (check.clean code//type))] (in [code//type codeA])) - {#.Some expected} + {.#Some expected} (do ! [codeA (typeA.with_type expected (analyse archive codeC))] @@ -165,8 +165,8 @@ [codeG (generate archive codeS) module_id (phase.lifted (archive.id current_module archive)) id (<learn> extension) - [target_name value directive] (/////generation.define! [module_id id] #.None codeG) - _ (/////generation.save! id #.None directive)] + [target_name value directive] (/////generation.define! [module_id id] {.#None} codeG) + _ (/////generation.save! id {.#None} directive)] (in [codeG value]))))) (def: .public (<full> archive extension codeT codeC) @@ -175,9 +175,9 @@ (Operation anchor expression directive [expression Any]))) (do phase.monad [state (///.lifted phase.get_state) - .let [analyse (value@ [#/////directive.analysis #/////directive.phase] state) - synthesize (value@ [#/////directive.synthesis #/////directive.phase] state) - generate (value@ [#/////directive.generation #/////directive.phase] state)] + .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) + synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) + generate (value@ [/////directive.#generation /////directive.#phase] state)] [_ codeA] (/////directive.lifted_analysis (/////analysis.with_scope (typeA.with_fresh_env @@ -199,11 +199,11 @@ (do phase.monad [[bundle state] phase.get_state .let [eval (/////analysis/evaluation.evaluator expander - (value@ [#/////directive.synthesis #/////directive.state] state) - (value@ [#/////directive.generation #/////directive.state] state) - (value@ [#/////directive.generation #/////directive.phase] state))]] + (value@ [/////directive.#synthesis /////directive.#state] state) + (value@ [/////directive.#generation /////directive.#state] state) + (value@ [/////directive.#generation /////directive.#phase] state))]] (phase.set_state [bundle - (revised@ [#/////directive.analysis #/////directive.state] + (revised@ [/////directive.#analysis /////directive.#state] (: (-> /////analysis.State+ /////analysis.State+) (|>> product.right [(///analysis.bundle eval host_analysis)])) @@ -219,15 +219,15 @@ (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ - (^ (list [_ {#.Identifier ["" short_name]}] valueC exported?C)) + (^ (list [_ {.#Identifier ["" short_name]}] valueC exported?C)) (do phase.monad [current_module (/////directive.lifted_analysis (///.lifted meta.current_module_name)) .let [full_name [current_module short_name]] - [type valueT value] (..definition archive full_name #.None valueC) + [type valueT value] (..definition archive full_name {.#None} valueC) [_ _ exported?] (evaluate! archive Bit exported?C) _ (/////directive.lifted_analysis - (module.define short_name {#.Definition [(:as Bit exported?) type value]})) + (module.define short_name {.#Definition [(:as Bit exported?) type value]})) _ (..refresh expander host_analysis) _ (..announce_definition! short_name type)] (in /////directive.no_requirements)) @@ -241,7 +241,7 @@ (/////directive.lifted_generation (monad.each phase.monad (function (_ tag) - (/////generation.log! (format "#" tag " : Tag of " (%.type owner)))) + (/////generation.log! (format tag " : Tag of " (%.type owner)))) tags))) (def: (def::type_tagged expander host_analysis) @@ -258,23 +258,23 @@ .let [full_name [current_module short_name]] [_ _ exported?] (evaluate! archive Bit exported?C) .let [exported? (:as Bit exported?)] - [type valueT value] (..definition archive full_name {#.Some .Type} valueC) + [type valueT value] (..definition archive full_name {.#Some .Type} valueC) labels (/////directive.lifted_analysis (do phase.monad [.let [[record? labels] (case labels - {#.Left tags} + {.#Left tags} [false tags] - {#.Right slots} + {.#Right slots} [true slots])] _ (case labels - #.End - (module.define short_name {#.Definition [exported? type value]}) + {.#End} + (module.define short_name {.#Definition [exported? type value]}) - {#.Item labels} - (module.define short_name {#.Type [exported? (:as .Type value) (if record? - {#.Right labels} - {#.Left labels})]})) + {.#Item labels} + (module.define short_name {.#Type [exported? (:as .Type value) (if record? + {.#Right labels} + {.#Left labels})]})) _ (module.declare_tags record? labels exported? (:as .Type value))] (in labels))) _ (..refresh expander host_analysis) @@ -302,8 +302,8 @@ "" (in []) _ (module.alias alias module)))) imports))] - (in [#/////directive.imports imports - #/////directive.referrals (list)])))])) + (in [/////directive.#imports imports + /////directive.#referrals (list)])))])) (exception: .public (cannot_alias_an_alias [local Alias foreign Alias @@ -325,15 +325,15 @@ [current_module (///.lifted meta.current_module_name) constant (///.lifted (meta.definition original))] (case constant - {#.Alias de_aliased} + {.#Alias de_aliased} (phase.except ..cannot_alias_an_alias [[current_module alias] original de_aliased]) - (^or {#.Definition _} - {#.Type _}) - (module.define alias {#.Alias original}) + (^or {.#Definition _} + {.#Type _}) + (module.define alias {.#Alias original}) - (^or {#.Label _} - {#.Slot _}) + (^or {.#Label _} + {.#Slot _}) (phase.except ..cannot_alias_a_label [[current_module alias] original])))) (def: def::alias @@ -343,8 +343,8 @@ (function (_ extension_name phase archive [alias def_name]) (do phase.monad [_ (///.lifted - (phase.sub [(value@ [#/////directive.analysis #/////directive.state]) - (with@ [#/////directive.analysis #/////directive.state])] + (phase.sub [(value@ [/////directive.#analysis /////directive.#state]) + (with@ [/////directive.#analysis /////directive.#state])] (define_alias alias def_name)))] (in /////directive.no_requirements)))])) @@ -428,7 +428,7 @@ (do phase.monad [programG (generate archive programS) artifact_id (/////generation.learn /////program.name)] - (/////generation.save! artifact_id #.None (program [module_id artifact_id] programG)))) + (/////generation.save! artifact_id {.#None} (program [module_id artifact_id] programG)))) (def: (def::program program) (All (_ anchor expression directive) @@ -438,9 +438,9 @@ (^ (list programC)) (do phase.monad [state (///.lifted phase.get_state) - .let [analyse (value@ [#/////directive.analysis #/////directive.phase] state) - synthesize (value@ [#/////directive.synthesis #/////directive.phase] state) - generate (value@ [#/////directive.generation #/////directive.phase] state)] + .let [analyse (value@ [/////directive.#analysis /////directive.#phase] state) + synthesize (value@ [/////directive.#synthesis /////directive.#phase] state) + generate (value@ [/////directive.#generation /////directive.#phase] state)] programS (prepare_program archive analyse synthesize programC) current_module (/////directive.lifted_analysis (///.lifted meta.current_module_name)) 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 8c6df79fd..aec90687b 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 @@ -45,10 +45,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) (template: (!unary function) 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 54b345e36..de36c0766 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 @@ -45,10 +45,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) ... [Procedures] @@ -101,7 +101,7 @@ Phase! (case synthesis ... TODO: Get rid of this ASAP - {#synthesis.Extension "lux syntax char case!" parameters} + {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] (in (:as Statement body))) @@ -121,8 +121,8 @@ (^template [<tag>] [(^ {<tag> value}) (/////\each _.return (expression archive synthesis))]) - ([#synthesis.Reference] - [#synthesis.Extension]) + ([synthesis.#Reference] + [synthesis.#Extension]) (^ (synthesis.branch/case case)) (//case.case! statement expression archive case) @@ -166,13 +166,13 @@ ... (in (_.apply/* (_.closure (list) ... (_.switch (_.the //runtime.i64_low_field inputG) ... conditionals! - ... {#.Some (_.return else!)})) + ... {.#Some (_.return else!)})) ... (list))) (in (<| (:as Expression) (: Statement) (_.switch (_.the //runtime.i64_low_field inputG) conditionals! - {#.Some else!})))))])) + {.#Some else!})))))])) ... [Bundles] (def: lux_procs 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 f3efd5f47..cb63e2a33 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 @@ -49,10 +49,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except /////extension.invalid_syntax [extension_name //////synthesis.%synthesis input])))) (def: $Boolean (type.class "java.lang.Boolean" (list))) 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 b070a0a6b..8784ae034 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 @@ -339,15 +339,15 @@ (do <>.monad [arrayJT (<t>.then parser.array <s>.text)] (case (parser.array? arrayJT) - {#.Some elementJT} + {.#Some elementJT} (case (parser.object? elementJT) - {#.Some elementJT} + {.#Some elementJT} (in elementJT) - #.None + {.#None} (<>.failure (exception.error ..not_an_object_array arrayJT))) - #.None + {.#None} (undefined)))) (def: (primitive_array_length_handler jvm_primitive) @@ -644,10 +644,10 @@ (do //////.monad [.let [$class (type.class class (list))]] (case (dictionary.value unboxed ..primitives) - {#.Some primitive} + {.#Some primitive} (in (_.getstatic $class field primitive)) - #.None + {.#None} (in (_.getstatic $class field (type.class unboxed (list)))))))])) (def: unitG (_.string //////synthesis.unit)) @@ -661,13 +661,13 @@ [valueG (generate archive valueS) .let [$class (type.class class (list))]] (case (dictionary.value unboxed ..primitives) - {#.Some primitive} + {.#Some primitive} (in ($_ _.composite valueG (_.putstatic $class field primitive) ..unitG)) - #.None + {.#None} (in ($_ _.composite valueG (_.checkcast $class) @@ -683,10 +683,10 @@ [objectG (generate archive objectS) .let [$class (type.class class (list)) getG (case (dictionary.value unboxed ..primitives) - {#.Some primitive} + {.#Some primitive} (_.getfield $class field primitive) - #.None + {.#None} (_.getfield $class field (type.class unboxed (list))))]] (in ($_ _.composite objectG @@ -703,10 +703,10 @@ objectG (generate archive objectS) .let [$class (type.class class (list)) putG (case (dictionary.value unboxed ..primitives) - {#.Some primitive} + {.#Some primitive} (_.putfield $class field primitive) - #.None + {.#None} (let [$unboxed (type.class unboxed (list))] ($_ _.composite (_.checkcast $unboxed) @@ -729,10 +729,10 @@ (do //////.monad [valueG (generate archive valueS)] (case (type.primitive? valueT) - {#.Right valueT} + {.#Right valueT} (in [valueT valueG]) - {#.Left valueT} + {.#Left valueT} (in [valueT ($_ _.composite valueG (_.checkcast valueT))])))) @@ -740,10 +740,10 @@ (def: (prepare_output outputT) (-> (Type Return) (Bytecode Any)) (case (type.void? outputT) - {#.Right outputT} + {.#Right outputT} ..unitG - {#.Left outputT} + {.#Left outputT} (\ _.monad in []))) (def: invoke::static @@ -857,15 +857,15 @@ (^template [<tag>] [(^ {<tag> leftP rightP}) {<tag> (recur leftP) (recur rightP)}]) - ([#//////synthesis.Alt] - [#//////synthesis.Seq]) + ([//////synthesis.#Alt] + [//////synthesis.#Seq]) (^template [<tag>] - [(^ {<tag> value}) + [(^ {<tag> _}) path]) - ([#//////synthesis.Pop] - [#//////synthesis.Bind] - [#//////synthesis.Access]) + ([//////synthesis.#Pop] + [//////synthesis.#Bind] + [//////synthesis.#Access]) _ (undefined)))) @@ -877,7 +877,7 @@ (^template [<tag>] [(^ {<tag> value}) body]) - ([#//////synthesis.Primitive] + ([//////synthesis.#Primitive] [//////synthesis.constant]) (^ (//////synthesis.variant [lefts right? sub])) @@ -928,8 +928,8 @@ (^ (//////synthesis.function/apply [functionS inputsS+])) (//////synthesis.function/apply [(recur functionS) (list\each recur inputsS+)]) - {#//////synthesis.Extension [name inputsS+]} - {#//////synthesis.Extension [name (list\each recur inputsS+)]}))) + {//////synthesis.#Extension [name inputsS+]} + {//////synthesis.#Extension [name (list\each recur inputsS+)]}))) (def: $Object (type.class "java.lang.Object" (list))) @@ -952,7 +952,7 @@ (_.putfield class (///reference.foreign_name register) $Object)))))] (method.method method.public "<init>" (anonymous_init_method env) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite (_.aload 0) (monad.each _.monad product.right inputsTG) (_.invokespecial super_class "<init>" (type.method [(list\each product.left inputsTG) type.void (list)])) @@ -972,17 +972,17 @@ (def: (returnG returnT) (-> (Type Return) (Bytecode Any)) (case (type.void? returnT) - {#.Right returnT} + {.#Right returnT} _.return - {#.Left returnT} + {.#Left returnT} (case (type.primitive? returnT) - {#.Left returnT} + {.#Left returnT} ($_ _.composite (_.checkcast returnT) _.areturn) - {#.Right returnT} + {.#Right returnT} (cond (or (\ type.equivalence = type.boolean returnT) (\ type.equivalence = type.byte returnT) (\ type.equivalence = type.short returnT) @@ -1027,7 +1027,7 @@ ... Give them names as "foreign" variables. list.enumeration (list\each (function (_ [id capture]) - [capture {#//////variable.Foreign id}])) + [capture {//////variable.#Foreign id}])) (dictionary.from_list //////variable.hash)) normalized_methods (list\each (function (_ [environment [ownerT name @@ -1037,7 +1037,7 @@ (let [local_mapping (|> environment list.enumeration (list\each (function (_ [foreign_id capture]) - [{#//////variable.Foreign foreign_id} + [{//////variable.#Foreign foreign_id} (|> global_mapping (dictionary.value capture) maybe.trusted)])) @@ -1066,7 +1066,7 @@ returnT exceptionsT]) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite bodyG (returnG returnT))})))) normalized_methods) 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 3523c19fa..1de9c4057 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 @@ -48,10 +48,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) (template: (!unary function) @@ -61,7 +61,7 @@ Phase! (case synthesis ... TODO: Get rid of this ASAP - {#synthesis.Extension "lux syntax char case!" parameters} + {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] (in (:as Statement body))) @@ -81,8 +81,8 @@ (^template [<tag>] [(^ {<tag> value}) (/////\each _.return (expression archive synthesis))]) - ([#synthesis.Reference] - [#synthesis.Extension]) + ([synthesis.#Reference] + [synthesis.#Extension]) (^ (synthesis.branch/case case)) (//case.case! statement expression archive case) 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 9a06cd980..131f8e57e 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 @@ -45,10 +45,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) (template: (!unary function) 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 cbb7c557d..d06f428a6 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 @@ -47,7 +47,7 @@ Phase! (case synthesis ... TODO: Get rid of this ASAP - {#synthesis.Extension "lux syntax char case!" parameters} + {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] (in (:as (Statement Any) body))) @@ -67,8 +67,8 @@ (^template [<tag>] [(^ {<tag> value}) (/////\each _.return (expression archive synthesis))]) - ([#synthesis.Reference] - [#synthesis.Extension]) + ([synthesis.#Reference] + [synthesis.#Extension]) (^ (synthesis.branch/case case)) (//case.case! false statement expression archive case) @@ -92,10 +92,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<synthesis>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) ... TODO: Get rid of this ASAP @@ -128,7 +128,7 @@ ... .let [dependencies (//case.dependencies (list\mix (function (_ right left) ... (synthesis.path/seq left right)) ... (synthesis.path/then input) - ... {#.Item (synthesis.path/then else) + ... {.#Item (synthesis.path/then else) ... (list\each (|>> product.right ... synthesis.path/then) ... conditionals)})) @@ -141,7 +141,7 @@ ... else! ... conditionals!)))] ... _ (generation.execute! closure) - ... _ (generation.save! (product.right artifact_id) #.None closure) + ... _ (generation.save! (product.right artifact_id) {.#None} closure) ] ... (in (_.apply/* @closure dependencies)) (in (<| (:as (Expression Any)) 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 2e533b5bd..1db4fb268 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 @@ -45,10 +45,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) ... (template: (!unary function) 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 6b6538363..f057e6e10 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 @@ -48,17 +48,17 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) (def: .public (statement expression archive synthesis) Phase! (case synthesis ... TODO: Get rid of this ASAP - {#synthesis.Extension "lux syntax char case!" parameters} + {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] (in (:as Statement @@ -79,8 +79,8 @@ (^template [<tag>] [(^ {<tag> value}) (/////\each _.return (expression archive synthesis))]) - ([#synthesis.Reference] - [#synthesis.Extension]) + ([synthesis.#Reference] + [synthesis.#Extension]) (^ (synthesis.branch/case case)) (//case.case! false statement expression archive case) @@ -123,7 +123,7 @@ _.nil)) branch!]))) conditionals)) - ... .let [closure (_.lambda #.None (list @input) + ... .let [closure (_.lambda {.#None} (list @input) ... (list\mix (function (_ [test then] else) ... (_.if test (_.return then) else)) ... (_.return else!) 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 7161326e1..e786087d1 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 @@ -45,10 +45,10 @@ Handler)) (function (_ extension_name phase archive input) (case (<s>.result parser input) - {#try.Success input'} + {try.#Success input'} (handler extension_name phase archive input') - {#try.Failure error} + {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) (template: (!unary function) 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 26a967a45..dca5d6673 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 @@ -34,7 +34,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) (^template [<tag> <generator>] @@ -52,6 +52,6 @@ [////synthesis.loop/recur /loop.recur] [////synthesis.function/abstraction /function.function]) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive generate extension) )) 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 5442b7268..ed9bd19a0 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 @@ -68,8 +68,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueG pathP)))) @@ -117,10 +117,10 @@ (_.go @fail) (..push! @temp))) (.case next! - {#.Some next!} + {.#Some next!} (list next!) - #.None + {.#None} (list))))))] [left_choice _.nil (<|)] @@ -147,20 +147,20 @@ (_.go @done)))) (expression archive bodyS)) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.setq (..register register) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur [$output @done @fail thenP]) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur [$output @done @fail elseP]) - #.None + {.#None} (in (_.go @fail)))] (in (.if when (_.if ..peek @@ -179,23 +179,23 @@ (in [(<=> [(|> match <format>) ..peek]) then!]))) - {#.Item item})] + {.#Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) (_.go @fail) clauses)))]) - ([#/////synthesis.I64_Fork //primitive.i64 _.=/2] - [#/////synthesis.F64_Fork //primitive.f64 _.=/2] - [#/////synthesis.Text_Fork //primitive.text _.string=/2]) + ([/////synthesis.#I64_Fork //primitive.i64 _.=/2] + [/////synthesis.#F64_Fork //primitive.f64 _.=/2] + [/////synthesis.#Text_Fork //primitive.text _.string=/2]) (^template [<complex> <simple> <choice>] [(^ (<complex> idx)) - (///////phase\in (<choice> @fail false idx #.None)) + (///////phase\in (<choice> @fail false idx {.#None})) (^ (<simple> idx nextP)) (|> nextP [$output @done @fail] recur - (\ ///////phase.monad each (|>> {#.Some} (<choice> @fail true idx))))]) + (\ ///////phase.monad each (|>> {.#Some} (<choice> @fail true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) @@ -248,7 +248,7 @@ pattern_matching! (pattern_matching $output expression archive pathP) .let [storage (|> pathP ////synthesis/case.storage - (value@ #////synthesis/case.bindings) + (value@ ////synthesis/case.#bindings) set.list (list\each (function (_ register) [(..register register) 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 5f38c7bad..3130f0121 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 @@ -43,7 +43,7 @@ (def: (with_closure inits function_definition) (-> (List (Expression Any)) (Expression Any) (Operation (Expression Any))) (case inits - #.End + {.#End} (\ ///////phase.monad in function_definition) _ 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 bae37c835..18bbc788e 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 @@ -36,7 +36,7 @@ (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop 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 1c7fd4877..2cee2de25 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 @@ -109,7 +109,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (let [g!name (code.local_identifier name) code_nameC (code.local_identifier (format "@" name))] (in (list (` (def: .public (~ g!name) @@ -120,7 +120,7 @@ (_.Expression Any) (_.defparameter (~ runtime_name) (~ code))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (let [g!name (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) 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 2a5fa7c1c..22ed7a7c6 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 @@ -17,10 +17,10 @@ (def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (expression archive singletonS) _ 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 65b06ce16..24db5395a 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 @@ -49,7 +49,7 @@ (^ (synthesis.tuple members)) (/structure.tuple expression archive members) - {#synthesis.Reference value} + {synthesis.#Reference value} (//reference.reference /reference.system archive value) (^ (synthesis.branch/case case)) @@ -76,7 +76,7 @@ (^ (synthesis.function/apply application)) (/function.apply expression archive application) - {#synthesis.Extension extension} + {synthesis.#Extension extension} (///extension.apply archive expression extension))) (def: .public generate 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 8f98d44ab..246bcb54d 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 @@ -82,8 +82,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.i32 (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueO (list.reversed pathP))))) @@ -166,12 +166,12 @@ [(^ (<simple> idx nextP)) (|> nextP recur - (\ ///////phase.monad each (|>> (_.then (<choice> true idx)) #.Some)))]) + (\ ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))]) ([/////synthesis.simple_left_side ..left_choice] [/////synthesis.simple_right_side ..right_choice]) (^ (/////synthesis.member/left 0)) - (///////phase\in {#.Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))}) + (///////phase\in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))}) ... Extra optimization (^ (/////synthesis.path/seq @@ -179,7 +179,7 @@ (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (recur thenP)] - (in {#.Some ($_ _.then + (in {.#Some ($_ _.then (_.define (..register register) (_.at (_.i32 +0) ..peek_cursor)) then!)})) @@ -190,7 +190,7 @@ (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (recur thenP)] - (in {#.Some ($_ _.then + (in {.#Some ($_ _.then (_.define (..register register) (<getter> (_.i32 (.int lefts)) ..peek_cursor)) then!)}))]) ([/////synthesis.member/left //runtime.tuple//left] @@ -199,7 +199,7 @@ (^ (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (recur thenP)] - (in {#.Some ($_ _.then + (in {.#Some ($_ _.then (_.define (..register register) ..peek_and_pop_cursor) then!)})) @@ -207,12 +207,12 @@ (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (recur nextP')] - (in {#.Some ($_ _.then + (in {.#Some ($_ _.then (multi_pop_cursor! (n.+ 2 extra_pops)) next!)}))) _ - (///////phase\in #.None))) + (///////phase\in {.#None}))) (def: (pattern_matching' statement expression archive) (-> Phase! Phase Archive @@ -221,28 +221,28 @@ (do ///////phase.monad [outcome (optimized_pattern_matching recur pathP)] (.case outcome - {#.Some outcome} + {.#Some outcome} (in outcome) - #.None + {.#None} (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (statement expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in pop_cursor!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.define (..register register) ..peek_cursor)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail_pm!))] (in (.if when (_.if ..peek_cursor @@ -252,7 +252,7 @@ else! then!)))) - {#/////synthesis.I64_Fork item} + {/////synthesis.#I64_Fork item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -260,20 +260,20 @@ (in [(//runtime.i64//= (//primitive.i64 (.int match)) ..peek_cursor) then!]))) - {#.Item item})] + {.#Item item})] (in (_.cond clauses ..fail_pm!))) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [cases (monad.each ! (function (_ [match then]) (\ ! each (|>> [(list (<format> match))]) (recur then))) - {#.Item item})] + {.#Item item})] (in (_.switch ..peek_cursor cases - {#.Some ..fail_pm!})))]) - ([#/////synthesis.F64_Fork //primitive.f64] - [#/////synthesis.Text_Fork //primitive.text]) + {.#Some ..fail_pm!})))]) + ([/////synthesis.#F64_Fork //primitive.f64] + [/////synthesis.#Text_Fork //primitive.text]) (^template [<complex> <choice>] [(^ (<complex> idx)) 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 f9e8d9c10..57083f023 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 @@ -41,7 +41,7 @@ (def: (with_closure @self inits body!) (-> Var (List Expression) Statement [Statement Expression]) (case inits - #.End + {.#End} [(_.function! @self (list) body!) @self] @@ -119,5 +119,5 @@ @self)))))))) ))] _ (/////generation.execute! definition) - _ (/////generation.save! (product.right function_name) #.None definition)] + _ (/////generation.save! (product.right function_name) {.#None} definition)] (in instantiation))) 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 52600eaeb..cde2c64a7 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 @@ -45,7 +45,7 @@ (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (statement expression archive bodyS) ... true loop @@ -64,7 +64,7 @@ (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop 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 f2be9fda5..b83068e2b 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 @@ -104,7 +104,7 @@ (macro.with_identifiers [g!_ runtime] (let [runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) Var @@ -116,7 +116,7 @@ (function ((~ g!_) (~ g!name)) (~ code)))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) inputs_typesC (list\each (function.constant (` _.Expression)) inputs)] @@ -775,12 +775,12 @@ (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) - _ (/////generation.save! ..module_id #.None ..runtime)] + _ (/////generation.save! ..module_id {.#None} ..runtime)] (in [(|> artifact.empty artifact.resource product.right) (row.row [..module_id - #.None + {.#None} (|> ..runtime _.code (\ utf8.codec encoded))])]))) 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 88072200f..d5838b04b 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 @@ -17,10 +17,10 @@ (def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in //runtime.unit) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (generate archive singletonS) _ 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 6a1a607cb..738700655 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 @@ -36,12 +36,12 @@ (^ (synthesis.tuple members)) (/structure.tuple generate archive members) - {#synthesis.Reference reference} + {synthesis.#Reference reference} (case reference - {#reference.Variable variable} + {reference.#Variable variable} (/reference.variable archive variable) - {#reference.Constant constant} + {reference.#Constant constant} (/reference.constant archive constant)) (^ (synthesis.branch/case [valueS pathS])) @@ -68,6 +68,6 @@ (^ (synthesis.function/apply application)) (/function.apply generate archive application) - {#synthesis.Extension extension} + {synthesis.#Extension extension} (///extension.apply archive generate extension) )) 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 2da725141..3493c8140 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 @@ -92,15 +92,15 @@ (def: (path' stack_depth @else @end phase archive path) (-> Nat Label Label (Generator Path)) (.case path - #synthesis.Pop + {synthesis.#Pop} (operation\in ..pop) - {#synthesis.Bind register} + {synthesis.#Bind register} (operation\in ($_ _.composite ..peek (_.astore register))) - {#synthesis.Then bodyS} + {synthesis.#Then bodyS} (do phase.monad [bodyG (phase archive bodyS)] (in ($_ _.composite @@ -171,7 +171,7 @@ ([synthesis.member/left //runtime.left_projection] [synthesis.member/right //runtime.right_projection]) - {#synthesis.Alt leftP rightP} + {synthesis.#Alt leftP rightP} (do phase.monad [@alt_else //runtime.forge_label left! (path' (++ stack_depth) @alt_else @end phase archive leftP) @@ -183,7 +183,7 @@ _.pop right!))) - {#synthesis.Seq leftP rightP} + {synthesis.#Seq leftP rightP} (do phase.monad [left! (path' stack_depth @else @end phase archive leftP) right! (path' stack_depth @else @end phase archive rightP)] @@ -243,10 +243,10 @@ [recordG (phase archive recordS)] (in (list\mix (function (_ step so_far) (.let [next (.case step - {#.Left lefts} + {.#Left lefts} (..left_projection lefts) - {#.Right lefts} + {.#Right lefts} (..right_projection lefts))] (_.composite so_far next))) recordG 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 b0833504c..c0ab7b58d 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 @@ -24,8 +24,8 @@ (file.get_file io.monad file.default file_path))] (\ file over_write bytecode))] (in (case outcome - {#try.Success definition} + {try.#Success definition} file_path - {#try.Failure error} + {try.#Failure error} error))))) 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 0aa307c72..b046e78b8 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 @@ -113,7 +113,7 @@ (row.row))) .let [bytecode (format.result class.writer class)] _ (generation.execute! [function_class bytecode]) - _ (generation.save! function_class #.None [function_class bytecode])] + _ (generation.save! function_class {.#None} [function_class bytecode])] (in instance))) (def: .public (apply generate archive [abstractionS inputsS]) 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 15a73026e..d9f9427a2 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 @@ -85,7 +85,7 @@ (method.method //.modifier ////runtime.apply::name (////runtime.apply::type apply_arity) (list) - {#.Some (case num_partials + {.#Some (case num_partials 0 ($_ _.composite ////reference.this (..inputs ..this_offset apply_arity) @@ -97,7 +97,7 @@ @labelsT (|> _.new_label (list.repeated (-- num_partials)) (monad.all _.monad)) - .let [cases (|> (list\composite {#.Item [@labelsH @labelsT]} + .let [cases (|> (list\composite {.#Item [@labelsH @labelsT]} (list @default)) list.enumeration (list\each (function (_ [stage @case]) 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 723ff6ce5..9a77e6a62 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 @@ -31,7 +31,7 @@ (method.method //.modifier name (..type arity) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite (_.set_label @begin) body _.areturn 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 91df54eca..ecddbaf46 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 @@ -94,7 +94,7 @@ (method.method //.modifier ..name (..type environment arity) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite ////reference.this (..super environment_size arity) (store_all environment_size (///foreign.put class) offset_foreign) 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 79926e5b8..105718c78 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 @@ -69,7 +69,7 @@ (method.method //.modifier //init.name (//init.type environment arity) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite ////reference.this (//init.super environment_size arity) (monad.each _.monad (function (_ register) 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 b5bdb1e1d..791bca2f5 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 @@ -43,7 +43,7 @@ (method.method //.modifier ..name (..type class) (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite (if (arity.multiary? arity) (//new.instance' (..current_environment class environment) class environment arity) ////reference.this) 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 0ffbbceb3..e6db5b72c 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 @@ -81,20 +81,20 @@ (def: (class_value class_name class) (-> Text (java/lang/Class java/lang/Object) (Try Any)) (case (java/lang/Class::getField ..value::field class) - {#try.Success field} - (case (java/lang/reflect/Field::get #.None field) - {#try.Success ?value} + {try.#Success field} + (case (java/lang/reflect/Field::get {.#None} field) + {try.#Success ?value} (case ?value - {#.Some value} - {#try.Success value} + {.#Some value} + {try.#Success value} - #.None + {.#None} (exception.except ..invalid_value [class_name])) - {#try.Failure error} + {try.#Failure error} (exception.except ..cannot_load [class_name error])) - {#try.Failure error} + {try.#Failure error} (exception.except ..invalid_field [class_name ..value::field error]))) (def: class_path_separator @@ -110,7 +110,7 @@ (list (field.field ..value::modifier ..value::field ..value::type (row.row))) (list (method.method ..init::modifier "<clinit>" ..init::type (list) - {#.Some + {.#Some ($_ _.composite valueG (_.putstatic (type.class bytecode_name (list)) ..value::field ..value::type) 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 9ed5eb48e..daf8fa2fc 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 @@ -51,21 +51,21 @@ value (case (signed.s1 value) - {#try.Success value} + {try.#Success value} (do _.monad [_ (_.bipush value) _ _.i2l] ..wrap_i64) - {#try.Failure _} + {try.#Failure _} (case (signed.s2 value) - {#try.Success value} + {try.#Success value} (do _.monad [_ (_.sipush value) _ _.i2l] ..wrap_i64) - {#try.Failure _} + {try.#Failure _} (do _.monad [_ (_.long value)] ..wrap_i64))))) 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 4074cf6cc..cb5f99c33 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 @@ -132,7 +132,7 @@ (let [super_class (|> ..^Object type.reflection reflection.reflection name.internal) main (method.method ..main::modifier "main" ..main::type (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite program ..input_list ..feed_inputs 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 778b23005..c61f58336 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 @@ -53,10 +53,10 @@ (def: .public (variable archive variable) (-> Archive Variable (Operation (Bytecode Any))) (case variable - {#variable.Local variable} + {variable.#Local variable} (operation\in (_.aload variable)) - {#variable.Foreign variable} + {variable.#Foreign variable} (..foreign archive variable))) (def: .public (constant archive name) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index c3c8f518c..eba8c2f00 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 @@ -151,7 +151,7 @@ (method.method ..modifier ..variant::name ..variant::type (list) - {#.Some ($_ _.composite + {.#Some ($_ _.composite new_variant ... A[3] (..set! ..variant_tag $tag) ... A[3] (..set! ..variant_last? $last?) ... A[3] @@ -213,7 +213,7 @@ (method.method ..modifier ..decode_frac::name ..decode_frac::type (list) - {#.Some + {.#Some (..risky ($_ _.composite _.aload_0 @@ -250,7 +250,7 @@ (method.method ..modifier name ..failure::type (list) - {#.Some + {.#Some ($_ _.composite (..illegal_state_exception message) _.athrow)})) @@ -272,7 +272,7 @@ (method.method ..modifier ..push::name ..push::type (list) - {#.Some + {.#Some (let [new_stack_frame! ($_ _.composite _.iconst_2 (_.anewarray //type.value)) @@ -291,7 +291,7 @@ (def: case::method (method.method ..modifier ..case::name ..case::type (list) - {#.Some + {.#Some (do _.monad [@loop _.new_label @perfect_match! _.new_label @@ -395,7 +395,7 @@ left_projection::method (method.method ..modifier ..left_projection::name ..projection_type (list) - {#.Some + {.#Some (do _.monad [@loop _.new_label @recursive _.new_label @@ -413,7 +413,7 @@ right_projection::method (method.method ..modifier ..right_projection::name ..projection_type (list) - {#.Some + {.#Some (do _.monad [@loop _.new_label @not_tail _.new_label @@ -466,7 +466,7 @@ (def: try::method (method.method ..modifier ..try::name ..try::type (list) - {#.Some + {.#Some (do _.monad [@try _.new_label @handler _.new_label @@ -539,7 +539,7 @@ (row.row)))] (do ////.monad [_ (generation.execute! [class bytecode])] - (generation.save! ..artifact_id #.None [class bytecode])))) + (generation.save! ..artifact_id {.#None} [class bytecode])))) (def: generate_function (Operation Any) @@ -549,7 +549,7 @@ (list\each (function (_ arity) (method.method method.public ..apply::name (..apply::type arity) (list) - {#.Some + {.#Some (let [previous_inputs (|> arity list.indices (monad.each _.monad _.aload))] @@ -563,10 +563,10 @@ (list& (method.method (modifier\composite method.public method.abstract) ..apply::name (..apply::type //function/arity.minimum) (list) - #.None))) + {.#None}))) <init>::method (method.method method.public "<init>" //function.init (list) - {#.Some + {.#Some (let [$partials _.iload_1] ($_ _.composite ..this @@ -596,7 +596,7 @@ (row.row)))] (do ////.monad [_ (generation.execute! [class bytecode])] - (generation.save! //function.artifact_id #.None [class bytecode])))) + (generation.save! //function.artifact_id {.#None} [class bytecode])))) (def: .public generate (Operation Any) 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 6b1a09aea..7455a3d3b 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 @@ -29,10 +29,10 @@ (def: .public (tuple generate archive membersS) (Generator (Tuple Synthesis)) (case membersS - #.End + {.#End} (\ phase.monad in //runtime.unit) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (generate archive singletonS) _ @@ -64,15 +64,15 @@ 4 _.iconst_4 5 _.iconst_5 tag (case (signed.s1 (.int tag)) - {#try.Success value} + {try.#Success value} (_.bipush value) - {#try.Failure _} + {try.#Failure _} (case (signed.s2 (.int tag)) - {#try.Success value} + {try.#Success value} (_.sipush value) - {#try.Failure _} + {try.#Failure _} (_.int (.i64 tag)))))) (def: .public (flag right?) 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 66472f114..44b40b6e9 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 @@ -49,7 +49,7 @@ (^ (synthesis.tuple members)) (/structure.tuple expression archive members) - {#synthesis.Reference value} + {synthesis.#Reference value} (//reference.reference /reference.system archive value) (^ (synthesis.branch/case case)) @@ -76,7 +76,7 @@ (^ (synthesis.function/apply application)) (/function.apply expression archive application) - {#synthesis.Extension extension} + {synthesis.#Extension extension} (///extension.apply archive expression extension))) (def: .public generate 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 7188a282c..90f2f3f3a 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 @@ -67,8 +67,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueO (list.reversed pathP))))) @@ -163,23 +163,23 @@ (-> Phase! Phase Archive Path (Operation Statement)) (function (recur pathP) (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (statement expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.local/1 (..register register) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] (in (.if when (_.if ..peek @@ -198,11 +198,11 @@ (in [(_.= (|> match <format>) ..peek) then!]))) - {#.Item item})] + {.#Item item})] (in (_.cond clauses ..fail!)))]) - ([#/////synthesis.I64_Fork (<| _.int .int)] - [#/////synthesis.F64_Fork _.float] - [#/////synthesis.Text_Fork _.string]) + ([/////synthesis.#I64_Fork (<| _.int .int)] + [/////synthesis.#F64_Fork _.float] + [/////synthesis.#Text_Fork _.string]) (^template [<complex> <simple> <choice>] [(^ (<complex> idx)) @@ -250,14 +250,14 @@ (def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage - (value@ #////synthesis/case.dependencies) + (value@ ////synthesis/case.#dependencies) set.list (list\each (function (_ variable) (.case variable - {#///////variable.Local register} + {///////variable.#Local register} (..register register) - {#///////variable.Foreign register} + {///////variable.#Foreign register} (..capture register)))))) (def: .public (case! statement expression archive [valueS pathP]) 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 dbae0c91b..e395e1b19 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 @@ -43,7 +43,7 @@ (def: (with_closure inits @self @args body!) (-> (List Expression) Var (List Var) Statement [Statement Expression]) (case inits - #.End + {.#End} [(_.function @self @args body!) @self] @@ -133,5 +133,5 @@ (_.apply/1 @self)))))))) ))] _ (/////generation.execute! definition) - _ (/////generation.save! (product.right function_name) #.None definition)] + _ (/////generation.save! (product.right function_name) {.#None} definition)] (in instantiation))) 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 57b7261ff..bee7ac538 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 @@ -53,7 +53,7 @@ (Operation [(List Expression) Statement])) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (|> bodyS (statement expression archive) (\ ///////phase.monad each (|>> [(list)]))) @@ -75,7 +75,7 @@ (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop @@ -93,7 +93,7 @@ (set.of_list _.hash) (set.difference (set.of_list _.hash locals)) set.list) - #.End + {.#End} [(_.function @loop locals scope!) @loop] @@ -108,7 +108,7 @@ )) (|> @context (_.apply/* foreigns))])))] _ (/////generation.execute! directive) - _ (/////generation.save! artifact_id #.None directive)] + _ (/////generation.save! artifact_id {.#None} directive)] (in (|> instantiation (_.apply/* initsO+)))))) (def: .public (recur! statement expression archive argsS+) 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 a6e448433..fa0a01ef7 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 @@ -127,7 +127,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) @@ -140,7 +140,7 @@ (function ((~ g!_) (~ g!name)) (_.set (~ g!name) (~ code)))))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) @@ -422,12 +422,12 @@ (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) - _ (/////generation.save! ..module_id #.None ..runtime)] + _ (/////generation.save! ..module_id {.#None} ..runtime)] (in [(|> artifact.empty artifact.resource product.right) (row.row [..module_id - #.None + {.#None} (|> ..runtime _.code (\ utf8.codec encoded))])]))) 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 29a909d0e..c2bd264e0 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 @@ -17,10 +17,10 @@ (def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (generate archive singletonS) _ 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 9c16f64cb..e2fc2ba88 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 @@ -39,10 +39,14 @@ [////synthesis.text] [////synthesis.variant] [////synthesis.tuple] - [#////synthesis.Reference] [////synthesis.branch/get] - [////synthesis.function/apply] - [#////synthesis.Extension]) + [////synthesis.function/apply]) + + (^template [<tag>] + [(^ {<tag> value}) + (//////phase\each _.return (expression archive synthesis))]) + ([////synthesis.#Reference] + [////synthesis.#Extension]) (^ (////synthesis.branch/case case)) (/case.case! statement expression archive case) @@ -72,7 +76,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) (^template [<tag> <generator>] @@ -95,7 +99,7 @@ (^ (////synthesis.loop/recur _)) (//////phase.except ..cannot_recur_as_an_expression []) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive expression extension))) (def: .public generate 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 a5532afc3..d6e4ccb15 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 @@ -88,8 +88,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueG (list.reversed pathP))))) @@ -163,23 +163,23 @@ (Generator! Path) (function (recur pathP) (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (statement expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.set! (..register register) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] (in (.if when (_.if ..peek @@ -198,11 +198,11 @@ (in [(_.=== (|> match <format>) ..peek) then!]))) - {#.Item item})] + {.#Item item})] (in (_.cond clauses ..fail!)))]) - ([#/////synthesis.I64_Fork //primitive.i64] - [#/////synthesis.F64_Fork //primitive.f64] - [#/////synthesis.Text_Fork //primitive.text]) + ([/////synthesis.#I64_Fork //primitive.i64] + [/////synthesis.#F64_Fork //primitive.f64] + [/////synthesis.#Text_Fork //primitive.text]) (^template [<complex> <simple> <choice>] [(^ (<complex> idx)) @@ -260,14 +260,14 @@ (def: .public dependencies (-> Path (List Var)) (|>> ////synthesis/case.storage - (value@ #////synthesis/case.dependencies) + (value@ ////synthesis/case.#dependencies) set.list (list\each (function (_ variable) (.case variable - {#///////variable.Local register} + {///////variable.#Local register} (..register register) - {#///////variable.Foreign register} + {///////variable.#Foreign register} (..capture register)))))) (def: .public (case! statement expression archive [valueS pathP]) 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 f630ec274..83e16e834 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 @@ -50,7 +50,7 @@ (def: (with_closure inits @selfG @selfL body!) (-> (List Expression) Global Var Statement [Statement Expression]) (case inits - #.End + {.#End} [($_ _.then (_.set! @selfL (_.closure (list (_.reference @selfL)) (list) body!)) (_.set! @selfG @selfL)) 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 055e107e0..7ce83fe85 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 @@ -51,7 +51,7 @@ (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (statement expression archive bodyS) ... true loop @@ -70,7 +70,7 @@ (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop @@ -92,7 +92,7 @@ (list\mix set.union (referenced_variables bodyS)) (set.difference loop_variables) set.list) - #.End + {.#End} [(_.define_function @loop (list) scope!) @loop] 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 d8a418657..81f608c20 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 @@ -95,7 +95,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.constant (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) @@ -108,7 +108,7 @@ (function ((~ g!_) (~ g!name)) (_.define (~ g!name) (~ code)))))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) @@ -317,9 +317,9 @@ (_.set! value (_.apply/1 op [..unit])) (_.return (..right value))) (list (with_vars [error] - [#_.class (_.constant "Exception") - #_.exception error - #_.handler (_.return (..left (_.do "getMessage" (list) error)))]))))) + [_.#class (_.constant "Exception") + _.#exception error + _.#handler (_.return (..left (_.do "getMessage" (list) error)))]))))) (runtime: (lux//program_args inputs) (with_vars [head tail] 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 cb499a364..8e1a366a8 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 @@ -20,10 +20,10 @@ (def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (expression archive singletonS) _ 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 b691c09d6..deca2222f 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 @@ -49,7 +49,7 @@ (^ (////synthesis.tuple members)) (/structure.tuple expression archive members) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) (^ (////synthesis.branch/case case)) @@ -76,7 +76,7 @@ (^ (////synthesis.function/apply application)) (/function.apply expression archive application) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive expression extension))) (def: .public generate 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 6cdabddd0..6b6e2ff74 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 @@ -93,8 +93,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple::left] - [#.Right //runtime.tuple::right]))] + ([.#Left //runtime.tuple::left] + [.#Right //runtime.tuple::right]))] (method source))) valueO (list.reversed pathP))))) @@ -156,14 +156,14 @@ (.if in_closure? (_.while (_.bool true) body! - #.None) + {.#None}) ($_ _.then (_.set (list g!once) (_.bool true)) (_.while g!once ($_ _.then (_.set (list g!once) (_.bool false)) body!) - {#.Some _.continue})))) + {.#Some _.continue})))) (def: (alternation in_closure? g!once pre! post!) (-> Bit SVar (Statement Any) (Statement Any) (Statement Any)) @@ -179,16 +179,16 @@ (-> (-> Path (Operation (Statement Any))) (-> Path (Operation (Maybe (Statement Any))))) (.case pathP - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail_pm!))] - (in {#.Some (.if when + (in {.#Some (.if when (_.if ..peek then! else!) @@ -204,15 +204,15 @@ (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - {#.Item item})] - (in {#.Some (_.cond clauses + {.#Item item})] + (in {.#Some (_.cond clauses ..fail_pm!)}))]) - ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] - [#/////synthesis.F64_Fork (<| //primitive.f64)] - [#/////synthesis.Text_Fork (<| //primitive.text)]) + ([/////synthesis.#I64_Fork (<| //primitive.i64 .int)] + [/////synthesis.#F64_Fork (<| //primitive.f64)] + [/////synthesis.#Text_Fork (<| //primitive.text)]) _ - (\ ///////phase.monad in #.None))) + (\ ///////phase.monad in {.#None}))) (def: (pattern_matching' in_closure? statement expression archive) (-> Bit Phase! Phase Archive Path (Operation (Statement Any))) @@ -220,18 +220,18 @@ (do [! ///////phase.monad] [?output (primitive_pattern_matching recur pathP)] (.case ?output - {#.Some output} + {.#Some output} (in output) - #.None + {.#None} (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (statement expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.set (list (..register register)) ..peek)) (^template [<complex> <simple> <choice>] @@ -298,14 +298,14 @@ (def: .public dependencies (-> Path (List SVar)) (|>> case.storage - (value@ #case.dependencies) + (value@ case.#dependencies) set.list (list\each (function (_ variable) (.case variable - {#///////variable.Local register} + {///////variable.#Local register} (..register register) - {#///////variable.Foreign register} + {///////variable.#Foreign register} (..capture register)))))) (def: .public (case! in_closure? statement expression archive [valueS pathP]) @@ -330,5 +330,5 @@ directive (_.def @case @dependencies+ pattern_matching!)] _ (/////generation.execute! directive) - _ (/////generation.save! case_artifact #.None directive)] + _ (/////generation.save! case_artifact {.#None} directive)] (in (_.apply/* @case @dependencies+)))) 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 fa9fc1656..bbb9fbd00 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 @@ -45,10 +45,10 @@ (def: (with_closure function_id @function inits function_definition) (-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any))) (case inits - #.End + {.#End} (do ///////phase.monad [_ (/////generation.execute! function_definition) - _ (/////generation.save! function_id #.None function_definition)] + _ (/////generation.save! function_id {.#None} function_definition)] (in @function)) _ @@ -60,7 +60,7 @@ function_definition (_.return @function)))] _ (/////generation.execute! directive) - _ (/////generation.save! function_id #.None directive)] + _ (/////generation.save! function_id {.#None} directive)] (in (_.apply/* @function inits))))) (def: input 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 b84826a26..066149a79 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 @@ -45,13 +45,13 @@ (-> (Statement Any) (Statement Any)) (_.while (_.bool true) body! - #.None)) + {.#None})) (def: .public (scope! statement expression archive [start initsS+ bodyS]) (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (statement expression archive bodyS) ... true loop @@ -68,7 +68,7 @@ (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop @@ -91,7 +91,7 @@ (set.of_list _.hash) (set.difference (set.of_list _.hash locals)) set.list) - #.End + {.#End} [actual_loop @loop] @@ -103,7 +103,7 @@ )) (_.apply/* @loop foreigns)]))] _ (/////generation.execute! directive) - _ (/////generation.save! loop_artifact #.None directive)] + _ (/////generation.save! loop_artifact {.#None} directive)] (in (_.apply/* instantiation initsO+))))) (def: .public (recur! statement expression archive argsS+) 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 c2055e2cc..e72faad54 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 @@ -126,7 +126,7 @@ (<>.some <code>.local_identifier)))) code <code>.any]) (case declaration - {#.Left name} + {.#Left name} (macro.with_identifiers [g!_] (let [nameC (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) @@ -138,7 +138,7 @@ (function ((~ g!_) (~ g!_)) (_.set (list (~ g!_)) (~ code)))))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (macro.with_identifiers [g!_] (let [nameC (code.local_identifier name) code_nameC (code.local_identifier (format "@" name)) @@ -174,7 +174,7 @@ (runtime: (lux::exec code globals) ($_ _.then - (_.exec code {#.Some globals}) + (_.exec code {.#Some globals}) (_.return ..unit))) (def: runtime::lux @@ -220,7 +220,7 @@ (_.return (_.item lefts tuple)) ... Needs recursion <recur>)) - #.None))) + {.#None}))) (runtime: (tuple::right lefts tuple) (with_vars [last_index_right right_index] @@ -234,7 +234,7 @@ ... Needs recursion. <recur>]) (_.return (_.slice_from right_index tuple)))) - #.None)))) + {.#None})))) (runtime: (sum::get sum wantsLast wantedTag) (let [no_match! (_.return _.none) @@ -261,7 +261,7 @@ (_.return (variant' (_.- wantedTag sum_tag) sum_flag sum_value))]) no_match!) - #.None))) + {.#None}))) (def: runtime::adt (Statement Any) @@ -449,12 +449,12 @@ (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) - _ (/////generation.save! ..module_id #.None ..runtime)] + _ (/////generation.save! ..module_id {.#None} ..runtime)] (in [(|> artifact.empty artifact.resource product.right) (row.row [..module_id - #.None + {.#None} (|> ..runtime _.code (\ utf8.codec encoded))])]))) 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 5950a81ff..86c429347 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 @@ -17,10 +17,10 @@ (def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (generate archive singletonS) _ 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 4e3e67097..5438a0266 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 @@ -36,7 +36,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) (^template [<tag> <generator>] @@ -54,6 +54,6 @@ [////synthesis.loop/recur /loop.recur] [////synthesis.function/abstraction /function.function]) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive generate extension) )) 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 15e9c75e5..e99973e60 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 @@ -71,8 +71,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple::left] - [#.Right //runtime.tuple::right]))] + ([.#Left //runtime.tuple::left] + [.#Right //runtime.tuple::right]))] (method source))) valueO (list.reversed pathP))))) @@ -135,23 +135,23 @@ (Generator Path) (function (recur pathP) (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop_cursor!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.set! (..register register) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] (in (.if when (_.if ..peek @@ -170,14 +170,14 @@ (in [(<=> (|> match <format>) ..peek) then!]))) - {#.Item item})] + {.#Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) ..fail! clauses)))]) - ([#/////synthesis.I64_Fork //primitive.i64 //runtime.i64::=] - [#/////synthesis.F64_Fork //primitive.f64 _.=] - [#/////synthesis.Text_Fork //primitive.text _.=]) + ([/////synthesis.#I64_Fork //primitive.i64 //runtime.i64::=] + [/////synthesis.#F64_Fork //primitive.f64 _.=] + [/////synthesis.#Text_Fork //primitive.text _.=]) (^template [<pm> <flag> <prep>] [(^ (<pm> idx)) @@ -213,11 +213,11 @@ (in (_.try ($_ _.then ..save_cursor! leftO) - #.None - {#.Some (..catch ($_ _.then + {.#None} + {.#Some (..catch ($_ _.then ..restore_cursor! rightO))} - #.None))) + {.#None}))) ))) (def: (pattern_matching expression archive pathP) @@ -225,9 +225,9 @@ (do ///////phase.monad [pattern_matching! (pattern_matching' expression archive pathP)] (in (_.try pattern_matching! - #.None - {#.Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))} - #.None)))) + {.#None} + {.#Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))} + {.#None})))) (def: .public (case expression archive [valueS pathP]) (Generator [Synthesis Path]) 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 87487db01..8d049ba86 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 @@ -42,7 +42,7 @@ (def: (with_closure function_id $function inits function_definition) (-> artifact.ID SVar (List Expression) Expression (Operation Expression)) (case inits - #.End + {.#End} (do ///////phase.monad [_ (/////generation.execute! function_definition) _ (/////generation.save! (%.nat function_id) 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 02d6712ec..d0cb917a6 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 @@ -37,7 +37,7 @@ (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop 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 9d2c878cf..2c61e52f2 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 @@ -126,10 +126,10 @@ (function (_ proc_name) (function (_ translate inputsS) (case (s.result inputsS ($_ p.and s.nat (s.tuple (p.many s.any)) s.any)) - {#e.Success [offset initsS+ bodyS]} + {e.#Success [offset initsS+ bodyS]} (loopT.translate_loop translate offset initsS+ bodyS) - {#e.Error error} + {e.#Error error} (&.throw Wrong_Syntax (wrong_syntax proc_name inputsS))) ))) 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 4975c0aec..54a0c637b 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 @@ -25,7 +25,7 @@ ... (def: (lua//global proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list [_ {#.Text name}])) +... (^ (list [_ {.#Text name}])) ... (do macro.Monad<Meta> ... [] ... (in name)) @@ -56,7 +56,7 @@ ... (def: (table//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list& tableS [_ {#.Text field}] argsS+)) +... (^ (list& tableS [_ {.#Text field}] argsS+)) ... (do [@ macro.Monad<Meta>] ... [tableO (translate tableS) ... argsO+ (monad.each @ translate argsS+)] 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 246a010c9..01d69d81b 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 @@ -98,7 +98,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) _.SVar @@ -108,7 +108,7 @@ _.Expression (_.set! (~ runtime_name) (~ code))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) inputs_typesC (list\each (function.constant (` _.Expression)) @@ -523,11 +523,11 @@ (_.try ($_ _.then (_.set! value (_.apply (list ..unit) op)) (..right value)) - #.None - {#.Some (_.function (list error) + {.#None} + {.#Some (_.function (list error) (..left (_.item (_.string "message") error)))} - #.None))) + {.#None}))) (runtime: (lux::program_args program_args) (with_vars [inputs value] 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 711366595..bafd70383 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 @@ -20,10 +20,10 @@ (def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (expression archive singletonS) _ 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 49389b109..2a456eba4 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 @@ -73,18 +73,18 @@ (All (_ expression) (-> (System expression) Variable expression)) (case variable - {#variable.Local register} + {variable.#Local register} (..local system register) - {#variable.Foreign register} + {variable.#Foreign register} (..foreign system register))) (def: .public (reference system archive reference) (All (_ anchor expression directive) (-> (System expression) Archive Reference (////generation.Operation anchor expression directive expression))) (case reference - {#reference.Constant value} + {reference.#Constant value} (..constant system archive value) - {#reference.Variable value} + {reference.#Variable value} (phase\in (..variable system value)))) 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 b9202972d..d2027e419 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 @@ -65,10 +65,10 @@ (^ (////synthesis.loop/recur _)) (//////phase.except ..cannot_recur_as_an_expression []) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive expression extension))) (def: .public generate 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 1e6cb7058..31fd8da27 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 @@ -56,7 +56,7 @@ ... TODO: Find some way to do 'let' without paying the price of the closure. (in (|> bodyO _.return - (_.lambda #.None (list (..register register))) + (_.lambda {.#None} (list (..register register))) (_.apply_lambda/* (list valueO)))))) (def: .public (let! statement expression archive [valueS register bodyS]) @@ -93,10 +93,10 @@ (in (list\mix (function (_ side source) (.let [method (.case side (^template [<side> <accessor>] - [(<side> lefts) + [{<side> lefts} (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueO (list.reversed pathP))))) @@ -188,16 +188,16 @@ (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] - (in {#.Some (.if when + (in {.#Some (.if when (_.if ..peek then! else!) @@ -213,15 +213,15 @@ (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - {#.Item item})] - (in {#.Some (_.cond clauses + {.#Item item})] + (in {.#Some (_.cond clauses ..fail!)}))]) - ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] - [#/////synthesis.F64_Fork (<| //primitive.f64)] - [#/////synthesis.Text_Fork (<| //primitive.text)]) + ([/////synthesis.#I64_Fork (<| //primitive.i64 .int)] + [/////synthesis.#F64_Fork (<| //primitive.f64)] + [/////synthesis.#Text_Fork (<| //primitive.text)]) _ - (\ ///////phase.monad in #.None))) + (\ ///////phase.monad in {.#None}))) (def: (pattern_matching' in_closure? statement expression archive) (-> Bit (Generator! Path)) @@ -229,28 +229,28 @@ (do ///////phase.monad [?output (primitive_pattern_matching recur pathP)] (.case ?output - {#.Some output} + {.#Some output} (in output) - #.None + {.#None} (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (statement expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in ..pop!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.set (list (..register register)) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] (in (.if when (_.if ..peek @@ -268,12 +268,12 @@ (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - {#.Item item})] + {.#Item item})] (in (_.cond clauses ..fail!)))]) - ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] - [#/////synthesis.F64_Fork (<| //primitive.f64)] - [#/////synthesis.Text_Fork (<| //primitive.text)]) + ([/////synthesis.#I64_Fork (<| //primitive.i64 .int)] + [/////synthesis.#F64_Fork (<| //primitive.f64)] + [/////synthesis.#Text_Fork (<| //primitive.text)]) (^template [<complex> <simple> <choice>] [(^ (<complex> idx)) @@ -353,5 +353,5 @@ (|> case (case! true statement expression archive) (\ ///////phase.monad each - (|>> (_.lambda #.None (list)) + (|>> (_.lambda {.#None} (list)) (_.apply_lambda/* (list)))))) 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 091d1fd31..b067a3319 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 @@ -45,7 +45,7 @@ (def: (with_closure inits self function_definition) (-> (List Expression) Text Expression [Statement Expression]) (case inits - #.End + {.#End} (let [@self (_.global self)] [(_.set (list @self) function_definition) @self]) @@ -84,7 +84,7 @@ initialize_self! (list.indices arity)) [declaration instatiation] (with_closure closureO+ function_name - (_.lambda {#.Some @self} (list (_.variadic @curried)) + (_.lambda {.#Some @self} (list (_.variadic @curried)) ($_ _.then (_.set (list @num_args) (_.the "length" @curried)) (_.cond (list [(|> @num_args (_.= arityO)) @@ -101,12 +101,12 @@ (_.apply_lambda/* (list output_func_args)))))]) ... (|> @num_args (_.< arityO)) (let [@missing (_.local "missing")] - (_.return (_.lambda #.None (list (_.variadic @missing)) + (_.return (_.lambda {.#None} (list (_.variadic @missing)) (_.return (|> @self (_.apply_lambda/* (list (_.splat (|> (_.array (list)) (_.do "concat" (list @curried)) (_.do "concat" (list @missing)))))))))))) )))] _ (/////generation.execute! declaration) - _ (/////generation.save! function_artifact #.None declaration)] + _ (/////generation.save! function_artifact {.#None} declaration)] (in instatiation))) 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 1aa61c2bc..b6be81745 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 @@ -52,7 +52,7 @@ (Generator! (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (statement expression archive bodyS) ... true loop @@ -69,7 +69,7 @@ (-> Phase! (Generator (Scope Synthesis))) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop @@ -77,7 +77,7 @@ (do [! ///////phase.monad] [body! (scope! statement expression archive [start initsS+ bodyS])] (in (|> body! - (_.lambda #.None (list)) + (_.lambda {.#None} (list)) (_.apply_lambda/* (list))))))) (def: .public (recur! statement expression archive argsS+) 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 643bde0b2..c10550d39 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 @@ -96,7 +96,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.local (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) LVar (~ runtime_name))) @@ -106,7 +106,7 @@ (function ((~ g!_) (~ g!name)) (_.set (list (~ g!name)) (~ code)))))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (macro.with_identifiers [g!_] (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) @@ -393,12 +393,12 @@ (Operation [Registry Output]) (do ///////phase.monad [_ (/////generation.execute! ..runtime) - _ (/////generation.save! ..module_id #.None ..runtime)] + _ (/////generation.save! ..module_id {.#None} ..runtime)] (in [(|> artifact.empty artifact.resource product.right) (row.row [..module_id - #.None + {.#None} (|> ..runtime _.code (\ utf8.codec encoded))])]))) 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 32ec74e4f..e3f1e558a 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 @@ -17,10 +17,10 @@ (def: .public (tuple generate archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (generate archive singletonS) _ 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 20108a0cd..26c13742e 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 @@ -36,7 +36,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - {#////synthesis.Reference value} + {////synthesis.#Reference value} (//reference.reference /reference.system archive value) (^template [<tag> <generator>] @@ -54,6 +54,6 @@ [////synthesis.loop/recur /loop.recur] [////synthesis.function/abstraction /function.function]) - {#////synthesis.Extension extension} + {////synthesis.#Extension extension} (///extension.apply archive generate extension) )) 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 bfdb9bf93..e2bdad616 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 @@ -69,8 +69,8 @@ (^template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) - ([#.Left //runtime.tuple//left] - [#.Right //runtime.tuple//right]))] + ([.#Left //runtime.tuple//left] + [.#Right //runtime.tuple//right]))] (method source))) valueO (list.reversed pathP))))) @@ -122,30 +122,30 @@ (list [(_.and (list (_.string?/1 @alt_error) (_.string=?/2 ..pm_error @alt_error))) on_failure]) - #.None + {.#None} happy_path)) (def: (pattern_matching' expression archive) (Generator Path) (function (recur pathP) (.case pathP - {#/////synthesis.Then bodyS} + {/////synthesis.#Then bodyS} (expression archive bodyS) - #/////synthesis.Pop + {/////synthesis.#Pop} (///////phase\in pop_cursor!) - {#/////synthesis.Bind register} + {/////synthesis.#Bind register} (///////phase\in (_.define_constant (..register register) ..peek)) - {#/////synthesis.Bit_Fork when thenP elseP} + {/////synthesis.#Bit_Fork when thenP elseP} (do [! ///////phase.monad] [then! (recur thenP) else! (.case elseP - {#.Some elseP} + {.#Some elseP} (recur elseP) - #.None + {.#None} (in ..fail!))] (in (.if when (_.if ..peek @@ -164,14 +164,14 @@ (in [(<=> (|> match <format>) ..peek) then!]))) - {#.Item item})] + {.#Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) ..fail! clauses)))]) - ([#/////synthesis.I64_Fork //primitive.i64 _.=/2] - [#/////synthesis.F64_Fork //primitive.f64 _.=/2] - [#/////synthesis.Text_Fork //primitive.text _.string=?/2]) + ([/////synthesis.#I64_Fork //primitive.i64 _.=/2] + [/////synthesis.#F64_Fork //primitive.f64 _.=/2] + [/////synthesis.#Text_Fork //primitive.text _.string=?/2]) (^template [<pm> <flag> <prep>] [(^ (<pm> idx)) 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 f0d2751f3..f45da0eaa 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 @@ -44,14 +44,14 @@ (-> (List Expression) Computation (Operation Computation)) (///////phase\in (case inits - #.End + {.#End} function_definition _ (|> function_definition (_.lambda [(|> (list.enumeration inits) (list\each (|>> product.left ..capture))) - #.None]) + {.#None}]) (_.apply/* inits))))) (def: @curried (_.var "curried")) @@ -76,13 +76,13 @@ @num_args (_.var "num_args") @self (_.var (///reference.artifact function_name))]] (with_closure closureO+ - (_.letrec (list [@self (_.lambda [(list) {#.Some @curried}] + (_.letrec (list [@self (_.lambda [(list) {.#Some @curried}] (_.let (list [@num_args (_.length/1 @curried)]) (<| (_.if (|> @num_args (_.=/2 arityO)) (<| (_.let (list [(//case.register 0) @self])) (_.let_values (list [[(|> (list.indices arity) (list\each ..input)) - #.None] + {.#None}] (_.apply/2 (_.var "apply") (_.var "values") @curried)])) bodyO)) (_.if (|> @num_args (_.>/2 arityO)) @@ -94,7 +94,7 @@ (apply_poly arity_args) (apply_poly output_func_args)))))) ... (|> @num_args (_.</2 arityO)) - (_.lambda [(list) {#.Some @missing}] + (_.lambda [(list) {.#Some @missing}] (|> @self (apply_poly (_.append/2 @curried @missing))))) ))]) 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 c5e6b5e0e..4718eca95 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 @@ -40,7 +40,7 @@ (Generator (Scope Synthesis)) (case initsS+ ... function/false/non-independent loop - #.End + {.#End} (expression archive bodyS) ... true loop @@ -52,7 +52,7 @@ (in (_.letrec (list [@scope (_.lambda [(|> initsS+ list.enumeration (list\each (|>> product.left (n.+ start) //case.register))) - #.None] + {.#None}] bodyO)]) (_.apply/* initsO+ @scope)))))) 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 0f8ae8b9a..1d15137f9 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 @@ -80,7 +80,7 @@ (let [runtime (code.local_identifier (///reference.artifact [..module_id runtime_id])) runtime_name (` (_.var (~ (code.text (%.code runtime)))))] (case declaration - {#.Left name} + {.#Left name} (let [g!name (code.local_identifier name)] (in (list (` (def: .public (~ g!name) Var @@ -90,7 +90,7 @@ _.Computation (_.define_constant (~ runtime_name) (~ code))))))) - {#.Right [name inputs]} + {.#Right [name inputs]} (let [g!name (code.local_identifier name) inputsC (list\each code.local_identifier inputs) inputs_typesC (list\each (function.constant (` _.Expression)) @@ -102,7 +102,7 @@ (` (def: (~ (code.local_identifier (format "@" name))) _.Computation (..with_vars [(~+ inputsC)] - (_.define_function (~ runtime_name) [(list (~+ inputsC)) #.None] + (_.define_function (~ runtime_name) [(list (~+ inputsC)) {.#None}] (~ code))))))))))))) (def: last_index @@ -214,14 +214,14 @@ (runtime: (lux//try op) (with_vars [error] (_.with_exception_handler - (_.lambda [(list error) #.None] + (_.lambda [(list error) {.#None}] (..left error)) - (_.lambda [(list) #.None] + (_.lambda [(list) {.#None}] (..right (_.apply/* (list ..unit) op)))))) (runtime: (lux//program_args program_args) (with_vars [@loop @input @output] - (_.letrec (list [@loop (_.lambda [(list @input @output) #.None] + (_.letrec (list [@loop (_.lambda [(list @input @output) {.#None}] (_.if (_.null?/1 @input) @output (_.apply/2 @loop (_.cdr/1 @input) (..some (_.vector/* (list (_.car/1 @input) @output))))))]) 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 cc84cf77c..d23bf422b 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 @@ -20,10 +20,10 @@ (def: .public (tuple expression archive elemsS+) (Generator (Tuple Synthesis)) (case elemsS+ - #.End + {.#End} (///////phase\in (//primitive.text /////synthesis.unit)) - {#.Item singletonS #.End} + {.#Item singletonS {.#End}} (expression archive singletonS) _ 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 faa6739cb..f7a4d8078 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 @@ -27,72 +27,72 @@ (def: (primitive analysis) (-> ///analysis.Primitive /.Primitive) (case analysis - #///analysis.Unit - {#/.Text /.unit} + {///analysis.#Unit} + {/.#Text /.unit} (^template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> value}]) - ([#///analysis.Bit #/.Bit] - [#///analysis.Frac #/.F64] - [#///analysis.Text #/.Text]) + ([///analysis.#Bit /.#Bit] + [///analysis.#Frac /.#F64] + [///analysis.#Text /.#Text]) (^template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> (.i64 value)}]) - ([#///analysis.Nat #/.I64] - [#///analysis.Int #/.I64] - [#///analysis.Rev #/.I64]))) + ([///analysis.#Nat /.#I64] + [///analysis.#Int /.#I64] + [///analysis.#Rev /.#I64]))) (def: (optimization archive) Phase (function (optimization' analysis) (case analysis - {#///analysis.Primitive analysis'} - (phase\in {#/.Primitive (..primitive analysis')}) + {///analysis.#Primitive analysis'} + (phase\in {/.#Primitive (..primitive analysis')}) - {#///analysis.Reference reference} - (phase\in {#/.Reference reference}) + {///analysis.#Reference reference} + (phase\in {/.#Reference reference}) - {#///analysis.Structure structure} + {///analysis.#Structure structure} (/.with_currying? false (case structure - {#///analysis.Variant variant} + {///analysis.#Variant variant} (do phase.monad - [valueS (optimization' (value@ #///analysis.value variant))] - (in (/.variant (with@ #///analysis.value valueS variant)))) + [valueS (optimization' (value@ ///analysis.#value variant))] + (in (/.variant (with@ ///analysis.#value valueS variant)))) - {#///analysis.Tuple tuple} + {///analysis.#Tuple tuple} (|> tuple (monad.each phase.monad optimization') (phase\each (|>> /.tuple))))) - {#///analysis.Case inputA branchesAB+} + {///analysis.#Case inputA branchesAB+} (/.with_currying? false (/case.synthesize optimization branchesAB+ archive inputA)) (^ (///analysis.no_op value)) (optimization' value) - {#///analysis.Apply _} + {///analysis.#Apply _} (/.with_currying? false (/function.apply optimization archive analysis)) - {#///analysis.Function environmentA bodyA} + {///analysis.#Function environmentA bodyA} (/function.abstraction optimization environmentA archive bodyA) - {#///analysis.Extension name args} + {///analysis.#Extension name args} (/.with_currying? false (function (_ state) (|> (//extension.apply archive optimization [name args]) (phase.result' state) - (case> {#try.Success output} - {#try.Success output} + (case> {try.#Success output} + {try.#Success output} - {#try.Failure _} + {try.#Failure _} (|> args (monad.each phase.monad optimization') - (phase\each (|>> [name] #/.Extension)) + (phase\each (|>> [name] {/.#Extension})) (phase.result' state)))))) ))) 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 6722a4e4e..a2cb2403a 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 @@ -31,19 +31,19 @@ (def: clean_up (-> Path Path) - (|>> {#/.Seq #/.Pop})) + (|>> {/.#Seq {/.#Pop}})) (def: (path' pattern end? thenC) (-> Pattern Bit (Operation Path) (Operation Path)) (case pattern - {#///analysis.Simple simple} + {///analysis.#Simple simple} (case simple - #///analysis.Unit + {///analysis.#Unit} thenC - {#///analysis.Bit when} + {///analysis.#Bit when} (///\each (function (_ then) - {#/.Bit_Fork when then #.None}) + {/.#Bit_Fork when then {.#None}}) thenC) (^template [<from> <to> <conversion>] @@ -51,38 +51,38 @@ (///\each (function (_ then) {<to> [(<conversion> test) then] (list)}) thenC)]) - ([#///analysis.Nat #/.I64_Fork .i64] - [#///analysis.Int #/.I64_Fork .i64] - [#///analysis.Rev #/.I64_Fork .i64] - [#///analysis.Frac #/.F64_Fork |>] - [#///analysis.Text #/.Text_Fork |>])) - - {#///analysis.Bind register} - (<| (\ ///.monad each (|>> {#/.Seq {#/.Bind register}})) + ([///analysis.#Nat /.#I64_Fork .i64] + [///analysis.#Int /.#I64_Fork .i64] + [///analysis.#Rev /.#I64_Fork .i64] + [///analysis.#Frac /.#F64_Fork |>] + [///analysis.#Text /.#Text_Fork |>])) + + {///analysis.#Bind register} + (<| (\ ///.monad each (|>> {/.#Seq {/.#Bind register}})) /.with_new_local thenC) - {#///analysis.Complex {#///analysis.Variant [lefts right? value_pattern]}} - (<| (///\each (|>> {#/.Seq {#/.Access {#/.Side (if right? - {#.Right lefts} - {#.Left lefts})}}})) + {///analysis.#Complex {///analysis.#Variant [lefts right? value_pattern]}} + (<| (///\each (|>> {/.#Seq {/.#Access {/.#Side (if right? + {.#Right lefts} + {.#Left lefts})}}})) (path' value_pattern end?) (when> [(new> (not end?) [])] [(///\each ..clean_up)]) thenC) - {#///analysis.Complex {#///analysis.Tuple tuple}} + {///analysis.#Complex {///analysis.#Tuple tuple}} (let [tuple::last (-- (list.size tuple))] (list\mix (function (_ [tuple::lefts tuple::member] nextC) (.case tuple::member - {#///analysis.Simple #///analysis.Unit} + {///analysis.#Simple {///analysis.#Unit}} nextC _ (let [right? (n.= tuple::last tuple::lefts) end?' (and end? right?)] - (<| (///\each (|>> {#/.Seq {#/.Access {#/.Member (if right? - {#.Right (-- tuple::lefts)} - {#.Left tuple::lefts})}}})) + (<| (///\each (|>> {/.#Seq {/.#Access {/.#Member (if right? + {.#Right (-- tuple::lefts)} + {.#Left tuple::lefts})}}})) (path' tuple::member end?') (when> [(new> (not end?') [])] [(///\each ..clean_up)]) nextC)))) @@ -92,7 +92,7 @@ (def: (path archive synthesize pattern bodyA) (-> Archive Phase Pattern Analysis (Operation Path)) - (path' pattern true (///\each (|>> #/.Then) (synthesize archive bodyA)))) + (path' pattern true (///\each (|>> {/.#Then}) (synthesize archive bodyA)))) (def: (weave_branch weave equivalence [new_test new_then] [[old_test old_then] old_tail]) (All (_ a) (-> (-> Path Path Path) (Equivalence a) [a Path] (/.Fork a Path) @@ -101,86 +101,86 @@ [[old_test (weave new_then old_then)] old_tail] [[old_test old_then] (case old_tail - #.End + {.#End} (list [new_test new_then]) - {#.Item old_item} - {#.Item (weave_branch weave equivalence [new_test new_then] old_item)})])) + {.#Item old_item} + {.#Item (weave_branch weave equivalence [new_test new_then] old_item)})])) (def: (weave_fork weave equivalence new_fork old_fork) (All (_ a) (-> (-> Path Path Path) (Equivalence a) (/.Fork a Path) (/.Fork a Path) (/.Fork a Path))) - (list\mix (..weave_branch weave equivalence) old_fork {#.Item new_fork})) + (list\mix (..weave_branch weave equivalence) old_fork {.#Item new_fork})) (def: (weave new old) (-> Path Path Path) - (with_expansions [<default> (as_is {#/.Alt old new})] + (with_expansions [<default> (as_is {/.#Alt old new})] (case [new old] [_ - {#/.Alt old_left old_right}] - {#/.Alt old_left + {/.#Alt old_left old_right}] + {/.#Alt old_left (weave new old_right)} - [{#/.Seq preN postN} - {#/.Seq preO postO}] + [{/.#Seq preN postN} + {/.#Seq preO postO}] (case (weave preN preO) - {#/.Alt _} + {/.#Alt _} <default> woven - {#/.Seq woven (weave postN postO)}) + {/.#Seq woven (weave postN postO)}) - [#/.Pop #/.Pop] + [{/.#Pop} {/.#Pop}] old - [{#/.Bit_Fork new_when new_then new_else} - {#/.Bit_Fork old_when old_then old_else}] + [{/.#Bit_Fork new_when new_then new_else} + {/.#Bit_Fork old_when old_then old_else}] (if (bit\= new_when old_when) - {#/.Bit_Fork old_when + {/.#Bit_Fork old_when (weave new_then old_then) (case [new_else old_else] - [#.None #.None] - #.None + [{.#None} {.#None}] + {.#None} - (^or [{#.Some woven_then} #.None] - [#.None {#.Some woven_then}]) - {#.Some woven_then} + (^or [{.#Some woven_then} {.#None}] + [{.#None} {.#Some woven_then}]) + {.#Some woven_then} - [{#.Some new_else} {#.Some old_else}] - {#.Some (weave new_else old_else)})} - {#/.Bit_Fork old_when + [{.#Some new_else} {.#Some old_else}] + {.#Some (weave new_else old_else)})} + {/.#Bit_Fork old_when (case new_else - #.None + {.#None} old_then - {#.Some new_else} + {.#Some new_else} (weave new_else old_then)) - {#.Some (case old_else - #.None + {.#Some (case old_else + {.#None} new_then - {#.Some old_else} + {.#Some old_else} (weave new_then old_else))}}) (^template [<tag> <equivalence>] [[{<tag> new_fork} {<tag> old_fork}] {<tag> (..weave_fork weave <equivalence> new_fork old_fork)}]) - ([#/.I64_Fork i64.equivalence] - [#/.F64_Fork frac.equivalence] - [#/.Text_Fork text.equivalence]) + ([/.#I64_Fork i64.equivalence] + [/.#F64_Fork frac.equivalence] + [/.#Text_Fork text.equivalence]) (^template [<access> <side>] - [[{#/.Access {<access> {<side> newL}}} - {#/.Access {<access> {<side> oldL}}}] + [[{/.#Access {<access> {<side> newL}}} + {/.#Access {<access> {<side> oldL}}}] (if (n.= newL oldL) old <default>)]) - ([#/.Side #.Left] - [#/.Side #.Right] - [#/.Member #.Left] - [#/.Member #.Right]) + ([/.#Side .#Left] + [/.#Side .#Right] + [/.#Member .#Left] + [/.#Member .#Right]) - [{#/.Bind newR} {#/.Bind oldR}] + [{/.#Bind newR} {/.#Bind oldR}] (if (n.= newR oldR) old <default>) @@ -196,25 +196,25 @@ <continue> (as_is (recur (++ lefts) tail)) <member> (as_is (if (list.empty? tail) - {#.Right (-- lefts)} - {#.Left lefts}))] + {.#Right (-- lefts)} + {.#Left lefts}))] (case patterns - #.End + {.#End} <failure> - {#.Item head tail} + {.#Item head tail} (case head - {#///analysis.Simple #///analysis.Unit} + {///analysis.#Simple {///analysis.#Unit}} <continue> - {#///analysis.Bind register} + {///analysis.#Bind register} (if (n.= @selection register) (list <member>) <continue>) - {#///analysis.Complex {#///analysis.Tuple sub_patterns}} + {///analysis.#Complex {///analysis.#Tuple sub_patterns}} (case (get sub_patterns @selection) - #.End + {.#End} <continue> sub_members @@ -231,8 +231,8 @@ (in (/.branch/case [input (list\mix weave headSP tailSP+)])))) (template: (!masking <variable> <output>) - [[[{#///analysis.Bind <variable>} - {#///analysis.Reference (///reference.local <output>)}] + [[[{///analysis.#Bind <variable>} + {///analysis.#Reference (///reference.local <output>)}] (list)]]) (def: .public (synthesize_let synthesize archive input @variable body) @@ -246,7 +246,7 @@ (-> Phase Archive Synthesis Register Register (Operation Synthesis)) (if (n.= @variable @output) (///\in input) - (..synthesize_let synthesize archive input @variable {#///analysis.Reference (///reference.local @output)}))) + (..synthesize_let synthesize archive input @variable {///analysis.#Reference (///reference.local @output)}))) (def: .public (synthesize_if synthesize archive test then else) (-> Phase Archive Synthesis Analysis Analysis (Operation Synthesis)) @@ -257,13 +257,13 @@ (template: (!get <patterns> <output>) [[[(///analysis.pattern/tuple <patterns>) - {#///analysis.Reference (///reference.local <output>)}] + {///analysis.#Reference (///reference.local <output>)}] (.list)]]) (def: .public (synthesize_get synthesize archive input patterns @member) (-> Phase Archive Synthesis (///analysis.Tuple ///analysis.Pattern) Register (Operation Synthesis)) (case (..get patterns @member) - #.End + {.#End} (..synthesize_case synthesize archive input (!get patterns @member)) path @@ -282,8 +282,8 @@ (^ (!masking @variable @output)) (..synthesize_masking synthesize^ archive inputS @variable @output) - [[{#///analysis.Bind @variable} body] - #.End] + [[{///analysis.#Bind @variable} body] + {.#End}] (..synthesize_let synthesize^ archive inputS @variable body) (^or (^ [[(///analysis.pattern/bit #1) then] @@ -306,7 +306,7 @@ (def: .public (count_pops path) (-> Path [Nat Path]) (case path - (^ (/.path/seq #/.Pop path')) + (^ (/.path/seq {/.#Pop} path')) (let [[pops post_pops] (count_pops path')] [(++ pops) post_pops]) @@ -338,26 +338,27 @@ [path path path_storage ..empty] (case path - (^or #/.Pop {#/.Access Access}) + (^or {/.#Pop} + {/.#Access Access}) path_storage (^ (/.path/bind register)) (revised@ #bindings (set.has register) path_storage) - {#/.Bit_Fork _ default otherwise} + {/.#Bit_Fork _ default otherwise} (|> (case otherwise - #.None + {.#None} path_storage - {#.Some otherwise} + {.#Some otherwise} (for_path otherwise path_storage)) (for_path default)) - (^or {#/.I64_Fork forks} - {#/.F64_Fork forks} - {#/.Text_Fork forks}) - (|> {#.Item forks} + (^or {/.#I64_Fork forks} + {/.#F64_Fork forks} + {/.#Text_Fork forks}) + (|> {.#Item forks} (list\each product.right) (list\mix for_path path_storage)) @@ -376,16 +377,16 @@ (^ (/.tuple members)) (list\mix for_synthesis synthesis_storage members) - {#/.Reference {#///reference.Variable {#///reference/variable.Local register}}} + {/.#Reference {///reference.#Variable {///reference/variable.#Local register}}} (if (set.member? (value@ #bindings synthesis_storage) register) synthesis_storage - (revised@ #dependencies (set.has {#///reference/variable.Local register}) synthesis_storage)) + (revised@ #dependencies (set.has {///reference/variable.#Local register}) synthesis_storage)) - {#/.Reference {#///reference.Variable var}} + {/.#Reference {///reference.#Variable var}} (revised@ #dependencies (set.has var) synthesis_storage) (^ (/.function/apply [functionS argsS])) - (list\mix for_synthesis synthesis_storage {#.Item functionS argsS}) + (list\mix for_synthesis synthesis_storage {.#Item functionS argsS}) (^ (/.function/abstraction [environment arity bodyS])) (list\mix for_synthesis synthesis_storage environment) @@ -423,7 +424,7 @@ (^ (/.loop/recur replacementsS+)) (list\mix for_synthesis synthesis_storage replacementsS+) - {#/.Extension [extension argsS]} + {/.#Extension [extension argsS]} (list\mix for_synthesis synthesis_storage argsS) _ 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 278b6343e..09725f153 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 @@ -56,7 +56,7 @@ (with_expansions [<apply> (as_is (/.function/apply [funcS argsS]))] (case funcS (^ (/.function/abstraction functionS)) - (if (n.= (value@ #/.arity functionS) + (if (n.= (value@ /.#arity functionS) (list.size argsS)) (do ! [locals /.locals] @@ -85,17 +85,17 @@ (def: (find_foreign environment register) (-> (Environment Synthesis) Register (Operation Synthesis)) (case (list.item register environment) - {#.Some aliased} + {.#Some aliased} (phase\in aliased) - #.None + {.#None} (phase.except ..cannot_find_foreign_variable_in_environment [register environment]))) (def: (grow_path grow path) (-> (-> Synthesis (Operation Synthesis)) Path (Operation Path)) (case path - {#/.Bind register} - (phase\in {#/.Bind (++ register)}) + {/.#Bind register} + (phase\in {/.#Bind (++ register)}) (^template [<tag>] [{<tag> left right} @@ -103,18 +103,18 @@ [left' (grow_path grow left) right' (grow_path grow right)] (in {<tag> left' right'}))]) - ([#/.Alt] [#/.Seq]) + ([/.#Alt] [/.#Seq]) - {#/.Bit_Fork when then else} + {/.#Bit_Fork when then else} (do [! phase.monad] [then (grow_path grow then) else (case else - {#.Some else} - (\ ! each (|>> {#.Some}) (grow_path grow else)) + {.#Some else} + (\ ! each (|>> {.#Some}) (grow_path grow else)) - #.None - (in #.None))] - (in {#/.Bit_Fork when then else})) + {.#None} + (in {.#None}))] + (in {/.#Bit_Fork when then else})) (^template [<tag>] [{<tag> [[test then] elses]} @@ -126,14 +126,14 @@ (in [else_test else_then]))) elses)] (in {<tag> [[test then] elses]}))]) - ([#/.I64_Fork] - [#/.F64_Fork] - [#/.Text_Fork]) + ([/.#I64_Fork] + [/.#F64_Fork] + [/.#Text_Fork]) - {#/.Then thenS} + {/.#Then thenS} (|> thenS grow - (phase\each (|>> {#/.Then}))) + (phase\each (|>> {/.#Then}))) _ (phase\in path))) @@ -141,14 +141,14 @@ (def: (grow environment expression) (-> (Environment Synthesis) Synthesis (Operation Synthesis)) (case expression - {#/.Structure structure} + {/.#Structure structure} (case structure - {#////analysis.Variant [lefts right? subS]} + {////analysis.#Variant [lefts right? subS]} (|> subS (grow environment) (phase\each (|>> [lefts right?] /.variant))) - {#////analysis.Tuple membersS+} + {////analysis.#Tuple membersS+} (|> membersS+ (monad.each phase.monad (grow environment)) (phase\each (|>> /.tuple)))) @@ -156,66 +156,66 @@ (^ (..self_reference)) (phase\in (/.function/apply [expression (list (/.variable/local 1))])) - {#/.Reference reference} + {/.#Reference reference} (case reference - {#////reference.Variable variable} + {////reference.#Variable variable} (case variable - {#////reference/variable.Local register} + {////reference/variable.#Local register} (phase\in (/.variable/local (++ register))) - {#////reference/variable.Foreign register} + {////reference/variable.#Foreign register} (..find_foreign environment register)) - {#////reference.Constant constant} + {////reference.#Constant constant} (phase\in expression)) - {#/.Control control} + {/.#Control control} (case control - {#/.Branch branch} + {/.#Branch branch} (case branch - {#/.Let [inputS register bodyS]} + {/.#Let [inputS register bodyS]} (do phase.monad [inputS' (grow environment inputS) bodyS' (grow environment bodyS)] (in (/.branch/let [inputS' (++ register) bodyS']))) - {#/.If [testS thenS elseS]} + {/.#If [testS thenS elseS]} (do phase.monad [testS' (grow environment testS) thenS' (grow environment thenS) elseS' (grow environment elseS)] (in (/.branch/if [testS' thenS' elseS']))) - {#/.Get members inputS} + {/.#Get members inputS} (do phase.monad [inputS' (grow environment inputS)] (in (/.branch/get [members inputS']))) - {#/.Case [inputS pathS]} + {/.#Case [inputS pathS]} (do phase.monad [inputS' (grow environment inputS) pathS' (grow_path (grow environment) pathS)] (in (/.branch/case [inputS' pathS'])))) - {#/.Loop loop} + {/.#Loop loop} (case loop - {#/.Scope [start initsS+ iterationS]} + {/.#Scope [start initsS+ iterationS]} (do [! phase.monad] [initsS+' (monad.each ! (grow environment) initsS+) iterationS' (grow environment iterationS)] (in (/.loop/scope [(++ start) initsS+' iterationS']))) - {#/.Recur argumentsS+} + {/.#Recur argumentsS+} (|> argumentsS+ (monad.each phase.monad (grow environment)) (phase\each (|>> /.loop/recur)))) - {#/.Function function} + {/.#Function function} (case function - {#/.Abstraction [_env _arity _body]} + {/.#Abstraction [_env _arity _body]} (do [! phase.monad] [_env' (monad.each ! - (|>> (case> {#/.Reference {#////reference.Variable {#////reference/variable.Foreign register}}} + (|>> (case> {/.#Reference {////reference.#Variable {////reference/variable.#Foreign register}}} (..find_foreign environment register) captured @@ -223,7 +223,7 @@ _env)] (in (/.function/abstraction [_env' _arity _body]))) - {#/.Apply funcS argsS+} + {/.#Apply funcS argsS+} (do [! phase.monad] [funcS (grow environment funcS) argsS+ (monad.each ! (grow environment) argsS+)] @@ -236,12 +236,12 @@ [funcS argsS+])))))) - {#/.Extension name argumentsS+} + {/.#Extension name argumentsS+} (|> argumentsS+ (monad.each phase.monad (grow environment)) - (phase\each (|>> {#/.Extension name}))) + (phase\each (|>> {/.#Extension name}))) - {#/.Primitive _} + {/.#Primitive _} (phase\in expression))) (def: .public (abstraction phase environment archive bodyA) @@ -258,21 +258,21 @@ (|> bodyS' (grow env') (\ ! each (function (_ body) - [#/.environment environment - #/.arity (++ down_arity') - #/.body body]))) + [/.#environment environment + /.#arity (++ down_arity') + /.#body body]))) _ - (in [#/.environment environment - #/.arity 1 - #/.body bodyS])))] + (in [/.#environment environment + /.#arity 1 + /.#body bodyS])))] (in (if currying? (/.function/abstraction abstraction) (case (//loop.optimization false 1 (list) abstraction) - {#.Some [startL initsL bodyL]} - (/.function/abstraction [#/.environment environment - #/.arity (value@ #/.arity abstraction) - #/.body (/.loop/scope [startL initsL bodyL])]) + {.#Some [startL initsL bodyL]} + (/.function/abstraction [/.#environment environment + /.#arity (value@ /.#arity abstraction) + /.#body (/.loop/scope [startL initsL bodyL])]) - #.None + {.#None} (/.function/abstraction abstraction)))))) 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 c65c261e8..b994bd92e 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 @@ -30,8 +30,8 @@ (-> (Transform Synthesis) Register (Transform Path)) (function (recur path) (case path - {#/.Bind register} - {#.Some {#/.Bind (register_optimization offset register)}} + {/.#Bind register} + {.#Some {/.#Bind (register_optimization offset register)}} (^template [<tag>] [{<tag> left right} @@ -39,18 +39,18 @@ [left' (recur left) right' (recur right)] (in {<tag> left' right'}))]) - ([#/.Alt] [#/.Seq]) + ([/.#Alt] [/.#Seq]) - {#/.Bit_Fork when then else} + {/.#Bit_Fork when then else} (do [! maybe.monad] [then (recur then) else (case else - {#.Some else} - (\ ! each (|>> #.Some) (recur else)) + {.#Some else} + (\ ! each (|>> {.#Some}) (recur else)) - #.None - (in #.None))] - (in {#/.Bit_Fork when then else})) + {.#None} + (in {.#None}))] + (in {/.#Bit_Fork when then else})) (^template [<tag>] [{<tag> [[test then] elses]} @@ -62,57 +62,57 @@ (in [else_test else_then]))) elses)] (in {<tag> [[test then] elses]}))]) - ([#/.I64_Fork] - [#/.F64_Fork] - [#/.Text_Fork]) + ([/.#I64_Fork] + [/.#F64_Fork] + [/.#Text_Fork]) - {#/.Then body} + {/.#Then body} (|> body body_optimization - (maybe\each (|>> {#/.Then}))) + (maybe\each (|>> {/.#Then}))) _ - {#.Some path}))) + {.#Some path}))) (def: (body_optimization true_loop? offset scope_environment arity expr) (-> Bit Register (Environment Synthesis) Arity (Transform Synthesis)) (loop [return? true expr expr] (case expr - {#/.Primitive _} - {#.Some expr} + {/.#Primitive _} + {.#Some expr} - {#/.Structure structure} + {/.#Structure structure} (case structure - {#analysis.Variant variant} + {analysis.#Variant variant} (do maybe.monad - [value' (|> variant (value@ #analysis.value) (recur false))] + [value' (|> variant (value@ analysis.#value) (recur false))] (in (|> variant - (with@ #analysis.value value') + (with@ analysis.#value value') /.variant))) - {#analysis.Tuple tuple} + {analysis.#Tuple tuple} (|> tuple (monad.each maybe.monad (recur false)) (maybe\each (|>> /.tuple)))) - {#/.Reference reference} + {/.#Reference reference} (case reference - (^ {#reference.Variable (variable.self)}) + (^ {reference.#Variable (variable.self)}) (if true_loop? - #.None - {#.Some expr}) + {.#None} + {.#Some expr}) (^ (reference.constant constant)) - {#.Some expr} + {.#Some expr} (^ (reference.local register)) - {#.Some {#/.Reference (reference.local (register_optimization offset register))}} + {.#Some {/.#Reference (reference.local (register_optimization offset register))}} (^ (reference.foreign register)) (if true_loop? (list.item register scope_environment) - {#.Some expr})) + {.#Some expr})) (^ (/.branch/case [input path])) (do maybe.monad @@ -141,12 +141,12 @@ (^ (/.loop/scope scope)) (do [! maybe.monad] [inits' (|> scope - (value@ #/.inits) + (value@ /.#inits) (monad.each ! (recur false))) - iteration' (recur return? (value@ #/.iteration scope))] - (in (/.loop/scope [#/.start (|> scope (value@ #/.start) (register_optimization offset)) - #/.inits inits' - #/.iteration iteration']))) + iteration' (recur return? (value@ /.#iteration scope))] + (in (/.loop/scope [/.#start (|> scope (value@ /.#start) (register_optimization offset)) + /.#inits inits' + /.#iteration iteration']))) (^ (/.loop/recur args)) (|> args @@ -165,45 +165,45 @@ [abstraction' (recur false abstraction)] (in (/.function/apply [abstraction' arguments']))))] (case abstraction - (^ {#/.Reference {#reference.Variable (variable.self)}}) + (^ {/.#Reference {reference.#Variable (variable.self)}}) (if (and return? (n.= arity (list.size arguments))) (in (/.loop/recur arguments')) (if true_loop? - #.None + {.#None} <application>)) _ <application>))) ... TODO: Stop relying on this custom code. - (^ {#/.Extension ["lux syntax char case!" (list& input else matches)]}) + (^ {/.#Extension ["lux syntax char case!" (list& input else matches)]}) (if return? (do [! maybe.monad] [input (recur false input) matches (monad.each ! (function (_ match) (case match - (^ {#/.Structure {#analysis.Tuple (list when then)}}) + (^ {/.#Structure {analysis.#Tuple (list when then)}}) (do ! [when (recur false when) then (recur return? then)] - (in {#/.Structure {#analysis.Tuple (list when then)}})) + (in {/.#Structure {analysis.#Tuple (list when then)}})) _ (recur false match))) matches) else (recur return? else)] - (in {#/.Extension ["lux syntax char case!" (list& input else matches)]})) - #.None) + (in {/.#Extension ["lux syntax char case!" (list& input else matches)]})) + {.#None}) - {#/.Extension [name args]} + {/.#Extension [name args]} (|> args (monad.each maybe.monad (recur false)) - (maybe\each (|>> [name] {#/.Extension})))))) + (maybe\each (|>> [name] {/.#Extension})))))) (def: .public (optimization true_loop? offset inits functionS) (-> Bit Register (List Synthesis) Abstraction (Maybe [Register (List Synthesis) Synthesis])) - (|> (value@ #/.body functionS) - (body_optimization true_loop? offset (value@ #/.environment functionS) (value@ #/.arity functionS)) + (|> (value@ /.#body functionS) + (body_optimization true_loop? offset (value@ /.#environment functionS) (value@ /.#arity functionS)) (maybe\each (|>> [offset inits])))) 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 17399b478..75647203b 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 @@ -39,27 +39,27 @@ (-> (Remover Synthesis) (Remover Path)) (function (recur path) (case path - {#/.Seq {#/.Bind register} + {/.#Seq {/.#Bind register} post} (if (n.= redundant register) (recur post) - {#/.Seq {#/.Bind (if (n.> redundant register) + {/.#Seq {/.#Bind (if (n.> redundant register) (-- register) register)} (recur post)}) - (^or {#/.Seq {#/.Access {#/.Member member}} - {#/.Seq {#/.Bind register} + (^or {/.#Seq {/.#Access {/.#Member member}} + {/.#Seq {/.#Bind register} post}} ... This alternative form should never occur in practice. ... Yet, it is "technically" possible to construct it. - {#/.Seq {#/.Seq {#/.Access {#/.Member member}} - {#/.Bind register}} + {/.#Seq {/.#Seq {/.#Access {/.#Member member}} + {/.#Bind register}} post}) (if (n.= redundant register) (recur post) - {#/.Seq {#/.Access {#/.Member member}} - {#/.Seq {#/.Bind (if (n.> redundant register) + {/.#Seq {/.#Access {/.#Member member}} + {/.#Seq {/.#Bind (if (n.> redundant register) (-- register) register)} (recur post)}}) @@ -67,11 +67,11 @@ (^template [<tag>] [{<tag> left right} {<tag> (recur left) (recur right)}]) - ([#/.Seq] - [#/.Alt]) + ([/.#Seq] + [/.#Alt]) - {#/.Bit_Fork when then else} - {#/.Bit_Fork when (recur then) (maybe\each recur else)} + {/.#Bit_Fork when then else} + {/.#Bit_Fork when (recur then) (maybe\each recur else)} (^template [<tag>] [{<tag> [[test then] tail]} @@ -79,93 +79,93 @@ (list\each (function (_ [test' then']) [test' (recur then')]) tail)]}]) - ([#/.I64_Fork] - [#/.F64_Fork] - [#/.Text_Fork]) + ([/.#I64_Fork] + [/.#F64_Fork] + [/.#Text_Fork]) - (^or #/.Pop - {#/.Access _}) + (^or {/.#Pop} + {/.#Access _}) path - {#/.Bind register} + {/.#Bind register} (undefined) - {#/.Then then} - {#/.Then (remove_local redundant then)} + {/.#Then then} + {/.#Then (remove_local redundant then)} ))) (def: (remove_local_from_variable redundant variable) (Remover Variable) (case variable - {#variable.Local register} - {#variable.Local (..prune redundant register)} + {variable.#Local register} + {variable.#Local (..prune redundant register)} - {#variable.Foreign register} + {variable.#Foreign register} variable)) (def: (remove_local redundant) (Remover Synthesis) (function (recur synthesis) (case synthesis - {#/.Primitive _} + {/.#Primitive _} synthesis - {#/.Structure structure} - {#/.Structure (case structure - {#analysis.Variant [lefts right value]} - {#analysis.Variant [lefts right (recur value)]} + {/.#Structure structure} + {/.#Structure (case structure + {analysis.#Variant [lefts right value]} + {analysis.#Variant [lefts right (recur value)]} - {#analysis.Tuple tuple} - {#analysis.Tuple (list\each recur tuple)})} + {analysis.#Tuple tuple} + {analysis.#Tuple (list\each recur tuple)})} - {#/.Reference reference} + {/.#Reference reference} (case reference - {#reference.Variable variable} + {reference.#Variable variable} (/.variable (..remove_local_from_variable redundant variable)) - {#reference.Constant constant} + {reference.#Constant constant} synthesis) - {#/.Control control} - {#/.Control (case control - {#/.Branch branch} - {#/.Branch (case branch - {#/.Let input register output} - {#/.Let (recur input) + {/.#Control control} + {/.#Control (case control + {/.#Branch branch} + {/.#Branch (case branch + {/.#Let input register output} + {/.#Let (recur input) (..prune redundant register) (recur output)} - {#/.If test then else} - {#/.If (recur test) (recur then) (recur else)} + {/.#If test then else} + {/.#If (recur test) (recur then) (recur else)} - {#/.Get path record} - {#/.Get path (recur record)} + {/.#Get path record} + {/.#Get path (recur record)} - {#/.Case input path} - {#/.Case (recur input) (remove_local_from_path remove_local redundant path)})} + {/.#Case input path} + {/.#Case (recur input) (remove_local_from_path remove_local redundant path)})} - {#/.Loop loop} - {#/.Loop (case loop - {#/.Scope [start inits iteration]} - {#/.Scope [(..prune redundant start) + {/.#Loop loop} + {/.#Loop (case loop + {/.#Scope [start inits iteration]} + {/.#Scope [(..prune redundant start) (list\each recur inits) (recur iteration)]} - {#/.Recur resets} - {#/.Recur (list\each recur resets)})} + {/.#Recur resets} + {/.#Recur (list\each recur resets)})} - {#/.Function function} - {#/.Function (case function - {#/.Abstraction [environment arity body]} - {#/.Abstraction [(list\each recur environment) + {/.#Function function} + {/.#Function (case function + {/.#Abstraction [environment arity body]} + {/.#Abstraction [(list\each recur environment) arity body]} - {#/.Apply abstraction inputs} - {#/.Apply (recur abstraction) (list\each recur inputs)})})} + {/.#Apply abstraction inputs} + {/.#Apply (recur abstraction) (list\each recur inputs)})})} - {#/.Extension name inputs} - {#/.Extension name (list\each recur inputs)}))) + {/.#Extension name inputs} + {/.#Extension name (list\each recur inputs)}))) (type: Redundancy (Dictionary Register Bit)) @@ -197,16 +197,16 @@ (All (_ a) (-> (Optimization a) (Optimization (List a)))) (function (recur [redundancy values]) (case values - #.End - {#try.Success [redundancy + {.#End} + {try.#Success [redundancy values]} - {#.Item head tail} + {.#Item head tail} (do try.monad [[redundancy head] (optimization [redundancy head]) [redundancy tail] (recur [redundancy tail])] (in [redundancy - {#.Item head tail}]))))) + {.#Item head tail}]))))) (template [<name>] [(exception: .public (<name> [register Register]) @@ -220,20 +220,20 @@ (def: (declare register redundancy) (-> Register Redundancy (Try Redundancy)) (case (dictionary.value register redundancy) - #.None - {#try.Success (dictionary.has register ..redundant! redundancy)} + {.#None} + {try.#Success (dictionary.has register ..redundant! redundancy)} - {#.Some _} + {.#Some _} (exception.except ..redundant_declaration [register]))) (def: (observe register redundancy) (-> Register Redundancy (Try Redundancy)) (case (dictionary.value register redundancy) - #.None + {.#None} (exception.except ..unknown_register [register]) - {#.Some _} - {#try.Success (dictionary.has register ..necessary! redundancy)})) + {.#Some _} + {try.#Success (dictionary.has register ..necessary! redundancy)})) (def: (format redundancy) (%.Format Redundancy) @@ -247,24 +247,24 @@ (-> (Optimization Synthesis) (Optimization Path)) (function (recur [redundancy path]) (case path - (^or #/.Pop - {#/.Access _}) - {#try.Success [redundancy + (^or {/.#Pop} + {/.#Access _}) + {try.#Success [redundancy path]} - {#/.Bit_Fork when then else} + {/.#Bit_Fork when then else} (do [! try.monad] [[redundancy then] (recur [redundancy then]) [redundancy else] (case else - {#.Some else} + {.#Some else} (\ ! each (function (_ [redundancy else]) - [redundancy {#.Some else}]) + [redundancy {.#Some else}]) (recur [redundancy else])) - #.None - (in [redundancy #.None]))] - (in [redundancy {#/.Bit_Fork when then else}])) + {.#None} + (in [redundancy {.#None}]))] + (in [redundancy {/.#Bit_Fork when then else}])) (^template [<tag> <type>] [{<tag> [[test then] elses]} @@ -277,23 +277,23 @@ (in [redundancy [else_test else_then]])))) [redundancy elses])] (in [redundancy {<tag> [[test then] elses]}]))]) - ([#/.I64_Fork (I64 Any)] - [#/.F64_Fork Frac] - [#/.Text_Fork Text]) + ([/.#I64_Fork (I64 Any)] + [/.#F64_Fork Frac] + [/.#Text_Fork Text]) - {#/.Bind register} + {/.#Bind register} (do try.monad [redundancy (..declare register redundancy)] (in [redundancy path])) - {#/.Alt left right} + {/.#Alt left right} (do try.monad [[redundancy left] (recur [redundancy left]) [redundancy right] (recur [redundancy right])] - (in [redundancy {#/.Alt left right}])) + (in [redundancy {/.#Alt left right}])) - {#/.Seq pre post} + {/.#Seq pre post} (do try.monad [.let [baseline (|> redundancy dictionary.keys @@ -313,56 +313,56 @@ (in [(list\mix dictionary.lacks redundancy (set.list bindings)) (|> redundants (list.sorted n.>) - (list\mix (..remove_local_from_path ..remove_local) {#/.Seq pre post}))])) + (list\mix (..remove_local_from_path ..remove_local) {/.#Seq pre post}))])) - {#/.Then then} + {/.#Then then} (do try.monad [[redundancy then] (optimization [redundancy then])] - (in [redundancy {#/.Then then}])) + (in [redundancy {/.#Then then}])) ))) (def: (optimization' [redundancy synthesis]) (Optimization Synthesis) - (with_expansions [<no_op> (as_is {#try.Success [redundancy + (with_expansions [<no_op> (as_is {try.#Success [redundancy synthesis]})] (case synthesis - {#/.Primitive _} + {/.#Primitive _} <no_op> - {#/.Structure structure} + {/.#Structure structure} (case structure - {#analysis.Variant [lefts right value]} + {analysis.#Variant [lefts right value]} (do try.monad [[redundancy value] (optimization' [redundancy value])] (in [redundancy - {#/.Structure {#analysis.Variant [lefts right value]}}])) + {/.#Structure {analysis.#Variant [lefts right value]}}])) - {#analysis.Tuple tuple} + {analysis.#Tuple tuple} (do try.monad [[redundancy tuple] (..list_optimization optimization' [redundancy tuple])] (in [redundancy - {#/.Structure {#analysis.Tuple tuple}}]))) + {/.#Structure {analysis.#Tuple tuple}}]))) - {#/.Reference reference} + {/.#Reference reference} (case reference - {#reference.Variable variable} + {reference.#Variable variable} (case variable - {#variable.Local register} + {variable.#Local register} (do try.monad [redundancy (..observe register redundancy)] <no_op>) - {#variable.Foreign register} + {variable.#Foreign register} <no_op>) - {#reference.Constant constant} + {reference.#Constant constant} <no_op>) - {#/.Control control} + {/.#Control control} (case control - {#/.Branch branch} + {/.#Branch branch} (case branch - {#/.Let input register output} + {/.#Let input register output} (do try.monad [[redundancy input] (optimization' [redundancy input]) redundancy (..declare register redundancy) @@ -371,70 +371,70 @@ (dictionary.value register) (maybe.else ..necessary!))]] (in [(dictionary.lacks register redundancy) - {#/.Control (if redundant? - {#/.Branch {#/.Case input - {#/.Seq #/.Pop - {#/.Then (..remove_local register output)}}}} - {#/.Branch {#/.Let input register output}})}])) + {/.#Control (if redundant? + {/.#Branch {/.#Case input + {/.#Seq {/.#Pop} + {/.#Then (..remove_local register output)}}}} + {/.#Branch {/.#Let input register output}})}])) - {#/.If test then else} + {/.#If test then else} (do try.monad [[redundancy test] (optimization' [redundancy test]) [redundancy then] (optimization' [redundancy then]) [redundancy else] (optimization' [redundancy else])] (in [redundancy - {#/.Control {#/.Branch {#/.If test then else}}}])) + {/.#Control {/.#Branch {/.#If test then else}}}])) - {#/.Get path record} + {/.#Get path record} (do try.monad [[redundancy record] (optimization' [redundancy record])] (in [redundancy - {#/.Control {#/.Branch {#/.Get path record}}}])) + {/.#Control {/.#Branch {/.#Get path record}}}])) - {#/.Case input path} + {/.#Case input path} (do try.monad [[redundancy input] (optimization' [redundancy input]) [redundancy path] (..path_optimization optimization' [redundancy path])] (in [redundancy - {#/.Control {#/.Branch {#/.Case input path}}}]))) + {/.#Control {/.#Branch {/.#Case input path}}}]))) - {#/.Loop loop} + {/.#Loop loop} (case loop - {#/.Scope [start inits iteration]} + {/.#Scope [start inits iteration]} (do try.monad [[redundancy inits] (..list_optimization optimization' [redundancy inits]) .let [[extension redundancy] (..extended start (list.size inits) redundancy)] [redundancy iteration] (optimization' [redundancy iteration])] (in [(list\mix dictionary.lacks redundancy extension) - {#/.Control {#/.Loop {#/.Scope [start inits iteration]}}}])) + {/.#Control {/.#Loop {/.#Scope [start inits iteration]}}}])) - {#/.Recur resets} + {/.#Recur resets} (do try.monad [[redundancy resets] (..list_optimization optimization' [redundancy resets])] (in [redundancy - {#/.Control {#/.Loop {#/.Recur resets}}}]))) + {/.#Control {/.#Loop {/.#Recur resets}}}]))) - {#/.Function function} + {/.#Function function} (case function - {#/.Abstraction [environment arity body]} + {/.#Abstraction [environment arity body]} (do [! try.monad] [[redundancy environment] (..list_optimization optimization' [redundancy environment]) [_ body] (optimization' [(..default arity) body])] (in [redundancy - {#/.Control {#/.Function {#/.Abstraction [environment arity body]}}}])) + {/.#Control {/.#Function {/.#Abstraction [environment arity body]}}}])) - {#/.Apply abstraction inputs} + {/.#Apply abstraction inputs} (do try.monad [[redundancy abstraction] (optimization' [redundancy abstraction]) [redundancy inputs] (..list_optimization optimization' [redundancy inputs])] (in [redundancy - {#/.Control {#/.Function {#/.Apply abstraction inputs}}}])))) + {/.#Control {/.#Function {/.#Apply abstraction inputs}}}])))) - {#/.Extension name inputs} + {/.#Extension name inputs} (do try.monad [[redundancy inputs] (..list_optimization optimization' [redundancy inputs])] (in [redundancy - {#/.Extension name inputs}]))))) + {/.#Extension name inputs}]))))) (def: .public optimization (-> Synthesis (Try Synthesis)) 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 6b9fbfd09..cd3bb3f30 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -42,16 +42,16 @@ (do ! [id (archive.id module archive) [descriptor document] (archive.find module archive)] - (in [[module id] (value@ #descriptor.registry descriptor)])))))] + (in [[module id] (value@ descriptor.#registry descriptor)])))))] (case (list.one (function (_ [[module module_id] registry]) (do maybe.monad [program_id (artifact.remember ..name registry)] (in [module_id program_id]))) registries) - {#.Some program_context} + {.#Some program_context} (in program_context) - #.None + {.#None} (|> registries (list\each (|>> product.left product.left)) (exception.except ..cannot_find_program))))) 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 b855ced2f..68df640bf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -171,11 +171,11 @@ ["Text" (%.text text)])) (template: (!failure parser where offset source_code) - [{#.Left [[where offset source_code] + [{.#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] + [{.#Left [[where offset source_code] (exception.error ..end_of_file current_module)]}]) (type: (Parser a) @@ -193,15 +193,15 @@ (template: (!letE <binding> <computation> <body>) [(case <computation> - {#.Right <binding>} + {.#Right <binding>} <body> - ... {#.Left error} + ... {.#Left error} <<otherwise>> (:expected <<otherwise>>))]) (template: (!horizontal where offset source_code) - [[(revised@ #.column ++ where) + [[(revised@ .#column ++ where) (!++ offset) source_code]]) @@ -225,62 +225,62 @@ (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) (loop [source (: Source [(!forward 1 where) offset source_code]) - stack (: (List Code) #.End)] + stack (: (List Code) {.#End})] (case (parse source) - {#.Right [source' top]} - (recur source' {#.Item top stack}) + {.#Right [source' top]} + (recur source' {.#Item top stack}) - {#.Left [source' error]} + {.#Left [source' error]} (if (same? <close> error) - {#.Right [source' + {.#Right [source' [where {<tag> (list.reversed stack)}]]} - {#.Left [source' error]}))))] + {.#Left [source' error]}))))] ... Form and tuple syntax is mostly the same, differing only in the ... delimiters involved. ... They may have an arbitrary number of arbitrary Code nodes as elements. - [form_parser ..close_form #.Form] - [variant_parser ..close_variant #.Variant] - [tuple_parser ..close_tuple #.Tuple] + [form_parser ..close_form .#Form] + [variant_parser ..close_variant .#Variant] + [tuple_parser ..close_tuple .#Tuple] ) (inline: (record_parser parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) (loop [source (: Source [(!forward 1 where) offset source_code]) - stack (: (List [Code Code]) #.End)] + stack (: (List [Code Code]) {.#End})] (case (parse source) - {#.Right [sourceF field]} + {.#Right [sourceF field]} (!letE [sourceFV value] (parse sourceF) - (recur sourceFV {#.Item [field value] stack})) + (recur sourceFV {.#Item [field value] stack})) - {#.Left [source' error]} + {.#Left [source' error]} (if (same? ..close_variant error) - {#.Right [source' - [where {#.Record (list.reversed stack)}]]} - {#.Left [source' error]})))) + {.#Right [source' + [where {.#Record (list.reversed stack)}]]} + {.#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 + {.#None} body g!_ - {#.Left [[where offset source_code] + {.#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])) (case ("lux text index" offset (static ..text_delimiter) source_code) - {#.Some g!end} + {.#Some g!end} (<| (let [g!content (!clip offset g!end source_code)]) (!guarantee_no_new_lines where offset source_code g!content) - {#.Right [[(let [size (!n/- offset g!end)] - (revised@ #.column (|>> (!n/+ size) (!n/+ 2)) where)) + {.#Right [[(let [size (!n/- offset g!end)] + (revised@ .#column (|>> (!n/+ size) (!n/+ 2)) where)) (!++ g!end) source_code] [where - {#.Text g!content}]]}) + {.#Text g!content}]]}) _ (!failure ..text_parser where offset source_code))) @@ -295,8 +295,7 @@ [..open_form] [..close_form] [..open_variant] [..close_variant] [..open_tuple] [..close_tuple] - [..text_delimiter] - [..sigil]) + [..text_delimiter]) <digit_separator> (static ..digit_separator)] (template: (!if_digit? @char @then @else) [("lux syntax char case!" @char @@ -338,23 +337,23 @@ (!clip <start> <end>) (text.replaced ..digit_separator "") (\ <codec> decoded)) - {#.Right output} - {#.Right [[(let [[where::file where::line where::column] where] + {.#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>] + {.#Left error} + {.#Left [[where <start> <source_code>] error]})]) (def: no_exponent Offset 0) -(with_expansions [<int_output> (as_is (!number_output source_code start end int.decimal #.Int)) - <frac_output> (as_is (!number_output source_code start end frac.decimal #.Frac)) +(with_expansions [<int_output> (as_is (!number_output source_code start end int.decimal .#Int)) + <frac_output> (as_is (!number_output source_code start end frac.decimal .#Frac)) <failure> (!failure ..frac_parser where offset source_code) <frac_separator> (static ..frac_separator) <signs> (template [<sign>] @@ -412,8 +411,8 @@ [] (!number_output source_code start g!end <codec> <tag>)))))] - [nat_parser n.decimal #.Nat] - [rev_parser rev.decimal #.Rev] + [nat_parser n.decimal .#Nat] + [rev_parser rev.decimal .#Rev] ) (template: (!signed_parser source_code//size offset where source_code @aliases @end) @@ -421,9 +420,9 @@ (!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 (!++/2 offset) source_code) - (!full_name_parser offset [where (!++ offset) source_code] where @aliases #.Identifier)))]) + (!full_name_parser offset [where (!++ offset) source_code] where @aliases .#Identifier)))]) -(with_expansions [<output> {#.Right [[(revised@ #.column (|>> (!n/+ (!n/- start end))) where) +(with_expansions [<output> {.#Right [[(revised@ .#column (|>> (!n/+ (!n/- start end))) where) end source_code] (!clip start end source_code)]}] @@ -440,7 +439,7 @@ (template: (!half_name_parser @offset @char @module) [(!if_name_char?|head @char (!letE [source' name] (..name_part_parser @offset (!forward 1 where) (!++ @offset) source_code) - {#.Right [source' [@module name]]}) + {.#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]) @@ -456,9 +455,9 @@ (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}]]})]) + {.#Right [source' [@where {@tag name}]]})]) -(with_expansions [<simple> (as_is {#.Right [source' ["" simple]]})] +(with_expansions [<simple> (as_is {.#Right [source' ["" simple]]})] (`` (def: (full_name_parser aliases start source) (-> Aliases Offset (Parser Name)) (<| (!letE [source' simple] (let [[where offset source_code] source] @@ -471,7 +470,7 @@ (if ("lux text =" "" complex) (let [[where offset source_code] source] (!failure ..full_name_parser where offset source_code)) - {#.Right [source'' [(|> aliases + {.#Right [source'' [(|> aliases (dictionary.value simple) (maybe.else simple)) complex]]})) @@ -479,7 +478,7 @@ (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}]]})]) + {.#Right [source' [@where {@tag full_name}]]})]) ... TODO: Grammar macro for specifying syntax. ... (grammar: lux_grammar @@ -492,14 +491,14 @@ <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)) - {#.Right [[(revised@ #.column (|>> !++/2) where) + {.#Right [[(revised@ .#column (|>> !++/2) where) (!++/2 offset/0) source_code] - [where {#.Bit value}]]}) + [where {.#Bit value}]]}) (def: .public (parse current_module aliases source_code//size) (-> Text Aliases Nat (Parser Code)) @@ -536,37 +535,15 @@ [(~~ (static ..text_delimiter))] (text_parser where (!++ offset/0) source_code) - ... Special code - [(~~ (static ..sigil))] - (<| (let [offset/1 (!++ offset/0)]) - (!with_char+ source_code//size source_code offset/1 char/1 - (!end_of_file where offset/1 source_code current_module)) - ("lux syntax char case!" char/1 - [[(~~ (static ..name_separator))] - (!short_name_parser source_code//size current_module <move_2> where #.Tag) - - (~~ (template [<char> <bit>] - [[<char>] - (..bit_syntax <bit> [where offset/0 source_code])] - - ["0" #0] - ["1" #1]))] - - ... else - (!if_name_char?|head char/1 - ... Tag - (!full_name_parser offset/1 <move_2> where aliases #.Tag) - (!failure ..parse where offset/0 source_code)))) - ... Coincidentally (= ..name_separator ..frac_separator) [(~~ (static ..name_separator)) ... (~~ (static ..frac_separator)) ] ... It's either a Rev, an identifier, or a comment. (with_expansions [<rev_parser> (rev_parser source_code//size offset/0 where (!++ offset/1) source_code) - <short_name_parser> (!short_name_parser source_code//size current_module [where offset/1 source_code] where #.Identifier) + <short_name_parser> (!short_name_parser source_code//size current_module [where offset/1 source_code] where .#Identifier) <comment_parser> (case ("lux text index" (!++ offset/1) (static text.new_line) source_code) - {#.Some end} + {.#Some end} (recur (!vertical where end source_code)) _ @@ -596,14 +573,29 @@ [(~~ (static ..positive_sign)) (~~ (static ..negative_sign))] (!signed_parser source_code//size offset/0 where source_code aliases - (!end_of_file where offset/0 source_code current_module))] + (!end_of_file where offset/0 source_code current_module)) + + [(~~ (static ..sigil))] + (<| (let [offset/1 (!++ offset/0)]) + (!with_char+ source_code//size source_code offset/1 char/1 + (!end_of_file where offset/1 source_code current_module)) + ("lux syntax char case!" char/1 + [(~~ (template [<char> <bit>] + [[<char>] + (..bit_syntax <bit> [where offset/0 source_code])] + + ["0" #0] + ["1" #1]))] + + ... else + (!full_name_parser offset/0 [<consume_1>] where aliases .#Identifier)))] ... else (!if_digit? char/0 ... Natural number (nat_parser source_code//size offset/0 where (!++ offset/0) source_code) ... Identifier - (!full_name_parser offset/0 [<consume_1>] where aliases #.Identifier)) + (!full_name_parser offset/0 [<consume_1>] where aliases .#Identifier)) ))) ))) )) 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 e718a2469..ad940f809 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -75,7 +75,7 @@ (type: .public (Path' s) (Variant - #Pop + {#Pop} {#Access Access} {#Bind Register} {#Bit_Fork Bit (Path' s) (Maybe (Path' s))} @@ -151,45 +151,45 @@ (def: .public path/pop Path - #Pop) + {#Pop}) (template [<name> <kind>] [(template: .public (<name> content) - [(.<| #..Access - <kind> + [(.<| {..#Access} + {<kind>} content)])] - [path/side #..Side] - [path/member #..Member] + [path/side ..#Side] + [path/member ..#Member] ) (template [<name> <kind> <side>] [(template: .public (<name> content) - [(.<| {#..Access} + [(.<| {..#Access} {<kind>} {<side>} content)])] - [side/left #..Side #.Left] - [side/right #..Side #.Right] - [member/left #..Member #.Left] - [member/right #..Member #.Right] + [side/left ..#Side .#Left] + [side/right ..#Side .#Right] + [member/left ..#Member .#Left] + [member/right ..#Member .#Right] ) (template [<name> <tag>] [(template: .public (<name> content) [{<tag> content}])] - [path/bind #..Bind] - [path/then #..Then] + [path/bind ..#Bind] + [path/then ..#Then] ) (template [<name> <tag>] [(template: .public (<name> left right) [{<tag> left right}])] - [path/alt #..Alt] - [path/seq #..Seq] + [path/alt ..#Alt] + [path/seq ..#Seq] ) (type: .public Abstraction @@ -223,27 +223,27 @@ (template [<name> <tag>] [(template: .public (<name> content) - [{#..Primitive {<tag> content}}])] + [{..#Primitive {<tag> content}}])] - [bit #..Bit] - [i64 #..I64] - [f64 #..F64] - [text #..Text] + [bit ..#Bit] + [i64 ..#I64] + [f64 ..#F64] + [text ..#Text] ) (template [<name> <tag>] [(template: .public (<name> content) - [(<| {#..Structure} + [(<| {..#Structure} {<tag>} content)])] - [variant #analysis.Variant] - [tuple #analysis.Tuple] + [variant analysis.#Variant] + [tuple analysis.#Tuple] ) (template [<name> <tag>] [(template: .public (<name> content) - [(.<| {#..Reference} + [(.<| {..#Reference} <tag> content)])] @@ -255,43 +255,43 @@ (template [<name> <family> <tag>] [(template: .public (<name> content) - [(.<| {#..Control} + [(.<| {..#Control} {<family>} {<tag>} content)])] - [branch/case #..Branch #..Case] - [branch/let #..Branch #..Let] - [branch/if #..Branch #..If] - [branch/get #..Branch #..Get] + [branch/case ..#Branch ..#Case] + [branch/let ..#Branch ..#Let] + [branch/if ..#Branch ..#If] + [branch/get ..#Branch ..#Get] - [loop/recur #..Loop #..Recur] - [loop/scope #..Loop #..Scope] + [loop/recur ..#Loop ..#Recur] + [loop/scope ..#Loop ..#Scope] - [function/abstraction #..Function #..Abstraction] - [function/apply #..Function #..Apply] + [function/abstraction ..#Function ..#Abstraction] + [function/apply ..#Function ..#Apply] ) (def: .public (%path' %then value) (All (_ a) (-> (Format a) (Format (Path' a)))) (case value - #Pop + {#Pop} "_" {#Bit_Fork when then else} (format "(?" " " (%.bit when) " " (%path' %then then) (case else - {#.Some else} + {.#Some else} (format " " (%.bit (not when)) " " (%path' %then else)) - #.None + {.#None} "") ")") (^template [<tag> <format>] [{<tag> item} - (|> {#.Item item} + (|> {.#Item item} (list\each (function (_ [test then]) (format (<format> test) " " (%path' %then then)))) (text.interposed " ") @@ -304,18 +304,18 @@ (case access {#Side side} (case side - {#.Left lefts} + {.#Left lefts} (format "(" (%.nat lefts) " #0" ")") - {#.Right lefts} + {.#Right lefts} (format "(" (%.nat lefts) " #1" ")")) {#Member member} (case member - {#.Left lefts} + {.#Left lefts} (format "[" (%.nat lefts) " #0" "]") - {#.Right lefts} + {.#Right lefts} (format "[" (%.nat lefts) " #1" "]"))) {#Bind register} @@ -348,12 +348,12 @@ {#Structure structure} (case structure - {#analysis.Variant [lefts right? content]} + {analysis.#Variant [lefts right? content]} (|> (%synthesis content) (format (%.nat lefts) " " (%.bit right?) " ") (text.enclosed ["{" "}"])) - {#analysis.Tuple members} + {analysis.#Tuple members} (|> members (list\each %synthesis) (text.interposed " ") @@ -393,7 +393,7 @@ {#Get members record} (|> (format (%.list (%path' %synthesis) - (list\each (|>> #Member #Access) members)) + (list\each (|>> {#Member} {#Access}) members)) " " (%synthesis record)) (text.enclosed ["{#get " "}"])) @@ -505,7 +505,7 @@ (def: (= reference sample) (case [reference sample] - [#Pop #Pop] + [{#Pop} {#Pop}] true [{#Bit_Fork reference_when reference_then reference_else} @@ -518,8 +518,8 @@ [[{<tag> reference_item} {<tag> sample_item}] (\ (list.equivalence (product.equivalence <equivalence> =)) = - {#.Item reference_item} - {#.Item sample_item})]) + {.#Item reference_item} + {.#Item sample_item})]) ([#I64_Fork i64.equivalence] [#F64_Fork f.equivalence] [#Text_Fork text.equivalence]) @@ -551,7 +551,7 @@ (def: (hash value) (case value - #Pop + {#Pop} 2 {#Access access} @@ -795,14 +795,14 @@ (template: .public (!bind_top register thenP) [($_ ..path/seq - {#..Bind register} - {#..Pop} + {..#Bind register} + {..#Pop} thenP)]) (template: .public (!multi_pop nextP) [($_ ..path/seq - {#..Pop} - {#..Pop} + {..#Pop} + {..#Pop} nextP)]) ... TODO: There are sister patterns to the simple side checks for tuples. @@ -816,7 +816,7 @@ [(template: .public (<name> idx nextP) [($_ ..path/seq (<side> idx) - #..Pop + ..#Pop nextP)])] [simple_left_side ..side/left] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index 0f1f5ef2c..2c5b688a2 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -90,70 +90,70 @@ (def: .public (id module archive) (-> Module Archive (Try ID)) - (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.value module resolver) - {#.Some [id _]} - {#try.Success id} + (let [(^slots [..#resolver]) (:representation archive)] + (case (dictionary.value module #resolver) + {.#Some [id _]} + {try.#Success id} - #.None + {.#None} (exception.except ..unknown_document [module - (dictionary.keys resolver)])))) + (dictionary.keys #resolver)])))) (def: .public (reserve module archive) (-> Module Archive (Try [ID Archive])) - (let [(^slots [#..next #..resolver]) (:representation archive)] - (case (dictionary.value module resolver) - {#.Some _} + (let [(^open "_[0]") (:representation archive)] + (case (dictionary.value module _#resolver) + {.#Some _} (exception.except ..module_has_already_been_reserved [module]) - #.None - {#try.Success [next + {.#None} + {try.#Success [_#next (|> archive :representation - (revised@ #..resolver (dictionary.has module [next #.None])) - (revised@ #..next ++) + (revised@ #resolver (dictionary.has module [_#next {.#None}])) + (revised@ #next ++) :abstraction)]}))) (def: .public (has module [descriptor document output] archive) (-> Module [Descriptor (Document Any) Output] Archive (Try Archive)) - (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.value module resolver) - {#.Some [id #.None]} - {#try.Success (|> archive + (let [(^slots [..#resolver]) (:representation archive)] + (case (dictionary.value module #resolver) + {.#Some [id {.#None}]} + {try.#Success (|> archive :representation - (revised@ #..resolver (dictionary.has module [id {#.Some [descriptor document output]}])) + (revised@ ..#resolver (dictionary.has module [id {.#Some [descriptor document output]}])) :abstraction)} - {#.Some [id {#.Some [existing_descriptor existing_document existing_output]}]} + {.#Some [id {.#Some [existing_descriptor existing_document existing_output]}]} (if (same? document existing_document) ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy... - {#try.Success archive} + {try.#Success archive} (exception.except ..cannot_replace_document [module existing_document document])) - #.None + {.#None} (exception.except ..module_must_be_reserved_before_it_can_be_added [module])))) (def: .public (find module archive) (-> Module Archive (Try [Descriptor (Document Any) Output])) - (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.value module resolver) - {#.Some [id {#.Some entry}]} - {#try.Success entry} + (let [(^slots [..#resolver]) (:representation archive)] + (case (dictionary.value module #resolver) + {.#Some [id {.#Some entry}]} + {try.#Success entry} - {#.Some [id #.None]} + {.#Some [id {.#None}]} (exception.except ..module_is_only_reserved [module]) - #.None + {.#None} (exception.except ..unknown_document [module - (dictionary.keys resolver)])))) + (dictionary.keys #resolver)])))) (def: .public (archived? archive module) (-> Archive Module Bit) (case (..find module archive) - {#try.Success _} + {try.#Success _} bit.yes - {#try.Failure _} + {try.#Failure _} bit.no)) (def: .public archived @@ -163,17 +163,17 @@ dictionary.entries (list.all (function (_ [module [id descriptor+document]]) (case descriptor+document - {#.Some _} {#.Some module} - #.None #.None))))) + {.#Some _} {.#Some module} + {.#None} {.#None}))))) (def: .public (reserved? archive module) (-> Archive Module Bit) - (let [(^slots [#..resolver]) (:representation archive)] - (case (dictionary.value module resolver) - {#.Some [id _]} + (let [(^slots [..#resolver]) (:representation archive)] + (case (dictionary.value module #resolver) + {.#Some [id _]} bit.yes - #.None + {.#None} bit.no))) (def: .public reserved @@ -199,10 +199,10 @@ (revised@ #resolver (function (_ resolver) (list\mix (function (_ [module [id entry]] resolver) (case entry - {#.Some _} + {.#Some _} (dictionary.has module [id entry] resolver) - #.None + {.#None} resolver)) resolver (dictionary.entries +resolver)))) @@ -230,14 +230,14 @@ (def: .public (export version archive) (-> Version Archive Binary) - (let [(^slots [#..next #..resolver]) (:representation archive)] - (|> resolver + (let [(^slots [..#next ..#resolver]) (:representation archive)] + (|> #resolver dictionary.entries (list.all (function (_ [module [id descriptor+document]]) (case descriptor+document - {#.Some _} {#.Some [module id]} - #.None #.None))) - [version next] + {.#Some _} {.#Some [module id]} + {.#None} {.#None}))) + [version #next] (binary.result ..writer)))) (exception: .public (version_mismatch [expected Version @@ -280,7 +280,7 @@ (in (:abstraction [#next next #resolver (list\mix (function (_ [module id] archive) - (dictionary.has module [id #.None] archive)) + (dictionary.has module [id {.#None}] archive)) (value@ #resolver (:representation ..empty)) reservations)])))) ) 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 75753c473..9681197b8 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -26,7 +26,7 @@ (type: .public Category (Variant - #Anonymous + {#Anonymous} {#Definition Text} {#Analyser Text} {#Synthesizer Text} @@ -64,7 +64,7 @@ (|> registry :representation (revised@ #artifacts (row.suffix [#id id - #category #Anonymous])) + #category {#Anonymous}])) :abstraction)])) (template [<tag> <create> <fetch>] @@ -86,8 +86,8 @@ (value@ #artifacts) row.list (list.all (|>> (value@ #category) - (case> {<tag> name} {#.Some name} - _ #.None)))))] + (case> {<tag> name} {.#Some name} + _ {.#None})))))] [#Definition definition definitions] [#Analyser analyser analysers] @@ -109,7 +109,8 @@ (function (_ value) (case value (^template [<nat> <tag> <writer>] - [{<tag> value} ((binary.and binary.nat <writer>) [<nat> value])]) + [{<tag> value} + ((binary.and binary.nat <writer>) [<nat> value])]) ([0 #Anonymous binary.any] [1 #Definition binary.text] [2 #Analyser binary.text] @@ -135,7 +136,8 @@ [tag <binary>.nat] (case tag (^template [<nat> <tag> <parser>] - [<nat> (\ ! each (|>> {<tag>}) <parser>)]) + [<nat> + (\ ! each (|>> {<tag>}) <parser>)]) ([0 #Anonymous <binary>.any] [1 #Definition <binary>.text] [2 #Analyser <binary>.text] @@ -149,7 +151,7 @@ (\ <>.monad each (row\mix (function (_ artifact registry) (product.right (case artifact - #Anonymous + {#Anonymous} (..resource registry) (^template [<tag> <create>] 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 e45c69fa2..f1f68d434 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/descriptor.lux @@ -44,7 +44,7 @@ <b>.text <b>.text <b>.nat - (\ <>.monad in #.Cached) + (\ <>.monad in {.#Cached}) (<b>.set text.hash <b>.text) artifact.parser )) 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 d007967f2..3207e7b8f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -37,7 +37,7 @@ (if (\ signature.equivalence = (key.signature key) document//signature) - {#try.Success (:sharing [e] + {try.#Success (:sharing [e] (Key e) key 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 f586c398a..a7acc969b 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency.lux @@ -57,10 +57,10 @@ (function (_ recur module) (do [! state.monad] [.let [parents (case (archive.find module archive) - {#try.Success [descriptor document]} - (value@ #descriptor.references descriptor) + {try.#Success [descriptor document]} + (value@ descriptor.#references descriptor) - {#try.Failure error} + {try.#Failure error} ..fresh)] ancestors (monad.each ! recur (set.list parents))] (in (list\mix set.union parents ancestors))))) 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 fe1e8d223..a41580fd6 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -61,9 +61,9 @@ (def: (archive fs static) (All (_ !) (-> (file.System !) Static file.Path)) - (format (value@ #static.target static) + (format (value@ static.#target static) (\ fs separator) - (value@ #static.host static))) + (value@ static.#host static))) (def: (unversioned_lux_archive fs static) (All (_ !) (-> (file.System !) Static file.Path)) @@ -88,14 +88,14 @@ (format (..module fs static module_id) (\ fs separator) (%.nat artifact_id) - (value@ #static.artifact_extension static))) + (value@ static.#artifact_extension static))) (def: (ensure_directory fs path) (-> (file.System Async) file.Path (Async (Try Any))) (do async.monad [? (\ fs directory? path)] (if ? - (in {#try.Success []}) + (in {try.#Success []}) (\ fs make_directory path)))) (def: .public (prepare fs static module_id) @@ -104,16 +104,16 @@ [.let [module (..module fs static module_id)] module_exists? (\ fs directory? module)] (if module_exists? - (in {#try.Success []}) + (in {try.#Success []}) (do (try.with !) [_ (ensure_directory fs (..unversioned_lux_archive fs static)) _ (ensure_directory fs (..versioned_lux_archive fs static))] (|> module (\ fs make_directory) - (\ ! each (|>> (case> {#try.Success output} - {#try.Success []} + (\ ! each (|>> (case> {try.#Success output} + {try.#Success []} - {#try.Failure error} + {try.#Failure error} (exception.except ..cannot_prepare [(..archive fs static) module_id error]))))))))) @@ -125,7 +125,7 @@ (def: .public (enable fs static) (-> (file.System Async) Static (Async (Try Any))) (do (try.with async.monad) - [_ (..ensure_directory fs (value@ #static.target static))] + [_ (..ensure_directory fs (value@ static.#target static))] (..ensure_directory fs (..archive fs static)))) (def: (general_descriptor fs static) @@ -174,7 +174,7 @@ content (document.read $.key document)] (in [module content]))) (archive.archived archive)))] - (in (with@ #.modules modules (fresh_analysis_state host))))) + (in (with@ .#modules modules (fresh_analysis_state host))))) (def: (cached_artifacts fs static module_id) (-> (file.System Async) Static archive.ID (Async (Try (Dictionary Text Binary)))) @@ -223,16 +223,16 @@ output (: Output row.empty)] (let [[analysers synthesizers generators directives] bundles] (case input - {#.Item [[artifact_id artifact_category] input']} + {.#Item [[artifact_id artifact_category] input']} (case (do ! [data (try.of_maybe (dictionary.value (format (%.nat artifact_id) extension) actual)) .let [context [module_id artifact_id] directive (\ host ingest context data)]] (case artifact_category - #artifact.Anonymous + {artifact.#Anonymous} (do ! - [.let [output (row.suffix [artifact_id #.None data] output)] - _ (\ host re_learn context #.None directive)] + [.let [output (row.suffix [artifact_id .#None data] output)] + _ (\ host re_learn context {.#None} directive)] (in [definitions [analysers synthesizers @@ -240,8 +240,8 @@ directives] output])) - {#artifact.Definition name} - (let [output (row.suffix [artifact_id #.None data] output)] + {artifact.#Definition name} + (let [output (row.suffix [artifact_id {.#None} data] output)] (if (text\= $/program.name name) (in [definitions [analysers @@ -250,7 +250,7 @@ directives] output]) (do ! - [value (\ host re_load context #.None directive)] + [value (\ host re_load context {.#None} directive)] (in [(dictionary.has name value definitions) [analysers synthesizers @@ -258,10 +258,10 @@ directives] output])))) - {#artifact.Analyser extension} + {artifact.#Analyser extension} (do ! - [.let [output (row.suffix [artifact_id #.None data] output)] - value (\ host re_load context #.None directive)] + [.let [output (row.suffix [artifact_id {.#None} data] output)] + value (\ host re_load context {.#None} directive)] (in [definitions [(dictionary.has extension (:as analysis.Handler value) analysers) synthesizers @@ -269,10 +269,10 @@ directives] output])) - {#artifact.Synthesizer extension} + {artifact.#Synthesizer extension} (do ! - [.let [output (row.suffix [artifact_id #.None data] output)] - value (\ host re_load context #.None directive)] + [.let [output (row.suffix [artifact_id {.#None} data] output)] + value (\ host re_load context {.#None} directive)] (in [definitions [analysers (dictionary.has extension (:as synthesis.Handler value) synthesizers) @@ -280,10 +280,10 @@ directives] output])) - {#artifact.Generator extension} + {artifact.#Generator extension} (do ! - [.let [output (row.suffix [artifact_id #.None data] output)] - value (\ host re_load context #.None directive)] + [.let [output (row.suffix [artifact_id {.#None} data] output)] + value (\ host re_load context {.#None} directive)] (in [definitions [analysers synthesizers @@ -291,10 +291,10 @@ directives] output])) - {#artifact.Directive extension} + {artifact.#Directive extension} (do ! - [.let [output (row.suffix [artifact_id #.None data] output)] - value (\ host re_load context #.None directive)] + [.let [output (row.suffix [artifact_id {.#None} data] output)] + value (\ host re_load context {.#None} directive)] (in [definitions [analysers synthesizers @@ -302,50 +302,50 @@ (dictionary.has extension (:as directive.Handler value) directives)] output])) - {#artifact.Custom name} + {artifact.#Custom name} (do ! - [.let [output (row.suffix [artifact_id {#.Some name} data] output)] - _ (\ host re_learn context {#.Some name} directive)] + [.let [output (row.suffix [artifact_id {.#Some name} data] output)] + _ (\ host re_learn context {.#Some name} directive)] (in [definitions [analysers synthesizers generators directives] output])))) - {#try.Success [definitions' bundles' output']} + {try.#Success [definitions' bundles' output']} (recur input' definitions' bundles' output') failure failure) - #.End - {#try.Success [definitions bundles output]})))) + {.#End} + {try.#Success [definitions bundles output]})))) content (document.read $.key document) definitions (monad.each ! (function (_ [def_name def_global]) (case def_global (^template [<tag>] [{<tag> payload} (in [def_name {<tag> payload}])]) - ([#.Alias] - [#.Label] - [#.Slot]) + ([.#Alias] + [.#Label] + [.#Slot]) - {#.Definition [exported? type _]} + {.#Definition [exported? type _]} (|> definitions (dictionary.value def_name) try.of_maybe (\ ! each (|>> [exported? type] - {#.Definition} + {.#Definition} [def_name]))) - {#.Type [exported? _ labels]} + {.#Type [exported? _ labels]} (|> definitions (dictionary.value def_name) try.of_maybe (\ ! each (function (_ def_value) - [def_name {#.Type [exported? (:as .Type def_value) labels]}]))))) - (value@ #.definitions content))] - (in [(document.write $.key (with@ #.definitions definitions content)) + [def_name {.#Type [exported? (:as .Type def_value) labels]}]))))) + (value@ .#definitions content))] + (in [(document.write $.key (with@ .#definitions definitions content)) bundles]))) (def: (load_definitions fs static module_id host_environment descriptor document) @@ -356,8 +356,8 @@ Bundles])))) (do (try.with async.monad) [actual (cached_artifacts fs static module_id) - .let [expected (|> descriptor (value@ #descriptor.registry) artifact.artifacts)] - [document bundles output] (async\in (loaded_document (value@ #static.artifact_extension static) host_environment module_id expected actual document))] + .let [expected (|> descriptor (value@ descriptor.#registry) artifact.artifacts)] + [document bundles output] (async\in (loaded_document (value@ static.#artifact_extension static) host_environment module_id expected actual document))] (in [[descriptor document output] bundles]))) (def: (purge! fs static [module_name module_id]) @@ -372,12 +372,12 @@ (def: (valid_cache? expected actual) (-> Descriptor Input Bit) - (and (text\= (value@ #descriptor.name expected) - (value@ #////.module actual)) - (text\= (value@ #descriptor.file expected) - (value@ #////.file actual)) - (n.= (value@ #descriptor.hash expected) - (value@ #////.hash actual)))) + (and (text\= (value@ descriptor.#name expected) + (value@ ////.#module actual)) + (text\= (value@ descriptor.#file expected) + (value@ ////.#file actual)) + (n.= (value@ descriptor.#hash expected) + (value@ ////.#hash actual)))) (type: Purge (Dictionary Module archive.ID)) @@ -387,8 +387,8 @@ Purge) (|>> (list.all (function (_ [valid_cache? [module_name [module_id _]]]) (if valid_cache? - #.None - {#.Some [module_name module_id]}))) + {.#None} + {.#Some [module_name module_id]}))) (dictionary.of_list text.hash))) (def: (full_purge caches load_order) @@ -401,7 +401,7 @@ (if (purged? module_name) purge (if (|> descriptor - (value@ #descriptor.references) + (value@ descriptor.#references) set.list (list.any? purged?)) (dictionary.has module_name module_id purge) @@ -428,7 +428,7 @@ (in [true [module_name [module_id [descriptor document]]]]) (do ! - [input (//context.read fs ..pseudo_module import contexts (value@ #static.host_module_extension static) module_name)] + [input (//context.read fs ..pseudo_module import contexts (value@ static.#host_module_extension static) module_name)] (in [(..valid_cache? descriptor input) [module_name [module_id [descriptor document]]]]))))))) load_order (|> pre_loaded_caches @@ -458,7 +458,7 @@ (archive.has module descriptor,document,output archive)) archive loaded_caches) - analysis_state (..analysis_state (value@ #static.host static) archive)] + analysis_state (..analysis_state (value@ static.#host static) archive)] (in [archive analysis_state (list\mix (function (_ [_ [+analysers +synthesizers +generators +directives]] @@ -477,12 +477,12 @@ (do async.monad [binary (\ fs read (..general_descriptor fs static))] (case binary - {#try.Success binary} + {try.#Success binary} (do (try.with async.monad) [archive (async\in (archive.import ///.version binary))] (..load_every_reserved_module host_environment fs static import contexts archive)) - {#try.Failure error} - (in {#try.Success [archive.empty - (fresh_analysis_state (value@ #static.host static)) + {try.#Failure error} + (in {try.#Success [archive.empty + (fresh_analysis_state (value@ static.#host static)) ..empty_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 69a0858e6..59d06a9fd 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -58,15 +58,15 @@ (-> (file.System Async) Module (List Context) Module Extension (Async (Try file.Path))) (case contexts - #.End + {.#End} (async\in (exception.except ..cannot_find_module [importer module])) - {#.Item context contexts'} + {.#Item context contexts'} (let [path (format (..path fs context module) extension)] (do async.monad [? (\ fs file? path)] (if ? - (in {#try.Success path}) + (in {try.#Success path}) (find_source_file fs importer contexts' module extension)))))) (def: (full_host_extension partial_host_extension) @@ -81,12 +81,12 @@ (do [! async.monad] [outcome (..find_source_file fs importer contexts module (..full_host_extension partial_host_extension))] (case outcome - {#try.Success path} + {try.#Success path} (|> path (\ fs read) (\ (try.with !) each (|>> [path]))) - {#try.Failure _} + {try.#Failure _} (do [! (try.with !)] [path (..find_source_file fs importer contexts module ..lux_extension)] (|> path @@ -97,16 +97,16 @@ (-> Module Import Extension Module (Try [file.Path Binary])) (let [path (format module (..full_host_extension partial_host_extension))] (case (dictionary.value path import) - {#.Some data} - {#try.Success [path data]} + {.#Some data} + {try.#Success [path data]} - #.None + {.#None} (let [path (format module ..lux_extension)] (case (dictionary.value path import) - {#.Some data} - {#try.Success [path data]} + {.#Some data} + {try.#Success [path data]} - #.None + {.#None} (exception.except ..cannot_find_module [importer module])))))) (def: (find_any_source_file fs importer import contexts partial_host_extension module) @@ -117,10 +117,10 @@ (do [! async.monad] [outcome (find_local_source_file fs importer import contexts partial_host_extension module)] (case outcome - {#try.Success [path data]} + {try.#Success [path data]} (in outcome) - {#try.Failure _} + {try.#Failure _} (in (..find_library_source_file importer import partial_host_extension module))))) (def: .public (read fs importer import contexts partial_host_extension module) @@ -129,13 +129,13 @@ (do (try.with async.monad) [[path binary] (..find_any_source_file fs importer import contexts partial_host_extension module)] (case (\ utf8.codec decoded binary) - {#try.Success code} - (in [#////.module module - #////.file path - #////.hash (text\hash code) - #////.code code]) + {try.#Success code} + (in [////.#module module + ////.#file path + ////.#hash (text\hash code) + ////.#code code]) - {#try.Failure _} + {try.#Failure _} (async\in (exception.except ..cannot_read_module [module]))))) (type: .public Enumeration diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager.lux b/stdlib/source/library/lux/tool/compiler/meta/packager.lux index e9224a8d0..73d919175 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager.lux @@ -35,8 +35,8 @@ (-> dependency.Order Order) (list\each (function (_ [module [module_id [descriptor document]]]) (|> descriptor - (value@ #descriptor.registry) + (value@ descriptor.#registry) artifact.artifacts row.list - (list\each (|>> (value@ #artifact.id))) + (list\each (|>> (value@ artifact.#id))) [module_id])))) 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 75eca1c30..9faeb3b47 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -143,7 +143,7 @@ (let [class_path (|> custom (maybe\each (|>> name.internal name.read)) (maybe.else (runtime.class_name [module artifact])) - (text.suffix (value@ #static.artifact_extension static)))] + (text.suffix (value@ static.#artifact_extension static)))] (do try.monad [_ (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new class_path) sink)] (in (do_to sink @@ -208,29 +208,29 @@ duplicates duplicates sink sink] (case (java/util/jar/JarInputStream::getNextJarEntry input) - {#try.Failure error} - {#try.Failure error} + {try.#Failure error} + {try.#Failure error} - {#try.Success ?entry} + {try.#Success ?entry} (case ?entry - #.None + {.#None} (exec (java/io/Closeable::close input) - {#try.Success [entries duplicates sink]}) + {try.#Success [entries duplicates sink]}) - {#.Some entry} + {.#Some entry} (let [entry_path (java/util/zip/ZipEntry::getName entry) entry_size (java/util/zip/ZipEntry::getSize entry)] (if (not (or (java/util/zip/ZipEntry::isDirectory entry) (text.starts_with? "META-INF/maven/" entry_path) (text.starts_with? "META-INF/leiningen/" entry_path))) (case (java/util/jar/JarOutputStream::putNextEntry (java/util/jar/JarEntry::new entry_path) sink) - {#try.Failure error} + {try.#Failure error} (recur entries (set.has entry_path duplicates) sink) - {#try.Success _} + {try.#Success _} (let [[entry_size entry_data] (read_jar_entry entry input)] (recur (set.has entry_path entries) duplicates 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 c78d07b6f..b5d364a3d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -88,12 +88,12 @@ (def: owner tar.Owner - [#tar.name tar.anonymous - #tar.id tar.no_id]) + [tar.#name tar.anonymous + tar.#id tar.no_id]) (def: ownership - [#tar.user ..owner - #tar.group ..owner]) + [tar.#user ..owner + tar.#group ..owner]) (def: (write_module now mapping [module [module_id [descriptor document output]]]) (-> Instant (Dictionary Module archive.ID) @@ -104,7 +104,7 @@ (..bundle_module output)) entry_content (: (Try tar.Content) (|> descriptor - (value@ #descriptor.references) + (value@ descriptor.#references) set.list (list.all (function (_ module) (dictionary.value module mapping))) (list\each (|>> ..module_file _.string _.load_relative/1)) @@ -114,7 +114,7 @@ (\ encoding.utf8 encoded) tar.content)) module_file (tar.path (..module_file module_id))] - (in {#tar.Normal [module_file now ..mode ..ownership entry_content]}))) + (in {tar.#Normal [module_file now ..mode ..ownership entry_content]}))) (def: .public (package now) (-> Instant Packager) diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index 4809e8ed9..a54785eed 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -53,13 +53,13 @@ (All (_ s o) (Operation s s)) (function (_ state) - {#try.Success [state state]})) + {try.#Success [state state]})) (def: .public (set_state state) (All (_ s o) (-> s (Operation s Any))) (function (_ _) - {#try.Success [state []]})) + {try.#Success [state []]})) (def: .public (sub [get set] operation) (All (_ s s' o) @@ -73,7 +73,7 @@ (def: .public failure (-> Text Operation) - (|>> #try.Failure (state.lifted try.monad))) + (|>> {try.#Failure} (state.lifted try.monad))) (def: .public (except exception parameters) (All (_ e) (-> (Exception e) e Operation)) @@ -94,7 +94,7 @@ (def: .public identity (All (_ s a) (Phase s a a)) (function (_ archive input state) - {#try.Success [state input]})) + {try.#Success [state input]})) (def: .public (composite pre post) (All (_ s0 s1 i t o) diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 0f345a12f..e61fc7b99 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -48,20 +48,21 @@ (case value (^template [<factor> <tag> <hash>] [{<tag> value} - ($_ n.* <factor> - (\ <hash> hash value))]) + (|> value + (\ <hash> hash) + (n.* <factor>))]) ([2 #Variable /variable.hash] [3 #Constant name.hash]) ))) (template [<name> <family> <tag>] [(template: .public (<name> content) - [(<| <family> + [(<| {<family>} {<tag>} content)])] - [local #..Variable #/variable.Local] - [foreign #..Variable #/variable.Foreign] + [local ..#Variable /variable.#Local] + [foreign ..#Variable /variable.#Foreign] ) (template [<name> <tag>] @@ -69,8 +70,8 @@ [(<| {<tag>} content)])] - [variable #..Variable] - [constant #..Constant] + [variable ..#Variable] + [constant ..#Constant] ) (def: .public self diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index bde1de15b..e3c5ce5c2 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -44,13 +44,14 @@ (def: hash (|>> (case> (^template [<factor> <tag>] [{<tag> register} - ($_ n.* <factor> - (\ n.hash hash register))]) + (|> register + (\ n.hash hash) + (n.* <factor>))]) ([2 #Local] [3 #Foreign]))))) (template: .public (self) - [{#..Local 0}]) + [{..#Local 0}]) (def: .public self? (-> Variable Bit) |