transformers-convert-0.2.0.0: Sensible conversions between some of the monad transformers

Safe HaskellSafe-Inferred

Control.Monad.Trans.Convert

Contents

Synopsis

to MaybeT

mMaybeToMaybeT :: Monad m => m (Maybe a) -> MaybeT m aSource

Transform a maybe value encapsulated in a Monad m into the equivalent MaybeT m monad transformer.

NOTE: this is not equivalent to either lift or hoistMaybe alone. Check the types carefully.

mMToMT :: Monad m => m (Maybe a) -> MaybeT m aSource

Shorter alias for mMaybeToMaybeT

ioMaybeToMaybeT :: IO (Maybe a) -> MaybeT IO aSource

Transform a IO (Maybe a) value into a MaybeT IO a value

ioMToMT :: IO (Maybe a) -> MaybeT IO aSource

Shorter alias for ioMaybeToMaybeT

mEitherToMaybeT :: Functor m => m (Either a b) -> MaybeT m bSource

Transform a either value encapsulated in a Monad m into the equivalent MaybeT m monad transformer.

Note: The left value is silently discarded.

mEToMT :: (Functor m, Monad m) => m (Either a b) -> MaybeT m bSource

Shorter alias for mEitherToMaybeT.

ioEitherToMaybeT :: IO (Either a b) -> MaybeT IO bSource

Transform a either value encapsulated in a IO monad into the equivalent MaybeT IO monad transformer.

Note: The left value is silently discarded.

ioEToMT :: IO (Either a b) -> MaybeT IO bSource

Shorter alias for mEitherToMaybeT.

mPairToMaybeT :: (Eq a, Monoid a, Functor m, Monad m) => m (a, a) -> MaybeT m aSource

Case analysis of a pair of monoid values returned by a monad into a MaybeT value. The value conversion is done by pairToMaybe.

mPairToMaybeT' :: (Eq a, Monoid a, Functor m, Monad m) => m (a, a) -> MaybeT m aSource

Case analysis of a pair of monoid values returned by a monad into a MaybeT value. The value conversion is done by pairToMaybe'.

mPairFstToMaybeT :: (Eq a, Monoid a, Functor m, Monad m) => m (a, b) -> MaybeT m aSource

Case analysis of a pair of monoid values returned by a monad into a MaybeT value. The value conversion is done by pairFstToMaybe.

mPairSndToMaybeT :: (Eq b, Monoid b, Functor m, Monad m) => m (a, b) -> MaybeT m bSource

Case analysis of a pair of monoid values returned by a monad into a MaybeT value. The value conversion is done by pairSndToMaybe.

mMonoidToMaybeT :: (Eq o, Monoid o, Functor m, Monad m) => m o -> MaybeT m oSource

Transform a monoid value encapsulated in a Monad m into the equivalent MaybeT m monad transformer (mempty -> Nothing).

mOToMT :: (Eq o, Monoid o, Functor m, Monad m) => m o -> MaybeT m oSource

Shorter alias for mMonoidToMaybeT

mBoolToMaybeT :: (Functor m, Monad m) => a -> m Bool -> MaybeT m aSource

Transform a boolean value encapsulated in a Monad m into the equivalent MaybeT m monad transformer (True -> Provided Default Value).

mBToMT :: (Functor m, Monad m) => a -> m Bool -> MaybeT m aSource

Shorter alias for mBoolToMaybeT.

tryIOMT :: (Eq a, Monoid a) => IO a -> MaybeT IO aSource

toEitherT

mMaybeToEitherT :: Monad m => b -> m (Maybe a) -> EitherT b m aSource

Transform a maybe value encapsulated in a Monad m into the equivalent EitherT b m monad transformer.

NOTE: this is not equivalent to either lift or hoistEither alone. Check the types carefully.

mMToET :: Monad m => b -> m (Maybe a) -> EitherT b m aSource

Shorter alias for mMaybeToEitherT

ioMaybeToEitherT :: b -> IO (Maybe a) -> EitherT b IO aSource

Transform a IO (Maybe a) value into a EitherT b IO a value

ioMToET :: b -> IO (Maybe a) -> EitherT b IO aSource

Shorter alias for ioMaybeToEitherT

mEitherToEitherT :: Monad m => m (Either b a) -> EitherT b m aSource

Transform a either value encapsulated in a Monad m into the equivalent EitherT e m monad transformer.

mEToET :: Monad m => m (Either b a) -> EitherT b m aSource

Shorter alias for mEitherToEitherT.

ioEitherToEitherT :: IO (Either b a) -> EitherT b IO aSource

Transform a either value encapsulated in a IO monad into the equivalent EitherT b IO monad transformer.

ioEToET :: IO (Either b a) -> EitherT b IO aSource

Shorter alias for mEitherToEitherT.

mPairToEitherT :: (Eq a, Monoid a, Functor m, Monad m) => m (b, a) -> EitherT b m aSource

Case analysis of a pair of monoid values returned by a monad into a EitherT value. The value conversion is done by pairToEither.

mPairToEitherT' :: (Eq b, Monoid b, Functor m, Monad m) => m (b, a) -> EitherT a m bSource

Case analysis of a pair of monoid values returned by a monad into a EitherT value. The value conversion is done by pairToEither'.

mPairBothToEitherT :: (Eq a, Monoid a, Functor m, Monad m) => b -> m (a, a) -> EitherT b m aSource

Case analysis of a pair of monoid values returned by a monad into a EitherT value. The value conversion is done by pairBothToEither.

mMonoidToEitherT :: (Eq a, Monoid a, Functor m, Monad m) => b -> m a -> EitherT b m aSource

Transform a monoid value encapsulated in a Monad m into the equivalent EitherT e m monad transformer (mempty -> Nothing).

mOToET :: (Eq a, Monoid a, Functor m, Monad m) => b -> m a -> EitherT b m aSource

Shorter alias for mMonoidToEitherT

mBoolToEitherT :: (Functor m, Monad m) => b -> a -> m Bool -> EitherT b m aSource

Transform a boolean value encapsulated in a Monad m into the equivalent Either m monad transformer. Uses boolToEither.

mBToET :: (Functor m, Monad m) => b -> a -> m Bool -> EitherT b m aSource

Shorter alias for mBoolToEitherT.

fmapLeftT :: Functor m => (a -> c) -> EitherT a m b -> EitherT c m bSource

Change the left type using the provided conversion function. This is a specialization of bimapEitherT.

 fmapLeftT f = bimapEitherT f id

or using the errors Data.EitherR

 fmapLeftT = fmapLT

fmapRightT :: Functor m => (b -> c) -> EitherT a m b -> EitherT a m cSource

Change the right type using the provided conversion function. This is a specialization of bimapEitherT.

tryIOET :: IO a -> EitherT IOException IO aSource

This function executes a IO action that could raise an IOException. If a IOException is raised, the function returns a left value in the EitherT IOException IO monad transformer.

tryIOET' :: (Eq a, Monoid a) => String -> IO a -> EitherT IOException IO aSource

This function executes a IO action that returns a monoid value, or raises an IOException. If a IOException is raised, or the returned value is an empty monoid, the function returns a left value in the EitherT IOException IO monad transformer. In the later case (empty monoid), the exception will be of userErrorType type, with the provided string text.