aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data')
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux62
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux8
-rw-r--r--stdlib/source/library/lux/data/collection/stream.lux8
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/class.lux2
-rw-r--r--stdlib/source/library/lux/data/format/css/id.lux2
-rw-r--r--stdlib/source/library/lux/data/format/css/property.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/query.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/selector.lux4
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux22
-rw-r--r--stdlib/source/library/lux/data/format/html.lux2
-rw-r--r--stdlib/source/library/lux/data/format/json.lux14
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux12
-rw-r--r--stdlib/source/library/lux/data/text.lux6
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux114
17 files changed, 136 insertions, 136 deletions
diff --git a/stdlib/source/library/lux/data/collection/dictionary.lux b/stdlib/source/library/lux/data/collection/dictionary.lux
index afb711861..cd14464e8 100644
--- a/stdlib/source/library/lux/data/collection/dictionary.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary.lux
@@ -289,7 +289,7 @@
(def (node#empty? node)
(All (_ k v) (-> (Node k v) Bit))
(`` (case node
- {#Base (~~ (static ..clean_bitmap)) _}
+ {#Base (,, (static ..clean_bitmap)) _}
#1
_
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index aba1374d3..77729c0b3 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -259,7 +259,7 @@
{.#Some root}
(let [reference (the #key root)]
- (`` (cond (~~ (with_template [<comp> <tag> <add>]
+ (`` (cond (,, (with_template [<comp> <tag> <add>]
[(<comp> reference key)
(let [side_root (the <tag> root)
outcome (again side_root)]
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index 478a3d6aa..176b9d9b4 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -79,7 +79,7 @@
(def wrong_syntax_error
(template (_ <it>)
- [((`` ("lux in-module" (~~ (static .prelude)) .wrong_syntax_error))
+ [((`` ("lux in-module" (,, (static .prelude)) .wrong_syntax_error))
(symbol <it>))]))
(def .public partial
@@ -87,7 +87,7 @@
(case (reversed tokens)
{.#Item tail heads}
{.#Right [state (list (..mix (function (_ head tail)
- (` {.#Item (~ head) (~ tail)}))
+ (` {.#Item (, head) (, tail)}))
tail
heads))]}
@@ -401,9 +401,9 @@
(if (< x x')
[{.#Item x' pre} post]
[pre {.#Item x' post}]))
- (`` [(is (~~ (type_of xs))
+ (`` [(is (,, (type_of xs))
(list))
- (is (~~ (type_of xs))
+ (is (,, (type_of xs))
(list))])
xs')]
(.all composite (sorted < pre) (list x) (sorted < post)))))
@@ -481,29 +481,29 @@
(let [(open "[0]") ..functor
indices (..indices num_lists)
type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices))
- zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars))
- (-> (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var)))))
+ zipped_type (` (.All ((, (symbol$ "0_")) (,* type_vars))
+ (-> (,* (each (is (-> Code Code) (function (_ var) (` (List (, var)))))
type_vars))
- (List [(~+ type_vars)]))))
+ (List [(,* type_vars)]))))
vars+lists (|> indices
(each ++)
(each (function (_ idx)
(let [base (nat#encoded idx)]
[(symbol$ base)
(symbol$ ("lux text concat" base "'"))]))))
- pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)}))
+ pattern (` [(,* (each (function (_ [v vs]) (` {.#Item (, v) (, vs)}))
vars+lists))])
g!step (symbol$ "0step0")
g!blank (symbol$ "0,0")
list_vars (each product.right vars+lists)
- code (` (is (~ zipped_type)
- (function ((~ g!step) (~+ list_vars))
- (case [(~+ list_vars)]
- (~ pattern)
- {.#Item [(~+ (each product.left vars+lists))]
- ((~ g!step) (~+ list_vars))}
-
- (~ g!blank)
+ code (` (is (, zipped_type)
+ (function ((, g!step) (,* list_vars))
+ (case [(,* list_vars)]
+ (, pattern)
+ {.#Item [(,* (each product.left vars+lists))]
+ ((, g!step) (,* list_vars))}
+
+ (, g!blank)
{.#End}))))]
{.#Right [state (list code)]})
{.#Left "Cannot zipped 0 lists."})
@@ -524,30 +524,30 @@
g!return_type (symbol$ "0return_type0")
g!func (symbol$ "0func0")
type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices))
- zipped_type (` (All ((~ (symbol$ "0_")) (~+ type_vars) (~ g!return_type))
- (-> (-> (~+ type_vars) (~ g!return_type))
- (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var)))))
+ zipped_type (` (All ((, (symbol$ "0_")) (,* type_vars) (, g!return_type))
+ (-> (-> (,* type_vars) (, g!return_type))
+ (,* (each (is (-> Code Code) (function (_ var) (` (List (, var)))))
type_vars))
- (List (~ g!return_type)))))
+ (List (, g!return_type)))))
vars+lists (|> indices
(each ++)
(each (function (_ idx)
(let [base (nat#encoded idx)]
[(symbol$ base)
(symbol$ ("lux text concat" base "'"))]))))
- pattern (` [(~+ (each (function (_ [v vs]) (` {.#Item (~ v) (~ vs)}))
+ pattern (` [(,* (each (function (_ [v vs]) (` {.#Item (, v) (, vs)}))
vars+lists))])
g!step (symbol$ "0step0")
g!blank (symbol$ "0,0")
list_vars (each product.right vars+lists)
- code (` (is (~ zipped_type)
- (function ((~ g!step) (~ g!func) (~+ list_vars))
- (case [(~+ list_vars)]
- (~ pattern)
- {.#Item ((~ g!func) (~+ (each product.left vars+lists)))
- ((~ g!step) (~ g!func) (~+ list_vars))}
-
- (~ g!blank)
+ code (` (is (, zipped_type)
+ (function ((, g!step) (, g!func) (,* list_vars))
+ (case [(,* list_vars)]
+ (, pattern)
+ {.#Item ((, g!func) (,* (each product.left vars+lists)))
+ ((, g!step) (, g!func) (,* list_vars))}
+
+ (, g!blank)
{.#End}))))]
{.#Right [state (list code)]})
{.#Left "Cannot zipped_with 0 lists."})
@@ -631,8 +631,8 @@
(macro (_ tokens state)
(case tokens
(pattern (.list test then))
- {.#Right [state (.list (` (.if (~ test)
- (~ then)
+ {.#Right [state (.list (` (.if (, test)
+ (, then)
(.list))))]}
_
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index 77873fa40..93bea49d4 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -227,7 +227,7 @@
... If so, a brand-new root must be established, that is
... 1-level taller.
(|> sequence
- (.has #root (|> (`` (is (Hierarchy (~~ (type_of val)))
+ (.has #root (|> (`` (is (Hierarchy (,, (type_of val)))
(empty_hierarchy [])))
(array.has! 0 {#Hierarchy (the #root sequence)})
(array.has! 1 (..path (the #level sequence) (the #tail sequence)))))
@@ -293,8 +293,8 @@
{try.#Success (if (n.< (tail_off sequence_size) idx)
(.revised #root (hierarchy#has (the #level sequence) idx val)
sequence)
- (.revised #tail (`` (is (-> (Base (~~ (type_of val)))
- (Base (~~ (type_of val))))
+ (.revised #tail (`` (is (-> (Base (,, (type_of val)))
+ (Base (,, (type_of val))))
(|>> array.clone (array.has! (branch_idx idx) val))))
sequence))}
(exception.except ..index_out_of_bounds [sequence idx]))))
@@ -369,7 +369,7 @@
(def .public sequence
(syntax (_ [elems (<>.some <code>.any)])
- (in (.list (` (..of_list (.list (~+ elems))))))))
+ (in (.list (` (..of_list (.list (,* elems))))))))
(def (node_equivalence //#=)
(All (_ a) (-> (Equivalence a) (Equivalence (Node a))))
diff --git a/stdlib/source/library/lux/data/collection/stream.lux b/stdlib/source/library/lux/data/collection/stream.lux
index 3c41ccda0..67708962c 100644
--- a/stdlib/source/library/lux/data/collection/stream.lux
+++ b/stdlib/source/library/lux/data/collection/stream.lux
@@ -133,10 +133,10 @@
body <code>.any
branches (<>.some <code>.any)])
(with_symbols [g!stream]
- (let [body+ (` (let [(~+ (|> patterns
+ (let [body+ (` (let [(,* (|> patterns
(list#each (function (_ pattern)
- (list (` [(~ pattern) (~ g!stream)])
- (` ((~! //.result) (~ g!stream))))))
+ (list (` [(, pattern) (, g!stream)])
+ (` ((,! //.result) (, g!stream))))))
list#conjoint))]
- (~ body)))]
+ (, body)))]
(in (list.partial g!stream body+ branches))))))
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index 2e7c7b59d..7bde19f24 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -58,8 +58,8 @@
(def .public tree
(syntax (_ [root tree^])
(in (list (loop (again [[value children] root])
- (` [#value (~ value)
- #children (list (~+ (list#each again children)))]))))))
+ (` [#value (, value)
+ #children (list (,* (list#each again children)))]))))))
(def .public (equivalence super)
(All (_ a) (-> (Equivalence a) (Equivalence (Tree a))))
diff --git a/stdlib/source/library/lux/data/format/css/class.lux b/stdlib/source/library/lux/data/format/css/class.lux
index cf0d3423a..1ddfdfebd 100644
--- a/stdlib/source/library/lux/data/format/css/class.lux
+++ b/stdlib/source/library/lux/data/format/css/class.lux
@@ -30,6 +30,6 @@
(do meta.monad
[module meta.current_module_name
class meta.seed]
- (in (list (` (..custom (~ (code.text (format "c" (%.nat_16 class)
+ (in (list (` (..custom (, (code.text (format "c" (%.nat_16 class)
"_" (%.nat_16 (text#hash module))))))))))))
)
diff --git a/stdlib/source/library/lux/data/format/css/id.lux b/stdlib/source/library/lux/data/format/css/id.lux
index ee61013bf..45746b427 100644
--- a/stdlib/source/library/lux/data/format/css/id.lux
+++ b/stdlib/source/library/lux/data/format/css/id.lux
@@ -30,6 +30,6 @@
(do meta.monad
[module meta.current_module_name
id meta.seed]
- (in (list (` (..custom (~ (code.text (format "i" (%.nat_16 id)
+ (in (list (` (..custom (, (code.text (format "i" (%.nat_16 id)
"_" (%.nat_16 (text#hash module))))))))))))
)
diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux
index 1a3b8ee02..353efa6c5 100644
--- a/stdlib/source/library/lux/data/format/css/property.lux
+++ b/stdlib/source/library/lux/data/format/css/property.lux
@@ -71,11 +71,11 @@
(Property <brand>)
(abstraction <property>))]
- (~~ (template.spliced <alias>+))))
+ (,, (template.spliced <alias>+))))
(with_expansions [<rows> (template.spliced <property>+)]
(with_template [<property>]
- [(`` (def .public (~~ (text_symbol <property>))
+ [(`` (def .public (,, (text_symbol <property>))
(Property <brand>)
(abstraction <property>)))]
diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux
index d3edc6d31..859eb7910 100644
--- a/stdlib/source/library/lux/data/format/css/query.lux
+++ b/stdlib/source/library/lux/data/format/css/query.lux
@@ -32,7 +32,7 @@
(|>> representation))
(with_template [<media>]
- [(`` (def .public (~~ (text_symbol <media>))
+ [(`` (def .public (,, (text_symbol <media>))
Media
(abstraction <media>)))]
@@ -50,7 +50,7 @@
(|>> representation))
(with_template [<feature> <brand>]
- [(`` (def .public ((~~ (text_symbol <feature>)) input)
+ [(`` (def .public ((,, (text_symbol <feature>)) input)
(-> (Value <brand>) Feature)
(abstraction (format "(" <feature> ": " (//value.value input) ")"))))]
diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux
index 1e8d3e0b9..a994398fd 100644
--- a/stdlib/source/library/lux/data/format/css/selector.lux
+++ b/stdlib/source/library/lux/data/format/css/selector.lux
@@ -68,7 +68,7 @@
<combinator>
(representation right))))]
- (~~ (template.spliced <combinator>+))))]
+ (,, (template.spliced <combinator>+))))]
[Can_Chain (Generic Any)
[["" and]]]
@@ -113,7 +113,7 @@
(Selector <kind>)
(abstraction <pseudo>))]
- (~~ (template.spliced <pseudo>+))))]
+ (,, (template.spliced <pseudo>+))))]
[Can_Chain
[[active ":active"]
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index d4732c5da..877e4f8e6 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -45,7 +45,7 @@
(`` (with_template [<name> <value>]
[(def .public <name> <abstraction> (abstraction <value>))]
- (~~ (template.spliced <sample>+))
+ (,, (template.spliced <sample>+))
))
(template.spliced <definition>+))]))
@@ -94,11 +94,11 @@
(Value <brand>)
(abstraction <value>))]
- (~~ (template.spliced <alias>+))))
+ (,, (template.spliced <alias>+))))
(with_expansions [<rows> (template.spliced <value>+)]
(with_template [<value>]
- [(`` (def .public (~~ (..text_symbol <value>))
+ [(`` (def .public (,, (..text_symbol <value>))
(Value <brand>)
(abstraction <value>)))]
@@ -990,7 +990,7 @@
(-> <input> (Value Filter))
(|>> <pre> (list) (..apply <function>)))]
- (~~ (template.spliced <function>+))))]
+ (,, (template.spliced <function>+))))]
[Nat (<| representation ..px n.frac)
[[blur "blur"]]]
@@ -1115,7 +1115,7 @@
(def .public (clip rectangle)
(-> Rectangle (Value Clip))
- (`` (..apply "rect" (list (~~ (with_template [<side>]
+ (`` (..apply "rect" (list (,, (with_template [<side>]
[(representation (the <side> rectangle))]
[#top] [#right] [#bottom] [#left]))))))
@@ -1260,9 +1260,9 @@
(..apply "matrix3d")))
(with_template [<name> <function> <input_types> <input_values>]
- [(`` (def .public (<name> [(~~ (template.spliced <input_values>))])
- (-> [(~~ (template.spliced <input_types>))] (Value Transform))
- (|> (list (~~ (template.spliced <input_values>)))
+ [(`` (def .public (<name> [(,, (template.spliced <input_values>))])
+ (-> [(,, (template.spliced <input_types>))] (Value Transform))
+ (|> (list (,, (template.spliced <input_values>)))
(list#each %number)
(..apply <function>))))]
@@ -1282,9 +1282,9 @@
)
(with_template [<name> <function> <input_types> <input_values>]
- [(`` (def .public (<name> [(~~ (template.spliced <input_values>))])
- (-> [(~~ (template.spliced <input_types>))] (Value Transform))
- (|> (list (~~ (template.spliced <input_values>)))
+ [(`` (def .public (<name> [(,, (template.spliced <input_values>))])
+ (-> [(,, (template.spliced <input_types>))] (Value Transform))
+ (|> (list (,, (template.spliced <input_values>)))
(list#each ..angle)
(..apply <function>))))]
diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux
index d6560ccfe..ba8f5ab31 100644
--- a/stdlib/source/library/lux/data/format/html.lux
+++ b/stdlib/source/library/lux/data/format/html.lux
@@ -109,7 +109,7 @@
[(primitive <sub_raw> Any)
(type .public <sub> (HTML (<super_raw> <sub_raw>)))]
- (~~ (template.spliced <sub>+))))]
+ (,, (template.spliced <sub>+))))]
[Element Element'
[[Content Content']
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index d419ac68f..1af453bb9 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -104,28 +104,28 @@
(^.with_template [<ctor> <input_tag> <output_tag>]
[{<input_tag> value}
- (` {<output_tag> (~ (<ctor> value))})])
+ (` {<output_tag> (, (<ctor> value))})])
([code.bit ..#Boolean' ..#Boolean]
[code.frac ..#Number' ..#Number]
[code.text ..#String' ..#String])
{#Array' members}
- (` {..#Array ((~! sequence.sequence) (~+ (sequence.list (sequence#each jsonF members))))})
+ (` {..#Array ((,! sequence.sequence) (,* (sequence.list (sequence#each jsonF members))))})
{#Object' pairs}
- (` {..#Object ((~! dictionary.of_list)
- (~! text.hash)
- (list (~+ (|> pairs
+ (` {..#Object ((,! dictionary.of_list)
+ (,! text.hash)
+ (list (,* (|> pairs
dictionary.entries
(list#each (function (_ [key_name value])
- (` [(~ (code.text key_name)) (~ (jsonF value))])))))))})
+ (` [(, (code.text key_name)) (, (jsonF value))])))))))})
{#Code' code}
code))
(def .public json
(syntax (_ [token ..jsonP])
- (in (list (` (is JSON (~ (jsonF token))))))))
+ (in (list (` (is JSON (, (jsonF token))))))))
(def .public (fields json)
(-> JSON (Try (List String)))
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index e0ed3924f..38746e8eb 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -126,12 +126,12 @@
(Parser Any)
(do <>.monad
[pre_end <binary>.bits_8
- _ (let [expected (`` (char (~~ (static ..blank))))]
+ _ (let [expected (`` (char (,, (static ..blank))))]
(<>.assertion (exception.error ..wrong_character [expected pre_end])
(n.= expected pre_end)))
end <binary>.bits_8
- _ (let [expected (`` (char (~~ (static ..null))))]
+ _ (let [expected (`` (char (,, (static ..null))))]
(<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end)))]
(in [])))
@@ -153,7 +153,7 @@
[digits (<binary>.segment ..big_size)
digits (<>.lifted (at utf8.codec decoded digits))
end <binary>.bits_8
- _ (let [expected (`` (char (~~ (static ..blank))))]
+ _ (let [expected (`` (char (,, (static ..blank))))]
(<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end)))]
(<>.lifted
@@ -243,7 +243,7 @@
0 (at utf8.codec encoded "")
_ (let [last_char (binary!.bits_8 end string)]
(`` (case (.nat last_char)
- (pattern (char (~~ (static ..null))))
+ (pattern (char (,, (static ..null))))
(again (-- end))
_
@@ -288,7 +288,7 @@
(do <>.monad
[string (<binary>.segment <size>)
end <binary>.bits_8
- .let [expected (`` (char (~~ (static ..null))))]
+ .let [expected (`` (char (,, (static ..null))))]
_ (<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end))]
(<>.lifted
@@ -330,7 +330,7 @@
(do <>.monad
[string (<binary>.segment ..magic_size)
end <binary>.bits_8
- .let [expected (`` (char (~~ (static ..null))))]
+ .let [expected (`` (char (,, (static ..null))))]
_ (<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end))]
(<>.lifted
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index 7bf3cd997..3ab11ff3a 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -188,11 +188,11 @@
(macro (_ tokens lux)
(case tokens
(pattern (list it))
- {.#Right [lux (list (` (.case ("js type-of" ("js constant" (~ it)))
+ {.#Right [lux (list (` (.case ("js type-of" ("js constant" (, it)))
"undefined"
.false
- (~' _)
+ (,' _)
.true)))]}
_
@@ -338,7 +338,7 @@
(def .public (space? char)
(-> Char Bit)
(with_expansions [<options> (with_template [<char>]
- [(pattern (.char (~~ (static <char>))))]
+ [(pattern (.char (,, (static <char>))))]
[..tab]
[..vertical_tab]
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 39fb077d0..674a53f67 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -82,7 +82,7 @@
(-> Text (Parser Code))
(do <>.monad
[symbol (<text>.enclosed ["\@<" ">"] (symbol^ current_module))]
- (in (` (is ((~! <text>.Parser) Text) (~ (code.symbol symbol)))))))
+ (in (` (is ((,! <text>.Parser) Text) (, (code.symbol symbol)))))))
(def re_range^
(Parser Code)
@@ -90,19 +90,19 @@
[from (|> regex_char^ (at ! each (|>> (//.char 0) maybe.trusted)))
_ (<text>.this "-")
to (|> regex_char^ (at ! each (|>> (//.char 0) maybe.trusted)))]
- (in (` ((~! <text>.range) (~ (code.nat from)) (~ (code.nat to)))))))
+ (in (` ((,! <text>.range) (, (code.nat from)) (, (code.nat to)))))))
(def re_char^
(Parser Code)
(do <>.monad
[char escaped_char^]
- (in (` ((~! ..copy) (~ (code.text char)))))))
+ (in (` ((,! ..copy) (, (code.text char)))))))
(def re_options^
(Parser Code)
(do <>.monad
[options (<text>.many escaped_char^)]
- (in (` ((~! <text>.one_of) (~ (code.text options)))))))
+ (in (` ((,! <text>.one_of) (, (code.text options)))))))
(def re_user_class^'
(Parser Code)
@@ -112,8 +112,8 @@
re_range^
re_options^))]
(in (case negate?
- {.#Some _} (` ((~! <text>.not) (all ((~! <>.either)) (~+ parts))))
- {.#None} (` (all ((~! <>.either)) (~+ parts)))))))
+ {.#Some _} (` ((,! <text>.not) (all ((,! <>.either)) (,* parts))))
+ {.#None} (` (all ((,! <>.either)) (,* parts)))))))
(def re_user_class^
(Parser Code)
@@ -123,7 +123,7 @@
(<text>.enclosed ["[" "]"]
..re_user_class^')))]
(in (list#mix (function (_ refinement base)
- (` ((~! refine^) (~ refinement) (~ base))))
+ (` ((,! refine^) (, refinement) (, base))))
init
rest))))
@@ -159,28 +159,28 @@
(do <>.monad
[]
(all <>.either
- (<>.after (<text>.this ".") (in (` (~! <text>.any))))
- (<>.after (<text>.this "\d") (in (` (~! <text>.decimal))))
- (<>.after (<text>.this "\D") (in (` ((~! <text>.not) (~! <text>.decimal)))))
- (<>.after (<text>.this "\s") (in (` (~! <text>.space))))
- (<>.after (<text>.this "\S") (in (` ((~! <text>.not) (~! <text>.space)))))
- (<>.after (<text>.this "\w") (in (` (~! word^))))
- (<>.after (<text>.this "\W") (in (` ((~! <text>.not) (~! word^)))))
-
- (<>.after (<text>.this "\p{Lower}") (in (` (~! <text>.lower))))
- (<>.after (<text>.this "\p{Upper}") (in (` (~! <text>.upper))))
- (<>.after (<text>.this "\p{Alpha}") (in (` (~! <text>.alpha))))
- (<>.after (<text>.this "\p{Digit}") (in (` (~! <text>.decimal))))
- (<>.after (<text>.this "\p{Alnum}") (in (` (~! <text>.alpha_num))))
- (<>.after (<text>.this "\p{Space}") (in (` (~! <text>.space))))
- (<>.after (<text>.this "\p{HexDigit}") (in (` (~! <text>.hexadecimal))))
- (<>.after (<text>.this "\p{OctDigit}") (in (` (~! <text>.octal))))
- (<>.after (<text>.this "\p{Blank}") (in (` (~! blank^))))
- (<>.after (<text>.this "\p{ASCII}") (in (` (~! ascii^))))
- (<>.after (<text>.this "\p{Contrl}") (in (` (~! control^))))
- (<>.after (<text>.this "\p{Punct}") (in (` (~! punct^))))
- (<>.after (<text>.this "\p{Graph}") (in (` (~! graph^))))
- (<>.after (<text>.this "\p{Print}") (in (` (~! print^))))
+ (<>.after (<text>.this ".") (in (` (,! <text>.any))))
+ (<>.after (<text>.this "\d") (in (` (,! <text>.decimal))))
+ (<>.after (<text>.this "\D") (in (` ((,! <text>.not) (,! <text>.decimal)))))
+ (<>.after (<text>.this "\s") (in (` (,! <text>.space))))
+ (<>.after (<text>.this "\S") (in (` ((,! <text>.not) (,! <text>.space)))))
+ (<>.after (<text>.this "\w") (in (` (,! word^))))
+ (<>.after (<text>.this "\W") (in (` ((,! <text>.not) (,! word^)))))
+
+ (<>.after (<text>.this "\p{Lower}") (in (` (,! <text>.lower))))
+ (<>.after (<text>.this "\p{Upper}") (in (` (,! <text>.upper))))
+ (<>.after (<text>.this "\p{Alpha}") (in (` (,! <text>.alpha))))
+ (<>.after (<text>.this "\p{Digit}") (in (` (,! <text>.decimal))))
+ (<>.after (<text>.this "\p{Alnum}") (in (` (,! <text>.alpha_num))))
+ (<>.after (<text>.this "\p{Space}") (in (` (,! <text>.space))))
+ (<>.after (<text>.this "\p{HexDigit}") (in (` (,! <text>.hexadecimal))))
+ (<>.after (<text>.this "\p{OctDigit}") (in (` (,! <text>.octal))))
+ (<>.after (<text>.this "\p{Blank}") (in (` (,! blank^))))
+ (<>.after (<text>.this "\p{ASCII}") (in (` (,! ascii^))))
+ (<>.after (<text>.this "\p{Contrl}") (in (` (,! control^))))
+ (<>.after (<text>.this "\p{Punct}") (in (` (,! punct^))))
+ (<>.after (<text>.this "\p{Graph}") (in (` (,! graph^))))
+ (<>.after (<text>.this "\p{Print}") (in (` (,! print^))))
)))
(def re_class^
@@ -198,12 +198,12 @@
(<>.either (do <>.monad
[_ (<text>.this "\")
id number^]
- (in (` ((~! ..copy) (~ (code.symbol ["" (n#encoded id)]))))))
+ (in (` ((,! ..copy) (, (code.symbol ["" (n#encoded id)]))))))
(do <>.monad
[_ (<text>.this "\k<")
captured_symbol symbol_part^
_ (<text>.this ">")]
- (in (` ((~! ..copy) (~ (code.symbol ["" captured_symbol]))))))))
+ (in (` ((,! ..copy) (, (code.symbol ["" captured_symbol]))))))))
(def (re_simple^ current_module)
(-> Text (Parser Code))
@@ -221,14 +221,14 @@
quantifier (<text>.one_of "?*+")]
(case quantifier
"?"
- (in (` ((~! <>.else) "" (~ base))))
+ (in (` ((,! <>.else) "" (, base))))
"*"
- (in (` ((~! together^) ((~! <>.some) (~ base)))))
+ (in (` ((,! together^) ((,! <>.some) (, base)))))
... "+"
_
- (in (` ((~! together^) ((~! <>.many) (~ base)))))
+ (in (` ((,! together^) ((,! <>.many) (, base)))))
)))
(exception .public (incorrect_quantification [from Nat
@@ -247,19 +247,19 @@
[[from to] (<>.and number^ (<>.after (<text>.this ",") number^))
_ (<>.assertion (exception.error ..incorrect_quantification [from to])
(n.<= to from))]
- (in (` ((~! together^) ((~! <>.between)
- (~ (code.nat from))
- (~ (code.nat (n.- from to)))
- (~ base))))))
+ (in (` ((,! together^) ((,! <>.between)
+ (, (code.nat from))
+ (, (code.nat (n.- from to)))
+ (, base))))))
(do !
[limit (<>.after (<text>.this ",") number^)]
- (in (` ((~! together^) ((~! <>.at_most) (~ (code.nat limit)) (~ base))))))
+ (in (` ((,! together^) ((,! <>.at_most) (, (code.nat limit)) (, base))))))
(do !
[limit (<>.before (<text>.this ",") number^)]
- (in (` ((~! together^) ((~! <>.at_least) (~ (code.nat limit)) (~ base))))))
+ (in (` ((,! together^) ((,! <>.at_least) (, (code.nat limit)) (, base))))))
(do !
[limit number^]
- (in (` ((~! together^) ((~! <>.exactly) (~ (code.nat limit)) (~ base))))))))))
+ (in (` ((,! together^) ((,! <>.exactly) (, (code.nat limit)) (, base))))))))))
(def (re_quantified^ current_module)
(-> Text (Parser Code))
@@ -297,7 +297,7 @@
[idx
names
(list.partial (list g!temp complex
- (` .let) (` [(~ g!total) (at (~! //.monoid) (~' composite) (~ g!total) (~ g!temp))]))
+ (` .let) (` [(, g!total) (at (,! //.monoid) (,' composite) (, g!total) (, g!temp))]))
steps)]
{.#Right [{#Capturing [?name num_captures]} scoped]}
@@ -308,12 +308,12 @@
{.#None}
[(++ idx) (code.symbol ["" (n#encoded idx)])])
access (if (n.> 0 num_captures)
- (` ((~! product.left) (~ name!)))
+ (` ((,! product.left) (, name!)))
name!)]
[idx!
(list.partial name! names)
(list.partial (list name! scoped
- (` .let) (` [(~ g!total) (at (~! //.monoid) (~' composite) (~ g!total) (~ access))]))
+ (` .let) (` [(, g!total) (at (,! //.monoid) (,' composite) (, g!total) (, access))]))
steps)])
)))
[0
@@ -323,10 +323,10 @@
(in [(if capturing?
(list.size names)
0)
- (` ((~! do) (~! <>.monad)
- [.let [(~ g!total) ""]
- (~+ (|> steps list.reversed list#conjoint))]
- ((~ (' in)) [(~ g!total) (~+ (list.reversed names))])))])
+ (` ((,! do) (,! <>.monad)
+ [.let [(, g!total) ""]
+ (,* (|> steps list.reversed list#conjoint))]
+ ((, (' in)) [(, g!total) (,* (list.reversed names))])))])
))
(def (unflatten^ lexer)
@@ -367,7 +367,7 @@
(-> [Nat Code] Code)
(if (n.> 0 num_captures)
alt
- (` ((~! unflatten^) (~ alt)))))
+ (` ((,! unflatten^) (, alt)))))
(def (re_alternative^ capturing? re_scoped^ current_module)
(-> Bit
@@ -381,11 +381,11 @@
(if (list.empty? tail)
(in head)
(in [(list#mix n.max (product.left head) (list#each product.left tail))
- (` (all ((~ (if capturing?
- (` (~! |||^))
- (` (~! |||_^)))))
- (~ (prep_alternative head))
- (~+ (list#each prep_alternative tail))))]))))
+ (` (all ((, (if capturing?
+ (` (,! |||^))
+ (` (,! |||_^)))))
+ (, (prep_alternative head))
+ (,* (list#each prep_alternative tail))))]))))
(def (re_scoped^ current_module)
(-> Text (Parser [Re_Group Code]))
@@ -433,8 +433,8 @@
body <code>.any
branches (<>.many <code>.any)])
(with_symbols [g!temp]
- (in (list.partial (` (^.multi (~ g!temp)
- [((~! <text>.result) (..regex (~ (code.text pattern))) (~ g!temp))
- {try.#Success (~ (maybe.else g!temp bindings))}]))
+ (in (list.partial (` (^.multi (, g!temp)
+ [((,! <text>.result) (..regex (, (code.text pattern))) (, g!temp))
+ {try.#Success (, (maybe.else g!temp bindings))}]))
body
branches)))))