diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/data/format/json.lux | 56 |
1 files changed, 28 insertions, 28 deletions
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux index 535de1b53..863c8cd3e 100644 --- a/stdlib/source/lux/data/format/json.lux +++ b/stdlib/source/lux/data/format/json.lux @@ -22,7 +22,7 @@ [dict #+ Dict])) [macro #+ Monad<Lux> with-gensyms] (macro [syntax #+ syntax:] - [ast] + [code] [poly #+ poly:]) [type] )) @@ -77,10 +77,10 @@ (^template [<ast-tag> <ctor> <json-tag>] [_ (<ast-tag> value)] (wrap (list (` (: JSON (<json-tag> (~ (<ctor> value)))))))) - ([#;Bool ast;bool #Boolean] - [#;Int (|>. int-to-real ast;real) #Number] - [#;Real ast;real #Number] - [#;Text ast;text #String]) + ([#;Bool code;bool #Boolean] + [#;Int (|>. int-to-real code;real) #Number] + [#;Real code;real #Number] + [#;Text code;text #String]) [_ (#;Tag ["" "null"])] (wrap (list (` (: JSON #Null)))) @@ -94,7 +94,7 @@ (function [[slot value]] (case slot [_ (#;Text key-name)] - (wrap (` [(~ (ast;text key-name)) (~ (wrapper value))])) + (wrap (` [(~ (code;text key-name)) (~ (wrapper value))])) _ (macro;fail "Wrong syntax for JSON object."))) @@ -709,8 +709,8 @@ ## [Syntax] (type: Shape - (#ArrayShape (List AST)) - (#ObjectShape (List [Text AST]))) + (#ArrayShape (List Code)) + (#ObjectShape (List [Text Code]))) (def: _shape^ (syntax;Syntax Shape) @@ -729,13 +729,13 @@ parsers (|> parts (list;zip2 (list;indices array-size)) (List/map (function [[idx parser]] - (` (nth (~ (ast;nat idx)) (~ parser))))))] + (` (nth (~ (code;nat idx)) (~ parser))))))] (wrap (list (` ($_ seq (~@ parsers)))))) (#ObjectShape kvs) (let [fields (List/map product;left kvs) parsers (List/map (function [[field-name parser]] - (` (field (~ (ast;text field-name)) (~ parser)))) + (` (field (~ (code;text field-name)) (~ parser)))) kvs)] (wrap (list (` ($_ seq (~@ parsers)))))) )) @@ -752,16 +752,16 @@ parsers (|> parts (list;zip2 (list;indices array-size)) (List/map (function [[idx parser]] - (` (nth (~ (ast;nat idx)) (~ parser))))))] - (wrap (list (` (ensure (array-size! (~ (ast;nat array-size))) + (` (nth (~ (code;nat idx)) (~ parser))))))] + (wrap (list (` (ensure (array-size! (~ (code;nat array-size))) ($_ seq (~@ parsers))))))) (#ObjectShape kvs) (let [fields (List/map product;left kvs) parsers (List/map (function [[field-name parser]] - (` (field (~ (ast;text field-name)) (~ parser)))) + (` (field (~ (code;text field-name)) (~ parser)))) kvs)] - (wrap (list (` (ensure (object-fields! (list (~@ (List/map ast;text fields)))) + (wrap (list (` (ensure (object-fields! (list (~@ (List/map code;text fields)))) ($_ seq (~@ parsers))))))) )) @@ -771,13 +771,13 @@ List/map) (poly: #hidden (Codec<JSON,?>//encode *env* :x:) - (let [->Codec//encode (: (-> AST AST) + (let [->Codec//encode (: (-> Code Code) (function [.type.] (` (-> (~ .type.) JSON))))] (with-expansions [<basic> (do-template [<type> <matcher> <encoder>] [(do @ [_ (<matcher> :x:)] (wrap (` (: (~ (->Codec//encode (` <type>))) <encoder>))))] - [Unit poly;unit (function [(~ (ast;symbol ["" "0"]))] #Null)] + [Unit poly;unit (function [(~ (code;symbol ["" "0"]))] #Null)] [Bool poly;bool ;;gen-boolean] [Int poly;int (|>. ;int-to-real ;;gen-number)] [Real poly;real ;;gen-number] @@ -839,10 +839,10 @@ pattern-matching (mapM @ (function [[name :case:]] (do @ - [#let [tag (ast;tag name)] + [#let [tag (code;tag name)] encoder (Codec<JSON,?>//encode new-*env* :case:)] (wrap (list (` ((~ tag) (~ g!case))) - (` (;;json [(~ (ast;text (product;right name))) + (` (;;json [(~ (code;text (product;right name))) ((~ encoder) (~ g!case))])))))) members) #let [:x:+ (case g!vars @@ -868,8 +868,8 @@ (function [[name :slot:]] (do @ [encoder (Codec<JSON,?>//encode new-*env* :slot:)] - (wrap [(` (~ (ast;text (product;right name)))) - (` ((~ encoder) (get@ (~ (ast;tag name)) (~ g!input))))]))) + (wrap [(` (~ (code;text (product;right name)))) + (` ((~ encoder) (get@ (~ (code;tag name)) (~ g!input))))]))) members) #let [:x:+ (case g!vars #;Nil @@ -881,7 +881,7 @@ (~ (->Codec//encode (` ((~ (type;to-ast :x:)) (~@ g!vars)))))))))]] (wrap (` (: (~ :x:+) (function [(~@ g!vars) (~ g!input)] - (;;json (~ (ast;record synthesis)))) + (;;json (~ (code;record synthesis)))) ))))) (with-gensyms [g!type-fun g!case] (do @ @@ -923,7 +923,7 @@ )))) (poly: #hidden (Codec<JSON,?>//decode *env* :x:) - (let [->Codec//decode (: (-> AST AST) + (let [->Codec//decode (: (-> Code Code) (function [.type.] (` (-> JSON (Error (~ .type.))))))] (with-expansions [<basic> (do-template [<type> <matcher> <decoder>] @@ -992,10 +992,10 @@ pattern-matching (mapM @ (function [[name :case:]] (do @ - [#let [tag (ast;tag name)] + [#let [tag (code;tag name)] decoder (Codec<JSON,?>//decode new-*env* :case:)] (wrap (list (` (do Monad<Parser> - [(~ g!_) (;;nth +0 (;;text! (~ (ast;text (product;right name))))) + [(~ g!_) (;;nth +0 (;;text! (~ (code;text (product;right name))))) (~ g!_) (;;nth +1 (~ decoder))] ((~ (' wrap)) ((~ tag) (~ g!_))))))))) members) @@ -1026,10 +1026,10 @@ extraction (mapM @ (function [[name :slot:]] (do @ - [#let [g!member (ast;symbol ["" (product;right name)])] + [#let [g!member (code;symbol ["" (product;right name)])] decoder (Codec<JSON,?>//decode new-*env* :slot:)] (wrap (list g!member - (` (;;get (~ (ast;text (product;right name))) (~ g!input))) + (` (;;get (~ (code;text (product;right name))) (~ g!input))) g!member (` ((~ decoder) (~ g!member))))))) members) @@ -1045,8 +1045,8 @@ (function [(~@ g!vars) (~ g!input)] (do Monad<Error> [(~@ (List/join extraction))] - ((~ (' wrap)) (~ (ast;record (List/map (function [[name :slot:]] - [(ast;tag name) (ast;symbol ["" (product;right name)])]) + ((~ (' wrap)) (~ (code;record (List/map (function [[name :slot:]] + [(code;tag name) (code;symbol ["" (product;right name)])]) members)))))) ))))) (with-gensyms [g!type-fun g!case g!input] |