From 118895081d97279a796cc704e6c23bf92ed79e5e Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 30 Mar 2019 21:45:45 -0400 Subject: Re-named "do-template" to "template". --- stdlib/source/lux.lux | 44 ++-- stdlib/source/lux/control/concatenative.lux | 2 +- stdlib/source/lux/control/concurrency/actor.lux | 4 +- stdlib/source/lux/control/concurrency/promise.lux | 4 +- .../source/lux/control/concurrency/semaphore.lux | 2 +- stdlib/source/lux/control/interval.lux | 8 +- stdlib/source/lux/control/number.lux | 4 +- stdlib/source/lux/control/order.lux | 6 +- stdlib/source/lux/control/predicate.lux | 4 +- stdlib/source/lux/control/remember.lux | 2 +- stdlib/source/lux/data/bit.lux | 2 +- stdlib/source/lux/data/collection/array.lux | 2 +- stdlib/source/lux/data/collection/bits.lux | 4 +- stdlib/source/lux/data/collection/dictionary.lux | 2 +- .../lux/data/collection/dictionary/ordered.lux | 12 +- .../lux/data/collection/dictionary/plist.lux | 2 +- stdlib/source/lux/data/collection/list.lux | 10 +- stdlib/source/lux/data/collection/row.lux | 4 +- stdlib/source/lux/data/collection/sequence.lux | 4 +- stdlib/source/lux/data/collection/set/ordered.lux | 4 +- .../lux/data/collection/tree/rose/parser.lux | 2 +- .../lux/data/collection/tree/rose/zipper.lux | 4 +- stdlib/source/lux/data/color.lux | 8 +- stdlib/source/lux/data/color/named.lux | 284 ++++++++++----------- stdlib/source/lux/data/format/binary.lux | 8 +- stdlib/source/lux/data/format/css.lux | 2 +- stdlib/source/lux/data/format/css/property.lux | 6 +- stdlib/source/lux/data/format/css/query.lux | 8 +- stdlib/source/lux/data/format/css/selector.lux | 18 +- stdlib/source/lux/data/format/css/value.lux | 34 +-- stdlib/source/lux/data/format/html.lux | 34 +-- stdlib/source/lux/data/format/json.lux | 16 +- stdlib/source/lux/data/format/markdown.lux | 8 +- stdlib/source/lux/data/name.lux | 2 +- stdlib/source/lux/data/number.lux | 2 +- stdlib/source/lux/data/number/complex.lux | 4 +- stdlib/source/lux/data/number/frac.lux | 14 +- stdlib/source/lux/data/number/i64.lux | 8 +- stdlib/source/lux/data/number/int.lux | 4 +- stdlib/source/lux/data/number/nat.lux | 4 +- stdlib/source/lux/data/number/ratio.lux | 6 +- stdlib/source/lux/data/number/rev.lux | 4 +- stdlib/source/lux/data/product.lux | 2 +- stdlib/source/lux/data/sum.lux | 4 +- stdlib/source/lux/data/text.lux | 2 +- stdlib/source/lux/data/text/encoding.lux | 2 +- stdlib/source/lux/data/text/format.lux | 12 +- stdlib/source/lux/data/text/lexer.lux | 16 +- stdlib/source/lux/data/text/unicode.lux | 6 +- stdlib/source/lux/host.js.lux | 6 +- stdlib/source/lux/host.jvm.lux | 8 +- stdlib/source/lux/host/js.lux | 22 +- stdlib/source/lux/host/jvm/constant.lux | 8 +- stdlib/source/lux/host/jvm/constant/tag.lux | 2 +- stdlib/source/lux/host/jvm/descriptor.lux | 4 +- stdlib/source/lux/host/jvm/encoding.lux | 4 +- stdlib/source/lux/host/jvm/modifier.lux | 2 +- stdlib/source/lux/host/jvm/version.lux | 26 +- stdlib/source/lux/host/python.lux | 28 +- stdlib/source/lux/host/scheme.lux | 20 +- stdlib/source/lux/locale/language.lux | 4 +- stdlib/source/lux/locale/territory.lux | 6 +- stdlib/source/lux/macro.lux | 10 +- stdlib/source/lux/macro/code.lux | 4 +- stdlib/source/lux/macro/poly.lux | 8 +- stdlib/source/lux/macro/poly/equivalence.lux | 6 +- stdlib/source/lux/macro/poly/json.lux | 8 +- stdlib/source/lux/macro/syntax.lux | 6 +- stdlib/source/lux/macro/syntax/common/reader.lux | 2 +- stdlib/source/lux/macro/template.lux | 2 +- stdlib/source/lux/math.lux | 16 +- stdlib/source/lux/math/logic/continuous.lux | 2 +- stdlib/source/lux/math/modular.lux | 4 +- stdlib/source/lux/math/random.lux | 10 +- stdlib/source/lux/test.lux | 2 +- stdlib/source/lux/time/day.lux | 2 +- stdlib/source/lux/time/duration.lux | 12 +- stdlib/source/lux/time/instant.lux | 4 +- stdlib/source/lux/time/month.lux | 2 +- stdlib/source/lux/tool/compiler/analysis.lux | 16 +- stdlib/source/lux/tool/compiler/default/syntax.lux | 14 +- stdlib/source/lux/tool/compiler/host.lux | 2 +- stdlib/source/lux/tool/compiler/meta/cache.lux | 2 +- .../source/lux/tool/compiler/meta/io/context.lux | 2 +- .../lux/tool/compiler/phase/analysis/inference.lux | 2 +- .../lux/tool/compiler/phase/analysis/module.lux | 6 +- .../lux/tool/compiler/phase/analysis/primitive.lux | 2 +- .../lux/tool/compiler/phase/analysis/scope.lux | 2 +- .../lux/tool/compiler/phase/analysis/structure.lux | 6 +- .../source/lux/tool/compiler/phase/extension.lux | 2 +- .../compiler/phase/extension/analysis/common.lux | 2 +- .../compiler/phase/extension/analysis/host.jvm.lux | 18 +- .../tool/compiler/phase/extension/statement.lux | 2 +- .../source/lux/tool/compiler/phase/generation.lux | 10 +- .../phase/generation/js/extension/common.lux | 6 +- .../phase/generation/js/extension/host.lux | 2 +- .../tool/compiler/phase/generation/js/runtime.lux | 4 +- .../phase/generation/python/extension/common.lux | 2 +- .../compiler/phase/generation/python/runtime.lux | 4 +- .../generation/scheme/extension/common.jvm.lux | 10 +- .../phase/generation/scheme/primitive.jvm.lux | 2 +- .../phase/generation/scheme/runtime.jvm.lux | 2 +- stdlib/source/lux/tool/compiler/reference.lux | 4 +- stdlib/source/lux/tool/compiler/statement.lux | 4 +- stdlib/source/lux/tool/compiler/synthesis.lux | 26 +- stdlib/source/lux/tool/interpreter/type.lux | 4 +- stdlib/source/lux/type.lux | 8 +- stdlib/source/lux/type/abstract.lux | 2 +- stdlib/source/lux/type/check.lux | 2 +- stdlib/source/lux/type/quotient.lux | 2 +- stdlib/source/lux/type/refinement.lux | 2 +- stdlib/source/lux/type/resource.lux | 12 +- stdlib/source/lux/type/unit.lux | 6 +- stdlib/source/lux/world/binary.lux | 2 +- stdlib/source/lux/world/console.lux | 4 +- stdlib/source/lux/world/db/jdbc.jvm.lux | 4 +- stdlib/source/lux/world/db/jdbc/input.jvm.lux | 8 +- stdlib/source/lux/world/db/jdbc/output.jvm.lux | 6 +- stdlib/source/lux/world/db/sql.lux | 32 +-- stdlib/source/lux/world/file.lux | 26 +- stdlib/source/lux/world/input/keyboard.lux | 2 +- stdlib/source/lux/world/net/http/cookie.lux | 4 +- stdlib/source/lux/world/net/http/mime.lux | 2 +- stdlib/source/lux/world/net/http/response.lux | 2 +- stdlib/source/lux/world/net/http/route.lux | 4 +- stdlib/source/lux/world/net/http/status.lux | 2 +- stdlib/source/lux/world/net/http/version.lux | 2 +- stdlib/source/lux/world/net/tcp.jvm.lux | 2 +- stdlib/source/lux/world/net/udp.jvm.lux | 2 +- .../source/lux/world/output/video/resolution.lux | 2 +- stdlib/source/program/compositor/cli.lux | 2 +- stdlib/source/program/licentia/document.lux | 2 +- .../source/program/licentia/license/definition.lux | 2 +- stdlib/source/program/licentia/license/term.lux | 2 +- stdlib/source/program/licentia/output.lux | 16 +- stdlib/source/program/scriptum.lux | 4 +- stdlib/source/test/lux.lux | 12 +- .../compiler/default/phase/analysis/primitive.lux | 4 +- .../default/phase/analysis/procedure/common.lux | 2 +- .../compiler/default/phase/analysis/reference.lux | 2 +- .../compiler/default/phase/analysis/structure.lux | 2 +- .../compiler/default/phase/synthesis/primitive.lux | 2 +- stdlib/source/test/lux/control/interval.lux | 2 +- stdlib/source/test/lux/control/region.lux | 4 +- stdlib/source/test/lux/data/color.lux | 2 +- stdlib/source/test/lux/data/number/frac.lux | 4 +- stdlib/source/test/lux/data/number/int.lux | 4 +- stdlib/source/test/lux/data/number/nat.lux | 4 +- stdlib/source/test/lux/data/number/ratio.lux | 2 +- stdlib/source/test/lux/data/number/rev.lux | 4 +- stdlib/source/test/lux/host.jvm.lux | 2 +- stdlib/source/test/lux/macro/code.lux | 2 +- stdlib/source/test/lux/macro/syntax.lux | 4 +- stdlib/source/test/lux/math/logic/fuzzy.lux | 4 +- stdlib/source/test/lux/type.lux | 4 +- 155 files changed, 639 insertions(+), 643 deletions(-) (limited to 'stdlib/source') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index ebdf57efb..2c550ebd9 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -2263,11 +2263,11 @@ #1 ("lux i64 =" test subject))) -(macro:' #export (do-template tokens) +(macro:' #export (template tokens) (list [(tag$ ["lux" "doc"]) (text$ ($_ "lux text concat" "## By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary." __paragraph - "(do-template [ ]" ..new-line + "(template [ ]" ..new-line " " "[(def: #export (-> Int Int) (i/+ ))]" __paragraph " " "[inc +1]" ..new-line " " "[dec -1]"))]) @@ -2281,15 +2281,15 @@ (|> data' (join-map (compose apply (make-env bindings'))) return) - (fail "Irregular arguments tuples for do-template."))) + (fail "Irregular arguments tuples for template."))) _ - (fail "Wrong syntax for do-template")} + (fail "Wrong syntax for template")} [(monad@map maybe-monad get-short bindings) (monad@map maybe-monad tuple->list data)]) _ - (fail "Wrong syntax for do-template")} + (fail "Wrong syntax for template")} tokens)) (def:''' #export (r/= test subject) @@ -2328,7 +2328,7 @@ #1 ("lux i64 =" test subject))) -(do-template [ +(template [ <<-doc> <<=-doc> <>-doc> <>=-doc>] [(def:''' #export ( test subject) @@ -2412,7 +2412,7 @@ ("lux coerce" Int param))] ("lux i64 -" subject flat))) -(do-template [ ] +(template [ ] [(def:''' #export ( param subject) (list [(tag$ ["lux" "doc"]) (text$ )]) @@ -2426,7 +2426,7 @@ [ Rev r/- "lux i64 -" "Rev(olution) substraction."] ) -(do-template [ ] +(template [ ] [(def:''' #export ( param subject) (list [(tag$ ["lux" "doc"]) (text$ )]) @@ -2525,7 +2525,7 @@ _ ("lux i64 left-shift" (n/- trailing-zeroes 64) 1)} trailing-zeroes))))) -(do-template [ ] +(template [ ] [(def:''' #export ( left right) (list [(tag$ ["lux" "doc"]) (text$ )]) @@ -2876,7 +2876,7 @@ _ #0} xs)) -(do-template [ ] +(template [ ] [(def:''' ( xy) #Nil (All [a b] (-> (& a b) )) @@ -3569,7 +3569,7 @@ (#Some y) (#Some y)))) -(do-template [
] +(template [ ] [(macro: #export ( tokens) {#.doc } (case (list@reverse tokens) @@ -3740,7 +3740,7 @@ _ #None)) -(do-template [ ] +(template [ ] [(def: ( type) (-> Type (List Type)) (case type @@ -4046,7 +4046,7 @@ (fail "Wrong syntax for type:")) )) -(do-template [ ] +(template [ ] [(def: #export ( value) (-> (I64 Any) ) (:coerce value))] @@ -5110,7 +5110,7 @@ (macro: #export (^template tokens) {#.doc (text$ ($_ "lux text concat" - "## It's similar to do-template, but meant to be used during pattern-matching." ..new-line + "## It's similar to template, but meant to be used during pattern-matching." ..new-line "(def: (beta-reduce env type)" ..new-line " (-> (List Type) Type Type)" ..new-line " (case type" ..new-line @@ -5167,7 +5167,7 @@ _ (fail "Wrong syntax for ^template"))) -(do-template [ ] +(template [ ] [(def: #export ( n) (-> ) ( [n]))] @@ -5220,7 +5220,7 @@ (-> Text Text) ($_ text@compose ..double-quote original ..double-quote)) -(do-template [ ] +(template [ ] [(def: #export ( value) {#.doc } (All [s] (-> (I64 s) (I64 s))) @@ -5522,7 +5522,7 @@ "Wherever a binding appears, the bound codes will be spliced in there." (test: "Code operations & structures" (with-expansions - [ (do-template [ ] + [ (template [ ] [(compare ) (compare (:: Code/encode encode )) (compare #1 (:: equivalence = ))] @@ -5748,7 +5748,7 @@ _ (fail (..wrong-syntax-error ["lux" "name-of"])))) -(do-template [ <%> <=> <0> <2>] +(template [ <%> <=> <0> <2>] [(def: #export ( n) (-> Bit) (<=> <0> (<%> <2> n))) @@ -5961,7 +5961,7 @@ )) (macro: #export (template: tokens) - {#.doc (doc "Define macros in the style of do-template and ^template." + {#.doc (doc "Define macros in the style of template and ^template." "For simple macros that do not need any fancy features." (template: (square x) (i/* x x)))} @@ -6049,7 +6049,7 @@ _ (fail (..wrong-syntax-error (name-of ..for)))))) -(do-template [ ] +(template [ ] [(def: ( xy) (All [a b] (-> [a b] )) (let [[x y] xy] @@ -6200,7 +6200,7 @@ (|> raw (shift param))) raw))) -(do-template [ <%>] +(template [ <%>] [(def: #export ( param subject) (-> [ ]) [( param subject) @@ -6242,7 +6242,7 @@ (nat@encode column))] ($_ "lux text concat" "[" fields "]"))) -(do-template [ ] +(template [ ] [(def: #export #0) (def: #export #1)] diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux index caae325a2..2ec99fe8f 100644 --- a/stdlib/source/lux/control/concatenative.lux +++ b/stdlib/source/lux/control/concatenative.lux @@ -199,7 +199,7 @@ (function (_ [stack r]) [stack (1 r)])) -(do-template [ ] +(template [ ] [(def: #export (=> [ ] []) (function (_ [[stack subject] param]) diff --git a/stdlib/source/lux/control/concurrency/actor.lux b/stdlib/source/lux/control/concurrency/actor.lux index 92cf0207e..133144a83 100644 --- a/stdlib/source/lux/control/concurrency/actor.lux +++ b/stdlib/source/lux/control/concurrency/actor.lux @@ -158,7 +158,7 @@ (promise.resolved (ex.throw ..poisoned []))) actor)) -(do-template [ ] +(template [ ] [(def: #export ( name) (-> Name cs.Annotations cs.Annotations) (|>> (#.Cons [(name-of ) @@ -184,7 +184,7 @@ (p.either (s.form (p.and s.local-identifier (p.some s.local-identifier))) (p.and s.local-identifier (:: p.monad wrap (list))))) -(do-template [ ] +(template [ ] [(def: #export (-> Text Text) (|>> (format "@")))] diff --git a/stdlib/source/lux/control/concurrency/promise.lux b/stdlib/source/lux/control/concurrency/promise.lux index 72fe34bcb..fa8acc6d9 100644 --- a/stdlib/source/lux/control/concurrency/promise.lux +++ b/stdlib/source/lux/control/concurrency/promise.lux @@ -126,7 +126,7 @@ (All [a b] (-> (Promise a) (Promise b) (Promise (| a b)))) (let [[a|b resolve] (..promise [])] (with-expansions - [ (do-template [ ] + [ (template [ ] [(io.run (await (|>> resolve) ))] [left #.Left] @@ -139,7 +139,7 @@ {#.doc "Homogeneous alternative combinator."} (All [a] (-> (Promise a) (Promise a) (Promise a))) (let [[left||right resolve] (..promise [])] - (`` (exec (~~ (do-template [] + (`` (exec (~~ (template [] [(io.run (await resolve ))] [left] diff --git a/stdlib/source/lux/control/concurrency/semaphore.lux b/stdlib/source/lux/control/concurrency/semaphore.lux index ddc73b300..2bc5be651 100644 --- a/stdlib/source/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/lux/control/concurrency/semaphore.lux @@ -125,7 +125,7 @@ (recur (inc step))) (:: promise.monad wrap [])))) - (do-template [ ] + (template [ ] [(def: ( (^:representation barrier)) (-> Barrier (Promise Any)) (do promise.monad diff --git a/stdlib/source/lux/control/interval.lux b/stdlib/source/lux/control/interval.lux index 60e452c54..046f5b77d 100644 --- a/stdlib/source/lux/control/interval.lux +++ b/stdlib/source/lux/control/interval.lux @@ -28,7 +28,7 @@ (def: bottom elem) (def: top elem))) -(do-template [ ] +(template [ ] [(def: #export ( interval) (All [a] (-> (Interval a) Bit)) (let [(^open ".") interval] @@ -54,7 +54,7 @@ (and (= bottom elem) (= top elem))))) -(do-template [ ] +(template [ ] [(def: #export ( elem interval) (All [a] (-> a (Interval a) Bit)) (let [(^open ".") interval] @@ -111,7 +111,7 @@ (or (meets? reference sample) (meets? sample reference))) -(do-template [ ] +(template [ ] [(def: #export ( reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) (let [(^open ".") reference] @@ -122,7 +122,7 @@ [finishes? top >= bottom] ) -(do-template [ ] +(template [ ] [(def: #export ( reference sample) (All [a] (-> a (Interval a) Bit)) (let [(^open ".") sample] diff --git a/stdlib/source/lux/control/number.lux b/stdlib/source/lux/control/number.lux index 3fc8faabf..b3a314ba5 100644 --- a/stdlib/source/lux/control/number.lux +++ b/stdlib/source/lux/control/number.lux @@ -4,11 +4,11 @@ (`` (signature: #export (Number n) {#.doc "Everything that should be expected of a number type."} - (~~ (do-template [] + (~~ (template [] [(: (-> n n n) )] [+] [-] [*] [/] [%])) - (~~ (do-template [] + (~~ (template [] [(: (-> n n) )] [negate] [signum] [abs])) )) diff --git a/stdlib/source/lux/control/order.lux b/stdlib/source/lux/control/order.lux index a56f512cb..68573b326 100644 --- a/stdlib/source/lux/control/order.lux +++ b/stdlib/source/lux/control/order.lux @@ -12,7 +12,7 @@ (: (Equivalence a) &equivalence) - (~~ (do-template [] + (~~ (template [] [(: (-> a a Bit) )] [<] [<=] [>] [>=] @@ -37,7 +37,7 @@ (or (> test subject) (:: equivalence = test subject)))))) -(do-template [ ] +(template [ ] [(def: #export ( order x y) (All [a] (-> (Order a) a a a)) @@ -52,7 +52,7 @@ (structure (def: &equivalence (:: equivalence.contravariant map-1 f (:: order &equivalence))) - (~~ (do-template [] + (~~ (template [] [(def: ( reference sample) (:: order (f reference) (f sample)))] diff --git a/stdlib/source/lux/control/predicate.lux b/stdlib/source/lux/control/predicate.lux index 605426da4..7d6433f33 100644 --- a/stdlib/source/lux/control/predicate.lux +++ b/stdlib/source/lux/control/predicate.lux @@ -8,7 +8,7 @@ (type: #export (Predicate a) (-> a Bit)) -(do-template [ ] +(template [ ] [(def: #export (All [a] (Predicate a)) (function.constant )) @@ -23,7 +23,7 @@ [all #1 intersection and] ) -(do-template [ ] +(template [ ] [(structure: #export (All [a] (Monoid (Predicate a))) (def: identity ) (def: compose ))] diff --git a/stdlib/source/lux/control/remember.lux b/stdlib/source/lux/control/remember.lux index 22488c4e2..34bb38001 100644 --- a/stdlib/source/lux/control/remember.lux +++ b/stdlib/source/lux/control/remember.lux @@ -51,7 +51,7 @@ (list))) (macro.fail (ex.construct must-remember [message focus]))))) -(do-template [ ] +(template [ ] [(syntax: #export ( {deadline ..deadline} {message s.text} {focus (p.maybe s.any)}) (wrap (list (` (..remember (~ (code.text (date@encode deadline))) (~ (code.text (format " " message))) diff --git a/stdlib/source/lux/data/bit.lux b/stdlib/source/lux/data/bit.lux index ab8c24a8e..72cfc096e 100644 --- a/stdlib/source/lux/data/bit.lux +++ b/stdlib/source/lux/data/bit.lux @@ -20,7 +20,7 @@ #1 1 #0 0))) -(do-template [ ] +(template [ ] [(structure: #export (Monoid Bit) (def: identity ) (def: (compose x y) ( x y)))] diff --git a/stdlib/source/lux/data/collection/array.lux b/stdlib/source/lux/data/collection/array.lux index d135b06d9..55e0ceb2b 100644 --- a/stdlib/source/lux/data/collection/array.lux +++ b/stdlib/source/lux/data/collection/array.lux @@ -271,7 +271,7 @@ (recur (f value so-far) (inc idx))) so-far))))) -(do-template [ ] +(template [ ] [(def: #export ( predicate array) (All [a] (-> (Predicate a) (Array a) Bit)) diff --git a/stdlib/source/lux/data/collection/bits.lux b/stdlib/source/lux/data/collection/bits.lux index 93158c54c..95732fe15 100644 --- a/stdlib/source/lux/data/collection/bits.lux +++ b/stdlib/source/lux/data/collection/bits.lux @@ -54,7 +54,7 @@ (|> bits (array.read idx) (maybe.default empty-chunk)) empty-chunk)) -(do-template [ ] +(template [ ] [(def: #export ( index input) (-> Nat Bits Bits) (let [[chunk-index bit-index] (n//% chunk-size index)] @@ -124,7 +124,7 @@ (recur (dec size|output))) output)))))) -(do-template [ ] +(template [ ] [(def: #export ( param subject) (-> Bits Bits Bits) (case (n/max (array.size param) diff --git a/stdlib/source/lux/data/collection/dictionary.lux b/stdlib/source/lux/data/collection/dictionary.lux index 9a9663228..a9c53ea18 100644 --- a/stdlib/source/lux/data/collection/dictionary.lux +++ b/stdlib/source/lux/data/collection/dictionary.lux @@ -613,7 +613,7 @@ (new Hash) kvs)) -(do-template [ ] +(template [ ] [(def: #export ( dict) (All [k v] (-> (Dictionary k v) (List ))) (|> dict entries (list@map )))] diff --git a/stdlib/source/lux/data/collection/dictionary/ordered.lux b/stdlib/source/lux/data/collection/dictionary/ordered.lux index e2d0f21fd..5bd957364 100644 --- a/stdlib/source/lux/data/collection/dictionary/ordered.lux +++ b/stdlib/source/lux/data/collection/dictionary/ordered.lux @@ -26,7 +26,7 @@ #left (Maybe (Node k v)) #right (Maybe (Node k v))}) -(do-template [ ] +(template [ ] [(def: ( key value left right) (All [k v] (-> k v (Maybe (Node k v)) (Maybe (Node k v)) (Node k v))) {#color @@ -91,7 +91,7 @@ (recur (get@ #left node)) (recur (get@ #right node))))))))) -(do-template [ ] +(template [ ] [(def: #export ( dict) (All [k v] (-> (Dictionary k v) (Maybe v))) (case (get@ #root dict) @@ -111,7 +111,7 @@ [max #right] ) -(do-template [ ] +(template [ ] [(def: #export ( dict) (All [k v] (-> (Dictionary k v) Nat)) (loop [node (get@ #root dict)] @@ -127,7 +127,7 @@ [depth n/max] ) -(do-template [ ] +(template [ ] [(def: ( self) (All [k v] (-> (Node k v) (Node k v))) (case (get@ #color self) @@ -256,7 +256,7 @@ (#.Some root) (let [reference (get@ #key root)] - (`` (cond (~~ (do-template [ ] + (`` (cond (~~ (template [ ] [( reference key) (let [side-root (get@ root) outcome (recur side-root)] @@ -537,7 +537,7 @@ (new Order) list)) -(do-template [ ] +(template [ ] [(def: #export ( dict) (All [k v] (-> (Dictionary k v) (List ))) (loop [node (get@ #root dict)] diff --git a/stdlib/source/lux/data/collection/dictionary/plist.lux b/stdlib/source/lux/data/collection/dictionary/plist.lux index 269c8bd02..2e08d72f2 100644 --- a/stdlib/source/lux/data/collection/dictionary/plist.lux +++ b/stdlib/source/lux/data/collection/dictionary/plist.lux @@ -20,7 +20,7 @@ (#.Some v') (get key properties')))) -(do-template [ ] +(template [ ] [(def: #export (All [a] (-> (PList a) (List ))) (list;map ))] diff --git a/stdlib/source/lux/data/collection/list.lux b/stdlib/source/lux/data/collection/list.lux index 46042d1d7..b2da3337b 100644 --- a/stdlib/source/lux/data/collection/list.lux +++ b/stdlib/source/lux/data/collection/list.lux @@ -68,7 +68,7 @@ _ #.Nil)) -(do-template [ ] +(template [ ] [(def: #export ( n xs) (All [a] (-> Nat (List a) (List a))) @@ -85,7 +85,7 @@ [drop (drop (dec n) xs') xs] ) -(do-template [ ] +(template [ ] [(def: #export ( predicate xs) (All [a] (-> (Predicate a) (List a) (List a))) @@ -235,7 +235,7 @@ (All [a] (-> (List a) Nat)) (fold (function (_ _ acc) (n/+ 1 acc)) 0 list)) -(do-template [ ] +(template [ ] [(def: #export ( predicate xs) (All [a] (-> (Predicate a) (List a) Bit)) @@ -335,7 +335,7 @@ xs')] ($_ compose (sort < pre) (list x) (sort < post))))) -(do-template [ ] +(template [ ] [(def: #export ( from to) {#.doc "Generates an inclusive interval of values [from, to]."} (-> (List )) @@ -365,7 +365,7 @@ (#.Cons x' xs') (or (:: eq = x x') (member? eq xs' x)))) -(do-template [ ] +(template [ ] [(def: #export ( xs) {#.doc } (All [a] (-> (List a) (Maybe ))) diff --git a/stdlib/source/lux/data/collection/row.lux b/stdlib/source/lux/data/collection/row.lux index 16ad5b51a..d56da4b79 100644 --- a/stdlib/source/lux/data/collection/row.lux +++ b/stdlib/source/lux/data/collection/row.lux @@ -40,7 +40,7 @@ Level 0) -(do-template [ ] +(template [ ] [(def: (-> Level Level) ( branching-exponent))] @@ -428,7 +428,7 @@ (All [a] (-> (Row a) (Row a))) (|>> ..to-list list.reverse (list@fold add ..empty))) -(do-template [ ] +(template [ ] [(def: #export (All [a] (-> (Predicate a) (Row a) Bit)) diff --git a/stdlib/source/lux/data/collection/sequence.lux b/stdlib/source/lux/data/collection/sequence.lux index bff7b621e..720515c2d 100644 --- a/stdlib/source/lux/data/collection/sequence.lux +++ b/stdlib/source/lux/data/collection/sequence.lux @@ -51,7 +51,7 @@ (#.Cons x xs') (#.Some (cycle' x xs' x xs')))) -(do-template [ ] +(template [ ] [(def: #export ( s) (All [a] (-> (Sequence a) )) (let [[h t] (continuation.run s)] @@ -67,7 +67,7 @@ (nth (dec idx) t) h))) -(do-template [ ] +(template [ ] [(def: #export ( pred xs) (All [a] (-> (Sequence a) (List a))) diff --git a/stdlib/source/lux/data/collection/set/ordered.lux b/stdlib/source/lux/data/collection/set/ordered.lux index 1be73506b..4d607ce15 100644 --- a/stdlib/source/lux/data/collection/set/ordered.lux +++ b/stdlib/source/lux/data/collection/set/ordered.lux @@ -24,7 +24,7 @@ (All [a] (-> (Set a) a Bit)) (|> set :representation (/.contains? elem))) - (do-template [ ] + (template [ ] [(def: #export (All [a] (-> (Set a) (Maybe a))) (|>> :representation ))] @@ -33,7 +33,7 @@ [max /.max] ) - (do-template [ ] + (template [ ] [(def: #export (-> (Set Any) Nat) (|>> :representation ))] diff --git a/stdlib/source/lux/data/collection/tree/rose/parser.lux b/stdlib/source/lux/data/collection/tree/rose/parser.lux index ba24cd908..17cee8931 100644 --- a/stdlib/source/lux/data/collection/tree/rose/parser.lux +++ b/stdlib/source/lux/data/collection/tree/rose/parser.lux @@ -31,7 +31,7 @@ (exception: #export cannot-move-further) -(do-template [ ] +(template [ ] [(def: #export (All [t] (Parser t [])) (function (_ zipper) diff --git a/stdlib/source/lux/data/collection/tree/rose/zipper.lux b/stdlib/source/lux/data/collection/tree/rose/zipper.lux index 9472d7d26..1a8ed4d5c 100644 --- a/stdlib/source/lux/data/collection/tree/rose/zipper.lux +++ b/stdlib/source/lux/data/collection/tree/rose/zipper.lux @@ -117,7 +117,7 @@ zipper (start ancestor)))) -(do-template [ ] +(template [ ] [(def: #export ( zipper) (All [a] (-> (Zipper a) (Zipper a))) (case (get@ zipper) @@ -239,7 +239,7 @@ (set@ #lefts side) (set@ #node next))))) -(do-template [ ] +(template [ ] [(def: #export ( value zipper) (All [a] (-> a (Zipper a) (Maybe (Zipper a)))) (case (get@ #parent zipper) diff --git a/stdlib/source/lux/data/color.lux b/stdlib/source/lux/data/color.lux index 7ca1764aa..bd02c4087 100644 --- a/stdlib/source/lux/data/color.lux +++ b/stdlib/source/lux/data/color.lux @@ -254,7 +254,7 @@ #green top #blue top})) -(do-template [ ] +(template [ ] [(def: #export ( ratio color) (-> Frac Color Color) (interpolate ratio color))] @@ -271,7 +271,7 @@ #green (adjust green) #blue (adjust blue)}))) -(do-template [ ] +(template [ ] [(def: #export ( ratio color) (-> Frac Color Color) (let [[hue saturation luminance] (to-hsl color)] @@ -292,7 +292,7 @@ +0.0 luminance]))) -(do-template [ <1> <2>] +(template [ <1> <2>] [(def: #export ( color) (-> Color [Color Color Color]) (let [[hue saturation luminance] (to-hsl color)] @@ -309,7 +309,7 @@ [split-complement (|> +1.0 (f// +5.0)) (|> +3.0 (f// +5.0))] ) -(do-template [ <1> <2> <3>] +(template [ <1> <2> <3>] [(def: #export ( color) (-> Color [Color Color Color Color]) (let [[hue saturation luminance] (to-hsl color)] diff --git a/stdlib/source/lux/data/color/named.lux b/stdlib/source/lux/data/color/named.lux index 76b8545f1..09e021727 100644 --- a/stdlib/source/lux/data/color/named.lux +++ b/stdlib/source/lux/data/color/named.lux @@ -4,152 +4,152 @@ [number (#+ hex)]]] ["." // (#+ Color)]) -(do-template [ ] +(template [ ] [(def: #export Color (//.from-rgb {#//.red (hex ) #//.green (hex ) #//.blue (hex )}))] - [alice-blue "F0" "F8" "FF"] - [antique-white "FA" "EB" "D7"] - [aqua "00" "FF" "FF"] - [aquamarine "7F" "FF" "D4"] - [azure "F0" "FF" "FF"] - [beige "F5" "F5" "DC"] - [bisque "FF" "E4" "C4"] - [black "00" "00" "00"] - [blanched-almond "FF" "EB" "CD"] - [blue "00" "00" "FF"] - [blue-violet "8A" "2B" "E2"] - [brown "A5" "2A" "2A"] - [burly-wood "DE" "B8" "87"] - [cadet-blue "5F" "9E" "A0"] - [chartreuse "7F" "FF" "00"] - [chocolate "D2" "69" "1E"] - [coral "FF" "7F" "50"] - [cornflower-blue "64" "95" "ED"] - [cornsilk "FF" "F8" "DC"] - [crimson "DC" "14" "3C"] - [cyan "00" "FF" "FF"] - [dark-blue "00" "00" "8B"] - [dark-cyan "00" "8B" "8B"] - [dark-goldenrod "B8" "86" "0B"] - [dark-gray "A9" "A9" "A9"] - [dark-green "00" "64" "00"] - [dark-khaki "BD" "B7" "6B"] - [dark-magenta "8B" "00" "8B"] - [dark-olive-green "55" "6B" "2F"] - [dark-orange "FF" "8C" "00"] - [dark-orchid "99" "32" "CC"] - [dark-red "8B" "00" "00"] - [dark-salmon "E9" "96" "7A"] - [dark-sea-green "8F" "BC" "8F"] - [dark-slate-blue "48" "3D" "8B"] - [dark-slate-gray "2F" "4F" "4F"] - [dark-turquoise "00" "CE" "D1"] - [dark-violet "94" "00" "D3"] - [deep-pink "FF" "14" "93"] - [deep-sky-blue "00" "BF" "FF"] - [dim-gray "69" "69" "69"] - [dodger-blue "1E" "90" "FF"] - [fire-brick "B2" "22" "22"] - [floral-white "FF" "FA" "F0"] - [forest-green "22" "8B" "22"] - [fuchsia "FF" "00" "FF"] - [gainsboro "DC" "DC" "DC"] - [ghost-white "F8" "F8" "FF"] - [gold "FF" "D7" "00"] - [goldenrod "DA" "A5" "20"] - [gray "80" "80" "80"] - [green "00" "80" "00"] - [green-yellow "AD" "FF" "2F"] - [honey-dew "F0" "FF" "F0"] - [hot-pink "FF" "69" "B4"] - [indian-red "CD" "5C" "5C"] - [indigo "4B" "00" "82"] - [ivory "FF" "FF" "F0"] - [khaki "F0" "E6" "8C"] - [lavender "E6" "E6" "FA"] - [lavender-blush "FF" "F0" "F5"] - [lawn-green "7C" "FC" "00"] - [lemon-chiffon "FF" "FA" "CD"] - [light-blue "AD" "D8" "E6"] - [light-coral "F0" "80" "80"] - [light-cyan "E0" "FF" "FF"] - [light-goldenrod-yellow "FA" "FA" "D2"] - [light-gray "D3" "D3" "D3"] - [light-green "90" "EE" "90"] - [light-pink "FF" "B6" "C1"] - [light-salmon "FF" "A0" "7A"] - [light-sea-green "20" "B2" "AA"] - [light-sky-blue "87" "CE" "FA"] - [light-slate-gray "77" "88" "99"] - [light-steel-blue "B0" "C4" "DE"] - [light-yellow "FF" "FF" "E0"] - [lime "00" "FF" "00"] - [lime-green "32" "CD" "32"] - [linen "FA" "F0" "E6"] - [magenta "FF" "00" "FF"] - [maroon "80" "00" "00"] - [medium-aquamarine "66" "CD" "AA"] - [medium-blue "00" "00" "CD"] - [medium-orchid "BA" "55" "D3"] - [medium-purple "93" "70" "DB"] - [medium-sea-green "3C" "B3" "71"] - [medium-slate-blue "7B" "68" "EE"] - [medium-spring-green "00" "FA" "9A"] - [medium-turquoise "48" "D1" "CC"] - [medium-violet-red "C7" "15" "85"] - [midnight-blue "19" "19" "70"] - [mint-cream "F5" "FF" "FA"] - [misty-rose "FF" "E4" "E1"] - [moccasin "FF" "E4" "B5"] - [navajo-white "FF" "DE" "AD"] - [navy "00" "00" "80"] - [old-lace "FD" "F5" "E6"] - [olive "80" "80" "00"] - [olive-drab "6B" "8E" "23"] - [orange "FF" "A5" "00"] - [orange-red "FF" "45" "00"] - [orchid "DA" "70" "D6"] - [pale-goldenrod "EE" "E8" "AA"] - [pale-green "98" "FB" "98"] - [pale-turquoise "AF" "EE" "EE"] - [pale-violet-red "DB" "70" "93"] - [papaya-whip "FF" "EF" "D5"] - [peach-puff "FF" "DA" "B9"] - [peru "CD" "85" "3F"] - [pink "FF" "C0" "CB"] - [plum "DD" "A0" "DD"] - [powder-blue "B0" "E0" "E6"] - [purple "80" "00" "80"] - [rebecca-purple "66" "33" "99"] - [red "FF" "00" "00"] - [rosy-brown "BC" "8F" "8F"] - [royal-blue "41" "69" "E1"] - [saddle-brown "8B" "45" "13"] - [salmon "FA" "80" "72"] - [sandy-brown "F4" "A4" "60"] - [sea-green "2E" "8B" "57"] - [sea-shell "FF" "F5" "EE"] - [sienna "A0" "52" "2D"] - [silver "C0" "C0" "C0"] - [sky-blue "87" "CE" "EB"] - [slate-blue "6A" "5A" "CD"] - [slate-gray "70" "80" "90"] - [snow "FF" "FA" "FA"] - [spring-green "00" "FF" "7F"] - [steel-blue "46" "82" "B4"] - [tan "D2" "B4" "8C"] - [teal "00" "80" "80"] - [thistle "D8" "BF" "D8"] - [tomato "FF" "63" "47"] - [turquoise "40" "E0" "D0"] - [violet "EE" "82" "EE"] - [wheat "F5" "DE" "B3"] - [white "FF" "FF" "FF"] - [white-smoke "F5" "F5" "F5"] - [yellow "FF" "FF" "00"] - [yellow-green "9A" "CD" "32"] + ["F0" "F8" "FF" alice-blue] + ["FA" "EB" "D7" antique-white] + ["00" "FF" "FF" aqua] + ["7F" "FF" "D4" aquamarine] + ["F0" "FF" "FF" azure] + ["F5" "F5" "DC" beige] + ["FF" "E4" "C4" bisque] + ["00" "00" "00" black] + ["FF" "EB" "CD" blanched-almond] + ["00" "00" "FF" blue] + ["8A" "2B" "E2" blue-violet] + ["A5" "2A" "2A" brown] + ["DE" "B8" "87" burly-wood] + ["5F" "9E" "A0" cadet-blue] + ["7F" "FF" "00" chartreuse] + ["D2" "69" "1E" chocolate] + ["FF" "7F" "50" coral] + ["64" "95" "ED" cornflower-blue] + ["FF" "F8" "DC" cornsilk] + ["DC" "14" "3C" crimson] + ["00" "FF" "FF" cyan] + ["00" "00" "8B" dark-blue] + ["00" "8B" "8B" dark-cyan] + ["B8" "86" "0B" dark-goldenrod] + ["A9" "A9" "A9" dark-gray] + ["00" "64" "00" dark-green] + ["BD" "B7" "6B" dark-khaki] + ["8B" "00" "8B" dark-magenta] + ["55" "6B" "2F" dark-olive-green] + ["FF" "8C" "00" dark-orange] + ["99" "32" "CC" dark-orchid] + ["8B" "00" "00" dark-red] + ["E9" "96" "7A" dark-salmon] + ["8F" "BC" "8F" dark-sea-green] + ["48" "3D" "8B" dark-slate-blue] + ["2F" "4F" "4F" dark-slate-gray] + ["00" "CE" "D1" dark-turquoise] + ["94" "00" "D3" dark-violet] + ["FF" "14" "93" deep-pink] + ["00" "BF" "FF" deep-sky-blue] + ["69" "69" "69" dim-gray] + ["1E" "90" "FF" dodger-blue] + ["B2" "22" "22" fire-brick] + ["FF" "FA" "F0" floral-white] + ["22" "8B" "22" forest-green] + ["FF" "00" "FF" fuchsia] + ["DC" "DC" "DC" gainsboro] + ["F8" "F8" "FF" ghost-white] + ["FF" "D7" "00" gold] + ["DA" "A5" "20" goldenrod] + ["80" "80" "80" gray] + ["00" "80" "00" green] + ["AD" "FF" "2F" green-yellow] + ["F0" "FF" "F0" honey-dew] + ["FF" "69" "B4" hot-pink] + ["CD" "5C" "5C" indian-red] + ["4B" "00" "82" indigo] + ["FF" "FF" "F0" ivory] + ["F0" "E6" "8C" khaki] + ["E6" "E6" "FA" lavender] + ["FF" "F0" "F5" lavender-blush] + ["7C" "FC" "00" lawn-green] + ["FF" "FA" "CD" lemon-chiffon] + ["AD" "D8" "E6" light-blue] + ["F0" "80" "80" light-coral] + ["E0" "FF" "FF" light-cyan] + ["FA" "FA" "D2" light-goldenrod-yellow] + ["D3" "D3" "D3" light-gray] + ["90" "EE" "90" light-green] + ["FF" "B6" "C1" light-pink] + ["FF" "A0" "7A" light-salmon] + ["20" "B2" "AA" light-sea-green] + ["87" "CE" "FA" light-sky-blue] + ["77" "88" "99" light-slate-gray] + ["B0" "C4" "DE" light-steel-blue] + ["FF" "FF" "E0" light-yellow] + ["00" "FF" "00" lime] + ["32" "CD" "32" lime-green] + ["FA" "F0" "E6" linen] + ["FF" "00" "FF" magenta] + ["80" "00" "00" maroon] + ["66" "CD" "AA" medium-aquamarine] + ["00" "00" "CD" medium-blue] + ["BA" "55" "D3" medium-orchid] + ["93" "70" "DB" medium-purple] + ["3C" "B3" "71" medium-sea-green] + ["7B" "68" "EE" medium-slate-blue] + ["00" "FA" "9A" medium-spring-green] + ["48" "D1" "CC" medium-turquoise] + ["C7" "15" "85" medium-violet-red] + ["19" "19" "70" midnight-blue] + ["F5" "FF" "FA" mint-cream] + ["FF" "E4" "E1" misty-rose] + ["FF" "E4" "B5" moccasin] + ["FF" "DE" "AD" navajo-white] + ["00" "00" "80" navy] + ["FD" "F5" "E6" old-lace] + ["80" "80" "00" olive] + ["6B" "8E" "23" olive-drab] + ["FF" "A5" "00" orange] + ["FF" "45" "00" orange-red] + ["DA" "70" "D6" orchid] + ["EE" "E8" "AA" pale-goldenrod] + ["98" "FB" "98" pale-green] + ["AF" "EE" "EE" pale-turquoise] + ["DB" "70" "93" pale-violet-red] + ["FF" "EF" "D5" papaya-whip] + ["FF" "DA" "B9" peach-puff] + ["CD" "85" "3F" peru] + ["FF" "C0" "CB" pink] + ["DD" "A0" "DD" plum] + ["B0" "E0" "E6" powder-blue] + ["80" "00" "80" purple] + ["66" "33" "99" rebecca-purple] + ["FF" "00" "00" red] + ["BC" "8F" "8F" rosy-brown] + ["41" "69" "E1" royal-blue] + ["8B" "45" "13" saddle-brown] + ["FA" "80" "72" salmon] + ["F4" "A4" "60" sandy-brown] + ["2E" "8B" "57" sea-green] + ["FF" "F5" "EE" sea-shell] + ["A0" "52" "2D" sienna] + ["C0" "C0" "C0" silver] + ["87" "CE" "EB" sky-blue] + ["6A" "5A" "CD" slate-blue] + ["70" "80" "90" slate-gray] + ["FF" "FA" "FA" snow] + ["00" "FF" "7F" spring-green] + ["46" "82" "B4" steel-blue] + ["D2" "B4" "8C" tan] + ["00" "80" "80" teal] + ["D8" "BF" "D8" thistle] + ["FF" "63" "47" tomato] + ["40" "E0" "D0" turquoise] + ["EE" "82" "EE" violet] + ["F5" "DE" "B3" wheat] + ["FF" "FF" "FF" white] + ["F5" "F5" "F5" white-smoke] + ["FF" "FF" "00" yellow] + ["9A" "CD" "32" yellow-green] ) diff --git a/stdlib/source/lux/data/format/binary.lux b/stdlib/source/lux/data/format/binary.lux index be2e105ee..b794fe029 100644 --- a/stdlib/source/lux/data/format/binary.lux +++ b/stdlib/source/lux/data/format/binary.lux @@ -99,7 +99,7 @@ (let [[valueS valueT] ((get@ #writer format) value)] (|> valueS binary.create (valueT 0)))) -(do-template [ ] +(template [ ] [(def: #export (Format (I64 Any)) {#reader (function (_ [offset binary]) @@ -215,7 +215,7 @@ {#reader (:: parser.monad map frac.bits-to-frac reader) #writer (|>> frac.frac-to-bits writer)})) -(do-template [ ] +(template [ ] [(def: #export (Format Binary) (let [mask (..mask )] @@ -243,7 +243,7 @@ [binary/64 ..bits/64 ..size/64 binary.write/64] ) -(do-template [ ] +(template [ ] [(def: #export (Format Text) (let [(^open "binary/.") ] @@ -260,7 +260,7 @@ (def: #export text ..utf8/64) -(do-template [ ] +(template [ ] [(def: #export ( extra-count valueF) (All [v] (-> Nat (Format v) (Format (Row v)))) {#reader (do parser.monad diff --git a/stdlib/source/lux/data/format/css.lux b/stdlib/source/lux/data/format/css.lux index 736a5e6f3..2bee92189 100644 --- a/stdlib/source/lux/data/format/css.lux +++ b/stdlib/source/lux/data/format/css.lux @@ -116,7 +116,7 @@ (!compose (..rule selector style) (..alter combinator selector inner))) - (do-template [ ] + (template [ ] [(def: #export (-> (Selector Any) Style (CSS Common) (CSS Common)) (..dependent ))] diff --git a/stdlib/source/lux/data/format/css/property.lux b/stdlib/source/lux/data/format/css/property.lux index b9e178ede..214a2f3c7 100644 --- a/stdlib/source/lux/data/format/css/property.lux +++ b/stdlib/source/lux/data/format/css/property.lux @@ -60,8 +60,8 @@ (-> (Property Any) Text) (|>> :representation)) - (do-template [ + +] - [(`` (do-template [ ] + (template [ + +] + [(`` (template [ ] [(def: #export (Property ) (:abstraction ))] @@ -69,7 +69,7 @@ (~~ (template.splice +)))) (with-expansions [ (template.splice +)] - (do-template [] + (template [] [(`` (def: #export (~~ (text-identifier )) (Property ) (:abstraction )))] diff --git a/stdlib/source/lux/data/format/css/query.lux b/stdlib/source/lux/data/format/css/query.lux index 1fb1b74bb..92dea7d19 100644 --- a/stdlib/source/lux/data/format/css/query.lux +++ b/stdlib/source/lux/data/format/css/query.lux @@ -29,7 +29,7 @@ (-> Media Text) (|>> :representation)) - (do-template [] + (template [] [(`` (def: #export (~~ (text-identifier )) Media (:abstraction )))] @@ -49,7 +49,7 @@ (-> Feature Text) (|>> :representation)) - (do-template [ ] + (template [ ] [(`` (def: #export ((~~ (text-identifier )) input) (-> (Value ) Feature) (:abstraction (format "(" ": " (//value.value input) ")"))))] @@ -111,7 +111,7 @@ (-> Query Text) (|>> :representation)) - (do-template [ ] + (template [ ] [(def: #export (-> Media Query) (|>> ..media (format ) :abstraction))] @@ -124,7 +124,7 @@ (-> Feature Query) (|>> ..feature (format "not ") :abstraction)) - (do-template [ ] + (template [ ] [(def: #export ( left right) (-> Query Query Query) (:abstraction (format (:representation left) diff --git a/stdlib/source/lux/data/format/css/selector.lux b/stdlib/source/lux/data/format/css/selector.lux index 7b80e4973..3c01a76a3 100644 --- a/stdlib/source/lux/data/format/css/selector.lux +++ b/stdlib/source/lux/data/format/css/selector.lux @@ -18,7 +18,7 @@ (abstract: #export (Generic brand) {} Any) -(do-template [ ] +(template [ ] [(abstract: {} Any) (type: #export (Generic ))] @@ -47,7 +47,7 @@ (-> Tag (Selector Cannot-Chain)) (|>> :abstraction)) - (do-template [ ] + (template [ ] [(def: #export (-> (Selector )) (|>> (format ) :abstraction))] @@ -56,8 +56,8 @@ [class Class "." Can-Chain] ) - (do-template [ +] - [(`` (do-template [ ] + (template [ +] + [(`` (template [ ] [(def: #export ( right left) (-> (Selector ) (Selector ) (Selector )) (:abstraction (format (:representation left) @@ -87,7 +87,7 @@ (-> Attribute (Selector Can-Chain)) (:abstraction (format "[" attribute "]"))) - (do-template [ ] + (template [ ] [(def: #export ( attribute value) (-> Attribute Text (Selector Can-Chain)) (:abstraction (format "[" attribute value "]")))] @@ -100,8 +100,8 @@ ["*=" contains?] ) - (do-template [ +] - [(`` (do-template [ ] + (template [ +] + [(`` (template [ ] [(def: #export (Selector Can-Chain) (:abstraction ))] @@ -170,7 +170,7 @@ (-> Nat Index) (|>> %n :abstraction)) - (do-template [ ] + (template [ ] [(def: #export Index (:abstraction ))] [odd "odd"] @@ -189,7 +189,7 @@ (%n (.nat variable))) (%i constant))))) - (do-template [ ] + (template [ ] [(def: #export ( index) (-> Index (Selector Can-Chain)) (|> (:representation index) diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux index 8967ed90a..1dae87811 100644 --- a/stdlib/source/lux/data/format/css/value.lux +++ b/stdlib/source/lux/data/format/css/value.lux @@ -34,7 +34,7 @@ (-> ) (|>> :representation)) - (`` (do-template [ ] + (`` (template [ ] [(def: #export (:abstraction ))] (~~ (template.splice +)) @@ -65,7 +65,7 @@ (-> (Value Any) Text) (|>> :representation)) - (do-template [ ] + (template [ ] [(def: #export Value (:abstraction ))] [initial "initial"] @@ -73,10 +73,10 @@ [unset "unset"] ) - (do-template [ + +] + (template [ + +] [(abstract: #export {} Any) - (`` (do-template [ ] + (`` (template [ ] [(def: #export (Value ) (:abstraction ))] @@ -84,7 +84,7 @@ (~~ (template.splice +)))) (with-expansions [ (template.splice +)] - (do-template [] + (template [] [(`` (def: #export (~~ (text-identifier )) (Value ) (:abstraction )))] @@ -800,7 +800,7 @@ (list;map %number) (..apply "cubic-bezier"))) - (do-template [ ] + (template [ ] [(def: #export (-> Nat (Value )) (|>> %n :abstraction))] @@ -833,7 +833,7 @@ "1.0" (format "0" (%r alpha))))))) - (do-template [ ] + (template [ ] [(def: #export ( value) (-> Frac (Value Length)) (:abstraction (format (%number value) )))] @@ -862,7 +862,7 @@ (%i value) (%n (.nat value)))) - (do-template [ ] + (template [ ] [(def: #export ( value) (-> Int (Value Time)) (:abstraction (format (if (i/< +0 value) @@ -948,7 +948,7 @@ (-> Nat Angle) (:abstraction (format (%n (n/% ..degree-limit value)) "deg"))) - (do-template [ ] + (template [ ] [(def: #export Angle (..degree ))] [000 to-top] @@ -957,7 +957,7 @@ [270 to-left] ) - (do-template [ ] + (template [ ] [(def: #export ( angle start next) (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) (let [[now after] next] @@ -994,8 +994,8 @@ (:abstraction Value (format (:representation horizontal) ..slice-separator (:representation vertical)))) - (do-template [
 +]
-      [(`` (do-template [ ]
+    (template [ 
 +]
+      [(`` (template [ ]
              [(def: #export 
                 (->  (Value Filter))
                 (|>> 
 (list) (..apply )))]
@@ -1039,7 +1039,7 @@
 
   (def: length-separator " ")
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( horizontal vertical)
        (-> (Value Length) (Value Length) (Value ))
        (:abstraction (format (:representation horizontal)
@@ -1074,7 +1074,7 @@
      [farthest-corner "farthest-corner"]]
     [])
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( shape extent location start next)
        (-> Shape (Maybe Extent) (Value Location)
            Stop (List/1 [(Maybe Hint) Stop])
@@ -1121,7 +1121,7 @@
 
   (def: #export (clip rectangle)
     (-> Rectangle (Value Clip))
-    (`` (..apply "rect" (list (~~ (do-template []
+    (`` (..apply "rect" (list (~~ (template []
                                     [(:representation (get@  rectangle))]
 
                                     [#top] [#right] [#bottom] [#left]))))))
@@ -1261,7 +1261,7 @@
         (list;map %number)
         (..apply "matrix3d")))
 
-  (do-template [   ]
+  (template [   ]
     [(`` (def: #export ( [(~~ (template.splice ))])
            (-> [(~~ (template.splice ))] (Value Transform))
            (|> (list (~~ (template.splice )))
@@ -1283,7 +1283,7 @@
     [perspective "perspective" [Frac] [value]]
     )
 
-  (do-template [   ]
+  (template [   ]
     [(`` (def: #export ( [(~~ (template.splice ))])
            (-> [(~~ (template.splice ))] (Value Transform))
            (|> (list (~~ (template.splice )))
diff --git a/stdlib/source/lux/data/format/html.lux b/stdlib/source/lux/data/format/html.lux
index 206485991..01b7d9df1 100644
--- a/stdlib/source/lux/data/format/html.lux
+++ b/stdlib/source/lux/data/format/html.lux
@@ -80,7 +80,7 @@
   
   Text
 
-  (do-template [ ]
+  (template [ ]
     [(abstract: #export  {} Any)
      (type: #export  (HTML ))]
 
@@ -98,11 +98,11 @@
     [Document Document']
     )
 
-  (do-template [  +]
+  (template [  +]
     [(abstract: #export ( brand) {} Any)
      (type: #export  (HTML ( Any)))
 
-     (`` (do-template [ ]
+     (`` (template [ ]
            [(abstract: #export  {} Any)
             (type: #export  (HTML ( )))]
 
@@ -157,7 +157,7 @@
              content
              (..close tag))))
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export 
        (-> Attributes )
        (..simple ))]
@@ -197,7 +197,7 @@
     (|>> ..sanitize
          :abstraction))
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export 
        Element
        (..simple  (list)))
@@ -264,7 +264,7 @@
     (#Circle Circle)
     (#Polygon Polygon))
 
-  (do-template [   ]
+  (template [   ]
     [(def: ( attributes shape)
        (-> Attributes  (HTML Any))
        (..simple "area" (list& ["shape" ]
@@ -300,7 +300,7 @@
           (..tag "map" attributes
                  (list@fold (function.flip ..and) head tail)))))
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export 
        (-> Attributes )
        (..empty ))]
@@ -312,7 +312,7 @@
     [track "track" Track]
     )
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( attributes media on-unsupported)
        (-> Attributes Media (Maybe Content) Element)
        (..tag  attributes
@@ -336,7 +336,7 @@
     (-> ID Input)
     (|>> ["for"] list (..empty "label")))
 
-  (do-template [   ]
+  (template [   ]
     [(def: #export ( description attributes content)
        (-> (Maybe Content) Attributes  )
        (..tag  attributes
@@ -354,7 +354,7 @@
     [figure "figure" "figcaption" Element]
     )
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export ( attributes content)
        (-> Attributes (Maybe Content) )
        (|> content
@@ -367,7 +367,7 @@
 
   (type: #export Phrase (-> Attributes Content Element))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        Phrase
        (..tag ))]
@@ -423,7 +423,7 @@
 
   (type: #export Composite (-> Attributes Element Element))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        Composite
        (..tag ))]
@@ -441,7 +441,7 @@
     [span "span"]
     )
 
-  (do-template [  ]
+  (template [  ]
     [(def: 
        (->  (HTML Any))
        (..tag  (list)))]
@@ -466,7 +466,7 @@
 
   (def: #export p ..paragraph)
 
-  (do-template [   ]
+  (template [   ]
     [(def: #export 
        (-> Attributes  )
        (..tag ))]
@@ -485,7 +485,7 @@
     [object "object" Parameter Element]
     )
 
-  (do-template [   ]
+  (template [   ]
     [(def: #export 
        (->  )
        (..tag  (list)))]
@@ -499,7 +499,7 @@
     [body "body" Element Body]
     )
 
-  (do-template [   ]
+  (template [   ]
     [(def: 
        (->  )
        (..tag  (list)))]
@@ -546,7 +546,7 @@
       (..tag "table" attributes
              content)))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        (-> Head Body Document)
        (let [doc-type ]
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux
index 64064fb1f..b03cb5ae9 100644
--- a/stdlib/source/lux/data/format/json.lux
+++ b/stdlib/source/lux/data/format/json.lux
@@ -26,7 +26,7 @@
     ["s" syntax (#+ syntax:)]
     ["." code]]])
 
-(do-template [ ]
+(template [ ]
   [(type: #export  )]
 
   [Null    Any]
@@ -43,7 +43,7 @@
   (#Array   (Row JSON))
   (#Object  (Dictionary String JSON)))
 
-(do-template [ ]
+(template [ ]
   [(type: #export  )]
 
   [Array   (Row JSON)]
@@ -130,7 +130,7 @@
     _
     (#error.Failure ($_ text@compose "Cannot set field '" key "' of a non-object."))))
 
-(do-template [   ]
+(template [   ]
   [(def: #export ( key json)
      {#.doc (code.text ($_ text@compose "A JSON object field getter for "  "."))}
      (-> Text JSON (Error ))
@@ -211,7 +211,7 @@
 
 (def: (show-null _) (-> Null Text) "null")
 
-(do-template [  ]
+(template [  ]
   [(def:  (->  Text) )]
 
   [show-boolean Boolean ..encode-boolean]
@@ -290,7 +290,7 @@
         (#.Cons head tail)
         (#error.Success [tail head]))))
 
-(do-template [   ]
+(template [   ]
   [(def: #export 
      {#.doc (code.text ($_ text@compose "Reads a JSON value as "  "."))}
      (Reader )
@@ -309,7 +309,7 @@
   [string  Text #String  "string"]
   )
 
-(do-template [      ]
+(template [      ]
   [(def: #export ( test)
      {#.doc (code.text ($_ text@compose "Asks whether a JSON value is a "  "."))}
      (->  (Reader Bit))
@@ -448,7 +448,7 @@
     [_ (l.this "null")]
     (wrap [])))
 
-(do-template [  ]
+(template [  ]
   [(def: 
      (l.Lexer Boolean)
      (do p.monad
@@ -527,7 +527,7 @@
      value (json~ [])]
     (wrap [key value])))
 
-(do-template [     ]
+(template [     ]
   [(def: ( json~)
      (-> (-> Any (l.Lexer JSON)) (l.Lexer ))
      (do p.monad
diff --git a/stdlib/source/lux/data/format/markdown.lux b/stdlib/source/lux/data/format/markdown.lux
index 81c7118e7..b5dcbc46f 100644
--- a/stdlib/source/lux/data/format/markdown.lux
+++ b/stdlib/source/lux/data/format/markdown.lux
@@ -48,7 +48,7 @@
 
   (def: blank-line (format text.new-line text.new-line))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( content)
        (-> Text Markdown)
        (:abstraction (format  " " (..sanitize content) ..blank-line)))]
@@ -73,7 +73,7 @@
     (Markdown Span)
     (:abstraction (format "  " text.new-line)))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        (-> (Markdown Span) (Markdown Span))
        (|>> :representation
@@ -158,7 +158,7 @@
 
   (type: #export Email Text)
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        (->  (Markdown Span))
        (|>> (text.enclose ["<" ">"]) :abstraction))]
@@ -167,7 +167,7 @@
     [email Email]
     )
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export ( pre post)
        (-> (Markdown ) (Markdown ) (Markdown ))
        (:abstraction (format (:representation pre)  (:representation post))))]
diff --git a/stdlib/source/lux/data/name.lux b/stdlib/source/lux/data/name.lux
index 0c658678b..286071169 100644
--- a/stdlib/source/lux/data/name.lux
+++ b/stdlib/source/lux/data/name.lux
@@ -12,7 +12,7 @@
 ##   [Text Text])
 
 ## [Functions]
-(do-template [ ]
+(template [ ]
   [(def: #export ( [module short])
      (-> Name Text)
      )]
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index eb3946fab..b4408518e 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -40,7 +40,7 @@
   (-> Text Text)
   (text.replace-all "," ""))
 
-(do-template [      ]
+(template [      ]
   [(macro: #export ( tokens state)
      {#.doc }
      (case tokens
diff --git a/stdlib/source/lux/data/number/complex.lux b/stdlib/source/lux/data/number/complex.lux
index d8c365bd5..d8334d104 100644
--- a/stdlib/source/lux/data/number/complex.lux
+++ b/stdlib/source/lux/data/number/complex.lux
@@ -48,7 +48,7 @@
        (f/= (get@ #imaginary param)
             (get@ #imaginary input))))
 
-(do-template [ ]
+(template [ ]
   [(def: #export ( param input)
      (-> Complex Complex Complex)
      {#real ( (get@ #real param)
@@ -220,7 +220,7 @@
     {#real (|> subject ..abs (get@ #real) math.log)
      #imaginary (math.atan2 real imaginary)}))
 
-(do-template [  ]
+(template [  ]
   [(def: #export ( param input)
      (->  Complex Complex)
      (|> input log ( param) exp))]
diff --git a/stdlib/source/lux/data/number/frac.lux b/stdlib/source/lux/data/number/frac.lux
index 02f7b4d88..924831dcf 100644
--- a/stdlib/source/lux/data/number/frac.lux
+++ b/stdlib/source/lux/data/number/frac.lux
@@ -45,7 +45,7 @@
           +1.0))
   )
 
-(do-template [  ]
+(template [  ]
   [(structure: #export  (Monoid Frac)
      (def: identity )
      (def: compose ))]
@@ -56,7 +56,7 @@
   [minimum        f/min ("lux frac max")]
   )
 
-(do-template [  ]
+(template [  ]
   [(def: #export 
      {#.doc }
      Frac
@@ -92,7 +92,7 @@
       #.None
       (#error.Failure "Could not decode Frac"))))
 
-(do-template [    ]
+(template [    ]
   [(structure: #export  (Codec Text Frac)
      (def: (encode value)
        (let [whole (frac-to-int value)
@@ -248,7 +248,7 @@
     (#.Cons x xs')
     ("lux text concat" x (re-join-chunks xs'))))
 
-(do-template [    ]
+(template [    ]
   [(def: ( on-left? input)
      (-> Bit Text Text)
      (let [max-num-chars (n//  64)
@@ -281,7 +281,7 @@
   [binary-to-octal bin-segment-to-octal octal-to-binary octal-segment-to-bin 3]
   )
 
-(do-template [   ]
+(template [   ]
   [(structure: #export  (Codec Text Frac)
      (def: (encode value)
        (let [sign (:: ..number signum value)
@@ -336,7 +336,7 @@
 (def: mantissa-size Nat 52)
 (def: exponent-size Nat 11)
 
-(do-template [ ]
+(template [ ]
   [(def:  (|>  (:: //nat.hex decode) error.assume .i64))]
 
   ["7FF7FFFFFFFFFFFF" not-a-number-bits]
@@ -385,7 +385,7 @@
                    (//i64.clear mantissa-size mantissa-bits)))
              )))
 
-(do-template [   ]
+(template [   ]
   [(def:  (|> 1 (//i64.left-shift ) dec (//i64.left-shift )))
    (def: ( input)
      (-> (I64 Any) I64)
diff --git a/stdlib/source/lux/data/number/i64.lux b/stdlib/source/lux/data/number/i64.lux
index 6f30bcb44..321c628e9 100644
--- a/stdlib/source/lux/data/number/i64.lux
+++ b/stdlib/source/lux/data/number/i64.lux
@@ -12,7 +12,7 @@
   (n/* bits-per-byte
        bytes-per-i64))
 
-(do-template [  ]
+(template [  ]
   [(def: #export ( param subject)
      {#.doc }
      (All [s] (-> (I64 Any) (I64 s) (I64 s)))
@@ -42,7 +42,7 @@
   (def: compose ..and)
   )
 
-(do-template [  ]
+(template [  ]
   [(def: #export ( param subject)
      {#.doc }
      (All [s] (-> Nat (I64 s) (I64 s)))
@@ -83,7 +83,7 @@
   (All [s] (-> Nat (I64 s) (I64 s)))
   (|> idx flag ..not (..and input)))
 
-(do-template [  ]
+(template [  ]
   [(def: #export ( idx input)
      {#.doc }
      (All [s] (-> Nat (I64 s) (I64 s)))
@@ -97,7 +97,7 @@
   (-> Nat (I64 Any) Bit)
   (|> input (:coerce I64) (..and (flag idx)) (n/= 0) .not))
 
-(do-template [ 
] +(template [
] [(def: #export ( distance input) (All [s] (-> Nat (I64 s) (I64 s))) (let [backwards-distance (n/- (n/% width distance) width)] diff --git a/stdlib/source/lux/data/number/int.lux b/stdlib/source/lux/data/number/int.lux index 679147008..9a2ce2b9b 100644 --- a/stdlib/source/lux/data/number/int.lux +++ b/stdlib/source/lux/data/number/int.lux @@ -54,7 +54,7 @@ +1)) ) -(do-template [ ] +(template [ ] [(structure: #export (Monoid Int) (def: identity ) (def: compose ))] @@ -97,7 +97,7 @@ (|> output (i/* ) (i/+ (.int digit-value))))) (#error.Success (i/* sign output))))) -(do-template [ ] +(template [ ] [(structure: #export (Codec Text Int) (def: (encode value) (if (i/= +0 value) diff --git a/stdlib/source/lux/data/number/nat.lux b/stdlib/source/lux/data/number/nat.lux index 70f8df0bd..fb47d2460 100644 --- a/stdlib/source/lux/data/number/nat.lux +++ b/stdlib/source/lux/data/number/nat.lux @@ -48,7 +48,7 @@ 0 0 _ 1))) -(do-template [ ] +(template [ ] [(structure: #export (Monoid Nat) (def: identity ) (def: compose ))] @@ -171,7 +171,7 @@ (^or (^ (char "f")) (^ (char "F"))) (#.Some 15) _ #.None)) -(do-template [ ] +(template [ ] [(structure: #export (Codec Text Nat) (def: (encode value) (loop [input value diff --git a/stdlib/source/lux/data/number/ratio.lux b/stdlib/source/lux/data/number/ratio.lux index 9c7baaab8..49ce1f194 100644 --- a/stdlib/source/lux/data/number/ratio.lux +++ b/stdlib/source/lux/data/number/ratio.lux @@ -48,7 +48,7 @@ (`` (structure: #export order (Order Ratio) (def: &equivalence ..equivalence) - (~~ (do-template [ ] + (~~ (template [ ] [(def: ( parameter subject) (let [[parameter' subject'] (..equalize parameter subject)] ( parameter' subject')))] @@ -60,7 +60,7 @@ )) )) -(do-template [ ] +(template [ ] [(def: #export ( left right) (-> Ratio Ratio Ratio) (if (:: ..order left right) @@ -142,7 +142,7 @@ #..denominator (~ (maybe.default (' 1) ?denominator))}))))) -(do-template [ ] +(template [ ] [(structure: #export (Monoid Ratio) diff --git a/stdlib/source/lux/data/number/rev.lux b/stdlib/source/lux/data/number/rev.lux index 7a8fe53da..fa79f597d 100644 --- a/stdlib/source/lux/data/number/rev.lux +++ b/stdlib/source/lux/data/number/rev.lux @@ -40,7 +40,7 @@ (def: top (.rev -1)) (def: bottom (.rev 0))) -(do-template [ ] +(template [ ] [(structure: #export (Monoid Rev) (def: identity (:: interval )) (def: compose ))] @@ -54,7 +54,7 @@ (-> Text Text) ("lux text clip" input 1 ("lux text size" input))) -(do-template [ ] +(template [ ] [(with-expansions [ (as-is (#error.Failure ("lux text concat" repr)))] (structure: #export (Codec Text Rev) (def: (encode value) diff --git a/stdlib/source/lux/data/product.lux b/stdlib/source/lux/data/product.lux index 257ac8ec2..baa78dd45 100644 --- a/stdlib/source/lux/data/product.lux +++ b/stdlib/source/lux/data/product.lux @@ -3,7 +3,7 @@ lux) ## [Functions] -(do-template [ ] +(template [ ] [(def: #export ( xy) (All [a b] (-> [a b] )) (let [[x y] xy] diff --git a/stdlib/source/lux/data/sum.lux b/stdlib/source/lux/data/sum.lux index edb9d19fd..2f7624113 100644 --- a/stdlib/source/lux/data/sum.lux +++ b/stdlib/source/lux/data/sum.lux @@ -2,7 +2,7 @@ {#.doc "Functionality for working with variants (particularly 2-variants)."} lux) -(do-template [ ] +(template [ ] [(def: #export ( value) (All [a b] (-> (| a b))) ( value))] @@ -28,7 +28,7 @@ (0 l) (0 (fl l)) (1 r) (1 (fr r))))) -(do-template [ ] +(template [ ] [(def: #export ( es) (All [a b] (-> (List (| a b)) (List ))) (case es diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux index 00ad654e2..110afd81d 100644 --- a/stdlib/source/lux/data/text.lux +++ b/stdlib/source/lux/data/text.lux @@ -25,7 +25,7 @@ (-> Char Text) (|>> (:coerce Int) "lux int char")) -(do-template [ ] +(template [ ] [(def: #export (from-code ))] [null 0] diff --git a/stdlib/source/lux/data/text/encoding.lux b/stdlib/source/lux/data/text/encoding.lux index 55cb06ef3..8f59bd530 100644 --- a/stdlib/source/lux/data/text/encoding.lux +++ b/stdlib/source/lux/data/text/encoding.lux @@ -20,7 +20,7 @@ Text - (do-template [ ] + (template [ ] [(def: #export Encoding (:abstraction ))] [ascii "ASCII"] diff --git a/stdlib/source/lux/data/text/format.lux b/stdlib/source/lux/data/text/format.lux index b96606cdc..0becf8633 100644 --- a/stdlib/source/lux/data/text/format.lux +++ b/stdlib/source/lux/data/text/format.lux @@ -40,7 +40,7 @@ {#.doc "A way to produce readable text from values."} (-> a Text)) -(do-template [ ] +(template [ ] [(def: #export (Format ) )] @@ -81,10 +81,6 @@ (def: #export (%list formatter) (All [a] (-> (Format a) (Format (List a)))) - (function (_ values) - (case values - #.Nil - "(list)" - - _ - (format "(list " (text.join-with " " (list@map formatter values)) ")")))) + (|>> (list@map (|>> formatter (format " "))) + (text.join-with "") + (text.enclose ["(list" ")"]))) diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/data/text/lexer.lux index 923fb91a8..e5f19edf6 100644 --- a/stdlib/source/lux/data/text/lexer.lux +++ b/stdlib/source/lux/data/text/lexer.lux @@ -85,7 +85,7 @@ {#basis offset #distance 1}]))) -(do-template [ ] +(template [ ] [(def: #export ( p) {#.doc "Produce a character if the lexer fails."} (All [a] (-> (Lexer a) (Lexer ))) @@ -169,7 +169,7 @@ (n/<= top char')))] (wrap char))) -(do-template [ ] +(template [ ] [(def: #export {#.doc (code.text ($_ //;compose "Only lex " " characters."))} (Lexer Text) @@ -199,7 +199,7 @@ (range (char "a") (char "f")) (range (char "A") (char "F")))) -(do-template [ ] +(template [ ] [(def: #export ( options) {#.doc (code.text ($_ //;compose "Only lex characters that are" " part of a piece of text."))} (-> Text (Lexer Text)) @@ -220,7 +220,7 @@ [none-of " not" .not] ) -(do-template [ ] +(template [ ] [(def: #export ( options) {#.doc (code.text ($_ //;compose "Only lex characters that are" " part of a piece of text."))} (-> Text (Lexer Slice)) @@ -275,7 +275,7 @@ [right::basis right::distance] right] (wrap [left::basis ("lux i64 +" left::distance right::distance)]))) -(do-template [ ] +(template [ ] [(def: #export ( lexer) {#.doc (code.text ($_ //;compose "Lex " " characters as a single continuous text."))} (-> (Lexer Text) (Lexer Text)) @@ -285,7 +285,7 @@ [many p.many "many"] ) -(do-template [ ] +(template [ ] [(def: #export ( lexer) {#.doc (code.text ($_ //;compose "Lex " " characters as a single continuous text."))} (-> (Lexer Slice) (Lexer Slice)) @@ -295,7 +295,7 @@ [many! p.many "many"] ) -(do-template [ ] +(template [ ] [(def: #export ( amount lexer) {#.doc (code.text ($_ //;compose "Lex " " N characters."))} (-> Nat (Lexer Text) (Lexer Text)) @@ -306,7 +306,7 @@ [at-least p.at-least "at least"] ) -(do-template [ ] +(template [ ] [(def: #export ( amount lexer) {#.doc (code.text ($_ //;compose "Lex " " N characters."))} (-> Nat (Lexer Slice) (Lexer Slice)) diff --git a/stdlib/source/lux/data/text/unicode.lux b/stdlib/source/lux/data/text/unicode.lux index 951bfe761..11a98b358 100644 --- a/stdlib/source/lux/data/text/unicode.lux +++ b/stdlib/source/lux/data/text/unicode.lux @@ -36,7 +36,7 @@ (-> Char Char Segment) (:abstraction (interval.between nat.enum (n/min start end) (n/max start end)))) - (do-template [ ] + (template [ ] [(def: #export (-> Segment Char) (|>> :representation (get@ )))] @@ -56,7 +56,7 @@ (interval.within? (:representation segment) char)) ) -(do-template [ ] +(template [ ] [(def: #export Segment (..segment (hex ) (hex )))] ## Normal segments @@ -347,7 +347,7 @@ Set (finger.branch (set half/0) (set half/1))) -(do-template [ ] +(template [ ] [(def: #export Set (set ))] [ascii (list basic-latin)] diff --git a/stdlib/source/lux/host.js.lux b/stdlib/source/lux/host.js.lux index 7c182f363..bf24adc38 100644 --- a/stdlib/source/lux/host.js.lux +++ b/stdlib/source/lux/host.js.lux @@ -10,7 +10,7 @@ ["." code] ["s" syntax (#+ syntax: Syntax)]]]) -(do-template [ ] +(template [ ] [(type: #export (#.Primitive #.Nil))] [Object "object"] @@ -19,7 +19,7 @@ [Undefined "undefined"] ) -(do-template [ ] +(template [ ] [(type: #export )] [String Text] @@ -62,7 +62,7 @@ (wrap (list (` (:coerce (~ (default (' ..Object) type)) ("js ref" (~ (code.text name)))))))) -(do-template [ ] +(template [ ] [(syntax: #export () {#.doc (doc ())} diff --git a/stdlib/source/lux/host.jvm.lux b/stdlib/source/lux/host.jvm.lux index cdef88e92..e4891f56b 100644 --- a/stdlib/source/lux/host.jvm.lux +++ b/stdlib/source/lux/host.jvm.lux @@ -22,7 +22,7 @@ ["s" syntax (#+ syntax: Syntax)]] ["." io]]) -(do-template [ ] +(template [ ] [(def: #export ( value) {#.doc (doc "Type converter." (: @@ -594,7 +594,7 @@ (wrap (`' ((~ (code.text (format "jvm invokestatic" ":" class-name ":" method-name ":" (text.join-with "," arg-decls')))) (~+ args)))))) -(do-template [ ] +(template [ ] [(def: ( params class-name method-name arg-decls) (-> (List Type-Paramameter) Text Text (List ArgDecl) (Syntax Code)) (do p.monad @@ -1561,7 +1561,7 @@ _ return-term)) -(do-template [ ] +(template [ ] [(def: ( member return-term) (-> Import-Member-Declaration Code Code) (case member @@ -1587,7 +1587,7 @@ (-> Type-Paramameter Code) (code.identifier ["" name])) -(do-template [ ] +(template [ ] [(def: ( mode [class expression]) (-> Primitive-Mode [Text Code] Code) (case mode diff --git a/stdlib/source/lux/host/js.lux b/stdlib/source/lux/host/js.lux index be8759a35..756530817 100644 --- a/stdlib/source/lux/host/js.lux +++ b/stdlib/source/lux/host/js.lux @@ -24,7 +24,7 @@ (-> (Code Any) Text) (|>> :representation)) - (do-template [ +] + (template [ +] [(abstract: #export ( brand) {} Any) (`` (type: #export (|> Any (~~ (template.splice +)))))] @@ -34,7 +34,7 @@ [Statement Statement' [Code]] ) - (do-template [ +] + (template [ +] [(abstract: #export {} Any) (`` (type: #export (|> (~~ (template.splice +)))))] @@ -44,7 +44,7 @@ [Label Label' [Code]] ) - (do-template [ ] + (template [ ] [(def: #export Computation (|> ..argument :abstraction))] [null "null"] @@ -68,7 +68,7 @@ (def: sanitize (-> Text Text) - (`` (|>> (~~ (do-template [ ] + (`` (|>> (~~ (template [ ] [(text.replace-all )] ["\" "\\"] @@ -187,7 +187,7 @@ ..argument :abstraction)) - (do-template [ ] + (template [ ] [(def: #export ( param subject) (-> Expression Expression Computation) (|> (format (:representation subject) " " " " (:representation param)) @@ -217,7 +217,7 @@ [bit-and "&"] ) - (do-template [ ] + (template [ ] [(def: #export (-> Expression Computation) (|>> :representation (text.prefix ) ..argument :abstraction))] @@ -227,7 +227,7 @@ [negate "-"] ) - (do-template [ ] + (template [ ] [(def: #export ( value) {#.doc "A 32-bit integer expression."} (-> Computation) @@ -339,7 +339,7 @@ (-> Label Loop Statement) (:abstraction (format (:representation label) ": " (:representation loop)))) - (do-template [ <0> <1>] + (template [ <0> <1>] [(def: #export <0> Statement (:abstraction (format ..statement-suffix))) @@ -352,7 +352,7 @@ ["continue" continue continue-at] ) - (do-template [ ] + (template [ ] [(def: #export (-> Location Expression) (|>> :representation @@ -375,13 +375,13 @@ else! (list.reverse clauses))) -(do-template [ + + +] +(template [ + + +] [(`` (def: #export ( function) (-> Expression (~~ (template.splice +)) Computation) (.function (_ (~~ (template.splice +))) (..apply/* function (list (~~ (template.splice +))))))) - (`` (do-template [ ] + (`` (template [ ] [(def: #export ( (..var )))] (~~ (template.splice +))))] diff --git a/stdlib/source/lux/host/jvm/constant.lux b/stdlib/source/lux/host/jvm/constant.lux index 0d6bbcbfe..d9fcc2731 100644 --- a/stdlib/source/lux/host/jvm/constant.lux +++ b/stdlib/source/lux/host/jvm/constant.lux @@ -68,7 +68,7 @@ (|>> :representation) Equivalence)) - (do-template [ ] + (template [ ] [(type: #export (Value )) (def: #export @@ -82,7 +82,7 @@ [string String (Index UTF8)] ) - (do-template [ ] + (template [ ] [(def: (Format ) (binary.adapt (|>> :abstraction) @@ -103,7 +103,7 @@ {#class (Index Class) #name-and-type (Index Name-And-Type)}) -(do-template [ ] +(template [ ] [(def: #export (Equivalence ) ($_ equivalence.product @@ -173,7 +173,7 @@ )] {#binary.reader (do parser.monad [tag (get@ #binary.reader /tag.format)] - (`` (cond (~~ (do-template [ ] + (`` (cond (~~ (template [ ] [(/tag;= tag) (:: @ map (|>> ) (get@ #binary.reader ))] diff --git a/stdlib/source/lux/host/jvm/constant/tag.lux b/stdlib/source/lux/host/jvm/constant/tag.lux index 3862f5158..0339489f9 100644 --- a/stdlib/source/lux/host/jvm/constant/tag.lux +++ b/stdlib/source/lux/host/jvm/constant/tag.lux @@ -20,7 +20,7 @@ (u1/= (:representation reference) (:representation sample)))) - (do-template [ ] + (template [ ] [(def: #export Tag (:abstraction (encoding.to-u1 )))] diff --git a/stdlib/source/lux/host/jvm/descriptor.lux b/stdlib/source/lux/host/jvm/descriptor.lux index 1647e32ea..d350cec65 100644 --- a/stdlib/source/lux/host/jvm/descriptor.lux +++ b/stdlib/source/lux/host/jvm/descriptor.lux @@ -28,14 +28,14 @@ (type: #export (Value kind) (Return (Value' kind))) (type: #export Void (Return Void')) - (do-template [ ] + (template [ ] [(type: #export (Value ))] [Base Base'] [Object Object'] [Array Array']) - (do-template [ ] + (template [ ] [(def: #export (Descriptor ) (:abstraction ))] diff --git a/stdlib/source/lux/host/jvm/encoding.lux b/stdlib/source/lux/host/jvm/encoding.lux index 08213e268..7d7fb636d 100644 --- a/stdlib/source/lux/host/jvm/encoding.lux +++ b/stdlib/source/lux/host/jvm/encoding.lux @@ -11,7 +11,7 @@ [type abstract]]) -(do-template [ ] +(template [ ] [(abstract: #export {} @@ -40,7 +40,7 @@ [4 U4 u4-bytes to-u4 from-u4 u4-equivalence] ) -(do-template [ ] +(template [ ] [(def: #export (Format ) (binary.adapt ))] diff --git a/stdlib/source/lux/host/jvm/modifier.lux b/stdlib/source/lux/host/jvm/modifier.lux index cb535a96b..e25e14b78 100644 --- a/stdlib/source/lux/host/jvm/modifier.lux +++ b/stdlib/source/lux/host/jvm/modifier.lux @@ -53,7 +53,7 @@ (abstract.:abstraction (//encoding.to-u2 (i64.and (//encoding.from-u2 (abstract.:representation (~ g!parameter))) (//encoding.from-u2 (abstract.:representation (~ g!subject))))))) - (.do-template [(~ g!) (~ g!)] + (.template [(~ g!) (~ g!)] [(.def: (~' #export) (~ g!) (~ g!name) (.|> ((~! number.hex) (~ g!)) //encoding.to-u2 abstract.:abstraction))] diff --git a/stdlib/source/lux/host/jvm/version.lux b/stdlib/source/lux/host/jvm/version.lux index 8641dd393..dd76a594d 100644 --- a/stdlib/source/lux/host/jvm/version.lux +++ b/stdlib/source/lux/host/jvm/version.lux @@ -14,23 +14,23 @@ (-> Nat Version) //encoding.to-u2) -(do-template [ ] +(template [ ] [(def: #export Major (..version ))] - [v1_1 45] - [v1_2 46] - [v1_3 47] - [v1_4 48] - [v5_0 49] - [v6_0 50] - [v7 51] - [v8 52] - [v9 53] - [v10 54] - [v11 55] - [v12 56] + [45 v1_1] + [46 v1_2] + [47 v1_3] + [48 v1_4] + [49 v5_0] + [50 v6_0] + [51 v7] + [52 v8] + [53 v9] + [54 v10] + [55 v11] + [56 v12] ) (def: #export format diff --git a/stdlib/source/lux/host/python.lux b/stdlib/source/lux/host/python.lux index 134e35798..322ac261e 100644 --- a/stdlib/source/lux/host/python.lux +++ b/stdlib/source/lux/host/python.lux @@ -36,7 +36,7 @@ (-> (Code Any) Text) (|>> :representation)) - (do-template [ ] + (template [ ] [(with-expansions [ (template.identifier [ "'"])] (`` (abstract: #export ( brand) {} Any)) (`` (type: #export ( brand) @@ -49,7 +49,7 @@ [Statement Code] ) - (do-template [ ] + (template [ ] [(with-expansions [ (template.identifier [ "'"])] (`` (abstract: #export {} Any)) (`` (type: #export ( ))))] @@ -72,7 +72,7 @@ (-> Text SVar) (|>> :abstraction)) - (do-template [ ] + (template [ ] [(def: #export (-> SVar (Var )) (|>> :representation (format ) :abstraction))] @@ -101,7 +101,7 @@ (def: #export float (-> Frac Literal) - (`` (|>> (cond> (~~ (do-template [ ] + (`` (|>> (cond> (~~ (template [ ] [[(f/= )] [(new> (format "float(" text.double-quote text.double-quote ")") [])]] @@ -116,7 +116,7 @@ (def: sanitize (-> Text Text) - (`` (|>> (~~ (do-template [ ] + (`` (|>> (~~ (template [ ] [(text.replace-all )] ["\" "\\"] @@ -150,7 +150,7 @@ (text.join-with ", ")) right-delimiter)))) - (do-template [
 ]
+  (template [ 
 ]
     [(def: #export 
        (-> (List (Expression Any)) Literal)
        (composite-literal 
  ..code))]
@@ -181,7 +181,7 @@
         ..expression
         (format (:representation func) "(" (text.join-with ", " (list@map ..code args)) ")")))
 
-  (do-template [  ]
+  (template [  ]
     [(def: ( var)
        (-> (Expression Any) Text)
        (format  (:representation var)))]
@@ -190,7 +190,7 @@
     [splat-keyword Keyword "**"]
     )
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( args extra func)
        (-> (List (Expression Any)) (Expression Any) (Expression Any) (Computation Any))
        (<| :abstraction
@@ -213,7 +213,7 @@
     (-> Text (List (Expression Any)) (Expression Any) (Computation Any))
     (..apply/* (..the method object) args))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( args extra method)
        (-> (List (Expression Any)) (Expression Any) Text
            (-> (Expression Any) (Computation Any)))
@@ -233,7 +233,7 @@
         ..expression
         (format (:representation then) " if " (:representation test) " else " (:representation else))))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( param subject)
        (-> (Expression Any) (Expression Any) (Computation Any))
        (<| :abstraction
@@ -307,7 +307,7 @@
              text.new-line
              (:representation post!))))
 
-  (do-template [ <0>]
+  (template [ <0>]
     [(def: #export <0>
        Statement
        (:abstraction ))]
@@ -354,7 +354,7 @@
                                      (..nest (:representation catch!)))))
                  (text.join-with "")))))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( message)
        (-> (Expression Any) (Statement Any))
        (:abstraction
@@ -399,7 +399,7 @@
 (syntax: (arity-types {arity s.nat})
   (wrap (list.repeat arity (` (Expression Any)))))
 
-(do-template [ +]
+(template [ +]
   [(with-expansions [ (template.identifier ["apply/" ])
                       (arity-inputs )
                       (arity-types )
@@ -408,7 +408,7 @@
        (-> (Expression Any)  (Computation Any))
        (..apply/* function (.list )))
 
-     (do-template []
+     (template []
        [(`` (def: #export (~~ (template.identifier [ "/" ]))
               ( (..var ))))]
 
diff --git a/stdlib/source/lux/host/scheme.lux b/stdlib/source/lux/host/scheme.lux
index 5a8741c78..af8e0b954 100644
--- a/stdlib/source/lux/host/scheme.lux
+++ b/stdlib/source/lux/host/scheme.lux
@@ -20,14 +20,14 @@
   
   Text
 
-  (do-template [  +]
+  (template [  +]
     [(abstract: #export ( brand) {} Any)
      (`` (type: #export  (|> Any  (~~ (template.splice +)))))]
     
     [Expression Expression' [Code]]
     )
 
-  (do-template [  +]
+  (template [  +]
     [(abstract: #export  {} Any)
      (`` (type: #export  (|>  (~~ (template.splice +)))))]
 
@@ -102,7 +102,7 @@
 
   (def: sanitize
     (-> Text Text)
-    (`` (|>> (~~ (do-template [ ]
+    (`` (|>> (~~ (template [ ]
                    [(text.replace-all  )]
 
                    [text.alarm "\a"]
@@ -138,7 +138,7 @@
     (-> Expression (List Expression) Computation)
     (:abstraction (..form (#.Cons func args))))
   
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        (-> (List Expression) Computation)
        (apply/* (..global )))]
@@ -151,19 +151,19 @@
     (-> Expression Computation)
     (..apply/* func (list)))
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export  (apply/0 (..global )))]
 
     [newline/0 "newline"]
     )
 
-  (do-template [ + + +]
+  (template [ + + +]
     [(`` (def: #export ( function)
            (-> Expression (~~ (template.splice +)) Computation)
            (.function (_ (~~ (template.splice +)))
              (..apply/* function (list (~~ (template.splice +)))))))
 
-     (`` (do-template [ ]
+     (`` (template [ ]
            [(def: #export  ( (..global )))]
 
            (~~ (template.splice +))))]
@@ -207,7 +207,7 @@
      [[vector-copy!/5 "vector-copy!"]]]
     )
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export ( param subject)
        (-> Expression Expression Computation)
        (..apply/2 (..global ) subject param))]
@@ -235,7 +235,7 @@
     [bit-xor/2 "bitwise-xor"]
     )
 
-  (do-template [ ]
+  (template [ ]
     [(def: #export 
        (-> (List Expression) Computation)
        (|>> (list& (..global )) ..form :abstraction))]
@@ -244,7 +244,7 @@
     [and "and"]
     )
 
-  (do-template [   
]
+  (template [   
]
     [(def: #export ( bindings body)
        (-> (List [ Expression]) Expression Computation)
        (:abstraction
diff --git a/stdlib/source/lux/locale/language.lux b/stdlib/source/lux/locale/language.lux
index 57857fcc3..1cfa9dd82 100644
--- a/stdlib/source/lux/locale/language.lux
+++ b/stdlib/source/lux/locale/language.lux
@@ -20,9 +20,9 @@
     (-> Language Text)
     (|>> :representation))
 
-  (do-template [  +]
+  (template [  +]
     [(def: #export  Language (:abstraction ))
-     (`` (do-template []
+     (`` (template []
            [(def: #export  Language )]
 
            (~~ (template.splice +))))]
diff --git a/stdlib/source/lux/locale/territory.lux b/stdlib/source/lux/locale/territory.lux
index d2cd5b347..b37148bb2 100644
--- a/stdlib/source/lux/locale/territory.lux
+++ b/stdlib/source/lux/locale/territory.lux
@@ -19,7 +19,7 @@
    #long Text
    #code Nat}
 
-  (do-template [  ]
+  (template [  ]
     [(def: #export 
        (-> Territory )
        (|>> :representation
@@ -31,7 +31,7 @@
     [numeric-code #code  Nat]
     )
 
-  (do-template [    
+] + (template [
+] [(def: #export
Territory (:abstraction {#name @@ -39,7 +39,7 @@ #long #code })) - (`` (do-template [] + (`` (template [] [(def: #export Territory
)] (~~ (template.splice +))))] diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux index e44efeb6c..059351420 100644 --- a/stdlib/source/lux/macro.lux +++ b/stdlib/source/lux/macro.lux @@ -164,7 +164,7 @@ _ #.None)) -(do-template [ ] +(template [ ] [(def: #export ( tag anns) (-> Name Code (Maybe )) (case (get-ann tag anns) @@ -195,7 +195,7 @@ (-> Name Code Bit) (maybe.default #0 (get-bit-ann flag-name anns))) -(do-template [ ] +(template [ ] [(def: #export {#.doc (code.text ($_ text;compose "Checks whether a definition is " "."))} (-> Code Bit) @@ -218,7 +218,7 @@ #.None #0)) -(do-template [ ] +(template [ ] [(def: ( input) (-> Code (Maybe )) (case input @@ -232,7 +232,7 @@ [parse-text #.Text Text] ) -(do-template [ ] +(template [ ] [(def: #export ( anns) {#.doc } (-> Code (List Text)) @@ -699,7 +699,7 @@ (function (_ compiler) (#error.Success [compiler (get@ #.type-context compiler)]))) -(do-template [ ] +(template [ ] [(macro: #export ( tokens) {#.doc (doc "Performs a macro-expansion and logs the resulting code." "You can either use the resulting code, or omit them." diff --git a/stdlib/source/lux/macro/code.lux b/stdlib/source/lux/macro/code.lux index b986c02f4..84f08e5f1 100644 --- a/stdlib/source/lux/macro/code.lux +++ b/stdlib/source/lux/macro/code.lux @@ -31,7 +31,7 @@ (def: _cursor Cursor ["" 0 0]) -(do-template [ ] +(template [ ] [(def: #export ( x) (-> Code) [_cursor ( x)])] @@ -49,7 +49,7 @@ [record (List [Code Code]) #.Record] ) -(do-template [ ] +(template [ ] [(def: #export ( name) {#.doc } (-> Text Code) diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux index aefdea082..4f5cd09a0 100644 --- a/stdlib/source/lux/macro/poly.lux +++ b/stdlib/source/lux/macro/poly.lux @@ -29,7 +29,7 @@ ["." type ("#;." equivalence) ["." check]]]) -(do-template [] +(template [] [(exception: #export ( {type Type}) (%type type))] @@ -45,7 +45,7 @@ [not-tuple] ) -(do-template [] +(template [] [(exception: #export ( {expected Type} {actual Type}) (ex.report ["Expected" (%type expected)] ["Actual" (%type actual)]))] @@ -147,7 +147,7 @@ (#error.Success [[_ inputs'] output]) (#error.Success [[env inputs'] [g!var output]]))))) -(do-template [ ] +(template [ ] [(def: #export ( poly) (All [a] (-> (Poly a) (Poly a))) (do p.monad @@ -226,7 +226,7 @@ (p.fail (ex.construct not-application headT)) (local (#.Cons funcT paramsT) poly)))) -(do-template [ ] +(template [ ] [(def: #export ( expected) (-> Type (Poly Any)) (do p.monad diff --git a/stdlib/source/lux/macro/poly/equivalence.lux b/stdlib/source/lux/macro/poly/equivalence.lux index 91b3c6c64..cc0b79234 100644 --- a/stdlib/source/lux/macro/poly/equivalence.lux +++ b/stdlib/source/lux/macro/poly/equivalence.lux @@ -48,7 +48,7 @@ (` ((~! eq.Equivalence) (~ (poly.to-code *env* type))))))]] ($_ p.either ## Basic types - (~~ (do-template [ ] + (~~ (template [ ] [(do @ [_ ] (wrap (` (: (~ (@Equivalence inputT)) @@ -62,7 +62,7 @@ [(poly.sub Frac) (~! frac.equivalence)] [(poly.sub Text) (~! text.equivalence)])) ## Composite types - (~~ (do-template [ ] + (~~ (template [ ] [(do @ [[_ argC] (poly.apply (p.and (poly.exactly ) equivalence))] @@ -85,7 +85,7 @@ (wrap (` (: (~ (@Equivalence inputT)) ((~! dictionary.equivalence) (~ valC)))))) ## Models - (~~ (do-template [ ] + (~~ (template [ ] [(do @ [_ (poly.exactly )] (wrap (` (: (~ (@Equivalence inputT)) diff --git a/stdlib/source/lux/macro/poly/json.lux b/stdlib/source/lux/macro/poly/json.lux index 6cf596049..cc5f3b5c9 100644 --- a/stdlib/source/lux/macro/poly/json.lux +++ b/stdlib/source/lux/macro/poly/json.lux @@ -89,7 +89,7 @@ (poly: #export codec//encode (with-expansions - [ (do-template [ ] + [ (template [ ] [(do @ [#let [g!_ (code.local-identifier "_______")] _ ] @@ -102,7 +102,7 @@ [(poly.sub Int) (:: (~! ..int-codec) (~' encode))] [(poly.sub Frac) (|>> #/.Number)] [(poly.sub Text) (|>> #/.String)]) -