aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/data/collection/sequence.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/data/collection/sequence.lux')
-rw-r--r--stdlib/source/library/lux/data/collection/sequence.lux100
1 files changed, 50 insertions, 50 deletions
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux
index 01a33b7c7..4c935a3d4 100644
--- a/stdlib/source/library/lux/data/collection/sequence.lux
+++ b/stdlib/source/library/lux/data/collection/sequence.lux
@@ -3,7 +3,7 @@
... https://hypirion.com/musings/understanding-persistent-vector-pt-3
(.using
[library
- [lux {"-" list}
+ [lux {"-" list has revised}
["@" target]
[abstract
[functor {"+" Functor}]
@@ -205,58 +205,58 @@
(def: .public (size sequence)
(All (_ a) (-> (Sequence a) Nat))
- (value@ #size sequence))
+ (the #size sequence))
(def: .public (suffix val sequence)
(All (_ a) (-> a (Sequence a) (Sequence a)))
... Check if there is room in the tail.
- (let [sequence_size (value@ #size sequence)]
+ (let [sequence_size (the #size sequence)]
(if (|> sequence_size (n.- (tail_off sequence_size)) (n.< full_node_size))
... If so, append to it.
(|> sequence
- (revised@ #size ++)
- (revised@ #tail (..expanded_tail val)))
+ (.revised #size ++)
+ (.revised #tail (..expanded_tail val)))
... Otherwise, push tail into the tree
... --------------------------------------------------------
... Will the root experience an overflow with this addition?
- (|> (if (n.> (i64.left_shifted (value@ #level sequence) 1)
+ (|> (if (n.> (i64.left_shifted (the #level sequence) 1)
(i64.right_shifted branching_exponent sequence_size))
... If so, a brand-new root must be established, that is
... 1-level taller.
(|> sequence
- (with@ #root (|> (`` (: (Hierarchy (~~ (:of val)))
- (empty_hierarchy [])))
- (array.has! 0 {#Hierarchy (value@ #root sequence)})
- (array.has! 1 (..path (value@ #level sequence) (value@ #tail sequence)))))
- (revised@ #level level_up))
+ (.has #root (|> (`` (: (Hierarchy (~~ (:of val)))
+ (empty_hierarchy [])))
+ (array.has! 0 {#Hierarchy (the #root sequence)})
+ (array.has! 1 (..path (the #level sequence) (the #tail sequence)))))
+ (.revised #level level_up))
... Otherwise, just push the current tail onto the root.
(|> sequence
- (revised@ #root (..with_tail sequence_size (value@ #level sequence) (value@ #tail sequence)))))
+ (.revised #root (..with_tail sequence_size (the #level sequence) (the #tail sequence)))))
... Finally, update the size of the sequence and grow a new
... tail with the new element as it's sole member.
- (revised@ #size ++)
- (with@ #tail (..tail val)))
+ (.revised #size ++)
+ (.has #tail (..tail val)))
)))
(exception: incorrect_sequence_structure)
(exception: .public [a] (index_out_of_bounds [sequence (Sequence a)
index Nat])
- (exception.report ["Size" (# n.decimal encoded (value@ #size sequence))]
+ (exception.report ["Size" (# n.decimal encoded (the #size sequence))]
["Index" (# n.decimal encoded index)]))
(exception: base_was_not_found)
(def: .public (within_bounds? sequence idx)
(All (_ a) (-> (Sequence a) Nat Bit))
- (n.< (value@ #size sequence) idx))
+ (n.< (the #size sequence) idx))
(def: (base_for idx sequence)
(All (_ a) (-> Index (Sequence a) (Try (Base a))))
(if (within_bounds? sequence idx)
- (if (n.< (tail_off (value@ #size sequence)) idx)
- (loop [level (value@ #level sequence)
- hierarchy (value@ #root sequence)]
+ (if (n.< (tail_off (the #size sequence)) idx)
+ (loop [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 [])
@@ -270,7 +270,7 @@
_
(exception.except ..incorrect_sequence_structure [])))))
- {try.#Success (value@ #tail sequence)})
+ {try.#Success (the #tail sequence)})
(exception.except ..index_out_of_bounds [sequence idx])))
(def: .public (item idx sequence)
@@ -284,12 +284,12 @@
(def: .public (has idx val sequence)
(All (_ a) (-> Nat a (Sequence a) (Try (Sequence a))))
- (let [sequence_size (value@ #size sequence)]
+ (let [sequence_size (the #size sequence)]
(if (within_bounds? sequence idx)
{try.#Success (if (n.< (tail_off sequence_size) idx)
- (revised@ #root (hierarchy#has (value@ #level sequence) idx val)
+ (.revised #root (hierarchy#has (the #level sequence) idx val)
sequence)
- (revised@ #tail (`` (: (-> (Base (~~ (:of val)))
+ (.revised #tail (`` (: (-> (Base (~~ (:of val)))
(Base (~~ (:of val))))
(|>> array.clone (array.has! (branch_idx idx) val))))
sequence))}
@@ -303,7 +303,7 @@
(def: .public (prefix sequence)
(All (_ a) (-> (Sequence a) (Sequence a)))
- (case (value@ #size sequence)
+ (case (the #size sequence)
0
empty
@@ -312,19 +312,19 @@
sequence_size
(if (|> sequence_size (n.- (tail_off sequence_size)) (n.> 1))
- (let [old_tail (value@ #tail sequence)
+ (let [old_tail (the #tail sequence)
new_tail_size (-- (array.size old_tail))]
(|> sequence
- (revised@ #size --)
- (with@ #tail (|> (array.empty new_tail_size)
- (array.copy! new_tail_size 0 old_tail 0)))))
+ (.revised #size --)
+ (.has #tail (|> (array.empty new_tail_size)
+ (array.copy! new_tail_size 0 old_tail 0)))))
(maybe.trusted
(do maybe.monad
[new_tail (base_for (n.- 2 sequence_size) sequence)
- .let [[level' root'] (let [init_level (value@ #level 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 (value@ #root sequence)))]
+ (without_tail sequence_size init_level (the #root sequence)))]
(with_expansions [<else> [level root]]
(if (n.> branching_exponent level)
(if (array.lacks? 1 root)
@@ -340,16 +340,16 @@
<else>)
<else>))))]]
(in (|> sequence
- (revised@ #size --)
- (with@ #level level')
- (with@ #root root')
- (with@ #tail new_tail))))))
+ (.revised #size --)
+ (.has #level level')
+ (.has #root root')
+ (.has #tail new_tail))))))
))
(def: .public (list sequence)
(All (_ a) (-> (Sequence a) (List a)))
- (list#composite (node#list {#Hierarchy (value@ #root sequence)})
- (node#list {#Base (value@ #tail sequence)})))
+ (list#composite (node#list {#Hierarchy (the #root sequence)})
+ (node#list {#Base (the #tail sequence)})))
(def: .public of_list
(All (_ a) (-> (List a) (Sequence a)))
@@ -361,7 +361,7 @@
(def: .public empty?
(All (_ a) (-> (Sequence a) Bit))
- (|>> (value@ #size) (n.= 0)))
+ (|>> (the #size) (n.= 0)))
(syntax: .public (sequence [elems (<>.some <code>.any)])
(in (.list (` (..of_list (.list (~+ elems)))))))
@@ -384,12 +384,12 @@
(All (_ a) (-> (Equivalence a) (Equivalence (Sequence a))))
(def: (= v1 v2)
- (and (n.= (value@ #size v1) (value@ #size v2))
+ (and (n.= (the #size v1) (the #size v2))
(let [(^open "node#[0]") (node_equivalence //#=)]
- (and (node#= {#Base (value@ #tail v1)}
- {#Base (value@ #tail v2)})
- (node#= {#Hierarchy (value@ #root v1)}
- {#Hierarchy (value@ #root v2)}))))))
+ (and (node#= {#Base (the #tail v1)}
+ {#Base (the #tail v2)})
+ (node#= {#Hierarchy (the #root v1)}
+ {#Hierarchy (the #root v2)}))))))
(implementation: node_mix
(Mix Node)
@@ -414,8 +414,8 @@
(mix $
(mix $
init
- {#Hierarchy (value@ #root xs)})
- {#Base (value@ #tail xs)}))))
+ {#Hierarchy (the #root xs)})
+ {#Base (the #tail xs)}))))
(implementation: .public monoid
(All (_ a) (Monoid (Sequence a)))
@@ -440,12 +440,12 @@
(Functor Sequence)
(def: (each $ xs)
- [#level (value@ #level xs)
- #size (value@ #size xs)
+ [#level (the #level xs)
+ #size (the #size xs)
#root (let [... TODO: This binding was established to get around a compilation error. Fix and inline!
$ (# node_functor each $)]
- (|> xs (value@ #root) (array.each $)))
- #tail (|> xs (value@ #tail) (array.each $))]))
+ (|> xs (the #root) (array.each $)))
+ #tail (|> xs (the #tail) (array.each $))]))
(implementation: .public apply
(Apply Sequence)
@@ -526,11 +526,11 @@
(case (let [... TODO: This binding was established to get around a compilation error. Fix and inline!
check (..one|node check)]
(|> items
- (value@ #root)
+ (the #root)
(array.one check)))
{.#None}
(|> items
- (value@ #tail)
+ (the #tail)
(array.one check))
output