diff options
author | Eduardo Julian | 2022-07-03 00:35:32 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-07-03 00:35:32 -0400 |
commit | 9e7ddacf853efd7a18c1911d2f287d483b083229 (patch) | |
tree | 140eee091b7453879f072a48044635d03aa5096b /stdlib/source/library/lux/tool/compiler | |
parent | 7e4c9ba2e02f06fa621ffe24bc0ca046536429ef (diff) |
Added a new custom type for pattern-matching macros.
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
45 files changed, 287 insertions, 286 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 2442874a0..b975614df 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except Tuple Variant nat int rev case local except) + [lux (.except Tuple Variant Pattern nat int rev case local except) [abstract [equivalence (.only Equivalence)] [hash (.only Hash)] 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 aefb5abc7..dd5fde4f2 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 @@ -1,6 +1,6 @@ (.require [library - [lux (.except Variant) + [lux (.except Variant Pattern) [abstract [equivalence (.except)] ["[0]" monad (.only do)]] @@ -191,7 +191,8 @@ ... their sub-patterns. {//pattern.#Complex {//complex.#Tuple membersP+}} (case (list.reversed membersP+) - (^.or (pattern (list)) (pattern (list _))) + (^.or (list) + (list _)) (exception.except ..invalid_tuple [(list.size membersP+)]) {.#Item lastP prevsP+} 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 d25fb1f8a..f91c4a145 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 @@ -161,7 +161,7 @@ [[just_before vars :inference: terms] (general' (list) archive analyse inferT args)] (in [:inference: terms]) ... (case vars - ... (pattern (list)) + ... (list) ... (in [:inference: terms]) ... _ 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 2e2982214..9a5de364f 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 - (pattern (list single)) + (list single) (in single) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux index 52c5de8fc..daf608222 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/pattern.lux @@ -1,6 +1,6 @@ (.require [library - [lux (.except nat int rev) + [lux (.except Pattern nat int rev) [abstract [equivalence (.only Equivalence)]] [data 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 594626581..30e4a1360 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 @@ -44,7 +44,7 @@ (template (_ analysis archive tag values) ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) [(case values - (pattern (list value)) + (list value) (/complex.variant analysis tag archive value) _ @@ -54,7 +54,7 @@ (template (_ analysis archive lefts right? values) ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) [(case values - (pattern (list value)) + (list value) (/complex.sum analysis lefts right? archive value) _ @@ -77,7 +77,7 @@ [[functionT functionA] (/type.inferring (analysis archive functionC))] (case functionA - (pattern (/.constant def_name)) + (/.constant def_name) (do ! [?macro (//extension.lifted (meta.macro def_name))] (case ?macro 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 65d951e0a..6356d32c5 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 @@ -1,6 +1,6 @@ (.require [library - [lux (.except case) + [lux (.except Pattern case) [abstract ["[0]" monad (.only do)]] [control @@ -246,7 +246,7 @@ [Text {.#Text pattern_value} {/simple.#Text pattern_value}] [Any {.#Tuple {.#End}} {/simple.#Unit}]) - (pattern [location {.#Tuple (list singleton)}]) + [location {.#Tuple (list singleton)}] (pattern_analysis {.#None} :input: singleton next) [location {.#Tuple sub_patterns}] @@ -274,7 +274,7 @@ _ (in []))] (.case members - (pattern (list singleton)) + (list singleton) (pattern_analysis {.#None} :input: singleton next) _ @@ -283,7 +283,7 @@ {.#None} (..tuple_pattern_analysis pattern_analysis :input: sub_patterns next)))) - (pattern [location {.#Variant (list.partial [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}]) + [location {.#Variant (list.partial [_ {.#Nat lefts}] [_ {.#Bit right?}] values)}] (/.with_location location (do ///.monad [[@ex_var+ :input:'] (/type.check (..tuple :input:))] @@ -324,7 +324,7 @@ _ (/.except ..mismatch [:input:' pattern])))) - (pattern [location {.#Variant (list.partial [_ {.#Symbol tag}] values)}]) + [location {.#Variant (list.partial [_ {.#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 2ee8cae7d..d7b26aa8f 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 @@ -294,14 +294,14 @@ output (is (List [Symbol Code]) {.#End})]) (case input - (pattern (list.partial [_ {.#Symbol ["" slotH]}] valueH tail)) + (list.partial [_ {.#Symbol ["" slotH]}] valueH tail) (if pattern_matching? (///#in {.#None}) (do ///.monad [slotH (///extension.lifted (meta.normal ["" slotH]))] (again tail {.#Item [slotH valueH] output}))) - (pattern (list.partial [_ {.#Symbol slotH}] valueH tail)) + (list.partial [_ {.#Symbol slotH}] valueH tail) (do ///.monad [slotH (///extension.lifted (meta.normal slotH))] (again tail {.#Item [slotH valueH] output})) @@ -386,13 +386,13 @@ (def .public (record analyse archive members) (-> Phase Archive (List Code) (Operation Analysis)) (case members - (pattern (list)) + (list) //simple.unit - (pattern (list singletonC)) + (list singletonC) (analyse archive singletonC) - (pattern (list [_ {.#Symbol pseudo_slot}] singletonC)) + (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/declaration.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/declaration.lux index 806308519..86602280e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/declaration.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/declaration.lux @@ -90,17 +90,17 @@ extension_eval (as Eval (wrapper (as_expected compiler_eval)))] _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code - (pattern [_ {.#Form (list.partial [_ {.#Text name}] inputs)}]) + [_ {.#Form (list.partial [_ {.#Text name}] inputs)}] (//extension.apply archive again [name inputs]) - (pattern [_ {.#Form (list.partial macro inputs)}]) + [_ {.#Form (list.partial macro inputs)}] (do ! [expansion (/.lifted_analysis (do ! [macroA (<| (///analysis/type.expecting Macro) (analysis archive macro))] (case macroA - (pattern (///analysis.constant macro_name)) + (///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 - (pattern (list.partial <lux_def_module> referrals)) + (list.partial <lux_def_module> referrals) (|> (again archive <lux_def_module>) (at ! each (revised /.#referrals (list#composite referrals)))) 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 39dc0ac97..eb88d937f 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 @@ -410,7 +410,7 @@ {.#None} (/////analysis.except ..non_jvm_type luxT)) - (pattern (lux_array_type elemT _)) + (lux_array_type elemT _) (phase#each jvm.array (jvm_type elemT)) {.#Primitive class parametersT} @@ -461,7 +461,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list arrayC)) + (list arrayC) (do phase.monad [_ (typeA.inference ..int) arrayA (<| (typeA.expecting {.#Primitive (|> (jvm.array primitive_type) @@ -477,7 +477,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list arrayC)) + (list arrayC) (<| typeA.with_var (function (_ [@read :read:])) typeA.with_var @@ -499,7 +499,7 @@ (-> (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list lengthC)) + (list lengthC) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -514,7 +514,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list lengthC)) + (list lengthC) (do phase.monad [lengthA (<| (typeA.expecting ..int) (analyse archive lengthC)) @@ -535,7 +535,7 @@ (def (check_parameter objectT) (-> .Type (Operation (Type Parameter))) (case objectT - (pattern (lux_array_type elementT _)) + (lux_array_type elementT _) (/////analysis.except ..non_parameter objectT) {.#Primitive name parameters} @@ -631,7 +631,7 @@ ... else (phase#in (jvm.class name (list))))) - (pattern (lux_array_type elementT _)) + (lux_array_type elementT _) (|> elementT check_jvm (phase#each jvm.array)) @@ -698,7 +698,7 @@ (-> .Type (Type Primitive) Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list idxC arrayC)) + (list idxC arrayC) (do phase.monad [_ (typeA.inference lux_type) idxA (<| (typeA.expecting ..int) @@ -715,7 +715,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list idxC arrayC)) + (list idxC arrayC) (<| typeA.with_var (function (_ [@read :read:])) typeA.with_var @@ -742,7 +742,7 @@ (list)}] (function (_ extension_name analyse archive args) (case args - (pattern (list idxC valueC arrayC)) + (list idxC valueC arrayC) (do phase.monad [_ (typeA.inference array_type) idxA (<| (typeA.expecting ..int) @@ -762,7 +762,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list idxC valueC arrayC)) + (list idxC valueC arrayC) (<| typeA.with_var (function (_ [@read :read:])) typeA.with_var @@ -840,7 +840,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list)) + (list) (do phase.monad [expectedT (///.lifted meta.expected_type) [_ :object:] (check_object expectedT) @@ -854,7 +854,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list objectC)) + (list objectC) (do phase.monad [_ (typeA.inference .Bit) [objectT objectA] (typeA.inferring @@ -869,7 +869,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list monitorC exprC)) + (list monitorC exprC) (do phase.monad [[monitorT monitorA] (typeA.inferring (analyse archive monitorC)) @@ -884,7 +884,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list exceptionC)) + (list exceptionC) (do phase.monad [_ (typeA.inference Nothing) [exceptionT exceptionA] (typeA.inferring @@ -904,7 +904,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list classC)) + (list classC) (case classC [_ {.#Text class}] (do phase.monad @@ -961,7 +961,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 - (pattern {.#Primitive _ (list.partial self_classT super_classT super_interfacesT+)}) + {.#Primitive _ (list.partial self_classT super_classT super_interfacesT+)} (monad.each phase.monad (function (_ superT) (do [! phase.monad] @@ -978,7 +978,7 @@ (-> java/lang/ClassLoader Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list fromC)) + (list fromC) (do [! phase.monad] [toT (///.lifted meta.expected_type) target_name (at ! each ..reflection (check_jvm toT)) 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 367240a34..005ecde81 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 @@ -139,7 +139,7 @@ Handler (function (_ extension_name analyse archive args) (case args - (pattern (list opC)) + (list opC) (<| typeA.with_var (function (_ [@var :var:])) (do [! ////.monad] @@ -156,7 +156,7 @@ Handler (function (_ extension_name analyse archive argsC+) (case argsC+ - (pattern (list [_ {.#Text module_name}] exprC)) + (list [_ {.#Text module_name}] exprC) (////analysis.with_current_module module_name (analyse archive exprC)) @@ -167,7 +167,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list typeC valueC)) + (list typeC valueC) (do [! ////.monad] [actualT (at ! each (|>> (as Type)) (eval archive Type typeC)) @@ -182,7 +182,7 @@ (-> Eval Handler) (function (_ extension_name analyse archive args) (case args - (pattern (list typeC valueC)) + (list typeC valueC) (do [! ////.monad] [actualT (at ! each (|>> (as Type)) (eval archive Type typeC)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux index 8c5f5dbc8..c992c73a8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/declaration/lux.lux @@ -127,7 +127,7 @@ [interim_artifacts codeG] (/////generation.with_interim_artifacts archive (generate archive codeS)) .let [@abstraction (case codeS - (pattern (/////synthesis.function/abstraction [env arity body])) + (/////synthesis.function/abstraction [env arity body]) (|> interim_artifacts list.last (maybe#each (|>> [arity]))) @@ -246,7 +246,7 @@ (-> Expander /////analysis.Bundle Handler) (function (_ extension_name phase archive inputsC+) (case inputsC+ - (pattern (list [_ {.#Symbol ["" short_name]}] valueC exported?C)) + (list [_ {.#Symbol ["" short_name]}] valueC exported?C) (do phase.monad [current_module (/////declaration.lifted_analysis (///.lifted meta.current_module_name)) @@ -426,7 +426,7 @@ (Handler anchor expression declaration))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (pattern (list nameC valueC)) + (list nameC valueC) (do phase.monad [target_platform (/////declaration.lifted_analysis (///.lifted meta.target)) @@ -434,11 +434,11 @@ [_ handlerV] (<definer> archive (as Text name) (let [raw_type (type_literal <def_type>)] (case target_platform - (^.or (pattern (static @.jvm)) - (pattern (static @.js))) + (^.or (static @.jvm) + (static @.js)) raw_type - (pattern (static @.python)) + (static @.python) (swapped binary.Binary Binary|Python raw_type) _ @@ -519,7 +519,7 @@ (-> (Program expression declaration) (Handler anchor expression declaration))) (function (handler extension_name phase archive inputsC+) (case inputsC+ - (pattern (list programC)) + (list programC) (do phase.monad [state (///.lifted phase.state) .let [analyse (the [/////declaration.#analysis /////declaration.#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 3205b9933..582107b3c 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 @@ -109,7 +109,7 @@ (in (as Statement body))) (^.with_template [<tag>] - [(pattern (<tag> value)) + [(<tag> value) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -121,30 +121,30 @@ [synthesis.function/apply]) (^.with_template [<tag>] - [(pattern {<tag> value}) + [{<tag> value} (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (//case.case! statement expression archive case) - (pattern (synthesis.branch/exec it)) + (synthesis.branch/exec it) (//case.exec! statement expression archive it) - (pattern (synthesis.branch/let let)) + (synthesis.branch/let let) (//case.let! statement expression archive let) - (pattern (synthesis.branch/if if)) + (synthesis.branch/if if) (//case.if! statement expression archive if) - (pattern (synthesis.loop/scope scope)) + (synthesis.loop/scope scope) (//loop.scope! statement expression archive scope) - (pattern (synthesis.loop/again updates)) + (synthesis.loop/again updates) (//loop.again! statement expression archive updates) - (pattern (synthesis.function/abstraction abstraction)) + (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 b72b69b2c..0d0a38730 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 @@ -830,7 +830,7 @@ [1 _]) body - (pattern [2 {synthesis.#Control {synthesis.#Branch {synthesis.#Let _ 2 (synthesis.tuple (list _ hidden))}}}]) + [2 {synthesis.#Control {synthesis.#Branch {synthesis.#Let _ 2 (synthesis.tuple (list _ hidden))}}}] hidden [_ {synthesis.#Control {synthesis.#Branch {synthesis.#Case _ path}}}] @@ -839,7 +839,7 @@ {synthesis.#Seq _ next} (again next) - (pattern {synthesis.#Then (synthesis.tuple (list _ hidden))}) + {synthesis.#Then (synthesis.tuple (list _ hidden))} hidden _ @@ -1004,11 +1004,11 @@ (-> Path Path)) (function (again path) (case path - (pattern (synthesis.path/then bodyS)) + (synthesis.path/then bodyS) (synthesis.path/then (normalize bodyS)) (^.with_template [<tag>] - [(pattern {<tag> leftP rightP}) + [{<tag> leftP rightP} {<tag> (again leftP) (again rightP)}]) ([synthesis.#Alt] [synthesis.#Seq]) @@ -1041,48 +1041,48 @@ (function (again body) (case body (^.with_template [<tag>] - [(pattern <tag>) + [<tag> body]) ([{synthesis.#Simple _}] [(synthesis.constant _)]) - (pattern (synthesis.variant [lefts right? sub])) + (synthesis.variant [lefts right? sub]) (synthesis.variant [lefts right? (again sub)]) - (pattern (synthesis.tuple members)) + (synthesis.tuple members) (synthesis.tuple (list#each again members)) - (pattern (synthesis.variable var)) + (synthesis.variable var) (|> mapping (dictionary.value body) (maybe.else var) synthesis.variable) - (pattern (synthesis.branch/case [inputS pathS])) + (synthesis.branch/case [inputS pathS]) (synthesis.branch/case [(again inputS) (normalize_path again pathS)]) - (pattern (synthesis.branch/exec [this that])) + (synthesis.branch/exec [this that]) (synthesis.branch/exec [(again this) (again that)]) - (pattern (synthesis.branch/let [inputS register outputS])) + (synthesis.branch/let [inputS register outputS]) (synthesis.branch/let [(again inputS) register (again outputS)]) - (pattern (synthesis.branch/if [testS thenS elseS])) + (synthesis.branch/if [testS thenS elseS]) (synthesis.branch/if [(again testS) (again thenS) (again elseS)]) - (pattern (synthesis.branch/get [path recordS])) + (synthesis.branch/get [path recordS]) (synthesis.branch/get [path (again recordS)]) - (pattern (synthesis.loop/scope [offset initsS+ bodyS])) + (synthesis.loop/scope [offset initsS+ bodyS]) (synthesis.loop/scope [offset (list#each again initsS+) (again bodyS)]) - (pattern (synthesis.loop/again updatesS+)) + (synthesis.loop/again updatesS+) (synthesis.loop/again (list#each again updatesS+)) - (pattern (synthesis.function/abstraction [environment arity bodyS])) + (synthesis.function/abstraction [environment arity bodyS]) (synthesis.function/abstraction [(list#each (function (_ captured) (case captured - (pattern (synthesis.variable var)) + (synthesis.variable var) (|> mapping (dictionary.value captured) (maybe.else var) @@ -1094,7 +1094,7 @@ arity bodyS]) - (pattern (synthesis.function/apply [functionS inputsS+])) + (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 abaf8d32f..00cd16e75 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 @@ -71,7 +71,7 @@ (in (as Statement body))) (^.with_template [<tag>] - [(pattern (<tag> value)) + [(<tag> value) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -83,32 +83,32 @@ [synthesis.function/apply]) (^.with_template [<tag>] - [(pattern {<tag> value}) + [{<tag> value} (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (//case.case! statement expression archive case) - (pattern (synthesis.branch/exec it)) + (synthesis.branch/exec it) (//case.exec! statement expression archive it) - (pattern (synthesis.branch/let let)) + (synthesis.branch/let let) (//case.let! statement expression archive let) - (pattern (synthesis.branch/if if)) + (synthesis.branch/if if) (//case.if! statement expression archive if) - (pattern (synthesis.loop/scope scope)) + (synthesis.loop/scope scope) (do /////.monad [[inits scope!] (//loop.scope! statement expression archive false scope)] (in scope!)) - (pattern (synthesis.loop/again updates)) + (synthesis.loop/again updates) (//loop.again! statement expression archive updates) - (pattern (synthesis.function/abstraction abstraction)) + (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 37ac2d627..6d42c51e7 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 @@ -56,7 +56,7 @@ (in (as (Statement Any) body))) (^.with_template [<tag>] - [(pattern (<tag> value)) + [(<tag> value) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -68,16 +68,16 @@ [synthesis.function/apply]) (^.with_template [<tag>] - [(pattern {<tag> value}) + [{<tag> value} (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (//case.case! false statement expression archive case) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -85,7 +85,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (pattern (synthesis.function/abstraction abstraction)) + (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 95b08bf3c..944bcec7c 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 @@ -68,7 +68,7 @@ body))) (^.with_template [<tag>] - [(pattern (<tag> value)) + [(<tag> value) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] [synthesis.i64] @@ -80,16 +80,16 @@ [synthesis.function/apply]) (^.with_template [<tag>] - [(pattern {<tag> value}) + [{<tag> value} (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] [synthesis.#Extension]) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (//case.case! false statement expression archive case) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] [synthesis.branch/let //case.let!] @@ -97,7 +97,7 @@ [synthesis.loop/scope //loop.scope!] [synthesis.loop/again //loop.again!]) - (pattern (synthesis.function/abstraction abstraction)) + (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 8af11bb77..1168d5b8b 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 @@ -30,7 +30,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -41,7 +41,7 @@ (//reference.reference /reference.system archive value) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<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 6059eddc2..c00fab798 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 @@ -141,7 +141,7 @@ (Generator [Var/1 _.Tag _.Tag Path]) (function (again [$output @done @fail pathP]) (.case pathP - (pattern (/////synthesis.path/then bodyS)) + (/////synthesis.path/then bodyS) (at ///////phase.monad each (function (_ outputV) (_.progn (list (_.setq $output outputV) @@ -190,40 +190,40 @@ [/////synthesis.#Text_Fork //primitive.text _.string=/2]) (^.with_template [<complex> <simple> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> @fail false idx {.#None})) - (pattern (<simple> idx nextP)) + (<simple> idx nextP) (|> nextP [$output @done @fail] again (at ///////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]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (..push! (_.elt/2 [..peek (_.int +0)]))) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.!multi_pop nextP)) + (/////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!))))) - (pattern (/////synthesis.path/alt preP postP)) + (/////synthesis.path/alt preP postP) (do [! ///////phase.monad] [@otherwise (at ! 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!))) - (pattern (/////synthesis.path/seq preP postP)) + (/////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 9ab55a0a6..9d2c7e1db 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 @@ -40,7 +40,7 @@ (function ((, g!_) (, g!extension)) (function ((, g!_) (, g!name) (, g!phase) (, g!archive) (, g!inputs)) (case (, g!inputs) - (pattern (list (,* g!input+))) + (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 907159f8a..bf12be34e 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 @@ -39,47 +39,47 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (pattern (synthesis.variant variantS)) + (synthesis.variant variantS) (/structure.variant expression archive variantS) - (pattern (synthesis.tuple members)) + (synthesis.tuple members) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (/case.case ///extension/common.statement expression archive case) - (pattern (synthesis.branch/exec it)) + (synthesis.branch/exec it) (/case.exec expression archive it) - (pattern (synthesis.branch/let let)) + (synthesis.branch/let let) (/case.let expression archive let) - (pattern (synthesis.branch/if if)) + (synthesis.branch/if if) (/case.if expression archive if) - (pattern (synthesis.branch/get get)) + (synthesis.branch/get get) (/case.get expression archive get) - (pattern (synthesis.loop/scope scope)) + (synthesis.loop/scope scope) (/loop.scope ///extension/common.statement expression archive scope) - (pattern (synthesis.loop/again updates)) + (synthesis.loop/again updates) (//////phase.except ..cannot_recur_as_an_expression []) - (pattern (synthesis.function/abstraction abstraction)) + (synthesis.function/abstraction abstraction) (/function.function ///extension/common.statement expression archive abstraction) - (pattern (synthesis.function/apply application)) + (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 24e27bd78..e93ef8b99 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 @@ -183,20 +183,20 @@ (-> Path (Operation (Maybe Statement)))) (.case pathP (^.with_template [<simple> <choice>] - [(pattern (<simple> idx nextP)) + [(<simple> idx nextP) (|> nextP again (at ///////phase.monad each (|>> (_.then (<choice> true idx)) {.#Some})))]) ([/////synthesis.simple_left_side ..left_choice] [/////synthesis.simple_right_side ..right_choice]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in {.#Some (push_cursor! (_.at (_.i32 +0) ..peek_cursor))}) ... Extra optimization - (pattern (/////synthesis.path/seq - (/////synthesis.member/left 0) - (/////synthesis.!bind_top register thenP))) + (/////synthesis.path/seq + (/////synthesis.member/left 0) + (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (in {.#Some (all _.then @@ -205,9 +205,9 @@ ... Extra optimization (^.with_template [<pm> <getter>] - [(pattern (/////synthesis.path/seq - (<pm> lefts) - (/////synthesis.!bind_top register thenP))) + [(/////synthesis.path/seq + (<pm> lefts) + (/////synthesis.!bind_top register thenP)) (do ///////phase.monad [then! (again thenP)] (in {.#Some (all _.then @@ -216,14 +216,14 @@ ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.!bind_top register thenP)) + (/////synthesis.!bind_top register thenP) (do ///////phase.monad [then! (again thenP)] (in {.#Some (all _.then (_.define (..register register) ..peek_and_pop_cursor) then!)})) - (pattern (/////synthesis.!multi_pop nextP)) + (/////synthesis.!multi_pop nextP) (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -299,19 +299,19 @@ [/////synthesis.#Text_Fork //primitive.text]) (^.with_template [<complex> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> false idx))]) ([/////synthesis.side/left ..left_choice] [/////synthesis.side/right ..right_choice]) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (push_cursor! (<getter> (_.i32 (.int lefts)) ..peek_cursor)))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) (^.with_template [<tag> <combinator>] - [(pattern (<tag> leftP rightP)) + [(<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 98411011a..124c94a02 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 - (pattern (list)) + (list) body - (pattern (list binding)) + (list binding) (let [$binding (//case.register offset)] (all _.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 8b5ee06f9..b1fa42f27 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 @@ -26,17 +26,17 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (///#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (pattern (synthesis.variant variantS)) + (synthesis.variant variantS) (/structure.variant generate archive variantS) - (pattern (synthesis.tuple members)) + (synthesis.tuple members) (/structure.tuple generate archive members) {synthesis.#Reference reference} @@ -47,31 +47,31 @@ {reference.#Constant constant} (/reference.constant archive constant)) - (pattern (synthesis.branch/case [valueS pathS])) + (synthesis.branch/case [valueS pathS]) (/case.case generate archive [valueS pathS]) - (pattern (synthesis.branch/exec [this that])) + (synthesis.branch/exec [this that]) (/case.exec generate archive [this that]) - (pattern (synthesis.branch/let [inputS register bodyS])) + (synthesis.branch/let [inputS register bodyS]) (/case.let generate archive [inputS register bodyS]) - (pattern (synthesis.branch/if [conditionS thenS elseS])) + (synthesis.branch/if [conditionS thenS elseS]) (/case.if generate archive [conditionS thenS elseS]) - (pattern (synthesis.branch/get [path recordS])) + (synthesis.branch/get [path recordS]) (/case.get generate archive [path recordS]) - (pattern (synthesis.loop/scope scope)) + (synthesis.loop/scope scope) (/loop.scope generate archive scope) - (pattern (synthesis.loop/again updates)) + (synthesis.loop/again updates) (/loop.again generate archive updates) - (pattern (synthesis.function/abstraction abstraction)) + (synthesis.function/abstraction abstraction) (/function.abstraction generate archive abstraction) - (pattern (synthesis.function/apply application)) + (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 bc03aae26..2903069f8 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 @@ -184,7 +184,7 @@ body! (_.when_continuous (_.goto @end))))) - (pattern (synthesis.side lefts right?)) + (synthesis.side lefts right?) (operation#in (do _.monad [@success _.new_label] @@ -202,16 +202,16 @@ //runtime.push))) (^.with_template [<pattern> <projection>] - [(pattern (<pattern> lefts)) + [(<pattern> lefts) (operation#in (all _.composite ..peek (<projection> lefts) //runtime.push)) ... Extra optimization - (pattern (synthesis.path/seq - (<pattern> lefts) - (synthesis.!bind_top register thenP))) + (synthesis.path/seq + (<pattern> lefts) + (synthesis.!bind_top register thenP)) (do phase.monad [then! (path' stack_depth @else @end phase archive thenP)] (in (all _.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 200b4db2e..13d5eb827 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 - (pattern (synthesis.constant $abstraction)) + (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/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/loop.lux index f95ac11cc..8758e7b06 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 - (pattern (synthesis.variable/local var)) + (synthesis.variable/local var) (n.= register var) _ 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 6971e4cfa..fbfb53b71 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 @@ -39,47 +39,47 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] [synthesis.i64 /primitive.i64] [synthesis.f64 /primitive.f64] [synthesis.text /primitive.text]) - (pattern (synthesis.variant variantS)) + (synthesis.variant variantS) (/structure.variant expression archive variantS) - (pattern (synthesis.tuple members)) + (synthesis.tuple members) (/structure.tuple expression archive members) {synthesis.#Reference value} (//reference.reference /reference.system archive value) - (pattern (synthesis.branch/case case)) + (synthesis.branch/case case) (/case.case ///extension/common.statement expression archive case) - (pattern (synthesis.branch/exec it)) + (synthesis.branch/exec it) (/case.exec expression archive it) - (pattern (synthesis.branch/let let)) + (synthesis.branch/let let) (/case.let expression archive let) - (pattern (synthesis.branch/if if)) + (synthesis.branch/if if) (/case.if expression archive if) - (pattern (synthesis.branch/get get)) + (synthesis.branch/get get) (/case.get expression archive get) - (pattern (synthesis.loop/scope scope)) + (synthesis.loop/scope scope) (/loop.scope ///extension/common.statement expression archive scope) - (pattern (synthesis.loop/again updates)) + (synthesis.loop/again updates) (//////phase.except ..cannot_recur_as_an_expression []) - (pattern (synthesis.function/abstraction abstraction)) + (synthesis.function/abstraction abstraction) (/function.function ///extension/common.statement expression archive abstraction) - (pattern (synthesis.function/apply application)) + (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 ea8ca09f0..9e0103911 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 @@ -229,24 +229,24 @@ [/////synthesis.#Text_Fork _.string]) (^.with_template [<complex> <simple> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> false idx)) - (pattern (<simple> idx nextP)) + (<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]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (|> ..peek (_.item (_.int +1)) ..push!)) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.!bind_top register thenP)) + (/////synthesis.!bind_top register thenP) (do ///////phase.monad [then! (again thenP)] (///////phase#in (all _.then @@ -254,7 +254,7 @@ then!))) (^.with_template [<tag> <combinator>] - [(pattern (<tag> preP postP)) + [(<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 e96ac884a..55c495cee 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 @@ -34,7 +34,7 @@ Phase! (case synthesis (^.with_template [<tag>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.bit] [////synthesis.i64] @@ -46,23 +46,23 @@ [////synthesis.function/apply]) (^.with_template [<tag>] - [(pattern {<tag> value}) + [{<tag> value} (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.#Reference] [////synthesis.#Extension]) - (pattern (////synthesis.branch/case case)) + (////synthesis.branch/case case) (/case.case! statement expression archive case) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<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!]) - (pattern (////synthesis.function/abstraction abstraction)) + (////synthesis.function/abstraction abstraction) (//////phase#each _.return (/function.function statement expression archive abstraction)) )) @@ -72,7 +72,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -83,7 +83,7 @@ (//reference.reference /reference.system archive value) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -93,13 +93,13 @@ [////synthesis.function/apply /function.apply]) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (pattern (////synthesis.loop/again _)) + (////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 39ae8fcd4..00094289c 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 @@ -208,33 +208,33 @@ [/////synthesis.#Text_Fork //primitive.text]) (^.with_template [<complex> <simple> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> false idx)) - (pattern (<simple> idx nextP)) + (<simple> idx nextP) (|> nextP again (at ///////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]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.!bind_top register thenP)) + (/////synthesis.!bind_top register thenP) (do ///////phase.monad [then! (again thenP)] (///////phase#in (all _.then (_.set! (..register register) ..peek_and_pop) then!))) - ... (pattern (/////synthesis.!multi_pop nextP)) + ... (/////synthesis.!multi_pop nextP) ... (.let [[extra_pops nextP'] (////synthesis/case.count_pops nextP)] ... (do ///////phase.monad ... [next! (again nextP')] @@ -243,7 +243,7 @@ ... next!)))) (^.with_template [<tag> <combinator>] - [(pattern (<tag> preP postP)) + [(<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 a5435e72d..ef9fdee7e 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 @@ -39,7 +39,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -47,7 +47,7 @@ [////synthesis.text /primitive.text]) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -60,13 +60,13 @@ [////synthesis.function/apply /function.apply]) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (pattern (////synthesis.loop/again updates)) + (////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 5062e41ae..02a90bd13 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 @@ -260,33 +260,33 @@ (///////phase#in (_.set (list (..register register)) ..peek)) (^.with_template [<complex> <simple> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> false idx)) - (pattern (<simple> idx nextP)) + (<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]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (pattern (/////synthesis.!bind_top register thenP)) + (/////synthesis.!bind_top register thenP) (do ! [then! (again thenP)] (///////phase#in (all _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (pattern (/////synthesis.!multi_pop nextP)) + (/////synthesis.!multi_pop nextP) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ! [next! (again nextP')] @@ -294,13 +294,13 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (pattern (/////synthesis.path/seq preP postP)) + (/////synthesis.path/seq preP postP) (do ! [pre! (again preP) post! (again postP)] (in (_.then pre! post!))) - (pattern (/////synthesis.path/alt preP postP)) + (/////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 135f3e4df..6028a0ac3 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 @@ -32,7 +32,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -43,7 +43,7 @@ (//reference.reference /reference.system archive value) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<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 51cb787a3..472f361b6 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 @@ -182,7 +182,7 @@ [/////synthesis.#Text_Fork //primitive.text _.=]) (^.with_template [<pm> <flag> <prep>] - [(pattern (<pm> idx)) + [(<pm> idx) (///////phase#in (all _.then (_.set! $temp (|> idx <prep> .int _.int (//runtime.sum::get ..peek (//runtime.flag <flag>)))) (_.if (_.= _.null $temp) @@ -191,16 +191,16 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (_.item (_.int +1) ..peek)) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple::left] [/////synthesis.member/right //runtime.tuple::right]) - (pattern (/////synthesis.path/seq leftP rightP)) + (/////synthesis.path/seq leftP rightP) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] @@ -208,7 +208,7 @@ leftO rightO))) - (pattern (/////synthesis.path/alt leftP rightP)) + (/////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/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux index 0201e556d..b5a3fcb3a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/host.lux @@ -25,7 +25,7 @@ ... (def (lua//global proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (pattern (list [_ {.#Text name}])) +... (list [_ {.#Text name}]) ... (do macro.Monad<Meta> ... [] ... (in name)) @@ -36,7 +36,7 @@ ... (def (lua//call proc translate inputs) ... (-> Text @.Proc) ... (case inputs -... (pattern (list.partial functionS argsS+)) +... (list.partial 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 -... (pattern (list.partial tableS [_ {.#Text field}] argsS+)) +... (list.partial 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 989d07127..ed6f6710e 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 @@ -39,7 +39,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -47,7 +47,7 @@ [////synthesis.text /primitive.text]) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] [////synthesis.tuple /structure.tuple] @@ -60,13 +60,13 @@ [////synthesis.function/apply /function.apply]) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] [////synthesis.loop/scope /loop.scope] [////synthesis.function/abstraction /function.function]) - (pattern (////synthesis.loop/again _)) + (////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 68c958870..f76b378c8 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 @@ -301,33 +301,33 @@ [/////synthesis.#Text_Fork (<| //primitive.text)]) (^.with_template [<complex> <simple> <choice>] - [(pattern (<complex> idx)) + [(<complex> idx) (///////phase#in (<choice> false idx)) - (pattern (<simple> idx nextP)) + (<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]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.!bind_top register thenP)) + (/////synthesis.!bind_top register thenP) (do ///////phase.monad [then! (again thenP)] (///////phase#in (all _.then (_.set (list (..register register)) ..peek_and_pop) then!))) - (pattern (/////synthesis.!multi_pop nextP)) + (/////synthesis.!multi_pop nextP) (.let [[extra_pops nextP'] (case.count_pops nextP)] (do ///////phase.monad [next! (again nextP')] @@ -335,7 +335,7 @@ (..multi_pop! (n.+ 2 extra_pops)) next!)))) - (pattern (/////synthesis.path/seq preP postP)) + (/////synthesis.path/seq preP postP) (do ///////phase.monad [pre! (again preP) post! (again postP)] @@ -343,7 +343,7 @@ pre! post!))) - (pattern (/////synthesis.path/alt preP postP)) + (/////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 24b418ffa..2dba1f481 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 @@ -32,7 +32,7 @@ Phase (case synthesis (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<tag> value) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] [////synthesis.i64 /primitive.i64] @@ -43,7 +43,7 @@ (//reference.reference /reference.system archive value) (^.with_template [<tag> <generator>] - [(pattern (<tag> value)) + [(<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 b9546d729..d35d72f9f 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 @@ -176,7 +176,7 @@ [/////synthesis.#Text_Fork //primitive.text _.string=?/2]) (^.with_template [<pm> <flag> <prep>] - [(pattern (<pm> idx)) + [(<pm> idx) (///////phase#in (_.let (list [@temp (|> idx <prep> .int _.int (//runtime.sum//get ..peek (_.bool <flag>)))]) (_.if (_.null?/1 @temp) ..fail! @@ -184,23 +184,23 @@ ([/////synthesis.side/left false (<|)] [/////synthesis.side/right true ++]) - (pattern (/////synthesis.member/left 0)) + (/////synthesis.member/left 0) (///////phase#in (..push_cursor! (_.vector_ref/2 ..peek (_.int +0)))) (^.with_template [<pm> <getter>] - [(pattern (<pm> lefts)) + [(<pm> lefts) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple//left] [/////synthesis.member/right //runtime.tuple//right]) - (pattern (/////synthesis.path/seq leftP rightP)) + (/////synthesis.path/seq leftP rightP) (do ///////phase.monad [leftO (again leftP) rightO (again rightP)] (in (_.begin (list leftO rightO)))) - (pattern (/////synthesis.path/alt leftP rightP)) + (/////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/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis.lux index 3aa00a192..b21dbdaae 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 @@ -77,7 +77,7 @@ (/.with_currying? false (/case.synthesize optimization branchesAB+ archive inputA)) - (pattern (///analysis.no_op value)) + (///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 b2e0d357d..e755791ab 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 @@ -1,6 +1,6 @@ (.require [library - [lux (.except) + [lux (.except Pattern) [abstract [equivalence (.only Equivalence)] ["[0]" monad (.only do)]] @@ -290,7 +290,7 @@ path (case input - (pattern (/.branch/get [sub_path sub_input])) + (/.branch/get [sub_path sub_input]) (///#in (/.branch/get [(list#composite path sub_path) sub_input])) _ @@ -301,11 +301,11 @@ (do [! ///.monad] [inputS (synthesize^ archive inputA)] (case [headB tailB+] - (pattern (!masking @variable @output)) + (!masking @variable @output) (..synthesize_masking synthesize^ archive inputS @variable @output) - (pattern [[(///pattern.unit) body] - {.#End}]) + [[(///pattern.unit) body] + {.#End}] (case inputA (^.or {///analysis.#Simple _} {///analysis.#Structure _} @@ -319,18 +319,18 @@ {.#End}] (..synthesize_let synthesize^ archive inputS @variable body) - (^.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])])) + (^.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])]) (..synthesize_if synthesize^ archive inputS then else) - (pattern (!get patterns @member)) + (!get patterns @member) (..synthesize_get synthesize^ archive inputS patterns @member) match @@ -339,7 +339,7 @@ (def .public (count_pops path) (-> Path [Nat Path]) (case path - (pattern (/.path/seq {/.#Pop} path')) + (/.path/seq {/.#Pop} path') (let [[pops post_pops] (count_pops path')] [(++ pops) post_pops]) @@ -374,7 +374,7 @@ {/.#Access Access}) path_storage - (pattern (/.path/bind register)) + (/.path/bind register) (revised #bindings (set.has register) path_storage) @@ -394,22 +394,22 @@ (list#each product.right) (list#mix for_path path_storage)) - (^.or (pattern (/.path/seq left right)) - (pattern (/.path/alt left right))) + (^.or (/.path/seq left right) + (/.path/alt left right)) (list#mix for_path path_storage (list left right)) - (pattern (/.path/then bodyS)) + (/.path/then bodyS) (loop (for_synthesis [bodyS bodyS synthesis_storage path_storage]) (case bodyS (^.or {/.#Simple _} - (pattern (/.constant _))) + (/.constant _)) synthesis_storage - (pattern (/.variant [lefts right? valueS])) + (/.variant [lefts right? valueS]) (for_synthesis valueS synthesis_storage) - (pattern (/.tuple members)) + (/.tuple members) (list#mix for_synthesis synthesis_storage members) {/.#Reference {///reference.#Variable {///reference/variable.#Local register}}} @@ -420,21 +420,21 @@ {/.#Reference {///reference.#Variable var}} (revised #dependencies (set.has var) synthesis_storage) - (pattern (/.function/apply [functionS argsS])) + (/.function/apply [functionS argsS]) (list#mix for_synthesis synthesis_storage {.#Item functionS argsS}) - (pattern (/.function/abstraction [environment arity bodyS])) + (/.function/abstraction [environment arity bodyS]) (list#mix for_synthesis synthesis_storage environment) - (pattern (/.branch/case [inputS pathS])) + (/.branch/case [inputS pathS]) (revised #dependencies (set.union (the #dependencies (for_path pathS synthesis_storage))) (for_synthesis inputS synthesis_storage)) - (pattern (/.branch/exec [before after])) + (/.branch/exec [before after]) (list#mix for_synthesis synthesis_storage (list before after)) - (pattern (/.branch/let [inputS register exprS])) + (/.branch/let [inputS register exprS]) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.has register)) @@ -442,13 +442,13 @@ (the #dependencies))) (for_synthesis inputS synthesis_storage)) - (pattern (/.branch/if [testS thenS elseS])) + (/.branch/if [testS thenS elseS]) (list#mix for_synthesis synthesis_storage (list testS thenS elseS)) - (pattern (/.branch/get [access whole])) + (/.branch/get [access whole]) (for_synthesis whole synthesis_storage) - (pattern (/.loop/scope [start initsS+ iterationS])) + (/.loop/scope [start initsS+ iterationS]) (revised #dependencies (set.union (|> synthesis_storage (revised #bindings (set.union (|> initsS+ @@ -459,7 +459,7 @@ (the #dependencies))) (list#mix for_synthesis synthesis_storage initsS+)) - (pattern (/.loop/again replacementsS+)) + (/.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 f1bf10c2c..a97634d68 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 @@ -60,7 +60,7 @@ argsS (monad.each ! (phase archive) argsA)] (with_expansions [<apply> (these (/.function/apply [funcS argsS]))] (case funcS - (pattern (/.function/abstraction functionS)) + (/.function/abstraction functionS) (if (n.= (the /.#arity functionS) (list.size argsS)) (do ! @@ -70,7 +70,7 @@ (maybe#each (is (-> [Nat (List Synthesis) Synthesis] Synthesis) (function (_ [start inits iteration]) (case iteration - (pattern (/.loop/scope [start' inits' output])) + (/.loop/scope [start' inits' output]) (if (and (n.= start start') (list.empty? inits')) (/.loop/scope [start inits output]) @@ -81,7 +81,7 @@ (maybe.else <apply>)))) (in <apply>)) - (pattern (/.function/apply [funcS' argsS'])) + (/.function/apply [funcS' argsS']) (in (/.function/apply [funcS' (list#composite argsS' argsS)])) _ @@ -158,7 +158,7 @@ (monad.each phase.monad (grow environment)) (phase#each (|>> /.tuple)))) - (pattern (..self_reference)) + (..self_reference) (phase#in (/.function/apply [expression (list (/.variable/local 1))])) {/.#Reference reference} @@ -240,7 +240,7 @@ [funcS (grow environment funcS) argsS+ (monad.each ! (grow environment) argsS+)] (in (/.function/apply (case funcS - (pattern (/.function/apply [(..self_reference) pre_argsS+])) + (/.function/apply [(..self_reference) pre_argsS+]) [(..self_reference) (list#composite pre_argsS+ argsS+)] @@ -265,7 +265,7 @@ (phase archive bodyA))) abstraction (is (Operation Abstraction) (case bodyS - (pattern (/.function/abstraction [env' down_arity' bodyS'])) + (/.function/abstraction [env' down_arity' bodyS']) (|> bodyS' (grow env') (at ! 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 eb5738a11..c967930bf 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 @@ -102,53 +102,53 @@ {/.#Reference reference} (case reference - (pattern {reference.#Variable (variable.self)}) + {reference.#Variable (variable.self)} (if true_loop? {.#None} {.#Some expr}) - (pattern (reference.constant constant)) + (reference.constant constant) {.#Some expr} - (pattern (reference.local register)) + (reference.local register) {.#Some {/.#Reference (reference.local (register_optimization offset register))}} - (pattern (reference.foreign register)) + (reference.foreign register) (if true_loop? (list.item register scope_environment) {.#Some expr})) - (pattern (/.branch/case [input path])) + (/.branch/case [input path]) (do maybe.monad [input' (again false input) path' (path_optimization (again return?) offset path)] (in (|> path' [input'] /.branch/case))) - (pattern (/.branch/exec [this that])) + (/.branch/exec [this that]) (do maybe.monad [this (again false this) that (again return? that)] (in (/.branch/exec [this that]))) - (pattern (/.branch/let [input register body])) + (/.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']))) - (pattern (/.branch/if [input then else])) + (/.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']))) - (pattern (/.branch/get [path record])) + (/.branch/get [path record]) (do maybe.monad [record (again false record)] (in (/.branch/get [path record]))) - (pattern (/.loop/scope scope)) + (/.loop/scope scope) (do [! maybe.monad] [inits' (|> scope (the /.#inits) @@ -158,24 +158,24 @@ /.#inits inits' /.#iteration iteration']))) - (pattern (/.loop/again args)) + (/.loop/again args) (|> args (monad.each maybe.monad (again false)) (maybe#each (|>> /.loop/again))) - (pattern (/.function/abstraction [environment arity body])) + (/.function/abstraction [environment arity body]) (do [! maybe.monad] [environment' (monad.each ! (again false) environment)] (in (/.function/abstraction [environment' arity body]))) - (pattern (/.function/apply [abstraction arguments])) + (/.function/apply [abstraction arguments]) (do [! maybe.monad] [arguments' (monad.each ! (again false) arguments)] (with_expansions [<application> (these (do ! [abstraction' (again false abstraction)] (in (/.function/apply [abstraction' arguments']))))] (case abstraction - (pattern {/.#Reference {reference.#Variable (variable.self)}}) + {/.#Reference {reference.#Variable (variable.self)}} (if (and return? (n.= arity (list.size arguments))) (in (/.loop/again arguments')) @@ -187,14 +187,14 @@ <application>))) ... TODO: Stop relying on this custom code. - (pattern {/.#Extension ["lux syntax char case!" (list.partial input else matches)]}) + {/.#Extension ["lux syntax char case!" (list.partial input else matches)]} (if return? (do [! maybe.monad] [input (again false input) matches (monad.each ! (function (_ match) (case match - (pattern {/.#Structure {analysis/complex.#Tuple (list when then)}}) + {/.#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/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 852a1e058..80b01b5b8 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -61,7 +61,7 @@ (def .public self? (-> Variable Bit) (|>> (pipe.case - (pattern (..self)) + (..self) true _ |