diff options
Diffstat (limited to 'stdlib/source/library')
-rw-r--r-- | stdlib/source/library/lux/data/collection/stream.lux (renamed from stdlib/source/library/lux/data/collection/sequence.lux) | 56 | ||||
-rw-r--r-- | stdlib/source/library/lux/documentation.lux | 14 |
2 files changed, 35 insertions, 35 deletions
diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/stream.lux index fcfe2d0ed..f09423882 100644 --- a/stdlib/source/library/lux/data/collection/sequence.lux +++ b/stdlib/source/library/lux/data/collection/stream.lux @@ -19,23 +19,23 @@ [number ["n" nat]]]]]) -(type: .public (Sequence a) - (Cont [a (Sequence a)])) +(type: .public (Stream a) + (Cont [a (Stream a)])) (def: .public (iterations step init) (All (_ a b) - (-> (-> a [a b]) a (Sequence b))) + (-> (-> a [a b]) a (Stream b))) (let [[next x] (step init)] (//.pending [x (iterations step next)]))) (def: .public (repeated x) (All (_ a) - (-> a (Sequence a))) + (-> a (Stream a))) (//.pending [x (repeated x)])) (def: .public (cycle [start next]) (All (_ a) - (-> [a (List a)] (Sequence a))) + (-> [a (List a)] (Stream a))) (loop [head start tail next] (//.pending [head (case tail @@ -46,18 +46,18 @@ (again head' tail'))]))) (template [<name> <return>] - [(def: .public (<name> sequence) - (All (_ a) (-> (Sequence a) <return>)) - (let [[head tail] (//.result sequence)] + [(def: .public (<name> stream) + (All (_ a) (-> (Stream a) <return>)) + (let [[head tail] (//.result stream)] <name>))] [head a] - [tail (Sequence a)] + [tail (Stream a)] ) -(def: .public (item idx sequence) - (All (_ a) (-> Nat (Sequence a) a)) - (let [[head tail] (//.result sequence)] +(def: .public (item idx stream) + (All (_ a) (-> Nat (Stream a) a)) + (let [[head tail] (//.result stream)] (case idx 0 head _ (item (-- idx) tail)))) @@ -65,7 +65,7 @@ (template [<taker> <dropper> <pred_type> <pred_test> <pred_step> <post_test>] [(def: .public (<taker> pred xs) (All (_ a) - (-> <pred_type> (Sequence a) (List a))) + (-> <pred_type> (Stream a) (List a))) (let [[x xs'] (//.result xs)] (if (<post_test> <pred_test>) (list& x (<taker> <pred_step> xs')) @@ -73,7 +73,7 @@ (def: .public (<dropper> pred xs) (All (_ a) - (-> <pred_type> (Sequence a) (Sequence a))) + (-> <pred_type> (Stream a) (Stream a))) (let [[x xs'] (//.result xs)] (if (<post_test> <pred_test>) (<dropper> <pred_step> xs') @@ -86,7 +86,7 @@ (template [<splitter> <pred_type> <pred_test> <pred_step>] [(def: .public (<splitter> pred xs) (All (_ a) - (-> <pred_type> (Sequence a) [(List a) (Sequence a)])) + (-> <pred_type> (Stream a) [(List a) (Stream a)])) (let [[x xs'] (//.result xs)] (if <pred_test> [(list) xs] @@ -97,27 +97,27 @@ [split_at Nat (n.= 0 pred) (-- pred)] ) -(def: .public (only predicate sequence) - (All (_ a) (-> (-> a Bit) (Sequence a) (Sequence a))) - (let [[head tail] (//.result sequence)] +(def: .public (only predicate stream) + (All (_ a) (-> (-> a Bit) (Stream a) (Stream a))) + (let [[head tail] (//.result stream)] (if (predicate head) (//.pending [head (only predicate tail)]) (only predicate tail)))) (def: .public (partition left? xs) - (All (_ a) (-> (-> a Bit) (Sequence a) [(Sequence a) (Sequence a)])) + (All (_ a) (-> (-> a Bit) (Stream a) [(Stream a) (Stream a)])) [(..only left? xs) (..only (bit.complement left?) xs)]) (implementation: .public functor - (Functor Sequence) + (Functor Stream) (def: (each f fa) (let [[head tail] (//.result fa)] (//.pending [(f head) (each f tail)])))) (implementation: .public comonad - (CoMonad Sequence) + (CoMonad Stream) (def: &functor ..functor) @@ -127,14 +127,14 @@ (let [[head tail] (//.result wa)] (//.pending [wa (disjoint tail)])))) -(syntax: .public (^sequence& [patterns (<code>.form (<>.many <code>.any)) - body <code>.any - branches (<>.some <code>.any)]) - (with_symbols [g!sequence] +(syntax: .public (^stream& [patterns (<code>.form (<>.many <code>.any)) + body <code>.any + branches (<>.some <code>.any)]) + (with_symbols [g!stream] (let [body+ (` (let [(~+ (|> patterns (list#each (function (_ pattern) - (list (` [(~ pattern) (~ g!sequence)]) - (` ((~! //.result) (~ g!sequence)))))) + (list (` [(~ pattern) (~ g!stream)]) + (` ((~! //.result) (~ g!stream)))))) list#conjoint))] (~ body)))] - (in (list& g!sequence body+ branches))))) + (in (list& g!stream body+ branches))))) diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index 5bd6f7f30..ec99259f9 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -18,7 +18,7 @@ [collection ["[0]" list ("[1]#[0]" monad mix monoid)] ["[0]" set {"+" Set}] - ["[0]" sequence {"+" Sequence}]] + ["[0]" stream {"+" Stream}]] [format ["md" markdown {"+" Markdown Block}]]] ["[0]" macro @@ -165,9 +165,9 @@ ) (def: type_variable_names - (Sequence Text) - (sequence.iterations (product.forked ++ parameter_type_name) - 0)) + (Stream Text) + (stream.iterations (product.forked ++ parameter_type_name) + 0)) (template [<name> <partition>] [(def: (<name> id) @@ -193,9 +193,9 @@ _ (let [parameter_id (n.- (list.size type_function_arguments) parameter_id)] (|> type_variable_names - (sequence.only (function (_ var_name) - (not (list.member? text.equivalence type_function_arguments var_name)))) - (sequence.item parameter_id))))) + (stream.only (function (_ var_name) + (not (list.member? text.equivalence type_function_arguments var_name)))) + (stream.item parameter_id))))) type_function_name)) (def: (level_parameters offset level) |