leveldb-haskell-0.6.1: Haskell bindings to LevelDB

Copyright(c) 2014 Kim Altintop
LicenseBSD3
Maintainerkim.altintop@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Stream.Monadic

Contents

Description

(Mostly mechanical) adaptation of the Data.Stream module from the stream-fusion package to a monadic Stream datatype similar to the one proposed by Michael Snoyman for the conduit package.

The intention here is to provide a high-level, Data.List-like interface to Database.LevelDB.Iterators with predictable space and time complexity (see Database.LevelDB.Streaming), and without introducing a dependency eg. on one of the streaming libraries (all relevant datatypes are fully exported, though, so it should be straightforward to write wrappers for your favourite streaming library).

Fusion and inlining rules and strictness annotations have been put in place faithfully, and may need further profiling. Also, some functions (from Data.List) have been omitted for various reasons. Missing functions may be added upon request.

Synopsis

Documentation

data Step a s Source

Constructors

Yield a !s 
Skip !s 
Done 

data Stream m a Source

Constructors

forall s . Stream (s -> m (Step a s)) (m s) 

Instances

Monad m => Functor (Stream m) 

Conversion with lists

toList :: (Functor m, Monad m) => Stream m a -> m [a] Source

fromList :: Monad m => [a] -> Stream m a Source

Basic functions

append :: (Functor m, Monad m) => Stream m a -> Stream m a -> Stream m a Source

cons :: (Functor m, Monad m) => a -> Stream m a -> Stream m a Source

snoc :: (Functor m, Monad m) => Stream m a -> a -> Stream m a Source

head :: Monad m => Stream m a -> m (Maybe a) Source

Unlike head, this function does not diverge if the Stream is empty. Instead, Nothing is returned.

last :: Monad m => Stream m a -> m (Maybe a) Source

Unlike last, this function does not diverge if the Stream is empty. Instead, Nothing is returned.

tail :: (Functor m, Monad m) => Stream m a -> Stream m a Source

Unlike tail, this function does not diverge if the Stream is empty. Instead, it is the identity in this case.

init :: (Functor m, Monad m) => Stream m a -> Stream m a Source

Unlike init, this function does not diverge if the Stream is empty. Instead, it is the identity in this case.

null :: Monad m => Stream m a -> m Bool Source

length :: Monad m => Stream m a -> m Int Source

Transformations

map :: Monad m => (a -> b) -> Stream m a -> Stream m b Source

mapM :: (Functor m, Monad m) => (a -> m b) -> Stream m a -> Stream m b Source

mapM_ :: (Functor m, Monad m) => (a -> m b) -> Stream m a -> Stream m () Source

reverse :: (Functor m, Monad m) => Stream m a -> m (Stream m a) Source

intersperse :: (Functor m, Monad m) => a -> Stream m a -> Stream m a Source

intercalate :: (Functor m, Monad m) => Stream m a -> Stream m [a] -> Stream m a Source

Folds

foldl :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b Source

foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b Source

foldr :: (Functor m, Monad m) => (a -> b -> b) -> b -> Stream m a -> m b Source

foldMap :: (Monoid m, Functor n, Monad n) => (a -> m) -> Stream n a -> n m Source

foldM :: Monad m => (b -> a -> m b) -> b -> Stream m a -> m b Source

foldM_ :: Monad m => (b -> a -> m b) -> b -> Stream m a -> m () Source

Special folds

concat :: (Functor m, Monad m) => Stream m [a] -> Stream m a Source

concatMap :: (Functor m, Monad m) => (a -> Stream m b) -> Stream m a -> Stream m b Source

and :: (Functor m, Monad m) => Stream m Bool -> m Bool Source

or :: (Functor m, Monad m) => Stream m Bool -> m Bool Source

any :: Monad m => (a -> Bool) -> Stream m a -> m Bool Source

all :: Monad m => (a -> Bool) -> Stream m a -> m Bool Source

sum :: (Num a, Monad m) => Stream m a -> m a Source

product :: (Num a, Monad m) => Stream m a -> m a Source

Building streams

Scans

scanl :: (Functor m, Monad m) => (b -> a -> b) -> b -> Stream m a -> Stream m b Source

Infinite streams

iterate :: Monad m => (a -> a) -> a -> Stream m a Source

repeat :: Monad m => a -> Stream m a Source

replicate :: Monad m => Int -> a -> Stream m a Source

cycle :: (Functor m, Monad m) => Stream m a -> Stream m a Source

Unlike cycle, this function does not diverge if the Stream is empty. Instead, it is the identity in this case.

Unfolding

unfoldr :: Monad m => (b -> Maybe (a, b)) -> b -> Stream m a Source

unfoldrM :: (Functor m, Monad m) => (b -> Maybe (a, m b)) -> m b -> Stream m a Source

Build a stream from a monadic seed (or state function).

Substreams

Extracting substreams

take :: (Functor m, Monad m) => Int -> Stream m a -> Stream m a Source

drop :: (Functor m, Monad m) => Int -> Stream m a -> Stream m a Source

splitAt :: (Functor m, Monad m) => Int -> Stream m a -> (Stream m a, Stream m a) Source

splitAt n s = (take n s, drop n s)

Note that the resulting Streams share their state, so do not interleave traversals.

takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a Source

dropWhile :: (Functor m, Monad m) => (a -> Bool) -> Stream m a -> Stream m a Source

span :: (Functor m, Monad m) => (a -> Bool) -> Stream m a -> (Stream m a, Stream m a) Source

break :: (Functor m, Monad m) => (a -> Bool) -> Stream m a -> (Stream m a, Stream m a) Source

Predicates

isPrefixOf :: (Eq a, Monad m) => Stream m a -> Stream m a -> m Bool Source

isSuffixOf :: (Eq a, Functor m, Monad m) => Stream m a -> Stream m a -> m Bool Source

Note that this is:

isSuffixOf a b = reverse a `isPrefixOf` reverse b

It might be more efficient to construct the Streams in reverse order and use isPrefixOf directly, as reverse is O(n) and requires a finite stream argument.

Searching streams

Searching by equality

elem :: (Eq a, Monad m) => a -> Stream m a -> m Bool Source

notElem :: (Eq a, Monad m) => a -> Stream m a -> m Bool Source

lookup :: (Eq a, Monad m) => a -> Stream m (a, b) -> m (Maybe b) Source

Searching with a predicate

find :: Monad m => (a -> Bool) -> Stream m a -> m (Maybe a) Source

filter :: Monad m => (a -> Bool) -> Stream m a -> Stream m a Source

Zipping and unzipping

zip :: (Functor m, Applicative m, Monad m) => Stream m a -> Stream m b -> Stream m (a, b) Source

zip3 :: (Functor m, Applicative m, Monad m) => Stream m a -> Stream m b -> Stream m c -> Stream m (a, b, c) Source

zip4 :: (Functor m, Applicative m, Monad m) => Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m (a, b, c, d) Source

zipWith :: (Functor m, Applicative m, Monad m) => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c Source

zipWith3 :: (Functor m, Applicative m, Monad m) => (a -> b -> c -> d) -> Stream m a -> Stream m b -> Stream m c -> Stream m d Source

zipWith4 :: (Functor m, Applicative m, Monad m) => (a -> b -> c -> d -> e) -> Stream m a -> Stream m b -> Stream m c -> Stream m d -> Stream m e Source

unzip :: (Functor m, Monad m) => Stream m (a, b) -> m ([a], [b]) Source

unzip3 :: (Functor m, Monad m) => Stream m (a, b, c) -> m ([a], [b], [c]) Source

unzip4 :: (Functor m, Monad m) => Stream m (a, b, c, d) -> m ([a], [b], [c], [d]) Source

Special streams

"Set" operations

delete :: (Eq a, Functor m, Monad m) => a -> Stream m a -> Stream m a Source

insert :: (Ord a, Functor m, Monad m) => a -> Stream m a -> Stream m a Source

Generalized functions

deleteBy :: (Functor m, Monad m) => (a -> a -> Bool) -> a -> Stream m a -> Stream m a Source

User-supplied comparison, replacing an Ord context

insertBy :: (Functor m, Monad m) => (a -> a -> Ordering) -> a -> Stream m a -> Stream m a Source

The "generic" operations

genericLength :: (Num i, Functor m, Monad m) => Stream m a -> m i Source

genericTake :: (Integral i, Functor m, Monad m) => i -> Stream m a -> Stream m a Source

genericDrop :: (Integral i, Functor m, Monad m) => i -> Stream m a -> Stream m a Source

genericSplitAt :: (Integral i, Functor m, Monad m) => i -> Stream m a -> (Stream m a, Stream m a) Source

genericReplicate :: (Integral i, Functor m, Monad m) => i -> a -> Stream m a Source

enumFromToInt :: Monad m => Int -> Int -> Stream m Int Source

Like fromList ([n..m] :: [Int]) but avoids allocating a list

enumFromToChar :: Monad m => Char -> Char -> Stream m Char Source

Like fromList ([n..m] :: [Char]) but avoids allocating a list

enumDeltaInteger :: Monad m => Integer -> Integer -> Stream m Integer Source

Like fromList ([n,n+d..] :: [Integer]) but avoids allocating a list