diff options
author | Eduardo Julian | 2022-03-15 07:24:35 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-03-15 07:24:35 -0400 |
commit | bc36487224f670c23002cc4575c0dba3e5dc1be1 (patch) | |
tree | 01601f7e5d992ace77a16cfa90240ffc4511a7af /stdlib/source/library/lux/tool/compiler | |
parent | 4ef1ac1dfe0edd1a11bb7f1fd13c8b6cb8f1bab4 (diff) |
De-sigil-ification: ^
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
65 files changed, 1052 insertions, 960 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux index b3a2f635f..4ee608dd2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/complex.lux @@ -49,7 +49,7 @@ [(..lefts right? pick) right?])) -(implementation: .public (equivalence (^open "/#[0]")) +(implementation: .public (equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Complex a)))) (def: (= reference sample) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux index 71bc09f77..34840bbea 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -17,6 +17,7 @@ ["[0]" dictionary {"+" Dictionary}] ["[0]" set {"+" Set} ("[1]#[0]" equivalence)]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -89,7 +90,7 @@ [{#Bit sideR} {#Bit sideS}] (bit#= sideR sideS) - (^template [<tag>] + (^.template [<tag>] [[{<tag> partialR} {<tag> partialS}] (set#= partialR partialS)]) ([#Nat] @@ -125,7 +126,7 @@ {#Bit it} (%.bit it) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> it} (|> it set.list @@ -164,13 +165,13 @@ (def: .public (coverage pattern) (-> Pattern (Try Coverage)) (case pattern - (^or {//pattern.#Simple {//simple.#Unit}} - {//pattern.#Bind _}) + (^.or {//pattern.#Simple {//simple.#Unit}} + {//pattern.#Bind _}) {try.#Success {#Exhaustive}} ... Simple patterns (other than unit/[]) always have partial coverage because there ... are too many possibilities as far as values go. - (^template [<from> <to> <hash>] + (^.template [<from> <to> <hash>] [{//pattern.#Simple {<from> it}} {try.#Success {<to> (set.of_list <hash> (list it))}}]) ([//simple.#Nat #Nat n.hash] @@ -189,7 +190,7 @@ ... their sub-patterns. {//pattern.#Complex {//complex.#Tuple membersP+}} (case (list.reversed membersP+) - (^or (^ (list)) (^ (list _))) + (^.or (pattern (list)) (pattern (list _))) (exception.except ..invalid_tuple [(list.size membersP+)]) {.#Item lastP prevsP+} @@ -273,7 +274,7 @@ {try.#Success {#Exhaustive}} <redundancy>) - (^template [<tag>] + (^.template [<tag>] [[{<tag> partialA} {<tag> partialSF}] (if (set.empty? (set.intersection partialA partialSF)) {try.#Success {<tag> (set.union partialA partialSF)}} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux index 4b18f2874..92435a3ae 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/inference.lux @@ -15,6 +15,7 @@ [collection ["[0]" list ("[1]#[0]" functor monoid)]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -59,7 +60,7 @@ {.#Primitive name co_variant} {.#Primitive name (list#each (quantified @var @parameter) co_variant)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (quantified @var @parameter left) (quantified @var @parameter right)}]) @@ -73,16 +74,16 @@ {.#Parameter @parameter} :it:) - (^template [<tag>] + (^.template [<tag>] [{<tag> env body} {<tag> (list#each (quantified @var @parameter) env) (quantified @var (n.+ 2 @parameter) body)}]) ([.#UnivQ] [.#ExQ]) - (^or {.#Parameter _} - {.#Ex _} - {.#Named _}) + (^.or {.#Parameter _} + {.#Ex _} + {.#Named _}) :it:)) ... Type-inference works by applying some (potentially quantified) type @@ -159,7 +160,7 @@ [[just_before vars :inference: terms] (general' (list) archive analyse inferT args)] (in [:inference: terms]) ... (case vars - ... (^ (list)) + ... (pattern (list)) ... (in [:inference: terms]) ... _ @@ -191,19 +192,19 @@ (-> Nat Type Type Type) (function (again it) (case it - (^or {.#Parameter index} - {.#Apply {.#Primitive "" {.#End}} - {.#Parameter index}}) + (^.or {.#Parameter index} + {.#Apply {.#Primitive "" {.#End}} + {.#Parameter index}}) (if (n.= @self index) recursion it) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^template [<tag>] + (^.template [<tag>] [{<tag> environment quantified} {<tag> (list#each again environment) (with_recursion (n.+ 2 @self) recursion quantified)}]) @@ -230,7 +231,7 @@ {.#Named name it} (again depth it) - (^template [<tag>] + (^.template [<tag>] [{<tag> env it} (phase#each (|>> {<tag> env}) (again (++ depth) it))]) 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 98fb50427..d86eab516 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 @@ -49,7 +49,7 @@ (do meta.monad [expansion (..expansion expander name macro inputs)] (case expansion - (^ (list single)) + (pattern (list single)) (in single) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux index 192e6552f..b7518ded0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/simple.lux @@ -7,6 +7,8 @@ ["[0]" bit ("[1]#[0]" equivalence)] ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -32,7 +34,7 @@ [{#Unit} {#Unit}] true - (^template [<tag> <=>] + (^.template [<tag> <=>] [[{<tag> reference} {<tag> sample}] (<=> reference sample)]) ([#Bit bit#=] @@ -51,7 +53,7 @@ {#Unit} "[]" - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> value} (<format> value)]) ([#Bit %.bit] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux index f8002874f..724d85a24 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux @@ -12,6 +12,8 @@ ["%" format {"+" format}]] [collection ["[0]" list]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -26,7 +28,7 @@ (def: .public (check action) (All (_ a) (-> (Check a) (Operation a))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (action (the .#type_context state)) {try.#Success [context' output]} {try.#Success [[bundle (has .#type_context context' state)] 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 e439110f9..cb2710a6b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -17,6 +17,7 @@ ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set {"+" Set}]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -135,7 +136,7 @@ (def: .public <get> (All (_ anchor expression directive) (Operation anchor expression directive <get_type>)) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (the <tag> state) {.#Some output} {try.#Success [stateE output]} @@ -168,7 +169,7 @@ (def: .public get_registry (All (_ anchor expression directive) (Operation anchor expression directive Registry)) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) {try.#Success [stateE (the #registry state)]})) (def: .public (set_registry value) @@ -204,7 +205,7 @@ (def: .public (evaluate! label code) (All (_ anchor expression directive) (-> unit.ID [(Maybe unit.ID) expression] (Operation anchor expression directive Any))) - (function (_ (^let state+ [bundle state])) + (function (_ (^.let state+ [bundle state])) (case (# (the #host state) evaluate label code) {try.#Success output} {try.#Success [state+ output]} @@ -215,7 +216,7 @@ (def: .public (execute! code) (All (_ anchor expression directive) (-> directive (Operation anchor expression directive Any))) - (function (_ (^let state+ [bundle state])) + (function (_ (^.let state+ [bundle state])) (case (# (the #host state) execute code) {try.#Success output} {try.#Success [state+ output]} @@ -226,7 +227,7 @@ (def: .public (define! context custom code) (All (_ anchor expression directive) (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Operation anchor expression directive [Text Any directive]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (# (the #host state) define context custom code) {try.#Success output} {try.#Success [stateE output]} @@ -253,7 +254,7 @@ [(`` (def: .public (<name> it (~~ (template.spliced <inputs>)) dependencies) (All (_ anchor expression directive) (-> <type> (~~ (template.spliced <input_types>)) (Set unit.ID) (Operation anchor expression directive artifact.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[id registry'] (<artifact> it <mandatory?> dependencies (the #registry state))] {try.#Success [[bundle (has #registry registry' state)] id]}))))] @@ -276,7 +277,7 @@ (def: .public (remember archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive unit.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) @@ -295,7 +296,7 @@ (def: .public (definition archive name) (All (_ anchor expression directive) (-> Archive Symbol (Operation anchor expression directive [unit.ID (Maybe category.Definition)]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[_module _name] name] (do try.monad [@module (archive.id _module archive) @@ -316,7 +317,7 @@ (def: .public (module_id module archive) (All (_ anchor expression directive) (-> descriptor.Module Archive (Operation anchor expression directive module.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (do try.monad [@module (archive.id module archive)] (in [stateE @module])))) @@ -324,7 +325,7 @@ (def: .public (context archive) (All (_ anchor expression directive) (-> Archive (Operation anchor expression directive unit.ID))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (the #context state) {.#None} (exception.except ..no_context []) @@ -360,7 +361,7 @@ (All (_ anchor expression directive a) (-> Archive (Set unit.ID) (Operation anchor expression directive a) (Operation anchor expression directive [unit.ID a]))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (let [[@artifact registry'] (registry.resource false dependencies (the #registry state)) @artifact (n.+ @artifact (the #registry_shift state))] (do try.monad 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 085e071a7..8d66cfd79 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 @@ -11,6 +11,7 @@ [collection ["[0]" list]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -42,7 +43,7 @@ (template: (variant_analysis analysis archive tag values) ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) [(case values - (^ (list value)) + (pattern (list value)) (/complex.variant analysis tag archive value) _ @@ -51,7 +52,7 @@ (template: (sum_analysis analysis archive lefts right? values) ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) [(case values - (^ (list value)) + (pattern (list value)) (/complex.sum analysis lefts right? archive value) _ @@ -72,7 +73,7 @@ [[functionT functionA] (/type.inferring (analysis archive functionC))] (case functionA - (^ (/.constant def_name)) + (pattern (/.constant def_name)) (do ! [?macro (//extension.lifted (meta.macro def_name))] (case ?macro @@ -95,7 +96,7 @@ ... of having useful error messages. (/.with_location location) (case code - (^template [<tag> <analyser>] + (^.template [<tag> <analyser>] [[_ {<tag> value}] (<analyser> value)]) ([.#Symbol /reference.reference] @@ -106,25 +107,25 @@ [.#Int /simple.int] [.#Rev /simple.rev]) - (^code [(~+ elems)]) + (^.` [(~+ elems)]) (/complex.record analysis archive elems) - (^code {(~ [_ {.#Symbol tag}]) (~+ values)}) + (^.` {(~ [_ {.#Symbol tag}]) (~+ values)}) (..variant_analysis analysis archive tag values) - (^code ({(~+ branches)} (~ input))) + (^.` ({(~+ branches)} (~ input))) (..case_analysis analysis archive input branches code) - (^code ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body))) + (^.` ([(~ [_ {.#Symbol ["" function_name]}]) (~ [_ {.#Symbol ["" arg_name]}])] (~ body))) (/function.function analysis function_name arg_name archive body) - (^code ((~ [_ {.#Text extension_name}]) (~+ extension_args))) + (^.` ((~ [_ {.#Text extension_name}]) (~+ extension_args))) (//extension.apply archive analysis [extension_name extension_args]) - (^code ((~ functionC) (~+ argsC+))) + (^.` ((~ functionC) (~+ argsC+))) (..apply_analysis expander analysis archive functionC argsC+) - (^code {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)}) + (^.` {(~ [_ {.#Nat lefts}]) (~ [_ {.#Bit right?}]) (~+ values)}) (..sum_analysis analysis archive lefts right? values) _ 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 fa5dd353a..8643a435a 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 @@ -18,6 +18,7 @@ [number ["n" nat]]] [macro + ["^" pattern] ["[0]" code]] ["[0]" type ["[0]" check {"+" Check}]]]] @@ -232,7 +233,7 @@ idx /scope.next] (in [{/pattern.#Bind idx} outputA]))) - (^template [<type> <input> <output>] + (^.template [<type> <input> <output>] [[location <input>] (simple_pattern_analysis <type> :input: location {/pattern.#Simple <output>} next)]) ([Bit {.#Bit pattern_value} {/simple.#Bit pattern_value}] @@ -243,7 +244,7 @@ [Text {.#Text pattern_value} {/simple.#Text pattern_value}] [Any {.#Tuple {.#End}} {/simple.#Unit}]) - (^ [location {.#Tuple (list singleton)}]) + (pattern [location {.#Tuple (list singleton)}]) (pattern_analysis {.#None} :input: singleton next) [location {.#Tuple sub_patterns}] @@ -271,7 +272,7 @@ _ (in []))] (.case members - (^ (list singleton)) + (pattern (list singleton)) (pattern_analysis {.#None} :input: singleton next) _ @@ -280,7 +281,7 @@ {.#None} (..tuple_pattern_analysis pattern_analysis :input: sub_patterns next)))) - (^ [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) + (pattern [location {.#Variant (list& [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) (/.with_location location (do ///.monad [[@ex_var+ :input:'] (/type.check (..tuple :input:))] @@ -291,8 +292,8 @@ num_cases (maybe.else size_sum num_tags) idx (/complex.tag right? lefts)] (.case (list.item idx flat_sum) - (^multi {.#Some caseT} - (n.< num_cases idx)) + (^.multi {.#Some caseT} + (n.< num_cases idx)) (do ///.monad [[testP nextA] (if (and (n.> num_cases size_sum) (n.= (-- num_cases) idx)) @@ -321,7 +322,7 @@ _ (/.except ..mismatch [:input:' pattern])))) - (^ [location {.#Variant (list& [_ {.#Symbol tag}] values)}]) + (pattern [location {.#Variant (list& [_ {.#Symbol tag}] values)}]) (/.with_location location (do ///.monad [tag (///extension.lifted (meta.normal tag)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index 669f4f59a..8c9407a1b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -296,14 +296,14 @@ output (: (List [Symbol Code]) {.#End})] (case input - (^ (list& [_ {.#Symbol ["" slotH]}] valueH tail)) + (pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail)) (if pattern_matching? (///#in {.#None}) (do ///.monad [slotH (///extension.lifted (meta.normal ["" slotH]))] (again tail {.#Item [slotH valueH] output}))) - (^ (list& [_ {.#Symbol slotH}] valueH tail)) + (pattern (list& [_ {.#Symbol slotH}] valueH tail)) (do ///.monad [slotH (///extension.lifted (meta.normal slotH))] (again tail {.#Item [slotH valueH] output})) @@ -388,13 +388,13 @@ (def: .public (record analyse archive members) (-> Phase Archive (List Code) (Operation Analysis)) (case members - (^ (list)) + (pattern (list)) //simple.unit - (^ (list singletonC)) + (pattern (list singletonC)) (analyse archive singletonC) - (^ (list [_ {.#Symbol pseudo_slot}] singletonC)) + (pattern (list [_ {.#Symbol pseudo_slot}] singletonC)) (do [! ///.monad] [head_k (///extension.lifted (meta.normal pseudo_slot)) slot (///extension.lifted (meta.try (meta.slot head_k)))] 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 f38a33f0d..f0f08dfcf 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 @@ -1,14 +1,16 @@ (.using [library [lux "*" + ["[0]" meta] [abstract monad] [control ["[0]" exception {"+" exception:}]] - ["[0]" meta] [data ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]]]] + ["%" format {"+" format}]]] + [macro + ["^" pattern]]]] ["[0]" // "_" ["/[1]" // "_" ["[1][0]" extension] @@ -48,7 +50,7 @@ {.#Definition [exported? actualT _]} (do ! [_ (/type.inference actualT) - (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^.let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> @@ -63,7 +65,7 @@ {.#Type [exported? value labels]} (do ! [_ (/type.inference .Type) - (^let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) + (^.let def_name [::module ::name]) (///extension.lifted (meta.normal def_name)) current (///extension.lifted meta.current_module_name)] (if (text#= current ::module) <return> 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 f5be4859f..b3e3fd242 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 @@ -90,17 +90,17 @@ extension_eval (:as Eval (wrapper (:expected compiler_eval)))] _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code - (^ [_ {.#Form (list& [_ {.#Text name}] inputs)}]) + (pattern [_ {.#Form (list& [_ {.#Text name}] inputs)}]) (//extension.apply archive again [name inputs]) - (^ [_ {.#Form (list& macro inputs)}]) + (pattern [_ {.#Form (list& macro inputs)}]) (do ! [expansion (/.lifted_analysis (do ! [macroA (<| (///analysis/type.expecting Macro) (analysis archive macro))] (case macroA - (^ (///analysis.constant macro_name)) + (pattern (///analysis.constant macro_name)) (do ! [?macro (//extension.lifted (meta.macro macro_name)) macro (case ?macro @@ -114,7 +114,7 @@ _ (//.except ..invalid_macro_call code))))] (case expansion - (^ (list& <lux_def_module> referrals)) + (pattern (list& <lux_def_module> referrals)) (|> (again archive <lux_def_module>) (# ! each (revised /.#referrals (list#composite referrals)))) 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 b4e91c905..c90c949af 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 @@ -15,7 +15,9 @@ ["%" format {"+" Format format}]] [collection ["[0]" list] - ["[0]" dictionary {"+" Dictionary}]]]]] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]]]] [///// ["//" phase] [meta @@ -117,7 +119,7 @@ (def: .public (apply archive phase [name parameters]) (All (_ s i o) (-> Archive (Phase s i o) (Extension i) (Operation s i o o))) - (function (_ (^let stateE [bundle state])) + (function (_ (^.let stateE [bundle state])) (case (dictionary.value name bundle) {.#Some handler} (((handler name phase) archive parameters) 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 5b833c0b7..8d2e90900 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 @@ -27,6 +27,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -400,7 +401,7 @@ {.#None} (/////analysis.except ..non_jvm_type luxT)) - (^ {.#Primitive (static array.type_name) (list elemT)}) + (pattern {.#Primitive (static array.type_name) (list elemT)}) (phase#each jvm.array (jvm_type elemT)) {.#Primitive class parametersT} @@ -448,7 +449,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list arrayC)) + (pattern (list arrayC)) (do phase.monad [_ (typeA.inference ..int) arrayA (<| (typeA.expecting {.#Primitive (|> (jvm.array primitive_type) @@ -464,7 +465,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list arrayC)) + (pattern (list arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -483,7 +484,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list lengthC)) + (pattern (list lengthC)) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -498,7 +499,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list lengthC)) + (pattern (list lengthC)) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -519,8 +520,8 @@ (def: (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT - (^ {.#Primitive (static array.type_name) - (list elementT)}) + (pattern {.#Primitive (static array.type_name) + (list elementT)}) (/////analysis.except ..non_parameter objectT) {.#Primitive name parameters} @@ -554,11 +555,11 @@ {.#None} (in (jvm.class ..object_class (list))))) - (^or {.#Ex id} - {.#Parameter id}) + (^.or {.#Ex id} + {.#Parameter id}) (phase#in (jvm.class ..object_class (list))) - (^template [<tag>] + (^.template [<tag>] [{<tag> env unquantified} (check_parameter unquantified)]) ([.#UnivQ] @@ -613,8 +614,8 @@ ... else (phase#in (jvm.class name (list))))) - (^ {.#Primitive (static array.type_name) - (list elementT)}) + (pattern {.#Primitive (static array.type_name) + (list elementT)}) (|> elementT check_jvm (phase#each jvm.array)) @@ -627,7 +628,7 @@ {.#Named name anonymous} (check_jvm anonymous) - (^template [<tag>] + (^.template [<tag>] [{<tag> env unquantified} (check_jvm unquantified)]) ([.#UnivQ] @@ -681,7 +682,7 @@ (-> .Type (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (^ (list idxC arrayC)) + (pattern (list idxC arrayC)) (do phase.monad [_ (typeA.inference lux_type) idxA (<| (typeA.expecting ..int) @@ -698,7 +699,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list idxC arrayC)) + (pattern (list idxC arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -722,7 +723,7 @@ (list)}] (function (_ extension_name analyse archive args) (case args - (^ (list idxC valueC arrayC)) + (pattern (list idxC valueC arrayC)) (do phase.monad [_ (typeA.inference array_type) idxA (<| (typeA.expecting ..int) @@ -742,7 +743,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list idxC valueC arrayC)) + (pattern (list idxC valueC arrayC)) (<| typeA.with_var (function (_ [@var :var:])) (do phase.monad @@ -817,7 +818,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list)) + (pattern (list)) (do phase.monad [expectedT (///.lifted meta.expected_type) [_ :object:] (check_object expectedT) @@ -831,7 +832,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list objectC)) + (pattern (list objectC)) (do phase.monad [_ (typeA.inference .Bit) [objectT objectA] (typeA.inferring @@ -846,7 +847,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list monitorC exprC)) + (pattern (list monitorC exprC)) (do phase.monad [[monitorT monitorA] (typeA.inferring (analyse archive monitorC)) @@ -861,7 +862,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list exceptionC)) + (pattern (list exceptionC)) (do phase.monad [_ (typeA.inference Nothing) [exceptionT exceptionA] (typeA.inferring @@ -881,7 +882,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list classC)) + (pattern (list classC)) (case classC [_ {.#Text class}] (do phase.monad @@ -938,7 +939,7 @@ (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+)}) + (pattern {.#Primitive _ (list& self_classT super_classT super_interfacesT+)}) (monad.each phase.monad (function (_ superT) (do [! phase.monad] @@ -955,7 +956,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (^ (list fromC)) + (pattern (list fromC)) (do [! phase.monad] [toT (///.lifted meta.expected_type) target_name (# ! each ..reflection (check_jvm toT)) @@ -2185,7 +2186,7 @@ (<| /////analysis.tuple (list (/////analysis.unit)) (case arity - (^or 0 1) + (^.or 0 1) bodyA 2 @@ -2399,7 +2400,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^template [<tag> <type> <constant>] + (^.template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) 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 21cf02c95..59193e0c8 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 @@ -15,6 +15,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -135,7 +137,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (^ (list opC)) + (pattern (list opC)) (<| typeA.with_var (function (_ [@var :var:])) (do [! ////.monad] @@ -152,7 +154,7 @@ Handler (function (_ extension_name analyse archive argsC+) (case argsC+ - (^ (list [_ {.#Text module_name}] exprC)) + (pattern (list [_ {.#Text module_name}] exprC)) (////analysis.with_current_module module_name (analyse archive exprC)) @@ -163,7 +165,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (^ (list typeC valueC)) + (pattern (list typeC valueC)) (do [! ////.monad] [actualT (# ! each (|>> (:as Type)) (eval archive Type typeC)) @@ -178,7 +180,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (^ (list typeC valueC)) + (pattern (list typeC valueC)) (do [! ////.monad] [actualT (# ! each (|>> (:as Type)) (eval archive Type typeC)) @@ -215,12 +217,12 @@ (do ! [input_type (///.lifted (meta.definition (symbol .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 {.#Tag _} - {.#Slot _}) + (^.or {.#Tag _} + {.#Slot _}) (////.failure (exception.error ..not_a_type [(symbol .Macro')])) {.#Alias real_name} 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 0dc4e8ed4..a35443c11 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 @@ -25,6 +25,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -230,7 +231,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^template [<tag> <type> <constant>] + (^.template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) @@ -916,7 +917,7 @@ _ (..save_class! name bytecode all_dependencies)] (in directive.no_requirements)))])) -(def: (method_declaration (^open "/[0]")) +(def: (method_declaration (open "/[0]")) (-> (jvm.Method_Declaration Code) (Resource Method)) (let [type (type.method [/#type_variables /#arguments /#return /#exceptions])] (method.method ($_ modifier#composite 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 3680787de..831211fb9 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 @@ -23,6 +23,7 @@ ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set {"+" Set}]]] [macro + ["^" pattern] ["[0]" code]] [math [number @@ -126,7 +127,7 @@ [interim_artifacts codeG] (/////generation.with_interim_artifacts archive (generate archive codeS)) .let [@abstraction (case codeS - (^ (/////synthesis.function/abstraction [env arity body])) + (pattern (/////synthesis.function/abstraction [env arity body])) (|> interim_artifacts list.last (maybe#each (|>> [arity]))) @@ -245,7 +246,7 @@ (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ - (^ (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) + (pattern (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) (do phase.monad [current_module (/////directive.lifted_analysis (///.lifted meta.current_module_name)) @@ -354,12 +355,12 @@ {.#Alias de_aliased} (phase.except ..cannot_alias_an_alias [[current_module alias] original de_aliased]) - (^or {.#Definition _} - {.#Type _}) + (^.or {.#Definition _} + {.#Type _}) (moduleA.define alias {.#Alias original}) - (^or {.#Tag _} - {.#Slot _}) + (^.or {.#Tag _} + {.#Slot _}) (phase.except ..cannot_alias_a_label [[current_module alias] original])))) (def: def::alias @@ -396,7 +397,7 @@ {.#Primitive name parameters} {.#Primitive name (list#each again parameters)} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] @@ -404,12 +405,12 @@ [.#Function] [.#Apply]) - (^or {.#Parameter _} - {.#Var _} - {.#Ex _}) + (^.or {.#Parameter _} + {.#Var _} + {.#Ex _}) type - (^template [<tag>] + (^.template [<tag>] [{<tag> closure body} {<tag> closure (again body)}]) ([.#UnivQ] @@ -425,7 +426,7 @@ (Handler anchor expression directive))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (^ (list nameC valueC)) + (pattern (list nameC valueC)) (do phase.monad [target_platform (/////directive.lifted_analysis (///.lifted meta.target)) @@ -433,11 +434,11 @@ [_ handlerV] (<definer> archive (:as Text name) (let [raw_type (type <def_type>)] (case target_platform - (^or (^ (static @.jvm)) - (^ (static @.js))) + (^.or (pattern (static @.jvm)) + (pattern (static @.js))) raw_type - (^ (static @.python)) + (pattern (static @.python)) (swapped binary.Binary Binary|Python raw_type) _ @@ -519,7 +520,7 @@ (-> (Program expression directive) (Handler anchor expression directive))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (^ (list programC)) + (pattern (list programC)) (do phase.monad [state (///.lifted phase.state) .let [analyse (the [/////directive.#analysis /////directive.#phase] state) 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 f162595e7..8f4bec35c 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 @@ -12,6 +12,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary]]] + [macro + ["^" pattern]] [math [number ["f" frac]]] @@ -105,8 +107,8 @@ [body (expression archive synthesis)] (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -117,31 +119,31 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (//case.exec! statement expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (//case.let! statement expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (//case.if! statement expression archive if) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (//loop.scope! statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//loop.again! statement expression archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) 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 4fbc7e603..a89e094ea 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 @@ -21,6 +21,7 @@ ["[0]" format "_" ["[1]" binary]]] [macro + ["^" pattern] ["[0]" template]] [math [number @@ -823,11 +824,11 @@ (-> Nat Synthesis Synthesis) (with_expansions [<oops> (panic! (%.format (%.nat arity) " " (//////synthesis.%synthesis body)))] (case [arity body] - (^or [0 _] - [1 _]) + (^.or [0 _] + [1 _]) body - (^ [2 {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Let _ 2 (//////synthesis.tuple (list _ hidden))}}}]) + (pattern [2 {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Let _ 2 (//////synthesis.tuple (list _ hidden))}}}]) hidden [_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}] @@ -836,7 +837,7 @@ {//////synthesis.#Seq _ next} (again next) - (^ {//////synthesis.#Then (//////synthesis.tuple (list _ hidden))}) + (pattern {//////synthesis.#Then (//////synthesis.tuple (list _ hidden))}) hidden _ @@ -874,16 +875,16 @@ (-> Path Path)) (function (again path) (case path - (^ (//////synthesis.path/then bodyS)) + (pattern (//////synthesis.path/then bodyS)) (//////synthesis.path/then (normalize bodyS)) - (^template [<tag>] - [(^ {<tag> leftP rightP}) + (^.template [<tag>] + [(pattern {<tag> leftP rightP}) {<tag> (again leftP) (again rightP)}]) ([//////synthesis.#Alt] [//////synthesis.#Seq]) - (^template [<tag>] + (^.template [<tag>] [{<tag> _} path]) ([//////synthesis.#Pop] @@ -893,7 +894,7 @@ {//////synthesis.#Bit_Fork when then else} {//////synthesis.#Bit_Fork when (again then) (maybe#each again else)} - (^template [<tag>] + (^.template [<tag>] [{<tag> [[exampleH nextH] tail]} {<tag> [[exampleH (again nextH)] (list#each (function (_ [example next]) @@ -910,49 +911,49 @@ (-> Mapping Synthesis Synthesis) (function (again body) (case body - (^template [<tag>] - [(^ <tag>) + (^.template [<tag>] + [(pattern <tag>) body]) ([{//////synthesis.#Simple _}] [(//////synthesis.constant _)]) - (^ (//////synthesis.variant [lefts right? sub])) + (pattern (//////synthesis.variant [lefts right? sub])) (//////synthesis.variant [lefts right? (again sub)]) - (^ (//////synthesis.tuple members)) + (pattern (//////synthesis.tuple members)) (//////synthesis.tuple (list#each again members)) - (^ (//////synthesis.variable var)) + (pattern (//////synthesis.variable var)) (|> mapping (dictionary.value body) (maybe.else var) //////synthesis.variable) - (^ (//////synthesis.branch/case [inputS pathS])) + (pattern (//////synthesis.branch/case [inputS pathS])) (//////synthesis.branch/case [(again inputS) (normalize_path again pathS)]) - (^ (//////synthesis.branch/exec [this that])) + (pattern (//////synthesis.branch/exec [this that])) (//////synthesis.branch/exec [(again this) (again that)]) - (^ (//////synthesis.branch/let [inputS register outputS])) + (pattern (//////synthesis.branch/let [inputS register outputS])) (//////synthesis.branch/let [(again inputS) register (again outputS)]) - (^ (//////synthesis.branch/if [testS thenS elseS])) + (pattern (//////synthesis.branch/if [testS thenS elseS])) (//////synthesis.branch/if [(again testS) (again thenS) (again elseS)]) - (^ (//////synthesis.branch/get [path recordS])) + (pattern (//////synthesis.branch/get [path recordS])) (//////synthesis.branch/get [path (again recordS)]) - (^ (//////synthesis.loop/scope [offset initsS+ bodyS])) + (pattern (//////synthesis.loop/scope [offset initsS+ bodyS])) (//////synthesis.loop/scope [offset (list#each again initsS+) (again bodyS)]) - (^ (//////synthesis.loop/again updatesS+)) + (pattern (//////synthesis.loop/again updatesS+)) (//////synthesis.loop/again (list#each again updatesS+)) - (^ (//////synthesis.function/abstraction [environment arity bodyS])) + (pattern (//////synthesis.function/abstraction [environment arity bodyS])) (//////synthesis.function/abstraction [(list#each (function (_ captured) (case captured - (^ (//////synthesis.variable var)) + (pattern (//////synthesis.variable var)) (|> mapping (dictionary.value captured) (maybe.else var) @@ -964,7 +965,7 @@ arity bodyS]) - (^ (//////synthesis.function/apply [functionS inputsS+])) + (pattern (//////synthesis.function/apply [functionS inputsS+])) (//////synthesis.function/apply [(again functionS) (list#each again inputsS+)]) {//////synthesis.#Extension [name inputsS+]} 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 40b036496..e8be23f6c 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 @@ -1,45 +1,47 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" lua {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" lua "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + ["@" target + ["_" lua {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" lua "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -66,8 +68,8 @@ [body (expression archive synthesis)] (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -78,33 +80,33 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (//case.exec! statement expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (//case.let! statement expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (//case.if! statement expression archive if) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (do /////.monad [[inits scope!] (//loop.scope! statement expression archive false scope)] (in scope!)) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//loop.again! statement expression archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) 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 c4be93d94..481eefce0 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 @@ -1,47 +1,49 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<[0]>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - [target - ["_" python {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - ["[0]" reference] - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" python "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop]]] - [// - [analysis {"+" }] - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<[0]>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + [target + ["_" python {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + ["[0]" reference] + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" python "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop]]] + [// + [analysis {"+" }] + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (statement expression archive synthesis) Phase! @@ -52,8 +54,8 @@ [body (expression archive synthesis)] (in (:as (Statement Any) body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -64,17 +66,17 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -82,7 +84,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) 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 2328c2f2a..7f71e4292 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 @@ -1,45 +1,47 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - [target - ["_" ruby {"+" Expression Statement}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["//" ruby "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] - ["[1][0]" primitive] - ["[1][0]" structure] - ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase ("[1]#[0]" monad)]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] + [math + [number + ["f" frac]]] + [target + ["_" ruby {"+" Expression Statement}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["//" ruby "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Handler Bundle Generator}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase ("[1]#[0]" monad)]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -64,8 +66,8 @@ (in (:as Statement body))) - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -76,17 +78,17 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -94,7 +96,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/////#each _.return (//function.function statement expression archive abstraction)) )) 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 1bd5a5f88..d92c3084f 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 @@ -1,33 +1,35 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -37,8 +39,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] 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 09ab89d42..60b9cd96e 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 @@ -11,6 +11,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix monoid)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -65,7 +67,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -140,7 +142,7 @@ (Generator [Var/1 _.Tag _.Tag Path]) (function (again [$output @done @fail pathP]) (.case pathP - (^ (/////synthesis.path/then bodyS)) + (pattern (/////synthesis.path/then bodyS)) (# ///////phase.monad each (function (_ outputV) (_.progn (list (_.setq $output outputV) @@ -170,7 +172,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -188,41 +190,41 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=/2]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> @fail false idx {.#None})) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP [$output @done @fail] again (# ///////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]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (..push! (_.elt/2 [..peek (_.int +0)]))) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (again [$output @done @fail nextP'])] (///////phase#in (_.progn (list (..multi_pop! (n.+ 2 extra_pops)) next!))))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do [! ///////phase.monad] [@otherwise (# ! each (|>> %.nat (format "lux_case_otherwise") _.tag) /////generation.next) pre! (again [$output @done @otherwise preP]) post! (again [$output @done @fail postP])] (in (..alternation @otherwise pre! post!))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ///////phase.monad [pre! (again [$output @done @fail preP]) post! (again [$output @done @fail postP])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux index 532b407a7..7a28610fb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/extension.lux @@ -1,25 +1,25 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - [parser - ["<[0]>" code]]] - [data - [collection - ["[0]" list ("[1]#[0]" functor)]]] - ["[0]" meta] - ["[0]" macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]]]] - ["[0]" /// "_" - ["[1][0]" extension] - [// - [synthesis {"+" Synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + [parser + ["<[0]>" code]]] + [data + [collection + ["[0]" list ("[1]#[0]" functor)]]] + ["[0]" meta] + ["[0]" macro {"+" with_symbols} + ["[0]" code] + [syntax {"+" syntax:}]]]] + ["[0]" /// "_" + ["[1][0]" extension] + [// + [synthesis {"+" Synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]) (syntax: (Vector [size <code>.nat elemT <code>.any]) @@ -43,7 +43,7 @@ (generation.Handler (~ g!anchor) (~ g!expression) (~ g!directive)))) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!archive) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do ///.monad [(~+ (|> g!input+ (list#each (function (_ g!input) 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 af1b3b605..637513242 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 @@ -1,82 +1,84 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" js]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" js]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [js + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [js - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant expression archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (/case.case ///extension/common.statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (/case.exec expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (/case.let expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (/case.if expression archive if) - (^ (synthesis.branch/get get)) + (pattern (synthesis.branch/get get)) (/case.get expression archive get) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope ///extension/common.statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.function ///extension/common.statement expression archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply expression archive application) {synthesis.#Extension extension} 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 e9b316c72..cca5cda23 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 @@ -9,6 +9,8 @@ ["[0]" text] [collection ["[0]" list ("[1]#[0]" functor mix)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -179,21 +181,21 @@ (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP - (^template [<simple> <choice>] - [(^ (<simple> idx nextP)) + (^.template [<simple> <choice>] + [(pattern (<simple> idx nextP)) (|> nextP again (# ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))]) ([/////synthesis.simple_left_side ..left_choice] [/////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))}) ... Extra optimization - (^ (/////synthesis.path/seq - (/////synthesis.member/left 0) - (/////synthesis.!bind_top register thenP))) + (pattern (/////synthesis.path/seq + (/////synthesis.member/left 0) + (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then @@ -201,10 +203,10 @@ then!)})) ... Extra optimization - (^template [<pm> <getter>] - [(^ (/////synthesis.path/seq - (<pm> lefts) - (/////synthesis.!bind_top register thenP))) + (^.template [<pm> <getter>] + [(pattern (/////synthesis.path/seq + (<pm> lefts) + (/////synthesis.!bind_top register thenP))) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then @@ -213,14 +215,14 @@ ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (in {.#Some ($_ _.then (_.define (..register register) ..peek_and_pop_cursor) then!)})) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -283,7 +285,7 @@ ..fail_pm! clauses))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [cases (monad.each ! (function (_ [match then]) @@ -295,20 +297,20 @@ ([/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^template [<complex> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx))]) ([/////synthesis.side/left ..left_choice] [/////synthesis.side/right ..right_choice]) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (push_cursor! (<getter> (_.i32 (.int lefts)) ..peek_cursor)))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^template [<tag> <combinator>] - [(^ (<tag> leftP rightP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> leftP rightP)) (do ///////phase.monad [left! (again leftP) right! (again rightP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux index e97ee4c43..c18131d4c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/loop.lux @@ -36,10 +36,10 @@ (def: (setup $iteration initial? offset bindings body) (-> Var Bit Register (List Expression) Statement Statement) (case bindings - (^ (list)) + (pattern (list)) body - (^ (list binding)) + (pattern (list binding)) (let [$binding (//case.register offset)] ($_ _.then (if initial? 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 7cabfc178..67ae82f54 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 @@ -2,7 +2,9 @@ [library [lux "*" [abstract - [monad {"+" do}]]]] + [monad {"+" do}]] + [macro + ["^" pattern]]]] ["[0]" / "_" [runtime {"+" Phase}] ["[1][0]" primitive] @@ -22,18 +24,18 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (///#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant generate archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple generate archive members) {synthesis.#Reference reference} @@ -44,31 +46,31 @@ {reference.#Constant constant} (/reference.constant archive constant)) - (^ (synthesis.branch/case [valueS pathS])) + (pattern (synthesis.branch/case [valueS pathS])) (/case.case generate archive [valueS pathS]) - (^ (synthesis.branch/exec [this that])) + (pattern (synthesis.branch/exec [this that])) (/case.exec generate archive [this that]) - (^ (synthesis.branch/let [inputS register bodyS])) + (pattern (synthesis.branch/let [inputS register bodyS])) (/case.let generate archive [inputS register bodyS]) - (^ (synthesis.branch/if [conditionS thenS elseS])) + (pattern (synthesis.branch/if [conditionS thenS elseS])) (/case.if generate archive [conditionS thenS elseS]) - (^ (synthesis.branch/get [path recordS])) + (pattern (synthesis.branch/get [path recordS])) (/case.get generate archive [path recordS]) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope generate archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (/loop.again generate archive updates) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.abstraction generate archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply generate archive application) {synthesis.#Extension 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 6504a5f55..4e237921c 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 @@ -10,6 +10,8 @@ ["[0]" list ("[1]#[0]" mix)]] ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -165,7 +167,7 @@ {synthesis.#Bind register} (..path|bind register) - (^template [<tag> <path>] + (^.template [<tag> <path>] [{<tag> it} (<path> again @else it)]) ([synthesis.#Bit_Fork ..path|bit_fork] @@ -181,7 +183,7 @@ body! (_.when_continuous (_.goto @end))))) - (^ (synthesis.side lefts right?)) + (pattern (synthesis.side lefts right?)) (operation#in (do _.monad [@success _.new_label] @@ -198,17 +200,17 @@ (_.set_label @success) //runtime.push))) - (^template [<pattern> <projection>] - [(^ (<pattern> lefts)) + (^.template [<pattern> <projection>] + [(pattern (<pattern> lefts)) (operation#in ($_ _.composite ..peek (<projection> lefts) //runtime.push)) ... Extra optimization - (^ (synthesis.path/seq - (<pattern> lefts) - (synthesis.!bind_top register thenP))) + (pattern (synthesis.path/seq + (<pattern> lefts) + (synthesis.!bind_top register thenP))) (do phase.monad [then! (path' stack_depth @else @end phase archive thenP)] (in ($_ _.composite diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index 6a9b7bf4b..1a0569fbc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -171,7 +171,7 @@ (def: .public (apply generate archive [abstractionS inputsS]) (Generator Apply) (case abstractionS - (^ (synthesis.constant $abstraction)) + (pattern (synthesis.constant $abstraction)) (do [! phase.monad] [[@definition |abstraction|] (generation.definition archive $abstraction) .let [actual_arity (list.size inputsS)]] 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 dc3e63e85..9e7d92565 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 @@ -5,7 +5,6 @@ [abstract [monad {"+" do}]] [control - pipe ["[0]" maybe] ["[0]" try {"+" Try}] ["[0]" exception {"+" exception:}] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index 23914096a..0d510baa6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux @@ -29,7 +29,7 @@ (def: (invariant? register changeS) (-> Register Synthesis Bit) (case changeS - (^ (synthesis.variable/local var)) + (pattern (synthesis.variable/local var)) (n.= register var) _ 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 c1b79618b..10f11edd9 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 @@ -6,6 +6,8 @@ [monad {"+" do}]] [control ["[0]" try]] + [macro + ["^" pattern]] [math [number ["i" int]]] @@ -32,7 +34,7 @@ (def: .public (i64 value) (-> (I64 Any) (Bytecode Any)) (case (.int value) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] @@ -40,7 +42,7 @@ ([+0 _.lconst_0] [+1 _.lconst_1]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -89,14 +91,14 @@ (def: .public (f64 value) (-> Frac (Bytecode Any)) (case value - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] ..wrap_f64)]) ([+1.0 _.dconst_1]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -104,7 +106,7 @@ ..wrap_f64)]) ([+2.0 _.fconst_2]) - (^template [<int> <instruction>] + (^.template [<int> <instruction>] [<int> (do _.monad [_ <instruction> 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 3319eb024..6493ea02a 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 @@ -1,82 +1,84 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" lua]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" lua]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [lua + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [lua - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+" } - [variable {"+" }]]]]]]]) + [analysis {"+" }] + ["[0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+" } + [variable {"+" }]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (^ (synthesis.variant variantS)) + (pattern (synthesis.variant variantS)) (/structure.variant expression archive variantS) - (^ (synthesis.tuple members)) + (pattern (synthesis.tuple members)) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^ (synthesis.branch/case case)) + (pattern (synthesis.branch/case case)) (/case.case ///extension/common.statement expression archive case) - (^ (synthesis.branch/exec it)) + (pattern (synthesis.branch/exec it)) (/case.exec expression archive it) - (^ (synthesis.branch/let let)) + (pattern (synthesis.branch/let let)) (/case.let expression archive let) - (^ (synthesis.branch/if if)) + (pattern (synthesis.branch/if if)) (/case.if expression archive if) - (^ (synthesis.branch/get get)) + (pattern (synthesis.branch/get get)) (/case.get expression archive get) - (^ (synthesis.loop/scope scope)) + (pattern (synthesis.loop/scope scope)) (/loop.scope ///extension/common.statement expression archive scope) - (^ (synthesis.loop/again updates)) + (pattern (synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) - (^ (synthesis.function/abstraction abstraction)) + (pattern (synthesis.function/abstraction abstraction)) (/function.function ///extension/common.statement expression archive abstraction) - (^ (synthesis.function/apply application)) + (pattern (synthesis.function/apply application)) (/function.apply expression archive application) {synthesis.#Extension extension} 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 7e879516a..6d79e0750 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 @@ -9,6 +9,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [target ["_" lua {"+" Expression Var Statement}]]]] ["[0]" // "_" @@ -207,7 +209,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -225,33 +227,33 @@ [/////synthesis.#F64_Fork _.float] [/////synthesis.#Text_Fork _.string]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (///////phase#each (_.then (<choice> true idx)) (again nextP))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +1)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.local/1 (..register register) ..peek_and_pop) then!))) - (^template [<tag> <combinator>] - [(^ (<tag> preP postP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] 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 205510ed1..460350507 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 @@ -1,37 +1,39 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" php]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" php]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: (statement expression archive synthesis) Phase! (case synthesis - (^template [<tag>] - [(^ (<tag> value)) + (^.template [<tag>] + [(pattern (<tag> value)) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.bit] [////synthesis.i64] @@ -42,24 +44,24 @@ [////synthesis.branch/get] [////synthesis.function/apply]) - (^template [<tag>] - [(^ {<tag> value}) + (^.template [<tag>] + [(pattern {<tag> value}) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.#Reference] [////synthesis.#Extension]) - (^ (////synthesis.branch/case case)) + (pattern (////synthesis.branch/case case)) (/case.case! statement expression archive case) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/let /case.let!] [////synthesis.branch/if /case.if!] [////synthesis.loop/scope /loop.scope!] [////synthesis.loop/again /loop.again!]) - (^ (////synthesis.function/abstraction abstraction)) + (pattern (////synthesis.function/abstraction abstraction)) (//////phase#each _.return (/function.function statement expression archive abstraction)) )) @@ -68,8 +70,8 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -79,8 +81,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -89,14 +91,14 @@ [////synthesis.branch/get /case.get] [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again _)) + (pattern (////synthesis.loop/again _)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Extension extension} 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 54685bfff..595c313cf 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 @@ -10,6 +10,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["i" int]]] @@ -85,7 +87,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -189,7 +191,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -204,34 +206,34 @@ [/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (# ///////phase.monad each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.set! (..register register) ..peek_and_pop) then!))) - ... (^ (/////synthesis.!multi_pop nextP)) + ... (pattern (/////synthesis.!multi_pop nextP)) ... (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] ... (do ///////phase.monad ... [next! (again nextP')] @@ -239,8 +241,8 @@ ... (..multi_pop! (n.+ 2 extra_pops)) ... next!)))) - (^template [<tag> <combinator>] - [(^ (<tag> preP postP)) + (^.template [<tag> <combinator>] + [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] 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 10a220018..7e620b07a 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 @@ -5,6 +5,8 @@ [monad {"+" do}]] [control ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] [target ["_" python]]]] ["[0]" / "_" @@ -35,16 +37,16 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -56,14 +58,14 @@ [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again updates)) + (pattern (////synthesis.loop/again updates)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Reference value} 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 bfb3ebdc8..3e4699361 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 @@ -9,6 +9,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -216,7 +218,7 @@ else! then!))})) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -256,34 +258,34 @@ {/////synthesis.#Bind register} (///////phase#in (_.set (list (..register register)) ..peek)) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (///////phase#each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ! [then! (again thenP)] (///////phase#in ($_ _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ! [next! (again nextP')] @@ -291,13 +293,13 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ! [pre! (again preP) post! (again postP)] (in (_.then pre! post!))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do ! [pre! (again preP) post! (again postP) 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 6e2e8ccb2..ff391b986 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 @@ -1,35 +1,37 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [target - ["_" r]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]] + [target + ["_" r]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -39,8 +41,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] 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 a7b82af5a..2b849271b 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 @@ -1,40 +1,41 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - [number - ["i" int]]] - [target - ["_" r {"+" Expression SVar}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["i" int]]] + [target + ["_" r {"+" Expression SVar}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register SVar) @@ -68,7 +69,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple::left] @@ -161,7 +162,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -179,8 +180,8 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=] [/////synthesis.#Text_Fork //primitive.text _.=]) - (^template [<pm> <flag> <prep>] - [(^ (<pm> idx)) + (^.template [<pm> <flag> <prep>] + [(pattern (<pm> idx)) (///////phase#in ($_ _.then (_.set! $temp (|> idx <prep> .int _.int (//runtime.sum::get ..peek (//runtime.flag <flag>)))) (_.if (_.= _.null $temp) @@ -189,16 +190,16 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (_.item (_.int +1) ..peek)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (^ (/////synthesis.path/seq leftP rightP)) + (pattern (/////synthesis.path/seq leftP rightP)) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] @@ -206,7 +207,7 @@ leftO rightO))) - (^ (/////synthesis.path/alt leftP rightP)) + (pattern (/////synthesis.path/alt leftP rightP)) (do [! ///////phase.monad] [leftO (again leftP) rightO (again rightP)] 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 65f464d29..e0800d768 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 @@ -1,28 +1,28 @@ (.using - lux - (lux (control [library - [monad {"+" do}]] - ["ex" exception {"+" exception:}] - ["p" parser]) - (data ["e" error] - [text] - text/format - [number] - (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered {"+" Dict}]))) - [macro {"+" with_symbols}] - (macro [code] - ["s" syntax {"+" syntax:}]) - [host]) - (luxc ["&" lang] - (lang ["la" analysis] - ["ls" synthesis] - (host [r {"+" Expression}]))) - [///] - (/// ["[0]T" runtime] - ["[0]T" case] - ["[0]T" function] - ["[0]T" loop])) + lux + (lux (control [library + [monad {"+" do}]] + ["ex" exception {"+" exception:}] + ["p" parser]) + (data ["e" error] + [text] + text/format + [number] + (coll [list "list/" Functor<List>] + (dictionary ["dict" unordered {"+" Dict}]))) + [macro {"+" with_symbols}] + (macro [code] + ["s" syntax {"+" syntax:}]) + [host]) + (luxc ["&" lang] + (lang ["la" analysis] + ["ls" synthesis] + (host [r {"+" Expression}]))) + [///] + (/// ["[0]T" runtime] + ["[0]T" case] + ["[0]T" function] + ["[0]T" loop])) ... [Types] (type: .public Translator @@ -74,7 +74,7 @@ (function ((~ g!_) (~ g!name)) (function ((~ g!_) (~ g!translate) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do macro.Monad<Meta> [(~+ (|> g!input+ (list/each (function (_ g!input) 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 04094f9a9..f459b2d31 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 @@ -1,19 +1,19 @@ (.using - lux - (lux (control [library - [monad {"+" do}]]) - (data [text] - text/format - (coll [list "list/" Functor<List>] - (dictionary ["dict" unordered {"+" Dict}]))) - [macro "macro/" Monad<Meta>]) - (luxc ["&" lang] - (lang ["la" analysis] - ["ls" synthesis] - (host [ruby {"+" Ruby Expression Statement}]))) - [///] - (/// ["[0]T" runtime]) - (// ["@" common])) + lux + (lux (control [library + [monad {"+" do}]]) + (data [text] + text/format + (coll [list "list/" Functor<List>] + (dictionary ["dict" unordered {"+" Dict}]))) + [macro "macro/" Monad<Meta>]) + (luxc ["&" lang] + (lang ["la" analysis] + ["ls" synthesis] + (host [ruby {"+" Ruby Expression Statement}]))) + [///] + (/// ["[0]T" runtime]) + (// ["@" common])) ... (template [<name> <lua>] ... [(def: (<name> _) @.Nullary <lua>)] @@ -25,7 +25,7 @@ ... (def: (lua//global proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list [_ {.#Text name}])) +... (pattern (list [_ {.#Text name}])) ... (do macro.Monad<Meta> ... [] ... (in name)) @@ -36,7 +36,7 @@ ... (def: (lua//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list& functionS argsS+)) +... (pattern (list& functionS argsS+)) ... (do [@ macro.Monad<Meta>] ... [functionO (translate functionS) ... argsO+ (monad.each @ translate argsS+)] @@ -56,7 +56,7 @@ ... (def: (table//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (^ (list& tableS [_ {.#Text field}] argsS+)) +... (pattern (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/ruby.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby.lux index ca563e3e1..8e8da02ef 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 @@ -1,50 +1,52 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" exception {"+" exception:}]] - [target - ["_" ruby]]]] - ["[0]" / "_" - [runtime {"+" Phase Phase!}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" exception {"+" exception:}]] + [macro + ["^" pattern]] + [target + ["_" ruby]]]] + ["[0]" / "_" + [runtime {"+" Phase Phase!}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" function] + ["[1][0]" case] + ["[1][0]" loop] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" function] - ["[1][0]" case] - ["[1][0]" loop] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension + [generation + [ruby + ["[1]/[0]" common]]]] ["/[1]" // "_" - ["[1][0]" extension - [generation - [ruby - ["[1]/[0]" common]]]] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+" } - [variable {"+" }]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+" } + [variable {"+" }]]]]]]]) (exception: .public cannot_recur_as_an_expression) (def: (expression archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -56,14 +58,14 @@ [////synthesis.function/apply /function.apply]) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (^ (////synthesis.loop/again _)) + (pattern (////synthesis.loop/again _)) (//////phase.except ..cannot_recur_as_an_expression []) {////synthesis.#Reference value} 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 d4abe4b2b..1d513b57b 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 @@ -11,6 +11,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -225,7 +227,7 @@ else! then!))})) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -282,7 +284,7 @@ else! then!)))) - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -299,34 +301,34 @@ [/////synthesis.#F64_Fork (<| //primitive.f64)] [/////synthesis.#Text_Fork (<| //primitive.text)]) - (^template [<complex> <simple> <choice>] - [(^ (<complex> idx)) + (^.template [<complex> <simple> <choice>] + [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) - (^ (<simple> idx nextP)) + (pattern (<simple> idx nextP)) (|> nextP again (///////phase#each (_.then (<choice> true idx))))]) ([/////synthesis.side/left /////synthesis.simple_left_side ..left_choice] [/////synthesis.side/right /////synthesis.simple_right_side ..right_choice]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.!bind_top register thenP)) + (pattern (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (///////phase#in ($_ _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (^ (/////synthesis.!multi_pop nextP)) + (pattern (/////synthesis.!multi_pop nextP)) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -334,7 +336,7 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (^ (/////synthesis.path/seq preP postP)) + (pattern (/////synthesis.path/seq preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP)] @@ -342,7 +344,7 @@ pre! post!))) - (^ (/////synthesis.path/alt preP postP)) + (pattern (/////synthesis.path/alt preP postP)) (do ///////phase.monad [pre! (again preP) post! (again postP) 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 9052782ec..690ab94b9 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 @@ -1,35 +1,37 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [target - ["_" scheme]]]] - ["[0]" / "_" - [runtime {"+" Phase}] - ["[1][0]" primitive] - ["[1][0]" structure] + [library + [lux "*" + [abstract + [monad {"+" do}]] + [macro + ["^" pattern]] + [target + ["_" scheme]]]] + ["[0]" / "_" + [runtime {"+" Phase}] + ["[1][0]" primitive] + ["[1][0]" structure] + ["[1][0]" reference] + ["[1][0]" case] + ["[1][0]" loop] + ["[1][0]" function] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["[1][0]" loop] - ["[1][0]" function] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" extension] ["/[1]" // "_" - ["[1][0]" extension] - ["/[1]" // "_" - [analysis {"+" }] - ["[1][0]" synthesis] - ["//[1]" /// "_" - ["[1][0]" phase ("[1]#[0]" monad)] - [reference {"+"} - [variable {"+"}]]]]]]]) + [analysis {"+" }] + ["[1][0]" synthesis] + ["//[1]" /// "_" + ["[1][0]" phase ("[1]#[0]" monad)] + [reference {"+"} + [variable {"+"}]]]]]]]) (def: .public (generate archive synthesis) Phase (case synthesis - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -39,8 +41,8 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^template [<tag> <generator>] - [(^ (<tag> value)) + (^.template [<tag> <generator>] + [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] 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 3db6fab36..aeed6ea59 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 @@ -1,40 +1,41 @@ (.using - [library - [lux {"-" case let if} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set]]] - [macro - ["[0]" template]] - [math - [number - ["i" int]]] - [target - ["_" scheme {"+" Expression Computation Var}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" case let if} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set]]] + [macro + ["^" pattern] + ["[0]" template]] + [math + [number + ["i" int]]] + [target + ["_" scheme {"+" Expression Computation Var}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" primitive] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" primitive] ["/[1]" // "_" - ["[1][0]" reference] + ["[1][0]" synthesis "_" + ["[1]/[0]" case]] ["/[1]" // "_" - ["[1][0]" synthesis "_" - ["[1]/[0]" case]] - ["/[1]" // "_" - ["[1][0]" synthesis {"+" Member Synthesis Path}] - ["[1][0]" generation] - ["//[1]" /// "_" - [reference - ["[1][0]" variable {"+" Register}]] - ["[1][0]" phase ("[1]#[0]" monad)] - [meta - [archive {"+" Archive}]]]]]]]) + ["[1][0]" synthesis {"+" Member Synthesis Path}] + ["[1][0]" generation] + ["//[1]" /// "_" + [reference + ["[1][0]" variable {"+" Register}]] + ["[1][0]" phase ("[1]#[0]" monad)] + [meta + [archive {"+" Archive}]]]]]]]) (def: .public register (-> Register Var) @@ -66,7 +67,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^template [<side> <accessor>] + (^.template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -155,7 +156,7 @@ else! then!)))) - (^template [<tag> <format> <=>] + (^.template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -173,8 +174,8 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=?/2]) - (^template [<pm> <flag> <prep>] - [(^ (<pm> idx)) + (^.template [<pm> <flag> <prep>] + [(pattern (<pm> idx)) (///////phase#in (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek (_.bool <flag>)))]) (_.if (_.null?/1 @temp) ..fail! @@ -182,23 +183,23 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (^ (/////synthesis.member/left 0)) + (pattern (/////synthesis.member/left 0)) (///////phase#in (..push_cursor! (_.vector_ref/2 ..peek (_.int +0)))) - (^template [<pm> <getter>] - [(^ (<pm> lefts)) + (^.template [<pm> <getter>] + [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (^ (/////synthesis.path/seq leftP rightP)) + (pattern (/////synthesis.path/seq leftP rightP)) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] (in (_.begin (list leftO rightO)))) - (^ (/////synthesis.path/alt leftP rightP)) + (pattern (/////synthesis.path/alt leftP rightP)) (do [! ///////phase.monad] [leftO (again leftP) rightO (again rightP)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux index 77eb47de5..b588619b7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/extension/common.lux @@ -1,32 +1,32 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["ex" exception {"+" exception:}] - [parser - ["<[0]>" code]]] - [data - ["[0]" product] - ["[0]" text] - [number {"+" hex} - ["f" frac]] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["dict" dictionary {"+" Dictionary}]]] - ["[0]" macro {"+" with_symbols} - ["[0]" code] - [syntax {"+" syntax:}]] - [target - ["_" scheme {"+" Expression Computation}]]]] - ["[0]" /// "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle}] - ["[1]//" /// - ["[1][0]" extension - ["[0]" bundle]] - ["[1]/" // "_" - ["[1][0]" synthesis {"+" Synthesis}]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["ex" exception {"+" exception:}] + [parser + ["<[0]>" code]]] + [data + ["[0]" product] + ["[0]" text] + [number {"+" hex} + ["f" frac]] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["dict" dictionary {"+" Dictionary}]]] + ["[0]" macro {"+" with_symbols} + ["[0]" code] + [syntax {"+" syntax:}]] + [target + ["_" scheme {"+" Expression Computation}]]]] + ["[0]" /// "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle}] + ["[1]//" /// + ["[1][0]" extension + ["[0]" bundle]] + ["[1]/" // "_" + ["[1][0]" synthesis {"+" Synthesis}]]]]) (syntax: (Vector [size <code>.nat elemT <code>.any]) @@ -48,7 +48,7 @@ Handler) (function ((~ g!_) (~ g!name) (~ g!phase) (~ g!inputs)) (case (~ g!inputs) - (^ (list (~+ g!input+))) + (pattern (list (~+ g!input+))) (do /////.monad [(~+ (|> g!input+ (list#each (function (_ g!input) 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 274c4d0ad..38fc993d0 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 @@ -9,7 +9,9 @@ [data [collection ["[0]" list ("[1]#[0]" functor)] - ["[0]" dictionary {"+" Dictionary}]]]]] + ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]]]] ["[0]" / "_" ["[1][0]" function] ["[1][0]" case] @@ -33,14 +35,14 @@ {///simple.#Unit} {/simple.#Text /.unit} - (^template [<analysis> <synthesis>] + (^.template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> value}]) ([///simple.#Bit /simple.#Bit] [///simple.#Frac /simple.#F64] [///simple.#Text /simple.#Text]) - (^template [<analysis> <synthesis>] + (^.template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> (.i64 value)}]) ([///simple.#Nat /simple.#I64] @@ -74,7 +76,7 @@ (/.with_currying? false (/case.synthesize optimization branchesAB+ archive inputA)) - (^ (///analysis.no_op value)) + (pattern (///analysis.no_op value)) (optimization' value) {///analysis.#Apply _} 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 a9fa9c013..d21a2a13e 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 @@ -13,6 +13,8 @@ [collection ["[0]" list ("[1]#[0]" functor mix monoid)] ["[0]" set {"+" Set}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -52,7 +54,7 @@ {/.#Bit_Fork when then {.#None}}) thenC) - (^template [<from> <to> <conversion>] + (^.template [<from> <to> <conversion>] [{<from> test} (///#each (function (_ then) {<to> [(<conversion> test) then] (list)}) @@ -150,8 +152,8 @@ [{.#None} {.#None}] {.#None} - (^or [{.#Some woven_then} {.#None}] - [{.#None} {.#Some woven_then}]) + (^.or [{.#Some woven_then} {.#None}] + [{.#None} {.#Some woven_then}]) {.#Some woven_then} [{.#Some new_else} {.#Some old_else}] @@ -170,14 +172,14 @@ {.#Some old_else} (weave new_then old_else))}}) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> new_fork} {<tag> old_fork}] {<tag> (..weave_fork weave <equivalence> new_fork old_fork)}]) ([/.#I64_Fork i64.equivalence] [/.#F64_Fork frac.equivalence] [/.#Text_Fork text.equivalence]) - (^template [<access> <side> <lefts> <right?>] + (^.template [<access> <side> <lefts> <right?>] [[{/.#Access {<access> [<lefts> newL <right?> <side>]}} {/.#Access {<access> [<lefts> oldL <right?> <side>]}}] (if (n.= newL oldL) @@ -285,7 +287,7 @@ path (case input - (^ (/.branch/get [sub_path sub_input])) + (pattern (/.branch/get [sub_path sub_input])) (///#in (/.branch/get [(list#composite path sub_path) sub_input])) _ @@ -296,15 +298,15 @@ (do [! ///.monad] [inputS (synthesize^ archive inputA)] (case [headB tailB+] - (^ (!masking @variable @output)) + (pattern (!masking @variable @output)) (..synthesize_masking synthesize^ archive inputS @variable @output) - (^ [[(///pattern.unit) body] - {.#End}]) + (pattern [[(///pattern.unit) body] + {.#End}]) (case inputA - (^or {///analysis.#Simple _} - {///analysis.#Structure _} - {///analysis.#Reference _}) + (^.or {///analysis.#Simple _} + {///analysis.#Structure _} + {///analysis.#Reference _}) (synthesize^ archive body) _ @@ -314,18 +316,18 @@ {.#End}] (..synthesize_let synthesize^ archive inputS @variable body) - (^or (^ [[(///pattern.bit #1) then] - (list [(///pattern.bit #0) else])]) - (^ [[(///pattern.bit #1) then] - (list [(///pattern.unit) else])]) - - (^ [[(///pattern.bit #0) else] - (list [(///pattern.bit #1) then])]) - (^ [[(///pattern.bit #0) else] - (list [(///pattern.unit) then])])) + (^.or (pattern [[(///pattern.bit #1) then] + (list [(///pattern.bit #0) else])]) + (pattern [[(///pattern.bit #1) then] + (list [(///pattern.unit) else])]) + + (pattern [[(///pattern.bit #0) else] + (list [(///pattern.bit #1) then])]) + (pattern [[(///pattern.bit #0) else] + (list [(///pattern.unit) then])])) (..synthesize_if synthesize^ archive inputS then else) - (^ (!get patterns @member)) + (pattern (!get patterns @member)) (..synthesize_get synthesize^ archive inputS patterns @member) match @@ -334,7 +336,7 @@ (def: .public (count_pops path) (-> Path [Nat Path]) (case path - (^ (/.path/seq {/.#Pop} path')) + (pattern (/.path/seq {/.#Pop} path')) (let [[pops post_pops] (count_pops path')] [(++ pops) post_pops]) @@ -366,11 +368,11 @@ [path path path_storage ..empty] (case path - (^or {/.#Pop} - {/.#Access Access}) + (^.or {/.#Pop} + {/.#Access Access}) path_storage - (^ (/.path/bind register)) + (pattern (/.path/bind register)) (revised #bindings (set.has register) path_storage) @@ -383,30 +385,30 @@ (for_path otherwise path_storage)) (for_path default)) - (^or {/.#I64_Fork forks} - {/.#F64_Fork forks} - {/.#Text_Fork forks}) + (^.or {/.#I64_Fork forks} + {/.#F64_Fork forks} + {/.#Text_Fork forks}) (|> {.#Item forks} (list#each product.right) (list#mix for_path path_storage)) - (^or (^ (/.path/seq left right)) - (^ (/.path/alt left right))) + (^.or (pattern (/.path/seq left right)) + (pattern (/.path/alt left right))) (list#mix for_path path_storage (list left right)) - (^ (/.path/then bodyS)) + (pattern (/.path/then bodyS)) (loop for_synthesis [bodyS bodyS synthesis_storage path_storage] (case bodyS - (^or {/.#Simple _} - (^ (/.constant _))) + (^.or {/.#Simple _} + (pattern (/.constant _))) synthesis_storage - (^ (/.variant [lefts right? valueS])) + (pattern (/.variant [lefts right? valueS])) (for_synthesis valueS synthesis_storage) - (^ (/.tuple members)) + (pattern (/.tuple members)) (list#mix for_synthesis synthesis_storage members) {/.#Reference {///reference.#Variable {///reference/variable.#Local register}}} @@ -417,21 +419,21 @@ {/.#Reference {///reference.#Variable var}} (revised #dependencies (set.has var) synthesis_storage) - (^ (/.function/apply [functionS argsS])) + (pattern (/.function/apply [functionS argsS])) (list#mix for_synthesis synthesis_storage {.#Item functionS argsS}) - (^ (/.function/abstraction [environment arity bodyS])) + (pattern (/.function/abstraction [environment arity bodyS])) (list#mix for_synthesis synthesis_storage environment) - (^ (/.branch/case [inputS pathS])) + (pattern (/.branch/case [inputS pathS])) (revised #dependencies (set.union (the #dependencies (for_path pathS synthesis_storage))) (for_synthesis inputS synthesis_storage)) - (^ (/.branch/exec [before after])) + (pattern (/.branch/exec [before after])) (list#mix for_synthesis synthesis_storage (list before after)) - (^ (/.branch/let [inputS register exprS])) + (pattern (/.branch/let [inputS register exprS])) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.has register)) @@ -439,13 +441,13 @@ (the #dependencies))) (for_synthesis inputS synthesis_storage)) - (^ (/.branch/if [testS thenS elseS])) + (pattern (/.branch/if [testS thenS elseS])) (list#mix for_synthesis synthesis_storage (list testS thenS elseS)) - (^ (/.branch/get [access whole])) + (pattern (/.branch/get [access whole])) (for_synthesis whole synthesis_storage) - (^ (/.loop/scope [start initsS+ iterationS])) + (pattern (/.loop/scope [start initsS+ iterationS])) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.union (|> initsS+ @@ -456,7 +458,7 @@ (the #dependencies))) (list#mix for_synthesis synthesis_storage initsS+)) - (^ (/.loop/again replacementsS+)) + (pattern (/.loop/again replacementsS+)) (list#mix for_synthesis synthesis_storage replacementsS+) {/.#Extension [extension 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 e9ec84dca..164261eb6 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 @@ -13,6 +13,8 @@ ["%" format {"+" format}]] [collection ["[0]" list ("[1]#[0]" functor monoid)]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -56,7 +58,7 @@ argsS (monad.each ! (phase archive) argsA)] (with_expansions [<apply> (as_is (/.function/apply [funcS argsS]))] (case funcS - (^ (/.function/abstraction functionS)) + (pattern (/.function/abstraction functionS)) (if (n.= (the /.#arity functionS) (list.size argsS)) (do ! @@ -66,7 +68,7 @@ (maybe#each (: (-> [Nat (List Synthesis) Synthesis] Synthesis) (function (_ [start inits iteration]) (case iteration - (^ (/.loop/scope [start' inits' output])) + (pattern (/.loop/scope [start' inits' output])) (if (and (n.= start start') (list.empty? inits')) (/.loop/scope [start inits output]) @@ -77,7 +79,7 @@ (maybe.else <apply>)))) (in <apply>)) - (^ (/.function/apply [funcS' argsS'])) + (pattern (/.function/apply [funcS' argsS'])) (in (/.function/apply [funcS' (list#composite argsS' argsS)])) _ @@ -98,7 +100,7 @@ {/.#Bind register} (phase#in {/.#Bind (++ register)}) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (do phase.monad [left' (grow_path grow left) @@ -117,7 +119,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] elses]} (do [! phase.monad] [then (grow_path grow then) @@ -154,7 +156,7 @@ (monad.each phase.monad (grow environment)) (phase#each (|>> /.tuple)))) - (^ (..self_reference)) + (pattern (..self_reference)) (phase#in (/.function/apply [expression (list (/.variable/local 1))])) {/.#Reference reference} @@ -236,7 +238,7 @@ [funcS (grow environment funcS) argsS+ (monad.each ! (grow environment) argsS+)] (in (/.function/apply (case funcS - (^ (/.function/apply [(..self_reference) pre_argsS+])) + (pattern (/.function/apply [(..self_reference) pre_argsS+])) [(..self_reference) (list#composite pre_argsS+ argsS+)] @@ -261,7 +263,7 @@ (phase archive bodyA))) abstraction (: (Operation Abstraction) (case bodyS - (^ (/.function/abstraction [env' down_arity' bodyS'])) + (pattern (/.function/abstraction [env' down_arity' bodyS'])) (|> bodyS' (grow env') (# ! each (function (_ body) 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 f3d6b8b68..2121e37b9 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 @@ -8,6 +8,8 @@ [data [collection ["[0]" list]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -34,7 +36,7 @@ {/.#Bind register} {.#Some {/.#Bind (register_optimization offset register)}} - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} (do maybe.monad [left' (again left) @@ -53,7 +55,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] elses]} (do [! maybe.monad] [then (again then) @@ -99,53 +101,53 @@ {/.#Reference reference} (case reference - (^ {reference.#Variable (variable.self)}) + (pattern {reference.#Variable (variable.self)}) (if true_loop? {.#None} {.#Some expr}) - (^ (reference.constant constant)) + (pattern (reference.constant constant)) {.#Some expr} - (^ (reference.local register)) + (pattern (reference.local register)) {.#Some {/.#Reference (reference.local (register_optimization offset register))}} - (^ (reference.foreign register)) + (pattern (reference.foreign register)) (if true_loop? (list.item register scope_environment) {.#Some expr})) - (^ (/.branch/case [input path])) + (pattern (/.branch/case [input path])) (do maybe.monad [input' (again false input) path' (path_optimization (again return?) offset path)] (in (|> path' [input'] /.branch/case))) - (^ (/.branch/exec [this that])) + (pattern (/.branch/exec [this that])) (do maybe.monad [this (again false this) that (again return? that)] (in (/.branch/exec [this that]))) - (^ (/.branch/let [input register body])) + (pattern (/.branch/let [input register body])) (do maybe.monad [input' (again false input) body' (again return? body)] (in (/.branch/let [input' (register_optimization offset register) body']))) - (^ (/.branch/if [input then else])) + (pattern (/.branch/if [input then else])) (do maybe.monad [input' (again false input) then' (again return? then) else' (again return? else)] (in (/.branch/if [input' then' else']))) - (^ (/.branch/get [path record])) + (pattern (/.branch/get [path record])) (do maybe.monad [record (again false record)] (in (/.branch/get [path record]))) - (^ (/.loop/scope scope)) + (pattern (/.loop/scope scope)) (do [! maybe.monad] [inits' (|> scope (the /.#inits) @@ -155,24 +157,24 @@ /.#inits inits' /.#iteration iteration']))) - (^ (/.loop/again args)) + (pattern (/.loop/again args)) (|> args (monad.each maybe.monad (again false)) (maybe#each (|>> /.loop/again))) - (^ (/.function/abstraction [environment arity body])) + (pattern (/.function/abstraction [environment arity body])) (do [! maybe.monad] [environment' (monad.each ! (again false) environment)] (in (/.function/abstraction [environment' arity body]))) - (^ (/.function/apply [abstraction arguments])) + (pattern (/.function/apply [abstraction arguments])) (do [! maybe.monad] [arguments' (monad.each ! (again false) arguments)] (with_expansions [<application> (as_is (do ! [abstraction' (again false abstraction)] (in (/.function/apply [abstraction' arguments']))))] (case abstraction - (^ {/.#Reference {reference.#Variable (variable.self)}}) + (pattern {/.#Reference {reference.#Variable (variable.self)}}) (if (and return? (n.= arity (list.size arguments))) (in (/.loop/again arguments')) @@ -184,14 +186,14 @@ <application>))) ... TODO: Stop relying on this custom code. - (^ {/.#Extension ["lux syntax char case!" (list& input else matches)]}) + (pattern {/.#Extension ["lux syntax char case!" (list& input else matches)]}) (if return? (do [! maybe.monad] [input (again false input) matches (monad.each ! (function (_ match) (case match - (^ {/.#Structure {analysis/complex.#Tuple (list when then)}}) + (pattern {/.#Structure {analysis/complex.#Tuple (list when then)}}) (do ! [when (again false when) then (again return? then)] 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 74abfe432..3d795ff2f 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 @@ -15,6 +15,8 @@ ["[0]" dictionary {"+" Dictionary}] ["[0]" list ("[1]#[0]" functor mix)] ["[0]" set]]] + [macro + ["^" pattern]] [math [number ["n" nat]]]]] @@ -50,14 +52,14 @@ register)} (again post)}) - (^or {/.#Seq {/.#Access {/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 {/access.#Member member}} - {/.#Bind register}} - post}) + (^.or {/.#Seq {/.#Access {/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 {/access.#Member member}} + {/.#Bind register}} + post}) (if (n.= redundant register) (again post) {/.#Seq {/.#Access {/access.#Member member}} @@ -66,7 +68,7 @@ register)} (again post)}}) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([/.#Seq] @@ -75,7 +77,7 @@ {/.#Bit_Fork when then else} {/.#Bit_Fork when (again then) (maybe#each again else)} - (^template [<tag>] + (^.template [<tag>] [{<tag> [[test then] tail]} {<tag> [[test (again then)] (list#each (function (_ [test' then']) @@ -85,8 +87,8 @@ [/.#F64_Fork] [/.#Text_Fork]) - (^or {/.#Pop} - {/.#Access _}) + (^.or {/.#Pop} + {/.#Access _}) path {/.#Bind register} @@ -253,8 +255,8 @@ (-> (Optimization Synthesis) (Optimization Path)) (function (again [redundancy path]) (case path - (^or {/.#Pop} - {/.#Access _}) + (^.or {/.#Pop} + {/.#Access _}) {try.#Success [redundancy path]} @@ -272,7 +274,7 @@ (in [redundancy {.#None}]))] (in [redundancy {/.#Bit_Fork when then else}])) - (^template [<tag> <type>] + (^.template [<tag> <type>] [{<tag> [[test then] elses]} (do [! try.monad] [[redundancy then] (again [redundancy then]) 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 b4e9e5b28..3fd47f828 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -17,6 +17,8 @@ [collection ["[0]" list ("[1]#[0]" functor)] ["[0]" dictionary {"+" Dictionary}]]] + [macro + ["^" pattern]] [math [number ["[0]" i64] @@ -287,7 +289,7 @@ "") ")") - (^template [<tag> <format>] + (^.template [<tag> <format>] [{<tag> item} (|> {.#Item item} (list#each (function (_ [test then]) @@ -420,7 +422,7 @@ (= reference_then sample_then) (# (maybe.equivalence =) = reference_else sample_else)) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference_item} {<tag> sample_item}] (# (list.equivalence (product.equivalence <equivalence> =)) = @@ -430,7 +432,7 @@ [#F64_Fork f.equivalence] [#Text_Fork text.equivalence]) - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (# <equivalence> = reference' sample')]) ([#Access /access.equivalence] @@ -439,7 +441,7 @@ [{#Bind reference'} {#Bind sample'}] (n.= reference' sample') - (^template [<tag>] + (^.template [<tag>] [[{<tag> leftR rightR} {<tag> leftS rightS}] (and (= leftR leftS) (= rightR rightS))]) @@ -472,7 +474,7 @@ (hash then) (# (maybe.hash (path'_hash super)) hash else)) - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> item} (let [case_hash (product.hash <hash> (path'_hash super)) @@ -482,7 +484,7 @@ [13 #F64_Fork f.hash] [17 #Text_Fork text.hash]) - (^template [<factor> <tag>] + (^.template [<factor> <tag>] [{<tag> fork} (let [again_hash (path'_hash super) fork_hash (product.hash again_hash again_hash)] @@ -494,7 +496,7 @@ (n.* 29 (# super hash body)) ))) -(implementation: (branch_equivalence (^open "#[0]")) +(implementation: (branch_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Branch a)))) (def: (= reference sample) @@ -560,7 +562,7 @@ (# (..path'_hash super) hash path)) ))) -(implementation: (loop_equivalence (^open "/#[0]")) +(implementation: (loop_equivalence (open "/#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Loop a)))) (def: (= reference sample) @@ -596,7 +598,7 @@ (# (list.hash super) hash resets)) ))) -(implementation: (function_equivalence (^open "#[0]")) +(implementation: (function_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Function a)))) (def: (= reference sample) @@ -635,12 +637,12 @@ (# (list.hash super) hash arguments)) ))) -(implementation: (control_equivalence (^open "#[0]")) +(implementation: (control_equivalence (open "#[0]")) (All (_ a) (-> (Equivalence a) (Equivalence (Control a)))) (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (# (<equivalence> #=) = reference sample)]) ([#Branch ..branch_equivalence] @@ -658,7 +660,7 @@ (def: (hash value) (case value - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value} (n.* <factor> (# (<hash> super) hash value))]) ([2 #Branch ..branch_hash] @@ -671,7 +673,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (# <equivalence> = reference' sample')]) ([#Simple /simple.equivalence] @@ -695,7 +697,7 @@ (def: (hash value) (let [again_hash [..equivalence hash]] (case value - (^template [<tag> <hash>] + (^.template [<tag> <hash>] [{<tag> value} (# <hash> hash value)]) ([#Simple /simple.hash] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux index 7d98c463a..05b5201f8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux @@ -10,6 +10,8 @@ ["[0]" bit ("[1]#[0]" equivalence)] ["[0]" text ("[1]#[0]" equivalence) ["%" format]]] + [macro + ["^" pattern]] [math [number ["[0]" i64 ("[1]#[0]" equivalence)] @@ -27,7 +29,7 @@ (def: .public (format it) (%.Format Simple) (case it - (^template [<pattern> <format>] + (^.template [<pattern> <format>] [{<pattern> value} (<format> value)]) ([#Bit %.bit] @@ -42,7 +44,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <eq> <format>] + (^.template [<tag> <eq> <format>] [[{<tag> reference'} {<tag> sample'}] (<eq> reference' sample')]) ([#Bit bit#= %.bit] @@ -62,7 +64,7 @@ (def: hash (|>> (pipe.case - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value'} (n.* <factor> (# <hash> hash value'))]) ([2 #Bit bit.hash] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index a63bde0a1..58bb26a18 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -88,7 +88,7 @@ (def: .public (id module archive) (-> descriptor.Module Archive (Try module.ID)) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} {try.#Success id} @@ -99,7 +99,7 @@ (def: .public (reserve module archive) (-> descriptor.Module Archive (Try [module.ID Archive])) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some _} (exception.except ..module_has_already_been_reserved [module]) @@ -114,7 +114,7 @@ (def: .public (has module entry archive) (-> descriptor.Module (Entry Any) Archive (Try Archive)) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#None}]} {try.#Success (|> archive @@ -142,7 +142,7 @@ (def: .public (find module archive) (-> descriptor.Module Archive (Try (Entry Any))) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#Some entry}]} {try.#Success entry} @@ -174,7 +174,7 @@ (def: .public (reserved? archive module) (-> Archive descriptor.Module Bit) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} true @@ -236,7 +236,7 @@ (def: .public (export version archive) (-> Version Archive Binary) - (let [(^open "/[0]") (:representation archive)] + (let [(open "/[0]") (:representation archive)] (|> /#resolver dictionary.entries (list.all (function (_ [module [id descriptor+document]]) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux index 61698487d..3f1bf2256 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact/category.lux @@ -8,6 +8,8 @@ [data ["[0]" product] ["[0]" text ("[1]#[0]" equivalence)]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]]]] @@ -49,7 +51,7 @@ [{#Definition left} {#Definition right}] (# definition_equivalence = left right) - (^template [<tag>] + (^.template [<tag>] [[{<tag> left} {<tag> right}] (text#= left right)]) ([#Analyser] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux index cc8fbbf2b..e798429e1 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/descriptor.lux @@ -13,6 +13,8 @@ ["[0]" set {"+" Set}]] ["[0]" format "_" ["[1]" binary {"+" Writer}]]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]] @@ -39,7 +41,7 @@ (def: (= left right) (case [left right] - (^template [<tag>] + (^.template [<tag>] [[{<tag>} {<tag>}] true]) ([.#Active] diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux index a1a201a79..8c11b0fca 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -20,6 +20,8 @@ ["[0]" dictionary {"+" Dictionary}]] [format ["[0]" binary {"+" Writer}]]] + [macro + ["^" pattern]] [type abstract]]] ["[0]" // "_" @@ -117,7 +119,7 @@ category (: (Writer Category) (function (_ value) (case value - (^template [<nat> <tag> <writer>] + (^.template [<nat> <tag> <writer>] [{<tag> value} ((binary.and binary.nat <writer>) [<nat> value])]) ([0 //category.#Anonymous binary.any] @@ -162,7 +164,7 @@ (do [! <>.monad] [tag <binary>.nat] (case tag - (^template [<nat> <tag> <parser>] + (^.template [<nat> <tag> <parser>] [<nat> (# ! each (|>> {<tag>}) <parser>)]) ([0 //category.#Anonymous <binary>.any] @@ -186,7 +188,7 @@ {//category.#Anonymous} (..resource mandatory? dependencies registry) - (^template [<tag> <create>] + (^.template [<tag> <create>] [{<tag> name} (<create> name mandatory? dependencies registry)]) ([//category.#Definition ..definition] diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux index f1c4a4806..90085fc31 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/artifact.lux @@ -12,6 +12,8 @@ ["[0]" set {"+" Set}] ["[0]" dictionary {"+" Dictionary}] ["[0]" sequence]]] + [macro + ["^" pattern]] [math [number ["[0]" nat]]] @@ -38,12 +40,12 @@ (-> Path (List Constant))) (function (again path) (case path - (^or {synthesis.#Pop} - {synthesis.#Access _} - {synthesis.#Bind _}) + (^.or {synthesis.#Pop} + {synthesis.#Access _} + {synthesis.#Bind _}) (list) - (^template [<tag>] + (^.template [<tag>] [{<tag> left right} ($_ list#composite (again left) @@ -61,7 +63,7 @@ {.#None} (again then)) - (^template [<tag>] + (^.template [<tag>] [{<tag> fork} (|> {.#Item fork} (list#each (|>> product.right again)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux index ba6bb8706..bbc2735e7 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux @@ -15,6 +15,8 @@ ["%" format]] [collection ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["^" pattern]] [math [number {"+" hex}]] [meta @@ -107,7 +109,7 @@ (def: .public target (-> Service Target) (|>> (pipe.case - (^or {#Compilation [host_dependencies libraries compilers sources target module]} - {#Interpretation [host_dependencies libraries compilers sources target module]} - {#Export [sources target]}) + (^.or {#Compilation [host_dependencies libraries compilers sources target module]} + {#Interpretation [host_dependencies libraries compilers sources target module]} + {#Export [sources target]}) target))) 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 f4125ab61..95d9a5e1a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -20,6 +20,8 @@ ["[0]" list ("[1]#[0]" mix)] ["[0]" dictionary {"+" Dictionary}] ["[0]" sequence {"+" Sequence}]]] + [macro + ["^" pattern]] [meta ["[0]" configuration {"+" Configuration}] ["[0]" version]] @@ -219,7 +221,7 @@ content (document.content $.key document) definitions (monad.each ! (function (_ [def_name def_global]) (case def_global - (^template [<tag>] + (^.template [<tag>] [{<tag> payload} (in [def_name {<tag> payload}])]) ([.#Alias] diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index 7dff736ed..3e962f14f 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -9,6 +9,8 @@ [data [text ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat]]] @@ -30,7 +32,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag> <equivalence>] + (^.template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (# <equivalence> = reference sample)]) ([#Variable /variable.equivalence] @@ -47,7 +49,7 @@ (def: (hash value) (case value - (^template [<factor> <tag> <hash>] + (^.template [<factor> <tag> <hash>] [{<tag> value} (|> value (# <hash> hash) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 0614c5b30..a9d4f432e 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -9,6 +9,8 @@ [data [text ["%" format {"+" Format}]]] + [macro + ["^" pattern]] [math [number ["n" nat] @@ -27,7 +29,7 @@ (def: (= reference sample) (case [reference sample] - (^template [<tag>] + (^.template [<tag>] [[{<tag> reference'} {<tag> sample'}] (n.= reference' sample')]) ([#Local] [#Foreign]) @@ -43,7 +45,7 @@ (def: hash (|>> (pipe.case - (^template [<factor> <tag>] + (^.template [<factor> <tag>] [{<tag> register} (|> register (# n.hash hash) @@ -57,7 +59,7 @@ (def: .public self? (-> Variable Bit) (|>> (pipe.case - (^ (..self)) + (pattern (..self)) true _ |