diff options
author | Eduardo Julian | 2022-06-12 00:38:20 -0400 |
---|---|---|
committer | Eduardo Julian | 2022-06-12 00:38:20 -0400 |
commit | b48ea68a83d01903554c7696c77eedaaf1035680 (patch) | |
tree | c342d8094c3158de16526f874ca9624418cd2dd2 /stdlib/source/library/lux/tool/compiler | |
parent | 7abf2d0ac55c229a8793bbff31f132596ffcb275 (diff) |
De-sigil-ification: suffix : [Part 3]
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
93 files changed, 649 insertions, 577 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/arity.lux b/stdlib/source/library/lux/tool/compiler/arity.lux index 055f46a63..c1e2796c3 100644 --- a/stdlib/source/library/lux/tool/compiler/arity.lux +++ b/stdlib/source/library/lux/tool/compiler/arity.lux @@ -8,7 +8,7 @@ (type: .public Arity Nat) -(template [<comparison> <name>] +(with_template [<comparison> <name>] [(def: .public <name> (-> Arity Bit) (<comparison> 1))] [n.< nullary?] diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index 81653a205..f25ade369 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -441,7 +441,7 @@ (list.only (|>> product.left (dictionary.key? to) not) (dictionary.entries from)))) - (template [<name> <path>] + (with_template [<name> <path>] [(def: (<name> from state) (All (_ <type_vars>) (-> <State+> <State+> (Try <State+>))) 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 b3c99bdbf..7563bce90 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -114,19 +114,22 @@ _ false))) -(template [<name> <tag>] - [(template: .public (<name> content) - [{<tag> content}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [{<tag> content}]))] [case ..#Case] ) -(template: .public (unit) - [{..#Simple {/simple.#Unit}}]) +(def: .public unit + (template (unit) + [{..#Simple {/simple.#Unit}}])) -(template [<name> <tag>] - [(template: .public (<name> value) - [{..#Simple {<tag> value}}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> value) + [{..#Simple {<tag> value}}]))] [bit /simple.#Bit] [nat /simple.#Nat] @@ -142,13 +145,14 @@ (type: .public (Reification c) [c (List c)]) -(template: .public (no_op value) - [(|> 1 - {variable.#Local} - {reference.#Variable} - {..#Reference} - {..#Function (list)} - {..#Apply value})]) +(def: .public no_op + (template (no_op value) + [(|> 1 + {variable.#Local} + {reference.#Variable} + {..#Reference} + {..#Function (list)} + {..#Apply value})])) (def: .public (reified [abstraction inputs]) (-> (Reification Analysis) Analysis) @@ -169,7 +173,7 @@ _ [abstraction inputs]))) -(template [<name> <tag>] +(with_template [<name> <tag>] [(def: .public <name> (syntax (_ [content <code>.any]) (in (list (` (.<| {..#Reference} @@ -183,11 +187,12 @@ [foreign ((~! reference.foreign))] ) -(template [<name> <tag>] - [(template: .public (<name> content) - [(.<| {..#Structure} - {<tag>} - content)])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Structure} + {<tag>} + content)]))] [variant /complex.#Variant] [tuple /complex.#Tuple] @@ -239,7 +244,7 @@ (%.format (%.text name) " ") (text.enclosed ["(" ")"])))) -(template [<special> <general>] +(with_template [<special> <general>] [(type: .public <special> (<general> .Lux Code Analysis))] @@ -330,7 +335,7 @@ {try.#Success [[bundle state] []]})) -(template [<name> <type> <field> <value>] +(with_template [<name> <type> <field> <value>] [(def: .public (<name> value) (-> <type> (Operation Any)) (extension.update (has <field> <value>)))] 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 b4b554a4f..cbb1e7ea4 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 @@ -90,7 +90,7 @@ [{#Bit sideR} {#Bit sideS}] (bit#= sideR sideS) - (^.template [<tag>] + (^.with_template [<tag>] [[{<tag> partialR} {<tag> partialS}] (set#= partialR partialS)]) ([#Nat] @@ -126,7 +126,7 @@ {#Bit it} (%.bit it) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> it} (|> it set.list @@ -171,7 +171,7 @@ ... Simple patterns (other than unit/[]) always have partial coverage because there ... are too many possibilities as far as values go. - (^.template [<from> <to> <hash>] + (^.with_template [<from> <to> <hash>] [{//pattern.#Simple {<from> it}} {try.#Success {<to> (set.of_list <hash> (list it))}}]) ([//simple.#Nat #Nat n.hash] @@ -274,7 +274,7 @@ {try.#Success {#Exhaustive}} <redundancy>) - (^.template [<tag>] + (^.with_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 1baaf5e1d..fb8f92d44 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 @@ -44,7 +44,7 @@ "Type" (%.type type) "Argument" (%.code argument))) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [type Type]) (exception.report "Type" (%.type type)))] @@ -60,7 +60,7 @@ {.#Primitive name co_variant} {.#Primitive name (list#each (quantified @var @parameter) co_variant)} - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} {<tag> (quantified @var @parameter left) (quantified @var @parameter right)}]) @@ -74,7 +74,7 @@ {.#Parameter @parameter} :it:) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> env body} {<tag> (list#each (quantified @var @parameter) env) (quantified @var (n.+ 2 @parameter) body)}]) @@ -199,12 +199,12 @@ recursion it) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] [.#Product] [.#Function] [.#Apply]) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> environment quantified} {<tag> (list#each again environment) (with_recursion (n.+ 2 @self) recursion quantified)}]) @@ -222,7 +222,7 @@ (list#each (|>> (n.* 2) ++ {.#Parameter})) list.reversed)) -(template [<name> <types> <inputs> <exception> <when> <then>] +(with_template [<name> <types> <inputs> <exception> <when> <then>] [(`` (def: .public (<name> (~~ (template.spliced <inputs>)) complex) (-> (~~ (template.spliced <types>)) Type (Operation Type)) (loop (again [depth 0 @@ -231,7 +231,7 @@ {.#Named name it} (again depth it) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> env it} (phase#each (|>> {<tag> env}) (again (++ depth) it))]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux index 1a897fb6c..086419cf3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux @@ -29,7 +29,7 @@ (exception.report "Module" module)) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [labels (List Label) owner Type]) (exception.report @@ -155,7 +155,7 @@ module (///extension.lifted (meta.module name))] (in [module output]))) -(template [<setter> <asker> <tag>] +(with_template [<setter> <asker> <tag>] [(def: .public (<setter> module_name) (-> Text (Operation Any)) (///extension.lifted 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 a462e62d1..23f8796db 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 @@ -52,22 +52,25 @@ {#Bind it} (//variable.format {//variable.#Local it}))) -(template [<name> <tag>] - [(template: .public (<name> content) - [(.<| {..#Complex} - <tag> - content)])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Complex} + <tag> + content)]))] [variant {//complex.#Variant}] [tuple {//complex.#Tuple}] ) -(template: .public (unit) - [{..#Simple {//simple.#Unit}}]) +(def: .public unit + (template (unit) + [{..#Simple {//simple.#Unit}}])) -(template [<name> <tag>] - [(template: .public (<name> content) - [{..#Simple {<tag> content}}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [{..#Simple {<tag> content}}]))] [bit //simple.#Bit] [nat //simple.#Nat] @@ -77,5 +80,6 @@ [text //simple.#Text] ) -(template: .public (bind register) - [{..#Bind register}]) +(def: .public bind + (template (bind register) + [{..#Bind register}])) 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 4907be964..e9d2d8b87 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 @@ -34,7 +34,7 @@ [{#Unit} {#Unit}] true - (^.template [<tag> <=>] + (^.with_template [<tag> <=>] [[{<tag> reference} {<tag> sample}] (<=> reference sample)]) ([#Bit bit#=] @@ -53,7 +53,7 @@ {#Unit} "[]" - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> value} (<format> value)]) ([#Bit %.bit] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux index 7f1c5d418..afe5c1aa8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/directive.lux @@ -55,7 +55,7 @@ [#imports (list#composite (the #imports left) (the #imports right)) #referrals (list#composite (the #referrals left) (the #referrals right))]) -(template [<special> <general>] +(with_template [<special> <general>] [(type: .public (<special> anchor expression directive) (<general> (..State anchor expression directive) Code Requirements))] @@ -66,7 +66,7 @@ [Bundle extension.Bundle] ) -(template [<name> <component> <phase>] +(with_template [<name> <component> <phase>] [(def: .public <name> (All (_ anchor expression directive) (Operation anchor expression directive <phase>)) @@ -78,7 +78,7 @@ [generation ..#generation (generation.Phase anchor expression directive)] ) -(template [<name> <component> <operation>] +(with_template [<name> <component> <operation>] [(def: .public <name> (All (_ anchor expression directive output) (-> (<operation> output) 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 42ad80162..695920880 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -46,7 +46,7 @@ (exception.report "Error" error)) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [it artifact.ID]) (exception.report "Artifact ID" (%.nat it)))] @@ -84,7 +84,7 @@ #log (Sequence Text) #interim_artifacts (List artifact.ID)])) -(template [<special> <general>] +(with_template [<special> <general>] [(type: .public (<special> anchor expression directive) (<general> (State anchor expression directive) Synthesis expression))] @@ -116,7 +116,7 @@ Buffer sequence.empty) -(template [<tag> +(with_template [<tag> <with_declaration> <with_type> <with_value> <set> <get> <get_type> <exception>] [(exception: .public <exception>) @@ -250,7 +250,7 @@ {.#None} (phase.except ..no_buffer_for_saving_code [artifact_id])))) -(template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>] +(with_template [<type> <mandatory?> <inputs> <input_types> <name> <artifact>] [(`` (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))) 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 0033addf3..55aa12407 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 @@ -40,53 +40,57 @@ (exception.report "Syntax" (%.code syntax))) -(template: (variant_analysis analysis archive tag values) - ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) - [(case values - (pattern (list value)) - (/complex.variant analysis tag archive value) - - _ - (/complex.variant analysis tag archive (code.tuple values)))]) - -(template: (sum_analysis analysis archive lefts right? values) - ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) - [(case values - (pattern (list value)) - (/complex.sum analysis lefts right? archive value) - - _ - (/complex.sum analysis lefts right? archive (code.tuple values)))]) - -(template: (case_analysis analysis archive input branches code) - ... (-> Phase Archive Code (List Code) Code (Operation Analysis)) - [(case (list.pairs branches) - {.#Some branches} - (/case.case analysis branches archive input) - - {.#None} - (//.except ..invalid [code]))]) - -(template: (apply_analysis expander analysis archive functionC argsC+) - ... (-> Expander Phase Archive Code (List Code) (Operation Analysis)) - [(do [! //.monad] - [[functionT functionA] (/type.inferring - (analysis archive functionC))] - (case functionA - (pattern (/.constant def_name)) - (do ! - [?macro (//extension.lifted (meta.macro def_name))] - (case ?macro - {.#Some macro} - (do ! - [expansion (//extension.lifted (/macro.single_expansion expander def_name macro argsC+))] - (analysis archive expansion)) - - _ - (/function.apply analysis argsC+ functionT functionA archive functionC))) +(def: variant_analysis + (template (_ analysis archive tag values) + ... (-> Phase Archive Symbol (List Code) (Operation Analysis)) + [(case values + (pattern (list value)) + (/complex.variant analysis tag archive value) _ - (/function.apply analysis argsC+ functionT functionA archive functionC)))]) + (/complex.variant analysis tag archive (code.tuple values)))])) + +(def: sum_analysis + (template (_ analysis archive lefts right? values) + ... (-> Phase Archive Nat Bit (List Code) (Operation Analysis)) + [(case values + (pattern (list value)) + (/complex.sum analysis lefts right? archive value) + + _ + (/complex.sum analysis lefts right? archive (code.tuple values)))])) + +(def: case_analysis + (template (_ analysis archive input branches code) + ... (-> Phase Archive Code (List Code) Code (Operation Analysis)) + [(case (list.pairs branches) + {.#Some branches} + (/case.case analysis branches archive input) + + {.#None} + (//.except ..invalid [code]))])) + +(def: apply_analysis + (template (_ expander analysis archive functionC argsC+) + ... (-> Expander Phase Archive Code (List Code) (Operation Analysis)) + [(do [! //.monad] + [[functionT functionA] (/type.inferring + (analysis archive functionC))] + (case functionA + (pattern (/.constant def_name)) + (do ! + [?macro (//extension.lifted (meta.macro def_name))] + (case ?macro + {.#Some macro} + (do ! + [expansion (//extension.lifted (/macro.single_expansion expander def_name macro argsC+))] + (analysis archive expansion)) + + _ + (/function.apply analysis argsC+ functionT functionA archive functionC))) + + _ + (/function.apply analysis argsC+ functionT functionA archive functionC)))])) (def: .public (phase expander) (-> Expander Phase) @@ -96,7 +100,7 @@ ... of having useful error messages. (/.with_location location) (case code - (^.template [<tag> <analyser>] + (^.with_template [<tag> <analyser>] [[_ {<tag> value}] (<analyser> value)]) ([.#Symbol /reference.reference] 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 bb9d617f6..0bb0f208d 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 @@ -235,7 +235,7 @@ idx /scope.next] (in [{/pattern.#Bind idx} outputA]))) - (^.template [<type> <input> <output>] + (^.with_template [<type> <input> <output>] [[location <input>] (simple_pattern_analysis <type> :input: location {/pattern.#Simple <output>} next)]) ([Bit {.#Bit pattern_value} {/simple.#Bit pattern_value}] 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 7e33dfdd9..0c16d0bc9 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 @@ -43,7 +43,7 @@ (exception.report "Type" (%.type type))) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [type Type members (List Code)]) (exception.report @@ -54,7 +54,7 @@ [cannot_analyse_tuple] ) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [type Type lefts Nat right? Bit diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux index 5a0806d79..a5e7a9d08 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/simple.lux @@ -11,7 +11,7 @@ [/// ["[1]" phase]]]]) -(template [<name> <type> <tag>] +(with_template [<name> <type> <tag>] [(def: .public (<name> value) (-> <type> (Operation Analysis)) (do ///.monad 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 2b779791f..c5044dba6 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 @@ -152,7 +152,7 @@ (getSuperclass [] "?" (java/lang/Class java/lang/Object)) (getInterfaces [] [(java/lang/Class java/lang/Object)])) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [class External field Text]) (exception.report @@ -195,9 +195,9 @@ External "java.lang.Object") -... TODO: Get rid of this template block and use the definition in +... TODO: Get rid of this with_template block and use the definition in ... lux/ffi.jvm.lux ASAP -(template [<name> <class>] +(with_template [<name> <class>] [(def: .public <name> .Type {.#Primitive <class> {.#End}})] @@ -239,7 +239,7 @@ #deprecated? Bit #throws (List .Type)])) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [type .Type]) (exception.report "Type" (%.type type)))] @@ -250,7 +250,7 @@ [non_jvm_type] ) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [class External]) (exception.report "Class/type" (%.text class)))] @@ -260,7 +260,7 @@ [primitives_are_not_objects] ) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [class_variables (List (Type Var)) class External method Text @@ -287,7 +287,7 @@ "To" (%.type to) "Value" (%.code value))) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [message Text]) message)] @@ -327,7 +327,7 @@ (///bundle.install "short-to-long" (//lux.unary ..short ..long)) ))) -(template [<name> <prefix> <type>] +(with_template [<name> <prefix> <type>] [(def: <name> Bundle (<| (///bundle.prefix (reflection.reflection <prefix>)) @@ -351,7 +351,7 @@ [bundle::long reflection.long ..long] ) -(template [<name> <prefix> <type>] +(with_template [<name> <prefix> <type>] [(def: <name> Bundle (<| (///bundle.prefix (reflection.reflection <prefix>)) @@ -389,8 +389,9 @@ [(reflection.reflection reflection.char) [box.char jvm.char]]) (dictionary.of_list text.hash))) -(template: (lux_array_type :read: :write:) - [{.#Primitive (static array.type_name) (list {.#Apply :write: {.#Apply :read: _Mutable}})}]) +(def: lux_array_type + (template (_ :read: :write:) + [{.#Primitive (static array.type_name) (list {.#Apply :write: {.#Apply :read: _Mutable}})}])) (def: (jvm_type luxT) (-> .Type (Operation (Type Value))) @@ -535,7 +536,7 @@ (/////analysis.except ..non_parameter objectT) {.#Primitive name parameters} - (`` (cond (or (~~ (template [<type>] + (`` (cond (or (~~ (with_template [<type>] [(text#= (..reflection <type>) name)] [jvm.boolean] @@ -569,7 +570,7 @@ {.#Parameter id}) (phase#in (jvm.class ..object_class (list))) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> env unquantified} (check_parameter unquantified)]) ([.#UnivQ] @@ -593,7 +594,7 @@ (-> .Type (Operation (Type Value))) (case objectT {.#Primitive name {.#End}} - (`` (cond (~~ (template [<type>] + (`` (cond (~~ (with_template [<type>] [(text#= (..reflection <type>) name) (phase#in <type>)] @@ -606,7 +607,7 @@ [jvm.double] [jvm.char])) - (~~ (template [<type>] + (~~ (with_template [<type>] [(text#= (..reflection (jvm.array <type>)) name) (phase#in (jvm.array <type>))] @@ -640,7 +641,7 @@ {.#Named name anonymous} (check_jvm anonymous) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> env unquantified} (check_jvm unquantified)]) ([.#UnivQ] @@ -657,7 +658,7 @@ _ (check_parameter objectT))) -(template [<name> <category> <parser>] +(with_template [<name> <category> <parser>] [(def: .public (<name> mapping typeJ) (-> Mapping (Type <category>) (Operation .Type)) (case (|> typeJ ..signature (<text>.result (<parser> mapping))) @@ -982,7 +983,7 @@ (analyse archive fromC)) source_name (at ! each ..reflection (check_jvm fromT)) can_cast? (is (Operation Bit) - (`` (cond (~~ (template [<primitive> <object>] + (`` (cond (~~ (with_template [<primitive> <object>] [(let [=primitive (reflection.reflection <primitive>)] (or (and (text#= =primitive source_name) (or (text#= <object> target_name) @@ -1171,7 +1172,7 @@ (list#each (|>> again (as (Type Parameter)))) (jvm.class name)) {.#None}) - (~~ (template [<read> <as> <write>] + (~~ (with_template [<read> <as> <write>] [(case (<read> it) {.#Some :sub:} (<write> (as (Type <as>) (again :sub:))) @@ -1252,7 +1253,7 @@ (-> (java/lang/Class java/lang/Object) (Type Class)) (jvm.class (java/lang/Class::getName it) (list))) -(template [<name> <type> <params>] +(with_template [<name> <type> <params>] [(`` (def: <name> (-> (<type> (~~ (template.spliced <params>))) (List (Type Class))) (|>> (~~ (template.symbol [<type> "::getExceptionTypes"])) @@ -1359,7 +1360,7 @@ {#Pass Method_Signature} {#Hint Method_Signature})) -(template [<name> <tag>] +(with_template [<name> <tag>] [(def: <name> (-> Evaluation (Maybe Method_Signature)) (|>> (pipe.case @@ -1373,7 +1374,7 @@ [hint #Hint] ) -(template [<name> <type> <method>] +(with_template [<name> <type> <method>] [(def: <name> (-> <type> (List (Type Var))) (|>> <method> @@ -1488,7 +1489,7 @@ candidates (/////analysis.except ..too_many_candidates [actual_class_tvars class_name ..constructor_method actual_method_tvars inputsJT candidates])))) -(template [<name> <category> <parser>] +(with_template [<name> <category> <parser>] [(def: .public <name> (Parser (Type <category>)) (<text>.then <parser> <code>.text))] @@ -1674,7 +1675,7 @@ (/////analysis.tuple (partial_list (/////analysis.text name) (list#each annotation_parameter_analysis parameters)))) -(template [<name> <category>] +(with_template [<name> <category>] [(def: <name> (-> (Type <category>) Analysis) (|>> ..signature /////analysis.text))] @@ -1695,7 +1696,7 @@ (list (/////analysis.text argument) (value_analysis argumentJT)))) -(template [<name> <only> <methods>] +(with_template [<name> <only> <methods>] [(def: (<name> [type class]) (-> [(Type Class) (java/lang/Class java/lang/Object)] (Try (List [(Type Class) Text (Type Method)]))) @@ -1734,7 +1735,7 @@ (def: jvm_package_separator ".") -(template [<name> <methods>] +(with_template [<name> <methods>] [(def: (<name> class_loader) (-> java/lang/ClassLoader (List (Type Class)) (Try (List [(Type Class) Text (Type Method)]))) (|>> (monad.each try.monad (function (_ type) @@ -1750,7 +1751,7 @@ [all_methods ..methods] ) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [expected (List [(Type Class) Text (Type Method)]) actual (List [(Type Class) Text (Type Method)])]) (let [%method (is (%.Format [(Type Class) Text (Type Method)]) @@ -2421,7 +2422,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^.template [<tag> <type> <constant>] + (^.with_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/lua.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux index 90ed93d25..39606222f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lua.lux @@ -168,7 +168,7 @@ (bundle.install "nil?" (/.unary Any Bit)) ))) -(template [<name> <fromT> <toT>] +(with_template [<name> <fromT> <toT>] [(def: <name> Handler (custom 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 c4392ff2a..e6c308b21 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 @@ -112,7 +112,7 @@ (def: visibility' (<text>.Parser (Modifier field.Field)) (`` (all <>.either - (~~ (template [<label> <modifier>] + (~~ (with_template [<label> <modifier>] [(<>.after (<text>.this <label>) (<>#in <modifier>))] ["public" field.public] @@ -127,7 +127,7 @@ (def: inheritance (Parser (Modifier class.Class)) (`` (all <>.either - (~~ (template [<label> <modifier>] + (~~ (with_template [<label> <modifier>] [(<>.after (<code>.this_text <label>) (<>#in <modifier>))] ["final" class.final] @@ -137,7 +137,7 @@ (def: state (Parser (Modifier field.Field)) (`` (all <>.either - (~~ (template [<label> <modifier>] + (~~ (with_template [<label> <modifier>] [(<>.after (<code>.this_text <label>) (<>#in <modifier>))] ["volatile" field.volatile] @@ -231,7 +231,7 @@ ... TODO: Handle annotations. {#Constant [name annotations type value]} (case value - (^.template [<tag> <type> <constant>] + (^.with_template [<tag> <type> <constant>] [[_ {<tag> value}] (do pool.monad [constant (`` (|> value (~~ (template.spliced <constant>)))) @@ -270,7 +270,7 @@ (<synthesis>.Parser (jvm.Annotation Synthesis)) (<synthesis>.tuple (<>.and <synthesis>.text (<>.some ..annotation_parameter_synthesis)))) -(template [<name> <type> <text>] +(with_template [<name> <type> <text>] [(def: <name> (<synthesis>.Parser (Type <type>)) (<text>.then <text> <synthesis>.text))] @@ -430,7 +430,7 @@ (<load> jvm_register) (value.wrap <type>) (_.astore lux_register))]]] - (`` (cond (~~ (template [<shift> <load> <type>] + (`` (cond (~~ (with_template [<shift> <load> <type>] [(at type.equivalence = <type> argumentT) (wrap_primitive <shift> <load> <type>)] @@ -513,7 +513,7 @@ [(all _.composite (value.unwrap <type>) <return>)]] - (`` (cond (~~ (template [<return> <type>] + (`` (cond (~~ (with_template [<return> <type>] [(at type.equivalence = <type> returnT) (unwrap_primitive <return> <type>)] @@ -831,7 +831,7 @@ (list#each (..mock_method super) methods) inheritance)) -(template [<name> <type> <parser>] +(with_template [<name> <type> <parser>] [(def: <name> (Parser <type>) (do [! <>.monad] 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 b66e2cc05..2072d1a8e 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 @@ -169,7 +169,7 @@ (synthesize archive codeA))] (definition' archive generate name code//type codeS))) -(template [<full> <partial> <learn>] +(with_template [<full> <partial> <learn>] [... TODO: Inline "<partial>" into "<full>" ASAP (def: (<partial> archive generate extension codeT codeS) (All (_ anchor expression directive) @@ -376,7 +376,7 @@ (in /////directive.no_requirements)))])) ... TODO: Stop requiring these types and the "swapped" function below to make types line-up. -(template [<name> <anonymous>] +(with_template [<name> <anonymous>] [(def: <name> Type (with_expansions [<original> binary.Binary] @@ -397,7 +397,7 @@ {.#Primitive name parameters} {.#Primitive name (list#each again parameters)} - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([.#Sum] @@ -410,7 +410,7 @@ {.#Ex _}) type - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> closure body} {<tag> closure (again body)}]) ([.#UnivQ] @@ -419,7 +419,7 @@ {.#Named name anonymous} {.#Named name (again anonymous)})))) -(template [<description> <mame> <def_type> <type> <scope> <definer>] +(with_template [<description> <mame> <def_type> <type> <scope> <definer>] [(def: (<mame> [anchorT expressionT directiveT] extender) (All (_ anchor expression directive) (-> [Type Type Type] Extender diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index 111d1d4aa..1eeb12ede 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -51,8 +51,9 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(template: (!unary function) - (|>> list _.apply (|> (_.constant function)))) +(def: !unary + (template (_ function) + (|>> list _.apply (|> (_.constant function))))) ... ... TODO: Get rid of this ASAP ... (def: lux::syntax_char_case! 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 db527fbd2..0b40aa0d3 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 @@ -54,7 +54,7 @@ ... [Procedures] ... [[Bits]] -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [paramG subjectG]) (Binary Expression) (<op> subjectG (//runtime.i64::number paramG)))] @@ -107,7 +107,7 @@ [body (expression archive synthesis)] (in (as Statement body))) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] @@ -119,7 +119,7 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 44674faf0..da40355f3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -90,7 +90,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.do methodS inputsG objectG))))])) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary Expression) (function.constant <unit>)) (def: <?> (Unary Expression) (_.= <unit>))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index cbae57e3c..7d035fe2f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -159,7 +159,7 @@ (/////bundle.install "is" (binary ..lux::is)) (/////bundle.install "try" (unary ..lux::try)))) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [maskG inputG]) (Binary (Bytecode Any)) (all _.composite @@ -172,7 +172,7 @@ [i64::xor _.lxor] ) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [shiftG inputG]) (Binary (Bytecode Any)) (all _.composite @@ -184,7 +184,7 @@ [i64::right_shifted _.lushr] ) -(template [<name> <type> <op>] +(with_template [<name> <type> <op>] [(def: (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite @@ -205,8 +205,8 @@ [f64::% type.double _.drem] ) -(template [<eq> <lt> <type> <cmp>] - [(template [<name> <reference>] +(with_template [<eq> <lt> <type> <cmp>] + [(with_template [<name> <reference>] [(def: (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite @@ -227,7 +227,7 @@ (-> (Type Class) (Type Primitive) (Bytecode Any)) (_.invokestatic class "toString" (type.method [(list) (list from) ..$String (list)]))) -(template [<name> <prepare> <transform>] +(with_template [<name> <prepare> <transform>] [(def: (<name> inputG) (Unary (Bytecode Any)) (all _.composite @@ -307,7 +307,7 @@ (def: no_op (Bytecode Any) (_#in [])) -(template [<name> <pre_subject> <pre_param> <op> <post>] +(with_template [<name> <pre_subject> <pre_param> <op> <post>] [(def: (<name> [paramG subjectG]) (Binary (Bytecode Any)) (all _.composite 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 d9b809f6c..202f4b5e0 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 @@ -79,7 +79,7 @@ [dependency ["[1]/[0]" artifact]]]]]]]]) -(template [<name> <0>] +(with_template [<name> <0>] [(def: <name> (Bytecode Any) (all _.composite @@ -91,7 +91,7 @@ [l2c _.i2c] ) -(template [<conversion> <name>] +(with_template [<conversion> <name>] [(def: (<name> inputG) (Unary (Bytecode Any)) (if (same? _.nop <conversion>) @@ -168,7 +168,7 @@ (/////bundle.install "short-to-long" (unary conversion::short_to_long)) ))) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [parameter! subject!]) (Binary (Bytecode Any)) (all _.composite @@ -217,7 +217,7 @@ (def: falseG (_.getstatic ..$Boolean "FALSE" ..$Boolean)) (def: trueG (_.getstatic ..$Boolean "TRUE" ..$Boolean)) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [reference subject]) (Binary (Bytecode Any)) (do _.monad @@ -240,7 +240,7 @@ [char::< _.if_icmplt] ) -(template [<name> <op> <reference>] +(with_template [<name> <op> <reference>] [(def: (<name> [reference subject]) (Binary (Bytecode Any)) (do _.monad @@ -340,7 +340,7 @@ (/////bundle.install "<" (binary char::<)) ))) -(template [<name> <category> <parser>] +(with_template [<name> <category> <parser>] [(def: .public <name> (Parser (Type <category>)) (<text>.then <parser> <synthesis>.text))] @@ -607,7 +607,7 @@ (function (_ extension_name generate archive [from to valueS]) (do //////.monad [valueG (generate archive valueS)] - (in (`` (cond (~~ (template [<object> <type>] + (in (`` (cond (~~ (with_template [<object> <type>] [(and (text#= (..reflection <type>) from) (text#= <object> to)) (all _.composite @@ -751,7 +751,7 @@ (_.invokestatic class method (type.method [(list) (list#each product.left inputsTG) outputT (list)])) (prepare_output outputT)))))])) -(template [<check_cast?> <name> <invoke>] +(with_template [<check_cast?> <name> <invoke>] [(def: <name> Handler (..custom @@ -878,13 +878,13 @@ (pattern (//////synthesis.path/then bodyS)) (//////synthesis.path/then (normalize bodyS)) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> leftP rightP}) {<tag> (again leftP) (again rightP)}]) ([//////synthesis.#Alt] [//////synthesis.#Seq]) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> _} path]) ([//////synthesis.#Pop] @@ -894,7 +894,7 @@ {//////synthesis.#Bit_Fork when then else} {//////synthesis.#Bit_Fork when (again then) (maybe#each again else)} - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> [[exampleH nextH] tail]} {<tag> [[exampleH (again nextH)] (list#each (function (_ [example next]) @@ -911,7 +911,7 @@ (-> Mapping Synthesis Synthesis) (function (again body) (case body - (^.template [<tag>] + (^.with_template [<tag>] [(pattern <tag>) body]) ([{//////synthesis.#Simple _}] @@ -1053,7 +1053,7 @@ [(all _.composite (///value.unwrap <type>) <return>)]] - (`` (cond (~~ (template [<return> <type>] + (`` (cond (~~ (with_template [<return> <type>] [(at type.equivalence = <type> returnT) (unwrap_primitive <return> <type>)] @@ -1108,7 +1108,7 @@ (<load> jvm_register) (///value.wrap <type>) (_.astore lux_register))]]] - (`` (cond (~~ (template [<shift> <load> <type>] + (`` (cond (~~ (with_template [<shift> <load> <type>] [(at type.equivalence = <type> argumentT) (wrap_primitive <shift> <load> <type>)] 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 5d9753b87..334e7a924 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 @@ -56,8 +56,9 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(template: (!unary function) - [(|>> list _.apply (|> (_.var function)))]) +(def: !unary + (template (_ function) + [(|>> list _.apply (|> (_.var function)))])) (def: .public (statement expression archive synthesis) Phase! @@ -68,7 +69,7 @@ [body (expression archive synthesis)] (in (as Statement body))) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] @@ -80,7 +81,7 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index 365fbe663..9b292c7e7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -83,7 +83,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.do methodS inputsG objectG))))])) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary Expression) (function.constant <unit>)) (def: <?> (Unary Expression) (_.= <unit>))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index 911e63531..422f9cd4d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -51,8 +51,9 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(template: (!unary function) - (|>> list _.apply (|> (_.constant function)))) +(def: !unary + (template (_ function) + (|>> list _.apply (|> (_.constant function))))) ... TODO: Get rid of this ASAP (def: lux::syntax_char_case! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux index 073c49818..e6bfc780f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/host.lux @@ -87,7 +87,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.do methodS inputsG objectG))))])) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary Expression) (function.constant <unit>)) (def: <?> (Unary Expression) (_.=== <unit>))] 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 e48f139a3..adc889695 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 @@ -54,7 +54,7 @@ [body (expression archive synthesis)] (in (as (Statement Any) body))) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] @@ -66,7 +66,7 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] @@ -75,7 +75,7 @@ (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index 0b00fd778..ba6885829 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -84,7 +84,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.do methodS inputsG objectG))))])) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary (Expression Any)) (function.constant <unit>)) (def: <?> (Unary (Expression Any)) (_.= <unit>))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index 8f1a0c53e..345d82477 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -51,8 +51,9 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -... (template: (!unary function) -... (|>> list _.apply (|> (_.constant function)))) +... (def: !unary +... (template (_ function) +... (|>> list _.apply (|> (_.constant function))))) ... ... ... TODO: Get rid of this ASAP ... ... (def: lux::syntax_char_case! 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 bee06eb6a..695b5e1e7 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 @@ -66,7 +66,7 @@ (in (as Statement body))) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern (<tag> value)) (/////#each _.return (expression archive synthesis))]) ([synthesis.bit] @@ -78,7 +78,7 @@ [synthesis.branch/get] [synthesis.function/apply]) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> value}) (/////#each _.return (expression archive synthesis))]) ([synthesis.#Reference] @@ -87,7 +87,7 @@ (pattern (synthesis.branch/case case)) (//case.case! false statement expression archive case) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([synthesis.branch/exec //case.exec!] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux index 4895535d5..6decb3fcf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux @@ -83,7 +83,7 @@ inputsG (monad.each ! (phase archive) inputsS)] (in (_.do methodS inputsG {.#None} objectG))))])) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary Expression) (function.constant <unit>)) (def: <?> (Unary Expression) (_.= <unit>))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index a3235673f..18f902d29 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -51,8 +51,9 @@ {try.#Failure error} (/////.except extension.invalid_syntax [extension_name %synthesis input])))) -(template: (!unary function) - (|>> list _.apply (|> (_.constant function)))) +(def: !unary + (template (_ function) + (|>> list _.apply (|> (_.constant function))))) ... TODO: Get rid of this ASAP (def: lux::syntax_char_case! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux index 8a1f1d824..bbec22567 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/host.lux @@ -64,7 +64,7 @@ (/.install "delete" (binary array::delete)) ))) -(template [<!> <?> <unit>] +(with_template [<!> <?> <unit>] [(def: <!> (Nullary Expression) (function.constant <unit>)) (def: <?> (Unary Expression) (_.eq?/2 <unit>))] 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 33572414f..e016f9109 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 @@ -28,7 +28,7 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -39,7 +39,7 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] 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 3a94f56d6..3e0aabf99 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 @@ -67,7 +67,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^.template [<side> <accessor>] + (^.with_template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -106,7 +106,7 @@ (-> Nat (Expression Any)) (_.setq @cursor (_.nthcdr/2 [(_.int (.int pops)) @cursor]))) -(template [<name> <flag> <prep>] +(with_template [<name> <flag> <prep>] [(def: (<name> @fail simple? idx next!) (-> _.Tag Bit Nat (Maybe (Expression Any)) (Expression Any)) (.let [<failure_condition> (_.eq/2 [@variant @temp])] @@ -172,7 +172,7 @@ else! then!)))) - (^.template [<tag> <format> <=>] + (^.with_template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -190,7 +190,7 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=/2]) - (^.template [<complex> <simple> <choice>] + (^.with_template [<complex> <simple> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> @fail false idx {.#None})) @@ -204,7 +204,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (..push! (_.elt/2 [..peek (_.int +0)]))) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux index bb9c5681f..6c484b274 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/runtime.lux @@ -41,7 +41,7 @@ (def: module_id 0) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> [_.Tag Register] (Expression Any) (Expression Any)))] @@ -170,9 +170,10 @@ (with_expansions [<recur> (these (all _.then (_.; (_.set lefts (_.-/2 [last_index_right lefts]))) (_.; (_.set tuple (_.nth last_index_right tuple)))))] - (template: (!recur <side>) - (<side> (_.-/2 [last_index_right lefts]) - (_.elt/2 [tuple last_index_right]))) + (def: !recur + (template (_ <side>) + (<side> (_.-/2 [last_index_right lefts]) + (_.elt/2 [tuple last_index_right])))) (runtime: (tuple//left lefts tuple) (with_vars [last_index_right] 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 fa1cabf00..a5471f9b6 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 @@ -37,7 +37,7 @@ (def: (expression archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] 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 963d0574b..aa18b4348 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 @@ -149,7 +149,7 @@ (_.statement (|> @cursor (_.do "splice" (list (|> @cursor ..length (_.- popsJS)) popsJS)))))) -(template [<name> <flag>] +(with_template [<name> <flag>] [(def: (<name> simple? idx) (-> Bit Nat Statement) (all _.then @@ -181,7 +181,7 @@ (-> (-> Path (Operation Statement)) (-> Path (Operation (Maybe Statement)))) (.case pathP - (^.template [<simple> <choice>] + (^.with_template [<simple> <choice>] [(pattern (<simple> idx nextP)) (|> nextP again @@ -203,7 +203,7 @@ then!)})) ... Extra optimization - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (/////synthesis.path/seq (<pm> lefts) (/////synthesis.!bind_top register thenP))) @@ -285,7 +285,7 @@ ..fail_pm! clauses))) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [cases (monad.each ! (function (_ [match then]) @@ -297,19 +297,19 @@ ([/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^.template [<complex> <choice>] + (^.with_template [<complex> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> false idx))]) ([/////synthesis.side/left ..left_choice] [/////synthesis.side/right ..right_choice]) - (^.template [<pm> <getter>] + (^.with_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>] + (^.with_template [<tag> <combinator>] [(pattern (<tag> leftP rightP)) (do ///////phase.monad [left! (again leftP) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux index 444254018..b51c272d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/runtime.lux @@ -39,7 +39,7 @@ ["[0]" registry (.only Registry)] ["[0]" unit]]]]]]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> [Register Text] Expression Statement))] @@ -281,7 +281,7 @@ (-> Expression Expression Computation) (_.new ..i64::new (list high low))) -(template [<name> <op>] +(with_template [<name> <op>] [(runtime: (<name> subject parameter) (_.return (..i64 (<op> (_.the ..i64_high_field subject) (_.the ..i64_high_field parameter)) 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 c4b026541..a23f31e36 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 @@ -24,7 +24,7 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (///#in (<generator> value))]) ([synthesis.bit /primitive.bit] 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 6857dae20..e96a88889 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 @@ -123,7 +123,7 @@ (_.set_label @else) else!))))) -(template [<name> <type> <unwrap> <dup> <pop> <test> <comparison> <if>] +(with_template [<name> <type> <unwrap> <dup> <pop> <test> <comparison> <if>] [(def: (<name> again @else cons) (-> (-> Path (Operation (Bytecode Any))) Label (Fork <type> Path) @@ -167,7 +167,7 @@ {synthesis.#Bind register} (..path|bind register) - (^.template [<tag> <path>] + (^.with_template [<tag> <path>] [{<tag> it} (<path> again @else it)]) ([synthesis.#Bit_Fork ..path|bit_fork] @@ -200,7 +200,7 @@ (_.set_label @success) //runtime.push))) - (^.template [<pattern> <projection>] + (^.with_template [<pattern> <projection>] [(pattern (<pattern> lefts)) (operation#in (all _.composite ..peek 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 21c740700..90c3044ae 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 @@ -34,7 +34,7 @@ (def: .public (i64 value) (-> (I64 Any) (Bytecode Any)) (case (.int value) - (^.template [<int> <instruction>] + (^.with_template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] @@ -42,7 +42,7 @@ ([+0 _.lconst_0] [+1 _.lconst_1]) - (^.template [<int> <instruction>] + (^.with_template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -91,14 +91,14 @@ (def: .public (f64 value) (-> Frac (Bytecode Any)) (case value - (^.template [<int> <instruction>] + (^.with_template [<int> <instruction>] [<int> (do _.monad [_ <instruction>] ..wrap_f64)]) ([+1.0 _.dconst_1]) - (^.template [<int> <instruction>] + (^.with_template [<int> <instruction>] [<int> (do _.monad [_ <instruction> @@ -106,7 +106,7 @@ ..wrap_f64)]) ([+2.0 _.fconst_2]) - (^.template [<int> <instruction>] + (^.with_template [<int> <instruction>] [<int> (do _.monad [_ <instruction> diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux index 11db49aed..7f6ade8c6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/reference.lux @@ -30,7 +30,7 @@ (Bytecode Any) _.aload_0) -(template [<name> <prefix>] +(with_template [<name> <prefix>] [(def: .public <name> (-> Register Text) (|>> %.nat (format <prefix>)))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 4c6a232f9..13f09e66e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -73,7 +73,7 @@ (type: .public Anchor [Label Register]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> Anchor (Bytecode Any) Definition))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux index a415f60fa..9cd5f6d93 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/value.lux @@ -10,10 +10,10 @@ (def: .public field "value") -(template [<name> <boolean> <byte> <short> <int> <long> <float> <double> <char>] +(with_template [<name> <boolean> <byte> <short> <int> <long> <float> <double> <char>] [(def: (<name> type) (-> (Type Primitive) Text) - (`` (cond (~~ (template [<type> <output>] + (`` (cond (~~ (with_template [<type> <output>] [(type#= <type> type) <output>] [type.boolean <boolean>] 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 8d861e382..e14772296 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 @@ -37,7 +37,7 @@ (def: (expression archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([synthesis.bit /primitive.bit] 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 fd878a2b7..725a1f82b 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 @@ -151,7 +151,7 @@ (def: fail! _.break) -(template [<name> <flag>] +(with_template [<name> <flag>] [(def: (<name> simple? idx) (-> Bit Nat Statement) (all _.then @@ -209,7 +209,7 @@ else! then!)))) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -227,7 +227,7 @@ [/////synthesis.#F64_Fork _.float] [/////synthesis.#Text_Fork _.string]) - (^.template [<complex> <simple> <choice>] + (^.with_template [<complex> <simple> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) @@ -239,7 +239,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +1)) ..push!)) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] @@ -252,7 +252,7 @@ (_.local/1 (..register register) ..peek_and_pop) then!))) - (^.template [<tag> <combinator>] + (^.with_template [<tag> <combinator>] [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux index 736dbb450..ff40f0f26 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/primitive.lux @@ -4,7 +4,7 @@ [target ["_" lua (.only Literal)]]]]) -(template [<name> <type> <implementation>] +(with_template [<name> <type> <implementation>] [(def: .public <name> (-> <type> Literal) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux index 93f3cb980..503638aeb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/runtime.lux @@ -39,7 +39,7 @@ ["[0]" registry (.only Registry)] ["[0]" unit]]]]]]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> [Register Label] Expression Statement))] 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 3d2107867..dea69708f 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 @@ -32,7 +32,7 @@ (def: (statement expression archive synthesis) Phase! (case synthesis - (^.template [<tag>] + (^.with_template [<tag>] [(pattern (<tag> value)) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.bit] @@ -44,7 +44,7 @@ [////synthesis.branch/get] [////synthesis.function/apply]) - (^.template [<tag>] + (^.with_template [<tag>] [(pattern {<tag> value}) (//////phase#each _.return (expression archive synthesis))]) ([////synthesis.#Reference] @@ -53,7 +53,7 @@ (pattern (////synthesis.branch/case case)) (/case.case! statement expression archive case) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/let /case.let!] @@ -70,7 +70,7 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -81,7 +81,7 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] @@ -91,7 +91,7 @@ [////synthesis.branch/get /case.get] [////synthesis.function/apply /function.apply]) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> statement expression archive value)]) ([////synthesis.branch/case /case.case] 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 c05a3813d..c4f5534ac 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 @@ -87,7 +87,7 @@ [valueG (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^.template [<side> <accessor>] + (^.with_template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -134,7 +134,7 @@ (_.int +0) (_.int (i.* -1 (.int pops)))]))) -(template [<name> <flag> <prep>] +(with_template [<name> <flag> <prep>] [(def: (<name> simple? idx) (-> Bit Nat Statement) (all _.then @@ -191,7 +191,7 @@ else! then!)))) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -206,7 +206,7 @@ [/////synthesis.#F64_Fork //primitive.f64] [/////synthesis.#Text_Fork //primitive.text]) - (^.template [<complex> <simple> <choice>] + (^.with_template [<complex> <simple> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) @@ -220,7 +220,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] @@ -241,7 +241,7 @@ ... (..multi_pop! (n.+ 2 extra_pops)) ... next!)))) - (^.template [<tag> <combinator>] + (^.with_template [<tag> <combinator>] [(pattern (<tag> preP postP)) (do ///////phase.monad [pre! (again preP) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux index 5c22acced..501c2ac3d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/runtime.lux @@ -38,7 +38,7 @@ [archive (.only Output Archive) ["[0]" artifact (.only Registry)]]]]]]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> [Nat Label] Expression Statement))] 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 f3e8d85b8..054e84344 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 @@ -37,7 +37,7 @@ (def: .public (expression archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -45,7 +45,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] @@ -58,7 +58,7 @@ [////synthesis.function/apply /function.apply]) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] 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 d05828a5f..0997c9a9b 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 @@ -155,7 +155,7 @@ (-> Nat (Statement Any)) (_.delete (_.slice_from (_.int (i.* -1 (.int pops))) @cursor))) -(template [<name> <flag>] +(with_template [<name> <flag>] [(def: (<name> simple? idx) (-> Bit Nat (Statement Any)) (all _.then @@ -218,7 +218,7 @@ else! then!))})) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -258,7 +258,7 @@ {/////synthesis.#Bind register} (///////phase#in (_.set (list (..register register)) ..peek)) - (^.template [<complex> <simple> <choice>] + (^.with_template [<complex> <simple> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) @@ -272,7 +272,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple::left] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux index c9ff8d221..7afebeba8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/primitive.lux @@ -6,7 +6,7 @@ ["[0]" // ["[1][0]" runtime]]) -(template [<type> <name> <implementation>] +(with_template [<type> <name> <implementation>] [(def: .public <name> (-> <type> (Expression Any)) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux index 8ed7f8bb8..12d1f65c7 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/runtime.lux @@ -41,7 +41,7 @@ ["[0]" registry (.only Registry)] ["[0]" unit]]]]]]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> Register (Expression Any) (Statement Any)))] @@ -283,7 +283,7 @@ (runtime: (i64::64 input) (with_vars [temp] - (`` (<| (~~ (template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (all _.then (_.set (list temp) (_.% <iteration> input)) @@ -336,7 +336,7 @@ (_.return (_.- (|> subject (..i64#/ param) (_.* param)) subject))) -(template [<runtime> <host>] +(with_template [<runtime> <host>] [(runtime: (<runtime> left right) (_.return (..i64::64 (<host> (..as_nat left) (..as_nat right)))))] 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 3e4cf4f0e..582d8dd42 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 @@ -30,7 +30,7 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -41,7 +41,7 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] 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 52626fefb..a587c3883 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 @@ -69,7 +69,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^.template [<side> <accessor>] + (^.with_template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple::left] @@ -162,7 +162,7 @@ else! then!)))) - (^.template [<tag> <format> <=>] + (^.with_template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -180,7 +180,7 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=] [/////synthesis.#Text_Fork //primitive.text _.=]) - (^.template [<pm> <flag> <prep>] + (^.with_template [<pm> <flag> <prep>] [(pattern (<pm> idx)) (///////phase#in (all _.then (_.set! $temp (|> idx <prep> .int _.int (//runtime.sum::get ..peek (//runtime.flag <flag>)))) @@ -193,7 +193,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (_.item (_.int +1) ..peek)) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple::left] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux index c377bbcc0..ca30d7b84 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/primitive.lux @@ -6,7 +6,7 @@ ["[0]" // ["[1][0]" runtime]]) -(template [<name> <type> <code>] +(with_template [<name> <type> <code>] [(def: .public <name> (-> <type> Expression) <code>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 025abf8f6..85f63171f 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 @@ -152,7 +152,7 @@ )) ... [[Bits]] -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -162,7 +162,7 @@ [bit//xor runtimeT.bit//xor] ) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> (runtimeT.int64_low paramO) subjectO))] @@ -189,7 +189,7 @@ ("static" MIN_VALUE Double) ("static" MAX_VALUE Double)) -(template [<name> <const> <encode>] +(with_template [<name> <const> <encode>] [(def: (<name> _) Nullary (<encode> <const>))] @@ -199,7 +199,7 @@ [frac//max Double::MAX_VALUE r.float] ) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (|> subjectO (<op> paramO)))] @@ -211,7 +211,7 @@ [int//rem runtimeT.int//%] ) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -228,7 +228,7 @@ [text//< r.<] ) -(template [<name> <cmp>] +(with_template [<name> <cmp>] [(def: (<name> [subjectO paramO]) Binary (<cmp> paramO subjectO))] 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 ece7d2035..1f79ef1d6 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 @@ -15,7 +15,7 @@ (/// ["[0]T" runtime]) (// ["@" common])) -... (template [<name> <lua>] +... (with_template [<name> <lua>] ... [(def: (<name> _) @.Nullary <lua>)] ... [lua//nil "nil"] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index e44c646d7..fbd61560c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -44,7 +44,7 @@ (def: module_id 0) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> _.SVar _.Expression _.Expression))] @@ -165,7 +165,7 @@ (def: high_shift (_.bit_shl (_.int +32))) -(template [<name> <power>] +(with_template [<name> <power>] [(runtime: <name> (|> (_.as::integer (_.int +2)) (_.** (_.as::integer (_.int <power>)))))] [f2^32 +32] @@ -219,7 +219,7 @@ (i64.left_shifted 32) (i64.or low))) -(template [<name> <value>] +(with_template [<name> <value>] [(runtime: <name> (..i64 <value>))] @@ -638,7 +638,7 @@ @adt::variant )) -(template [<name> <op>] +(with_template [<name> <op>] [(runtime: (<name> mask input) (i64::new (<op> (i64_high mask) (i64_high input)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux index 94f243273..ef188574b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux @@ -67,7 +67,7 @@ (phase#each (|>> ..artifact (at system constant')) (////generation.remember archive name))) -(template [<sigil> <name>] +(with_template [<sigil> <name>] [(def: .public (<name> system) (All (_ expression) (-> (System expression) 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 f0e8638e4..6a11d8996 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 @@ -37,7 +37,7 @@ (def: (expression archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -45,7 +45,7 @@ [////synthesis.f64 /primitive.f64] [////synthesis.text /primitive.text]) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> expression archive value)]) ([////synthesis.variant /structure.variant] @@ -58,7 +58,7 @@ [////synthesis.function/apply /function.apply]) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> ///extension/common.statement expression archive value)]) ([////synthesis.branch/case /case.case] 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 56b9b11f6..4c9de660a 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 @@ -159,7 +159,7 @@ {.#None} @cursor))) -(template [<name> <flag>] +(with_template [<name> <flag>] [(def: (<name> simple? idx) (-> Bit Nat Statement) (all _.then @@ -227,7 +227,7 @@ else! then!))})) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -284,7 +284,7 @@ else! then!)))) - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -301,7 +301,7 @@ [/////synthesis.#F64_Fork (<| //primitive.f64)] [/////synthesis.#Text_Fork (<| //primitive.text)]) - (^.template [<complex> <simple> <choice>] + (^.with_template [<complex> <simple> <choice>] [(pattern (<complex> idx)) (///////phase#in (<choice> false idx)) @@ -315,7 +315,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (|> ..peek (_.item (_.int +0)) ..push!)) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push!))]) ([/////synthesis.member/left //runtime.tuple//left] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux index c717441cb..162936972 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/primitive.lux @@ -4,7 +4,7 @@ [target ["_" ruby (.only Literal)]]]]) -(template [<type> <name> <implementation>] +(with_template [<type> <name> <implementation>] [(def: .public <name> (-> <type> Literal) <implementation>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux index 85a7286c1..ca2346d95 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/runtime.lux @@ -40,7 +40,7 @@ ["[0]" unit] ["[0]" registry (.only Registry)]]]]]]) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> Register Expression Statement))] @@ -286,7 +286,7 @@ (runtime: (i64::i64 input) [..mruby? (_.return input)] (with_vars [temp] - (`` (<| (~~ (template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (all _.then (_.set (list temp) (_.% <iteration> input)) @@ -313,19 +313,20 @@ (def: i32::up (_.bit_shl (_.int +32))) -(template: (i64 @high @low) - [(|> (_.? (i32::positive? @high) - @high - (|> (_.manual "+0xFFFFFFFF") - (_.- @high) - _.bit_not)) - i32::up - (_.bit_or @low))]) +(def: i64 + (template (_ @high @low) + [(|> (_.? (i32::positive? @high) + @high + (|> (_.manual "+0xFFFFFFFF") + (_.- @high) + _.bit_not)) + i32::up + (_.bit_or @low))])) (def: as_nat (_.% ..i64::+iteration)) -(template [<runtime> <host>] +(with_template [<runtime> <host>] [(runtime: (<runtime> left right) [..normal_ruby? (_.return (..i64::i64 (<host> (..as_nat left) (..as_nat right))))] (with_vars [high low] 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 061a5c26c..2702efa5e 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 @@ -30,7 +30,7 @@ (def: .public (generate archive synthesis) Phase (case synthesis - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (//////phase#in (<generator> value))]) ([////synthesis.bit /primitive.bit] @@ -41,7 +41,7 @@ {////synthesis.#Reference value} (//reference.reference /reference.system archive value) - (^.template [<tag> <generator>] + (^.with_template [<tag> <generator>] [(pattern (<tag> value)) (<generator> generate archive value)]) ([////synthesis.variant /structure.variant] 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 9a7db7f48..bcaf13e2f 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 @@ -67,7 +67,7 @@ [valueO (expression archive valueS)] (in (list#mix (function (_ side source) (.let [method (.case side - (^.template [<side> <accessor>] + (^.with_template [<side> <accessor>] [(<side> lefts) (<accessor> (_.int (.int lefts)))]) ([.#Left //runtime.tuple//left] @@ -156,7 +156,7 @@ else! then!)))) - (^.template [<tag> <format> <=>] + (^.with_template [<tag> <format> <=>] [{<tag> item} (do [! ///////phase.monad] [clauses (monad.each ! (function (_ [match then]) @@ -174,7 +174,7 @@ [/////synthesis.#F64_Fork //primitive.f64 _.=/2] [/////synthesis.#Text_Fork //primitive.text _.string=?/2]) - (^.template [<pm> <flag> <prep>] + (^.with_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) @@ -186,7 +186,7 @@ (pattern (/////synthesis.member/left 0)) (///////phase#in (..push_cursor! (_.vector_ref/2 ..peek (_.int +0)))) - (^.template [<pm> <getter>] + (^.with_template [<pm> <getter>] [(pattern (<pm> lefts)) (///////phase#in (|> ..peek (<getter> (_.int (.int lefts))) ..push_cursor!))]) ([/////synthesis.member/left //runtime.tuple//left] 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 0de2a275a..3bf0659ba 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 @@ -80,7 +80,7 @@ (bundle.install "is?" (binary (product.uncurried _.eq?/2))) (bundle.install "try" (unary ///runtime.lux//try)))) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -104,7 +104,7 @@ Binary (///runtime.i64//logical_right_shifted (_.remainder/2 (_.int +64) paramO) subjectO)) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (|> subjectO (<op> paramO)))] @@ -116,7 +116,7 @@ [i64::% _.remainder/2] ) -(template [<name> <op>] +(with_template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -133,7 +133,7 @@ [text::< _.string<?/2] ) -(template [<name> <cmp>] +(with_template [<name> <cmp>] [(def: (<name> [subjectO paramO]) Binary (<cmp> paramO subjectO))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux index 5cebadb2b..0772c64bc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/primitive.lux @@ -4,7 +4,7 @@ [target ["_" scheme (.only Expression)]]]]) -(template [<name> <type> <code>] +(with_template [<name> <type> <code>] [(def: .public <name> (-> <type> Expression) <code>)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux index 63c9ae0ab..ab4177125 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/runtime.lux @@ -42,7 +42,7 @@ (def: module_id 0) -(template [<name> <base>] +(with_template [<name> <base>] [(type: .public <name> (<base> Var Expression Expression))] @@ -255,7 +255,7 @@ (runtime: (i64//64 input) (with_vars [temp] - (`` (<| (~~ (template [<scenario> <iteration> <cap> <entrance>] + (`` (<| (~~ (with_template [<scenario> <iteration> <cap> <entrance>] [(_.if (|> input <scenario>) (_.let (list [temp (_.remainder/2 <iteration> input)]) (_.if (|> temp <scenario>) @@ -283,7 +283,7 @@ ..as_nat (_.arithmetic_shift/2 (_.-/2 shift (_.int +0))))))) -(template [<runtime> <host>] +(with_template [<runtime> <host>] [(runtime: (<runtime> left right) (..i64//64 (<host> (..as_nat left) (..as_nat right))))] 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 99db4589b..de5d4c9e4 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 @@ -35,14 +35,14 @@ {///simple.#Unit} {/simple.#Text /.unit} - (^.template [<analysis> <synthesis>] + (^.with_template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> value}]) ([///simple.#Bit /simple.#Bit] [///simple.#Frac /simple.#F64] [///simple.#Text /simple.#Text]) - (^.template [<analysis> <synthesis>] + (^.with_template [<analysis> <synthesis>] [{<analysis> value} {<synthesis> (.i64 value)}]) ([///simple.#Nat /simple.#I64] 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 a24d6f7d4..fcd14c576 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 @@ -54,7 +54,7 @@ {/.#Bit_Fork when then {.#None}}) thenC) - (^.template [<from> <to> <conversion>] + (^.with_template [<from> <to> <conversion>] [{<from> test} (///#each (function (_ then) {<to> [(<conversion> test) then] (list)}) @@ -172,14 +172,14 @@ {.#Some old_else} (weave new_then old_else))}}) - (^.template [<tag> <equivalence>] + (^.with_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?>] + (^.with_template [<access> <side> <lefts> <right?>] [[{/.#Access {<access> [<lefts> newL <right?> <side>]}} {/.#Access {<access> [<lefts> oldL <right?> <side>]}}] (if (n.= newL oldL) @@ -243,10 +243,11 @@ tailSP+ (monad.each ! (product.uncurried (path archive synthesize)) tailPA+)] (in (/.branch/case [input (list#mix weave headSP tailSP+)])))) -(template: (!masking <variable> <output>) - [[[{///pattern.#Bind <variable>} - {///analysis.#Reference (///reference.local <output>)}] - (list)]]) +(def: !masking + (template (_ <variable> <output>) + [[[{///pattern.#Bind <variable>} + {///analysis.#Reference (///reference.local <output>)}] + (list)]])) (def: .public (synthesize_exec synthesize archive before after) (-> Phase Archive Synthesis Analysis (Operation Synthesis)) @@ -274,10 +275,11 @@ else (synthesize archive else)] (in (/.branch/if [test then else])))) -(template: (!get <patterns> <output>) - [[[(///pattern.tuple <patterns>) - {///analysis.#Reference (///reference.local <output>)}] - (.list)]]) +(def: !get + (template (_ <patterns> <output>) + [[[(///pattern.tuple <patterns>) + {///analysis.#Reference (///reference.local <output>)}] + (.list)]])) (def: .public (synthesize_get synthesize archive input patterns @member) (-> Phase Archive Synthesis (///complex.Tuple Pattern) Register (Operation Synthesis)) 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 ac7a81a73..81e10d318 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 @@ -42,8 +42,9 @@ (enum.range n.enum 1) (list#each (|>> /.variable/local)))) -(template: .public (self_reference) - [(/.variable/local 0)]) +(def: .public self_reference + (template (self_reference) + [(/.variable/local 0)])) (def: (expanded_nested_self_reference arity) (-> Arity Synthesis) @@ -100,7 +101,7 @@ {/.#Bind register} (phase#in {/.#Bind (++ register)}) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} (do phase.monad [left' (grow_path grow left) @@ -119,7 +120,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> [[test then] elses]} (do [! phase.monad] [then (grow_path grow then) 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 d57b85be1..eeb412da4 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 @@ -36,7 +36,7 @@ {/.#Bind register} {.#Some {/.#Bind (register_optimization offset register)}} - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} (do maybe.monad [left' (again left) @@ -55,7 +55,7 @@ (in {.#None}))] (in {/.#Bit_Fork when then else})) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> [[test then] elses]} (do [! maybe.monad] [then (again 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 1ea006203..6cd117d2d 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 @@ -68,7 +68,7 @@ register)} (again post)}}) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} {<tag> (again left) (again right)}]) ([/.#Seq] @@ -77,7 +77,7 @@ {/.#Bit_Fork when then else} {/.#Bit_Fork when (again then) (maybe#each again else)} - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> [[test then] tail]} {<tag> [[test (again then)] (list#each (function (_ [test' then']) @@ -216,7 +216,7 @@ (in [redundancy {.#Item head tail}]))))) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [register Register]) (exception.report "Register" (%.nat register)))] @@ -274,7 +274,7 @@ (in [redundancy {.#None}]))] (in [redundancy {/.#Bit_Fork when then else}])) - (^.template [<tag> <type>] + (^.with_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/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index 3b7d560b4..d0bc4dbdc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -33,8 +33,9 @@ [control ["[0]" maybe] ["[0]" exception (.only exception:)] - [parser - [text (.only Offset)]]] + ["<>" parser (.only) + [text (.only Offset)] + ["<[0]>" code]]] [data ["[0]" text (.only) ["%" format (.only format)]] @@ -42,6 +43,7 @@ ["[0]" list] ["[0]" dictionary (.only Dictionary)]]] [macro + [syntax (.only syntax)] ["[0]" template]] [meta ["[0]" symbol]] @@ -52,11 +54,18 @@ ["[0]" rev] ["[0]" frac]]]]]) -(template: (inline: <declaration> <type> <body>) - [(for @.python (def: <declaration> <type> <body>) - ... TODO: No longer skip inlining Lua after Rembulan isn't being used anymore. - @.lua (def: <declaration> <type> <body>) - (template: <declaration> [<body>]))]) +(def: declaration_name + (syntax (_ [[name parameters] (<code>.form (<>.and <code>.any (<>.some <code>.any)))]) + (in (list name)))) + +(def: inline: + (template (_ <declaration> <type> <body>) + [(for @.python (def: <declaration> <type> <body>) + ... TODO: No longer skip inlining Lua after Rembulan isn't being used anymore. + @.lua (def: <declaration> <type> <body>) + (`` (def: (~~ (..declaration_name <declaration>)) + (template <declaration> + [<body>]))))])) ... TODO: Implement "lux syntax char case!" as a custom extension. ... That way, it should be possible to obtain the char without wrapping @@ -74,29 +83,33 @@ (type: Char Nat) -(template [<extension> <diff> <name>] - [(template: (<name> value) - [(<extension> <diff> value)])] +(with_template [<extension> <diff> <name>] + [(def: <name> + (template (_ value) + [(<extension> <diff> value)]))] ["lux i64 +" 1 !++] ["lux i64 +" 2 !++/2] ["lux i64 -" 1 !--] ) -(template: (!clip from to text) - [("lux text clip" from (n.- from to) text)]) +(def: !clip + (template (_ from to text) + [("lux text clip" from (n.- from to) text)])) -(template [<name> <extension>] - [(template: (<name> reference subject) - [(<extension> reference subject)])] +(with_template [<name> <extension>] + [(def: <name> + (template (_ reference subject) + [(<extension> reference subject)]))] [!n/= "lux i64 ="] [!i/< "lux i64 <"] ) -(template [<name> <extension>] - [(template: (<name> param subject) - [(<extension> param subject)])] +(with_template [<name> <extension>] + [(def: <name> + (template (_ param subject) + [(<extension> param subject)]))] [!n/+ "lux i64 +"] [!n/- "lux i64 -"] @@ -114,7 +127,7 @@ (def: .public text_delimiter text.double_quote) -(template [<char> <definition>] +(with_template [<char> <definition>] [(def: .public <definition> <char>)] ... Form delimiters @@ -174,40 +187,46 @@ (exception.report "Text" (%.text text))) -(template: (!failure parser where offset source_code) - [{.#Left [[where offset source_code] - (exception.error ..unrecognized_input [where (%.symbol (symbol parser)) source_code offset])]}]) +(def: !failure + (template (_ parser where offset source_code) + [{.#Left [[where offset source_code] + (exception.error ..unrecognized_input [where (%.symbol (symbol parser)) source_code offset])]}])) -(template: (!end_of_file where offset source_code current_module) - [{.#Left [[where offset source_code] - (exception.error ..end_of_file current_module)]}]) +(def: !end_of_file + (template (_ where offset source_code current_module) + [{.#Left [[where offset source_code] + (exception.error ..end_of_file current_module)]}])) (type: (Parser a) (-> Source (Either [Source Text] [Source a]))) -(template: (!with_char+ @source_code_size @source_code @offset @char @else @body) - [(if (!i/< (as Int @source_code_size) - (as Int @offset)) - (let [@char ("lux text char" @offset @source_code)] - @body) - @else)]) - -(template: (!with_char @source_code @offset @char @else @body) - [(!with_char+ ("lux text size" @source_code) @source_code @offset @char @else @body)]) - -(template: (!letE <binding> <computation> <body>) - [(case <computation> - {.#Right <binding>} - <body> - - ... {.#Left error} - <<otherwise>> - (as_expected <<otherwise>>))]) - -(template: (!horizontal where offset source_code) - [[(revised .#column ++ where) - (!++ offset) - source_code]]) +(def: !with_char+ + (template (_ @source_code_size @source_code @offset @char @else @body) + [(if (!i/< (as Int @source_code_size) + (as Int @offset)) + (let [@char ("lux text char" @offset @source_code)] + @body) + @else)])) + +(def: !with_char + (template (_ @source_code @offset @char @else @body) + [(!with_char+ ("lux text size" @source_code) @source_code @offset @char @else @body)])) + +(def: !letE + (template (_ <binding> <computation> <body>) + [(case <computation> + {.#Right <binding>} + <body> + + ... {.#Left error} + <<otherwise>> + (as_expected <<otherwise>>))])) + +(def: !horizontal + (template (_ where offset source_code) + [[(revised .#column ++ where) + (!++ offset) + source_code]])) (inline: (!new_line where) (-> Location Location) @@ -219,12 +238,13 @@ (let [[where::file where::line where::column] where] [where::file where::line (!n/+ length where::column)])) -(template: (!vertical where offset source_code) - [[(!new_line where) - (!++ offset) - source_code]]) +(def: !vertical + (template (_ where offset source_code) + [[(!new_line where) + (!++ offset) + source_code]])) -(template [<name> <close> <tag>] +(with_template [<name> <close> <tag>] [(inline: (<name> parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) @@ -248,14 +268,15 @@ [tuple_parser ..close_tuple .#Tuple] ) -(template: (!guarantee_no_new_lines where offset source_code content body) - [(case ("lux text index" 0 (static text.new_line) content) - {.#None} - body +(def: !guarantee_no_new_lines + (template (_ where offset source_code content body) + [(case ("lux text index" 0 (static text.new_line) content) + {.#None} + body - g!_ - {.#Left [[where offset source_code] - (exception.error ..text_cannot_contain_new_lines content)]})]) + g!_ + {.#Left [[where offset source_code] + (exception.error ..text_cannot_contain_new_lines content)]})])) (def: (text_parser where offset source_code) (-> Location Offset Text (Either [Source Text] [Source Code])) @@ -274,7 +295,7 @@ (!failure ..text_parser where offset source_code))) (with_expansions [<digits> (these "0" "1" "2" "3" "4" "5" "6" "7" "8" "9") - <non_symbol_chars> (template [<char>] + <non_symbol_chars> (with_template [<char>] [(~~ (static <char>))] [text.space] @@ -285,56 +306,61 @@ [..open_tuple] [..close_tuple] [..text_delimiter]) <digit_separator> (static ..digit_separator)] - (template: (!if_digit? @char @then @else) - [("lux syntax char case!" @char - [[<digits>] - @then] - - ... else - @else)]) - - (template: (!if_digit?+ @char @then @else_options @else) - [(`` ("lux syntax char case!" @char - [[<digits> <digit_separator>] - @then - - (~~ (template.spliced @else_options))] - - ... else - @else))]) - - (`` (template: (!if_symbol_char?|tail @char @then @else) - [("lux syntax char case!" @char - [[<non_symbol_chars>] - @else] - - ... else - @then)])) - - (`` (template: (!if_symbol_char?|head @char @then @else) - [("lux syntax char case!" @char - [[<non_symbol_chars> <digits>] - @else] - - ... else - @then)])) + (def: !if_digit? + (template (_ @char @then @else) + [("lux syntax char case!" @char + [[<digits>] + @then] + + ... else + @else)])) + + (def: !if_digit?+ + (template (_ @char @then @else_options @else) + [(`` ("lux syntax char case!" @char + [[<digits> <digit_separator>] + @then + + (~~ (template.spliced @else_options))] + + ... else + @else))])) + + (`` (def: !if_symbol_char?|tail + (template (_ @char @then @else) + [("lux syntax char case!" @char + [[<non_symbol_chars>] + @else] + + ... else + @then)]))) + + (`` (def: !if_symbol_char?|head + (template (_ @char @then @else) + [("lux syntax char case!" @char + [[<non_symbol_chars> <digits>] + @else] + + ... else + @then)]))) ) -(template: (!number_output <source_code> <start> <end> <codec> <tag>) - [(case (|> <source_code> - (!clip <start> <end>) - (text.replaced ..digit_separator "") - (at <codec> decoded)) - {.#Right output} - {.#Right [[(let [[where::file where::line where::column] where] - [where::file where::line (!n/+ (!n/- <start> <end>) where::column)]) - <end> - <source_code>] - [where {<tag> output}]]} - - {.#Left error} - {.#Left [[where <start> <source_code>] - error]})]) +(def: !number_output + (template (_ <source_code> <start> <end> <codec> <tag>) + [(case (|> <source_code> + (!clip <start> <end>) + (text.replaced ..digit_separator "") + (at <codec> decoded)) + {.#Right output} + {.#Right [[(let [[where::file where::line where::column] where] + [where::file where::line (!n/+ (!n/- <start> <end>) where::column)]) + <end> + <source_code>] + [where {<tag> output}]]} + + {.#Left error} + {.#Left [[where <start> <source_code>] + error]})])) (def: no_exponent Offset @@ -344,7 +370,7 @@ <frac_output> (these (!number_output source_code start end frac.decimal .#Frac)) <failure> (!failure ..frac_parser where offset source_code) <frac_separator> (static ..frac_separator) - <signs> (template [<sign>] + <signs> (with_template [<sign>] [(~~ (static <sign>))] [..positive_sign] @@ -388,7 +414,7 @@ <int_output>)))) ) -(template [<parser> <codec> <tag>] +(with_template [<parser> <codec> <tag>] [(inline: (<parser> source_code//size start where offset source_code) (-> Nat Nat Location Offset Text (Either [Source Text] [Source Code])) @@ -403,12 +429,13 @@ [rev_parser rev.decimal .#Rev] ) -(template: (!signed_parser source_code//size offset where source_code @aliases @end) - [(<| (let [g!offset/1 (!++ offset)]) - (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) - (!if_digit? g!char/1 - (signed_parser source_code//size offset where (!++/2 offset) source_code) - (!full_symbol_parser offset [where (!++ offset) source_code] where @aliases .#Symbol)))]) +(def: !signed_parser + (template (_ source_code//size offset where source_code @aliases @end) + [(<| (let [g!offset/1 (!++ offset)]) + (!with_char+ source_code//size source_code g!offset/1 g!char/1 @end) + (!if_digit? g!char/1 + (signed_parser source_code//size offset where (!++/2 offset) source_code) + (!full_symbol_parser offset [where (!++ offset) source_code] where @aliases .#Symbol)))])) (with_expansions [<output> {.#Right [[(revised .#column (|>> (!n/+ (!n/- start end))) where) end @@ -424,11 +451,12 @@ (again (!++ end)) <output>)))))) -(template: (!half_symbol_parser @offset @char @module) - [(!if_symbol_char?|head @char - (!letE [source' symbol] (..symbol_part_parser @offset (!forward 1 where) (!++ @offset) source_code) - {.#Right [source' [@module symbol]]}) - (!failure ..!half_symbol_parser where @offset source_code))]) +(def: !half_symbol_parser + (template (_ @offset @char @module) + [(!if_symbol_char?|head @char + (!letE [source' symbol] (..symbol_part_parser @offset (!forward 1 where) (!++ @offset) source_code) + {.#Right [source' [@module symbol]]}) + (!failure ..!half_symbol_parser where @offset source_code))])) (`` (def: (short_symbol_parser source_code//size current_module [where offset/0 source_code]) (-> Nat Text (Parser Symbol)) @@ -441,9 +469,10 @@ (!half_symbol_parser offset/1 char/1 current_module)) (!half_symbol_parser offset/0 char/0 (static ..prelude)))))) -(template: (!short_symbol_parser source_code//size @current_module @source @where @tag) - [(!letE [source' symbol] (..short_symbol_parser source_code//size @current_module @source) - {.#Right [source' [@where {@tag symbol}]]})]) +(def: !short_symbol_parser + (template (_ source_code//size @current_module @source @where @tag) + [(!letE [source' symbol] (..short_symbol_parser source_code//size @current_module @source) + {.#Right [source' [@where {@tag symbol}]]})])) (with_expansions [<simple> (these {.#Right [source' ["" simple]]})] (`` (def: (full_symbol_parser aliases start source) @@ -464,9 +493,10 @@ complex]]})) <simple>))))) -(template: (!full_symbol_parser @offset @source @where @aliases @tag) - [(!letE [source' full_symbol] (..full_symbol_parser @aliases @offset @source) - {.#Right [source' [@where {@tag full_symbol}]]})]) +(def: !full_symbol_parser + (template (_ @offset @source @where @aliases @tag) + [(!letE [source' full_symbol] (..full_symbol_parser @aliases @offset @source) + {.#Right [source' [@where {@tag full_symbol}]]})])) ... TODO: Grammar macro for specifying syntax. ... (grammar: lux_grammar @@ -478,8 +508,9 @@ <move_2> (these [(!forward 1 where) (!++/2 offset/0) source_code]) <again> (these (parse current_module aliases source_code//size))] - (template: (!close closer) - [{.#Left [<move_1> closer]}]) + (def: !close + (template (_ closer) + [{.#Left [<move_1> closer]}])) (def: (bit_syntax value [where offset/0 source_code]) (-> Bit (Parser Code)) @@ -497,7 +528,7 @@ (function (again [where offset/0 source_code]) (<| (!with_char+ source_code//size source_code offset/0 char/0 (!end_of_file where offset/0 source_code current_module)) - (with_expansions [<composites> (template [<open> <close> <parser>] + (with_expansions [<composites> (with_template [<open> <close> <parser>] [[(~~ (static <open>))] (<parser> <again> <consume_1>) @@ -568,7 +599,7 @@ (!with_char+ source_code//size source_code offset/1 char/1 (!end_of_file where offset/1 source_code current_module)) ("lux syntax char case!" char/1 - [(~~ (template [<char> <bit>] + [(~~ (with_template [<char> <bit>] [[<char>] (..bit_syntax <bit> [where offset/0 source_code])] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index 2f9b007dd..831374079 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -125,7 +125,7 @@ {#Control (Control Synthesis)} {#Extension (Extension Synthesis)}))) -(template [<special> <general>] +(with_template [<special> <general>] [(type: .public <special> (<general> ..State Analysis Synthesis))] @@ -143,30 +143,33 @@ Path {#Pop}) -(template [<name> <kind>] - [(template: .public (<name> content) - [(.<| {..#Access} - {<kind>} - content)])] +(with_template [<name> <kind>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Access} + {<kind>} + content)]))] [path/side /access.#Side] [path/member /access.#Member] ) -(template [<name> <access> <lefts> <right?>] - [(template: .public (<name> lefts right?) - [(.<| {..#Access} - {<access>} - [<lefts> lefts - <right?> right?])])] +(with_template [<name> <access> <lefts> <right?>] + [(def: .public <name> + (template (<name> lefts right?) + [(.<| {..#Access} + {<access>} + [<lefts> lefts + <right?> right?])]))] [side /access.#Side /side.#lefts /side.#right?] [member /access.#Member /member.#lefts /member.#right?] ) -(template [<access> <side> <name>] - [(template: .public (<name> lefts) - [(<access> lefts <side>)])] +(with_template [<access> <side> <name>] + [(def: .public <name> + (template (<name> lefts) + [(<access> lefts <side>)]))] [..side #0 side/left] [..side #1 side/right] @@ -175,17 +178,19 @@ [..member #1 member/right] ) -(template [<name> <tag>] - [(template: .public (<name> content) - [{<tag> content}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [{<tag> content}]))] [path/bind ..#Bind] [path/then ..#Then] ) -(template [<name> <tag>] - [(template: .public (<name> left right) - [{<tag> left right}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> left right) + [{<tag> left right}]))] [path/alt ..#Alt] [path/seq ..#Seq] @@ -201,7 +206,7 @@ Text "") -(template [<with> <query> <tag> <type>] +(with_template [<with> <query> <tag> <type>] [(def: .public (<with> value) (-> <type> (All (_ a) (-> (Operation a) (Operation a)))) (extension.temporary (has <tag> value))) @@ -220,9 +225,10 @@ [locals ..locals]) (..with_locals (++ locals)))) -(template [<name> <tag>] - [(template: .public (<name> content) - [{..#Simple {<tag> content}}])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [{..#Simple {<tag> content}}]))] [bit /simple.#Bit] [i64 /simple.#I64] @@ -230,21 +236,23 @@ [text /simple.#Text] ) -(template [<name> <tag>] - [(template: .public (<name> content) - [(.<| {..#Structure} - {<tag>} - content)])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Structure} + {<tag>} + content)]))] [variant analysis/complex.#Variant] [tuple analysis/complex.#Tuple] ) -(template [<name> <tag>] - [(template: .public (<name> content) - [(.<| {..#Reference} - <tag> - content)])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Reference} + <tag> + content)]))] [variable reference.variable] [constant reference.constant] @@ -252,12 +260,13 @@ [variable/foreign reference.foreign] ) -(template [<name> <family> <tag>] - [(template: .public (<name> content) - [(.<| {..#Control} - {<family>} - {<tag>} - content)])] +(with_template [<name> <family> <tag>] + [(def: .public <name> + (template (<name> content) + [(.<| {..#Control} + {<family>} + {<tag>} + content)]))] [branch/case ..#Branch ..#Case] [branch/exec ..#Branch ..#Exec] @@ -289,7 +298,7 @@ "") ")") - (^.template [<tag> <format>] + (^.with_template [<tag> <format>] [{<tag> item} (|> {.#Item item} (list#each (function (_ [test then]) @@ -422,7 +431,7 @@ (= reference_then sample_then) (at (maybe.equivalence =) = reference_else sample_else)) - (^.template [<tag> <equivalence>] + (^.with_template [<tag> <equivalence>] [[{<tag> reference_item} {<tag> sample_item}] (at (list.equivalence (product.equivalence <equivalence> =)) = @@ -432,7 +441,7 @@ [#F64_Fork f.equivalence] [#Text_Fork text.equivalence]) - (^.template [<tag> <equivalence>] + (^.with_template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (at <equivalence> = reference' sample')]) ([#Access /access.equivalence] @@ -441,7 +450,7 @@ [{#Bind reference'} {#Bind sample'}] (n.= reference' sample') - (^.template [<tag>] + (^.with_template [<tag>] [[{<tag> leftR rightR} {<tag> leftS rightS}] (and (= leftR leftS) (= rightR rightS))]) @@ -474,7 +483,7 @@ (hash then) (at (maybe.hash (path'_hash super)) hash else)) - (^.template [<factor> <tag> <hash>] + (^.with_template [<factor> <tag> <hash>] [{<tag> item} (let [case_hash (product.hash <hash> (path'_hash super)) @@ -484,7 +493,7 @@ [13 #F64_Fork f.hash] [17 #Text_Fork text.hash]) - (^.template [<factor> <tag>] + (^.with_template [<factor> <tag>] [{<tag> fork} (let [again_hash (path'_hash super) fork_hash (product.hash again_hash again_hash)] @@ -642,7 +651,7 @@ (def: (= reference sample) (case [reference sample] - (^.template [<tag> <equivalence>] + (^.with_template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (at (<equivalence> #=) = reference sample)]) ([#Branch ..branch_equivalence] @@ -660,7 +669,7 @@ (def: (hash value) (case value - (^.template [<factor> <tag> <hash>] + (^.with_template [<factor> <tag> <hash>] [{<tag> value} (n.* <factor> (at (<hash> super) hash value))]) ([2 #Branch ..branch_hash] @@ -673,7 +682,7 @@ (def: (= reference sample) (case [reference sample] - (^.template [<tag> <equivalence>] + (^.with_template [<tag> <equivalence>] [[{<tag> reference'} {<tag> sample'}] (at <equivalence> = reference' sample')]) ([#Simple /simple.equivalence] @@ -697,7 +706,7 @@ (def: (hash value) (let [again_hash [..equivalence hash]] (case value - (^.template [<tag> <hash>] + (^.with_template [<tag> <hash>] [{<tag> value} (at <hash> hash value)]) ([#Simple /simple.hash] @@ -706,17 +715,19 @@ [#Control (..control_hash again_hash)] [#Extension (extension.hash again_hash)]))))) -(template: .public (!bind_top register thenP) - [(all ..path/seq - {..#Bind register} - {..#Pop} - thenP)]) +(def: .public !bind_top + (template (!bind_top register thenP) + [(all ..path/seq + {..#Bind register} + {..#Pop} + thenP)])) -(template: .public (!multi_pop nextP) - [(all ..path/seq - {..#Pop} - {..#Pop} - nextP)]) +(def: .public !multi_pop + (template (!multi_pop nextP) + [(all ..path/seq + {..#Pop} + {..#Pop} + nextP)])) ... TODO: There are sister patterns to the simple side checks for tuples. ... These correspond to the situation where tuple members are accessed @@ -725,12 +736,13 @@ ... After re-implementing unused-variable-elimination, must add those ... pattern-optimizations again, since a lot of BINDs will become POPs ... and thus will result in useless code being generated. -(template [<name> <side>] - [(template: .public (<name> idx nextP) - [(all ..path/seq - (<side> idx) - {..#Pop} - nextP)])] +(with_template [<name> <side>] + [(def: .public <name> + (template (<name> idx nextP) + [(all ..path/seq + (<side> idx) + {..#Pop} + nextP)]))] [simple_left_side ..side/left] [simple_right_side ..side/right] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis/simple.lux index a0fdb6e67..6a6e4b3b0 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 @@ -29,7 +29,7 @@ (def: .public (format it) (%.Format Simple) (case it - (^.template [<pattern> <format>] + (^.with_template [<pattern> <format>] [{<pattern> value} (<format> value)]) ([#Bit %.bit] @@ -44,7 +44,7 @@ (def: (= reference sample) (case [reference sample] - (^.template [<tag> <eq> <format>] + (^.with_template [<tag> <eq> <format>] [[{<tag> reference'} {<tag> sample'}] (<eq> reference' sample')]) ([#Bit bit#= %.bit] @@ -64,7 +64,7 @@ (def: hash (|>> (pipe.case - (^.template [<factor> <tag> <hash>] + (^.with_template [<factor> <tag> <hash>] [{<tag> value'} (n.* <factor> (at <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 cf56ab7f3..1f12940df 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -56,7 +56,7 @@ "Old key" (signature.description (document.signature old)) "New key" (signature.description (document.signature new)))) -(template [<name>] +(with_template [<name>] [(exception: .public (<name> [it descriptor.Module]) (exception.report "Module" (%.text it)))] 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 d6dc3c74f..a3780a1b8 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 @@ -51,7 +51,7 @@ [{#Definition left} {#Definition right}] (at definition_equivalence = left right) - (^.template [<tag>] + (^.with_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 dade0e5d8..bc35ee361 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 @@ -41,7 +41,7 @@ (def: (= left right) (case [left right] - (^.template [<tag>] + (^.with_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 7206a2f6c..dc0ed11fc 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -59,7 +59,7 @@ dependencies])) abstraction)])) - (template [<tag> <create> <fetch> <type> <name> <+resolver>] + (with_template [<tag> <create> <fetch> <type> <name> <+resolver>] [(def: .public (<create> it mandatory? dependencies registry) (-> <type> Bit (Set unit.ID) Registry [ID Registry]) (let [id (..next registry)] @@ -119,7 +119,7 @@ category (is (Writer Category) (function (_ value) (case value - (^.template [<nat> <tag> <writer>] + (^.with_template [<nat> <tag> <writer>] [{<tag> value} ((binary.and binary.nat <writer>) [<nat> value])]) ([0 //category.#Anonymous binary.any] @@ -164,7 +164,7 @@ (do [! <>.monad] [tag <binary>.nat] (case tag - (^.template [<nat> <tag> <parser>] + (^.with_template [<nat> <tag> <parser>] [<nat> (at ! each (|>> {<tag>}) <parser>)]) ([0 //category.#Anonymous <binary>.any] @@ -188,7 +188,7 @@ {//category.#Anonymous} (..resource mandatory? dependencies registry) - (^.template [<tag> <create>] + (^.with_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 6e5f46df9..160c23890 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 @@ -45,7 +45,7 @@ {synthesis.#Bind _}) (list) - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> left right} (.all list#composite (again left) @@ -63,7 +63,7 @@ {.#None} (again then)) - (^.template [<tag>] + (^.with_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 d611dde33..40ae2eb84 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux @@ -70,7 +70,7 @@ {#Interpretation Interpretation} {#Export Export})) -(template [<name> <long> <type> <parser>] +(with_template [<name> <long> <type> <parser>] [(def: <name> (Parser <type>) (<cli>.named <long> <parser>))] diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux index 1d37314b6..84107e91d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux @@ -30,7 +30,7 @@ (list.equivalence text.equivalence) )) -(template [<ascii> <name>] +(with_template [<ascii> <name>] [(def: <name> Text (text.of_char (hex <ascii>)))] diff --git a/stdlib/source/library/lux/tool/compiler/meta/context.lux b/stdlib/source/library/lux/tool/compiler/meta/context.lux index b65bfc16e..cfacb3fe9 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/context.lux @@ -15,7 +15,7 @@ #target Path #artifact_extension Extension])) -(template [<name> <host> <host_module_extension> <artifact_extension>] +(with_template [<name> <host> <host_module_extension> <artifact_extension>] [(def: .public (<name> target) (-> Path Context) [#host <host> 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 ff44f3258..4935aae78 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -221,7 +221,7 @@ content (document.content $.key document) definitions (monad.each ! (function (_ [def_name def_global]) (case def_global - (^.template [<tag>] + (^.with_template [<tag>] [{<tag> payload} (in [def_name {<tag> payload}])]) ([.#Alias] diff --git a/stdlib/source/library/lux/tool/compiler/phase.lux b/stdlib/source/library/lux/tool/compiler/phase.lux index 480ad7380..48b08b54b 100644 --- a/stdlib/source/library/lux/tool/compiler/phase.lux +++ b/stdlib/source/library/lux/tool/compiler/phase.lux @@ -106,10 +106,11 @@ (function (_ state) (try#each (|>> [state]) error))) -(template: .public (assertion exception message test) - [(if test - (at ..monad in []) - (..except exception message))]) +(def: .public assertion + (template (assertion exception message test) + [(if test + (at ..monad in []) + (..except exception message))])) (def: .public identity (All (_ s a) (Phase s a a)) diff --git a/stdlib/source/library/lux/tool/compiler/reference.lux b/stdlib/source/library/lux/tool/compiler/reference.lux index c20c13688..cd028073c 100644 --- a/stdlib/source/library/lux/tool/compiler/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/reference.lux @@ -32,7 +32,7 @@ (def: (= reference sample) (case [reference sample] - (^.template [<tag> <equivalence>] + (^.with_template [<tag> <equivalence>] [[{<tag> reference} {<tag> sample}] (at <equivalence> = reference sample)]) ([#Variable /variable.equivalence] @@ -49,7 +49,7 @@ (def: (hash value) (case value - (^.template [<factor> <tag> <hash>] + (^.with_template [<factor> <tag> <hash>] [{<tag> value} (|> value (at <hash> hash) @@ -58,27 +58,30 @@ [3 #Constant symbol.hash]) ))) -(template [<name> <family> <tag>] - [(template: .public (<name> content) - [(<| {<family>} - {<tag>} - content)])] +(with_template [<name> <family> <tag>] + [(def: .public <name> + (template (<name> content) + [(<| {<family>} + {<tag>} + content)]))] [local ..#Variable /variable.#Local] [foreign ..#Variable /variable.#Foreign] ) -(template [<name> <tag>] - [(template: .public (<name> content) - [(<| {<tag>} - content)])] +(with_template [<name> <tag>] + [(def: .public <name> + (template (<name> content) + [(<| {<tag>} + content)]))] [variable ..#Variable] [constant ..#Constant] ) -(`` (template: .public self - [(..variable (~~ (/variable.self)))])) +(`` (def: .public self + (template (self) + [(..variable (~~ (/variable.self)))]))) (def: .public format (Format Reference) diff --git a/stdlib/source/library/lux/tool/compiler/reference/variable.lux b/stdlib/source/library/lux/tool/compiler/reference/variable.lux index 488901fff..ad3be0e06 100644 --- a/stdlib/source/library/lux/tool/compiler/reference/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/reference/variable.lux @@ -29,7 +29,7 @@ (def: (= reference sample) (case [reference sample] - (^.template [<tag>] + (^.with_template [<tag>] [[{<tag> reference'} {<tag> sample'}] (n.= reference' sample')]) ([#Local] [#Foreign]) @@ -45,7 +45,7 @@ (def: hash (|>> (pipe.case - (^.template [<factor> <tag>] + (^.with_template [<factor> <tag>] [{<tag> register} (|> register (at n.hash hash) @@ -53,8 +53,9 @@ ([2 #Local] [3 #Foreign]))))) -(template: .public (self) - [{..#Local 0}]) +(def: .public self + (template (self) + [{..#Local 0}])) (def: .public self? (-> Variable Bit) |