diff options
Diffstat (limited to 'stdlib/source/library/lux/data/collection/sequence.lux')
-rw-r--r-- | stdlib/source/library/lux/data/collection/sequence.lux | 148 |
1 files changed, 109 insertions, 39 deletions
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux index c015edb06..86558bbb1 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 (.require [library - [lux (.except list has revised only) + [lux (.except list has revised only all) [abstract [functor (.only Functor)] [apply (.only Apply)] @@ -63,7 +63,8 @@ (with_template [<name> <op>] [(def <name> - (-> Level Level) + (-> Level + Level) (<op> branching_exponent))] [level_up n.+] @@ -79,15 +80,19 @@ (-- full_node_size)) (def branch_idx - (-> Index Index) + (-> Index + Index) (i64.and branch_idx_mask)) (def (empty_hierarchy _) - (All (_ a) (-> Any (Hierarchy a))) + (All (_ of) + (-> Any + (Hierarchy of))) (array.empty ..full_node_size)) (def (tail_off sequence_size) - (-> Nat Nat) + (-> Nat + Nat) (if (n.< full_node_size sequence_size) 0 (|> (-- sequence_size) @@ -95,7 +100,9 @@ (i64.left_shifted branching_exponent)))) (def (path level tail) - (All (_ a) (-> Level (Base a) (Node a))) + (All (_ of) + (-> Level (Base of) + (Node of))) (if (n.= 0 level) {#Base tail} (|> (empty_hierarchy []) @@ -103,12 +110,16 @@ {#Hierarchy}))) (def (tail singleton) - (All (_ a) (-> a (Base a))) + (All (_ of) + (-> of + (Base of))) (|> (array.empty 1) (array.has! 0 singleton))) (def (with_tail size level tail parent) - (All (_ a) (-> Nat Level (Base a) (Hierarchy a) (Hierarchy a))) + (All (_ of) + (-> Nat Level (Base of) (Hierarchy of) + (Hierarchy of))) (let [sub_idx (branch_idx (i64.right_shifted level (-- size))) ... If we're currently on a bottom node sub_node (if (n.= branching_exponent level) @@ -129,14 +140,18 @@ (array.has! sub_idx sub_node)))) (def (expanded_tail val tail) - (All (_ a) (-> a (Base a) (Base a))) + (All (_ of) + (-> of (Base of) + (Base of))) (let [tail_size (array.size tail)] (|> (array.empty (++ tail_size)) (array.copy! tail_size 0 tail 0) (array.has! tail_size val)))) (def (hierarchy#has level idx val hierarchy) - (All (_ a) (-> Level Index a (Hierarchy a) (Hierarchy a))) + (All (_ of) + (-> Level Index of (Hierarchy of) + (Hierarchy of))) (let [sub_idx (branch_idx (i64.right_shifted level idx))] (when (array.item sub_idx hierarchy) {#Hierarchy sub_node} @@ -154,7 +169,9 @@ (undefined)))) (def (without_tail size level hierarchy) - (All (_ a) (-> Nat Level (Hierarchy a) (Maybe (Hierarchy a)))) + (All (_ of) + (-> Nat Level (Hierarchy of) + (Maybe (Hierarchy of)))) (let [sub_idx (branch_idx (i64.right_shifted level (n.- 2 size)))] (cond (n.= 0 sub_idx) {.#None} @@ -179,7 +196,9 @@ ))) (def (node#list node) - (All (_ a) (-> (Node a) (List a))) + (All (_ of) + (-> (Node of) + (List of))) (when node {#Base base} (array.list {.#None} base) @@ -192,12 +211,12 @@ (list#composite (node#list sub) acc)) {.#End})))) -(type .public (Sequence a) +(type .public (Sequence of) (Record [#level Level #size Nat - #root (Hierarchy a) - #tail (Base a)])) + #root (Hierarchy of) + #tail (Base of)])) (def .public empty Sequence @@ -207,11 +226,15 @@ #tail (array.empty 0)]) (def .public (size sequence) - (All (_ a) (-> (Sequence a) Nat)) + (All (_ of) + (-> (Sequence of) + Nat)) (the #size sequence)) (def .public (suffix val sequence) - (All (_ a) (-> a (Sequence a) (Sequence a))) + (All (_ of) + (-> of (Sequence of) + (Sequence of))) ... Check if there is room in the tail. (let [sequence_size (the #size sequence)] (if (|> sequence_size (n.- (tail_off sequence_size)) (n.< full_node_size)) @@ -244,7 +267,8 @@ (exception.def incorrect_sequence_structure) (exception.def .public (index_out_of_bounds [sequence index]) - (All (_ a) (Exception [(Sequence a) Nat])) + (All (_ of) + (Exception [(Sequence of) Nat])) (exception.report (.list ["Size" (at n.decimal encoded (the #size sequence))] ["Index" (at n.decimal encoded index)]))) @@ -252,11 +276,15 @@ (exception.def base_was_not_found) (def .public (within_bounds? sequence idx) - (All (_ a) (-> (Sequence a) Nat Bit)) + (All (_ of) + (-> (Sequence of) Nat + Bit)) (n.< (the #size sequence) idx)) (def (base_for idx sequence) - (All (_ a) (-> Index (Sequence a) (Try (Base a)))) + (All (_ of) + (-> Index (Sequence of) + (Try (Base of)))) (if (within_bounds? sequence idx) (if (n.< (tail_off (the #size sequence)) idx) (loop (again [level (the #level sequence) @@ -278,7 +306,9 @@ (exception.except ..index_out_of_bounds [sequence idx]))) (def .public (item idx sequence) - (All (_ a) (-> Nat (Sequence a) (Try a))) + (All (_ of) + (-> Nat (Sequence of) + (Try of))) (do try.monad [base (base_for idx sequence) .let [index (branch_idx idx)]] @@ -287,7 +317,9 @@ {try.#Success (array.item index base)}))) (def .public (has idx val sequence) - (All (_ a) (-> Nat a (Sequence a) (Try (Sequence a)))) + (All (_ of) + (-> Nat of (Sequence of) + (Try (Sequence of)))) (let [sequence_size (the #size sequence)] (if (within_bounds? sequence idx) {try.#Success (if (n.< (tail_off sequence_size) idx) @@ -300,13 +332,17 @@ (exception.except ..index_out_of_bounds [sequence idx])))) (def .public (revised idx revision it) - (All (_ a) (-> Nat (-> a a) (Sequence a) (Try (Sequence a)))) + (All (_ of) + (-> Nat (-> of of) (Sequence of) + (Try (Sequence of)))) (do try.monad [val (..item idx it)] (..has idx (revision val) it))) (def .public (prefix sequence) - (All (_ a) (-> (Sequence a) (Sequence a))) + (All (_ of) + (-> (Sequence of) + (Sequence of))) (when (the #size sequence) 0 empty @@ -351,20 +387,28 @@ )) (def .public (list sequence) - (All (_ a) (-> (Sequence a) (List a))) + (All (_ of) + (-> (Sequence of) + (List of))) (list#composite (node#list {#Hierarchy (the #root sequence)}) (node#list {#Base (the #tail sequence)}))) (def .public of_list - (All (_ a) (-> (List a) (Sequence a))) + (All (_ of) + (-> (List of) + (Sequence of))) (list#mix ..suffix ..empty)) (def .public (member? equivalence sequence val) - (All (_ a) (-> (Equivalence a) (Sequence a) a Bit)) + (All (_ of) + (-> (Equivalence of) (Sequence of) of + Bit)) (list.member? equivalence (list sequence) val)) (def .public empty? - (All (_ a) (-> (Sequence a) Bit)) + (All (_ of) + (-> (Sequence of) + Bit)) (|>> (the #size) (n.= 0))) (def .public sequence @@ -372,7 +416,9 @@ (in (.list (` (..of_list (.list (,* elems)))))))) (def (node_equivalence //#=) - (All (_ a) (-> (Equivalence a) (Equivalence (Node a)))) + (All (_ of) + (-> (Equivalence of) + (Equivalence (Node of)))) (implementation (def (= v1 v2) (when [v1 v2] @@ -386,7 +432,9 @@ false)))) (def .public (equivalence //#=) - (All (_ a) (-> (Equivalence a) (Equivalence (Sequence a)))) + (All (_ of) + (-> (Equivalence of) + (Equivalence (Sequence of)))) (implementation (def (= v1 v2) (and (n.= (the #size v1) (the #size v2)) @@ -423,7 +471,8 @@ {#Base (the #tail xs)}))))) (def .public monoid - (All (_ a) (Monoid (Sequence a))) + (All (_ of) + (Monoid (Sequence of))) (implementation (def identity ..empty) @@ -479,15 +528,18 @@ (mix (function (_ post pre) (composite pre post)) identity))))) (def .public reversed - (All (_ a) (-> (Sequence a) (Sequence a))) + (All (_ of) + (-> (Sequence of) + (Sequence of))) (|>> ..list list.reversed (list#mix suffix ..empty))) (with_template [<name> <array> <init> <op>] [(def .public <name> - (All (_ a) - (-> (Predicate a) (Sequence a) Bit)) + (All (_ of) + (-> (Predicate of) (Sequence of) + Bit)) (let [help (is (All (_ a) (-> (Predicate a) (Node a) Bit)) (function (help predicate node) @@ -507,7 +559,9 @@ ) (def .public (only when items) - (All (_ a) (-> (-> a Bit) (Sequence a) (Sequence a))) + (All (_ of) + (-> (-> of Bit) (Sequence of) + (Sequence of))) (..mix (function (_ item output) (if (when item) (..suffix item output) @@ -516,8 +570,9 @@ items)) (def (one|node check items) - (All (_ a b) - (-> (-> a (Maybe b)) (Node a) (Maybe b))) + (All (_ input output) + (-> (-> input (Maybe output)) (Node input) + (Maybe output))) (when items {#Base items} (array.one check items) @@ -526,8 +581,9 @@ (array.one (one|node check) items))) (def .public (one check items) - (All (_ a b) - (-> (-> a (Maybe b)) (Sequence a) (Maybe b))) + (All (_ input output) + (-> (-> input (Maybe output)) (Sequence input) + (Maybe output))) (when (let [... TODO: This binding was established to get around a compilation error. Fix and inline! check (..one|node check)] (|> items @@ -540,3 +596,17 @@ output output)) + +(def .public (all ? it) + (All (_ input output) + (-> (-> input (Maybe output)) (Sequence input) + (Sequence output))) + (..mix (function (_ in out) + (when (? in) + {.#Some in} + (suffix in out) + + {.#None} + out)) + (sequence) + it)) |