typed-streams-0.1.0.1: A stream based replacement for lists

Safe HaskellNone
LanguageHaskell2010

Data.Stream

Description

The Data.Stream.Typed module contains more detailed documenation.

This module simply imports functions from Data.Stream.Typed and modifies them so inputs and outputs are always of type UnknownStream, which this module renames Stream (yes, this clashes with Stream in Data.Stream.Typed).

Because of this, using this module more closely emulates how ordinary lists work, but you miss some of the compile time information you can get using the "typed" module.

Synopsis

Documentation

class ToStream a Source #

Add instances to the toStream class to allow for easy conversion to streams. Technically you could just use runTimeFoldableToStream and ,unknownFoldableToStream to wrap data in streams, but with this approach you can specialise for particular datatypes if appropriate.

Minimal complete definition

toStream

Instances

ToStream ByteString Source # 
ToStream ByteString Source # 
ToStream [a] Source # 

Methods

toStream :: [a] -> Stream (LengthT [a]) (Element [a]) Source #

ToStream (Vector a) Source # 

Methods

toStream :: Vector a -> Stream (LengthT (Vector a)) (Element (Vector a)) Source #

Unbox a => ToStream (Vector a) Source # 

Methods

toStream :: Vector a -> Stream (LengthT (Vector a)) (Element (Vector a)) Source #

ToStream (Array i e) Source # 

Methods

toStream :: Array i e -> Stream (LengthT (Array i e)) (Element (Array i e)) Source #

type family Element mono :: * #

Type family for getting the type of the elements of a monomorphic container.

Instances

type Element ByteString 
type Element ByteString 
type Element IntSet 
type Element Text 
type Element Text 
type Element [a] 
type Element [a] = a
type Element (Maybe a) 
type Element (Maybe a) = a
type Element (IO a) 
type Element (IO a) = a
type Element (Identity a) 
type Element (Identity a) = a
type Element (Option a) 
type Element (Option a) = a
type Element (NonEmpty a) 
type Element (NonEmpty a) = a
type Element (ZipList a) 
type Element (ZipList a) = a
type Element (IntMap a) 
type Element (IntMap a) = a
type Element (Tree a) 
type Element (Tree a) = a
type Element (Seq a) 
type Element (Seq a) = a
type Element (ViewL a) 
type Element (ViewL a) = a
type Element (ViewR a) 
type Element (ViewR a) = a
type Element (Set e) 
type Element (Set e) = e
type Element (HashSet e) 
type Element (HashSet e) = e
type Element (Vector a) 
type Element (Vector a) = a
type Element (Vector a) 
type Element (Vector a) = a
type Element (Vector a) 
type Element (Vector a) = a
type Element (r -> a) 
type Element (r -> a) = a
type Element (Either a b) 
type Element (Either a b) = b
type Element (a, b) 
type Element (a, b) = b
type Element (Array i e) # 
type Element (Array i e) = e
type Element (Arg a b) 
type Element (Arg a b) = b
type Element (WrappedMonad m a) 
type Element (WrappedMonad m a) = a
type Element (Map k v) 
type Element (Map k v) = v
type Element (MaybeT m a) 
type Element (MaybeT m a) = a
type Element (ListT m a) 
type Element (ListT m a) = a
type Element (HashMap k v) 
type Element (HashMap k v) = v
type Element (WrappedArrow a b c) 
type Element (WrappedArrow a b c) = c
type Element (Const * m a) 
type Element (Const * m a) = a
type Element (StateT s m a) 
type Element (StateT s m a) = a
type Element (StateT s m a) 
type Element (StateT s m a) = a
type Element (WriterT w m a) 
type Element (WriterT w m a) = a
type Element (WriterT w m a) 
type Element (WriterT w m a) = a
type Element (IdentityT * m a) 
type Element (IdentityT * m a) = a
type Element (Product * f g a) 
type Element (Product * f g a) = a
type Element (ContT * r m a) 
type Element (ContT * r m a) = a
type Element (ReaderT * r m a) 
type Element (ReaderT * r m a) = a
type Element (Compose * * f g a) 
type Element (Compose * * f g a) = a
type Element (RWST r w s m a) 
type Element (RWST r w s m a) = a
type Element (RWST r w s m a) 
type Element (RWST r w s m a) = a

zip :: Stream a -> Stream b -> Stream (a, b) Source #

zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c Source #

filter :: (a -> Bool) -> Stream a -> Stream a Source #

concatMap :: (a -> Stream b) -> Stream a -> Stream b Source #

replicate :: Integral b => b -> a -> Stream a Source #

iterate :: (a -> a) -> a -> Stream a Source #

repeat :: a -> Stream a Source #

unfoldr :: (b -> Maybe (a, b)) -> b -> UnknownStream a Source #