From 49d59ddc16a588115e02303fd325e46d6c1c87ac Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Tue, 3 Jul 2018 22:30:49 -0400 Subject: - Re-named "stream" to "sequence". - Updated copyright dates for lux-mode. --- stdlib/source/lux/data/coll/sequence.lux | 146 +++++++++++++++++++++++++++++++ stdlib/source/lux/data/coll/stream.lux | 146 ------------------------------- 2 files changed, 146 insertions(+), 146 deletions(-) create mode 100644 stdlib/source/lux/data/coll/sequence.lux delete mode 100644 stdlib/source/lux/data/coll/stream.lux (limited to 'stdlib/source') diff --git a/stdlib/source/lux/data/coll/sequence.lux b/stdlib/source/lux/data/coll/sequence.lux new file mode 100644 index 000000000..b8908403b --- /dev/null +++ b/stdlib/source/lux/data/coll/sequence.lux @@ -0,0 +1,146 @@ +(.module: + lux + (lux (control functor + monad + comonad + [continuation #+ pending Cont] + ["p" parser]) + [macro #+ with-gensyms] + (macro [code] + ["s" syntax #+ syntax: Syntax]) + (data (coll [list "List/" Monad]) + bool))) + +## [Types] +(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) (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 sequence by applying a function to a value, and to its result, on and on..."} + (All [a] + (-> (-> a a) a (Sequence a))) + (pending [x (iterate f (f x))])) + +(def: #export (repeat x) + {#.doc "Repeat a value forever."} + (All [a] + (-> a (Sequence a))) + (pending [x (repeat x)])) + +(def: #export (cycle xs) + {#.doc "Go over the elements of a list forever. + + The list should not be empty."} + (All [a] + (-> (List a) (Maybe (Sequence a)))) + (case xs + #.Nil #.None + (#.Cons x xs') (#.Some (cycle' x xs' x xs')))) + +(do-template [ ] + [(def: #export ( s) + (All [a] (-> (Sequence a) )) + (let [[h t] (continuation.run s)] + ))] + + [head a h] + [tail (Sequence a) t]) + +(def: #export (nth idx s) + (All [a] (-> Nat (Sequence a) a)) + (let [[h t] (continuation.run s)] + (if (n/> +0 idx) + (nth (dec idx) t) + h))) + +(do-template [ ] + [(def: #export ( pred xs) + (All [a] + (-> (Sequence a) (List a))) + (let [[x xs'] (continuation.run xs)] + (if + (list& x ( xs')) + (list)))) + + (def: #export ( pred xs) + (All [a] + (-> (Sequence a) (Sequence a))) + (let [[x xs'] (continuation.run xs)] + (if + ( xs') + xs))) + + (def: #export ( pred xs) + (All [a] + (-> (Sequence a) [(List a) (Sequence a)])) + (let [[x xs'] (continuation.run xs)] + (if + (let [[tail next] ( xs')] + [(#.Cons [x tail]) next]) + [(list) xs])))] + + [take-while drop-while split-while (-> a Bool) (pred x) pred] + [take drop split Nat (n/> +0 pred) (dec pred)] + ) + +(def: #export (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: #export (filter p xs) + (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 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) (Sequence a) [(Sequence a) (Sequence a)])) + [(filter p xs) (filter (complement p) xs)]) + +## [Structures] +(struct: #export _ (Functor Sequence) + (def: (map f fa) + (let [[h t] (continuation.run fa)] + (pending [(f h) (map f t)])))) + +(struct: #export _ (CoMonad Sequence) + (def: functor Functor) + (def: unwrap head) + (def: (split wa) + (let [[head tail] (continuation.run wa)] + (pending [wa (split tail)])))) + +## [Pattern-matching] +(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!sequence] + (let [body+ (` (let [(~+ (List/join (List/map (function (_ pattern) + (list (` [(~ pattern) (~ g!sequence)]) + (` ((~! continuation.run) (~ g!sequence))))) + patterns)))] + (~ body)))] + (wrap (list& g!sequence body+ branches))))) diff --git a/stdlib/source/lux/data/coll/stream.lux b/stdlib/source/lux/data/coll/stream.lux deleted file mode 100644 index 305a5da4e..000000000 --- a/stdlib/source/lux/data/coll/stream.lux +++ /dev/null @@ -1,146 +0,0 @@ -(.module: - lux - (lux (control functor - monad - comonad - [continuation #+ pending Cont] - ["p" parser]) - [macro #+ with-gensyms] - (macro [code] - ["s" syntax #+ syntax: Syntax]) - (data (coll [list "List/" Monad]) - bool))) - -## [Types] -(type: #export (Stream a) - {#.doc "An infinite stream of values."} - (Cont [a (Stream a)])) - -## [Utils] -(def: (cycle' x xs init full) - (All [a] - (-> a (List a) a (List a) (Stream 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..."} - (All [a] - (-> (-> a a) a (Stream a))) - (pending [x (iterate f (f x))])) - -(def: #export (repeat x) - {#.doc "Repeat a value forever."} - (All [a] - (-> a (Stream a))) - (pending [x (repeat x)])) - -(def: #export (cycle xs) - {#.doc "Go over the elements of a list forever. - - The list should not be empty."} - (All [a] - (-> (List a) (Maybe (Stream a)))) - (case xs - #.Nil #.None - (#.Cons x xs') (#.Some (cycle' x xs' x xs')))) - -(do-template [ ] - [(def: #export ( s) - (All [a] (-> (Stream a) )) - (let [[h t] (continuation.run s)] - ))] - - [head a h] - [tail (Stream a) t]) - -(def: #export (nth idx s) - (All [a] (-> Nat (Stream a) a)) - (let [[h t] (continuation.run s)] - (if (n/> +0 idx) - (nth (dec idx) t) - h))) - -(do-template [ ] - [(def: #export ( pred xs) - (All [a] - (-> (Stream a) (List a))) - (let [[x xs'] (continuation.run xs)] - (if - (list& x ( xs')) - (list)))) - - (def: #export ( pred xs) - (All [a] - (-> (Stream a) (Stream a))) - (let [[x xs'] (continuation.run xs)] - (if - ( xs') - xs))) - - (def: #export ( pred xs) - (All [a] - (-> (Stream a) [(List a) (Stream a)])) - (let [[x xs'] (continuation.run xs)] - (if - (let [[tail next] ( xs')] - [(#.Cons [x tail]) next]) - [(list) xs])))] - - [take-while drop-while split-while (-> a Bool) (pred x) pred] - [take drop split Nat (n/> +0 pred) (dec pred)] - ) - -(def: #export (unfold step init) - {#.doc "A stateful way of infinitely calculating the values of a stream."} - (All [a b] - (-> (-> a [a b]) a (Stream b))) - (let [[next x] (step init)] - (pending [x (unfold step next)]))) - -(def: #export (filter p xs) - (All [a] (-> (-> a Bool) (Stream a) (Stream 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. - - 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)])) - [(filter p xs) (filter (complement p) xs)]) - -## [Structures] -(struct: #export _ (Functor Stream) - (def: (map f fa) - (let [[h t] (continuation.run fa)] - (pending [(f h) (map f t)])))) - -(struct: #export _ (CoMonad Stream) - (def: functor Functor) - (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)] - (func x y z)))} - (with-gensyms [g!stream] - (let [body+ (` (let [(~+ (List/join (List/map (function (_ pattern) - (list (` [(~ pattern) (~ g!stream)]) - (` ((~! continuation.run) (~ g!stream))))) - patterns)))] - (~ body)))] - (wrap (list& g!stream body+ branches))))) -- cgit v1.2.3