diff options
Diffstat (limited to 'stdlib/source')
-rw-r--r-- | stdlib/source/lux/data/format/json.lux | 22 | ||||
-rw-r--r-- | stdlib/source/lux/data/text.lux | 46 | ||||
-rw-r--r-- | stdlib/source/lux/data/text/format.lux | 2 | ||||
-rw-r--r-- | stdlib/source/lux/data/text/lexer.lux | 13 | ||||
-rw-r--r-- | stdlib/source/lux/macro/code.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/macro/poly/text-encoder.lux | 2 |
6 files changed, 35 insertions, 54 deletions
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux index 573849b9e..0ce1b602a 100644 --- a/stdlib/source/lux/data/format/json.lux +++ b/stdlib/source/lux/data/format/json.lux @@ -109,11 +109,11 @@ ## [Values] (def: #hidden (show-null _) (-> Null Text) "null") (do-template [<name> <type> <codec>] - [(def: <name> (-> <type> Text) (:: <codec> encode))] + [(def: <name> (-> <type> Text) <codec>)] - [show-boolean Boolean bool;Codec<Text,Bool>] - [show-number Number number;Codec<Text,Real>] - [show-string String text;Codec<Text,Text>]) + [show-boolean Boolean (:: bool;Codec<Text,Bool> encode)] + [show-number Number (:: number;Codec<Text,Real> encode)] + [show-string String text;encode]) (def: (show-array show-json elems) (-> (-> JSON Text) (-> Array Text)) @@ -126,7 +126,7 @@ (format "{" (|> object d;entries - (L/map (function [[key value]] (format (:: text;Codec<Text,Text> encode key) ":" (show-json value)))) + (L/map (function [[key value]] (format (show-string key) ":" (show-json value)))) (text;join-with ",")) "}")) @@ -395,7 +395,7 @@ [text Text #String "text" id] ) -(do-template [<test> <check> <type> <eq> <codec> <tag> <desc> <pre>] +(do-template [<test> <check> <type> <eq> <encoder> <tag> <desc> <pre>] [(def: #export (<test> test json) {#;doc (#;TextA (format "Asks whether a JSON value is a " <desc> "."))} (-> <type> (Parser Bool)) @@ -415,15 +415,15 @@ (if (:: <eq> = test value) (#R;Success []) (#R;Error (format "Value mismatch: " - (:: <codec> encode test) "=/=" (:: <codec> encode value))))) + (<encoder> test) "=/=" (<encoder> value))))) _ (#R;Error (format "JSON value is not a " <desc> ": " (show-json json)))))] - [bool? bool! Bool bool;Eq<Bool> bool;Codec<Text,Bool> #Boolean "boolean" id] - [int? int! Int number;Eq<Int> number;Codec<Text,Int> #Number "number" real-to-int] - [real? real! Real number;Eq<Real> number;Codec<Text,Real> #Number "number" id] - [text? text! Text text;Eq<Text> text;Codec<Text,Text> #String "string" id] + [bool? bool! Bool bool;Eq<Bool> (:: bool;Codec<Text,Bool> encode) #Boolean "boolean" id] + [int? int! Int number;Eq<Int> (:: number;Codec<Text,Int> encode) #Number "number" real-to-int] + [real? real! Real number;Eq<Real> (:: number;Codec<Text,Real> encode) #Number "number" id] + [text? text! Text text;Eq<Text> text;encode #String "string" id] ) (def: #export (char json) diff --git a/stdlib/source/lux/data/text.lux b/stdlib/source/lux/data/text.lux index ad33c67ac..dca74423c 100644 --- a/stdlib/source/lux/data/text.lux +++ b/stdlib/source/lux/data/text.lux @@ -134,39 +134,19 @@ (open Monoid<Text>) -(struct: #export _ (Codec Text Text) - (def: (encode original) - (let [escaped (|> original - (replace-all "\\" "\\\\") - (replace-all "\t" "\\t") - (replace-all "\v" "\\v") - (replace-all "\b" "\\b") - (replace-all "\n" "\\n") - (replace-all "\r" "\\r") - (replace-all "\f" "\\f") - (replace-all "\"" "\\\"") - )] - ($_ append "\"" escaped "\""))) - - (def: (decode input) - (if (and (starts-with? "\"" input) - (ends-with? "\"" input)) - (case (clip +1 (n.dec (size input)) input) - (#;Some input') - (|> input' - (replace-all "\\\\" "\\") - (replace-all "\\t" "\t") - (replace-all "\\v" "\v") - (replace-all "\\b" "\b") - (replace-all "\\n" "\n") - (replace-all "\\r" "\r") - (replace-all "\\f" "\f") - (replace-all "\\\"" "\"") - #;Some) - - #;None - (#;Left "Could not decode text")) - (#;Left "Could not decode text")))) +(def: #export (encode original) + (-> Text Text) + (let [escaped (|> original + (replace-all "\\" "\\\\") + (replace-all "\t" "\\t") + (replace-all "\v" "\\v") + (replace-all "\b" "\\b") + (replace-all "\n" "\\n") + (replace-all "\r" "\\r") + (replace-all "\f" "\\f") + (replace-all "\"" "\\\"") + )] + ($_ append "\"" escaped "\""))) (struct: #export _ (Hash Text) (def: eq Eq<Text>) diff --git a/stdlib/source/lux/data/text/format.lux b/stdlib/source/lux/data/text/format.lux index 127921e41..639a2f39b 100644 --- a/stdlib/source/lux/data/text/format.lux +++ b/stdlib/source/lux/data/text/format.lux @@ -39,7 +39,7 @@ [%d Deg (:: number;Codec<Text,Deg> encode)] [%r Real (:: number;Codec<Text,Real> encode)] [%c Char (:: char;Codec<Text,Char> encode)] - [%t Text (:: text;Codec<Text,Text> encode)] + [%t Text text;encode] [%ident Ident (:: ident;Codec<Text,Ident> encode)] [%code Code code;to-text] [%type Type type;to-text] diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/data/text/lexer.lux index 8c40af821..3d7423ca2 100644 --- a/stdlib/source/lux/data/text/lexer.lux +++ b/stdlib/source/lux/data/text/lexer.lux @@ -59,8 +59,7 @@ (case (text;split (text;size reference) input) #;None (#R;Error "") (#;Some [_ input']) (#R;Success [input' []])) - (let [(^open "T/") text;Codec<Text,Text>] - (#R;Error (format "Invalid match: " (T/encode reference) " @ " (T/encode input))))))) + (#R;Error (format "Invalid match: " (text;encode reference) " @ " (text;encode input)))))) (def: #export (this? reference) {#;doc "Lex a text if it matches the given sample."} @@ -79,7 +78,7 @@ (function [input] (case input "" (#R;Success [input []]) - _ (#R;Error (format "The text input has not been fully consumed @ " (:: text;Codec<Text,Text> encode input))) + _ (#R;Error (format "The text input has not been fully consumed @ " (text;encode input))) ))) (def: #export peek @@ -107,7 +106,7 @@ [input get-input char any #let [char' (|> char (text;nth +0) assume)] - _ (p;assert (format "Character is not within range: " (C/encode bottom) "-" (C/encode top) " @ " (:: text;Codec<Text,Text> encode input)) + _ (p;assert (format "Character is not within range: " (C/encode bottom) "-" (C/encode top) " @ " (text;encode input)) (and (C/>= bottom char') (C/<= top char')))] (wrap char))) @@ -155,7 +154,7 @@ _ (#R;Error "")) - (#R;Error (format "Character (" init ") is not one of: " options " @ " (:: text;Codec<Text,Text> encode input)))) + (#R;Error (format "Character (" init ") is not one of: " options " @ " (text;encode input)))) _ (#R;Error "Cannot parse character from empty text.")))) @@ -173,7 +172,7 @@ _ (#R;Error "")) - (#R;Error (format "Character (" init ") is one of: " options " @ " (:: text;Codec<Text,Text> encode input)))) + (#R;Error (format "Character (" init ") is one of: " options " @ " (text;encode input)))) _ (#R;Error "Cannot parse character from empty text.")))) @@ -190,7 +189,7 @@ (#;Some [input' output]) (if (p output) (#R;Success [input' (char;as-text output)]) - (#R;Error (format "Character does not satisfy predicate: " (:: text;Codec<Text,Text> encode input)))) + (#R;Error (format "Character does not satisfy predicate: " (text;encode input)))) _ (#R;Error "Cannot parse character from empty text.")))) diff --git a/stdlib/source/lux/macro/code.lux b/stdlib/source/lux/macro/code.lux index 6d2dd4604..caa846e61 100644 --- a/stdlib/source/lux/macro/code.lux +++ b/stdlib/source/lux/macro/code.lux @@ -108,9 +108,11 @@ [#;Deg Codec<Text,Deg>] [#;Real Codec<Text,Real>] [#;Char char;Codec<Text,Char>] - [#;Text text;Codec<Text,Text>] [#;Symbol Codec<Text,Ident>]) + [_ (#;Text value)] + (text;encode value) + [_ (#;Tag ident)] (Text/append "#" (:: Codec<Text,Ident> encode ident)) diff --git a/stdlib/source/lux/macro/poly/text-encoder.lux b/stdlib/source/lux/macro/poly/text-encoder.lux index e1250c9e7..af0cff4f8 100644 --- a/stdlib/source/lux/macro/poly/text-encoder.lux +++ b/stdlib/source/lux/macro/poly/text-encoder.lux @@ -49,7 +49,7 @@ [Deg poly;deg (:: number;Codec<Text,Deg> encode)] [Real poly;real (:: number;Codec<Text,Real> encode)] [Char poly;char (:: char;Codec<Text,Char> encode)] - [Text poly;text (:: text;Codec<Text,Text> encode)])] + [Text poly;text text;encode])] ($_ macro;either ## Primitives <basic> |