aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/polytypic
diff options
context:
space:
mode:
authorEduardo Julian2022-07-02 05:38:27 -0400
committerEduardo Julian2022-07-02 05:38:27 -0400
commitb96beb587c11fcfbce86ce2d62351600cf6cad1b (patch)
treec9a558ab1391ac97cb11e8777ea78299f1ab5555 /stdlib/source/polytypic
parent104130efba46a875eba566384578f8aa8593ad37 (diff)
More traditional names for unquoting macros.
Diffstat (limited to 'stdlib/source/polytypic')
-rw-r--r--stdlib/source/polytypic/lux/abstract/equivalence.lux98
-rw-r--r--stdlib/source/polytypic/lux/abstract/functor.lux40
-rw-r--r--stdlib/source/polytypic/lux/data/format/json.lux162
3 files changed, 150 insertions, 150 deletions
diff --git a/stdlib/source/polytypic/lux/abstract/equivalence.lux b/stdlib/source/polytypic/lux/abstract/equivalence.lux
index 0c83b9ab5..bc044fe6b 100644
--- a/stdlib/source/polytypic/lux/abstract/equivalence.lux
+++ b/stdlib/source/polytypic/lux/abstract/equivalence.lux
@@ -48,50 +48,50 @@
inputT <type>.next
.let [@Equivalence (is (-> Type Code)
(function (_ type)
- (` ((~! /.Equivalence) (~ (poly.code *env* type))))))]]
+ (` ((,! /.Equivalence) (, (poly.code *env* type))))))]]
(all <>.either
... Basic types
- (~~ (with_template [<matcher> <eq>]
+ (,, (with_template [<matcher> <eq>]
[(do !
[_ <matcher>]
- (in (` (is (~ (@Equivalence inputT))
+ (in (` (is (, (@Equivalence inputT))
<eq>))))]
- [(<type>.exactly Any) (function ((~ g!_) (~ g!_) (~ g!_)) #1)]
- [(<type>.sub Bit) (~! bit.equivalence)]
- [(<type>.sub Nat) (~! nat.equivalence)]
- [(<type>.sub Int) (~! int.equivalence)]
- [(<type>.sub Rev) (~! rev.equivalence)]
- [(<type>.sub Frac) (~! frac.equivalence)]
- [(<type>.sub Text) (~! text.equivalence)]))
+ [(<type>.exactly Any) (function ((, g!_) (, g!_) (, g!_)) #1)]
+ [(<type>.sub Bit) (,! bit.equivalence)]
+ [(<type>.sub Nat) (,! nat.equivalence)]
+ [(<type>.sub Int) (,! int.equivalence)]
+ [(<type>.sub Rev) (,! rev.equivalence)]
+ [(<type>.sub Frac) (,! frac.equivalence)]
+ [(<type>.sub Text) (,! text.equivalence)]))
... Composite types
- (~~ (with_template [<name> <eq>]
+ (,, (with_template [<name> <eq>]
[(do !
[[_ argC] (<type>.applied (<>.and (<type>.exactly <name>)
equivalence))]
- (in (` (is (~ (@Equivalence inputT))
- (<eq> (~ argC))))))]
+ (in (` (is (, (@Equivalence inputT))
+ (<eq> (, argC))))))]
- [.Maybe (~! maybe.equivalence)]
- [.List (~! list.equivalence)]
- [sequence.Sequence (~! sequence.equivalence)]
- [array.Array (~! array.equivalence)]
- [queue.Queue (~! queue.equivalence)]
- [set.Set (~! set.equivalence)]
- [tree.Tree (~! tree.equivalence)]
+ [.Maybe (,! maybe.equivalence)]
+ [.List (,! list.equivalence)]
+ [sequence.Sequence (,! sequence.equivalence)]
+ [array.Array (,! array.equivalence)]
+ [queue.Queue (,! queue.equivalence)]
+ [set.Set (,! set.equivalence)]
+ [tree.Tree (,! tree.equivalence)]
))
(do !
[[_ _ valC] (<type>.applied (all <>.and
(<type>.exactly dictionary.Dictionary)
<type>.any
equivalence))]
- (in (` (is (~ (@Equivalence inputT))
- ((~! dictionary.equivalence) (~ valC))))))
+ (in (` (is (, (@Equivalence inputT))
+ ((,! dictionary.equivalence) (, valC))))))
... Models
- (~~ (with_template [<type> <eq>]
+ (,, (with_template [<type> <eq>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (is (~ (@Equivalence inputT))
+ (in (` (is (, (@Equivalence inputT))
<eq>))))]
[duration.Duration duration.equivalence]
@@ -103,7 +103,7 @@
(do !
[_ (<type>.applied (<>.and (<type>.exactly unit.Measure)
<type>.any))]
- (in (` (is (~ (@Equivalence inputT))
+ (in (` (is (, (@Equivalence inputT))
unit.equivalence))))
... Variants
(do !
@@ -112,19 +112,19 @@
g!_ (code.local "_____________")
g!left (code.local "_____________left")
g!right (code.local "_____________right")]]
- (in (` (is (~ (@Equivalence inputT))
- (function ((~ g!_) (~ g!left) (~ g!right))
- (case [(~ g!left) (~ g!right)]
- (~+ (list#conjoint (list#each (function (_ [tag g!eq])
+ (in (` (is (, (@Equivalence inputT))
+ (function ((, g!_) (, g!left) (, g!right))
+ (case [(, g!left) (, g!right)]
+ (,* (list#conjoint (list#each (function (_ [tag g!eq])
(if (nat.= last tag)
- (list (` [{(~ (code.nat (-- tag))) #1 (~ g!left)}
- {(~ (code.nat (-- tag))) #1 (~ g!right)}])
- (` ((~ g!eq) (~ g!left) (~ g!right))))
- (list (` [{(~ (code.nat tag)) #0 (~ g!left)}
- {(~ (code.nat tag)) #0 (~ g!right)}])
- (` ((~ g!eq) (~ g!left) (~ g!right))))))
+ (list (` [{(, (code.nat (-- tag))) #1 (, g!left)}
+ {(, (code.nat (-- tag))) #1 (, g!right)}])
+ (` ((, g!eq) (, g!left) (, g!right))))
+ (list (` [{(, (code.nat tag)) #0 (, g!left)}
+ {(, (code.nat tag)) #0 (, g!right)}])
+ (` ((, g!eq) (, g!left) (, g!right))))))
(list.enumeration members))))
- (~ g!_)
+ (, g!_)
#0))))))
... Tuples
(do !
@@ -133,33 +133,33 @@
indices (list.indices (list.size g!eqs))
g!lefts (list#each (|>> nat#encoded (text#composite "left") code.local) indices)
g!rights (list#each (|>> nat#encoded (text#composite "right") code.local) indices)]]
- (in (` (is (~ (@Equivalence inputT))
- (function ((~ g!_) [(~+ g!lefts)] [(~+ g!rights)])
- (and (~+ (|> (list.zipped_3 g!eqs g!lefts g!rights)
+ (in (` (is (, (@Equivalence inputT))
+ (function ((, g!_) [(,* g!lefts)] [(,* g!rights)])
+ (and (,* (|> (list.zipped_3 g!eqs g!lefts g!rights)
(list#each (function (_ [g!eq g!left g!right])
- (` ((~ g!eq) (~ g!left) (~ g!right)))))))))))))
+ (` ((, g!eq) (, g!left) (, g!right)))))))))))))
... Type recursion
(do !
[[g!self bodyC] (<type>.recursive equivalence)
.let [g!_ (code.local "_____________")]]
- (in (` (is (~ (@Equivalence inputT))
- ((~! /.rec) (.function ((~ g!_) (~ g!self))
- (~ bodyC)))))))
+ (in (` (is (, (@Equivalence inputT))
+ ((,! /.rec) (.function ((, g!_) (, g!self))
+ (, bodyC)))))))
<type>.recursive_self
... Type applications
(do !
[[funcC argsC] (<type>.applied (<>.and equivalence (<>.many equivalence)))]
- (in (` ((~ funcC) (~+ argsC)))))
+ (in (` ((, funcC) (,* argsC)))))
... Parameters
<type>.parameter
... Polymorphism
(do !
[[funcC varsC bodyC] (<type>.polymorphic equivalence)]
- (in (` (is (All ((~ g!_) (~+ varsC))
- (-> (~+ (list#each (|>> (~) ((~! /.Equivalence)) (`)) varsC))
- ((~! /.Equivalence) ((~ (poly.code *env* inputT)) (~+ varsC)))))
- (function ((~ funcC) (~+ varsC))
- (~ bodyC))))))
+ (in (` (is (All ((, g!_) (,* varsC))
+ (-> (,* (list#each (|>> (,) ((,! /.Equivalence)) (`)) varsC))
+ ((,! /.Equivalence) ((, (poly.code *env* inputT)) (,* varsC)))))
+ (function ((, funcC) (,* varsC))
+ (, bodyC))))))
<type>.recursive_call
... If all else fails...
(|> <type>.any
diff --git a/stdlib/source/polytypic/lux/abstract/functor.lux b/stdlib/source/polytypic/lux/abstract/functor.lux
index db17e49ac..43b8b2902 100644
--- a/stdlib/source/polytypic/lux/abstract/functor.lux
+++ b/stdlib/source/polytypic/lux/abstract/functor.lux
@@ -37,10 +37,10 @@
.let [@Functor (is (-> Type Code)
(function (_ unwrappedT)
(if (n.= 1 num_vars)
- (` ((~! /.Functor) (~ (poly.code *env* unwrappedT))))
+ (` ((,! /.Functor) (, (poly.code *env* unwrappedT))))
(let [paramsC (|> num_vars -- list.indices (list#each (|>> %.nat code.local)))]
- (` (All ((~ g!_) (~+ paramsC))
- ((~! /.Functor) ((~ (poly.code *env* unwrappedT)) (~+ paramsC)))))))))
+ (` (All ((, g!_) (,* paramsC))
+ ((,! /.Functor) ((, (poly.code *env* unwrappedT)) (,* paramsC)))))))))
Arg<?> (is (-> Code (<type>.Parser Code))
(function (Arg<?> valueC)
(all <>.either
@@ -48,19 +48,19 @@
(do <>.monad
[.let [varI (|> num_vars (n.* 2) --)]
_ (<type>.this_parameter varI)]
- (in (` ((~ funcC) (~ valueC)))))
+ (in (` ((, funcC) (, valueC)))))
... Variants
(do !
[_ (in [])
membersC (<type>.variant (<>.many (Arg<?> valueC)))
.let [last (-- (list.size membersC))]]
- (in (` (case (~ valueC)
- (~+ (list#conjoint (list#each (function (_ [tag memberC])
+ (in (` (case (, valueC)
+ (,* (list#conjoint (list#each (function (_ [tag memberC])
(if (n.= last tag)
- (list (` {(~ (code.nat (-- tag))) #1 (~ valueC)})
- (` {(~ (code.nat (-- tag))) #1 (~ memberC)}))
- (list (` {(~ (code.nat tag)) #0 (~ valueC)})
- (` {(~ (code.nat tag)) #0 (~ memberC)}))))
+ (list (` {(, (code.nat (-- tag))) #1 (, valueC)})
+ (` {(, (code.nat (-- tag))) #1 (, memberC)}))
+ (list (` {(, (code.nat tag)) #0 (, valueC)})
+ (` {(, (code.nat tag)) #0 (, memberC)}))))
(list.enumeration membersC))))))))
... Tuples
(do <>.monad
@@ -75,9 +75,9 @@
(again (++ idx)
(list#composite pairsCC (list [slotC memberC])))))
(in pairsCC)))))]
- (in (` (case (~ valueC)
- [(~+ (list#each product.left pairsCC))]
- [(~+ (list#each product.right pairsCC))]))))
+ (in (` (case (, valueC)
+ [(,* (list#each product.left pairsCC))]
+ [(,* (list#each product.right pairsCC))]))))
... Functions
(do !
[_ (in [])
@@ -88,13 +88,13 @@
.let [inC+ (|> (list.size inT+)
list.indices
(list#each (|>> %.nat (format "____________inC") code.local)))]]
- (in (` (function ((~ g!) (~+ inC+))
- (let [(~ outL) ((~ valueC) (~+ inC+))]
- (~ outC))))))
+ (in (` (function ((, g!) (,* inC+))
+ (let [(, outL) ((, valueC) (,* inC+))]
+ (, outC))))))
... Recursion
(do <>.monad
[_ <type>.recursive_call]
- (in (` ((~' each) (~ funcC) (~ valueC)))))
+ (in (` ((,' each) (, funcC) (, valueC)))))
... Parameters
(do <>.monad
[_ <type>.any]
@@ -104,7 +104,7 @@
(<>.either (<type>.polymorphic
(Arg<?> inputC))
(<>.failure (format "Cannot create Functor for: " (%.type inputT)))))]
- (in (` (is (~ (@Functor inputT))
+ (in (` (is (, (@Functor inputT))
(implementation
- (def ((~' each) (~ funcC) (~ inputC))
- (~ outputC)))))))))
+ (def ((,' each) (, funcC) (, inputC))
+ (, outputC)))))))))
diff --git a/stdlib/source/polytypic/lux/data/format/json.lux b/stdlib/source/polytypic/lux/data/format/json.lux
index a8eee64d0..5f79d7fe4 100644
--- a/stdlib/source/polytypic/lux/data/format/json.lux
+++ b/stdlib/source/polytypic/lux/data/format/json.lux
@@ -105,20 +105,20 @@
[(do !
[.let [g!_ (code.local "_______")]
_ <matcher>]
- (in (` (is (~ (@JSON#encoded inputT))
+ (in (` (is (, (@JSON#encoded inputT))
<encoder>))))]
- [(<type>.exactly Any) (function ((~ g!_) (~ (code.symbol ["" "0"]))) {/.#Null})]
+ [(<type>.exactly Any) (function ((, g!_) (, (code.symbol ["" "0"]))) {/.#Null})]
[(<type>.sub Bit) (|>> {/.#Boolean})]
- [(<type>.sub Nat) (at (~! ..nat_codec) (~' encoded))]
- [(<type>.sub Int) (at (~! ..int_codec) (~' encoded))]
+ [(<type>.sub Nat) (at (,! ..nat_codec) (,' encoded))]
+ [(<type>.sub Int) (at (,! ..int_codec) (,' encoded))]
[(<type>.sub Frac) (|>> {/.#Number})]
[(<type>.sub Text) (|>> {/.#String})])
<time> (with_template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (is (~ (@JSON#encoded inputT))
- (|>> (at (~! <codec>) (~' encoded)) {/.#String})))))]
+ (in (` (is (, (@JSON#encoded inputT))
+ (|>> (at (,! <codec>) (,' encoded)) {/.#String})))))]
... [duration.Duration duration.codec]
... [instant.Instant instant.codec]
@@ -130,7 +130,7 @@
.let [g!_ (code.local "_______")
@JSON#encoded (is (-> Type Code)
(function (_ type)
- (` (-> (~ (poly.code *env* type)) /.JSON))))]
+ (` (-> (, (poly.code *env* type)) /.JSON))))]
inputT <type>.next]
(all <>.either
<basic>
@@ -138,8 +138,8 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Measure)
<type>.any))]
- (in (` (is (~ (@JSON#encoded inputT))
- (at (~! measure_codec) (~' encoded))))))
+ (in (` (is (, (@JSON#encoded inputT))
+ (at (,! measure_codec) (,' encoded))))))
(do !
[.let [g!_ (code.local "_______")
g!key (code.local "_______key")
@@ -148,42 +148,42 @@
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
encoded))]
- (in (` (is (~ (@JSON#encoded inputT))
- (|>> ((~! dictionary.entries))
- ((~! list#each) (function ((~ g!_) [(~ g!key) (~ g!val)])
- [(~ g!key) ((~ =val=) (~ g!val))]))
- ((~! dictionary.of_list) (~! text.hash))
+ (in (` (is (, (@JSON#encoded inputT))
+ (|>> ((,! dictionary.entries))
+ ((,! list#each) (function ((, g!_) [(, g!key) (, g!val)])
+ [(, g!key) ((, =val=) (, g!val))]))
+ ((,! dictionary.of_list) (,! text.hash))
{/.#Object})))))
(do !
[[_ =sub=] (<type>.applied (all <>.and
(<type>.exactly .Maybe)
encoded))]
- (in (` (is (~ (@JSON#encoded inputT))
- ((~! ..nullable) (~ =sub=))))))
+ (in (` (is (, (@JSON#encoded inputT))
+ ((,! ..nullable) (, =sub=))))))
(do !
[[_ =sub=] (<type>.applied (all <>.and
(<type>.exactly .List)
encoded))]
- (in (` (is (~ (@JSON#encoded inputT))
- (|>> ((~! list#each) (~ =sub=)) ((~! sequence.of_list)) {/.#Array})))))
+ (in (` (is (, (@JSON#encoded inputT))
+ (|>> ((,! list#each) (, =sub=)) ((,! sequence.of_list)) {/.#Array})))))
(do !
[.let [g!_ (code.local "_______")
g!input (code.local "_______input")]
members (<type>.variant (<>.many encoded))
.let [last (-- (list.size members))]]
- (in (` (is (~ (@JSON#encoded inputT))
- (function ((~ g!_) (~ g!input))
- (case (~ g!input)
- (~+ (list#conjoint (list#each (function (_ [tag g!encoded])
+ (in (` (is (, (@JSON#encoded inputT))
+ (function ((, g!_) (, g!input))
+ (case (, g!input)
+ (,* (list#conjoint (list#each (function (_ [tag g!encoded])
(if (n.= last tag)
- (.list (` {(~ (code.nat (-- tag))) #1 (~ g!input)})
- (` ((~! /.json) [(~ (code.frac (..tag (-- tag))))
+ (.list (` {(, (code.nat (-- tag))) #1 (, g!input)})
+ (` ((,! /.json) [(, (code.frac (..tag (-- tag))))
#1
- ((~ g!encoded) (~ g!input))])))
- (.list (` {(~ (code.nat tag)) #0 (~ g!input)})
- (` ((~! /.json) [(~ (code.frac (..tag tag)))
+ ((, g!encoded) (, g!input))])))
+ (.list (` {(, (code.nat tag)) #0 (, g!input)})
+ (` ((,! /.json) [(, (code.frac (..tag tag)))
#0
- ((~ g!encoded) (~ g!input))])))))
+ ((, g!encoded) (, g!input))])))))
(list.enumeration members))))))))))
(do !
[g!encoders (<type>.tuple (<>.many encoded))
@@ -191,33 +191,33 @@
g!members (|> (list.size g!encoders)
list.indices
(list#each (|>> n#encoded code.local)))]]
- (in (` (is (~ (@JSON#encoded inputT))
- (function ((~ g!_) [(~+ g!members)])
- ((~! /.json) [(~+ (list#each (function (_ [g!member g!encoded])
- (` ((~ g!encoded) (~ g!member))))
+ (in (` (is (, (@JSON#encoded inputT))
+ (function ((, g!_) [(,* g!members)])
+ ((,! /.json) [(,* (list#each (function (_ [g!member g!encoded])
+ (` ((, g!encoded) (, g!member))))
(list.zipped_2 g!members g!encoders)))]))))))
... Type recursion
(do !
[[selfC non_recC] (<type>.recursive encoded)
.let [g! (code.local "____________")]]
- (in (` (is (~ (@JSON#encoded inputT))
- ((~! ..rec_encoded) (.function ((~ g!) (~ selfC))
- (~ non_recC)))))))
+ (in (` (is (, (@JSON#encoded inputT))
+ ((,! ..rec_encoded) (.function ((, g!) (, selfC))
+ (, non_recC)))))))
<type>.recursive_self
... Type applications
(do !
[partsC (<type>.applied (<>.many encoded))]
- (in (` ((~+ partsC)))))
+ (in (` ((,* partsC)))))
... Polymorphism
(do !
[[funcC varsC bodyC] (<type>.polymorphic encoded)]
- (in (` (is (All ((~ g!_) (~+ varsC))
- (-> (~+ (list#each (function (_ varC) (` (-> (~ varC) /.JSON)))
+ (in (` (is (All ((, g!_) (,* varsC))
+ (-> (,* (list#each (function (_ varC) (` (-> (, varC) /.JSON)))
varsC))
- (-> ((~ (poly.code *env* inputT)) (~+ varsC))
+ (-> ((, (poly.code *env* inputT)) (,* varsC))
/.JSON)))
- (function ((~ funcC) (~+ varsC))
- (~ bodyC))))))
+ (function ((, funcC) (,* varsC))
+ (, bodyC))))))
<type>.parameter
<type>.recursive_call
... If all else fails...
@@ -230,8 +230,8 @@
[<basic> (with_template [<matcher> <decoder>]
[(do !
[_ <matcher>]
- (in (` (is (~ (@JSON#decoded inputT))
- (~! <decoder>)))))]
+ (in (` (is (, (@JSON#decoded inputT))
+ (,! <decoder>)))))]
[(<type>.exactly Any) </>.null]
[(<type>.sub Bit) </>.boolean]
@@ -242,8 +242,8 @@
<time> (with_template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! <>.codec) (~! <codec>) (~! </>.string))))))]
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! <>.codec) (,! <codec>) (,! </>.string))))))]
... [duration.Duration duration.codec]
... [instant.Instant instant.codec]
@@ -255,7 +255,7 @@
.let [g!_ (code.local "_______")
@JSON#decoded (is (-> Type Code)
(function (_ type)
- (` (</>.Parser (~ (poly.code *env* type))))))]
+ (` (</>.Parser (, (poly.code *env* type))))))]
inputT <type>.next]
(all <>.either
<basic>
@@ -263,65 +263,65 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Measure)
<type>.any))]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! <>.codec) (~! measure_codec) (~! </>.any))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! <>.codec) (,! measure_codec) (,! </>.any))))))
(do !
[[_ _ valC] (<type>.applied (all <>.and
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
decoded))]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! </>.dictionary) (~ valC))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! </>.dictionary) (, valC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .Maybe)
decoded))]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! </>.nullable) (~ subC))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! </>.nullable) (, subC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .List)
decoded))]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! </>.array) ((~! <>.some) (~ subC)))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! </>.array) ((,! <>.some) (, subC)))))))
(do !
[members (<type>.variant (<>.many decoded))
.let [last (-- (list.size members))]]
- (in (` (is (~ (@JSON#decoded inputT))
- (all ((~! <>.or))
- (~+ (list#each (function (_ [tag memberC])
+ (in (` (is (, (@JSON#decoded inputT))
+ (all ((,! <>.or))
+ (,* (list#each (function (_ [tag memberC])
(if (n.= last tag)
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.this_boolean) (~ (code.bit #1))))
- ((~! <>.after) ((~! </>.this_number) (~ (code.frac (..tag (-- tag))))))
- ((~! </>.array))))
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.this_boolean) (~ (code.bit #0))))
- ((~! <>.after) ((~! </>.this_number) (~ (code.frac (..tag tag)))))
- ((~! </>.array))))))
+ (` (|> (, memberC)
+ ((,! <>.after) ((,! </>.this_boolean) (, (code.bit #1))))
+ ((,! <>.after) ((,! </>.this_number) (, (code.frac (..tag (-- tag))))))
+ ((,! </>.array))))
+ (` (|> (, memberC)
+ ((,! <>.after) ((,! </>.this_boolean) (, (code.bit #0))))
+ ((,! <>.after) ((,! </>.this_number) (, (code.frac (..tag tag)))))
+ ((,! </>.array))))))
(list.enumeration members))))))))
(do !
[g!decoders (<type>.tuple (<>.many decoded))]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! </>.array) (all ((~! <>.and)) (~+ g!decoders)))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! </>.array) (all ((,! <>.and)) (,* g!decoders)))))))
... Type recursion
(do !
[[selfC bodyC] (<type>.recursive decoded)
.let [g! (code.local "____________")]]
- (in (` (is (~ (@JSON#decoded inputT))
- ((~! <>.rec) (.function ((~ g!) (~ selfC))
- (~ bodyC)))))))
+ (in (` (is (, (@JSON#decoded inputT))
+ ((,! <>.rec) (.function ((, g!) (, selfC))
+ (, bodyC)))))))
<type>.recursive_self
... Type applications
(do !
[[funcC argsC] (<type>.applied (<>.and decoded (<>.many decoded)))]
- (in (` ((~ funcC) (~+ argsC)))))
+ (in (` ((, funcC) (,* argsC)))))
... Polymorphism
(do !
[[funcC varsC bodyC] (<type>.polymorphic decoded)]
- (in (` (is (All ((~ g!_) (~+ varsC))
- (-> (~+ (list#each (|>> (~) </>.Parser (`)) varsC))
- (</>.Parser ((~ (poly.code *env* inputT)) (~+ varsC)))))
- (function ((~ funcC) (~+ varsC))
- (~ bodyC))))))
+ (in (` (is (All ((, g!_) (,* varsC))
+ (-> (,* (list#each (|>> (,) </>.Parser (`)) varsC))
+ (</>.Parser ((, (poly.code *env* inputT)) (,* varsC)))))
+ (function ((, funcC) (,* varsC))
+ (, bodyC))))))
<type>.parameter
<type>.recursive_call
... If all else fails...
@@ -330,10 +330,10 @@
(def .public codec
(syntax (_ [inputT <code>.any])
- (in (.list (` (is (codec.Codec /.JSON (~ inputT))
+ (in (.list (` (is (codec.Codec /.JSON (, inputT))
(implementation
- (def (~' encoded)
- ((~! ..encoded) (~ inputT)))
- (def (~' decoded)
- ((~! </>.result) ((~! ..decoded) (~ inputT))))
+ (def (,' encoded)
+ ((,! ..encoded) (, inputT)))
+ (def (,' decoded)
+ ((,! </>.result) ((,! ..decoded) (, inputT))))
)))))))