monad-extras-0.5.2: Extra utility functions for working with monads

Safe HaskellNone

Control.Monad.Extra

Synopsis

Documentation

skip :: Monad m => m ()Source

Synonym for return ().

discard :: Monad m => a -> m ()Source

Discards a value

obvious :: Applicative f => f ()Source

Synonym for pure ().

bind :: Monad m => m a -> (a -> m b) -> m bSource

Function name for >>=, as fmap is to <$>.

om :: Monad m => (a -> b -> m c) -> m a -> b -> m cSource

Combinator for working with monadic values:

>>> om when (return True) $ print "Hello"
"Hello"
>>> return True >>= flip when (print "Hello")
"Hello"
>>> om forM_ (return [True]) print
True
>>> flip forM_ print =<< return [True]
True
>>> mapM_ print =<< return [True]
True

Subsumes the need for individual functions for whenM, unlessM, etc.

nom :: Monad m => (a -> b -> m c) -> a -> m b -> m cSource

Variant of om which changes the roles of the 2nd and 3rd arguments.

>>> nom mapM_ print $ return [True]
True
>>> mapM_ print =<< return [True]
True

doCallCC :: Monad m => ((r -> ContT r m b) -> ContT r m r) -> m rSource

Convenience function if all you want to use is callCC.

label :: ContT r m (ContT r m a)Source

Return a continuation that one can jump back to within ContT.

>>> flip runContT return $ do { k <- label; ...; k }

io :: MonadIO m => IO a -> m aSource

Short-hand for liftIO.

liftMaybe :: MonadPlus m => Maybe a -> m aSource

Lift a Maybe value into the MaybeT monad transformer.

embed :: MonadBaseControl base m => (a -> m b) -> m (a -> base (StM m b))Source

Embed a transformer (Kleisli) arrow as an arrow in the base monad returning a mutated transformer state. If you do not want the transformation and your base monad is IO, use embedIO.

embedIO :: (MonadBaseControl IO m, MonadIO m) => (a -> m b) -> m (a -> IO b)Source

Return an IO action that closes over the current monad transformer, but throws away any residual effects within that transformer.

embedIO2 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> m r) -> m (a -> b -> IO r)Source

embedIO3 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> m r) -> m (a -> b -> c -> IO r)Source

embedIO4 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> m r) -> m (a -> b -> c -> d -> IO r)Source

embedIO5 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> e -> m r) -> m (a -> b -> c -> d -> e -> IO r)Source

embedIO6 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> e -> f -> m r) -> m (a -> b -> c -> d -> e -> f -> IO r)Source

embedIO7 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> e -> f -> g -> m r) -> m (a -> b -> c -> d -> e -> f -> g -> IO r)Source

embedIO8 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> e -> f -> g -> h -> m r) -> m (a -> b -> c -> d -> e -> f -> g -> h -> IO r)Source

embedIO9 :: (MonadBaseControl IO m, MonadIO m) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> m r) -> m (a -> b -> c -> d -> e -> f -> g -> h -> i -> IO r)Source

sequenceUntil :: Monad m => (a -> Bool) -> [m a] -> m [a]Source

Draw monadic actions from a list until one of them yields a value satisfying the predicate, and then return all the values up to and including the first that succeeds in a list within that monad.

newtype ComposeT f g m a Source

A type wrapper for composing monad transformers. This is very similar to Compose, just one level up.

Constructors

ComposeT 

Fields

getComposeT :: f (g m) a
 

Instances

(MonadIO (f (g m)), Applicative (f (g m))) => MonadBase IO (ComposeT f g m) 
(Applicative (f (g m)), MonadBaseControl IO (f (g m)), MonadIO (f (g m))) => MonadBaseControl IO (ComposeT f g m) 
(MFunctor f, MonadTrans f, MonadTrans g) => MonadTrans (ComposeT f g) 
Monad (f (g m)) => Monad (ComposeT f g m) 
Functor (f (g m)) => Functor (ComposeT f g m) 
Applicative (f (g m)) => Applicative (ComposeT f g m) 
MonadIO (f (g m)) => MonadIO (ComposeT f g m)