aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/data/format
diff options
context:
space:
mode:
authorEduardo Julian2019-03-15 00:23:49 -0400
committerEduardo Julian2019-03-15 00:23:49 -0400
commitf9d4d316ef9666f6b122b0eec8180351216e95f8 (patch)
tree2a66da0c7552dcb3642ba37afd53f1bef44eef41 /stdlib/source/lux/data/format
parent9449d89f611ba3192373fdeb6848d02707ff1292 (diff)
Changed the convention for the structure opening separator from "/" to ";", to avoid confusion since "/" is used for relative module paths.
Diffstat (limited to 'stdlib/source/lux/data/format')
-rw-r--r--stdlib/source/lux/data/format/binary.lux18
-rw-r--r--stdlib/source/lux/data/format/css.lux8
-rw-r--r--stdlib/source/lux/data/format/css/value.lux22
-rw-r--r--stdlib/source/lux/data/format/html.lux18
-rw-r--r--stdlib/source/lux/data/format/json.lux86
-rw-r--r--stdlib/source/lux/data/format/markdown.lux8
-rw-r--r--stdlib/source/lux/data/format/xml.lux62
7 files changed, 111 insertions, 111 deletions
diff --git a/stdlib/source/lux/data/format/binary.lux b/stdlib/source/lux/data/format/binary.lux
index 361748c49..be2e105ee 100644
--- a/stdlib/source/lux/data/format/binary.lux
+++ b/stdlib/source/lux/data/format/binary.lux
@@ -4,7 +4,7 @@
[monoid (#+ Monoid)]
["." fold]
[monad (#+ do Monad)]
- ["." parser (#+ Parser) ("#/." functor)]
+ ["." parser (#+ Parser) ("#;." functor)]
["ex" exception (#+ exception:)]
[equivalence (#+ Equivalence)]]
[data
@@ -17,7 +17,7 @@
[format (#+ %n)]]
[collection
["." list]
- ["." row (#+ Row) ("#/." functor)]]]
+ ["." row (#+ Row) ("#;." functor)]]]
[type (#+ :share)]
[world
["." binary (#+ Binary)]]])
@@ -78,9 +78,9 @@
(-> a' a)
(Format a)
(Format a')))
- (let [(^open "_/.") format]
- {#reader (|> _/reader (parser/map post-read))
- #writer (|>> pre-write _/writer)}))
+ (let [(^open "_;.") format]
+ {#reader (|> _;reader (parser;map post-read))
+ #writer (|>> pre-write _;writer)}))
(def: #export (read format input)
(All [a] (-> (Format a) Binary (Error a)))
@@ -287,13 +287,13 @@
value (if (n/= original-count capped-count)
value
(|> value row.to-list (list.take capped-count) row.from-list))
- (^open "mutation/.") ..monoid
+ (^open "mutation;.") ..monoid
[size mutation] (|> value
- (row/map (get@ #writer valueF))
+ (row;map (get@ #writer valueF))
(:: row.fold fold
(function (_ post pre)
- (mutation/compose pre post))
- mutation/identity))]
+ (mutation;compose pre post))
+ mutation;identity))]
[(n/+ <size> size)
(function (_ offset binary)
(error.assume
diff --git a/stdlib/source/lux/data/format/css.lux b/stdlib/source/lux/data/format/css.lux
index accc59e0e..736a5e6f3 100644
--- a/stdlib/source/lux/data/format/css.lux
+++ b/stdlib/source/lux/data/format/css.lux
@@ -8,7 +8,7 @@
format
["." encoding (#+ Encoding)]]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[type
abstract]
[world
@@ -59,7 +59,7 @@
["font-style" (|> font (get@ #/font.style) (maybe.default /value.normal-style) /value.value)]
["font-weight" (|> font (get@ #/font.weight) (maybe.default /value.normal-weight) /value.value)]
with-unicode)
- (list/map (function (_ [property value])
+ (list;map (function (_ [property value])
(format property ": " value ";")))
(text.join-with /style.separator)
(text.enclose ["{" "}"])
@@ -87,7 +87,7 @@
(-> (Value Animation) (List Frame) (CSS Special))
(:abstraction (format "@keyframes " (/value.value animation) " {"
(|> frames
- (list/map (function (_ frame)
+ (list;map (function (_ frame)
(format (/value.percentage (get@ #when frame)) " {"
(/style.inline (get@ #what frame))
"}")))
@@ -107,7 +107,7 @@
(|> css
:representation
(text.split-all-with ..css-separator)
- (list/map (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
+ (list;map (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
(text.join-with ..css-separator)
:abstraction))
diff --git a/stdlib/source/lux/data/format/css/value.lux b/stdlib/source/lux/data/format/css/value.lux
index a681bde1a..8967ed90a 100644
--- a/stdlib/source/lux/data/format/css/value.lux
+++ b/stdlib/source/lux/data/format/css/value.lux
@@ -9,7 +9,7 @@
["." text
format]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[type
abstract]
[macro
@@ -797,7 +797,7 @@
(def: #export (cubic-bezier p0 p1 p2 p3)
(-> Frac Frac Frac Frac (Value Timing))
(|> (list p0 p1 p2 p3)
- (list/map %number)
+ (list;map %number)
(..apply "cubic-bezier")))
(do-template [<name> <brand>]
@@ -963,7 +963,7 @@
(let [[now after] next]
(..apply <function> (list& (:representation Angle angle)
(with-hint now)
- (list/map with-hint after)))))]
+ (list;map with-hint after)))))]
[linear-gradient "linear-gradient"]
[repeating-linear-gradient "repeating-linear-gradient"]
@@ -1090,7 +1090,7 @@
[now after] next]
(..apply <function> (list& (..shape shape)
(with-hint now)
- (list/map with-hint after)))))]
+ (list;map with-hint after)))))]
[radial-gradient "radial-gradient"]
[repeating-radial-gradient "repeating-radial-gradient"]
@@ -1162,7 +1162,7 @@
(case options
(#.Cons _)
(|> options
- (list/map ..font-name)
+ (list;map ..font-name)
(text.join-with ",")
(:abstraction Value))
@@ -1201,7 +1201,7 @@
(-> (List (List (Maybe (Value Grid)))) (Value Grid-Template))
(let [empty (: (Value Grid)
(:abstraction "."))]
- (|>> (list/map (|>> (list/map (|>> (maybe.default empty)
+ (|>> (list;map (|>> (list;map (|>> (maybe.default empty)
:representation))
(text.join-with ..grid-column-separator)
(text.enclose ["'" "'"])))
@@ -1238,7 +1238,7 @@
(def: #export (quotes [left0 right0] [left1 right1])
(-> [Quote Quote] [Quote Quote] (Value Quotes))
(|> (list left0 right0 left1 right1)
- (list/map (|>> ..quote-text %t))
+ (list;map (|>> ..quote-text %t))
(text.join-with ..quote-separator)
:abstraction))
@@ -1248,7 +1248,7 @@
[Frac Frac]
(Value Transform))
(|> (list a b c d tx ty)
- (list/map %number)
+ (list;map %number)
(..apply "matrix")))
(def: #export (matrix-3d [a0 b0 c0 d0] [a1 b1 c1 d1] [a2 b2 c2 d2] [a3 b3 c3 d3])
@@ -1258,14 +1258,14 @@
[Frac Frac Frac Frac]
(Value Transform))
(|> (list a0 b0 c0 d0 a1 b1 c1 d1 a2 b2 c2 d2 a3 b3 c3 d3)
- (list/map %number)
+ (list;map %number)
(..apply "matrix3d")))
(do-template [<name> <function> <input-types> <input-values>]
[(`` (def: #export (<name> [(~~ (template.splice <input-values>))])
(-> [(~~ (template.splice <input-types>))] (Value Transform))
(|> (list (~~ (template.splice <input-values>)))
- (list/map %number)
+ (list;map %number)
(..apply <function>))))]
[translate-2d "translate" [Frac Frac] [x y]]
@@ -1287,7 +1287,7 @@
[(`` (def: #export (<name> [(~~ (template.splice <input-values>))])
(-> [(~~ (template.splice <input-types>))] (Value Transform))
(|> (list (~~ (template.splice <input-values>)))
- (list/map ..angle)
+ (list;map ..angle)
(..apply <function>))))]
[rotate-2d "rotate" [Angle] [angle]]
diff --git a/stdlib/source/lux/data/format/html.lux b/stdlib/source/lux/data/format/html.lux
index a8766b651..0cf59690c 100644
--- a/stdlib/source/lux/data/format/html.lux
+++ b/stdlib/source/lux/data/format/html.lux
@@ -6,7 +6,7 @@
["." text
format]
[collection
- ["." list ("#/." functor fold)]]]
+ ["." list ("#;." functor fold)]]]
["." function]
[type
abstract]
@@ -58,7 +58,7 @@
(def: attributes
(-> Attributes Text)
- (|>> (list/map (function (_ [key val])
+ (|>> (list;map (function (_ [key val])
(format key "=" text.double-quote (..sanitize val) text.double-quote)))
(text.join-with " ")))
@@ -253,7 +253,7 @@
(def: (%polygon [first second third extra])
(Format Polygon)
(|> (list& first second third extra)
- (list/map %coord)
+ (list;map %coord)
(text.join-with ..coord-separator)))
(type: #export Shape
@@ -289,13 +289,13 @@
(-> Attributes (List [Attributes Shape]) Image Image)
($_ ..and
for
- (case (list/map (product.uncurry ..area) areas)
+ (case (list;map (product.uncurry ..area) areas)
#.Nil
(..empty "map" attributes)
(#.Cons head tail)
(..tag "map" attributes
- (list/fold (function.flip ..and) head tail)))))
+ (list;fold (function.flip ..and) head tail)))))
(do-template [<name> <tag> <type>]
[(def: #export <name>
@@ -449,7 +449,7 @@
(def: #export (description-list attributes descriptions)
(-> Attributes (List [Content Element]) Element)
- (case (list/map (function (_ [term description])
+ (case (list;map (function (_ [term description])
($_ ..and
(..term term)
(..description description)))
@@ -459,7 +459,7 @@
(#.Cons head tail)
(..tag "dl" attributes
- (list/fold (function.flip ..and) head tail))))
+ (list;fold (function.flip ..and) head tail))))
(def: #export p ..paragraph)
@@ -511,14 +511,14 @@
(def: #export (table attributes caption columns headers rows footer)
(-> Attributes (Maybe Content) (Maybe Column) Header (List Cell) (Maybe Cell) Element)
(let [head (..table-head (..table-row headers))
- content (case (list/map table-row rows)
+ content (case (list;map table-row rows)
#.Nil
head
(#.Cons first rest)
(..and head
(..table-body
- (list/fold (function.flip ..and) first rest))))
+ (list;fold (function.flip ..and) first rest))))
content (case footer
#.None
content
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux
index f2f7eef35..a213fa1d0 100644
--- a/stdlib/source/lux/data/format/json.lux
+++ b/stdlib/source/lux/data/format/json.lux
@@ -5,7 +5,7 @@
["." monad (#+ Monad do)]
[equivalence (#+ Equivalence)]
codec
- ["p" parser (#+ Parser) ("#/." monad)]
+ ["p" parser (#+ Parser) ("#;." monad)]
["ex" exception (#+ exception:)]]
[data
["." bit]
@@ -14,12 +14,12 @@
["." sum]
["." product]
[number
- ["." frac ("#/." decimal)]]
- ["." text ("#/." equivalence monoid)
+ ["." frac ("#;." decimal)]]
+ ["." text ("#;." equivalence monoid)
["l" lexer]]
[collection
- ["." list ("#/." fold monad)]
- ["." row (#+ Row row) ("#/." monad)]
+ ["." list ("#;." fold monad)]
+ ["." row (#+ Row row) ("#;." monad)]
["." dictionary (#+ Dictionary)]]]
["." macro (#+ monad with-gensyms)
["s" syntax (#+ syntax:)]
@@ -76,7 +76,7 @@
(wrap (list (` (: JSON #Null))))
[_ (#.Tuple members)]
- (wrap (list (` (: JSON (#Array ((~! row) (~+ (list/map wrapper members))))))))
+ (wrap (list (` (: JSON (#Array ((~! row) (~+ (list;map wrapper members))))))))
[_ (#.Record pairs)]
(do ..monad
@@ -102,7 +102,7 @@
(#error.Success (dictionary.keys obj))
_
- (#error.Failure ($_ text/compose "Cannot get the fields of a non-object."))))
+ (#error.Failure ($_ text;compose "Cannot get the fields of a non-object."))))
(def: #export (get key json)
{#.doc "A JSON object field getter."}
@@ -114,10 +114,10 @@
(#error.Success value)
#.None
- (#error.Failure ($_ text/compose "Missing field '" key "' on object.")))
+ (#error.Failure ($_ text;compose "Missing field '" key "' on object.")))
_
- (#error.Failure ($_ text/compose "Cannot get field '" key "' of a non-object."))))
+ (#error.Failure ($_ text;compose "Cannot get field '" key "' of a non-object."))))
(def: #export (set key value json)
{#.doc "A JSON object field setter."}
@@ -127,18 +127,18 @@
(#error.Success (#Object (dictionary.put key value obj)))
_
- (#error.Failure ($_ text/compose "Cannot set field '" key "' of a non-object."))))
+ (#error.Failure ($_ text;compose "Cannot set field '" key "' of a non-object."))))
(do-template [<name> <tag> <type> <desc>]
[(def: #export (<name> key json)
- {#.doc (code.text ($_ text/compose "A JSON object field getter for " <desc> "."))}
+ {#.doc (code.text ($_ text;compose "A JSON object field getter for " <desc> "."))}
(-> Text JSON (Error <type>))
(case (get key json)
(#error.Success (<tag> value))
(#error.Success value)
(#error.Success _)
- (#error.Failure ($_ text/compose "Wrong value type at key: " key))
+ (#error.Failure ($_ text;compose "Wrong value type at key: " key))
(#error.Failure error)
(#error.Failure error)))]
@@ -165,7 +165,7 @@
[(#Array xs) (#Array ys)]
(and (n/= (row.size xs) (row.size ys))
- (list/fold (function (_ idx prev)
+ (list;fold (function (_ idx prev)
(and prev
(maybe.default #0
(do maybe.monad
@@ -177,7 +177,7 @@
[(#Object xs) (#Object ys)]
(and (n/= (dictionary.size xs) (dictionary.size ys))
- (list/fold (function (_ [xk xv] prev)
+ (list;fold (function (_ [xk xv] prev)
(and prev
(case (dictionary.get xk ys)
#.None #0
@@ -208,16 +208,16 @@
(def: (show-array show-json elems)
(-> (-> JSON Text) (-> Array Text))
- ($_ text/compose "["
- (|> elems (row/map show-json) row.to-list (text.join-with ","))
+ ($_ text;compose "["
+ (|> elems (row;map show-json) row.to-list (text.join-with ","))
"]"))
(def: (show-object show-json object)
(-> (-> JSON Text) (-> Object Text))
- ($_ text/compose "{"
+ ($_ text;compose "{"
(|> object
dictionary.entries
- (list/map (function (_ [key value]) ($_ text/compose (show-string key) ":" (show-json value))))
+ (list;map (function (_ [key value]) ($_ text;compose (show-string key) ":" (show-json value))))
(text.join-with ","))
"}"))
@@ -241,7 +241,7 @@
(exception: #export (unconsumed-input {input (List JSON)})
(|> input
- (list/map show-json)
+ (list;map show-json)
(text.join-with text.new-line)))
(exception: #export (empty-input)
@@ -279,7 +279,7 @@
(do-template [<name> <type> <tag> <desc>]
[(def: #export <name>
- {#.doc (code.text ($_ text/compose "Reads a JSON value as " <desc> "."))}
+ {#.doc (code.text ($_ text;compose "Reads a JSON value as " <desc> "."))}
(Reader <type>)
(do p.monad
[head any]
@@ -288,7 +288,7 @@
(wrap value)
_
- (fail ($_ text/compose "JSON value is not " <desc> ".")))))]
+ (fail ($_ text;compose "JSON value is not " <desc> ".")))))]
[null Any #Null "null"]
[boolean Bit #Boolean "boolean"]
@@ -298,7 +298,7 @@
(do-template [<test> <check> <type> <eq> <encoder> <tag> <desc>]
[(def: #export (<test> test)
- {#.doc (code.text ($_ text/compose "Asks whether a JSON value is a " <desc> "."))}
+ {#.doc (code.text ($_ text;compose "Asks whether a JSON value is a " <desc> "."))}
(-> <type> (Reader Bit))
(do p.monad
[head any]
@@ -307,10 +307,10 @@
(wrap (:: <eq> = test value))
_
- (fail ($_ text/compose "JSON value is not " <desc> ".")))))
+ (fail ($_ text;compose "JSON value is not " <desc> ".")))))
(def: #export (<check> test)
- {#.doc (code.text ($_ text/compose "Ensures a JSON value is a " <desc> "."))}
+ {#.doc (code.text ($_ text;compose "Ensures a JSON value is a " <desc> "."))}
(-> <type> (Reader Any))
(do p.monad
[head any]
@@ -318,10 +318,10 @@
(<tag> value)
(if (:: <eq> = test value)
(wrap [])
- (fail ($_ text/compose "Value mismatch: " (<encoder> test) " =/= " (<encoder> value))))
+ (fail ($_ text;compose "Value mismatch: " (<encoder> test) " =/= " (<encoder> value))))
_
- (fail ($_ text/compose "JSON value is not a " <desc> ".")))))]
+ (fail ($_ text;compose "JSON value is not a " <desc> ".")))))]
[boolean? boolean! Bit bit.equivalence encode-boolean #Boolean "boolean"]
[number? number! Frac frac.equivalence (:: frac.decimal encode) #Number "number"]
@@ -353,7 +353,7 @@
(fail (ex.construct unconsumed-input remainder))))
_
- (fail (text/compose "JSON value is not an array: " (show-json head))))))
+ (fail (text;compose "JSON value is not an array: " (show-json head))))))
(def: #export (object parser)
{#.doc "Parses a JSON object. Use this with the 'field' combinator."}
@@ -364,7 +364,7 @@
(#Object kvs)
(case (p.run (|> kvs
dictionary.entries
- (list/map (function (_ [key value])
+ (list;map (function (_ [key value])
(list (#String key) value)))
list.concat)
parser)
@@ -380,7 +380,7 @@
(fail (ex.construct unconsumed-input remainder))))
_
- (fail (text/compose "JSON value is not an object: " (show-json head))))))
+ (fail (text;compose "JSON value is not an object: " (show-json head))))))
(def: #export (field field-name parser)
{#.doc "Parses a field inside a JSON object. Use this inside the 'object' combinator."}
@@ -388,7 +388,7 @@
(function (recur inputs)
(case inputs
(^ (list& (#String key) value inputs'))
- (if (text/= key field-name)
+ (if (text;= key field-name)
(case (p.run (list value) parser)
(#error.Success [#.Nil output])
(#error.Success [inputs' output])
@@ -456,8 +456,8 @@
[mark (l.one-of "eE")
signed?' (l.this? "-")
offset (l.many l.decimal)]
- (wrap ($_ text/compose mark (if signed?' "-" "") offset))))]
- (case (frac/decode ($_ text/compose (if signed? "-" "") digits "." decimals exp))
+ (wrap ($_ text;compose mark (if signed?' "-" "") offset))))]
+ (case (frac;decode ($_ text;compose (if signed? "-" "") digits "." decimals exp))
(#error.Failure message)
(p.fail message)
@@ -468,32 +468,32 @@
(l.Lexer Text)
($_ p.either
(p.after (l.this "\t")
- (p/wrap text.tab))
+ (p;wrap text.tab))
(p.after (l.this "\b")
- (p/wrap text.back-space))
+ (p;wrap text.back-space))
(p.after (l.this "\n")
- (p/wrap text.new-line))
+ (p;wrap text.new-line))
(p.after (l.this "\r")
- (p/wrap text.carriage-return))
+ (p;wrap text.carriage-return))
(p.after (l.this "\f")
- (p/wrap text.form-feed))
- (p.after (l.this (text/compose "\" text.double-quote))
- (p/wrap text.double-quote))
+ (p;wrap text.form-feed))
+ (p.after (l.this (text;compose "\" text.double-quote))
+ (p;wrap text.double-quote))
(p.after (l.this "\\")
- (p/wrap "\"))))
+ (p;wrap "\"))))
(def: string~
(l.Lexer String)
(<| (l.enclosed [text.double-quote text.double-quote])
(loop [_ []])
(do p.monad
- [chars (l.some (l.none-of (text/compose "\" text.double-quote)))
+ [chars (l.some (l.none-of (text;compose "\" text.double-quote)))
stop l.peek])
- (if (text/= "\" stop)
+ (if (text;= "\" stop)
(do @
[escaped escaped~
next-chars (recur [])]
- (wrap ($_ text/compose chars escaped next-chars)))
+ (wrap ($_ text;compose chars escaped next-chars)))
(wrap chars))))
(def: (kv~ json~)
diff --git a/stdlib/source/lux/data/format/markdown.lux b/stdlib/source/lux/data/format/markdown.lux
index 58f1f14b3..81c7118e7 100644
--- a/stdlib/source/lux/data/format/markdown.lux
+++ b/stdlib/source/lux/data/format/markdown.lux
@@ -4,7 +4,7 @@
["." text
format]
[collection
- ["." list ("#/." functor)]]]
+ ["." list ("#;." functor)]]]
[type
abstract]
[world
@@ -87,7 +87,7 @@
(def: (prefix with)
(-> Text (-> Text Text))
(|>> (text.split-all-with text.new-line)
- (list/map (function (_ line)
+ (list;map (function (_ line)
(if (text.empty? line)
line
(format with line))))
@@ -107,7 +107,7 @@
(-> (List [(Markdown Span) (Maybe (Markdown Block))])
(Markdown Block))
(|>> list.enumerate
- (list/map (function (_ [idx [summary detail]])
+ (list;map (function (_ [idx [summary detail]])
(format (%n (inc idx)) ". " (:representation summary) text.new-line
(case detail
(#.Some detail)
@@ -121,7 +121,7 @@
(def: #export bullet-list
(-> (List [(Markdown Span) (Maybe (Markdown Block))])
(Markdown Block))
- (|>> (list/map (function (_ [summary detail])
+ (|>> (list;map (function (_ [summary detail])
(format "*. " (:representation summary) text.new-line
(case detail
(#.Some detail)
diff --git a/stdlib/source/lux/data/format/xml.lux b/stdlib/source/lux/data/format/xml.lux
index a00ff24fa..85081f86c 100644
--- a/stdlib/source/lux/data/format/xml.lux
+++ b/stdlib/source/lux/data/format/xml.lux
@@ -4,18 +4,18 @@
monad
[equivalence (#+ Equivalence)]
codec
- ["p" parser ("#/." monad)]
+ ["p" parser ("#;." monad)]
["ex" exception (#+ exception:)]]
[data
["." error (#+ Error)]
["." product]
- ["." name ("#/." equivalence codec)]
+ ["." name ("#;." equivalence codec)]
[number
["." int]]
- ["." text ("#/." equivalence monoid)
+ ["." text ("#;." equivalence monoid)
["l" lexer]]
[collection
- ["." list ("#/." monad)]
+ ["." list ("#;." monad)]
["d" dictionary]]]])
(type: #export Tag Name)
@@ -30,11 +30,11 @@
(def: xml-standard-escape-char^
(l.Lexer Text)
($_ p.either
- (p.after (l.this "&lt;") (p/wrap "<"))
- (p.after (l.this "&gt;") (p/wrap ">"))
- (p.after (l.this "&amp;") (p/wrap "&"))
- (p.after (l.this "&apos;") (p/wrap "'"))
- (p.after (l.this "&quot;") (p/wrap text.double-quote))))
+ (p.after (l.this "&lt;") (p;wrap "<"))
+ (p.after (l.this "&gt;") (p;wrap ">"))
+ (p.after (l.this "&amp;") (p;wrap "&"))
+ (p.after (l.this "&apos;") (p;wrap "'"))
+ (p.after (l.this "&quot;") (p;wrap text.double-quote))))
(def: xml-unicode-escape-char^
(l.Lexer Text)
@@ -57,7 +57,7 @@
(def: xml-char^
(l.Lexer Text)
- (p.either (l.none-of ($_ text/compose "<>&'" text.double-quote))
+ (p.either (l.none-of ($_ text;compose "<>&'" text.double-quote))
xml-escape-char^))
(def: xml-identifier
@@ -67,7 +67,7 @@
l.alpha)
tail (l.some (p.either (l.one-of "_.-")
l.alpha-num))]
- (wrap ($_ text/compose head tail))))
+ (wrap ($_ text;compose head tail))))
(def: namespaced-symbol^
(l.Lexer Name)
@@ -111,10 +111,10 @@
spaced^
(p.after (l.this "/"))
(l.enclosed ["<" ">"]))]
- (p.assert ($_ text/compose "Close tag does not match open tag." text.new-line
- "Expected: " (name/encode expected) text.new-line
- " Actual: " (name/encode actual) text.new-line)
- (name/= expected actual))))
+ (p.assert ($_ text;compose "Close tag does not match open tag." text.new-line
+ "Expected: " (name;encode expected) text.new-line
+ " Actual: " (name;encode actual) text.new-line)
+ (name;= expected actual))))
(def: comment^
(l.Lexer Text)
@@ -142,7 +142,7 @@
(l.Lexer XML)
(|> (p.either cdata^
(l.many xml-char^))
- (p/map (|>> #Text))))
+ (p;map (|>> #Text))))
(def: xml^
(l.Lexer XML)
@@ -188,23 +188,23 @@
(-> Tag Text)
(case namespace
"" name
- _ ($_ text/compose namespace ":" name)))
+ _ ($_ text;compose namespace ":" name)))
(def: (write-attrs attrs)
(-> Attrs Text)
(|> attrs
d.entries
- (list/map (function (_ [key value])
- ($_ text/compose (write-tag key) "=" text.double-quote (sanitize-value value) text.double-quote)))
+ (list;map (function (_ [key value])
+ ($_ text;compose (write-tag key) "=" text.double-quote (sanitize-value value) text.double-quote)))
(text.join-with " ")))
(def: xml-header
Text
- ($_ text/compose "<?xml version=" text.double-quote "1.0" text.double-quote " encoding=" text.double-quote "UTF-8" text.double-quote "?>"))
+ ($_ text;compose "<?xml version=" text.double-quote "1.0" text.double-quote " encoding=" text.double-quote "UTF-8" text.double-quote "?>"))
(def: #export (write input)
(-> XML Text)
- ($_ text/compose xml-header
+ ($_ text;compose xml-header
(loop [input input]
(case input
(#Text value)
@@ -214,12 +214,12 @@
(let [tag (write-tag xml-tag)
attrs (if (d.empty? xml-attrs)
""
- ($_ text/compose " " (write-attrs xml-attrs)))]
+ ($_ text;compose " " (write-attrs xml-attrs)))]
(if (list.empty? xml-children)
- ($_ text/compose "<" tag attrs "/>")
- ($_ text/compose "<" tag attrs ">"
+ ($_ text;compose "<" tag attrs "/>")
+ ($_ text;compose "<" tag attrs ">"
(|> xml-children
- (list/map recur)
+ (list;map recur)
(text.join-with ""))
"</" tag ">")))))))
@@ -231,11 +231,11 @@
(def: (= reference sample)
(case [reference sample]
[(#Text reference/value) (#Text sample/value)]
- (text/= reference/value sample/value)
+ (text;= reference/value sample/value)
[(#Node reference/tag reference/attrs reference/children)
(#Node sample/tag sample/attrs sample/children)]
- (and (name/= reference/tag sample/tag)
+ (and (name;= reference/tag sample/tag)
(:: (d.equivalence text.equivalence) = reference/attrs sample/attrs)
(n/= (list.size reference/children)
(list.size sample/children))
@@ -253,13 +253,13 @@
(exception: #export unknown-attribute)
(exception: #export (wrong-tag {tag Name})
- (name/encode tag))
+ (name;encode tag))
-(def: blank-line ($_ text/compose text.new-line text.new-line))
+(def: blank-line ($_ text;compose text.new-line text.new-line))
(exception: #export (unconsumed-inputs {inputs (List XML)})
(|> inputs
- (list/map (:: ..codec encode))
+ (list;map (:: ..codec encode))
(text.join-with blank-line)))
(def: #export text
@@ -321,7 +321,7 @@
(ex.throw unexpected-input [])
(#Node _tag _attrs _children)
- (if (name/= tag _tag)
+ (if (name;= tag _tag)
(#error.Success [docs []])
(ex.throw wrong-tag tag))))))