Copyright | (c) 2017 Harendra Kumar |
---|---|
License | BSD3 |
Maintainer | harendra.kumar@gmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
This module is designed to be imported qualified:
import qualified Streamly.Prelude as S
Functions with the suffix M
are general functions that work on monadic
arguments. The corresponding functions without the suffix M
work on pure
arguments and can in general be derived from their monadic versions but are
provided for convenience and for consistency with other pure APIs in the
base
package.
Deconstruction and folds accept a SerialT
type instead of a polymorphic
type to ensure that streams always have a concrete monomorphic type by
default, reducing type errors. In case you want to use any other type of
stream you can use one of the type combinators provided in the Streamly
module to convert the stream type.
- nil :: IsStream t => t m a
- consM :: (IsStream t, Monad m) => m a -> t m a -> t m a
- (|:) :: (IsStream t, Monad m) => m a -> t m a -> t m a
- cons :: IsStream t => a -> t m a -> t m a
- (.:) :: IsStream t => a -> t m a -> t m a
- unfoldr :: IsStream t => (b -> Maybe (a, b)) -> b -> t m a
- unfoldrM :: (IsStream t, Monad m) => (b -> m (Maybe (a, b))) -> b -> t m a
- once :: (IsStream t, Monad m) => m a -> t m a
- replicateM :: (IsStream t, Monad m) => Int -> m a -> t m a
- repeatM :: (IsStream t, Monad m) => m a -> t m a
- iterate :: IsStream t => (a -> a) -> a -> t m a
- iterateM :: (IsStream t, Monad m) => (a -> m a) -> a -> t m a
- fromFoldable :: (IsStream t, Foldable f) => f a -> t m a
- uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a))
- foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b
- foldrM :: Monad m => (a -> b -> m b) -> b -> SerialT m a -> m b
- foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b
- foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b
- foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b
- foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b
- mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m ()
- toList :: Monad m => SerialT m a -> m [a]
- all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
- any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
- head :: Monad m => SerialT m a -> m (Maybe a)
- tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a))
- last :: Monad m => SerialT m a -> m (Maybe a)
- null :: Monad m => SerialT m a -> m Bool
- length :: Monad m => SerialT m a -> m Int
- elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
- notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
- maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
- minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
- sum :: (Monad m, Num a) => SerialT m a -> m a
- product :: (Monad m, Num a) => SerialT m a -> m a
- scanl' :: IsStream t => (b -> a -> b) -> b -> t m a -> t m b
- scanx :: IsStream t => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
- filter :: IsStream t => (a -> Bool) -> t m a -> t m a
- take :: IsStream t => Int -> t m a -> t m a
- takeWhile :: IsStream t => (a -> Bool) -> t m a -> t m a
- drop :: IsStream t => Int -> t m a -> t m a
- dropWhile :: IsStream t => (a -> Bool) -> t m a -> t m a
- reverse :: IsStream t => t m a -> t m a
- mapM :: (IsStream t, Monad m) => (a -> m b) -> t m a -> t m b
- sequence :: (IsStream t, Monad m) => t m (m a) -> t m a
- zipWith :: IsStream t => (a -> b -> c) -> t m a -> t m b -> t m c
- zipWithM :: IsStream t => (a -> b -> t m c) -> t m a -> t m b -> t m c
- zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c
- zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> t m c) -> t m a -> t m b -> t m c
- fromHandle :: (IsStream t, MonadIO m) => Handle -> t m String
- toHandle :: MonadIO m => Handle -> SerialT m String -> m ()
- each :: (IsStream t, Foldable f) => f a -> t m a
- scan :: IsStream t => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
- foldl :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b
- foldlM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b
Construction
Primitives to construct or inspect a stream.
consM :: (IsStream t, Monad m) => m a -> t m a -> t m a infixr 5 Source #
Constructs a stream by adding a monadic action at the head of an existing stream. For example:
> toList $ getLine `consM` getLine `consM` nil hello world ["hello","world"]
Since: 0.2.0
(|:) :: (IsStream t, Monad m) => m a -> t m a -> t m a infixr 5 Source #
Operator equivalent of consM
.
> toList $ getLine |: getLine |: nil hello world ["hello","world"]
Since: 0.2.0
cons :: IsStream t => a -> t m a -> t m a infixr 5 Source #
Construct a stream by adding a pure value at the head of an existing
stream. Same as consM . return
. For example:
> toList $ 1 `cons` 2 `cons` 3 `cons` nil [1,2,3]
Since: 0.1.0
General Unfold
unfoldr :: IsStream t => (b -> Maybe (a, b)) -> b -> t m a Source #
Build a Stream by unfolding pure steps starting from a seed.
Since: 0.1.0
unfoldrM :: (IsStream t, Monad m) => (b -> m (Maybe (a, b))) -> b -> t m a Source #
Build a Stream by unfolding monadic steps starting from a seed.
Since: 0.1.0
Special Generation
Generate a monadic stream from an input structure, a seed or a generation function.
once :: (IsStream t, Monad m) => m a -> t m a Source #
Create a singleton stream by executing a monadic action once. Same as
m `consM` nil
but more efficient.
> toList $ once getLine hello ["hello"]
Since: 0.2.0
replicateM :: (IsStream t, Monad m) => Int -> m a -> t m a Source #
Generate a stream by performing a monadic action n
times.
Since: 0.1.1
repeatM :: (IsStream t, Monad m) => m a -> t m a Source #
Generate a stream by repeatedly executing a monadic action forever.
Since: 0.2.0
iterate :: IsStream t => (a -> a) -> a -> t m a Source #
Iterate a pure function from a seed value, streaming the results forever.
Since: 0.1.2
iterateM :: (IsStream t, Monad m) => (a -> m a) -> a -> t m a Source #
Iterate a monadic function from a seed value, streaming the results forever.
Since: 0.1.2
fromFoldable :: (IsStream t, Foldable f) => f a -> t m a Source #
Construct a stream from a Foldable
container.
Since: 0.2.0
Deconstruction
uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) Source #
Decompose a stream into its head and tail. If the stream is empty, returns
Nothing
. If the stream is non-empty, returns 'Just (a, ma)', where a
is
the head of the stream and ma
its tail.
Since: 0.1.0
Folding
General Folds
foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b Source #
Lazy right associative fold. For example, to fold a stream into a list:
>> runIdentity $ foldr (:) [] (serially $ fromFoldable [1,2,3]) [1,2,3]
Since: 0.1.0
foldrM :: Monad m => (a -> b -> m b) -> b -> SerialT m a -> m b Source #
Lazy right fold with a monadic step function. For example, to fold a stream into a list:
>> runIdentity $ foldrM (\x xs -> return (x : xs)) [] (serially $ fromFoldable [1,2,3]) [1,2,3]
Since: 0.2.0
foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b Source #
Strict left associative fold.
Since: 0.2.0
foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b Source #
Like foldl'
but with a monadic step function.
Since: 0.2.0
foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b Source #
Strict left fold with an extraction function. Like the standard strict
left fold, but applies a user supplied extraction function (the third
argument) to the folded value at the end. This is designed to work with the
foldl
library. The suffix x
is a mnemonic for extraction.
Since: 0.2.0
foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b Source #
Like foldx
, but with a monadic step function.
Since: 0.2.0
Special Folds
mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m () Source #
Apply a monadic action to each element of the stream and discard the output of the action.
Since: 0.1.0
toList :: Monad m => SerialT m a -> m [a] Source #
Convert a stream into a list in the underlying monad.
Since: 0.1.0
all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool Source #
Determine whether all elements of a stream satisfy a predicate.
Since: 0.1.0
any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool Source #
Determine whether any of the elements of a stream satisfy a predicate.
Since: 0.1.0
head :: Monad m => SerialT m a -> m (Maybe a) Source #
Extract the first element of the stream, if any.
Since: 0.1.0
tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) Source #
Extract all but the first element of the stream, if any.
Since: 0.1.1
last :: Monad m => SerialT m a -> m (Maybe a) Source #
Extract the last element of the stream, if any.
Since: 0.1.1
elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool Source #
Determine whether an element is present in the stream.
Since: 0.1.0
notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool Source #
Determine whether an element is not present in the stream.
Since: 0.1.0
maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) Source #
Determine the maximum element in a stream.
Since: 0.1.0
minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a) Source #
Determine the minimum element in a stream.
Since: 0.1.0
sum :: (Monad m, Num a) => SerialT m a -> m a Source #
Determine the sum of all elements of a stream of numbers
Since: 0.1.0
product :: (Monad m, Num a) => SerialT m a -> m a Source #
Determine the product of all elements of a stream of numbers
Since: 0.1.1
Scans
scanx :: IsStream t => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b Source #
Strict left scan with an extraction function. Like scanl'
, but applies a
user supplied extraction function (the third argument) at each step. This is
designed to work with the foldl
library. The suffix x
is a mnemonic for
extraction.
Since: 0.2.0
Filtering
filter :: IsStream t => (a -> Bool) -> t m a -> t m a Source #
Include only those elements that pass a predicate.
Since: 0.1.0
take :: IsStream t => Int -> t m a -> t m a Source #
Take first n
elements from the stream and discard the rest.
Since: 0.1.0
takeWhile :: IsStream t => (a -> Bool) -> t m a -> t m a Source #
End the stream as soon as the predicate fails on an element.
Since: 0.1.0
drop :: IsStream t => Int -> t m a -> t m a Source #
Discard first n
elements from the stream and take the rest.
Since: 0.1.0
dropWhile :: IsStream t => (a -> Bool) -> t m a -> t m a Source #
Drop elements in the stream as long as the predicate succeeds and then take the rest of the stream.
Since: 0.1.0
Reordering
reverse :: IsStream t => t m a -> t m a Source #
Returns the elements of the stream in reverse order. The stream must be finite.
Since: 0.1.1
Mapping
mapM :: (IsStream t, Monad m) => (a -> m b) -> t m a -> t m b Source #
Replace each element of the stream with the result of a monadic action applied on the element.
Since: 0.1.0
sequence :: (IsStream t, Monad m) => t m (m a) -> t m a Source #
Reduce a stream of monadic actions to a stream of the output of those actions.
Since: 0.1.0
Zipping
zipWith :: IsStream t => (a -> b -> c) -> t m a -> t m b -> t m c Source #
Zip two streams serially using a pure zipping function.
Since: 0.1.0
zipWithM :: IsStream t => (a -> b -> t m c) -> t m a -> t m b -> t m c Source #
Zip two streams serially using a monadic zipping function.
Since: 0.1.0
zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c Source #
Zip two streams concurrently (i.e. both the elements being zipped are generated concurrently) using a pure zipping function.
Since: 0.1.0
zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> t m c) -> t m a -> t m b -> t m c Source #
Zip two streams asyncly (i.e. both the elements being zipped are generated concurrently) using a monadic zipping function.
Since: 0.1.0
IO
fromHandle :: (IsStream t, MonadIO m) => Handle -> t m String Source #
Read lines from an IO Handle into a stream of Strings.
Since: 0.1.0
toHandle :: MonadIO m => Handle -> SerialT m String -> m () Source #
Write a stream of Strings to an IO Handle.
Since: 0.1.0
Deprecated
scan :: IsStream t => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b Source #
Deprecated: Please use scanx instead.
Since: 0.1.1