aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/poly/lux/data/format/json.lux
diff options
context:
space:
mode:
authorEduardo Julian2022-03-16 08:37:23 -0400
committerEduardo Julian2022-03-16 08:37:23 -0400
commitbf53ee92fc3c33a4885aa227e55d24f7ba3cb2c4 (patch)
tree49683a62ae8e110c62b42a9a6386bb2ddb3c47c6 /stdlib/source/poly/lux/data/format/json.lux
parentd710d9f4fc098e7c243c8a5f23cd42683f13e07f (diff)
De-sigil-ification: prefix :
Diffstat (limited to 'stdlib/source/poly/lux/data/format/json.lux')
-rw-r--r--stdlib/source/poly/lux/data/format/json.lux264
1 files changed, 132 insertions, 132 deletions
diff --git a/stdlib/source/poly/lux/data/format/json.lux b/stdlib/source/poly/lux/data/format/json.lux
index 0985eb5ed..67f6fb464 100644
--- a/stdlib/source/poly/lux/data/format/json.lux
+++ b/stdlib/source/poly/lux/data/format/json.lux
@@ -1,43 +1,43 @@
(.using
- [library
- [lux "*"
- ["[0]" debug]
- [abstract
- [monad {"+" do}]
- ["[0]" codec]]
- [control
- ["[0]" try]
- ["<>" parser
- ["</>" json]
- ["<[0]>" type]
- ["<[0]>" code]]]
- [data
- ["[0]" text
- ["%" format {"+" format}]]
- [collection
- ["[0]" list ("[1]#[0]" monad)]
- ["[0]" sequence {"+" sequence}]
- ["[0]" dictionary]]]
- [macro
- [syntax {"+" syntax:}]
- ["[0]" code]]
- [math
- [number
- ["n" nat ("[1]#[0]" decimal)]
- ["[0]" i64]
- ["[0]" int]
- ["[0]" frac]]]
- [time
- ... ["[0]" instant]
- ... ["[0]" duration]
- ["[0]" date]
- ["[0]" day]
- ["[0]" month]]
- ["[0]" type
- ["[0]" unit]
- ["[0]" poly {"+" poly:}]]]]
- [\\library
- ["[0]" / {"+" JSON}]])
+ [library
+ [lux "*"
+ ["[0]" debug]
+ [abstract
+ [monad {"+" do}]
+ ["[0]" codec]]
+ [control
+ ["[0]" try]
+ ["<>" parser
+ ["</>" json]
+ ["<[0]>" type]
+ ["<[0]>" code]]]
+ [data
+ ["[0]" text
+ ["%" format {"+" format}]]
+ [collection
+ ["[0]" list ("[1]#[0]" monad)]
+ ["[0]" sequence {"+" sequence}]
+ ["[0]" dictionary]]]
+ [macro
+ [syntax {"+" syntax:}]
+ ["[0]" code]]
+ [math
+ [number
+ ["n" nat ("[1]#[0]" decimal)]
+ ["[0]" i64]
+ ["[0]" int]
+ ["[0]" frac]]]
+ [time
+ ... ["[0]" instant]
+ ... ["[0]" duration]
+ ["[0]" date]
+ ["[0]" day]
+ ["[0]" month]]
+ ["[0]" type
+ ["[0]" unit]
+ ["[0]" poly {"+" poly:}]]]]
+ [\\library
+ ["[0]" / {"+" JSON}]])
(def: tag
(-> Nat Frac)
@@ -102,8 +102,8 @@
[(do !
[.let [g!_ (code.local_symbol "_______")]
_ <matcher>]
- (in (` (: (~ (@JSON#encoded inputT))
- <encoder>))))]
+ (in (` (is (~ (@JSON#encoded inputT))
+ <encoder>))))]
[(<type>.exactly Any) (function ((~ g!_) (~ (code.symbol ["" "0"]))) {/.#Null})]
[(<type>.sub Bit) (|>> {/.#Boolean})]
@@ -114,8 +114,8 @@
<time> (template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (: (~ (@JSON#encoded inputT))
- (|>> (# (~! <codec>) (~' encoded)) {/.#String})))))]
+ (in (` (is (~ (@JSON#encoded inputT))
+ (|>> (# (~! <codec>) (~' encoded)) {/.#String})))))]
... [duration.Duration duration.codec]
... [instant.Instant instant.codec]
@@ -125,9 +125,9 @@
(do [! <>.monad]
[*env* <type>.env
.let [g!_ (code.local_symbol "_______")
- @JSON#encoded (: (-> Type Code)
- (function (_ type)
- (` (-> (~ (poly.code *env* type)) /.JSON))))]
+ @JSON#encoded (is (-> Type Code)
+ (function (_ type)
+ (` (-> (~ (poly.code *env* type)) /.JSON))))]
inputT <type>.next]
($_ <>.either
<basic>
@@ -135,8 +135,8 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Qty)
<type>.any))]
- (in (` (: (~ (@JSON#encoded inputT))
- (# (~! qty_codec) (~' encoded))))))
+ (in (` (is (~ (@JSON#encoded inputT))
+ (# (~! qty_codec) (~' encoded))))))
(do !
[.let [g!_ (code.local_symbol "_______")
g!key (code.local_symbol "_______key")
@@ -145,61 +145,61 @@
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
encoded))]
- (in (` (: (~ (@JSON#encoded inputT))
- (|>> ((~! dictionary.entries))
- ((~! list#each) (function ((~ g!_) [(~ g!key) (~ g!val)])
- [(~ g!key) ((~ =val=) (~ g!val))]))
- ((~! dictionary.of_list) (~! text.hash))
- {/.#Object})))))
+ (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 ($_ <>.and
(<type>.exactly .Maybe)
encoded))]
- (in (` (: (~ (@JSON#encoded inputT))
- ((~! ..nullable) (~ =sub=))))))
+ (in (` (is (~ (@JSON#encoded inputT))
+ ((~! ..nullable) (~ =sub=))))))
(do !
[[_ =sub=] (<type>.applied ($_ <>.and
(<type>.exactly .List)
encoded))]
- (in (` (: (~ (@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_symbol "_______")
g!input (code.local_symbol "_______input")]
members (<type>.variant (<>.many encoded))
.let [last (-- (list.size members))]]
- (in (` (: (~ (@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))))
- #1
- ((~ g!encoded) (~ g!input))])))
- (.list (` {(~ (code.nat tag)) #0 (~ g!input)})
- (` ((~! /.json) [(~ (code.frac (..tag tag)))
- #0
- ((~ g!encoded) (~ g!input))])))))
- (list.enumeration members))))))))))
+ (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))))
+ #1
+ ((~ g!encoded) (~ g!input))])))
+ (.list (` {(~ (code.nat tag)) #0 (~ g!input)})
+ (` ((~! /.json) [(~ (code.frac (..tag tag)))
+ #0
+ ((~ g!encoded) (~ g!input))])))))
+ (list.enumeration members))))))))))
(do !
[g!encoders (<type>.tuple (<>.many encoded))
.let [g!_ (code.local_symbol "_______")
g!members (|> (list.size g!encoders)
list.indices
(list#each (|>> n#encoded code.local_symbol)))]]
- (in (` (: (~ (@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)))]))))))
+ (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_symbol "____________")]]
- (in (` (: (~ (@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 !
@@ -208,13 +208,13 @@
... Polymorphism
(do !
[[funcC varsC bodyC] (<type>.polymorphic encoded)]
- (in (` (: (All ((~ g!_) (~+ varsC))
- (-> (~+ (list#each (function (_ varC) (` (-> (~ varC) /.JSON)))
- varsC))
- (-> ((~ (poly.code *env* inputT)) (~+ varsC))
- /.JSON)))
- (function ((~ funcC) (~+ varsC))
- (~ bodyC))))))
+ (in (` (is (All ((~ g!_) (~+ varsC))
+ (-> (~+ (list#each (function (_ varC) (` (-> (~ varC) /.JSON)))
+ varsC))
+ (-> ((~ (poly.code *env* inputT)) (~+ varsC))
+ /.JSON)))
+ (function ((~ funcC) (~+ varsC))
+ (~ bodyC))))))
<type>.parameter
<type>.recursive_call
... If all else fails...
@@ -226,8 +226,8 @@
[<basic> (template [<matcher> <decoder>]
[(do !
[_ <matcher>]
- (in (` (: (~ (@JSON#decoded inputT))
- (~! <decoder>)))))]
+ (in (` (is (~ (@JSON#decoded inputT))
+ (~! <decoder>)))))]
[(<type>.exactly Any) </>.null]
[(<type>.sub Bit) </>.boolean]
@@ -238,8 +238,8 @@
<time> (template [<type> <codec>]
[(do !
[_ (<type>.exactly <type>)]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! <>.codec) (~! <codec>) (~! </>.string))))))]
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! <>.codec) (~! <codec>) (~! </>.string))))))]
... [duration.Duration duration.codec]
... [instant.Instant instant.codec]
@@ -249,9 +249,9 @@
(do [! <>.monad]
[*env* <type>.env
.let [g!_ (code.local_symbol "_______")
- @JSON#decoded (: (-> Type Code)
- (function (_ type)
- (` (</>.Parser (~ (poly.code *env* type))))))]
+ @JSON#decoded (is (-> Type Code)
+ (function (_ type)
+ (` (</>.Parser (~ (poly.code *env* type))))))]
inputT <type>.next]
($_ <>.either
<basic>
@@ -259,52 +259,52 @@
(do !
[unitT (<type>.applied (<>.after (<type>.exactly unit.Qty)
<type>.any))]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! <>.codec) (~! qty_codec) (~! </>.any))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! <>.codec) (~! qty_codec) (~! </>.any))))))
(do !
[[_ _ valC] (<type>.applied ($_ <>.and
(<type>.exactly dictionary.Dictionary)
(<type>.exactly .Text)
decoded))]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! </>.dictionary) (~ valC))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! </>.dictionary) (~ valC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .Maybe)
decoded))]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! </>.nullable) (~ subC))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! </>.nullable) (~ subC))))))
(do !
[[_ subC] (<type>.applied (<>.and (<type>.exactly .List)
decoded))]
- (in (` (: (~ (@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 (` (: (~ (@JSON#decoded inputT))
- ($_ ((~! <>.or))
- (~+ (list#each (function (_ [tag memberC])
- (if (n.= last tag)
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag (-- tag))))))
- ((~! </>.array))))
- (` (|> (~ memberC)
- ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #0))))
- ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag tag)))))
- ((~! </>.array))))))
- (list.enumeration members))))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ($_ ((~! <>.or))
+ (~+ (list#each (function (_ [tag memberC])
+ (if (n.= last tag)
+ (` (|> (~ memberC)
+ ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #1))))
+ ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag (-- tag))))))
+ ((~! </>.array))))
+ (` (|> (~ memberC)
+ ((~! <>.after) ((~! </>.boolean!) (~ (code.bit #0))))
+ ((~! <>.after) ((~! </>.number!) (~ (code.frac (..tag tag)))))
+ ((~! </>.array))))))
+ (list.enumeration members))))))))
(do !
[g!decoders (<type>.tuple (<>.many decoded))]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! </>.array) ($_ ((~! <>.and)) (~+ g!decoders)))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! </>.array) ($_ ((~! <>.and)) (~+ g!decoders)))))))
... Type recursion
(do !
[[selfC bodyC] (<type>.recursive decoded)
.let [g! (code.local_symbol "____________")]]
- (in (` (: (~ (@JSON#decoded inputT))
- ((~! <>.rec) (.function ((~ g!) (~ selfC))
- (~ bodyC)))))))
+ (in (` (is (~ (@JSON#decoded inputT))
+ ((~! <>.rec) (.function ((~ g!) (~ selfC))
+ (~ bodyC)))))))
<type>.recursive_self
... Type applications
(do !
@@ -313,11 +313,11 @@
... Polymorphism
(do !
[[funcC varsC bodyC] (<type>.polymorphic decoded)]
- (in (` (: (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...
@@ -325,10 +325,10 @@
))))
(syntax: .public (codec [inputT <code>.any])
- (in (.list (` (: (codec.Codec /.JSON (~ inputT))
- (implementation
- (def: (~' encoded)
- ((~! ..encoded) (~ inputT)))
- (def: (~' decoded)
- ((~! </>.result) ((~! ..decoded) (~ inputT))))
- ))))))
+ (in (.list (` (is (codec.Codec /.JSON (~ inputT))
+ (implementation
+ (def: (~' encoded)
+ ((~! ..encoded) (~ inputT)))
+ (def: (~' decoded)
+ ((~! </>.result) ((~! ..decoded) (~ inputT))))
+ ))))))