| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Foundation.Monad
- class Monad m => MonadIO (m :: * -> *) where
- class AMPMonad m => MonadFailure (m :: * -> *) where
- class AMPMonad m => MonadThrow m where
- class MonadThrow m => MonadCatch m where
- class MonadCatch m => MonadBracket m where
- class MonadTrans trans where
- newtype Identity a :: * -> * = Identity {
- runIdentity :: a
- replicateM :: Applicative m => CountOf a -> m a -> m [a]
Documentation
class Monad m => MonadIO (m :: * -> *) 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:
Minimal complete definition
class AMPMonad m => MonadFailure (m :: * -> *) where #
Monad that can represent failure
Similar to MonadFail but with a parametrized Failure linked to the Monad
Minimal complete definition
Associated Types
type Failure (m :: * -> *) :: * #
The associated type with the MonadFailure, representing what failure can be encoded in this monad
Instances
| MonadFailure Maybe | |
| MonadFailure (Either a) | |
| (Functor m, MonadFailure m) => MonadFailure (StateT s m) # | |
| MonadFailure m => MonadFailure (ReaderT r m) # | |
| AMPMonad m => MonadFailure (ExceptT e m) # | |
| MonadFailure m => MonadFailure (Conduit i o m) # | |
| Monad state => MonadFailure (Builder collection mutCollection step state err) | |
class AMPMonad m => MonadThrow m where Source #
Monad that can throw exception
Minimal complete definition
Methods
throw :: Exception e => e -> m a Source #
Throw immediatity an exception.
Only a MonadCatch monad will be able to catch the exception using catch
Instances
| MonadThrow IO Source # | |
| MonadThrow m => MonadThrow (ResourceT m) Source # | |
| (Functor m, MonadThrow m) => MonadThrow (StateT s m) Source # | |
| MonadThrow m => MonadThrow (ReaderT r m) Source # | |
| MonadThrow m => MonadThrow (Conduit i o m) Source # | |
class MonadThrow m => MonadCatch m where Source #
Monad that can catch exception
Minimal complete definition
Instances
| MonadCatch IO Source # | |
| MonadCatch m => MonadCatch (ResourceT m) Source # | |
| (Functor m, MonadCatch m) => MonadCatch (StateT s m) Source # | |
| MonadCatch m => MonadCatch (ReaderT r m) Source # | |
| MonadCatch m => MonadCatch (Conduit i o m) Source # | |
class MonadCatch m => MonadBracket m where Source #
Monad that can ensure cleanup actions are performed even in the case of exceptions, both synchronous and asynchronous. This usually excludes continuation-based monads.
Minimal complete definition
Methods
Arguments
| :: m a | acquire some resource |
| -> (a -> b -> m ignored1) | cleanup, no exception thrown |
| -> (a -> SomeException -> m ignored2) | cleanup, some exception thrown. The exception will be rethrown |
| -> (a -> m b) | inner action to perform with the resource |
| -> m b |
A generalized version of the standard bracket function which allows distinguishing different exit cases.
Instances
| MonadBracket IO Source # | |
| MonadBracket m => MonadBracket (ResourceT m) Source # | |
| MonadBracket m => MonadBracket (ReaderT r m) Source # | |
class MonadTrans trans where Source #
Basic Transformer class
Minimal complete definition
Methods
lift :: AMPMonad m => m a -> trans m a Source #
Lift a computation from an inner monad to the current transformer monad
Instances
| MonadTrans ResourceT Source # | |
| MonadTrans (StateT s) Source # | |
| MonadTrans (ReaderT r) Source # | |
| MonadTrans (ExceptT e) Source # | |
| MonadTrans (Conduit i o) Source # | |
newtype Identity a :: * -> * #
Identity functor and monad. (a non-strict monad)
Since: 4.8.0.0
Constructors
| Identity | |
Fields
| |
Instances
| Monad Identity | Since: 4.8.0.0 |
| Functor Identity | Since: 4.8.0.0 |
| MonadFix Identity | Since: 4.8.0.0 |
| Applicative Identity | Since: 4.8.0.0 |
| Foldable Identity | Since: 4.8.0.0 |
| Traversable Identity | |
| Bounded a => Bounded (Identity a) | |
| Enum a => Enum (Identity a) | |
| Eq a => Eq (Identity a) | |
| Floating a => Floating (Identity a) | |
| Fractional a => Fractional (Identity a) | |
| Integral a => Integral (Identity a) | |
| Data a => Data (Identity a) | Since: 4.9.0.0 |
| Num a => Num (Identity a) | |
| Ord a => Ord (Identity a) | |
| Read a => Read (Identity a) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
| Real a => Real (Identity a) | |
| RealFloat a => RealFloat (Identity a) | |
| RealFrac a => RealFrac (Identity a) | |
| Show a => Show (Identity a) | This instance would be equivalent to the derived instances of the
Since: 4.8.0.0 |
| Ix a => Ix (Identity a) | |
| IsString a => IsString (Identity a) | |
| Generic (Identity a) | |
| Semigroup a => Semigroup (Identity a) | Since: 4.9.0.0 |
| Monoid a => Monoid (Identity a) | |
| Storable a => Storable (Identity a) | |
| Bits a => Bits (Identity a) | |
| FiniteBits a => FiniteBits (Identity a) | |
| Generic1 * Identity | |
| type Rep (Identity a) | |
| type Rep1 * Identity | |
replicateM :: Applicative m => CountOf a -> m a -> m [a] Source #
performs the action replicateM n actn times,
gathering the results.