monadLib-3.5.2: A collection of monad transformers.

MonadLib.Derive

Description

This module defines a number of functions that make it easy to get the functionality of MonadLib for user-defined newtypes.

Synopsis

Documentation

data Iso m n Source

An isomorphism between (usually) monads. Typically the constructor and selector of a newtype delcaration.

Constructors

Iso (forall a. m a -> n a) (forall a. n a -> m a) 

derive_fmap :: Functor m => Iso m n -> (a -> b) -> n a -> n bSource

Derive the implementation of fmap from Functor.

derive_return :: Monad m => Iso m n -> a -> n aSource

Derive the implementation of return from Monad.

derive_bind :: Monad m => Iso m n -> n a -> (a -> n b) -> n bSource

Derive the implementation of >>= from Monad.

derive_fail :: Monad m => Iso m n -> String -> n aSource

derive_mfix :: MonadFix m => Iso m n -> (a -> n a) -> n aSource

Derive the implementation of mfix from MonadFix.

derive_ask :: ReaderM m i => Iso m n -> n iSource

Derive the implementation of ask from ReaderM.

derive_put :: WriterM m i => Iso m n -> i -> n ()Source

Derive the implementation of put from WriterM.

derive_get :: StateM m i => Iso m n -> n iSource

Derive the implementation of get from StateM.

derive_set :: StateM m i => Iso m n -> i -> n ()Source

Derive the implementation of set from StateM.

derive_raise :: ExceptionM m i => Iso m n -> i -> n aSource

Derive the implementation of raise from ExceptionM.

derive_callCC :: ContM m => Iso m n -> ((a -> n b) -> n a) -> n aSource

Derive the implementation of callCC from ContM.

derive_abort :: AbortM m i => Iso m n -> i -> n aSource

derive_local :: RunReaderM m i => Iso m n -> i -> n a -> n aSource

Derive the implementation of local from RunReaderM.

derive_collect :: RunWriterM m i => Iso m n -> n a -> n (a, i)Source

Derive the implementation of collect from RunWriterM.

derive_try :: RunExceptionM m i => Iso m n -> n a -> n (Either i a)Source

Derive the implementation of try from RunExceptionM.

derive_mzero :: MonadPlus m => Iso m n -> n aSource

Derive the implementation of mzero from MonadPlus.

derive_mplus :: MonadPlus m => Iso m n -> n a -> n a -> n aSource

Derive the implementation of mplus from MonadPlus.

derive_lift :: (MonadT t, Monad m) => Iso (t m) n -> m a -> n aSource

Derive the implementation of lift from MonadT.

derive_inBase :: BaseM m x => Iso m n -> x a -> n aSource

Derive the implementation of inBase from BaseM.