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/binary.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/bits.lux18
-rw-r--r--stdlib/source/library/lux/data/collection/dictionary/ordered.lux18
-rw-r--r--stdlib/source/library/lux/data/collection/list.lux8
-rw-r--r--stdlib/source/library/lux/data/collection/queue/priority.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux10
-rw-r--r--stdlib/source/library/lux/data/collection/stream.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/tree.lux6
-rw-r--r--stdlib/source/library/lux/data/collection/tree/finger.lux4
-rw-r--r--stdlib/source/library/lux/data/collection/tree/zipper.lux4
-rw-r--r--stdlib/source/library/lux/data/format/json.lux2
-rw-r--r--stdlib/source/library/lux/data/format/tar.lux2
-rw-r--r--stdlib/source/library/lux/data/format/xml.lux4
-rw-r--r--stdlib/source/library/lux/data/text.lux18
-rw-r--r--stdlib/source/library/lux/data/text/escape.lux16
-rw-r--r--stdlib/source/library/lux/data/text/unicode/set.lux2
16 files changed, 63 insertions, 63 deletions
diff --git a/stdlib/source/library/lux/data/binary.lux b/stdlib/source/library/lux/data/binary.lux
index 4baadaf05..6cea2f879 100644
--- a/stdlib/source/library/lux/data/binary.lux
+++ b/stdlib/source/library/lux/data/binary.lux
@@ -34,8 +34,8 @@
(def: .public (aggregate $ init it)
(All (_ a) (-> (-> I64 a a) a Binary a))
(let [size (/.size it)]
- (loop [index 0
- output init]
+ (loop (again [index 0
+ output init])
(if (n.< size index)
(again (++ index) ($ (/.bytes/1 index it) output))
output))))
diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux
index 797bb5981..c6f692f52 100644
--- a/stdlib/source/library/lux/data/collection/bits.lux
+++ b/stdlib/source/library/lux/data/collection/bits.lux
@@ -64,9 +64,9 @@
[(def: .public (<name> index input)
(-> Nat Bits Bits)
(let [[chunk_index bit_index] (n./% chunk_size index)]
- (loop [size|output (n.max (++ chunk_index)
- (array.size input))
- output ..empty]
+ (loop (again [size|output (n.max (++ chunk_index)
+ (array.size input))
+ output ..empty])
(let [idx|output (-- size|output)]
(if (n.> 0 size|output)
(case (|> (..chunk idx|output input)
@@ -98,7 +98,7 @@
(-> Bits Bits Bit)
(let [chunks (n.min (array.size reference)
(array.size sample))]
- (loop [idx 0]
+ (loop (again [idx 0])
(if (n.< chunks idx)
(.or (|> (..chunk idx sample)
(i64.and (..chunk idx reference))
@@ -114,8 +114,8 @@
..empty
size|output
- (loop [size|output size|output
- output ..empty]
+ (loop (again [size|output size|output
+ output ..empty])
(let [idx (-- size|output)]
(case (|> input (..chunk idx) i64.not .nat)
0
@@ -139,8 +139,8 @@
..empty
size|output
- (loop [size|output size|output
- output ..empty]
+ (loop (again [size|output size|output
+ output ..empty])
(let [idx (-- size|output)]
(if (n.> 0 size|output)
(case (|> (..chunk idx subject)
@@ -168,7 +168,7 @@
(def: (= reference sample)
(let [size (n.max (array.size reference)
(array.size sample))]
- (loop [idx 0]
+ (loop (again [idx 0])
(if (n.< size idx)
(.and ("lux i64 ="
(..chunk idx reference)
diff --git a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
index 217c07d1e..b9226a891 100644
--- a/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
+++ b/stdlib/source/library/lux/data/collection/dictionary/ordered.lux
@@ -62,7 +62,7 @@
(All (_ k v) (-> k (Dictionary k v) (Maybe v)))
(let [... (open "_#[0]") (the #&order dict)
]
- (loop [node (the #root dict)]
+ (loop (again [node (the #root dict)])
(case node
{.#None}
{.#None}
@@ -87,7 +87,7 @@
(All (_ k v) (-> (Dictionary k v) k Bit))
(let [... (open "_#[0]") (the #&order dict)
]
- (loop [node (the #root dict)]
+ (loop (again [node (the #root dict)])
(case node
{.#None}
#0
@@ -109,7 +109,7 @@
{.#None}
{.#Some node}
- (loop [node node]
+ (loop (again [node node])
(case (the <side> node)
{.#None}
{.#Some (the #value node)}
@@ -123,7 +123,7 @@
(def: .public (size dict)
(All (_ k v) (-> (Dictionary k v) Nat))
- (loop [node (the #root dict)]
+ (loop (again [node (the #root dict)])
(case node
{.#None}
0
@@ -252,7 +252,7 @@
(def: .public (has key value dict)
(All (_ k v) (-> k v (Dictionary k v) (Dictionary k v)))
(let [(open "_#[0]") (the #&order dict)
- root' (loop [?root (the #root dict)]
+ root' (loop (again [?root (the #root dict)])
(case ?root
{.#None}
{.#Some (red key value {.#None} {.#None})}
@@ -475,7 +475,7 @@
(def: .public (lacks key dict)
(All (_ k v) (-> k (Dictionary k v) (Dictionary k v)))
(let [(open "_#[0]") (the #&order dict)
- [?root found?] (loop [?root (the #root dict)]
+ [?root found?] (loop (again [?root (the #root dict)])
(case ?root
{.#Some root}
(let [root_key (the #key root)
@@ -546,7 +546,7 @@
(template [<name> <type> <output>]
[(def: .public (<name> dict)
(All (_ k v) (-> (Dictionary k v) (List <type>)))
- (loop [node (the #root dict)]
+ (loop (again [node (the #root dict)])
(case node
{.#None}
(list)
@@ -567,8 +567,8 @@
(def: (= reference sample)
(let [(open "/#[0]") (the #&order reference)]
- (loop [entriesR (entries reference)
- entriesS (entries sample)]
+ (loop (again [entriesR (entries reference)
+ entriesS (entries sample)])
(case [entriesR entriesS]
[{.#End} {.#End}]
#1
diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux
index 450bfea3a..19d15e35e 100644
--- a/stdlib/source/library/lux/data/collection/list.lux
+++ b/stdlib/source/library/lux/data/collection/list.lux
@@ -434,8 +434,8 @@
(def: (nat#encoded value)
(-> Nat Text)
- (loop [input value
- output ""]
+ (loop (again [input value
+ output ""])
(let [digit (case (n.% 10 input)
0 "0"
1 "1"
@@ -597,8 +597,8 @@
(def: .public (enumeration xs)
(All (_ a) (-> (List a) (List [Nat a])))
- (loop [idx 0
- xs xs]
+ (loop (again [idx 0
+ xs xs])
(case xs
{.#End}
{.#End}
diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux
index 102472124..904858147 100644
--- a/stdlib/source/library/lux/data/collection/queue/priority.lux
+++ b/stdlib/source/library/lux/data/collection/queue/priority.lux
@@ -58,7 +58,7 @@
0
{.#Some tree}
- (loop [node tree]
+ (loop (again [node tree])
(case (tree.root node)
{0 #0 _}
1
@@ -73,7 +73,7 @@
false
{.#Some tree}
- (loop [node tree]
+ (loop (again [node tree])
(case (tree.root node)
{0 #0 reference}
(# equivalence = reference member)
@@ -88,7 +88,7 @@
(do maybe.monad
[tree (representation queue)
.let [highest_priority (tree.tag tree)]]
- (loop [node tree]
+ (loop (again [node tree])
(case (tree.root node)
{0 #0 reference}
(if (n.= highest_priority (tree.tag node))
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index 285a65109..f786a9276 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -257,8 +257,8 @@
(All (_ a) (-> Index (Sequence a) (Try (Base a))))
(if (within_bounds? sequence idx)
(if (n.< (tail_off (the #size sequence)) idx)
- (loop [level (the #level sequence)
- hierarchy (the #root sequence)]
+ (loop (again [level (the #level sequence)
+ hierarchy (the #root sequence)])
(let [index (branch_idx (i64.right_shifted level idx))]
(if (array.lacks? index hierarchy)
(exception.except ..base_was_not_found [])
@@ -324,9 +324,9 @@
(do maybe.monad
[new_tail (base_for (n.- 2 sequence_size) sequence)
.let [[level' root'] (let [init_level (the #level sequence)]
- (loop [level init_level
- root (maybe.else (empty_hierarchy [])
- (without_tail sequence_size init_level (the #root sequence)))]
+ (loop (again [level init_level
+ root (maybe.else (empty_hierarchy [])
+ (without_tail sequence_size init_level (the #root sequence)))])
(with_expansions [<else> [level root]]
(if (n.> branching_exponent level)
(if (array.lacks? 1 root)
diff --git a/stdlib/source/library/lux/data/collection/stream.lux b/stdlib/source/library/lux/data/collection/stream.lux
index 2c059103a..672fa8f72 100644
--- a/stdlib/source/library/lux/data/collection/stream.lux
+++ b/stdlib/source/library/lux/data/collection/stream.lux
@@ -36,8 +36,8 @@
(def: .public (cycle [start next])
(All (_ a)
(-> [a (List a)] (Stream a)))
- (loop [head start
- tail next]
+ (loop (again [head start
+ tail next])
(//.pending [head (case tail
{.#End}
(again start next)
diff --git a/stdlib/source/library/lux/data/collection/tree.lux b/stdlib/source/library/lux/data/collection/tree.lux
index b0940209e..58694df25 100644
--- a/stdlib/source/library/lux/data/collection/tree.lux
+++ b/stdlib/source/library/lux/data/collection/tree.lux
@@ -55,9 +55,9 @@
(<>.and <code>.any)))
(syntax: .public (tree [root tree^])
- (in (list (` (~ (loop [[value children] root]
- (` [#value (~ value)
- #children (list (~+ (list#each again children)))])))))))
+ (in (list (loop (again [[value children] root])
+ (` [#value (~ value)
+ #children (list (~+ (list#each again children)))])))))
(implementation: .public (equivalence super)
(All (_ a) (-> (Equivalence a) (Equivalence (Tree a))))
diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux
index 26caf5317..3c8e5e1db 100644
--- a/stdlib/source/library/lux/data/collection/tree/finger.lux
+++ b/stdlib/source/library/lux/data/collection/tree/finger.lux
@@ -87,8 +87,8 @@
(let [[monoid tag root] (representation tree)]
(if (predicate tag)
(let [(open "tag//[0]") monoid]
- (loop [_tag tag//identity
- _node root]
+ (loop (again [_tag tag//identity
+ _node root])
(case _node
{0 #0 value}
{.#Some value}
diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux
index 9986e63a8..4f9889f9c 100644
--- a/stdlib/source/library/lux/data/collection/tree/zipper.lux
+++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux
@@ -177,7 +177,7 @@
{.#Some forward}
{.#None}
- (loop [@ zipper]
+ (loop (again [@ zipper])
(case (..right @)
{.#Some forward}
{.#Some forward}
@@ -223,7 +223,7 @@
{.#None}
{.#Some @}
- (loop [@ @]
+ (loop (again [@ @])
(case (<move> @)
{.#None}
{.#Some @}
diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux
index 0a08da9b6..2f21d8dc5 100644
--- a/stdlib/source/library/lux/data/format/json.lux
+++ b/stdlib/source/library/lux/data/format/json.lux
@@ -383,7 +383,7 @@
(def: string_parser
(Parser String)
(<| (<text>.enclosed [text.double_quote text.double_quote])
- (loop [_ []])
+ (loop (again [_ []]))
(do [! <>.monad]
[chars (<text>.some (<text>.none_of (text#composite "\" text.double_quote)))
stop <text>.next])
diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux
index 2387b162f..264acaf46 100644
--- a/stdlib/source/library/lux/data/format/tar.lux
+++ b/stdlib/source/library/lux/data/format/tar.lux
@@ -233,7 +233,7 @@
(-> Binary (Try Binary))
(case (binary.size string)
0 {try.#Success string}
- size (loop [end (-- size)]
+ size (loop (again [end (-- size)])
(case end
0 {try.#Success (# utf8.codec encoded "")}
_ (do try.monad
diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux
index b7e3fd2e3..81fee7699 100644
--- a/stdlib/source/library/lux/data/format/xml.lux
+++ b/stdlib/source/library/lux/data/format/xml.lux
@@ -246,8 +246,8 @@
(function (_ input)
($_ text#composite
..xml_header text.new_line
- (loop [prefix ""
- input input]
+ (loop (again [prefix ""
+ input input])
(case input
{#Text value}
(sanitize_value value)
diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux
index 5ac09a8e5..e52ca50c0 100644
--- a/stdlib/source/library/lux/data/text.lux
+++ b/stdlib/source/library/lux/data/text.lux
@@ -68,9 +68,9 @@
(def: .public (last_index part text)
(-> Text Text (Maybe Nat))
- (loop [offset 0
- output (is (Maybe Nat)
- {.#None})]
+ (loop (again [offset 0
+ output (is (Maybe Nat)
+ {.#None})])
(let [output' ("lux text index" offset part text)]
(case output'
{.#None}
@@ -164,8 +164,8 @@
(def: .public (all_split_by token sample)
(-> Text Text (List Text))
- (loop [input sample
- output (is (List Text) (list))]
+ (loop (again [input sample
+ output (is (List Text) (list))])
(case (..split_by token input)
{.#Some [pre post]}
(|> output
@@ -212,8 +212,8 @@
(def: .public (replaced pattern replacement template)
(-> Text Text Text Text)
(with_expansions [... Inefficient default
- <default> (loop [left ""
- right template]
+ <default> (loop (again [left ""
+ right template])
(case (..split_by pattern right)
{.#Some [pre post]}
(again ($_ "lux text concat" left pre replacement) post)
@@ -301,8 +301,8 @@
(as Nat))
... Platform-independent default.
(let [length ("lux text size" input)]
- (loop [index 0
- hash 0]
+ (loop (again [index 0
+ hash 0])
(if (n.< length index)
(again (++ index)
(|> hash
diff --git a/stdlib/source/library/lux/data/text/escape.lux b/stdlib/source/library/lux/data/text/escape.lux
index 3209c406d..a3b549273 100644
--- a/stdlib/source/library/lux/data/text/escape.lux
+++ b/stdlib/source/library/lux/data/text/escape.lux
@@ -112,10 +112,10 @@
(def: .public (escaped text)
(-> Text Text)
- (loop [offset 0
- previous ""
- current text
- limit ("lux text size" text)]
+ (loop (again [offset 0
+ previous ""
+ current text
+ limit ("lux text size" text)])
(if (n.< limit offset)
(case ("lux text char" offset current)
(^.template [<char> <replacement>]
@@ -196,10 +196,10 @@
(def: .public (un_escaped text)
(-> Text (Try Text))
- (loop [offset 0
- previous ""
- current text
- limit ("lux text size" text)]
+ (loop (again [offset 0
+ previous ""
+ current text
+ limit ("lux text size" text)])
(if (n.< limit offset)
(case ("lux text char" offset current)
(pattern (static ..sigil_char))
diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux
index 89359273b..df7afedc8 100644
--- a/stdlib/source/library/lux/data/text/unicode/set.lux
+++ b/stdlib/source/library/lux/data/text/unicode/set.lux
@@ -214,7 +214,7 @@
(def: .public (member? set character)
(-> Set Char Bit)
- (loop [tree (representation set)]
+ (loop (again [tree (representation set)])
(if (//block.within? (tree.tag tree) character)
(case (tree.root tree)
{0 #0 _}