{-# LANGUAGE Unsafe, OverlappingInstances, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, UndecidableInstances, TypeOperators #-} module Control.Monad.Lifter where import Control.Monad.Trans import Control.Monad.ST import Control.Monad.Identity import Control.Monad.Morph import Control.Monad.PlusMonad -- | An automatic lifter. The idea of automatic lifting is due to Dan Piponi. class Lifter m n where lf :: m t -> n t instance Lifter (ST RealWorld) IO where lf = stToIO instance Lifter IO IO where lf = id instance Lifter (ST s) (ST s) where lf = id instance Lifter Identity Identity where lf = id instance (MonadTrans n, Monad x, Lifter m x) => Lifter m (n x) where lf = lift . lf instance (Monad x, MFunctor m) => Lifter (m Identity) (m x) where lf = hoist (return . runIdentity)