diff options
author | Eduardo Julian | 2018-07-03 22:30:49 -0400 |
---|---|---|
committer | Eduardo Julian | 2018-07-03 22:30:49 -0400 |
commit | 49d59ddc16a588115e02303fd325e46d6c1c87ac (patch) | |
tree | 72cd5b349684fdeb4ddaaa370c91c11217a07466 /stdlib/source | |
parent | f505b42847bd7ba54b14d4b593b883c1bb25501d (diff) |
- Re-named "stream" to "sequence".
- Updated copyright dates for lux-mode.
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/data/coll/sequence.lux (renamed from stdlib/source/lux/data/coll/stream.lux) | 64 |
1 files changed, 32 insertions, 32 deletions
diff --git a/stdlib/source/lux/data/coll/stream.lux b/stdlib/source/lux/data/coll/sequence.lux index 305a5da4e..b8908403b 100644 --- a/stdlib/source/lux/data/coll/stream.lux +++ b/stdlib/source/lux/data/coll/sequence.lux @@ -12,29 +12,29 @@ bool))) ## [Types] -(type: #export (Stream a) - {#.doc "An infinite stream of values."} - (Cont [a (Stream a)])) +(type: #export (Sequence a) + {#.doc "An infinite sequence of values."} + (Cont [a (Sequence a)])) ## [Utils] (def: (cycle' x xs init full) (All [a] - (-> a (List a) a (List a) (Stream a))) + (-> a (List a) a (List a) (Sequence a))) (case xs #.Nil (pending [x (cycle' init full init full)]) (#.Cons x' xs') (pending [x (cycle' x' xs' init full)]))) ## [Functions] (def: #export (iterate f x) - {#.doc "Create a stream by applying a function to a value, and to its result, on and on..."} + {#.doc "Create a sequence by applying a function to a value, and to its result, on and on..."} (All [a] - (-> (-> a a) a (Stream a))) + (-> (-> a a) a (Sequence a))) (pending [x (iterate f (f x))])) (def: #export (repeat x) {#.doc "Repeat a value forever."} (All [a] - (-> a (Stream a))) + (-> a (Sequence a))) (pending [x (repeat x)])) (def: #export (cycle xs) @@ -42,22 +42,22 @@ The list should not be empty."} (All [a] - (-> (List a) (Maybe (Stream a)))) + (-> (List a) (Maybe (Sequence a)))) (case xs #.Nil #.None (#.Cons x xs') (#.Some (cycle' x xs' x xs')))) (do-template [<name> <return> <part>] [(def: #export (<name> s) - (All [a] (-> (Stream a) <return>)) + (All [a] (-> (Sequence a) <return>)) (let [[h t] (continuation.run s)] <part>))] [head a h] - [tail (Stream a) t]) + [tail (Sequence a) t]) (def: #export (nth idx s) - (All [a] (-> Nat (Stream a) a)) + (All [a] (-> Nat (Sequence a) a)) (let [[h t] (continuation.run s)] (if (n/> +0 idx) (nth (dec idx) t) @@ -66,7 +66,7 @@ (do-template [<taker> <dropper> <splitter> <pred-type> <pred-test> <pred-step>] [(def: #export (<taker> pred xs) (All [a] - (-> <pred-type> (Stream a) (List a))) + (-> <pred-type> (Sequence a) (List a))) (let [[x xs'] (continuation.run xs)] (if <pred-test> (list& x (<taker> <pred-step> xs')) @@ -74,7 +74,7 @@ (def: #export (<dropper> pred xs) (All [a] - (-> <pred-type> (Stream a) (Stream a))) + (-> <pred-type> (Sequence a) (Sequence a))) (let [[x xs'] (continuation.run xs)] (if <pred-test> (<dropper> <pred-step> xs') @@ -82,7 +82,7 @@ (def: #export (<splitter> pred xs) (All [a] - (-> <pred-type> (Stream a) [(List a) (Stream a)])) + (-> <pred-type> (Sequence a) [(List a) (Sequence a)])) (let [[x xs'] (continuation.run xs)] (if <pred-test> (let [[tail next] (<splitter> <pred-step> xs')] @@ -94,53 +94,53 @@ ) (def: #export (unfold step init) - {#.doc "A stateful way of infinitely calculating the values of a stream."} + {#.doc "A stateful way of infinitely calculating the values of a sequence."} (All [a b] - (-> (-> a [a b]) a (Stream b))) + (-> (-> a [a b]) a (Sequence b))) (let [[next x] (step init)] (pending [x (unfold step next)]))) (def: #export (filter p xs) - (All [a] (-> (-> a Bool) (Stream a) (Stream a))) + (All [a] (-> (-> a Bool) (Sequence a) (Sequence a))) (let [[x xs'] (continuation.run xs)] (if (p x) (pending [x (filter p xs')]) (filter p xs')))) (def: #export (partition p xs) - {#.doc "Split a stream in two based on a predicate. + {#.doc "Split a sequence in two based on a predicate. The left side contains all entries for which the predicate is true. The right side contains all entries for which the predicate is false."} - (All [a] (-> (-> a Bool) (Stream a) [(Stream a) (Stream a)])) + (All [a] (-> (-> a Bool) (Sequence a) [(Sequence a) (Sequence a)])) [(filter p xs) (filter (complement p) xs)]) ## [Structures] -(struct: #export _ (Functor Stream) +(struct: #export _ (Functor Sequence) (def: (map f fa) (let [[h t] (continuation.run fa)] (pending [(f h) (map f t)])))) -(struct: #export _ (CoMonad Stream) - (def: functor Functor<Stream>) +(struct: #export _ (CoMonad Sequence) + (def: functor Functor<Sequence>) (def: unwrap head) (def: (split wa) (let [[head tail] (continuation.run wa)] (pending [wa (split tail)])))) ## [Pattern-matching] -(syntax: #export (^stream& {patterns (s.form (p.many s.any))} - body - {branches (p.some s.any)}) - {#.doc (doc "Allows destructuring of streams in pattern-matching expressions." - "Caveat emptor: Only use it for destructuring, and not for testing values within the streams." - (let [(^stream& x y z _tail) (some-stream-func 1 2 3)] +(syntax: #export (^sequence& {patterns (s.form (p.many s.any))} + body + {branches (p.some s.any)}) + {#.doc (doc "Allows destructuring of sequences in pattern-matching expressions." + "Caveat emptor: Only use it for destructuring, and not for testing values within the sequences." + (let [(^sequence& x y z _tail) (some-sequence-func 1 2 3)] (func x y z)))} - (with-gensyms [g!stream] + (with-gensyms [g!sequence] (let [body+ (` (let [(~+ (List/join (List/map (function (_ pattern) - (list (` [(~ pattern) (~ g!stream)]) - (` ((~! continuation.run) (~ g!stream))))) + (list (` [(~ pattern) (~ g!sequence)]) + (` ((~! continuation.run) (~ g!sequence))))) patterns)))] (~ body)))] - (wrap (list& g!stream body+ branches))))) + (wrap (list& g!sequence body+ branches))))) |