| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Agda.Utils.Monad
Synopsis
- bracket_ :: Monad m => m a -> (a -> m ()) -> m b -> m b
- finally :: MonadError e m => m a -> m () -> m a
- andM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
- dropWhileM :: Monad m => (a -> m Bool) -> [a] -> m [a]
- concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
- or2M :: Monad m => m Bool -> m Bool -> m Bool
- forMaybeMM :: Monad m => m [a] -> (a -> m (Maybe b)) -> m [b]
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- unlessM :: Monad m => m Bool -> m () -> m ()
- guardWithError :: MonadError e m => e -> Bool -> m ()
- tryMaybe :: (MonadError e m, Functor m) => m a -> m (Maybe a)
- tell1 :: (Monoid ws, Singleton w ws, MonadWriter ws m) => w -> m ()
- (==<<) :: Monad m => (a -> b -> m c) -> (m a, m b) -> m c
- whenM :: Monad m => m Bool -> m () -> m ()
- guardM :: (Monad m, MonadPlus m) => m Bool -> m ()
- ifNotM :: Monad m => m Bool -> m a -> m a -> m a
- and2M :: Monad m => m Bool -> m Bool -> m Bool
- allM :: (Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool
- orM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
- anyM :: (Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool
- altM1 :: Monad m => (a -> m (Either err b)) -> [a] -> m (Either err b)
- orEitherM :: (Monoid e, Monad m, Functor m) => [m (Either e b)] -> m (Either e b)
- mapM' :: (Foldable t, Applicative m, Monoid b) => (a -> m b) -> t a -> m b
- forM' :: (Foldable t, Applicative m, Monoid b) => t a -> (a -> m b) -> m b
- mapMM :: (Traversable t, Monad m) => (a -> m b) -> m (t a) -> m (t b)
- forMM :: (Traversable t, Monad m) => m (t a) -> (a -> m b) -> m (t b)
- mapMM_ :: (Foldable t, Monad m) => (a -> m ()) -> m (t a) -> m ()
- forMM_ :: (Foldable t, Monad m) => m (t a) -> (a -> m ()) -> m ()
- mapMaybeMM :: Monad m => (a -> m (Maybe b)) -> m [a] -> m [b]
- forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b]
- dropWhileEndM :: Monad m => (a -> m Bool) -> [a] -> m [a]
- partitionM :: (Functor m, Applicative m) => (a -> m Bool) -> [a] -> m ([a], [a])
- fromMaybeMP :: MonadPlus m => Maybe a -> m a
- catMaybesMP :: MonadPlus m => m (Maybe a) -> m a
- scatterMP :: (MonadPlus m, Foldable t) => m (t a) -> m a
- tryCatch :: (MonadError e m, Functor m) => m () -> m (Maybe e)
- localState :: MonadState s m => m a -> m a
- embedWriter :: (Monoid w, Monad m) => Writer w a -> WriterT w m a
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
- (<$) :: Functor f => a -> f b -> f a
Documentation
Arguments
| :: Monad m | |
| => m a | Acquires resource. Run first. |
| -> (a -> m ()) | Releases resource. Run last. |
| -> m b | Computes result. Run in-between. |
| -> m b |
Bracket without failure. Typically used to preserve state.
finally :: MonadError e m => m a -> m () -> m a Source #
Finally for the Error class. Errors in the finally part take
precedence over prior errors.
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b] Source #
A monadic version of .mapMaybe :: (a -> Maybe b) -> [a] -> [b]
dropWhileM :: Monad m => (a -> m Bool) -> [a] -> m [a] Source #
A monadic version of .dropWhile :: (a -> Bool) -> [a] -> [a]
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #
forMaybeMM :: Monad m => m [a] -> (a -> m (Maybe b)) -> m [b] Source #
The for version of mapMaybeMM.
guardWithError :: MonadError e m => e -> Bool -> m () Source #
Like guard, but raise given error when condition fails.
tryMaybe :: (MonadError e m, Functor m) => m a -> m (Maybe a) Source #
Try a computation, return Nothing if an Error occurs.
altM1 :: Monad m => (a -> m (Either err b)) -> [a] -> m (Either err b) Source #
Lazy monadic disjunction with Either truth values.
Returns the last error message if all fail.
orEitherM :: (Monoid e, Monad m, Functor m) => [m (Either e b)] -> m (Either e b) Source #
Lazy monadic disjunction with accumulation of errors in a monoid. Errors are discarded if we succeed.
mapM' :: (Foldable t, Applicative m, Monoid b) => (a -> m b) -> t a -> m b Source #
Generalized version of traverse_ :: Applicative m => (a -> m ()) -> [a] -> m ()
Executes effects and collects results in left-to-right order.
Works best with left-associative monoids.
Note that there is an alternative
mapM' f t = foldr mappend mempty $ mapM f t
that collects results in right-to-left order (effects still left-to-right). It might be preferable for right associative monoids.
forM' :: (Foldable t, Applicative m, Monoid b) => t a -> (a -> m b) -> m b Source #
Generalized version of for_ :: Applicative m => [a] -> (a -> m ()) -> m ()
mapMM :: (Traversable t, Monad m) => (a -> m b) -> m (t a) -> m (t b) Source #
forMM :: (Traversable t, Monad m) => m (t a) -> (a -> m b) -> m (t b) Source #
mapMaybeMM :: Monad m => (a -> m (Maybe b)) -> m [a] -> m [b] Source #
A version of with a computation for the input list.mapMaybeM
dropWhileEndM :: Monad m => (a -> m Bool) -> [a] -> m [a] Source #
A monadic version of .
Effects happen starting at the end of the list until dropWhileEnd :: (a -> Bool) -> [a] -> m [a]p becomes false.
partitionM :: (Functor m, Applicative m) => (a -> m Bool) -> [a] -> m ([a], [a]) Source #
A `monadic' version of @partition :: (a -> Bool) -> [a] -> ([a],[a])
catMaybesMP :: MonadPlus m => m (Maybe a) -> m a Source #
scatterMP :: (MonadPlus m, Foldable t) => m (t a) -> m a Source #
Branch over elements of a monadic Foldable data structure.
tryCatch :: (MonadError e m, Functor m) => m () -> m (Maybe e) Source #
Run a command, catch the exception and return it.
localState :: MonadState s m => m a -> m a Source #
Restore state after computation.
when :: Applicative f => Bool -> f () -> f () Source #
Conditional execution of Applicative expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging if the Boolean value debug
is True, and otherwise do nothing.
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where Source #
Monads that also support choice and failure.
Minimal complete definition
Nothing
Methods
The identity of mplus. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
mplus :: m a -> m a -> m a Source #
An associative operation. The default definition is
mplus = (<|>)
Instances
| MonadPlus NLM Source # | |
| MonadPlus IResult | |
| MonadPlus Parser | |
| MonadPlus Result | |
| MonadPlus STM | Takes the first non- Since: base-4.3.0.0 |
| MonadPlus P | Since: base-2.1 |
| MonadPlus ReadP | Since: base-2.1 |
| MonadPlus ReadPrec | Since: base-2.1 |
| MonadPlus Get | Since: binary-0.7.1.0 |
| MonadPlus Seq | |
| MonadPlus DList | |
| MonadPlus IO | Takes the first non-throwing Since: base-4.9.0.0 |
| MonadPlus Array | |
| MonadPlus SmallArray | |
| MonadPlus Vector | |
| MonadPlus Maybe | Picks the leftmost Since: base-2.1 |
| MonadPlus List | Combines lists by concatenation, starting from the empty list. Since: base-2.1 |
| (Functor m, Applicative m, Monad m) => MonadPlus (ListT m) Source # | |
| MonadPlus (Parser i) | |
| (ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methods mzero :: ArrowMonad a a0 Source # mplus :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 Source # | |
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| MonadPlus (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| Monad m => MonadPlus (MaybeT m) | |
| MonadPlus m => MonadPlus (Kleisli m a) | Since: base-4.14.0.0 |
| MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 |
| MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 |
| MonadPlus f => MonadPlus (Rec1 f) | Since: base-4.9.0.0 |
| (Monoid w, Functor m, MonadPlus m) => MonadPlus (AccumT w m) | |
| (Monad m, Monoid e) => MonadPlus (ExceptT e m) | |
| MonadPlus m => MonadPlus (IdentityT m) | |
| MonadPlus m => MonadPlus (ReaderT r m) | |
| MonadPlus m => MonadPlus (SelectT r m) | |
| MonadPlus m => MonadPlus (StateT s m) | |
| MonadPlus m => MonadPlus (StateT s m) | |
| (Functor m, MonadPlus m) => MonadPlus (WriterT w m) | |
| (Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
| (Monoid w, MonadPlus m) => MonadPlus (WriterT w m) | |
| MonadPlus m => MonadPlus (Reverse m) | Derived instance. |
| (MonadPlus f, MonadPlus g) => MonadPlus (Product f g) | Since: base-4.9.0.0 |
| (MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | Since: base-4.9.0.0 |
| MonadPlus f => MonadPlus (M1 i c f) | Since: base-4.9.0.0 |
| (Functor m, MonadPlus m) => MonadPlus (RWST r w s m) | |
| (Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
| (Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) | |
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source #
An infix synonym for fmap.
The name of this operator is an allusion to $.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $ is function application, <$> is function
application lifted over a Functor.
Examples
Convert from a to a Maybe Int using Maybe
Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an
Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "17"
Double each element of a list:
>>>(*2) <$> [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>even <$> (2,2)(2,True)
(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 Source #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
Example
Used in combination with (, <$>)( can be used to build a record.<*>)
>>>data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>produceFoo :: Applicative f => f Foo
>>>produceBar :: Applicative f => f Bar>>>produceBaz :: Applicative f => f Baz
>>>mkState :: Applicative f => f MyState>>>mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz