Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => MonadIO (m :: Type -> Type) where
- class MonadCatch m => MonadMask (m :: Type -> Type)
- data ByteStream m r
- streamFile :: (MonadIO m, MonadMask m) => FilePath -> (ByteStream m () -> m r) -> m r
- streamHandle :: MonadIO m => Handle -> ByteStream m ()
- streamInput :: (MonadIO m, MonadMask m) => FilePath -> (ByteStream m () -> m r) -> m r
- streamInputs :: MonadIO m => [FilePath] -> (Stream (ByteStream m) m () -> r) -> r
- withOutputFile :: (MonadIO m, MonadMask m) => FilePath -> (Handle -> m a) -> m a
- data UnwantedTerminal = UnwantedTerminal
- protectTerm :: (Functor f, MonadIO m) => Stream f m r -> Stream f m r
- psequence :: MonadIO m => Int -> Stream (Of (IO a)) m b -> Stream (Of a) m b
- progressGen :: MonadLog m => (Int -> a -> String) -> Int -> Stream (Of a) m r -> Stream (Of a) m r
- progressNum :: MonadLog m => String -> Int -> Stream (Of a) m r -> Stream (Of a) m r
- progressPos :: MonadLog m => (a -> (Refseq, Int)) -> String -> Refs -> Int -> Stream (Of a) m r -> Stream (Of a) m r
- mergeStreams :: (Monad m, Ord a) => Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
- mergeStreamsBy :: Monad m => (a -> a -> Ordering) -> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
- mergeStreamsOn :: (Monad m, Ord b) => (a -> b) -> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s)
- join :: Monad m => m (m a) -> m a
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- class Applicative f => Alternative (f :: Type -> Type) where
- (<|>) :: f a -> f a -> f a
- newtype Compose (f :: k -> Type) (g :: k1 -> k) (a :: k1) :: forall k k1. (k -> Type) -> (k1 -> k) -> k1 -> Type = Compose {
- getCompose :: f (g a)
- data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type
- class Bifunctor (p :: Type -> Type -> Type) where
- class Monad m => MonadIO (m :: Type -> Type) where
- newtype Identity a = Identity {
- runIdentity :: a
- void :: Functor f => f a -> f ()
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- class MFunctor (t :: (Type -> Type) -> k -> Type) where
- class (MFunctor t, MonadTrans t) => MMonad (t :: (Type -> Type) -> Type -> Type) where
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- mappedPost :: (Monad m, Functor g) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- mapped :: (Monad m, Functor f) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- strictly :: (a, b) -> Of a b
- lazily :: Of a b -> (a, b)
- cutoff :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Maybe r)
- untilJust :: (Monad m, Applicative f) => m (Maybe r) -> Stream f m r
- delays :: (MonadIO m, Applicative f) => Double -> Stream f m r
- never :: (Monad m, Applicative f) => Stream f m r
- groups :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream (Sum (Stream f m) (Stream g m)) m r
- unzips :: (Monad m, Functor f, Functor g) => Stream (Compose f g) m r -> Stream f (Stream g m) r
- expandPost :: (Monad m, Functor g) => (forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g (Stream h m) r
- expand :: (Monad m, Functor f) => (forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g (Stream h m) r
- unseparate :: (Monad m, Functor f, Functor g) => Stream f (Stream g m) r -> Stream (Sum f g) m r
- separate :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream f (Stream g m) r
- interleaves :: (Monad m, Applicative h) => Stream h m r -> Stream h m r -> Stream h m r
- zips :: (Monad m, Functor f, Functor g) => Stream f m r -> Stream g m r -> Stream (Compose f g) m r
- zipsWith' :: Monad m => (forall x y p. (x -> y -> p) -> f x -> g y -> h p) -> Stream f m r -> Stream g m r -> Stream h m r
- zipsWith :: (Monad m, Functor h) => (forall x y. f x -> g y -> h (x, y)) -> Stream f m r -> Stream g m r -> Stream h m r
- yields :: (Monad m, Functor f) => f r -> Stream f m r
- effect :: (Monad m, Functor f) => m (Stream f m r) -> Stream f m r
- wrap :: (Monad m, Functor f) => f (Stream f m r) -> Stream f m r
- hoistUnexposed :: (Monad m, Functor f) => (forall a. m a -> n a) -> Stream f m r -> Stream f n r
- replicates :: (Monad m, Functor f) => Int -> f () -> Stream f m ()
- repeatsM :: (Monad m, Functor f) => m (f ()) -> Stream f m r
- repeats :: (Monad m, Functor f) => f () -> Stream f m r
- distribute :: (Monad m, Functor f, MonadTrans t, MFunctor t, Monad (t (Stream f m))) => Stream f (t m) r -> t (Stream f m) r
- chunksOf :: (Monad m, Functor f) => Int -> Stream f m r -> Stream (Stream f m) m r
- takes :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m ()
- splitsAt :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Stream f m r)
- concats :: (Monad m, Functor f) => Stream (Stream f m) m r -> Stream f m r
- iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a
- iterTM :: (Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a
- intercalates :: (Monad m, Monad (t m), MonadTrans t) => t m x -> Stream (t m) m r -> t m r
- mapsM_ :: (Functor f, Monad m) => (forall x. f x -> m x) -> Stream f m r -> m r
- run :: Monad m => Stream m m r -> m r
- decompose :: (Monad m, Functor f) => Stream (Compose m f) m r -> Stream f m r
- mapsMPost :: (Monad m, Functor g) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- mapsPost :: (Monad m, Functor g) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r
- mapsM :: (Monad m, Functor f) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r
- maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r
- unfold :: (Monad m, Functor f) => (s -> m (Either r (f s))) -> s -> Stream f m r
- inspect :: Monad m => Stream f m r -> m (Either r (f (Stream f m r)))
- streamBuild :: (forall b. (r -> b) -> (m b -> b) -> (f b -> b) -> b) -> Stream f m r
- streamFold :: (Functor f, Monad m) => (r -> b) -> (m b -> b) -> (f b -> b) -> Stream f m r -> b
- destroy :: (Functor f, Monad m) => Stream f m r -> (f b -> b) -> (m b -> b) -> (r -> b) -> b
- data Stream (f :: Type -> Type) (m :: Type -> Type) r
- data Of a b = !a :> b
- each :: (Monad m, Foldable f) => f a -> Stream (Of a) m ()
Documentation
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
class MonadCatch m => MonadMask (m :: Type -> Type) #
A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.
Instances should ensure that, in the following code:
fg = f `finally` g
The action g
is called regardless of what occurs within f
, including
async exceptions. Some monads allow f
to abort the computation via other
effects than throwing an exception. For simplicity, we will consider aborting
and throwing an exception to be two forms of "throwing an error".
If f
and g
both throw an error, the error thrown by fg
depends on which
errors we're talking about. In a monad transformer stack, the deeper layers
override the effects of the inner layers; for example, ExceptT e1 (Except
e2) a
represents a value of type Either e2 (Either e1 a)
, so throwing both
an e1
and an e2
will result in Left e2
. If f
and g
both throw an
error from the same layer, instances should ensure that the error from g
wins.
Effects other than throwing an error are also overriden by the deeper layers.
For example, StateT s Maybe a
represents a value of type s -> Maybe (a,
s)
, so if an error thrown from f
causes this function to return Nothing
,
any changes to the state which f
also performed will be erased. As a
result, g
will see the state as it was before f
. Once g
completes,
f
's error will be rethrown, so g
' state changes will be erased as well.
This is the normal interaction between effects in a monad transformer stack.
By contrast, lifted-base's
version of finally
always discards all of g
's non-IO effects, and g
never sees any of f
's non-IO effects, regardless of the layer ordering and
regardless of whether f
throws an error. This is not the result of
interacting effects, but a consequence of MonadBaseControl
's approach.
Instances
MonadMask IO | |
e ~ SomeException => MonadMask (Either e) | Since: exceptions-0.8.3 |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (MaybeT m) | Since: exceptions-0.10.0 |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (Logged m) Source # | |
Defined in Control.Monad.Log | |
MonadMask m => MonadMask (ExceptT e m) | Since: exceptions-0.9.0 |
Defined in Control.Monad.Catch mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b # uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b # generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) # | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
Defined in Control.Monad.Catch mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b # uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b # generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) # | |
MonadMask m => MonadMask (StateT s m) | |
Defined in Control.Monad.Catch | |
(Error e, MonadMask m) => MonadMask (ErrorT e m) | |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (IdentityT m) | |
Defined in Control.Monad.Catch mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b # uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b # generalBracket :: IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) # | |
MonadMask m => MonadMask (StateT s m) | |
Defined in Control.Monad.Catch | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
Defined in Control.Monad.Catch mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b # uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b # generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) # | |
MonadMask m => MonadMask (ReaderT r m) | |
Defined in Control.Monad.Catch mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b # uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b # generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) # | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
Defined in Control.Monad.Catch mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b # uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b # generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) # | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
Defined in Control.Monad.Catch mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b # uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b # generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) # |
data ByteStream m r Source #
A space-efficient representation of a succession of Word8
vectors, supporting many
efficient operations.
An effectful ByteStream
contains 8-bit bytes, or by using certain
operations can be interpreted as containing 8-bit characters. It
also contains an offset, which will be needed to track the virtual
offsets in the BGZF decode.
Instances
streamFile :: (MonadIO m, MonadMask m) => FilePath -> (ByteStream m () -> m r) -> m r Source #
streamHandle :: MonadIO m => Handle -> ByteStream m () Source #
streamInput :: (MonadIO m, MonadMask m) => FilePath -> (ByteStream m () -> m r) -> m r Source #
Reads stdin
if the filename is "-", else reads the named file.
streamInputs :: MonadIO m => [FilePath] -> (Stream (ByteStream m) m () -> r) -> r Source #
Reads multiple inputs in sequence.
Only one file is opened at a time, so they must also be consumed in sequence. The filename "-" refers to stdin, if no filenames are given, stdin is read.
data UnwantedTerminal Source #
Instances
Show UnwantedTerminal Source # | |
Defined in Bio.Streaming showsPrec :: Int -> UnwantedTerminal -> ShowS # show :: UnwantedTerminal -> String # showList :: [UnwantedTerminal] -> ShowS # | |
Exception UnwantedTerminal Source # | |
Defined in Bio.Streaming |
progressGen :: MonadLog m => (Int -> a -> String) -> Int -> Stream (Of a) m r -> Stream (Of a) m r Source #
A general progress indicator that logs some message after a set number of records have passed through.
progressNum :: MonadLog m => String -> Int -> Stream (Of a) m r -> Stream (Of a) m r Source #
A simple progress indicator that logs the number of records.
progressPos :: MonadLog m => (a -> (Refseq, Int)) -> String -> Refs -> Int -> Stream (Of a) m r -> Stream (Of a) m r Source #
A simple progress indicator that logs a position every set number of passed records.
mergeStreams :: (Monad m, Ord a) => Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s) Source #
mergeStreamsBy :: Monad m => (a -> a -> Ordering) -> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s) Source #
mergeStreamsOn :: (Monad m, Ord b) => (a -> b) -> Stream (Of a) m r -> Stream (Of a) m s -> Stream (Of a) m (r, s) Source #
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
Instances
newtype Compose (f :: k -> Type) (g :: k1 -> k) (a :: k1) :: forall k k1. (k -> Type) -> (k1 -> k) -> k1 -> Type infixr 9 #
Right-to-left composition of functors. The composition of applicative functors is always applicative, but the composition of monads is not always a monad.
Compose infixr 9 | |
|
Instances
Functor f => Generic1 (Compose f g :: k -> Type) | |
Functor f => MFunctor (Compose f :: (Type -> Type) -> Type -> Type) | |
(Functor f, Functor g) => Functor (Compose f g) | Since: base-4.9.0.0 |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Foldable f, Foldable g) => Foldable (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose fold :: Monoid m => Compose f g m -> m # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m # foldr :: (a -> b -> b) -> b -> Compose f g a -> b # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b # foldl :: (b -> a -> b) -> b -> Compose f g a -> b # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b # foldr1 :: (a -> a -> a) -> Compose f g a -> a # foldl1 :: (a -> a -> a) -> Compose f g a -> a # toList :: Compose f g a -> [a] # null :: Compose f g a -> Bool # length :: Compose f g a -> Int # elem :: Eq a => a -> Compose f g a -> Bool # maximum :: Ord a => Compose f g a -> a # minimum :: Ord a => Compose f g a -> a # | |
(Traversable f, Traversable g) => Traversable (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Alternative f, Applicative g) => Alternative (Compose f g) | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Compose f g) | Since: base-4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Read1 f, Read1 g) => Read1 (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose f g a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose f g a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Compose f g a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Compose f g a] # | |
(Show1 f, Show1 g) => Show1 (Compose f g) | Since: base-4.9.0.0 |
(Hashable1 f, Hashable1 g) => Hashable1 (Compose f g) | |
Defined in Data.Hashable.Class | |
(Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) | Since: base-4.9.0.0 |
(Typeable a, Typeable f, Typeable g, Typeable k1, Typeable k2, Data (f (g a))) => Data (Compose f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Compose f g a -> c (Compose f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose f g a) # toConstr :: Compose f g a -> Constr # dataTypeOf :: Compose f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Compose f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose f g a)) # gmapT :: (forall b. Data b => b -> b) -> Compose f g a -> Compose f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Compose f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Compose f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose f g a -> m (Compose f g a) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose compare :: Compose f g a -> Compose f g a -> Ordering # (<) :: Compose f g a -> Compose f g a -> Bool # (<=) :: Compose f g a -> Compose f g a -> Bool # (>) :: Compose f g a -> Compose f g a -> Bool # (>=) :: Compose f g a -> Compose f g a -> Bool # | |
(Read1 f, Read1 g, Read a) => Read (Compose f g a) | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Compose f g a) | Since: base-4.9.0.0 |
Generic (Compose f g a) | |
(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Compose f g a) | In general, |
Defined in Data.Hashable.Class | |
type Rep1 (Compose f g :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
type Rep (Compose f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose |
data Sum (f :: k -> Type) (g :: k -> Type) (a :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type #
Lifted sum of functors.
Instances
Generic1 (Sum f g :: k -> Type) | |
(Functor f, Functor g) => Functor (Sum f g) | Since: base-4.9.0.0 |
(Foldable f, Foldable g) => Foldable (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum fold :: Monoid m => Sum f g m -> m # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m # foldr :: (a -> b -> b) -> b -> Sum f g a -> b # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b # foldl :: (b -> a -> b) -> b -> Sum f g a -> b # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b # foldr1 :: (a -> a -> a) -> Sum f g a -> a # foldl1 :: (a -> a -> a) -> Sum f g a -> a # elem :: Eq a => a -> Sum f g a -> Bool # maximum :: Ord a => Sum f g a -> a # minimum :: Ord a => Sum f g a -> a # | |
(Traversable f, Traversable g) => Traversable (Sum f g) | Since: base-4.9.0.0 |
(Eq1 f, Eq1 g) => Eq1 (Sum f g) | Since: base-4.9.0.0 |
(Ord1 f, Ord1 g) => Ord1 (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Read1 f, Read1 g) => Read1 (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Show1 f, Show1 g) => Show1 (Sum f g) | Since: base-4.9.0.0 |
(Hashable1 f, Hashable1 g) => Hashable1 (Sum f g) | |
Defined in Data.Hashable.Class | |
(Eq1 f, Eq1 g, Eq a) => Eq (Sum f g a) | Since: base-4.9.0.0 |
(Typeable a, Typeable f, Typeable g, Typeable k, Data (f a), Data (g a)) => Data (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g0. g0 -> c g0) -> Sum f g a -> c (Sum f g a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum f g a) # toConstr :: Sum f g a -> Constr # dataTypeOf :: Sum f g a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sum f g a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum f g a)) # gmapT :: (forall b. Data b => b -> b) -> Sum f g a -> Sum f g a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum f g a -> r # gmapQ :: (forall d. Data d => d -> u) -> Sum f g a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum f g a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum f g a -> m (Sum f g a) # | |
(Ord1 f, Ord1 g, Ord a) => Ord (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum | |
(Read1 f, Read1 g, Read a) => Read (Sum f g a) | Since: base-4.9.0.0 |
(Show1 f, Show1 g, Show a) => Show (Sum f g a) | Since: base-4.9.0.0 |
Generic (Sum f g a) | |
(Hashable1 f, Hashable1 g, Hashable a) => Hashable (Sum f g a) | |
Defined in Data.Hashable.Class | |
type Rep1 (Sum f g :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum type Rep1 (Sum f g :: k -> Type) = D1 (MetaData "Sum" "Data.Functor.Sum" "base" False) (C1 (MetaCons "InL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)) :+: C1 (MetaCons "InR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 g))) | |
type Rep (Sum f g a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum type Rep (Sum f g a) = D1 (MetaData "Sum" "Data.Functor.Sum" "base" False) (C1 (MetaCons "InL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))) :+: C1 (MetaCons "InR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (g a)))) |
class Bifunctor (p :: Type -> Type -> Type) where #
A bifunctor is a type constructor that takes
two type arguments and is a functor in both arguments. That
is, unlike with Functor
, a type constructor such as Either
does not need to be partially applied for a Bifunctor
instance, and the methods in this class permit mapping
functions over the Left
value or the Right
value,
or both at the same time.
Formally, the class Bifunctor
represents a bifunctor
from Hask
-> Hask
.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a Bifunctor
by either defining bimap
or by
defining both first
and second
.
If you supply bimap
, you should ensure that:
bimap
id
id
≡id
If you supply first
and second
, ensure:
first
id
≡id
second
id
≡id
If you supply both, you should also ensure:
bimap
f g ≡first
f.
second
g
These ensure by parametricity:
bimap
(f.
g) (h.
i) ≡bimap
f h.
bimap
g ifirst
(f.
g) ≡first
f.
first
gsecond
(f.
g) ≡second
f.
second
g
Since: base-4.8.0.0
bimap :: (a -> b) -> (c -> d) -> p a c -> p b d #
Map over both arguments at the same time.
bimap
f g ≡first
f.
second
g
Examples
>>>
bimap toUpper (+1) ('j', 3)
('J',4)
>>>
bimap toUpper (+1) (Left 'j')
Left 'J'
>>>
bimap toUpper (+1) (Right 3)
Right 4
Instances
Bifunctor Either | Since: base-4.8.0.0 |
Bifunctor (,) | Since: base-4.8.0.0 |
Bifunctor Arg | Since: base-4.9.0.0 |
Bifunctor Of | |
Bifunctor ((,,) x1) | Since: base-4.8.0.0 |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Bifunctor (K1 i :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Bifunctor ((,,,) x1 x2) | Since: base-4.8.0.0 |
Bifunctor ((,,,,) x1 x2 x3) | Since: base-4.8.0.0 |
Bifunctor ((,,,,,) x1 x2 x3 x4) | Since: base-4.8.0.0 |
Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) | Since: base-4.8.0.0 |
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Identity | |
|
Instances
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit,
resulting in an Either
Int
Int
:Either
Int
'()'
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
class MFunctor (t :: (Type -> Type) -> k -> Type) where #
A functor in the category of monads, using hoist
as the analog of fmap
:
hoist (f . g) = hoist f . hoist g hoist id = id
hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #
Lift a monad morphism from m
to n
into a monad morphism from
(t m)
to (t n)
The first argument to hoist
must be a monad morphism, even though the
type system does not enforce this
Instances
class (MFunctor t, MonadTrans t) => MMonad (t :: (Type -> Type) -> Type -> Type) where #
A monad in the category of monads, using lift
from MonadTrans
as the
analog of return
and embed
as the analog of (=<<
):
embed lift = id embed f (lift m) = f m embed g (embed f t) = embed (\m -> embed g (f m)) t
Instances
MMonad MaybeT | |
MMonad ListT | |
MMonad (ExceptT e) | |
Monoid w => MMonad (WriterT w) | |
Error e => MMonad (ErrorT e) | |
MMonad (IdentityT :: (Type -> Type) -> Type -> Type) | |
Monoid w => MMonad (WriterT w) | |
Functor f => MMonad (Stream f) | |
MMonad (Furrow a) Source # | |
MMonad (ReaderT r :: (Type -> Type) -> Type -> Type) | |
class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
mapped :: (Monad m, Functor f) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r #
Map layers of one functor to another with a transformation involving the base monad. This could be trivial, e.g.
let noteBeginning text x = putStrLn text >> return text
this is completely functor-general
maps
and mapped
obey these rules:
maps id = id mapped return = id maps f . maps g = maps (f . g) mapped f . mapped g = mapped (f <=< g) maps f . mapped g = mapped (fmap f . g) mapped f . maps g = mapped (f <=< fmap g)
maps
is more fundamental than mapped
, which is best understood as a convenience
for effecting this frequent composition:
mapped phi = decompose . maps (Compose . phi)
Note that lazily
, strictly
, fst'
, and mapOf
are all so-called natural transformations on the primitive Of a
functor.
If we write
type f ~~> g = forall x . f x -> g x
then we can restate some types as follows:
mapOf :: (a -> b) -> Of a ~~> Of b -- Bifunctor first lazily :: Of a ~~> (,) a Identity . fst' :: Of a ~~> Identity a
Manipulation of a Stream f m r
by mapping often turns on recognizing natural transformations of f
.
Thus maps
is far more general the the map
of the Streaming.Prelude
, which can be
defined thus:
S.map :: (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r S.map f = maps (mapOf f)
i.e.
S.map f = maps (\(a :> x) -> (f a :> x))
This rests on recognizing that mapOf
is a natural transformation; note though
that it results in such a transformation as well:
S.map :: (a -> b) -> Stream (Of a) m ~~> Stream (Of b) m
Thus we can maps
it in turn.
never :: (Monad m, Applicative f) => Stream f m r #
never
interleaves the pure applicative action with the return of the monad forever.
It is the empty
of the Alternative
instance, thus
never <|> a = a a <|> never = a
and so on. If w is a monoid then never :: Stream (Of w) m r
is
the infinite sequence of mempty
, and
str1 <|> str2
appends the elements monoidally until one of streams ends.
Thus we have, e.g.
>>>
S.stdoutLn $ S.take 2 $ S.stdinLn <|> S.repeat " " <|> S.stdinLn <|> S.repeat " " <|> S.stdinLn
1<Enter> 2<Enter> 3<Enter> 1 2 3 4<Enter> 5<Enter> 6<Enter> 4 5 6
This is equivalent to
>>>
S.stdoutLn $ S.take 2 $ foldr (<|>) never [S.stdinLn, S.repeat " ", S.stdinLn, S.repeat " ", S.stdinLn ]
Where f
is a monad, (<|>)
sequences the conjoined streams stepwise. See the
definition of paste
here,
where the separate steps are bytestreams corresponding to the lines of a file.
Given, say,
data Branch r = Branch r r deriving Functor -- add obvious applicative instance
then never :: Stream Branch Identity r
is the pure infinite binary tree with
(inaccessible) r
s in its leaves. Given two binary trees, tree1 <|> tree2
intersects them, preserving the leaves that came first,
so tree1 <|> never = tree1
Stream Identity m r
is an action in m
that is indefinitely delayed. Such an
action can be constructed with e.g. untilJust
.
untilJust :: (Monad m, Applicative f) => m (Maybe r) -> Stream f m r
Given two such items, <|>
instance races them.
It is thus the iterative monad transformer specially defined in
Control.Monad.Trans.Iter
So, for example, we might write
>>>
let justFour str = if length str == 4 then Just str else Nothing
>>>
let four = untilJust (fmap justFour getLine)
>>>
run four
one<Enter> two<Enter> three<Enter> four<Enter> "four"
The Alternative
instance in
Control.Monad.Trans.Free
is avowedly wrong, though no explanation is given for this.
groups :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream (Sum (Stream f m) (Stream g m)) m r #
Group layers in an alternating stream into adjoining sub-streams of one type or another.
expandPost :: (Monad m, Functor g) => (forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g (Stream h m) r #
If Of
had a Comonad
instance, then we'd have
copy = expandPost extend
See expand
for a version that requires a Functor f
instance
instead.
expand :: (Monad m, Functor f) => (forall a b. (g a -> b) -> f a -> h b) -> Stream f m r -> Stream g (Stream h m) r #
If Of
had a Comonad
instance, then we'd have
copy = expand extend
See expandPost
for a version that requires a Functor g
instance instead.
separate :: (Monad m, Functor f, Functor g) => Stream (Sum f g) m r -> Stream f (Stream g m) r #
Given a stream on a sum of functors, make it a stream on the left functor,
with the streaming on the other functor as the governing monad. This is
useful for acting on one or the other functor with a fold, leaving the
other material for another treatment. It generalizes
partitionEithers
, but actually streams properly.
>>>
let odd_even = S.maps (S.distinguish even) $ S.each [1..10::Int]
>>>
:t separate odd_even
separate odd_even :: Monad m => Stream (Of Int) (Stream (Of Int) m) ()
Now, for example, it is convenient to fold on the left and right values separately:
>>>
S.toList $ S.toList $ separate odd_even
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())
Or we can write them to separate files or whatever:
>>>
S.writeFile "even.txt" . S.show $ S.writeFile "odd.txt" . S.show $ S.separate odd_even
>>>
:! cat even.txt
2 4 6 8 10>>>
:! cat odd.txt
1 3 5 7 9
Of course, in the special case of Stream (Of a) m r
, we can achieve the above
effects more simply by using copy
>>>
S.toList . S.filter even $ S.toList . S.filter odd $ S.copy $ each [1..10::Int]
[2,4,6,8,10] :> ([1,3,5,7,9] :> ())
But separate
and unseparate
are functor-general.
interleaves :: (Monad m, Applicative h) => Stream h m r -> Stream h m r -> Stream h m r #
Interleave functor layers, with the effects of the first preceding the effects of the second. When the first stream runs out, any remaining effects in the second are ignored.
interleaves = zipsWith (liftA2 (,))
>>>
let paste = \a b -> interleaves (Q.lines a) (maps (Q.cons' '\t') (Q.lines b))
>>>
Q.stdout $ Q.unlines $ paste "hello\nworld\n" "goodbye\nworld\n"
hello goodbye world world
zips :: (Monad m, Functor f, Functor g) => Stream f m r -> Stream g m r -> Stream (Compose f g) m r #
zipsWith' :: Monad m => (forall x y p. (x -> y -> p) -> f x -> g y -> h p) -> Stream f m r -> Stream g m r -> Stream h m r #
Zip two streams together.
zipsWith :: (Monad m, Functor h) => (forall x y. f x -> g y -> h (x, y)) -> Stream f m r -> Stream g m r -> Stream h m r #
Zip two streams together. The zipsWith'
function should generally
be preferred for efficiency.
yields :: (Monad m, Functor f) => f r -> Stream f m r #
yields
is like lift
for items in the streamed functor.
It makes a singleton or one-layer succession.
lift :: (Monad m, Functor f) => m r -> Stream f m r yields :: (Monad m, Functor f) => f r -> Stream f m r
Viewed in another light, it is like a functor-general version of yield
:
S.yield a = yields (a :> ())
effect :: (Monad m, Functor f) => m (Stream f m r) -> Stream f m r #
Wrap an effect that returns a stream
effect = join . lift
wrap :: (Monad m, Functor f) => f (Stream f m r) -> Stream f m r #
Wrap a new layer of a stream. So, e.g.
S.cons :: Monad m => a -> Stream (Of a) m r -> Stream (Of a) m r S.cons a str = wrap (a :> str)
and, recursively:
S.each :: (Monad m, Foldable t) => t a -> Stream (Of a) m () S.each = foldr (\a b -> wrap (a :> b)) (return ())
The two operations
wrap :: (Monad m, Functor f ) => f (Stream f m r) -> Stream f m r effect :: (Monad m, Functor f ) => m (Stream f m r) -> Stream f m r
are fundamental. We can define the parallel operations yields
and lift
in
terms of them
yields :: (Monad m, Functor f ) => f r -> Stream f m r yields = wrap . fmap return lift :: (Monad m, Functor f ) => m r -> Stream f m r lift = effect . fmap return
hoistUnexposed :: (Monad m, Functor f) => (forall a. m a -> n a) -> Stream f m r -> Stream f n r #
A less-efficient version of hoist
that works properly even when its
argument is not a monad morphism.
hoistUnexposed = hoist . unexposed
replicates :: (Monad m, Functor f) => Int -> f () -> Stream f m () #
Repeat a functorial layer, command or instruction a fixed number of times.
replicates n = takes n . repeats
repeatsM :: (Monad m, Functor f) => m (f ()) -> Stream f m r #
Repeat an effect containing a functorial layer, command or instruction forever.
repeats :: (Monad m, Functor f) => f () -> Stream f m r #
Repeat a functorial layer (a "command" or "instruction") forever.
distribute :: (Monad m, Functor f, MonadTrans t, MFunctor t, Monad (t (Stream f m))) => Stream f (t m) r -> t (Stream f m) r #
Make it possible to 'run' the underlying transformed monad.
chunksOf :: (Monad m, Functor f) => Int -> Stream f m r -> Stream (Stream f m) m r #
Break a stream into substreams each with n functorial layers.
>>>
S.print $ mapped S.sum $ chunksOf 2 $ each [1,1,1,1,1]
2 2 1
splitsAt :: (Monad m, Functor f) => Int -> Stream f m r -> Stream f m (Stream f m r) #
Split a succession of layers after some number, returning a streaming or effectful pair.
>>>
rest <- S.print $ S.splitAt 1 $ each [1..3]
1>>>
S.print rest
2 3
splitAt 0 = return splitAt n >=> splitAt m = splitAt (m+n)
Thus, e.g.
>>>
rest <- S.print $ splitsAt 2 >=> splitsAt 2 $ each [1..5]
1 2 3 4>>>
S.print rest
5
concats :: (Monad m, Functor f) => Stream (Stream f m) m r -> Stream f m r #
Dissolves the segmentation into layers of Stream f m
layers.
iterT :: (Functor f, Monad m) => (f (m a) -> m a) -> Stream f m a -> m a #
Specialized fold following the usage of Control.Monad.Trans.Free
iterT alg = streamFold return join alg iterT alg = runIdentityT . iterTM (IdentityT . alg . fmap runIdentityT)
iterTM :: (Functor f, Monad m, MonadTrans t, Monad (t m)) => (f (t m a) -> t m a) -> Stream f m a -> t m a #
Specialized fold following the usage of Control.Monad.Trans.Free
iterTM alg = streamFold return (join . lift) iterTM alg = iterT alg . hoist lift
intercalates :: (Monad m, Monad (t m), MonadTrans t) => t m x -> Stream (t m) m r -> t m r #
Interpolate a layer at each segment. This specializes to e.g.
intercalates :: (Monad m, Functor f) => Stream f m () -> Stream (Stream f m) m r -> Stream f m r
mapsM_ :: (Functor f, Monad m) => (forall x. f x -> m x) -> Stream f m r -> m r #
Map each layer to an effect, and run them all.
decompose :: (Monad m, Functor f) => Stream (Compose m f) m r -> Stream f m r #
Rearrange a succession of layers of the form Compose m (f x)
.
we could as well define decompose
by mapsM
:
decompose = mapped getCompose
but mapped
is best understood as:
mapped phi = decompose . maps (Compose . phi)
since maps
and hoist
are the really fundamental operations that preserve the
shape of the stream:
maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r hoist :: (Monad m, Functor f) => (forall a. m a -> n a) -> Stream f m r -> Stream f n r
mapsMPost :: (Monad m, Functor g) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r #
Map layers of one functor to another with a transformation involving the base monad.
mapsMPost
is essentially the same as mapsM
, but it imposes a Functor
constraint on
its target functor rather than its source functor. It should be preferred if fmap
is cheaper for the target functor than for the source functor.
mapsPost
is more fundamental than mapsMPost
, which is best understood as a convenience
for effecting this frequent composition:
mapsMPost phi = decompose . mapsPost (Compose . phi)
The streaming prelude exports the same function under the better name mappedPost
,
which overlaps with the lens libraries.
mapsPost :: (Monad m, Functor g) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r #
Map layers of one functor to another with a transformation. Compare
hoist, which has a similar effect on the monadic
parameter.
mapsPost id = id mapsPost f . mapsPost g = mapsPost (f . g) mapsPost f = maps f
mapsPost
is essentially the same as maps
, but it imposes a Functor
constraint on
its target functor rather than its source functor. It should be preferred if fmap
is cheaper for the target functor than for the source functor.
mapsM :: (Monad m, Functor f) => (forall x. f x -> m (g x)) -> Stream f m r -> Stream g m r #
Map layers of one functor to another with a transformation involving the base monad.
maps
is more fundamental than mapsM
, which is best understood as a convenience
for effecting this frequent composition:
mapsM phi = decompose . maps (Compose . phi)
The streaming prelude exports the same function under the better name mapped
,
which overlaps with the lens libraries.
maps :: (Monad m, Functor f) => (forall x. f x -> g x) -> Stream f m r -> Stream g m r #
Map layers of one functor to another with a transformation. Compare
hoist, which has a similar effect on the monadic
parameter.
maps id = id maps f . maps g = maps (f . g)
unfold :: (Monad m, Functor f) => (s -> m (Either r (f s))) -> s -> Stream f m r #
Build a Stream
by unfolding steps starting from a seed. See also
the specialized unfoldr
in the prelude.
unfold inspect = id -- modulo the quotient we work with unfold Pipes.next :: Monad m => Producer a m r -> Stream ((,) a) m r unfold (curry (:>) . Pipes.next) :: Monad m => Producer a m r -> Stream (Of a) m r
inspect :: Monad m => Stream f m r -> m (Either r (f (Stream f m r))) #
Inspect the first stage of a freely layered sequence.
Compare Pipes.next
and the replica Streaming.Prelude.next
.
This is the uncons
for the general unfold
.
unfold inspect = id Streaming.Prelude.unfoldr StreamingPrelude.next = id
streamBuild :: (forall b. (r -> b) -> (m b -> b) -> (f b -> b) -> b) -> Stream f m r #
Reflect a church-encoded stream; cp. GHC.Exts.build
streamFold return_ effect_ step_ (streamBuild psi) = psi return_ effect_ step_
streamFold :: (Functor f, Monad m) => (r -> b) -> (m b -> b) -> (f b -> b) -> Stream f m r -> b #
streamFold
reorders the arguments of destroy
to be more akin
to foldr
It is more convenient to query in ghci to figure out
what kind of 'algebra' you need to write.
>>>
:t streamFold return join
(Monad m, Functor f) => (f (m a) -> m a) -> Stream f m a -> m a -- iterT
>>>
:t streamFold return (join . lift)
(Monad m, Monad (t m), Functor f, MonadTrans t) => (f (t m a) -> t m a) -> Stream f m a -> t m a -- iterTM
>>>
:t streamFold return effect
(Monad m, Functor f, Functor g) => (f (Stream g m r) -> Stream g m r) -> Stream f m r -> Stream g m r
>>>
:t \f -> streamFold return effect (wrap . f)
(Monad m, Functor f, Functor g) => (f (Stream g m a) -> g (Stream g m a)) -> Stream f m a -> Stream g m a -- maps
>>>
:t \f -> streamFold return effect (effect . fmap wrap . f)
(Monad m, Functor f, Functor g) => (f (Stream g m a) -> m (g (Stream g m a))) -> Stream f m a -> Stream g m a -- mapped
streamFold done eff construct = eff . iterT (return . construct . fmap eff) . fmap done
destroy :: (Functor f, Monad m) => Stream f m r -> (f b -> b) -> (m b -> b) -> (r -> b) -> b #
Map a stream to its church encoding; compare Data.List.foldr
.
destroyExposed
may be more efficient in some cases when
applicable, but it is less safe.
destroy s construct eff done = eff . iterT (return . construct . fmap eff) . fmap done $ s
data Stream (f :: Type -> Type) (m :: Type -> Type) r #
Instances
(Functor f, MonadState s m) => MonadState s (Stream f m) | |
(Functor f, MonadReader r m) => MonadReader r (Stream f m) | |
(Functor f, MonadError e m) => MonadError e (Stream f m) | |
Defined in Streaming.Internal throwError :: e -> Stream f m a # catchError :: Stream f m a -> (e -> Stream f m a) -> Stream f m a # | |
Functor f => MMonad (Stream f) | |
Functor f => MonadTrans (Stream f) | |
Defined in Streaming.Internal | |
Functor f => MFunctor (Stream f :: (Type -> Type) -> Type -> Type) | |
(Functor f, Monad m) => Monad (Stream f m) | |
(Functor f, Monad m) => Functor (Stream f m) | Operates covariantly on the stream result, not on its elements: Stream (Of a) m r ^ ^ | `--- This is what |
(Functor f, MonadFail m) => MonadFail (Stream f m) | |
Defined in Streaming.Internal | |
(Functor f, Monad m) => Applicative (Stream f m) | |
Defined in Streaming.Internal | |
(Applicative f, Monad m) => Alternative (Stream f m) | The empty = never (<|>) = zipsWith (liftA2 (,)) |
(Applicative f, Monad m) => MonadPlus (Stream f m) | |
(Monad m, Functor f, Eq1 m, Eq1 f) => Eq1 (Stream f m) | |
(Monad m, Functor f, Ord1 m, Ord1 f) => Ord1 (Stream f m) | |
Defined in Streaming.Internal | |
(Monad m, Functor f, Show (m ShowSWrapper), Show (f ShowSWrapper)) => Show1 (Stream f m) | |
(MonadIO m, Functor f) => MonadIO (Stream f m) | |
Defined in Streaming.Internal | |
(Functor f, PrimMonad m) => PrimMonad (Stream f m) Source # | |
(Monad m, Eq (m (Either r (f (Stream f m r))))) => Eq (Stream f m r) | |
(Monad m, Ord (m (Either r (f (Stream f m r))))) => Ord (Stream f m r) | |
Defined in Streaming.Internal | |
(Monad m, Show r, Show (m ShowSWrapper), Show (f (Stream f m r))) => Show (Stream f m r) | |
(Functor f, Monad m, Semigroup w) => Semigroup (Stream f m w) | |
(Functor f, Monad m, Monoid w) => Monoid (Stream f m w) | |
type PrimState (Stream f m) Source # | |
Defined in Bio.Streaming |
A left-strict pair; the base functor for streams of individual elements.
!a :> b infixr 5 |
Instances
Bifunctor Of | |
Eq2 Of | |
Ord2 Of | |
Defined in Data.Functor.Of | |
Show2 Of | |
Monoid a => Monad (Of a) | |
Functor (Of a) | |
Monoid a => Applicative (Of a) | |
Foldable (Of a) | |
Defined in Data.Functor.Of fold :: Monoid m => Of a m -> m # foldMap :: Monoid m => (a0 -> m) -> Of a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Of a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Of a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Of a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Of a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Of a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Of a a0 -> a0 # elem :: Eq a0 => a0 -> Of a a0 -> Bool # maximum :: Ord a0 => Of a a0 -> a0 # minimum :: Ord a0 => Of a a0 -> a0 # | |
Traversable (Of a) | |
Eq a => Eq1 (Of a) | |
Ord a => Ord1 (Of a) | |
Defined in Data.Functor.Of | |
Show a => Show1 (Of a) | |
Generic1 (Of a :: Type -> Type) | |
(Eq a, Eq b) => Eq (Of a b) | |
(Data a, Data b) => Data (Of a b) | |
Defined in Data.Functor.Of gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Of a b -> c (Of a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Of a b) # toConstr :: Of a b -> Constr # dataTypeOf :: Of a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Of a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Of a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Of a b -> Of a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Of a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Of a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Of a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Of a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) # | |
(Ord a, Ord b) => Ord (Of a b) | |
(Read a, Read b) => Read (Of a b) | |
(Show a, Show b) => Show (Of a b) | |
Generic (Of a b) | |
(Semigroup a, Semigroup b) => Semigroup (Of a b) | |
(Monoid a, Monoid b) => Monoid (Of a b) | |
type Rep1 (Of a :: Type -> Type) | |
Defined in Data.Functor.Of type Rep1 (Of a :: Type -> Type) = D1 (MetaData "Of" "Data.Functor.Of" "streaming-0.2.3.0-BED3UAk7ZDVHBgMwY4RzUk" False) (C1 (MetaCons ":>" (InfixI RightAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep (Of a b) | |
Defined in Data.Functor.Of type Rep (Of a b) = D1 (MetaData "Of" "Data.Functor.Of" "streaming-0.2.3.0-BED3UAk7ZDVHBgMwY4RzUk" False) (C1 (MetaCons ":>" (InfixI RightAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) |
each :: (Monad m, Foldable f) => f a -> Stream (Of a) m () #
Stream the elements of a pure, foldable container.
>>>
S.print $ each [1..3]
1 2 3