diff options
author | Eduardo Julian | 2019-03-30 21:45:45 -0400 |
---|---|---|
committer | Eduardo Julian | 2019-03-30 21:45:45 -0400 |
commit | 118895081d97279a796cc704e6c23bf92ed79e5e (patch) | |
tree | 1ea654e3f913bfc5f978bba46620c535e7a4a7bc /stdlib/source/lux/tool | |
parent | 5009bfaa56119a58e675a1e6008623790b54cc1c (diff) |
Re-named "do-template" to "template".
Diffstat (limited to '')
27 files changed, 79 insertions, 79 deletions
diff --git a/stdlib/source/lux/tool/compiler/analysis.lux b/stdlib/source/lux/tool/compiler/analysis.lux index a8ad548d9..c2a6d0cb7 100644 --- a/stdlib/source/lux/tool/compiler/analysis.lux +++ b/stdlib/source/lux/tool/compiler/analysis.lux @@ -68,14 +68,14 @@ (type: #export Match (Match' Analysis)) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (<tag> content))] [control/case #..Case] ) -(do-template [<name> <type> <tag>] +(template [<name> <type> <tag>] [(def: #export <name> (-> <type> Analysis) (|>> <tag> #..Primitive))] @@ -121,7 +121,7 @@ _ [abstraction inputs]))) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (.<| #..Reference <tag> @@ -131,7 +131,7 @@ [constant #reference.Constant] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (.<| #..Complex <tag> @@ -141,7 +141,7 @@ [pattern/tuple #..Tuple] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (.<| #..Structure <tag> @@ -154,7 +154,7 @@ (template: #export (pattern/unit) (#..Simple #..Unit)) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (#..Simple (<tag> content)))] @@ -233,7 +233,7 @@ (format (%t name) " ") (text.enclose ["(" ")"])))) -(do-template [<special> <general>] +(template [<special> <general>] [(type: #export <special> (<general> .Lux Code Analysis))] @@ -305,7 +305,7 @@ (#error.Failure (format "@ " (%cursor cursor) text.new-line error))))))) -(do-template [<name> <type> <field> <value>] +(template [<name> <type> <field> <value>] [(def: #export (<name> value) (-> <type> (Operation Any)) (extension.update (set@ <field> <value>)))] diff --git a/stdlib/source/lux/tool/compiler/default/syntax.lux b/stdlib/source/lux/tool/compiler/default/syntax.lux index 8eaf3a558..5f894622b 100644 --- a/stdlib/source/lux/tool/compiler/default/syntax.lux +++ b/stdlib/source/lux/tool/compiler/default/syntax.lux @@ -57,7 +57,7 @@ (type: Char Nat) -(do-template [<name> <extension> <diff>] +(template [<name> <extension> <diff>] [(template: (<name> value) (<extension> value <diff>))] @@ -69,7 +69,7 @@ (template: (!clip from to text) ("lux text clip" text from to)) -(do-template [<name> <extension>] +(template [<name> <extension>] [(template: (<name> reference subject) (<extension> subject reference))] @@ -77,7 +77,7 @@ [!i/< "lux int <"] ) -(do-template [<name> <extension>] +(template [<name> <extension>] [(template: (<name> param subject) (<extension> subject param))] @@ -180,7 +180,7 @@ ## else <cannot-close>)))))))) -(do-template [<name> <close> <tag> <context>] +(template [<name> <close> <tag> <context>] [(`` (def: (<name> parse source) (-> Parser Parser) (let [[_ _ source-code] source @@ -267,7 +267,7 @@ (or (!digit? char) ("lux i64 =" (.char (~~ (static ..digit-separator))) char)))) -(with-expansions [<clauses> (do-template [<char>] +(with-expansions [<clauses> (template [<char>] [("lux i64 =" (.char (~~ (static <char>))) char) #0] @@ -345,7 +345,7 @@ ## else <int-output>)))))) -(do-template [<name> <codec> <tag>] +(template [<name> <codec> <tag>] [(template: (<name> source-code//size start where offset source-code) (loop [g!end offset] (<| (!with-char+ source-code//size source-code g!end g!char (!number-output start g!end <codec> <tag>)) @@ -512,7 +512,7 @@ _ <end-of-file>) - (~~ (do-template [<char> <bit>] + (~~ (template [<char> <bit>] [[<char>] (#error.Success [[(update@ #.column (|>> !inc/2) where) (!inc offset/1) diff --git a/stdlib/source/lux/tool/compiler/host.lux b/stdlib/source/lux/tool/compiler/host.lux index 218de67a4..71158e724 100644 --- a/stdlib/source/lux/tool/compiler/host.lux +++ b/stdlib/source/lux/tool/compiler/host.lux @@ -3,7 +3,7 @@ (type: #export Host Text) -(do-template [<name> <value>] +(template [<name> <value>] [(def: #export <name> Host <value>)] [common-lisp "Common Lisp"] diff --git a/stdlib/source/lux/tool/compiler/meta/cache.lux b/stdlib/source/lux/tool/compiler/meta/cache.lux index 45b33f4f7..382ca7bfd 100644 --- a/stdlib/source/lux/tool/compiler/meta/cache.lux +++ b/stdlib/source/lux/tool/compiler/meta/cache.lux @@ -41,7 +41,7 @@ ["Expected" (//archive.describe expected)] ["Actual" (//archive.describe actual)])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {message Text}) message)] diff --git a/stdlib/source/lux/tool/compiler/meta/io/context.lux b/stdlib/source/lux/tool/compiler/meta/io/context.lux index 40dd5bd7d..c9f52cc76 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/context.lux @@ -21,7 +21,7 @@ ["#/" // (#+ Input) ["#." host]]]]) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {module Module}) (ex.report ["Module" module]))] diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux b/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux index d677d4222..57b9ed357 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/inference.lux @@ -40,7 +40,7 @@ (ex.report ["Expected" (%i (.int expected))] ["Actual" (%i (.int actual))])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {type Type}) (%type type))] diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux index 0d69f524c..db02af343 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux @@ -27,7 +27,7 @@ (ex.report ["Module" module] ["Tag" tag])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {tags (List Text)} {owner Type}) (ex.report ["Tags" (text.join-with " " tags)] ["Type" (%type owner)]))] @@ -156,7 +156,7 @@ module (///extension.lift (macro.find-module name))] (wrap [module output]))) -(do-template [<setter> <asker> <tag>] +(template [<setter> <asker> <tag>] [(def: #export (<setter> module-name) (-> Text (Operation Any)) (///extension.lift @@ -196,7 +196,7 @@ [set-cached cached? #.Cached] ) -(do-template [<name> <tag> <type>] +(template [<name> <tag> <type>] [(def: (<name> module-name) (-> Text (Operation <type>)) (///extension.lift diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux b/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux index 60e3392e6..b42065f8f 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/primitive.lux @@ -8,7 +8,7 @@ [// ["/" analysis (#+ Analysis Operation)]]]]) -(do-template [<name> <type> <tag>] +(template [<name> <type> <tag>] [(def: #export (<name> value) (-> <type> (Operation Analysis)) (do ///.monad diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux index 9033344b3..8383ae615 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux @@ -137,7 +137,7 @@ (ex.throw cannot-create-local-binding-without-a-scope [])) )) -(do-template [<name> <val-type>] +(template [<name> <val-type>] [(def: <name> (Bindings Text [Type <val-type>]) {#.counter 0 diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux index 9d78121d5..da8f0dee4 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux @@ -34,7 +34,7 @@ ["Tag" (%n tag)] ["Expression" (%code code)])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {type Type} {members (List Code)}) (ex.report ["Type" (%type type)] ["Expression" (%code (` [(~+ members)]))]))] @@ -46,7 +46,7 @@ (exception: #export (not-a-quantified-type {type Type}) (%type type)) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {type Type} {tag Tag} {code Code}) (ex.report ["Type" (%type type)] ["Tag" (%n tag)] @@ -60,7 +60,7 @@ (ex.report ["Key" (%code key)] ["Record" (%code (code.record record))])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {key Name} {record (List [Name Code])}) (ex.report ["Tag" (%code (code.tag key))] ["Record" (%code (code.record (list;map (function (_ [keyI valC]) diff --git a/stdlib/source/lux/tool/compiler/phase/extension.lux b/stdlib/source/lux/tool/compiler/phase/extension.lux index 653d3e011..7ce75f6e5 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension.lux @@ -37,7 +37,7 @@ (type: #export (Phase s i o) (//.Phase (State s i o) i o)) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {name Name}) (ex.report ["Extension" (%t name)]))] diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux index bff1d8527..18ac68d99 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/common.lux @@ -95,7 +95,7 @@ _ (////.throw ///.invalid-syntax [extension-name])))) -(do-template [<name> <type>] +(template [<name> <type>] [(def: (<name> eval) (-> Eval Handler) (function (_ extension-name analyse args) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux index 428bffd66..abace9a94 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/host.jvm.lux @@ -38,7 +38,7 @@ (import: #long java/lang/reflect/Type (getTypeName [] String)) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {jvm-type java/lang/reflect/Type}) (ex.report ["JVM Type" (java/lang/reflect/Type::getTypeName jvm-type)]))] @@ -48,7 +48,7 @@ [cannot-convert-to-a-lux-type] ) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {type Type}) (%type type))] @@ -57,7 +57,7 @@ [non-jvm-type] ) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {name Text}) name)] @@ -65,7 +65,7 @@ [non-throwable] ) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {message Text}) message)] @@ -89,7 +89,7 @@ [cannot-correspond-type-with-a-class] ) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {class Text} {method Text} {hints (List Method-Signature)}) @@ -103,7 +103,7 @@ [too-many-candidates] ) -(do-template [<name> <class>] +(template [<name> <class>] [(def: #export <name> Type (#.Primitive <class> (list)))] ## Boxes @@ -157,7 +157,7 @@ (///bundle.install "short-to-long" (//common.unary Short Long)) ))) -(do-template [<name> <prefix> <type>] +(template [<name> <prefix> <type>] [(def: <name> Bundle (<| (///bundle.prefix <prefix>) @@ -181,7 +181,7 @@ [bundle::long "long" Long] ) -(do-template [<name> <prefix> <type>] +(template [<name> <prefix> <type>] [(def: <name> Bundle (<| (///bundle.prefix <prefix>) @@ -1060,7 +1060,7 @@ (#Hint Method-Signature) #Fail) -(do-template [<name> <tag>] +(template [<name> <tag>] [(def: <name> (-> Evaluation (Maybe Method-Signature)) (|>> (case> (<tag> output) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux index 4f36ef89f..ecba5d158 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/statement.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/statement.lux @@ -214,7 +214,7 @@ _ (///.throw //.invalid-syntax [extension-name])))) -(do-template [<mame> <type> <scope>] +(template [<mame> <type> <scope>] [(def: <mame> (All [anchor expression statement] (Handler anchor expression statement)) diff --git a/stdlib/source/lux/tool/compiler/phase/generation.lux b/stdlib/source/lux/tool/compiler/phase/generation.lux index 882e1127f..f0609d666 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation.lux @@ -36,7 +36,7 @@ ["Old Host Name" old-host-name] ["New Host Name" new-host-name])) -(do-template [<name>] +(template [<name>] [(exception: #export (<name> {name Name}) (exception.report ["Output" (%name name)]))] @@ -52,7 +52,7 @@ (signature: #export (Host expression statement) (: (-> Text expression (Error Any)) evaluate!) - (: (-> Text statement (Error Nothing)) + (: (-> Text statement (Error Any)) execute!) (: (-> Name expression (Error [Text Any statement])) define!)) @@ -69,7 +69,7 @@ #counter Nat #name-cache (Dictionary Name Text)}) -(do-template [<special> <general>] +(template [<special> <general>] [(type: #export (<special> anchor expression statement) (<general> (State anchor expression statement) Synthesis expression))] @@ -116,7 +116,7 @@ (def: #export empty-buffer Buffer row.empty) -(do-template [<tag> +(template [<tag> <with-declaration> <with-type> <with-value> <set> <get> <get-type> <exception>] [(exception: #export <exception>) @@ -184,7 +184,7 @@ (-> Text (Operation anchor expression statement Text))) (:: //.monad map (|>> %n (format prefix)) ..next)) -(do-template [<name> <inputT>] +(template [<name> <inputT>] [(def: #export (<name> label code) (All [anchor expression statement] (-> Text <inputT> (Operation anchor expression statement Any))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux index 2e661dc29..9a065a73e 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux @@ -20,7 +20,7 @@ ## [Procedures] ## [[Bits]] -(do-template [<name> <op>] +(template [<name> <op>] [(def: (<name> [paramG subjectG]) (Binary Expression) (<op> subjectG (///runtime.i64//to-number paramG)))] @@ -35,7 +35,7 @@ (#static MIN_VALUE Double) (#static MAX_VALUE Double)) -(do-template [<name> <const>] +(template [<name> <const>] [(def: (<name> _) (Nullary Expression) (///primitive.f64 <const>))] @@ -64,7 +64,7 @@ (Binary Expression) (|> subjectG (_.do "concat" (list paramG)))) -(do-template [<name> <runtime>] +(template [<name> <runtime>] [(def: (<name> [subjectG paramG extraG]) (Trinary Expression) (<runtime> subjectG paramG extraG))] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux index aed6c4711..70f581d69 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux @@ -19,7 +19,7 @@ ["#/" // #_ ["#." synthesis]]]]]) -(do-template [<name> <js>] +(template [<name> <js>] [(def: (<name> _) (Nullary Expression) <js>)] [js//null _.null] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux index 0e3864bd0..8dcdb866a 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/runtime.lux @@ -23,7 +23,7 @@ ["." synthesis]]]] ) -(do-template [<name> <base>] +(template [<name> <base>] [(type: #export <name> (<base> Var Expression Statement))] @@ -320,7 +320,7 @@ (_.bit-or (up-16 x16) x00))) )))) -(do-template [<name> <op>] +(template [<name> <op>] [(runtime: (<name> subject parameter) (_.return (i64//new (<op> (_.the ..i64-high-field subject) (_.the ..i64-high-field parameter)) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux index 4cfc7a1e6..43ebd105f 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/extension/common.lux @@ -44,7 +44,7 @@ (#static MIN_VALUE Double) (#static MAX_VALUE Double)) -(do-template [<name> <const>] +(template [<name> <const>] [(def: (<name> _) (Nullary (Expression Any)) (_.float <const>))] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux index 564bbdb35..a8f601922 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/python/runtime.lux @@ -23,7 +23,7 @@ ["." synthesis]]]] ) -(do-template [<name> <base>] +(template [<name> <base>] [(type: #export <name> (<base> SVar (Expression Any) (Statement Any)))] @@ -295,7 +295,7 @@ (def: inc (|>> (_.+ (_.int +1)))) -(do-template [<name> <top-cmp>] +(template [<name> <top-cmp>] [(def: (<name> top value) (-> (Expression Any) (Expression Any) (Computation Any)) (_.and (|> value (_.>= (_.int +0))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux index 950a32e1d..0de327e23 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.jvm.lux @@ -73,7 +73,7 @@ (bundle.install "is?" (binary (product.uncurry _.eq?/2))) (bundle.install "try" (unary ///runtime.lux//try)))) -(do-template [<name> <op>] +(template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -113,7 +113,7 @@ (#static MIN_VALUE Double) (#static MAX_VALUE Double)) -(do-template [<name> <const> <encode>] +(template [<name> <const> <encode>] [(def: (<name> _) Nullary (<encode> <const>))] @@ -123,7 +123,7 @@ [frac::max (Double::MAX_VALUE) _.float] ) -(do-template [<name> <op>] +(template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (|> subjectO (<op> paramO)))] @@ -135,7 +135,7 @@ [int::% _.remainder/2] ) -(do-template [<name> <op>] +(template [<name> <op>] [(def: (<name> [subjectO paramO]) Binary (<op> paramO subjectO))] @@ -152,7 +152,7 @@ [text::< _.string<?/2] ) -(do-template [<name> <cmp>] +(template [<name> <cmp>] [(def: (<name> [subjectO paramO]) Binary (<cmp> paramO subjectO))] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux index d53a0691e..5405e4c55 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/primitive.jvm.lux @@ -3,7 +3,7 @@ [host ["_" scheme (#+ Expression)]]]) -(do-template [<name> <type> <code>] +(template [<name> <type> <code>] [(def: #export <name> (-> <type> Expression) <code>)] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux index 62245a659..d3c949df1 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/runtime.jvm.lux @@ -22,7 +22,7 @@ ["#." name] ["#." synthesis]]]]) -(do-template [<name> <base>] +(template [<name> <base>] [(type: #export <name> (<base> Var Expression Expression))] diff --git a/stdlib/source/lux/tool/compiler/reference.lux b/stdlib/source/lux/tool/compiler/reference.lux index a20691986..7022b2496 100644 --- a/stdlib/source/lux/tool/compiler/reference.lux +++ b/stdlib/source/lux/tool/compiler/reference.lux @@ -39,7 +39,7 @@ (#Foreign register) (n/* 2 register)))) -(do-template [<name> <family> <tag>] +(template [<name> <family> <tag>] [(template: #export (<name> content) (<| <family> <tag> @@ -49,7 +49,7 @@ [foreign #..Variable #..Foreign] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (<| <tag> content))] diff --git a/stdlib/source/lux/tool/compiler/statement.lux b/stdlib/source/lux/tool/compiler/statement.lux index 49fd51c7b..441b47f83 100644 --- a/stdlib/source/lux/tool/compiler/statement.lux +++ b/stdlib/source/lux/tool/compiler/statement.lux @@ -45,7 +45,7 @@ {#imports (list;compose (get@ #imports left) (get@ #imports right)) #referrals (list;compose (get@ #referrals left) (get@ #referrals right))}) -(do-template [<special> <general>] +(template [<special> <general>] [(type: #export (<special> anchor expression statement) (<general> (..State anchor expression statement) Code Requirements))] @@ -56,7 +56,7 @@ [Bundle extension.Bundle] ) -(do-template [<name> <component> <operation>] +(template [<name> <component> <operation>] [(def: #export (<name> operation) (All [anchor expression statement output] (-> (<operation> output) diff --git a/stdlib/source/lux/tool/compiler/synthesis.lux b/stdlib/source/lux/tool/compiler/synthesis.lux index 71abfee04..6b147ffae 100644 --- a/stdlib/source/lux/tool/compiler/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/synthesis.lux @@ -94,7 +94,7 @@ (#Control (Control Synthesis)) (#Extension (Extension Synthesis))) -(do-template [<special> <general>] +(template [<special> <general>] [(type: #export <special> (<general> ..State Analysis Synthesis))] @@ -112,7 +112,7 @@ Path #Pop) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (#..Test (<tag> content)))] @@ -122,7 +122,7 @@ [path/text #..Text] ) -(do-template [<name> <kind>] +(template [<name> <kind>] [(template: #export (<name> content) (.<| #..Access <kind> @@ -132,7 +132,7 @@ [path/member #..Member] ) -(do-template [<name> <kind> <side>] +(template [<name> <kind> <side>] [(template: #export (<name> content) (.<| #..Access <kind> @@ -145,7 +145,7 @@ [member/right #..Member #.Right] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (<tag> content))] @@ -153,7 +153,7 @@ [path/then #..Then] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> left right) (<tag> [left right]))] @@ -169,7 +169,7 @@ (def: #export unit Text "") -(do-template [<name> <type> <tag>] +(template [<name> <type> <tag>] [(def: #export (<name> value) (-> <type> (All [a] (-> (Operation a) (Operation a)))) (extension.temporary (set@ <tag> value)))] @@ -182,7 +182,7 @@ (All [a] (-> (Operation a) (Operation a)))) (extension.with-state {#locals arity})) -(do-template [<name> <tag> <type>] +(template [<name> <tag> <type>] [(def: #export <name> (Operation <type>) (extension.read (get@ <tag>)))] @@ -196,7 +196,7 @@ [locals ..locals]) (..with-locals (inc locals)))) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (#..Primitive (<tag> content)))] @@ -206,7 +206,7 @@ [text #..Text] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (<| #..Structure <tag> @@ -216,7 +216,7 @@ [tuple #//analysis.Tuple] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (.<| #..Reference <tag> @@ -226,7 +226,7 @@ [variable/foreign //reference.foreign] ) -(do-template [<name> <tag>] +(template [<name> <tag>] [(template: #export (<name> content) (.<| #..Reference <tag> @@ -236,7 +236,7 @@ [constant //reference.constant] ) -(do-template [<name> <family> <tag>] +(template [<name> <family> <tag>] [(template: #export (<name> content) (.<| #..Control <family> diff --git a/stdlib/source/lux/tool/interpreter/type.lux b/stdlib/source/lux/tool/interpreter/type.lux index f6a66a76a..19f94af1b 100644 --- a/stdlib/source/lux/tool/interpreter/type.lux +++ b/stdlib/source/lux/tool/interpreter/type.lux @@ -36,7 +36,7 @@ [_ (poly.exactly Any)] (wrap (function.constant "[]"))) - (~~ (do-template [<type> <formatter>] + (~~ (template [<type> <formatter>] [(do p.monad [_ (poly.sub <type>)] (wrap (|>> (:coerce <type>) <formatter>)))] @@ -51,7 +51,7 @@ (def: (special-representation representation) (-> (Poly Representation) (Poly Representation)) (`` ($_ p.either - (~~ (do-template [<type> <formatter>] + (~~ (template [<type> <formatter>] [(do p.monad [_ (poly.sub <type>)] (wrap (|>> (:coerce <type>) <formatter>)))] |