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/bit.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux2
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux8
-rw-r--r--stdlib/source/library/lux/data/collection/row.lux12
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux18
-rw-r--r--stdlib/source/library/lux/data/format/binary.lux14
-rw-r--r--stdlib/source/library/lux/data/format/css.lux6
-rw-r--r--stdlib/source/library/lux/data/format/css/value.lux16
-rw-r--r--stdlib/source/library/lux/data/format/html.lux4
-rw-r--r--stdlib/source/library/lux/data/format/json.lux6
-rw-r--r--stdlib/source/library/lux/data/format/markdown.lux6
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux38
-rw-r--r--stdlib/source/library/lux/data/format/xml.lux4
-rw-r--r--stdlib/source/library/lux/data/text.lux2
-rw-r--r--stdlib/source/library/lux/data/text/escape.lux6
-rw-r--r--stdlib/source/library/lux/data/text/format.lux2
-rw-r--r--stdlib/source/library/lux/data/text/regex.lux10
-rw-r--r--stdlib/source/library/lux/data/text/unicode/set.lux8
18 files changed, 79 insertions, 85 deletions
diff --git a/stdlib/source/library/lux/data/bit.lux b/stdlib/source/library/lux/data/bit.lux
index 22ff7fe2f..efdca1f5b 100644
--- a/stdlib/source/library/lux/data/bit.lux
+++ b/stdlib/source/library/lux/data/bit.lux
@@ -64,4 +64,4 @@
{#.doc (example "Generates the complement of a predicate."
"That is a predicate that returns the oposite of the original predicate.")}
(All [a] (-> (-> a Bit) (-> a Bit)))
- (function.compose not))
+ (function.composite not))
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index e6b05bf51..84e883b1d 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -266,7 +266,7 @@
outcome (recur side_root)]
(if (same? side_root outcome)
?root
- (#.Some (<add> (maybe.assume outcome)
+ (#.Some (<add> (maybe.trusted outcome)
root))))]
[_\< #left ..with_left]
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index 7298a5039..8cba7efb2 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -592,9 +592,11 @@
{#.doc (.example "Enhances a monad with List functionality.")}
(All [M] (-> (Monad M) (Monad (All [a] (M (List a))))))
- (def: &functor (functor.compose (get@ #monad.&functor monad) ..functor))
+ (def: &functor
+ (functor.composite (get@ #monad.&functor monad) ..functor))
- (def: in (|>> (\ ..monad in) (\ monad in)))
+ (def: in
+ (|>> (\ ..monad in) (\ monad in)))
(def: (join MlMla)
(do {! monad}
@@ -606,7 +608,7 @@
(monad.seq ! lMla))]
(in (..joined lla)))))
-(def: .public (lift monad)
+(def: .public (lifted monad)
{#.doc (.example "Wraps a monadic value with List machinery.")}
(All [M a] (-> (Monad M) (-> (M a) (M (List a)))))
(\ monad map (\ ..monad in)))
diff --git a/stdlib/source/library/lux/data/collection/row.lux b/stdlib/source/library/lux/data/collection/row.lux
index 230de34a1..6a4b88587 100644
--- a/stdlib/source/library/lux/data/collection/row.lux
+++ b/stdlib/source/library/lux/data/collection/row.lux
@@ -126,13 +126,13 @@
(array.copy! tail_size 0 tail 0)
(array.write! tail_size val))))
-(def: (put' level idx val hierarchy)
+(def: (has' level idx val hierarchy)
(All [a] (-> Level Index a (Hierarchy a) (Hierarchy a)))
(let [sub_idx (branch_idx (i64.right_shifted level idx))]
(case (array.read! sub_idx hierarchy)
(#.Some (#Hierarchy sub_node))
(|> (array.clone hierarchy)
- (array.write! sub_idx (#Hierarchy (put' (level_down level) idx val sub_node))))
+ (array.write! sub_idx (#Hierarchy (has' (level_down level) idx val sub_node))))
(^multi (#.Some (#Base base))
(n.= 0 (level_down level)))
@@ -279,7 +279,7 @@
#.None
(exception.except ..incorrect_row_structure []))))
-(def: .public (put idx val row)
+(def: .public (has idx val row)
(All [a] (-> Nat a (Row a) (Try (Row a))))
(let [row_size (get@ #size row)]
(if (within_bounds? row idx)
@@ -289,7 +289,7 @@
(|>> array.clone (array.write! (branch_idx idx) val)))}
(|>> array.clone (array.write! (branch_idx idx) val)))
row)
- (update@ #root (put' (get@ #level row) idx val)
+ (update@ #root (has' (get@ #level row) idx val)
row)))
(exception.except ..index_out_of_bounds [row idx]))))
@@ -297,7 +297,7 @@
(All [a] (-> Nat (-> a a) (Row a) (Try (Row a))))
(do try.monad
[val (..item idx row)]
- (..put idx (f val) row)))
+ (..has idx (f val) row)))
(def: .public (pop row)
(All [a] (-> (Row a) (Row a)))
@@ -316,7 +316,7 @@
(update@ #size dec)
(set@ #tail (|> (array.empty new_tail_size)
(array.copy! new_tail_size 0 old_tail 0)))))
- (maybe.assume
+ (maybe.trusted
(do maybe.monad
[new_tail (base_for (n.- 2 row_size) row)
.let [[level' root'] (let [init_level (get@ #level row)]
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index d60fd99d4..a7d2cc0b4 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -23,11 +23,12 @@
{#.doc "An infinite sequence of values."}
(Cont [a (Sequence a)]))
-(def: .public (iterations f x)
- {#.doc "Create a sequence by applying a function to a value, and to its result, on and on..."}
- (All [a]
- (-> (-> a a) a (Sequence a)))
- (//.pending [x (iterations f (f x))]))
+(def: .public (iterations step init)
+ {#.doc "A stateful way of infinitely calculating the values of a sequence."}
+ (All [a b]
+ (-> (-> a [a b]) a (Sequence b)))
+ (let [[next x] (step init)]
+ (//.pending [x (iterations step next)])))
(def: .public (repeated x)
{#.doc "Repeat a value forever."}
@@ -101,13 +102,6 @@
[split_at Nat (n.= 0 pred) (dec pred)]
)
-(def: .public (unfold step init)
- {#.doc "A stateful way of infinitely calculating the values of a sequence."}
- (All [a b]
- (-> (-> a [a b]) a (Sequence b)))
- (let [[next x] (step init)]
- (//.pending [x (unfold step next)])))
-
(def: .public (only predicate sequence)
{#.doc (example "A new sequence only with items that satisfy the predicate.")}
(All [a] (-> (-> a Bit) (Sequence a) (Sequence a)))
diff --git a/stdlib/source/library/lux/data/format/binary.lux b/stdlib/source/library/lux/data/format/binary.lux
index e16c2cebd..e23ade3fb 100644
--- a/stdlib/source/library/lux/data/format/binary.lux
+++ b/stdlib/source/library/lux/data/format/binary.lux
@@ -78,7 +78,7 @@
[(n.+ <size> offset)
(|> binary
(<write> offset value)
- try.assumed)])]))]
+ try.trusted)])]))]
[bits/8 /.size/8 binary.write/8!]
[bits/16 /.size/16 binary.write/16!]
@@ -97,7 +97,7 @@
(function (_ [offset binary])
(|> binary
(binary.write/8! offset <number>)
- try.assumed
+ try.trusted
[(.inc offset)]
caseT))])])
([0 #.Left left]
@@ -142,7 +142,7 @@
[size
(function (_ [offset binary])
[(n.+ size offset)
- (try.assumed
+ (try.trusted
(binary.copy (n.min size (binary.size value))
0
value
@@ -159,7 +159,7 @@
[size'
(function (_ [offset binary])
[(n.+ size' offset)
- (try.assumed
+ (try.trusted
(do try.monad
[_ (<write> offset size binary)]
(binary.copy size 0 value (n.+ <size> offset) binary)))])]))))]
@@ -202,7 +202,7 @@
specification\identity))]
[(n.+ <size> size)
(function (_ [offset binary])
- (try.assumed
+ (try.trusted
(do try.monad
[_ (<write> offset capped_count binary)]
(in (mutation [(n.+ <size> offset) binary])))))])))]
@@ -247,7 +247,7 @@
(function (_ [offset binary])
(|> binary
(binary.write/8! offset <number>)
- try.assumed
+ try.trusted
[(.inc offset)]
caseT))])])
([0 #.Primitive (..and ..text (..list recur))]
@@ -282,7 +282,7 @@
(function (_ [offset binary])
(|> binary
(binary.write/8! offset <number>)
- try.assumed
+ try.trusted
[(.inc offset)]
caseT))])])
([0 #.Bit ..bit]
diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux
index d86deb7e5..7ec9a0d35 100644
--- a/stdlib/source/library/lux/data/format/css.lux
+++ b/stdlib/source/library/lux/data/format/css.lux
@@ -67,7 +67,7 @@
with_unicode)
(list\map (function (_ [property value])
(format property ": " value ";")))
- (text.join_with /style.separator)
+ (text.interposed /style.separator)
(text.enclosed ["{" "}"])
(format "@font-face")
:abstraction)))
@@ -98,7 +98,7 @@
(format (/value.percentage (get@ #when frame)) " {"
(/style.inline (get@ #what frame))
"}")))
- (text.join_with ..css_separator))
+ (text.interposed ..css_separator))
"}")))
(template: (!compose <pre> <post>)
@@ -115,7 +115,7 @@
:representation
(text.all_split_by ..css_separator)
(list\map (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
- (text.join_with ..css_separator)
+ (text.interposed ..css_separator)
:abstraction))
(def: .public (dependent combinator selector style inner)
diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux
index c2fb914c2..0c8e8f70f 100644
--- a/stdlib/source/library/lux/data/format/css/value.lux
+++ b/stdlib/source/library/lux/data/format/css/value.lux
@@ -61,7 +61,7 @@
(let [raw (%.frac value)]
(if (f.< +0.0 value)
raw
- (|> raw (text.split_at 1) maybe.assume product.right))))
+ (|> raw (text.split_at 1) maybe.trusted product.right))))
(abstract: .public (Value brand)
{}
@@ -786,7 +786,7 @@
(def: (apply name inputs)
(-> Text (List Text) Value)
(|> inputs
- (text.join_with ..value_separator)
+ (text.interposed ..value_separator)
(text.enclosed ["(" ")"])
(format name)
:abstraction))
@@ -1042,7 +1042,7 @@
(|> blur (maybe.else ..default_shadow_length) :representation)
(|> spread (maybe.else ..default_shadow_length) :representation)
(:representation color))
- (text.join_with " ")
+ (text.interposed " ")
(list)
(..apply "drop-shadow")))
@@ -1119,7 +1119,7 @@
(|> spread (maybe.else ..default_shadow_length) :representation)
(:representation color)
with_inset)
- (text.join_with " ")
+ (text.interposed " ")
:abstraction)))
(type: .public Rectangle
@@ -1172,7 +1172,7 @@
(#.Item _)
(|> options
(list\map ..font_name)
- (text.join_with ",")
+ (text.interposed ",")
(:abstraction Value))
#.End
@@ -1212,9 +1212,9 @@
(:abstraction "."))]
(|>> (list\map (|>> (list\map (|>> (maybe.else empty)
:representation))
- (text.join_with ..grid_column_separator)
+ (text.interposed ..grid_column_separator)
(text.enclosed ["'" "'"])))
- (text.join_with ..grid_row_separator)
+ (text.interposed ..grid_row_separator)
:abstraction)))
(def: .public (resolution dpi)
@@ -1248,7 +1248,7 @@
(-> [Quote Quote] [Quote Quote] (Value Quotes))
(|> (list left0 right0 left1 right1)
(list\map (|>> ..quote_text %.text))
- (text.join_with ..quote_separator)
+ (text.interposed ..quote_separator)
:abstraction))
(def: .public (matrix_2d [a b] [c d] [tx ty])
diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux
index 3c3566a56..3a8daf5c0 100644
--- a/stdlib/source/library/lux/data/format/html.lux
+++ b/stdlib/source/library/lux/data/format/html.lux
@@ -64,7 +64,7 @@
(-> Attributes Text)
(|>> (list\map (function (_ [key val])
(format key "=" text.double_quote (..safe val) text.double_quote)))
- (text.join_with " ")))
+ (text.interposed " ")))
(def: (open tag attributes)
(-> Tag Attributes Text)
@@ -259,7 +259,7 @@
(Format Polygon)
(|> (list& first second third extra)
(list\map %coord)
- (text.join_with ..coord_separator)))
+ (text.interposed ..coord_separator)))
(type: .public Shape
(#Rectangle Rectangle)
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 7f6ca24a8..c6a7ebef0 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -227,7 +227,7 @@
value (let [raw (\ f.decimal encode value)]
(if (f.< +0.0 value)
raw
- (|> raw (text.split_at 1) maybe.assume product.right))))))
+ (|> raw (text.split_at 1) maybe.trusted product.right))))))
(def: escape "\")
(def: escaped_dq (text\compose ..escape text.double_quote))
@@ -256,7 +256,7 @@
(-> (-> JSON Text) (-> Array Text))
(|>> (row\map format)
row.list
- (text.join_with ..value_separator)
+ (text.interposed ..value_separator)
(text.enclosed [..array_start ..array_end])))
(def: (kv_format format [key value])
@@ -271,7 +271,7 @@
(-> (-> JSON Text) (-> Object Text))
(|>> dictionary.entries
(list\map (..kv_format format))
- (text.join_with ..value_separator)
+ (text.interposed ..value_separator)
(text.enclosed [..object_start ..object_end])))
(def: .public (format json)
diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux
index 281425105..11254a92c 100644
--- a/stdlib/source/library/lux/data/format/markdown.lux
+++ b/stdlib/source/library/lux/data/format/markdown.lux
@@ -93,7 +93,7 @@
(if (text.empty? line)
line
(format with line))))
- (text.join_with text.new_line)))
+ (text.interposed text.new_line)))
(def: indent
(-> Text Text)
@@ -121,7 +121,7 @@
#.None
""))))
- (text.join_with text.new_line)
+ (text.interposed text.new_line)
..block))
(def: .public bullet_list
@@ -139,7 +139,7 @@
#.None
""))))
- (text.join_with text.new_line)
+ (text.interposed text.new_line)
..block))
(def: .public snippet
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 8dd91b2ee..7f1346df1 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -44,7 +44,7 @@
max_size)
padding (|> "0"
(list.repeated padding_size)
- (text.join_with ""))]
+ text.joined)]
(format padding number)))
(def: blank " ")
@@ -132,9 +132,9 @@
(Parser Small)
(do <>.monad
[digits (<binary>.segment ..small_size)
- digits (<>.lift (\ utf8.codec decode digits))
+ digits (<>.lifted (\ utf8.codec decode digits))
_ ..small_suffix]
- (<>.lift
+ (<>.lifted
(do {! try.monad}
[value (\ n.octal decode digits)]
(..small value)))))
@@ -143,12 +143,12 @@
(Parser Big)
(do <>.monad
[digits (<binary>.segment ..big_size)
- digits (<>.lift (\ utf8.codec decode digits))
+ digits (<>.lifted (\ utf8.codec decode digits))
end <binary>.bits/8
_ (let [expected (`` (char (~~ (static ..blank))))]
(<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end)))]
- (<>.lift
+ (<>.lifted
(do {! try.monad}
[value (\ n.octal decode digits)]
(..big value)))))
@@ -201,9 +201,9 @@
(Parser [Nat Checksum])
(do <>.monad
[ascii (<binary>.segment ..small_size)
- digits (<>.lift (\ utf8.codec decode ascii))
+ digits (<>.lifted (\ utf8.codec decode ascii))
_ ..small_suffix
- value (<>.lift
+ value (<>.lifted
(\ n.octal decode digits))]
(in [value
(:abstraction (format digits ..checksum_suffix))])))
@@ -285,7 +285,7 @@
.let [expected (`` (char (~~ (static ..null))))]
_ (<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end))]
- (<>.lift
+ (<>.lifted
(do {! try.monad}
[ascii (..un_padded string)
text (\ utf8.codec decode ascii)]
@@ -293,7 +293,7 @@
(def: .public <none>
<type>
- (try.assumed (<in> "")))
+ (try.trusted (<in> "")))
)]
[Name Text ..name_size name_is_too_long name from_name name_writer name_parser anonymous]
@@ -329,7 +329,7 @@
.let [expected (`` (char (~~ (static ..null))))]
_ (<>.assertion (exception.error ..wrong_character [expected end])
(n.= expected end))]
- (<>.lift
+ (<>.lifted
(\ try.monad map (|>> :abstraction)
(\ utf8.codec decode string)))))
)
@@ -436,7 +436,7 @@
(<options>)
_
- (<>.lift
+ (<>.lifted
(exception.except ..invalid_link_flag [(.nat linkflag)]))))))
)
@@ -459,7 +459,7 @@
(Writer Mode)
(|>> :representation
..small
- try.assumed
+ try.trusted
..small_writer))
(exception: .public (invalid_mode {value Nat})
@@ -520,7 +520,7 @@
(if (n.<= (:representation ..maximum_mode)
value)
(in (:abstraction value))
- (<>.lift
+ (<>.lifted
(exception.except ..invalid_mode [value]))))))
)
@@ -584,7 +584,7 @@
(def: no_device
Device
- (try.assumed (..small 0)))
+ (try.trusted (..small 0)))
(type: .public Tar
(Row Entry))
@@ -777,7 +777,7 @@
modification_time ..big_parser
[actual checksum_code] ..checksum_parser
_ (let [expected (expected_checksum checksum_code binary_header)]
- (<>.lift
+ (<>.lifted
(exception.assertion ..wrong_checksum [expected actual]
(n.= expected actual))))
link_flag ..link_flag_parser
@@ -817,7 +817,7 @@
.let [size (get@ #size header)
rounded_size (..rounded_content_size size)]
content (<binary>.segment (..from_big size))
- content (<>.lift (..content content))
+ content (<>.lifted (..content content))
_ (<binary>.segment (n.- (..from_big size) rounded_size))]
(in [(get@ #path header)
(|> header
@@ -838,7 +838,7 @@
(-> Link_Flag (-> Header Path) (Parser Path))
(do <>.monad
[header ..header_parser
- _ (<>.lift
+ _ (<>.lifted
(exception.assertion ..wrong_link_flag [expected (get@ #link_flag header)]
(n.= (..link_flag expected)
(..link_flag (get@ #link_flag header)))))]
@@ -864,7 +864,7 @@
(do <>.monad
[block (<binary>.segment ..block_size)]
(let [actual (..checksum block)]
- (<>.lift
+ (<>.lifted
(exception.assertion ..wrong_checksum [0 actual]
(n.= 0 actual))))))
@@ -875,7 +875,7 @@
(do <>.monad
[_ (<>.at_most 2 end_of_archive_block_parser)
done? <binary>.end?]
- (<>.lift
+ (<>.lifted
(exception.assertion ..invalid_end_of_archive []
done?))))
diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux
index 637ba71f7..67722607c 100644
--- a/stdlib/source/library/lux/data/format/xml.lux
+++ b/stdlib/source/library/lux/data/format/xml.lux
@@ -239,7 +239,7 @@
dictionary.entries
(list\map (function (_ [key value])
($_ text\compose (..attribute key) "=" text.double_quote (sanitize_value value) text.double_quote)))
- (text.join_with " "))))]
+ (text.interposed " "))))]
(function (_ input)
($_ text\compose
..xml_header text.new_line
@@ -269,7 +269,7 @@
($_ text\compose prefix "<" tag attrs ">"
(|> xml_children
(list\map (|>> (recur (text\compose prefix text.tab)) (text\compose text.new_line)))
- (text.join_with ""))
+ text.joined)
text.new_line prefix "</" tag ">")))))
))))
(def: decode
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index e2f781d64..2670bdae3 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -297,7 +297,7 @@
(|>> list.reversed
(list\fold compose identity))))
-(def: .public (join_with separator texts)
+(def: .public (interposed separator texts)
(-> Text (List Text) Text)
(case separator
"" (..joined texts)
diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux
index fe56f754b..f46331176 100644
--- a/stdlib/source/library/lux/data/text/escape.lux
+++ b/stdlib/source/library/lux/data/text/escape.lux
@@ -23,7 +23,7 @@
(template [<char> <sigil>]
[(def: <char>
- (|> <sigil> (//.char 0) maybe.assume))]
+ (|> <sigil> (//.char 0) maybe.trusted))]
[sigil_char ..sigil]
[\u_sigil "u"]
@@ -31,7 +31,7 @@
(template [<literal> <sigil> <escaped>]
[(def: <sigil>
- (|> <literal> (//.char 0) maybe.assume))
+ (|> <literal> (//.char 0) maybe.trusted))
(def: <escaped>
(format ..sigil <literal>))]
@@ -50,7 +50,7 @@
(template [<char> <text>]
[(def: <char>
- (|> <text> (//.char 0) maybe.assume))]
+ (|> <text> (//.char 0) maybe.trusted))]
[\0 //.\0]
[\a //.\a]
diff --git a/stdlib/source/library/lux/data/text/format.lux b/stdlib/source/library/lux/data/text/format.lux
index 3438e3f96..1a274b692 100644
--- a/stdlib/source/library/lux/data/text/format.lux
+++ b/stdlib/source/library/lux/data/text/format.lux
@@ -121,7 +121,7 @@
(def: .public (list formatter)
(All [a] (-> (Format a) (Format (List a))))
(|>> (list\map (|>> formatter (format " ")))
- (text.join_with "")
+ text.joined
(text.enclosed ["(list" ")"])))
(def: .public (maybe format)
diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux
index 795bee383..4998e9ce9 100644
--- a/stdlib/source/library/lux/data/text/regex.lux
+++ b/stdlib/source/library/lux/data/text/regex.lux
@@ -52,11 +52,9 @@
(-> Text (Parser Text))
(<>.after (<text>.this reference) (<>\in reference)))
-(def: (join_text^ part^)
+(def: join_text^
(-> (Parser (List Text)) (Parser Text))
- (do <>.monad
- [parts part^]
- (in (//.join_with "" parts))))
+ (\ <>.monad map //.joined))
(def: name_char^
(Parser Text)
@@ -87,9 +85,9 @@
(def: re_range^
(Parser Code)
(do {! <>.monad}
- [from (|> regex_char^ (\ ! map (|>> (//.char 0) maybe.assume)))
+ [from (|> regex_char^ (\ ! map (|>> (//.char 0) maybe.trusted)))
_ (<text>.this "-")
- to (|> regex_char^ (\ ! map (|>> (//.char 0) maybe.assume)))]
+ to (|> regex_char^ (\ ! map (|>> (//.char 0) maybe.trusted)))]
(in (` ((~! <text>.range) (~ (code.nat from)) (~ (code.nat to)))))))
(def: re_char^
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index ab3c1672b..be47d038a 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -31,7 +31,7 @@
(Tree :@: Block [])
- (def: .public (compose left right)
+ (def: .public (composite left right)
(-> Set Set Set)
(:abstraction
(\ builder branch
@@ -47,7 +47,7 @@
(-> [Block (List Block)] Set)
(list\fold (: (-> Block Set Set)
(function (_ block set)
- (..compose (..singleton block) set)))
+ (..composite (..singleton block) set)))
(..singleton head)
tail))
@@ -154,7 +154,7 @@
(def: .public character
Set
- ($_ ..compose
+ ($_ ..composite
..character/0
..character/1
..character/2
@@ -197,7 +197,7 @@
(def: .public full
Set
- ($_ ..compose
+ ($_ ..composite
..character
..non_character
))