diff options
author | Eduardo Julian | 2021-09-10 01:21:23 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-09-10 01:21:23 -0400 |
commit | cd71a864ad5be13ed6ec6d046e0a2cb1087bdf94 (patch) | |
tree | af6366578f98f1a8e551f4da9f3ad230fd63a4dd /stdlib/source/library/lux/tool/compiler | |
parent | ef77466323f85a3d1b65b46a3deb93652ef22085 (diff) |
Migrated variants to the new syntax.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
109 files changed, 1634 insertions, 1614 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 35759ca87..a43b9a4d9 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -94,22 +94,22 @@ (def: (reader current_module aliases [location offset source_code]) (-> Module Aliases Source (///analysis.Operation Reader)) (function (_ [bundle state]) - (#try.Success [[bundle state] - (///syntax.parse current_module aliases ("lux text size" source_code))]))) + {#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 + {#try.Success [[bundle (|> compiler (with@ #.source source') (with@ #.location location))] - [source' output]]))))) + [source' output]]})))) (type: (Operation a) (All (_ anchor expression directive) @@ -209,13 +209,13 @@ (..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)) @@ -257,16 +257,16 @@ #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)])])) + final_buffer)]}])) - (#.Some [source requirements temporary_payload]) + {#.Some [source requirements temporary_payload]} (let [[temporary_buffer temporary_registry] temporary_payload] (in [state - (#.Left [#///.dependencies (|> requirements + {#.Left [#///.dependencies (|> requirements (value@ #///directive.imports) (list\each product.left)) #///.process (function (_ state archive) @@ -284,5 +284,5 @@ (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))))))])])) + (..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 d24ad8f33..f884282eb 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -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,20 +423,20 @@ [[_ dependence] (stm.update (..depend importer module) dependence)] (in dependence)))] (case (..verify_dependencies importer module dependence) - (#try.Failure error) - (in [(async.resolved (#try.Failure error)) + {#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])) + (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]) @@ -446,7 +446,7 @@ [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])])) + signal]}])) - (#try.Failure error) - (in [(async\in (#try.Failure error)) + {#try.Failure error} + (in [(async\in {#try.Failure error}) #.None]))))))))))) _ (case signal #.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))))) @@ -579,7 +579,7 @@ #.End (in [archive state]) - (#.Item _) + {#.Item _} (do ! [archive,document+ (|> new_dependencies (list\each (import! 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)] _ (..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/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 35c150116..fb9566948 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -38,12 +38,12 @@ (type: .public Primitive (.Variant #Unit - (#Bit Bit) - (#Nat Nat) - (#Int Int) - (#Rev Rev) - (#Frac Frac) - (#Text Text))) + {#Bit Bit} + {#Nat Nat} + {#Int Int} + {#Rev Rev} + {#Frac Frac} + {#Text Text})) (type: .public Tag Nat) @@ -77,15 +77,15 @@ (type: .public (Composite a) (.Variant - (#Variant (Variant a)) - (#Tuple (Tuple a)))) + {#Variant (Variant a)} + {#Tuple (Tuple a)})) (type: .public Pattern (Rec Pattern (.Variant - (#Simple Primitive) - (#Complex (Composite Pattern)) - (#Bind Register)))) + {#Simple Primitive} + {#Complex (Composite Pattern)} + {#Bind Register}))) (type: .public (Branch' e) (Record @@ -101,13 +101,13 @@ (type: .public Analysis (Rec Analysis (.Variant - (#Primitive Primitive) - (#Structure (Composite Analysis)) - (#Reference Reference) - (#Case Analysis (Match' Analysis)) - (#Function (Environment Analysis) Analysis) - (#Apply Analysis Analysis) - (#Extension (Extension Analysis))))) + {#Primitive Primitive} + {#Structure (Composite Analysis)} + {#Reference Reference} + {#Case Analysis (Match' Analysis)} + {#Function (Environment Analysis) Analysis} + {#Apply Analysis Analysis} + {#Extension (Extension Analysis)}))) (type: .public Branch (Branch' Analysis)) @@ -124,7 +124,7 @@ true (^template [<tag> <=>] - [[(<tag> reference) (<tag> sample)] + [[{<tag> reference} {<tag> sample}] (<=> reference sample)]) ([#Bit bit\=] [#Nat n.=] @@ -141,13 +141,13 @@ (def: (= reference sample) (case [reference sample] - [(#Variant [reference_lefts reference_right? reference_value]) - (#Variant [sample_lefts sample_right? sample_value])] + [{#Variant [reference_lefts reference_right? reference_value]} + {#Variant [sample_lefts sample_right? sample_value]}] (and (n.= reference_lefts sample_lefts) (bit\= reference_right? sample_right?) (/\= reference_value sample_value)) - [(#Tuple reference) (#Tuple sample)] + [{#Tuple reference} {#Tuple sample}] (\ (list.equivalence /\=) = reference sample) _ @@ -161,13 +161,13 @@ (def: (hash value) (case value - (#Variant [lefts right? value]) + {#Variant [lefts right? value]} ($_ n.* 2 (\ n.hash hash lefts) (\ bit.hash hash right?) (\ super hash value)) - (#Tuple members) + {#Tuple members} ($_ n.* 3 (\ (list.hash super) hash members)) ))) @@ -177,13 +177,13 @@ (def: (= reference sample) (case [reference sample] - [(#Simple reference) (#Simple sample)] + [{#Simple reference} {#Simple sample}] (\ primitive_equivalence = reference sample) - [(#Complex reference) (#Complex sample)] + [{#Complex reference} {#Complex sample}] (\ (composite_equivalence =) = reference sample) - [(#Bind reference) (#Bind sample)] + [{#Bind reference} {#Bind sample}] (n.= reference sample) _ @@ -201,31 +201,31 @@ (def: (= reference sample) (case [reference sample] - [(#Primitive reference) (#Primitive sample)] + [{#Primitive reference} {#Primitive sample}] (\ primitive_equivalence = reference sample) - [(#Structure reference) (#Structure sample)] + [{#Structure reference} {#Structure sample}] (\ (composite_equivalence =) = reference sample) - [(#Reference reference) (#Reference sample)] + [{#Reference reference} {#Reference sample}] (\ reference.equivalence = reference sample) - [(#Case [reference_analysis reference_match]) - (#Case [sample_analysis sample_match])] + [{#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])] + [{#Function [reference_environment reference_analysis]} + {#Function [sample_environment sample_analysis]}] (and (= reference_analysis sample_analysis) (\ (list.equivalence =) = reference_environment sample_environment)) - [(#Apply [reference_input reference_abstraction]) - (#Apply [sample_input sample_abstraction])] + [{#Apply [reference_input reference_abstraction]} + {#Apply [sample_input sample_abstraction]}] (and (= reference_input sample_input) (= reference_abstraction sample_abstraction)) - [(#Extension reference) (#Extension sample)] + [{#Extension reference} {#Extension sample}] (\ (extension.equivalence =) = reference sample) _ @@ -239,11 +239,11 @@ ) (template: .public (unit) - [(#..Primitive #..Unit)]) + [{#..Primitive #..Unit}]) (template [<name> <tag>] [(template: .public (<name> value) - [(#..Primitive (<tag> value))])] + [{#..Primitive {<tag> value}}])] [bit #..Bit] [nat #..Nat] @@ -264,14 +264,17 @@ (n.= (-- size) tag)) (template: .public (no_op value) - [(|> 1 #variable.Local #reference.Variable #..Reference - (#..Function (list)) - (#..Apply value))]) + [(|> 1 + {#variable.Local} + {#reference.Variable} + {#..Reference} + {#..Function (list)} + {#..Apply value})]) (def: .public (apply [abstraction inputs]) (-> (Application Analysis) Analysis) (list\mix (function (_ input abstraction') - (#Apply input abstraction')) + {#Apply input abstraction'}) abstraction inputs)) @@ -280,39 +283,39 @@ (loop [abstraction analysis inputs (list)] (case abstraction - (#Apply input next) - (recur next (#.Item input inputs)) + {#Apply input next} + (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] + [variable/local (reference.local)] + [variable/foreign (reference.foreign)] ) (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 - <tag> + [(.<| {#..Structure} + {<tag>} content)])] [variant #..Variant] @@ -320,11 +323,11 @@ ) (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] @@ -335,18 +338,18 @@ ) (template: .public (pattern/bind register) - [(#..Bind register)]) + [{#..Bind register}]) (def: .public (%analysis analysis) (Format Analysis) (case analysis - (#Primitive primitive) + {#Primitive primitive} (case primitive #Unit "[]" (^template [<tag> <format>] - [(<tag> value) + [{<tag> value} (<format> value)]) ([#Bit %.bit] [#Nat %.nat] @@ -355,24 +358,24 @@ [#Frac %.frac] [#Text %.text])) - (#Structure structure) + {#Structure structure} (case structure - (#Variant [lefts right? value]) + {#Variant [lefts right? value]} (format "(" (%.nat lefts) " " (%.bit right?) " " (%analysis value) ")") - (#Tuple members) + {#Tuple members} (|> members (list\each %analysis) (text.interposed " ") (text.enclosed ["[" "]"]))) - (#Reference reference) + {#Reference reference} (reference.format reference) - (#Case analysis match) + {#Case analysis match} "{?}" - (#Function environment body) + {#Function environment body} (|> (%analysis body) (format " ") (format (|> environment @@ -381,15 +384,15 @@ (text.enclosed ["[" "]"]))) (text.enclosed ["(" ")"])) - (#Apply _) + {#Apply _} (|> analysis ..application - #.Item + {#.Item} (list\each %analysis) (text.interposed " ") (text.enclosed ["(" ")"])) - (#Extension name parameters) + {#Extension name parameters} (|> parameters (list\each %analysis) (text.interposed " ") @@ -412,12 +415,12 @@ (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')] - output]) + {#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)) @@ -434,18 +437,18 @@ (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 (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]]) + {#.Item head tail} + {#try.Success [[bundle' (with@ #.scopes tail state')] + [head output]]} #.End - (#try.Failure "Impossible error: Drained scopes!")) + {#try.Failure "Impossible error: Drained scopes!"}) - (#try.Failure error) - (#try.Failure error)))) + {#try.Failure error} + {#try.Failure error}))) (def: scope_reset (List Scope) @@ -455,18 +458,18 @@ (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')] - output]) + {#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)))) + (function.constant {#.Some name}))) (def: .public (with_location location action) (All (_ a) (-> Location (Operation a) (Operation a))) @@ -475,12 +478,12 @@ (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')] - output]) + {#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) @@ -490,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)) @@ -505,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))) @@ -516,18 +519,18 @@ (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>] [(def: .public (<name> value) @@ -535,7 +538,7 @@ (extension.update (with@ <field> <value>)))] [set_source_code Source #.source value] - [set_current_module Text #.current_module (#.Some value)] + [set_current_module Text #.current_module {#.Some value}] [set_location Location #.location value] ) 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 0b9e317fe..ed5983d14 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 dd8d86836..cd74d94f4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -70,7 +70,7 @@ (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] 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 7ed71e658..72a086650 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -115,21 +115,21 @@ (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')] - output]) + (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 (exception.except <exception> [])))) @@ -138,8 +138,8 @@ (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 (with_anchor anchor) @@ -160,14 +160,14 @@ (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 (All (_ anchor expression directive) @@ -197,10 +197,10 @@ (-> 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]) + {#try.Success output} + {#try.Success [state+ output]} - (#try.Failure error) + {#try.Failure error} (exception.except ..cannot_interpret error)))) (def: .public (execute! code) @@ -208,10 +208,10 @@ (-> directive (Operation anchor expression directive Any))) (function (_ (^@ state+ [bundle state])) (case (\ (value@ #host state) execute! code) - (#try.Success output) - (#try.Success [state+ output]) + {#try.Success output} + {#try.Success [state+ output]} - (#try.Failure error) + {#try.Failure error} (exception.except ..cannot_interpret error)))) (def: .public (define! context custom code) @@ -219,10 +219,10 @@ (-> 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]) + {#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,11 +231,11 @@ (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 (phase.except ..no_buffer_for_saving_code [artifact_id])))) @@ -246,8 +246,8 @@ (-> 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)] - id]))))] + {#try.Success [[bundle (with@ #registry registry' state)] + id]})))] [learn artifact.definition] [learn_custom artifact.custom] @@ -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 (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) @@ -301,7 +301,7 @@ #.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 c8c2b9fd3..53968905c 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 @@ -41,7 +41,7 @@ (-> Archive Phase (Fix (-> (Code' (Ann Location)) (Operation Analysis)))) (case code' (^template [<tag> <analyser>] - [(<tag> value) + [{<tag> value} (<analyser> value)]) ([#.Bit /primitive.bit] [#.Nat /primitive.nat] @@ -50,28 +50,28 @@ [#.Frac /primitive.frac] [#.Text /primitive.text]) - (^ (#.Form (list& [_ (#.Tag tag)] - values))) + (^ {#.Form (list& [_ {#.Tag tag}] + values)}) (case values - (#.Item value #.End) + {#.Item value #.End} (/structure.tagged_sum compile tag archive value) _ (/structure.tagged_sum compile tag archive (` [(~+ values)]))) - (^ (#.Form (list& [_ (#.Nat lefts)] [_ (#.Bit right?)] - values))) + (^ {#.Form (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) + {#.Tag tag} (/structure.tagged_sum compile tag archive (' [])) - (^ (#.Tuple elems)) + (^ {#.Tuple elems}) (/structure.record archive compile elems) _ @@ -80,30 +80,30 @@ (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 [_ (#.Record branches)] input))) + (^ {#.Form (list [_ {#.Record branches}] input)}) (/case.case compile branches archive input) - (^ (#.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])]))] - body))) + (^ {#.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 ec8fb396e..d7a7bf6ab 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,8 +69,8 @@ #.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 @@ -85,53 +85,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 (/.except ..cannot_simplify_for_pattern_matching caseT))) - (#.Product _) + {#.Product _} (|> caseT type.flat_tuple (list\each (re_quantify envs)) @@ -169,56 +169,56 @@ (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))]) + (^ [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)))] (.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 (/.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]) @@ -227,17 +227,17 @@ [#.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)))] @@ -261,22 +261,22 @@ _ (/.except ..cannot_match_with_pattern [inputT' pattern])))))) - [location (#.Tag tag)] + [location {#.Tag tag}] (/.with_location location (analyse_pattern #.None inputT (` ((~ pattern))) next)) - (^ [location (#.Form (list& [_ (#.Nat lefts)] [_ (#.Bit right?)] values))]) + (^ [location {#.Form (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) @@ -292,7 +292,7 @@ _ (/.except ..sum_has_no_case [idx inputT]))) - (#.UnivQ _) + {#.UnivQ _} (do ///.monad [[ex_id exT] (//type.with_env check.existential)] @@ -304,7 +304,7 @@ _ (/.except ..cannot_match_with_pattern [inputT' pattern])))) - (^ [location (#.Form (list& [_ (#.Tag tag)] values))]) + (^ [location {#.Form (list& [_ {#.Tag tag}] values)}]) (/.with_location location (do ///.monad [tag (///extension.lifted (meta.normal tag)) @@ -312,7 +312,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) @@ -321,7 +321,7 @@ (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)) @@ -333,13 +333,13 @@ 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 (/.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 5dcedd669..70623af8a 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 @@ -51,16 +51,16 @@ (Rec Coverage (.Variant #Partial - (#Bit Bit) - (#Variant (Maybe Nat) (Dictionary Nat Coverage)) - (#Seq Coverage Coverage) - (#Alt Coverage Coverage) + {#Bit Bit} + {#Variant (Maybe Nat) (Dictionary Nat Coverage)} + {#Seq Coverage Coverage} + {#Alt Coverage Coverage} #Exhaustive))) (def: .public (exhaustive? coverage) (-> Coverage Bit) (case coverage - (#Exhaustive _) + {#Exhaustive _} #1 _ @@ -72,12 +72,12 @@ #Partial "#Partial" - (#Bit value') + {#Bit value'} (|> value' %.bit - (text.enclosed ["(#Bit " ")"])) + (text.enclosed ["{#Bit " "}"])) - (#Variant ?max_cases cases) + {#Variant ?max_cases cases} (|> cases dictionary.entries (list\each (function (_ [idx coverage]) @@ -85,13 +85,13 @@ (text.interposed " ") (text.enclosed ["{" "}"]) (format (%.nat (..cases ?max_cases)) " ") - (text.enclosed ["(#Variant " ")"])) + (text.enclosed ["{#Variant " "}"])) - (#Seq left right) - (format "(#Seq " (%coverage left) " " (%coverage right) ")") + {#Seq left right} + (format "{#Seq " (%coverage left) " " (%coverage right) "}") - (#Alt left right) - (format "(#Alt " (%coverage left) " " (%coverage right) ")") + {#Alt left right} + (format "{#Alt " (%coverage left) " " (%coverage right) "}") #Exhaustive "#Exhaustive")) @@ -99,14 +99,14 @@ (def: .public (determine pattern) (-> Pattern (Operation Coverage)) (case pattern - (^or (#/.Simple #/.Unit) - (#/.Bind _)) + (^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> _)) + [{#/.Simple {<tag> _}} (////\in #Partial)]) ([#/.Nat] [#/.Int] @@ -117,17 +117,17 @@ ... 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)) - (////\in (#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 @@ -139,22 +139,22 @@ (in leftC) _ - (in (#Seq leftC rightC))))) + (in {#Seq leftC rightC})))) lastC prevsP+))) ... 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) + (in {#Variant (if right? + {#.Some idx} #.None) - (|> (dictionary.empty n.hash) - (dictionary.has idx value_coverage))))))) + (|> (dictionary.empty n.hash) + (dictionary.has idx value_coverage))})))) (def: (xor left right) (-> Bit Bit Bit) @@ -176,7 +176,7 @@ (def: (flat_alt coverage) (-> Coverage (List Coverage)) (case coverage - (#Alt left right) + {#Alt left right} (list& left (flat_alt right)) _ @@ -188,19 +188,19 @@ [#Exhaustive #Exhaustive] #1 - [(#Bit sideR) (#Bit sideS)] + [{#Bit sideR} {#Bit sideS}] (bit\= sideR sideS) - [(#Variant allR casesR) (#Variant allS casesS)] + [{#Variant allR casesR} {#Variant allS casesS}] (and (n.= (cases allR) (cases allS)) (\ (dictionary.equivalence =) = casesR casesS)) - [(#Seq leftR rightR) (#Seq leftS rightS)] + [{#Seq leftR rightR} {#Seq leftS rightS}] (and (= leftR leftS) (= rightR rightS)) - [(#Alt _) (#Alt _)] + [{#Alt _} {#Alt _}] (let [flatR (flat_alt reference) flatS (flat_alt sample)] (and (n.= (list.size flatR) (list.size flatS)) @@ -230,11 +230,11 @@ (try\in #Partial) ... 2 bit coverages are exhaustive if they complement one another. - (^multi [(#Bit sideA) (#Bit sideSF)] + (^multi [{#Bit sideA} {#Bit sideSF}] (xor sideA sideSF)) (try\in #Exhaustive) - [(#Variant allA casesA) (#Variant allSF casesSF)] + [{#Variant allA casesA} {#Variant allSF casesSF}] (let [addition_cases (cases allSF) so_far_cases (cases allA)] (cond (and (known_cases? addition_cases) @@ -250,7 +250,7 @@ [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'))) @@ -264,15 +264,15 @@ (dictionary.size casesM)) (list.every? exhaustive? (dictionary.values casesM))) #Exhaustive - (#Variant (case allSF - (#.Some _) + {#Variant (case allSF + {#.Some _} allSF _ allA) - casesM)))))) + casesM}))))) - [(#Seq leftA rightA) (#Seq leftSF rightSF)] + [{#Seq leftA rightA} {#Seq leftSF rightSF}] (case [(coverage/= leftSF leftA) (coverage/= rightSF rightA)] ... Same prefix [#1 #0] @@ -283,17 +283,17 @@ ... (since only the "left" part would influence whether the ... merged coverage is exhaustive or not). (in leftSF) - (in (#Seq leftSF rightM)))) + (in {#Seq leftSF rightM}))) ... Same suffix [#0 #1] (do try.monad [leftM (merged leftA leftSF)] - (in (#Seq leftM rightA))) + (in {#Seq leftM rightA})) ... The 2 sequences cannot possibly be merged. [#0 #0] - (try\in (#Alt so_far addition)) + (try\in {#Alt so_far addition}) ... There is nothing the addition adds to the coverage. [#1 #1] @@ -308,12 +308,12 @@ (try\in #Exhaustive) ... The left part will always match, so the addition is redundant. - (^multi [(#Seq left right) single] + (^multi [{#Seq left right} single] (coverage/= left single)) (exception.except ..redundant_pattern [so_far addition]) ... The right part is not necessary, since it can always match the left. - (^multi [single (#Seq left right)] + (^multi [single {#Seq left right}] (coverage/= left single)) (try\in single) @@ -326,7 +326,7 @@ ... other ones in the original Alt. ... This process must be repeated until no further productive ... merges can be done. - [_ (#Alt leftS rightS)] + [_ {#Alt leftS rightS}] (do [! try.monad] [.let [fuse_once (: (-> Coverage (List Coverage) (Try [(Maybe Coverage) @@ -337,34 +337,34 @@ #.End (in [#.None (list coverageA)]) - (#.Item altSF altsSF') + {#.Item altSF altsSF'} (case (merged coverageA altSF) - (#try.Success altMSF) + {#try.Success altMSF} (case altMSF - (#Alt _) + {#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 (case (list.reversed possibilitiesSF) - (#.Item last prevs) - (in (list\mix (function (_ left right) (#Alt left right)) + {#.Item last prevs} + (in (list\mix (function (_ left right) {#Alt left right}) last prevs)) @@ -376,4 +376,4 @@ ... The addition cannot possibly improve the coverage. (exception.except ..redundant_pattern [so_far addition]) ... There are now 2 alternative paths. - (try\in (#Alt so_far addition))))) + (try\in {#Alt so_far addition})))) 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 fe0a32584..c0733c07a 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,31 +54,31 @@ (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 (/.failure (ex.error cannot_analyse [expectedT function_name arg_name body]))) (^template [<tag> <instancer>] - [(<tag> _) + [{<tag> _} (do ! [[_ instanceT] (//type.with_env <instancer>)] (recur (maybe.trusted (type.applied (list instanceT) expectedT))))]) ([#.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,17 +86,17 @@ (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))) + bodyA})) /.with_scope ... Functions have access not only to their argument, but ... also to themselves, through a local variable. 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 b6d610a7f..47768945d 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,27 +66,28 @@ (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))]) + [{<tag> left right} + {<tag> + (replace parameter_idx replacement left) + (replace parameter_idx replacement right)}]) ([#.Sum] [#.Product] [#.Function] [#.Apply]) - (#.Parameter idx) + {#.Parameter idx} (if (n.= parameter_idx idx) replacement type) (^template [<tag>] - [(<tag> env quantified) - (<tag> (list\each (replace parameter_idx replacement) env) - (replace (n.+ 2 parameter_idx) replacement quantified))]) + [{<tag> env quantified} + {<tag> (list\each (replace parameter_idx replacement) env) + (replace (n.+ 2 parameter_idx) replacement quantified)}]) ([#.UnivQ] [#.ExQ]) @@ -96,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) @@ -120,17 +121,17 @@ [_ (//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 @@ -146,9 +147,9 @@ (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 @@ -161,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]) @@ -169,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) _ @@ -188,22 +189,22 @@ (-> 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))]) + [{<tag> left right} + {<tag> (recur left) (recur right)}]) ([#.Sum] [#.Product] [#.Function] [#.Apply]) - (#.Parameter index) + {#.Parameter index} (if (n.= target index) sub base) (^template [<tag>] - [(<tag> environment quantified) - (<tag> (list\each recur environment) quantified)]) + [{<tag> environment quantified} + {<tag> (list\each recur environment) quantified}]) ([#.UnivQ] [#.ExQ]) _ @@ -213,26 +214,26 @@ (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>] - [(<tag> env bodyT) + [{<tag> env bodyT} (do ///.monad [bodyT+ (record' record_size (n.+ 2 target) originalT bodyT)] - (in (<tag> env bodyT+)))]) + (in {<tag> env bodyT+}))]) ([#.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 (/.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)))) @@ -251,20 +252,20 @@ (loop [depth 0 currentT inferT] (case currentT - (#.Named name unnamedT) + {#.Named name unnamedT} (do ///.monad [unnamedT+ (recur depth unnamedT)] (in unnamedT+)) (^template [<tag>] - [(<tag> env bodyT) + [{<tag> env bodyT} (do ///.monad [bodyT+ (recur (++ depth) bodyT)] - (in (<tag> env bodyT+)))]) + (in {<tag> env bodyT+}))]) ([#.UnivQ] [#.ExQ]) - (#.Sum _) + {#.Sum _} (let [cases (type.flat_variant currentT) actual_size (list.size cases) boundary (-- expected_size)] @@ -272,7 +273,7 @@ (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)] @@ -296,9 +297,9 @@ ... 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 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 31ace4429..84124d32f 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 @@ -82,14 +82,14 @@ (do ///.monad [self_name meta.current_module_name] (function (_ state) - (#try.Success [(revised@ #.modules + {#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) - []]))))) + []]})))) (def: .public (alias alias module) (-> Text Text (Operation Any)) @@ -97,11 +97,11 @@ (do ///.monad [self_name meta.current_module_name] (function (_ state) - (#try.Success [(revised@ #.modules + {#try.Success [(revised@ #.modules (plist.revised self_name (revised@ #.module_aliases (: (-> (List [Text Text]) (List [Text Text])) - (|>> (#.Item [alias module]))))) + (|>> {#.Item [alias module]})))) state) - []]))))) + []]})))) (def: .public (exists? module) (-> Text (Operation Bit)) @@ -110,8 +110,8 @@ (|> state (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)) @@ -122,26 +122,26 @@ (function (_ state) (case (plist.value name (value@ #.definitions self)) #.None - (#try.Success [(revised@ #.modules + {#try.Success [(revised@ #.modules (plist.has self_name (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) - []])))) + []]}))) (def: .public (with_module hash name action) (All (_ a) (-> Nat Text (Operation a) (Operation [Module a]))) @@ -158,15 +158,15 @@ (///extension.lifted (function (_ state) (case (|> state (value@ #.modules) (plist.value module_name)) - (#.Some module) + {#.Some module} (let [active? (case (value@ #.module_state module) #.Active #1 _ #0)] (if active? - (#try.Success [(revised@ #.modules + {#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>]) state))) @@ -178,11 +178,11 @@ (///extension.lifted (function (_ state) (case (|> state (value@ #.modules) (plist.value module_name)) - (#.Some module) - (#try.Success [state + {#.Some module} + {#try.Success [state (case (value@ #.module_state module) <tag> #1 - _ #0)]) + _ #0)]} #.None ((/.except' unknown_module module_name) state)))))] @@ -197,8 +197,8 @@ (///extension.lifted (function (_ state) (case (|> state (value@ #.modules) (plist.value module_name)) - (#.Some module) - (#try.Success [state (value@ #.module_hash module)]) + {#.Some module} + {#try.Success [state (value@ #.module_hash module)]} #.None ((/.except' unknown_module module_name) state))))) @@ -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) _ @@ -218,6 +218,6 @@ (monad.each ! (function (_ [index short]) (..define (format "#" 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 17b41ba71..ad481b931 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,7 +16,7 @@ (-> <type> (Operation Analysis)) (do ///.monad [_ (//type.infer <type>)] - (in (#/.Primitive (<tag> value)))))] + (in {#/.Primitive {<tag> value}})))] [bit .Bit #/.Bit] [nat .Nat #/.Nat] @@ -30,4 +30,4 @@ (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 f3bc9d282..26946da08 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 @@ -40,10 +40,10 @@ (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,10 +84,10 @@ (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)))) @@ -99,7 +99,7 @@ (do [! ///.monad] [?var (variable simple_name)] (case ?var - (#.Some varA) + {#.Some varA} (in varA) #.None 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 aa452e685..2b3e9f411 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 @@ -41,7 +41,7 @@ (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) @@ -54,9 +54,9 @@ (loop [idx 0 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 @@ -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))) @@ -85,25 +85,25 @@ (list.split_when (|>> (reference? name))))] (case outer #.End - (#.Right [state #.None]) + {#.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)])))) scope) - (product.right ref+inner))])) + (product.right ref+inner)}])) [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) @@ -113,7 +113,7 @@ (All (_ a) (-> [Text Type] (Operation a) (Operation a))) (function (_ [bundle state]) (case (value@ #.scopes state) - (#.Item head tail) + {#.Item head tail} (let [old_mappings (value@ [#.locals #.mappings] head) new_var_id (value@ [#.locals #.counter] head) new_head (revised@ #.locals @@ -121,21 +121,21 @@ (|>> (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]) + {#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')] - output])) + {#.Item head' tail'} + (let [scopes' {#.Item (with@ #.locals (value@ #.locals head) head') + tail'}] + {#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 [])) @@ -165,19 +165,19 @@ #.End (list) - (#.Item top _) + {#.Item top _} (value@ #.name top))] (case (action [bundle (revised@ #.scopes - (|>> (#.Item (scope parent_name name))) + (|>> {#.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]) + output]} - (#try.Failure error) - (#try.Failure error))))) + {#try.Failure error} + {#try.Failure error})))) (exception: .public cannot_get_next_reference_when_there_is_no_scope) @@ -186,8 +186,8 @@ (///extension.lifted (function (_ state) (case (value@ #.scopes state) - (#.Item top _) - (#try.Success [state (value@ [#.locals #.counter] top)]) + {#.Item top _} + {#try.Success [state (value@ [#.locals #.counter] top)]} #.End (exception.except ..cannot_get_next_reference_when_there_is_no_scope []))))) @@ -195,11 +195,11 @@ (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)) 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 f6c226e9a..417fe9709 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 @@ -113,10 +113,10 @@ (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))] @@ -125,16 +125,16 @@ #.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)) @@ -145,7 +145,7 @@ (/.except ..cannot_infer_numeric_tag [expectedT tag valueC]))) (^template [<tag> <instancer>] - [(<tag> _) + [{<tag> _} (do ! [[instance_id instanceT] (//type.with_env <instancer>)] (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT)) @@ -153,15 +153,15 @@ ([#.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)) _ @@ -169,7 +169,7 @@ _ (case (type.applied (list inputT) funT) - (#.Some outputT) + {#.Some outputT} (//type.with_type outputT (recur valueC)) @@ -187,26 +187,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]))))] @@ -218,19 +218,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)) @@ -245,7 +245,7 @@ (in (/.tuple (list\each product.right membersTA)))))) (^template [<tag> <instancer>] - [(<tag> _) + [{<tag> _} (do ! [[instance_id instanceT] (//type.with_env <instancer>)] (//type.with_type (maybe.trusted (type.applied (list instanceT) expectedT)) @@ -253,15 +253,15 @@ ([#.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)) _ @@ -269,7 +269,7 @@ _ (case (type.applied (list inputT) funT) - (#.Some outputT) + {#.Some outputT} (//type.with_type outputT (product archive analyse membersC)) @@ -289,7 +289,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,13 +308,13 @@ output (: (List [Name Code]) #.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)) + (\ ///.monad in {#.Some output}) _ (\ ///.monad in #.None)))) @@ -327,16 +327,16 @@ (case record ... empty_record = empty_tuple = unit/any = [] #.End - (\ ///.monad in (#.Some [0 (list) Any])) + (\ ///.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)] @@ -350,7 +350,7 @@ (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))) @@ -363,9 +363,9 @@ .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) + {#try.Failure error} (in #.None))) )) @@ -378,12 +378,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)) @@ -398,18 +398,18 @@ #.None (..product archive analyse members) - (#.Some slots) + {#.Some slots} (do ! [record_size,membersC,recordT (..order slots)] (case record_size,membersC,recordT #.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 7a5bde817..33a8715d5 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 @@ -19,17 +19,17 @@ (def: .public (with_type expected) (All (_ a) (-> Type (Operation a) (Operation a))) (///extension.localized (value@ #.expected) (with@ #.expected) - (function.constant (#.Some 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)] - output]) + {#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 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 3d3163553..dc47f7039 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)] @@ -70,10 +70,10 @@ extension_eval (:as Eval (wrapper (:expected compiler_eval)))] _ (//.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,7 +84,7 @@ (do ! [?macro (//extension.lifted (meta.macro macro_name)) macro (case ?macro - (#.Some macro) + {#.Some macro} (in macro) #.None 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 d54049e4e..2fd695eef 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 @@ -98,8 +98,8 @@ (function (_ [bundle state]) (case (dictionary.value name bundle) #.None - (#try.Success [[(dictionary.has name (extender handler) bundle) state] - []]) + {#try.Success [[(dictionary.has name (extender handler) bundle) state] + []]} _ (exception.except ..cannot_overwrite name)))) @@ -119,7 +119,7 @@ (-> 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) @@ -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 66b58bf74..36578eb15 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,8 +128,8 @@ [objectA (analysis/type.with_type Any (phase archive objectC)) _ (analysis/type.infer .Any)] - (in (#analysis.Extension extension (list (analysis.text fieldC) - objectA)))))])) + (in {#analysis.Extension extension (list (analysis.text fieldC) + objectA)})))])) (def: object::do Handler @@ -141,9 +141,9 @@ (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)))))])) + inputsA)})))])) (def: bundle::object Bundle @@ -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,8 +201,8 @@ (phase archive abstractionC)) _ (analysis/type.infer (for [@.js ffi.Function] Any))] - (in (#analysis.Extension extension (list (analysis.nat arity) - abstractionA)))))])) + (in {#analysis.Extension extension (list (analysis.nat arity) + abstractionA)})))])) (def: .public bundle 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 9ea592c20..bc9151306 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 - (list& class super_class super_interfaces))) + {#.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,23 +355,23 @@ (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 (/////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 (phase\in primitive_type) @@ -387,7 +387,7 @@ (do phase.monad [parameterJT (jvm_type parameterT)] (case (jvm_parser.parameter? parameterJT) - (#.Some parameterJT) + {#.Some parameterJT} (in parameterJT) #.None @@ -395,7 +395,7 @@ 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)) + (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,8 +438,8 @@ (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)) - arrayA)))) + (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature arrayJT)) + arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -452,9 +452,9 @@ (do phase.monad [lengthA (typeA.with_type ..int (analyse archive lengthC)) - _ (typeA.infer (#.Primitive (|> (jvm.array primitive_type) ..reflection) - (list)))] - (in (#/////analysis.Extension extension_name (list lengthA)))) + _ (typeA.infer {#.Primitive (|> (jvm.array primitive_type) ..reflection) + (list)})] + (in {#/////analysis.Extension extension_name (list lengthA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -470,13 +470,13 @@ expectedT (///.lifted meta.expected_type) expectedJT (jvm_array_type expectedT) elementJT (case (jvm_parser.array? expectedJT) - (#.Some elementJT) + {#.Some elementJT} (in elementJT) #.None (/////analysis.except ..non_array expectedT))] - (in (#/////analysis.Extension extension_name (list (/////analysis.text (..signature elementJT)) - lengthA)))) + (in {#/////analysis.Extension extension_name (list (/////analysis.text (..signature elementJT)) + lengthA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 1 (list.size args)])))) @@ -484,11 +484,11 @@ (def: (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT - (^ (#.Primitive (static array.type_name) - (list elementT))) + (^ {#.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,24 +506,24 @@ ... else (phase\in (jvm.class name (list))))) - (#.Named name anonymous) + {#.Named name anonymous} (check_parameter anonymous) (^template [<tag>] - [(<tag> id) + [{<tag> id} (phase\in (jvm.class ..object_class (list)))]) ([#.Var] [#.Ex]) (^template [<tag>] - [(<tag> env unquantified) + [{<tag> env unquantified} (check_parameter unquantified)]) ([#.UnivQ] [#.ExQ]) - (#.Apply inputT abstractionT) + {#.Apply inputT abstractionT} (case (type.applied (list inputT) abstractionT) - (#.Some outputT) + {#.Some outputT} (check_parameter outputT) #.None @@ -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,34 +565,34 @@ (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) - (list elementT))) + (^ {#.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) + [{<tag> env unquantified} (check_jvm unquantified)]) ([#.UnivQ] [#.ExQ]) - (#.Apply inputT abstractionT) + {#.Apply inputT abstractionT} (case (type.applied (list inputT) abstractionT) - (#.Some outputT) + {#.Some outputT} (check_jvm outputT) #.None @@ -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) - (list)) + 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,17 +647,17 @@ 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)))) + arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 2 (list.size args)])))) (def: (write_primitive_array_handler lux_type jvm_type) (-> .Type (Type Primitive) Handler) - (let [array_type (#.Primitive (|> (jvm.array jvm_type) ..reflection) - (list))] + (let [array_type {#.Primitive (|> (jvm.array jvm_type) ..reflection) + (list)}] (function (_ extension_name analyse archive args) (case args (^ (list idxC valueC arrayC)) @@ -669,9 +669,9 @@ (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)))) + arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)]))))) @@ -693,10 +693,10 @@ (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)))) + arrayA)})) _ (/////analysis.except ///.incorrect_arity [extension_name 3 (list.size args)])))) @@ -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) + {#.Some super} (list& super (array.list #.None (java/lang/Class::getGenericInterfaces source_class))) #.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))) + {#.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,15 +959,15 @@ (case (|> candidate_parents (list.only product.right) (list\each product.left)) - (#.Item [next_name nextT] _) + {#.Item [next_name nextT] _} (recur [next_name nextT]) #.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))) + 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)) @@ -1122,7 +1122,7 @@ (and prev (jvm\= expectedJC (: (Type Value) (case (jvm_parser.var? actualJC) - (#.Some name) + {#.Some name} (|> aliasing (dictionary.value name) (maybe.else name) @@ -1151,7 +1151,7 @@ (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) @@ -1217,7 +1217,7 @@ inputsT _ - (list& (#.Primitive (java/lang/Class::getName owner) owner_tvarsT) + (list& {#.Primitive (java/lang/Class::getName owner) owner_tvarsT} inputsT))) outputT)]] (in [methodT @@ -1245,7 +1245,7 @@ (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)]] @@ -1255,14 +1255,14 @@ (type: Evaluation (Variant - (#Pass Method_Signature) - (#Hint Method_Signature))) + {#Pass Method_Signature} + {#Hint Method_Signature})) (template [<name> <tag>] [(def: <name> (-> Evaluation (Maybe Method_Signature)) - (|>> (case> (<tag> output) - (#.Some output) + (|>> (case> {<tag> output} + {#.Some output} _ #.None)))] @@ -1310,7 +1310,7 @@ (|>> #Hint)) (method_signature method_style method)))))))] (case (list.all pass! candidates) - (#.Item method #.End) + {#.Item method #.End} (in method) #.End @@ -1340,7 +1340,7 @@ (if passes? (|>> #Pass) (|>> #Hint)) (constructor_signature constructor))))))] (case (list.all pass! candidates) - (#.Item constructor #.End) + {#.Item constructor #.End} (in constructor) #.End @@ -1387,10 +1387,10 @@ (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))))))])) + (decorate_inputs argsT argsA))})))])) (def: (invoke::virtual class_loader) (-> java/lang/ClassLoader Handler) @@ -1405,17 +1405,17 @@ (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 - (decorate_inputs argsT argsA))))))])) + (decorate_inputs argsT argsA))})))])) (def: (invoke::special class_loader) (-> java/lang/ClassLoader Handler) @@ -1430,10 +1430,10 @@ (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))))))])) + (decorate_inputs argsT argsA))})))])) (def: (invoke::interface class_loader) (-> java/lang/ClassLoader Handler) @@ -1451,18 +1451,18 @@ (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_name (list)))) - (/////analysis.text method) - (/////analysis.text (..signature outputJT)) - objectA - (decorate_inputs argsT argsA))))))])) + (in {#/////analysis.Extension extension_name + (list& (/////analysis.text (..signature (jvm.class class_name (list)))) + (/////analysis.text method) + (/////analysis.text (..signature outputJT)) + objectA + (decorate_inputs argsT argsA))})))])) (def: (invoke::constructor class_loader) (-> java/lang/ClassLoader Handler) @@ -1476,8 +1476,8 @@ _ (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)))) - (decorate_inputs argsT argsA))))))])) + (in {#/////analysis.Extension extension_name (list& (/////analysis.text (..signature (jvm.class class (list)))) + (decorate_inputs argsT argsA))})))])) (def: (bundle::member class_loader) (-> java/lang/ClassLoader Bundle) @@ -1693,7 +1693,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,10 +1707,10 @@ (/////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))) + (/////analysis.tuple (list bodyA))} )))))) (type: .public (Virtual_Method a) @@ -1769,7 +1769,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,10 +1785,10 @@ (/////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))) + (/////analysis.tuple (list bodyA))} )))))) (type: .public (Static_Method a) @@ -1857,10 +1857,10 @@ (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))) + (/////analysis.tuple (list bodyA))} )))))) (type: .public (Overriden_Method a) @@ -1914,10 +1914,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) + {#.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) @@ -1966,25 +1966,25 @@ bodyA 2 - (#/////analysis.Case (/////analysis.unit) - [[#/////analysis.when - (#/////analysis.Bind 2) + {#/////analysis.Case (/////analysis.unit) + [[#/////analysis.when + {#/////analysis.Bind 2} - #/////analysis.then - bodyA] - (list)]) + #/////analysis.then + bodyA] + (list)]} _ - (#/////analysis.Case (/////analysis.unit) - [[#/////analysis.when - (#/////analysis.Complex - (#/////analysis.Tuple (|> arity - list.indices - (list\each (|>> (n.+ 2) #/////analysis.Bind))))) + {#/////analysis.Case (/////analysis.unit) + [[#/////analysis.when + {#/////analysis.Complex + {#/////analysis.Tuple (|> arity + list.indices + (list\each (|>> (n.+ 2) #/////analysis.Bind)))}} - #/////analysis.then - bodyA] - (list)])))) + #/////analysis.then + bodyA] + (list)]}))) (def: .public (analyse_overriden_method analyse archive selfT mapping supers method) (-> Phase Archive .Type Mapping (List (Type Class)) (Overriden_Method Code) (Operation Analysis)) @@ -2012,7 +2012,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,15 +2028,15 @@ (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)) + (..hide_method_body (list.size arguments) bodyA)} )))))) (type: .public (Method_Definition a) (Variant - (#Overriden_Method (Overriden_Method a)))) + {#Overriden_Method (Overriden_Method a)})) (def: .public parameter_types (-> (List (Type Var)) (Check (List [(Type Var) .Type]))) @@ -2082,7 +2082,7 @@ (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 @@ -2154,7 +2154,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,14 +2165,14 @@ (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 - (list (class_analysis super_class) - (/////analysis.tuple (list\each class_analysis super_interfaces)) - (/////analysis.tuple (list\each typed_analysis constructor_argsA+)) - (/////analysis.tuple methodsA))))))])) + (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+)) + (/////analysis.tuple methodsA))})))])) (def: (bundle::class class_loader) (-> java/lang/ClassLoader Bundle) 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 f7ed4ed54..c9c1dfb0b 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,8 +128,8 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in (#analysis.Extension extension (list (analysis.text fieldC) - objectA)))))])) + (in {#analysis.Extension extension (list (analysis.text fieldC) + objectA)})))])) (def: object::do Handler @@ -141,9 +141,9 @@ (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)))))])) + inputsA)})))])) (def: bundle::object Bundle @@ -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,8 +232,8 @@ abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] - (in (#analysis.Extension extension (list (analysis.nat arity) - abstractionA)))))])) + (in {#analysis.Extension extension (list (analysis.nat arity) + abstractionA)})))])) (def: .public bundle 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 fb283bf9e..0609bee0a 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 a52f8bb53..16717539b 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,8 +138,8 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in (#analysis.Extension extension (list (analysis.text fieldC) - objectA)))))])) + (in {#analysis.Extension extension (list (analysis.text fieldC) + objectA)})))])) (def: object::do Handler @@ -151,9 +151,9 @@ (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)))))])) + inputsA)})))])) (def: bundle::object Bundle @@ -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 700f80163..ec21b45bc 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,8 +136,8 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in (#analysis.Extension extension (list (analysis.text fieldC) - objectA)))))])) + (in {#analysis.Extension extension (list (analysis.text fieldC) + objectA)})))])) (def: object::do Handler @@ -149,9 +149,9 @@ (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)))))])) + inputsA)})))])) (def: bundle::object Bundle @@ -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,8 +203,8 @@ abstractionA (analysis/type.with_type (-> inputT Any) (phase archive abstractionC)) _ (analysis/type.infer ..Function)] - (in (#analysis.Extension extension (list (analysis.nat arity) - abstractionA)))))])) + (in {#analysis.Extension extension (list (analysis.nat arity) + abstractionA)})))])) (def: python::exec Handler @@ -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 6bf24f1fa..525458cdd 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,8 +128,8 @@ [objectA (analysis/type.with_type ..Object (phase archive objectC)) _ (analysis/type.infer .Any)] - (in (#analysis.Extension extension (list (analysis.text fieldC) - objectA)))))])) + (in {#analysis.Extension extension (list (analysis.text fieldC) + objectA)})))])) (def: object::do Handler @@ -141,9 +141,9 @@ (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)))))])) + inputsA)})))])) (def: bundle::object Bundle @@ -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 2075522d7..a0df81d93 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 6dc2b393d..76c66e37d 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 @@ -144,8 +144,8 @@ ))) (type: Field - (#Constant Constant) - (#Variable Variable)) + {#Constant Constant} + {#Variable Variable}) (def: field (Parser Field) @@ -155,10 +155,10 @@ )) (type: Method_Definition - (#Constructor (jvm.Constructor Code)) - (#Virtual_Method (jvm.Virtual_Method Code)) - (#Static_Method (jvm.Static_Method Code)) - (#Overriden_Method (jvm.Overriden_Method Code))) + {#Constructor (jvm.Constructor Code)} + {#Virtual_Method (jvm.Virtual_Method Code)} + {#Static_Method (jvm.Static_Method Code)} + {#Overriden_Method (jvm.Overriden_Method Code)}) (def: method (Parser Method_Definition) @@ -186,10 +186,10 @@ (-> Field (Resource field.Field)) (case field ... TODO: Handle annotations. - (#Constant [name annotations type value]) + {#Constant [name annotations type value]} (case value (^template [<tag> <type> <constant>] - [[_ (<tag> value)] + [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) attribute (attribute.constant constant)] @@ -210,7 +210,7 @@ (undefined)) ... TODO: Handle annotations. - (#Variable [name visibility state annotations type]) + {#Variable [name visibility state annotations type]} (field.field (modifier\composite visibility state) name type (row.row)))) @@ -225,16 +225,16 @@ [methodA (: (Operation analysis.Analysis) (directive.lifted_analysis (case methodC - (#Constructor method) + {#Constructor method} (jvm.analyse_constructor_method analyse selfT mapping method) - (#Virtual_Method method) + {#Virtual_Method method} (jvm.analyse_virtual_method analyse selfT mapping method) - (#Static_Method method) + {#Static_Method method} (jvm.analyse_static_method analyse mapping method) - (#Overriden_Method method) + {#Overriden_Method method} (jvm.analyse_overriden_method analyse selfT mapping method))))] (directive.lifted_synthesis (synthesize methodA))))) @@ -275,7 +275,7 @@ (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) 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 0ebdde096..4ea0c4e7a 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]) @@ -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))] @@ -219,7 +219,7 @@ (-> 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)) @@ -227,7 +227,7 @@ [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)) @@ -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])) + (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) @@ -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 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 facb40e7e..8c6df79fd 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 1072bffe4..54b345e36 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))) @@ -115,9 +115,13 @@ [synthesis.text] [synthesis.variant] [synthesis.tuple] - [#synthesis.Reference] [synthesis.branch/get] - [synthesis.function/apply] + [synthesis.function/apply]) + + (^template [<tag>] + [(^ {<tag> value}) + (/////\each _.return (expression archive synthesis))]) + ([#synthesis.Reference] [#synthesis.Extension]) (^ (synthesis.branch/case case)) @@ -162,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 2ff3fd02a..f3efd5f47 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 e0626e0b6..b070a0a6b 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,9 +339,9 @@ (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 @@ -644,7 +644,7 @@ (do //////.monad [.let [$class (type.class class (list))]] (case (dictionary.value unboxed ..primitives) - (#.Some primitive) + {#.Some primitive} (in (_.getstatic $class field primitive)) #.None @@ -661,7 +661,7 @@ [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) @@ -683,7 +683,7 @@ [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 @@ -703,7 +703,7 @@ 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 @@ -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 @@ -855,13 +855,13 @@ (//////synthesis.path/then (normalize bodyS)) (^template [<tag>] - [(^ (<tag> leftP rightP)) - (<tag> (recur leftP) (recur rightP))]) + [(^ {<tag> leftP rightP}) + {<tag> (recur leftP) (recur rightP)}]) ([#//////synthesis.Alt] [#//////synthesis.Seq]) (^template [<tag>] - [(^ (<tag> value)) + [(^ {<tag> value}) path]) ([#//////synthesis.Pop] [#//////synthesis.Bind] @@ -875,7 +875,7 @@ (function (recur body) (case body (^template [<tag>] - [(^ (<tag> value)) + [(^ {<tag> value}) body]) ([#//////synthesis.Primitive] [//////synthesis.constant]) @@ -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,12 +952,12 @@ (_.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)])) store_capturedG - _.return))))) + _.return)}))) (def: (anonymous_instance generate archive class env) (-> Phase Archive (Type category.Class) (Environment Synthesis) (Operation (Bytecode Any))) @@ -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,9 +1066,9 @@ returnT exceptionsT]) (list) - (#.Some ($_ _.composite + {#.Some ($_ _.composite bodyG - (returnG returnT))))))) + (returnG returnT))})))) normalized_methods) bytecode (<| (\ ! each (format.result class.writer)) //////.lifted 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 1be1bcfa5..3523c19fa 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))) @@ -75,9 +75,13 @@ [synthesis.text] [synthesis.variant] [synthesis.tuple] - [#synthesis.Reference] [synthesis.branch/get] - [synthesis.function/apply] + [synthesis.function/apply]) + + (^template [<tag>] + [(^ {<tag> value}) + (/////\each _.return (expression archive synthesis))]) + ([#synthesis.Reference] [#synthesis.Extension]) (^ (synthesis.branch/case 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 d5f740ed4..9a06cd980 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 03cb557dc..cbb7c557d 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))) @@ -61,9 +61,13 @@ [synthesis.text] [synthesis.variant] [synthesis.tuple] - [#synthesis.Reference] [synthesis.branch/get] - [synthesis.function/apply] + [synthesis.function/apply]) + + (^template [<tag>] + [(^ {<tag> value}) + (/////\each _.return (expression archive synthesis))]) + ([#synthesis.Reference] [#synthesis.Extension]) (^ (synthesis.branch/case case)) @@ -88,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 @@ -124,10 +128,10 @@ ... .let [dependencies (//case.dependencies (list\mix (function (_ right left) ... (synthesis.path/seq left right)) ... (synthesis.path/then input) - ... (#.Item (synthesis.path/then else) - ... (list\each (|>> product.right - ... synthesis.path/then) - ... conditionals)))) + ... {#.Item (synthesis.path/then else) + ... (list\each (|>> product.right + ... synthesis.path/then) + ... conditionals)})) ... @closure (_.var (reference.artifact artifact_id)) ... closure (_.def @closure dependencies ... ($_ _.then 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 68725c83a..2e533b5bd 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 a253cb8de..6b6538363 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 @@ -73,9 +73,13 @@ [synthesis.text] [synthesis.variant] [synthesis.tuple] - [#synthesis.Reference] [synthesis.branch/get] - [synthesis.function/apply] + [synthesis.function/apply]) + + (^template [<tag>] + [(^ {<tag> value}) + (/////\each _.return (expression archive synthesis))]) + ([#synthesis.Reference] [#synthesis.Extension]) (^ (synthesis.branch/case case)) 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 bc2ad5cba..7161326e1 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 1b1f29f46..26a967a45 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 90f67a68a..5442b7268 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 @@ -117,7 +117,7 @@ (_.go @fail) (..push! @temp))) (.case next! - (#.Some next!) + {#.Some next!} (list next!) #.None @@ -150,14 +150,14 @@ #/////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 @@ -171,7 +171,7 @@ then!)))) (^template [<tag> <format> <=>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -179,7 +179,7 @@ (in [(<=> [(|> match <format>) ..peek]) then!]))) - (#.Item item))] + {#.Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) (_.go @fail) @@ -195,7 +195,7 @@ (^ (<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]) 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 0f7c76ed8..1c7fd4877 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 eb78e6402..2a5fa7c1c 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 @@ -20,7 +20,7 @@ #.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 e6aa9cdce..65b06ce16 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 5f634c533..8f98d44ab 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 @@ -171,7 +171,7 @@ [/////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,9 +179,9 @@ (/////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!)))) + then!)})) ... Extra optimization (^template [<pm> <getter>] @@ -190,26 +190,26 @@ (/////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!))))]) + then!)}))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) (^ (/////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!)))) + then!)})) (^ (/////synthesis.!multi_pop nextP)) (.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!))))) + next!)}))) _ (///////phase\in #.None))) @@ -221,25 +221,25 @@ (do ///////phase.monad [outcome (optimized_pattern_matching recur pathP)] (.case outcome - (#.Some outcome) + {#.Some outcome} (in outcome) #.None (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (statement expression archive bodyS) #/////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 @@ -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,7 +260,7 @@ (in [(//runtime.i64//= (//primitive.i64 (.int match)) ..peek_cursor) then!]))) - (#.Item item))] + {#.Item item})] (in (_.cond clauses ..fail_pm!))) (^template [<tag> <format>] @@ -268,10 +268,10 @@ (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!))))]) + {#.Some ..fail_pm!})))]) ([#/////synthesis.F64_Fork //primitive.f64] [#/////synthesis.Text_Fork //primitive.text]) 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 58bf53a29..f2be9fda5 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)] 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 c4284d345..88072200f 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 @@ -20,7 +20,7 @@ #.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 c2a125d4a..6a1a607cb 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 075e8d68a..2da725141 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 @@ -95,12 +95,12 @@ #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 d1785ac0a..b0833504c 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/method/apply.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/apply.lux index a16c047e7..994a9f33f 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]) @@ -132,7 +132,7 @@ (apply (n.+ ..this_offset arity_inputs) additional_inputs) _.areturn)) - ... (i.< over_extent (.int stage)) +... (i.< over_extent (.int stage)) (let [current_environment (|> (list.indices (list.size environment)) (list\each (///foreign.get class)) (monad.all _.monad)) @@ -154,4 +154,4 @@ ($_ _.composite ///partial/count.value (_.tableswitch (try.trusted (signed.s4 +0)) @default [@labelsH @labelsT]) - cases))))))) + cases)))}))) 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 ae02754ae..723ff6ce5 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,11 +31,11 @@ (method.method //.modifier name (..type arity) (list) - (#.Some ($_ _.composite + {#.Some ($_ _.composite (_.set_label @begin) body _.areturn - )))) + )})) (def: .public method (-> Arity Label (Bytecode Any) (Resource Method)) 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 e39e582db..91df54eca 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,9 +94,9 @@ (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) (store_all (-- arity) (///partial.put class) offset_partial) - _.return))))) + _.return)}))) 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 0e8365945..79926e5b8 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) @@ -78,4 +78,4 @@ (monad.each _.monad (function (_ register) (///partial.put class register (_.aload (after_arity register)))) (list.indices (n.- ///arity.minimum arity))) - _.areturn))))) + _.areturn)}))) 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 f406c2879..b5bdb1e1d 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,8 +43,8 @@ (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) - _.areturn)))) + _.areturn)})) 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 6e5030da6..0ffbbceb3 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) + {#try.Success field} (case (java/lang/reflect/Field::get #.None field) - (#try.Success ?value) + {#try.Success ?value} (case ?value - (#.Some value) - (#try.Success value) + {#.Some value} + {#try.Success value} #.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,11 +110,11 @@ (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) - _.return)))) + _.return)})) (row.row))] (io.run! (do [! (try.with io.monad)] [bytecode (\ ! each (format.result class.writer) 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 3edc41c03..9ed5eb48e 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 8ba5655a1..4074cf6cc 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,12 +132,12 @@ (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 ..run_io - _.return)))] + _.return)})] [..class (<| (format.result class.writer) try.trusted 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 931f8fd72..778b23005 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 ad6166d3f..c3c8f518c 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,12 +151,12 @@ (method.method ..modifier ..variant::name ..variant::type (list) - (#.Some ($_ _.composite - new_variant ... A[3] - (..set! ..variant_tag $tag) ... A[3] + {#.Some ($_ _.composite + new_variant ... A[3] + (..set! ..variant_tag $tag) ... A[3] (..set! ..variant_last? $last?) ... A[3] (..set! ..variant_value $value) ... A[3] - _.areturn))))) + _.areturn)}))) (def: .public left_flag _.aconst_null) (def: .public right_flag ..unit) @@ -213,13 +213,13 @@ (method.method ..modifier ..decode_frac::name ..decode_frac::type (list) - (#.Some + {#.Some (..risky ($_ _.composite _.aload_0 (_.invokestatic //type.frac "parseDouble" (type.method [(list) (list //type.text) type.double (list)])) (//value.wrap type.double) - ))))) + ))})) (def: .public log! (Bytecode Any) @@ -250,10 +250,10 @@ (method.method ..modifier name ..failure::type (list) - (#.Some + {#.Some ($_ _.composite (..illegal_state_exception message) - _.athrow)))) + _.athrow)})) (def: pm_failure::name "pm_failure") (def: .public pm_failure (..procedure ..pm_failure::name ..failure::type)) @@ -272,7 +272,7 @@ (method.method ..modifier ..push::name ..push::type (list) - (#.Some + {#.Some (let [new_stack_frame! ($_ _.composite _.iconst_2 (_.anewarray //type.value)) @@ -282,7 +282,7 @@ new_stack_frame! (..set! ..stack_head $head) (..set! ..stack_tail $tail) - _.areturn))))) + _.areturn))})) (def: case::name "case") (def: case::type (type.method [(list) (list //type.variant //type.tag //type.flag) //type.value (list)])) @@ -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 @@ -320,7 +320,7 @@ ($_ _.composite ... tag, sumT update_$variant ... tag, sumT - update_$tag ... sub_tag + update_$tag ... sub_tag (_.goto @loop_start)))) super_nested_tag ($_ _.composite @@ -340,15 +340,15 @@ _.dup2 (_.if_icmpeq @tags_match!) _.dup2 (_.if_icmpgt @maybe_nested) $last? (_.ifnull @mismatch!) ... tag, sumT - super_nested ... super_variant + super_nested ... super_variant _.areturn (_.set_label @tags_match!) ... tag, sumT - $last? ... tag, sumT, wants_last? + $last? ... tag, sumT, wants_last? $variant ::last? ... tag, sumT, wants_last?, is_last? (_.if_acmpeq @perfect_match!) ... tag, sumT - (_.set_label @maybe_nested) ... tag, sumT - $variant ::last? ... tag, sumT, last? - (_.ifnull @mismatch!) ... tag, sumT + (_.set_label @maybe_nested) ... tag, sumT + $variant ::last? ... tag, sumT, last? + (_.ifnull @mismatch!) ... tag, sumT (recur @loop) (_.set_label @perfect_match!) ... tag, sumT ... _.pop2 @@ -358,7 +358,7 @@ ... _.pop2 not_found _.areturn - ))))) + ))})) (def: projection_type (type.method [(list) (list //type.tuple //type.offset) //type.value (list)])) @@ -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 @@ -408,12 +408,12 @@ _.areturn (_.set_label @recursive) ... Recursive - (recur @loop))))) + (recur @loop)))}) right_projection::method (method.method ..modifier ..right_projection::name ..projection_type (list) - (#.Some + {#.Some (do _.monad [@loop _.new_label @not_tail _.new_label @@ -443,7 +443,7 @@ (recur @loop) (_.set_label @slice) super_nested - _.areturn))))] + _.areturn))})] [left_projection::method right_projection::method])) @@ -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 @@ -501,7 +501,7 @@ (_.invokevirtual //type.error "printStackTrace" (type.method [(list) (list ^PrintWriter) type.void (list)])) ... W (_.invokevirtual ^StringWriter "toString" (type.method [(list) (list) //type.text (list)])) ... S ..left_injection _.areturn - ))))) + ))})) (def: reflection (All (_ category) @@ -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))] @@ -559,14 +559,14 @@ (_.checkcast //function.class) (_.aload arity) (_.invokevirtual //function.class ..apply::name (..apply::type //function/arity.minimum)) - _.areturn)))))) + _.areturn))}))) (list& (method.method (modifier\composite method.public method.abstract) ..apply::name (..apply::type //function/arity.minimum) (list) #.None))) <init>::method (method.method method.public "<init>" //function.init (list) - (#.Some + {#.Some (let [$partials _.iload_1] ($_ _.composite ..this @@ -574,7 +574,7 @@ ..this $partials (_.putfield //function.class //function/count.field //function/count.type) - _.return)))) + _.return))}) modifier (: (Modifier Class) ($_ modifier\composite class.public 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 c3bb19132..6b1a09aea 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 @@ -32,7 +32,7 @@ #.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 7cc28fb4d..66472f114 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 d21406763..7188a282c 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 @@ -163,20 +163,20 @@ (-> Phase! Phase Archive Path (Operation Statement)) (function (recur pathP) (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (statement expression archive bodyS) #/////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 @@ -190,7 +190,7 @@ then!)))) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -198,7 +198,7 @@ (in [(_.= (|> match <format>) ..peek) then!]))) - (#.Item item))] + {#.Item item})] (in (_.cond clauses ..fail!)))]) ([#/////synthesis.I64_Fork (<| _.int .int)] [#/////synthesis.F64_Fork _.float] @@ -254,10 +254,10 @@ 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/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index 9ed2c2624..a6e448433 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) 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 10be9ba18..29a909d0e 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 @@ -20,7 +20,7 @@ #.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 fae8d8d61..9c16f64cb 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 @@ -72,7 +72,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 +95,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 295d24457..a5532afc3 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 @@ -163,20 +163,20 @@ (Generator! Path) (function (recur pathP) (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (statement expression archive bodyS) #/////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 @@ -190,7 +190,7 @@ then!)))) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -198,7 +198,7 @@ (in [(_.=== (|> match <format>) ..peek) then!]))) - (#.Item item))] + {#.Item item})] (in (_.cond clauses ..fail!)))]) ([#/////synthesis.I64_Fork //primitive.i64] [#/////synthesis.F64_Fork //primitive.f64] @@ -264,10 +264,10 @@ 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/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 0fe181b78..d8a418657 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) 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 69f687713..cb499a364 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 @@ -23,7 +23,7 @@ #.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 86433d927..b691c09d6 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 c4f914d01..6cdabddd0 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 @@ -163,7 +163,7 @@ ($_ _.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,34 +179,34 @@ (-> (-> 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 (in ..fail_pm!))] - (in (#.Some (.if when + (in {#.Some (.if when (_.if ..peek then! else!) (_.if ..peek else! - then!))))) + then!))})) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (\ ! each (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - (#.Item item))] - (in (#.Some (_.cond clauses - ..fail_pm!))))]) + {#.Item item})] + (in {#.Some (_.cond clauses + ..fail_pm!)}))]) ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] [#/////synthesis.F64_Fork (<| //primitive.f64)] [#/////synthesis.Text_Fork (<| //primitive.text)]) @@ -220,18 +220,18 @@ (do [! ///////phase.monad] [?output (primitive_pattern_matching recur pathP)] (.case ?output - (#.Some output) + {#.Some output} (in output) #.None (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (statement expression archive bodyS) #/////synthesis.Pop (///////phase\in ..pop!) - (#/////synthesis.Bind register) + {#/////synthesis.Bind register} (///////phase\in (_.set (list (..register register)) ..peek)) (^template [<complex> <simple> <choice>] @@ -302,10 +302,10 @@ 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]) 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 16283e2e9..c2055e2cc 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 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 3d0903731..5950a81ff 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 @@ -20,7 +20,7 @@ #.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 4a6d95239..4e3e67097 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 83859e8be..15e9c75e5 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 @@ -135,20 +135,20 @@ (Generator Path) (function (recur pathP) (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (expression archive bodyS) #/////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 @@ -162,7 +162,7 @@ then!)))) (^template [<tag> <format> <=>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -170,7 +170,7 @@ (in [(<=> (|> match <format>) ..peek) then!]))) - (#.Item item))] + {#.Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) ..fail! @@ -214,9 +214,9 @@ ..save_cursor! leftO) #.None - (#.Some (..catch ($_ _.then + {#.Some (..catch ($_ _.then ..restore_cursor! - rightO))) + rightO))} #.None))) ))) @@ -226,7 +226,7 @@ [pattern_matching! (pattern_matching' expression archive pathP)] (in (_.try pattern_matching! #.None - (#.Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))) + {#.Some (..catch (_.stop (_.string "Invalid expression for pattern-matching.")))} #.None)))) (def: .public (case expression archive [valueS pathP]) 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 d240e786b..9d2c878cf 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 ea6f59abd..4975c0aec 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 e7d794d5e..246a010c9 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)) @@ -524,9 +524,9 @@ (_.set! value (_.apply (list ..unit) op)) (..right value)) #.None - (#.Some (_.function (list error) + {#.Some (_.function (list error) (..left (_.item (_.string "message") - error)))) + error)))} #.None))) (runtime: (lux::program_args program_args) 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 4d6562a4f..711366595 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 @@ -23,7 +23,7 @@ #.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 4913559a1..49389b109 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 9202b75d3..b9202972d 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 8d19caff8..1e6cb7058 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 @@ -188,34 +188,34 @@ (-> (-> 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 (in ..fail!))] - (in (#.Some (.if when + (in {#.Some (.if when (_.if ..peek then! else!) (_.if ..peek else! - then!))))) + then!))})) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (\ ! each (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - (#.Item item))] - (in (#.Some (_.cond clauses - ..fail!))))]) + {#.Item item})] + (in {#.Some (_.cond clauses + ..fail!)}))]) ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] [#/////synthesis.F64_Fork (<| //primitive.f64)] [#/////synthesis.Text_Fork (<| //primitive.text)]) @@ -229,25 +229,25 @@ (do ///////phase.monad [?output (primitive_pattern_matching recur pathP)] (.case ?output - (#.Some output) + {#.Some output} (in output) #.None (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (statement expression archive bodyS) #/////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 @@ -261,14 +261,14 @@ then!)))) (^template [<tag> <format>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (\ ! each (|>> [(_.= (|> match <format>) ..peek)]) (recur then))) - (#.Item item))] + {#.Item item})] (in (_.cond clauses ..fail!)))]) ([#/////synthesis.I64_Fork (<| //primitive.i64 .int)] 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 108f98020..091d1fd31 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 @@ -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)) 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 c5f424373..643bde0b2 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) 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 a93fba45e..32ec74e4f 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 @@ -20,7 +20,7 @@ #.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 079ef448c..20108a0cd 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 16a00e907..bfdb9bf93 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 @@ -129,20 +129,20 @@ (Generator Path) (function (recur pathP) (.case pathP - (#/////synthesis.Then bodyS) + {#/////synthesis.Then bodyS} (expression archive bodyS) #/////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 @@ -156,7 +156,7 @@ then!)))) (^template [<tag> <format> <=>] - [(<tag> item) + [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) (do ! @@ -164,7 +164,7 @@ (in [(<=> (|> match <format>) ..peek) then!]))) - (#.Item item))] + {#.Item item})] (in (list\mix (function (_ [when then] else) (_.if when then else)) ..fail! 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 d18881c4d..f0d2751f3 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 @@ -76,7 +76,7 @@ @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])) @@ -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/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index 996f552b1..0f8ae8b9a 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)) 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 ad071de02..cc84cf77c 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 @@ -23,7 +23,7 @@ #.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 5b5403a37..faa6739cb 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 @@ -28,18 +28,18 @@ (-> ///analysis.Primitive /.Primitive) (case analysis #///analysis.Unit - (#/.Text /.unit) + {#/.Text /.unit} (^template [<analysis> <synthesis>] - [(<analysis> value) - (<synthesis> value)]) + [{<analysis> value} + {<synthesis> value}]) ([#///analysis.Bit #/.Bit] [#///analysis.Frac #/.F64] [#///analysis.Text #/.Text]) (^template [<analysis> <synthesis>] - [(<analysis> value) - (<synthesis> (.i64 value))]) + [{<analysis> value} + {<synthesis> (.i64 value)}]) ([#///analysis.Nat #/.I64] [#///analysis.Int #/.I64] [#///analysis.Rev #/.I64]))) @@ -48,48 +48,48 @@ 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)))) - (#///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)) 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 d42f0da7e..50b89c2e2 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,25 +31,25 @@ (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 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>] - [(<from> test) + [{<from> test} (///\each (function (_ then) - (<to> [(<conversion> test) then] (list))) + {<to> [(<conversion> test) then] (list)}) thenC)]) ([#///analysis.Nat #/.I64_Fork .i64] [#///analysis.Int #/.I64_Fork .i64] @@ -57,32 +57,32 @@ [#///analysis.Frac #/.F64_Fork |>] [#///analysis.Text #/.Text_Fork |>])) - (#///analysis.Bind register) - (<| (\ ///.monad each (|>> (#/.Seq (#/.Bind register)))) + {#///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)))) @@ -104,74 +104,74 @@ #.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 - (weave new old_right)) + {#/.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] 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 - (weave new_then old_then) - (case [new_else old_else] - [#.None #.None] - #.None - - (^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 - (case new_else - #.None - old_then - - (#.Some new_else) - (weave new_else old_then)) - (#.Some (case old_else - #.None - new_then - - (#.Some old_else) - (weave new_then old_else))))) + {#/.Bit_Fork old_when + (weave new_then old_then) + (case [new_else old_else] + [#.None #.None] + #.None + + (^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 + (case new_else + #.None + old_then + + {#.Some new_else} + (weave new_else old_then)) + {#.Some (case old_else + #.None + new_then + + {#.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))]) + [[{<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]) (^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>)]) @@ -180,7 +180,7 @@ [#/.Member #.Left] [#/.Member #.Right]) - [(#/.Bind newR) (#/.Bind oldR)] + [{#/.Bind newR} {#/.Bind oldR}] (if (n.= newR oldR) old <default>) @@ -196,23 +196,23 @@ <continue> (as_is (recur (++ lefts) tail)) <member> (as_is (if (list.empty? tail) - (#.Right (-- lefts)) - (#.Left lefts)))] + {#.Right (-- lefts)} + {#.Left lefts}))] (case patterns #.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 <continue> @@ -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,7 +257,7 @@ (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) @@ -282,7 +282,7 @@ (^ (!masking @variable @output)) (..synthesize_masking synthesize^ archive inputS @variable @output) - [[(#///analysis.Bind @variable) body] + [[{#///analysis.Bind @variable} body] #.End] (..synthesize_let synthesize^ archive inputS @variable body) @@ -338,26 +338,26 @@ [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 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 +376,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 +423,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 96139976a..278b6343e 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 @@ -85,7 +85,7 @@ (def: (find_foreign environment register) (-> (Environment Synthesis) Register (Operation Synthesis)) (case (list.item register environment) - (#.Some aliased) + {#.Some aliased} (phase\in aliased) #.None @@ -94,30 +94,30 @@ (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) + [{<tag> left right} (do phase.monad [left' (grow_path grow left) right' (grow_path grow right)] - (in (<tag> left' right')))]) + (in {<tag> left' right'}))]) ([#/.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))) + (in {#/.Bit_Fork when then else})) (^template [<tag>] - [(<tag> [[test then] elses]) + [{<tag> [[test then] elses]} (do [! phase.monad] [then (grow_path grow then) elses (monad.each ! (function (_ [else_test else_then]) @@ -125,15 +125,15 @@ [else_then (grow_path grow else_then)] (in [else_test else_then]))) elses)] - (in (<tag> [[test then] elses])))]) + (in {<tag> [[test then] elses]}))]) ([#/.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) @@ -269,7 +269,7 @@ (in (if currying? (/.function/abstraction abstraction) (case (//loop.optimization false 1 (list) abstraction) - (#.Some [startL initsL bodyL]) + {#.Some [startL initsL bodyL]} (/.function/abstraction [#/.environment environment #/.arity (value@ #/.arity abstraction) #/.body (/.loop/scope [startL initsL bodyL])]) 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 3b9d37fdd..c65c261e8 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,30 +30,30 @@ (-> (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) + [{<tag> left right} (do maybe.monad [left' (recur left) right' (recur right)] - (in (<tag> left' right')))]) + (in {<tag> left' right'}))]) ([#/.Alt] [#/.Seq]) - (#/.Bit_Fork when then else) + {#/.Bit_Fork when then else} (do [! maybe.monad] [then (recur then) else (case else - (#.Some else) + {#.Some else} (\ ! each (|>> #.Some) (recur else)) #.None (in #.None))] - (in (#/.Bit_Fork when then else))) + (in {#/.Bit_Fork when then else})) (^template [<tag>] - [(<tag> [[test then] elses]) + [{<tag> [[test then] elses]} (do [! maybe.monad] [then (recur then) elses (monad.each ! (function (_ [else_test else_then]) @@ -61,58 +61,58 @@ [else_then (recur else_then)] (in [else_test else_then]))) elses)] - (in (<tag> [[test then] elses])))]) + (in {<tag> [[test then] elses]}))]) ([#/.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))] (in (|> variant (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)) + {#.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 @@ -165,7 +165,7 @@ [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')) @@ -177,30 +177,30 @@ <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)]))) + (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])) 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 91e229d1a..757bdb4c3 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,133 +39,133 @@ (-> (Remover Synthesis) (Remover Path)) (function (recur path) (case path - (#/.Seq (#/.Bind register) - post) + {#/.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))) + register)} + (recur post)}) - (^or (#/.Seq (#/.Access (#/.Member member)) - (#/.Seq (#/.Bind register) - post)) + (^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)) - post)) + {#/.Seq {#/.Seq {#/.Access {#/.Member member}} + {#/.Bind register}} + post}) (if (n.= redundant register) (recur post) - (#/.Seq (#/.Access (#/.Member member)) - (#/.Seq (#/.Bind (if (n.> redundant register) - (-- register) - register)) - (recur post)))) + {#/.Seq {#/.Access {#/.Member member}} + {#/.Seq {#/.Bind (if (n.> redundant register) + (-- register) + register)} + (recur post)}}) (^template [<tag>] - [(<tag> left right) - (<tag> (recur left) (recur right))]) + [{<tag> left right} + {<tag> (recur left) (recur right)}]) ([#/.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]) - (<tag> [[test (recur then)] + [{<tag> [[test then] tail]} + {<tag> [[test (recur then)] (list\each (function (_ [test' then']) [test' (recur then')]) - tail)])]) + tail)]}]) ([#/.I64_Fork] [#/.F64_Fork] [#/.Text_Fork]) (^or #/.Pop - (#/.Access _)) + {#/.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) - (..prune redundant register) - (recur output)) + {#/.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 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]) + 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)) @@ -198,15 +198,15 @@ (function (recur [redundancy values]) (case values #.End - (#try.Success [redundancy - values]) + {#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]) @@ -221,9 +221,9 @@ (-> Register Redundancy (Try Redundancy)) (case (dictionary.value register redundancy) #.None - (#try.Success (dictionary.has register ..redundant! redundancy)) + {#try.Success (dictionary.has register ..redundant! redundancy)} - (#.Some _) + {#.Some _} (exception.except ..redundant_declaration [register]))) (def: (observe register redundancy) @@ -232,8 +232,8 @@ #.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) @@ -248,26 +248,26 @@ (function (recur [redundancy path]) (case path (^or #/.Pop - (#/.Access _)) - (#try.Success [redundancy - path]) + {#/.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)])) + (in [redundancy {#/.Bit_Fork when then else}])) (^template [<tag> <type>] - [(<tag> [[test then] elses]) + [{<tag> [[test then] elses]} (do [! try.monad] [[redundancy then] (recur [redundancy then]) [redundancy elses] (..list_optimization (: (Optimization [<type> Path]) @@ -276,24 +276,24 @@ [[redundancy else_then] (recur [redundancy else_then])] (in [redundancy [else_test else_then]])))) [redundancy elses])] - (in [redundancy (<tag> [[test then] elses])]))]) + (in [redundancy {<tag> [[test then] elses]}]))]) ([#/.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 - synthesis]))] + (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 f085683fc..6b9fbfd09 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -48,7 +48,7 @@ [program_id (artifact.remember ..name registry)] (in [module_id program_id]))) registries) - (#.Some program_context) + {#.Some program_context} (in program_context) #.None 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 ec444b003..b855ced2f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -171,12 +171,12 @@ ["Text" (%.text text)])) (template: (!failure parser where offset source_code) - [(#.Left [[where offset source_code] - (exception.error ..unrecognized_input [where (%.name (name_of parser)) source_code offset])])]) + [{#.Left [[where offset source_code] + (exception.error ..unrecognized_input [where (%.name (name_of parser)) source_code offset])]}]) (template: (!end_of_file where offset source_code current_module) - [(#.Left [[where offset source_code] - (exception.error ..end_of_file current_module)])]) + [{#.Left [[where offset source_code] + (exception.error ..end_of_file current_module)]}]) (type: (Parser a) (-> Source (Either [Source Text] [Source a]))) @@ -193,10 +193,10 @@ (template: (!letE <binding> <computation> <body>) [(case <computation> - (#.Right <binding>) + {#.Right <binding>} <body> - ... (#.Left error) + ... {#.Left error} <<otherwise>> (:expected <<otherwise>>))]) @@ -227,14 +227,14 @@ (loop [source (: Source [(!forward 1 where) offset source_code]) 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' - [where (<tag> (list.reversed stack))]]) - (#.Left [source' error])))))] + {#.Right [source' + [where {<tag> (list.reversed stack)}]]} + {#.Left [source' error]}))))] ... Form and tuple syntax is mostly the same, differing only in the ... delimiters involved. @@ -250,15 +250,15 @@ (loop [source (: Source [(!forward 1 where) offset source_code]) 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) @@ -266,21 +266,21 @@ body g!_ - (#.Left [[where offset source_code] - (exception.error ..text_cannot_contain_new_lines content)]))]) + {#.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)] + {#.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))) @@ -338,16 +338,16 @@ (!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)]]) + [where {<tag> output}]]} - (#.Left error) - (#.Left [[where <start> <source_code>] - error]))]) + {#.Left error} + {#.Left [[where <start> <source_code>] + error]})]) (def: no_exponent Offset @@ -423,10 +423,10 @@ (signed_parser source_code//size offset where (!++/2 offset) source_code) (!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)])] + (!clip start end source_code)]}] (inline: (name_part_parser start where offset source_code) (-> Nat Location Offset Text (Either [Source Text] [Source Text])) @@ -440,7 +440,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 +456,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,15 +471,15 @@ (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]]))) + complex]]})) <simple>))))) (template: (!full_name_parser @offset @source @where @aliases @tag) [(!letE [source' full_name] (..full_name_parser @aliases @offset @source) - (#.Right [source' [@where (@tag full_name)]]))]) + {#.Right [source' [@where {@tag full_name}]]})]) ... TODO: Grammar macro for specifying syntax. ... (grammar: lux_grammar @@ -492,14 +492,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)) @@ -566,7 +566,7 @@ (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) <comment_parser> (case ("lux text index" (!++ offset/1) (static text.new_line) source_code) - (#.Some end) + {#.Some end} (recur (!vertical where end source_code)) _ 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 2209cdcce..e718a2469 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -54,10 +54,10 @@ (type: .public Primitive (Variant - (#Bit Bit) - (#I64 (I64 Any)) - (#F64 Frac) - (#Text Text))) + {#Bit Bit} + {#I64 (I64 Any)} + {#F64 Frac} + {#Text Text})) (type: .public Side (Either Nat Nat)) @@ -67,8 +67,8 @@ (type: .public Access (Variant - (#Side Side) - (#Member Member))) + {#Side Side} + {#Member Member})) (type: .public (Fork value next) [[value next] (List [value next])]) @@ -76,15 +76,15 @@ (type: .public (Path' s) (Variant #Pop - (#Access Access) - (#Bind Register) - (#Bit_Fork Bit (Path' s) (Maybe (Path' s))) - (#I64_Fork (Fork (I64 Any) (Path' s))) - (#F64_Fork (Fork Frac (Path' s))) - (#Text_Fork (Fork Text (Path' s))) - (#Alt (Path' s) (Path' s)) - (#Seq (Path' s) (Path' s)) - (#Then s))) + {#Access Access} + {#Bind Register} + {#Bit_Fork Bit (Path' s) (Maybe (Path' s))} + {#I64_Fork (Fork (I64 Any) (Path' s))} + {#F64_Fork (Fork Frac (Path' s))} + {#Text_Fork (Fork Text (Path' s))} + {#Alt (Path' s) (Path' s)} + {#Seq (Path' s) (Path' s)} + {#Then s})) (type: .public (Abstraction' s) (Record @@ -99,10 +99,10 @@ (type: .public (Branch s) (Variant - (#Let s Register s) - (#If s s s) - (#Get (List Member) s) - (#Case s (Path' s)))) + {#Let s Register s} + {#If s s s} + {#Get (List Member) s} + {#Case s (Path' s)})) (type: .public (Scope s) (Record @@ -112,28 +112,28 @@ (type: .public (Loop s) (Variant - (#Scope (Scope s)) - (#Recur (List s)))) + {#Scope (Scope s)} + {#Recur (List s)})) (type: .public (Function s) (Variant - (#Abstraction (Abstraction' s)) - (#Apply s (List s)))) + {#Abstraction (Abstraction' s)} + {#Apply s (List s)})) (type: .public (Control s) (Variant - (#Branch (Branch s)) - (#Loop (Loop s)) - (#Function (Function s)))) + {#Branch (Branch s)} + {#Loop (Loop s)} + {#Function (Function s)})) (type: .public Synthesis (Rec Synthesis (Variant - (#Primitive Primitive) - (#Structure (Composite Synthesis)) - (#Reference Reference) - (#Control (Control Synthesis)) - (#Extension (Extension Synthesis))))) + {#Primitive Primitive} + {#Structure (Composite Synthesis)} + {#Reference Reference} + {#Control (Control Synthesis)} + {#Extension (Extension Synthesis)}))) (template [<special> <general>] [(type: .public <special> @@ -165,9 +165,9 @@ (template [<name> <kind> <side>] [(template: .public (<name> content) - [(.<| #..Access - <kind> - <side> + [(.<| {#..Access} + {<kind>} + {<side>} content)])] [side/left #..Side #.Left] @@ -178,7 +178,7 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(<tag> content)])] + [{<tag> content}])] [path/bind #..Bind] [path/then #..Then] @@ -186,7 +186,7 @@ (template [<name> <tag>] [(template: .public (<name> left right) - [(<tag> [left right])])] + [{<tag> left right}])] [path/alt #..Alt] [path/seq #..Seq] @@ -223,7 +223,7 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(#..Primitive (<tag> content))])] + [{#..Primitive {<tag> content}}])] [bit #..Bit] [i64 #..I64] @@ -233,8 +233,8 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(<| #..Structure - <tag> + [(<| {#..Structure} + {<tag>} content)])] [variant #analysis.Variant] @@ -243,7 +243,7 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(.<| #..Reference + [(.<| {#..Reference} <tag> content)])] @@ -255,9 +255,9 @@ (template [<name> <family> <tag>] [(template: .public (<name> content) - [(.<| #..Control - <family> - <tag> + [(.<| {#..Control} + {<family>} + {<tag>} content)])] [branch/case #..Branch #..Case] @@ -278,11 +278,11 @@ #Pop "_" - (#Bit_Fork when then else) + {#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 @@ -290,8 +290,8 @@ ")") (^template [<tag> <format>] - [(<tag> item) - (|> (#.Item item) + [{<tag> item} + (|> {#.Item item} (list\each (function (_ [test then]) (format (<format> test) " " (%path' %then then)))) (text.interposed " ") @@ -300,125 +300,125 @@ [#F64_Fork %.frac] [#Text_Fork %.text]) - (#Access access) + {#Access access} (case access - (#Side side) + {#Side side} (case side - (#.Left lefts) + {#.Left lefts} (format "(" (%.nat lefts) " #0" ")") - (#.Right lefts) + {#.Right lefts} (format "(" (%.nat lefts) " #1" ")")) - (#Member member) + {#Member member} (case member - (#.Left lefts) + {#.Left lefts} (format "[" (%.nat lefts) " #0" "]") - (#.Right lefts) + {#.Right lefts} (format "[" (%.nat lefts) " #1" "]"))) - (#Bind register) + {#Bind register} (format "(@ " (%.nat register) ")") - (#Alt left right) + {#Alt left right} (format "(Variant " (%path' %then left) " " (%path' %then right) ")") - (#Seq left right) + {#Seq left right} (format "(Tuple " (%path' %then left) " " (%path' %then right) ")") - (#Then then) + {#Then then} (|> (%then then) (text.enclosed ["(! " ")"])))) (def: .public (%synthesis value) (Format Synthesis) (case value - (#Primitive primitive) + {#Primitive primitive} (case primitive (^template [<pattern> <format>] - [(<pattern> value) + [{<pattern> value} (<format> value)]) ([#Bit %.bit] [#F64 %.frac] [#Text %.text]) - (#I64 value) + {#I64 value} (%.int (.int value))) - (#Structure structure) + {#Structure structure} (case structure - (#analysis.Variant [lefts right? content]) + {#analysis.Variant [lefts right? content]} (|> (%synthesis content) (format (%.nat lefts) " " (%.bit right?) " ") - (text.enclosed ["(" ")"])) + (text.enclosed ["{" "}"])) - (#analysis.Tuple members) + {#analysis.Tuple members} (|> members (list\each %synthesis) (text.interposed " ") (text.enclosed ["[" "]"]))) - (#Reference reference) + {#Reference reference} (reference.format reference) - (#Control control) + {#Control control} (case control - (#Function function) + {#Function function} (case function - (#Abstraction [environment arity body]) + {#Abstraction [environment arity body]} (let [environment' (|> environment (list\each %synthesis) (text.interposed " ") (text.enclosed ["[" "]"]))] (|> (format environment' " " (%.nat arity) " " (%synthesis body)) - (text.enclosed ["(#function " ")"]))) + (text.enclosed ["{#function " "}"]))) - (#Apply func args) + {#Apply func args} (|> args (list\each %synthesis) (text.interposed " ") (format (%synthesis func) " ") (text.enclosed ["(" ")"]))) - (#Branch branch) + {#Branch branch} (case branch - (#Let input register body) + {#Let input register body} (|> (format (%.nat register) " " (%synthesis input) " " (%synthesis body)) - (text.enclosed ["(#let " ")"])) + (text.enclosed ["{#let " "}"])) - (#If test then else) + {#If test then else} (|> (format (%synthesis test) " " (%synthesis then) " " (%synthesis else)) - (text.enclosed ["(#if " ")"])) + (text.enclosed ["{#if " "}"])) - (#Get members record) + {#Get members record} (|> (format (%.list (%path' %synthesis) (list\each (|>> #Member #Access) members)) " " (%synthesis record)) - (text.enclosed ["(#get " ")"])) + (text.enclosed ["{#get " "}"])) - (#Case input path) + {#Case input path} (|> (format (%synthesis input) " " (%path' %synthesis path)) - (text.enclosed ["(#case " ")"]))) + (text.enclosed ["{#case " "}"]))) - (#Loop loop) + {#Loop loop} (case loop - (#Scope scope) + {#Scope scope} (|> (format (%.nat (value@ #start scope)) " " (|> (value@ #inits scope) (list\each %synthesis) (text.interposed " ") (text.enclosed ["[" "]"])) " " (%synthesis (value@ #iteration scope))) - (text.enclosed ["(#loop " ")"])) + (text.enclosed ["{#loop " "}"])) - (#Recur args) + {#Recur args} (|> args (list\each %synthesis) (text.interposed " ") - (text.enclosed ["(#recur " ")"])))) + (text.enclosed ["{#recur " "}"])))) - (#Extension [name args]) + {#Extension [name args]} (|> (list\each %synthesis args) (text.interposed " ") (format (%.text name) " ") @@ -434,13 +434,13 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <eq> <format>] - [[(<tag> reference') (<tag> sample')] + [[{<tag> reference'} {<tag> sample'}] (<eq> reference' sample')]) ([#Bit bit\= %.bit] [#F64 f.= %.frac] [#Text text\= %.text]) - [(#I64 reference') (#I64 sample')] + [{#I64 reference'} {#I64 sample'}] (i.= (.int reference') (.int sample')) _ @@ -453,7 +453,7 @@ (def: hash (|>> (case> (^template [<tag> <hash>] - [(<tag> value') + [{<tag> value'} (\ <hash> hash value')]) ([#Bit bit.hash] [#F64 f.hash] @@ -478,7 +478,7 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [[(<tag> reference) (<tag> sample)] + [[{<tag> reference} {<tag> sample}] (\ <equivalence> = reference sample)]) ([#Side ..side_equivalence] [#Member ..member_equivalence]) @@ -495,7 +495,7 @@ (let [sub_hash (sum.hash n.hash n.hash)] (case value (^template [<tag>] - [(<tag> value) + [{<tag> value} (\ sub_hash hash value)]) ([#Side] [#Member]))))) @@ -508,33 +508,33 @@ [#Pop #Pop] true - [(#Bit_Fork reference_when reference_then reference_else) - (#Bit_Fork sample_when sample_then sample_else)] + [{#Bit_Fork reference_when reference_then reference_else} + {#Bit_Fork sample_when sample_then sample_else}] (and (bit\= reference_when sample_when) (= reference_then sample_then) (\ (maybe.equivalence =) = reference_else sample_else)) (^template [<tag> <equivalence>] - [[(<tag> reference_item) - (<tag> sample_item)] + [[{<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]) (^template [<tag> <equivalence>] - [[(<tag> reference') (<tag> sample')] + [[{<tag> reference'} {<tag> sample'}] (\ <equivalence> = reference' sample')]) ([#Access ..access_equivalence] [#Then equivalence]) - [(#Bind reference') (#Bind sample')] + [{#Bind reference'} {#Bind sample'}] (n.= reference' sample') (^template [<tag>] - [[(<tag> leftR rightR) (<tag> leftS rightS)] + [[{<tag> leftR rightR} {<tag> leftS rightS}] (and (= leftR leftS) (= rightR rightS))]) ([#Alt] @@ -554,20 +554,20 @@ #Pop 2 - (#Access access) + {#Access access} (n.* 3 (\ ..access_hash hash access)) - (#Bind register) + {#Bind register} (n.* 5 (\ n.hash hash register)) - (#Bit_Fork when then else) + {#Bit_Fork when then else} ($_ n.* 7 (\ bit.hash hash when) (hash then) (\ (maybe.hash (path'_hash super)) hash else)) (^template [<factor> <tag> <hash>] - [(<tag> item) + [{<tag> item} (let [case_hash (product.hash <hash> (path'_hash super)) item_hash (product.hash case_hash (list.hash case_hash))] @@ -577,14 +577,14 @@ [17 #Text_Fork text.hash]) (^template [<factor> <tag>] - [(<tag> fork) + [{<tag> fork} (let [recur_hash (path'_hash super) fork_hash (product.hash recur_hash recur_hash)] (n.* <factor> (\ fork_hash hash fork)))]) ([19 #Alt] [23 #Seq]) - (#Then body) + {#Then body} (n.* 29 (\ super hash body)) ))) @@ -593,25 +593,25 @@ (def: (= reference sample) (case [reference sample] - [(#Let [reference_input reference_register reference_body]) - (#Let [sample_input sample_register sample_body])] + [{#Let [reference_input reference_register reference_body]} + {#Let [sample_input sample_register sample_body]}] (and (\= reference_input sample_input) (n.= reference_register sample_register) (\= reference_body sample_body)) - [(#If [reference_test reference_then reference_else]) - (#If [sample_test sample_then sample_else])] + [{#If [reference_test reference_then reference_else]} + {#If [sample_test sample_then sample_else]}] (and (\= reference_test sample_test) (\= reference_then sample_then) (\= reference_else sample_else)) - [(#Get [reference_path reference_record]) - (#Get [sample_path sample_record])] + [{#Get [reference_path reference_record]} + {#Get [sample_path sample_record]}] (and (\ (list.equivalence ..member_equivalence) = reference_path sample_path) (\= reference_record sample_record)) - [(#Case [reference_input reference_path]) - (#Case [sample_input sample_path])] + [{#Case [reference_input reference_path]} + {#Case [sample_input sample_path]}] (and (\= reference_input sample_input) (\ (path'_equivalence \=) = reference_path sample_path)) @@ -626,24 +626,24 @@ (def: (hash value) (case value - (#Let [input register body]) + {#Let [input register body]} ($_ n.* 2 (\ super hash input) (\ n.hash hash register) (\ super hash body)) - (#If [test then else]) + {#If [test then else]} ($_ n.* 3 (\ super hash test) (\ super hash then) (\ super hash else)) - (#Get [path record]) + {#Get [path record]} ($_ n.* 5 (\ (list.hash ..member_hash) hash path) (\ super hash record)) - (#Case [input path]) + {#Case [input path]} ($_ n.* 7 (\ super hash input) (\ (..path'_hash super) hash path)) @@ -654,13 +654,13 @@ (def: (= reference sample) (case [reference sample] - [(#Scope [reference_start reference_inits reference_iteration]) - (#Scope [sample_start sample_inits sample_iteration])] + [{#Scope [reference_start reference_inits reference_iteration]} + {#Scope [sample_start sample_inits sample_iteration]}] (and (n.= reference_start sample_start) (\ (list.equivalence \=) = reference_inits sample_inits) (\= reference_iteration sample_iteration)) - [(#Recur reference) (#Recur sample)] + [{#Recur reference} {#Recur sample}] (\ (list.equivalence \=) = reference sample) _ @@ -674,13 +674,13 @@ (def: (hash value) (case value - (#Scope [start inits iteration]) + {#Scope [start inits iteration]} ($_ n.* 2 (\ n.hash hash start) (\ (list.hash super) hash inits) (\ super hash iteration)) - (#Recur resets) + {#Recur resets} ($_ n.* 3 (\ (list.hash super) hash resets)) ))) @@ -690,14 +690,14 @@ (def: (= reference sample) (case [reference sample] - [(#Abstraction [reference_environment reference_arity reference_body]) - (#Abstraction [sample_environment sample_arity sample_body])] + [{#Abstraction [reference_environment reference_arity reference_body]} + {#Abstraction [sample_environment sample_arity sample_body]}] (and (\ (list.equivalence \=) = reference_environment sample_environment) (n.= reference_arity sample_arity) (\= reference_body sample_body)) - [(#Apply [reference_abstraction reference_arguments]) - (#Apply [sample_abstraction sample_arguments])] + [{#Apply [reference_abstraction reference_arguments]} + {#Apply [sample_abstraction sample_arguments]}] (and (\= reference_abstraction sample_abstraction) (\ (list.equivalence \=) = reference_arguments sample_arguments)) @@ -712,13 +712,13 @@ (def: (hash value) (case value - (#Abstraction [environment arity body]) + {#Abstraction [environment arity body]} ($_ n.* 2 (\ (list.hash super) hash environment) (\ n.hash hash arity) (\ super hash body)) - (#Apply [abstraction arguments]) + {#Apply [abstraction arguments]} ($_ n.* 3 (\ super hash abstraction) (\ (list.hash super) hash arguments)) @@ -730,7 +730,7 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [[(<tag> reference) (<tag> sample)] + [[{<tag> reference} {<tag> sample}] (\ (<equivalence> \=) = reference sample)]) ([#Branch ..branch_equivalence] [#Loop ..loop_equivalence] @@ -748,7 +748,7 @@ (def: (hash value) (case value (^template [<factor> <tag> <hash>] - [(<tag> value) + [{<tag> value} (n.* <factor> (\ (<hash> super) hash value))]) ([2 #Branch ..branch_hash] [3 #Loop ..loop_hash] @@ -761,7 +761,7 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [[(<tag> reference') (<tag> sample')] + [[{<tag> reference'} {<tag> sample'}] (\ <equivalence> = reference' sample')]) ([#Primitive ..primitive_equivalence] [#Structure (analysis.composite_equivalence =)] @@ -785,7 +785,7 @@ (let [recur_hash [..equivalence hash]] (case value (^template [<tag> <hash>] - [(<tag> value) + [{<tag> value} (\ <hash> hash value)]) ([#Primitive ..primitive_hash] [#Structure (analysis.composite_hash recur_hash)] @@ -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. diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index d7d2fe237..83bbc51e9 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -92,8 +92,8 @@ (-> Module Archive (Try ID)) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.value module resolver) - (#.Some [id _]) - (#try.Success id) + {#.Some [id _]} + {#try.Success id} #.None (exception.except ..unknown_document [module @@ -103,31 +103,31 @@ (-> Module Archive (Try [ID Archive])) (let [(^slots [#..next #..resolver]) (:representation archive)] (case (dictionary.value module resolver) - (#.Some _) + {#.Some _} (exception.except ..module_has_already_been_reserved [module]) #.None - (#try.Success [next + {#try.Success [next (|> archive :representation (revised@ #..resolver (dictionary.has module [next #.None])) (revised@ #..next ++) - :abstraction)])))) + :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 + {#.Some [id #.None]} + {#try.Success (|> archive :representation - (revised@ #..resolver (dictionary.has module [id (#.Some [descriptor document output])])) - :abstraction)) + (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 @@ -137,10 +137,10 @@ (-> Module Archive (Try [Descriptor (Document Any) Output])) (let [(^slots [#..resolver]) (:representation archive)] (case (dictionary.value module resolver) - (#.Some [id (#.Some entry)]) - (#try.Success entry) + {#.Some [id {#.Some entry}]} + {#try.Success entry} - (#.Some [id #.None]) + {#.Some [id #.None]} (exception.except ..module_is_only_reserved [module]) #.None @@ -150,10 +150,10 @@ (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,14 +163,14 @@ dictionary.entries (list.all (function (_ [module [id descriptor+document]]) (case descriptor+document - (#.Some _) (#.Some module) + {#.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 _]) + {#.Some [id _]} bit.yes #.None @@ -199,7 +199,7 @@ (revised@ #resolver (function (_ resolver) (list\mix (function (_ [module [id entry]] resolver) (case entry - (#.Some _) + {#.Some _} (dictionary.has module [id entry] resolver) #.None @@ -235,7 +235,7 @@ dictionary.entries (list.all (function (_ [module [id descriptor+document]]) (case descriptor+document - (#.Some _) (#.Some [module id]) + {#.Some _} {#.Some [module id]} #.None #.None))) [version next] (binary.result ..writer)))) 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 a9851c301..6c2662602 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -27,12 +27,12 @@ (type: .public Category (Variant #Anonymous - (#Definition Text) - (#Analyser Text) - (#Synthesizer Text) - (#Generator Text) - (#Directive Text) - (#Custom Text))) + {#Definition Text} + {#Analyser Text} + {#Synthesizer Text} + {#Generator Text} + {#Directive Text} + {#Custom Text})) (type: .public Artifact (Record @@ -75,7 +75,7 @@ (|> registry :representation (revised@ #artifacts (row.suffix [#id id - #category (<tag> name)])) + #category {<tag> name}])) (revised@ #resolver (dictionary.has name id)) :abstraction)])) @@ -86,7 +86,7 @@ (value@ #artifacts) row.list (list.all (|>> (value@ #category) - (case> (<tag> name) (#.Some name) + (case> {<tag> name} {#.Some name} _ #.None)))))] [#Definition definition definitions] @@ -109,7 +109,7 @@ (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 +135,7 @@ [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] @@ -153,7 +153,7 @@ (..resource registry) (^template [<tag> <create>] - [(<tag> name) + [{<tag> name} (<create> name registry)]) ([#Definition ..definition] [#Analyser ..analyser] 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 3fcf381d3..96d5a9922 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -37,12 +37,12 @@ (if (\ signature.equivalence = (key.signature key) document//signature) - (#try.Success (:sharing [e] + {#try.Success (:sharing [e] (Key e) key e - (:expected document//content))) + (:expected document//content))} (exception.except ..invalid_signature [(key.signature key) document//signature])))) 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 e839651e4..f586c398a 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]) + {#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 1d7baccbd..fe1e8d223 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -95,7 +95,7 @@ (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]))))))))) @@ -223,7 +223,7 @@ 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] @@ -240,7 +240,7 @@ directives] output])) - (#artifact.Definition name) + {#artifact.Definition name} (let [output (row.suffix [artifact_id #.None data] output)] (if (text\= $/program.name name) (in [definitions @@ -258,7 +258,7 @@ 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)] @@ -269,7 +269,7 @@ 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)] @@ -280,7 +280,7 @@ 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)] @@ -291,7 +291,7 @@ 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)] @@ -302,48 +302,48 @@ (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]))))) + {#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)])]) + [{<tag> payload} + (in [def_name {<tag> payload}])]) ([#.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])]))))) + [def_name {#.Type [exported? (:as .Type def_value) labels]}]))))) (value@ #.definitions content))] (in [(document.write $.key (with@ #.definitions definitions content)) bundles]))) @@ -388,7 +388,7 @@ (|>> (list.all (function (_ [valid_cache? [module_name [module_id _]]]) (if valid_cache? #.None - (#.Some [module_name module_id])))) + {#.Some [module_name module_id]}))) (dictionary.of_list text.hash))) (def: (full_purge caches load_order) @@ -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 + {#try.Failure error} + (in {#try.Success [archive.empty (fresh_analysis_state (value@ #static.host static)) - ..empty_bundles]))))) + ..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 af43ef991..69a0858e6 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -61,12 +61,12 @@ #.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,14 +97,14 @@ (-> 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 (let [path (format module ..lux_extension)] (case (dictionary.value path import) - (#.Some data) - (#try.Success [path data]) + {#.Some data} + {#try.Success [path data]} #.None (exception.except ..cannot_find_module [importer 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) + {#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/jvm.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux index f8bb67b70..75eca1c30 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/jvm.lux @@ -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 (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 b471a30f5..c78d07b6f 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -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 3f6caddbf..4809e8ed9 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) @@ -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 4e48f1db9..0f345a12f 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -21,8 +21,8 @@ (type: .public Reference (Variant - (#Variable Variable) - (#Constant Constant))) + {#Variable Variable} + {#Constant Constant})) (implementation: .public equivalence (Equivalence Reference) @@ -30,7 +30,7 @@ (def: (= reference sample) (case [reference sample] (^template [<tag> <equivalence>] - [[(<tag> reference) (<tag> sample)] + [[{<tag> reference} {<tag> sample}] (\ <equivalence> = reference sample)]) ([#Variable /variable.equivalence] [#Constant name.equivalence]) @@ -47,7 +47,7 @@ (def: (hash value) (case value (^template [<factor> <tag> <hash>] - [(<tag> value) + [{<tag> value} ($_ n.* <factor> (\ <hash> hash value))]) ([2 #Variable /variable.hash] @@ -57,7 +57,7 @@ (template [<name> <family> <tag>] [(template: .public (<name> content) [(<| <family> - <tag> + {<tag>} content)])] [local #..Variable #/variable.Local] @@ -66,7 +66,7 @@ (template [<name> <tag>] [(template: .public (<name> content) - [(<| <tag> + [(<| {<tag>} content)])] [variable #..Variable] @@ -79,8 +79,8 @@ (def: .public format (Format Reference) - (|>> (case> (#Variable variable) + (|>> (case> {#Variable variable} (/variable.format variable) - (#Constant constant) + {#Constant constant} (%.name constant)))) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index eea52b976..bde1de15b 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -19,8 +19,8 @@ (type: .public Variable (Variant - (#Local Register) - (#Foreign Register))) + {#Local Register} + {#Foreign Register})) (implementation: .public equivalence (Equivalence Variable) @@ -28,7 +28,7 @@ (def: (= reference sample) (case [reference sample] (^template [<tag>] - [[(<tag> reference') (<tag> sample')] + [[{<tag> reference'} {<tag> sample'}] (n.= reference' sample')]) ([#Local] [#Foreign]) @@ -43,14 +43,14 @@ (def: hash (|>> (case> (^template [<factor> <tag>] - [(<tag> register) + [{<tag> register} ($_ n.* <factor> (\ n.hash hash register))]) ([2 #Local] [3 #Foreign]))))) (template: .public (self) - [(#..Local 0)]) + [{#..Local 0}]) (def: .public self? (-> Variable Bit) @@ -62,8 +62,8 @@ (def: .public format (Format Variable) - (|>> (case> (#Local local) + (|>> (case> {#Local local} (%.format "+" (%.nat local)) - (#Foreign foreign) + {#Foreign foreign} (%.format "-" (%.nat foreign))))) |