-- | -- Module: Control.ContStuff.MonadsTf -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: experimental -- -- This module provides contstuff class instances for the monads from -- the monads-tf package. This makes using both transformer libraries -- in a single project much more convenient. {-# LANGUAGE FlexibleInstances, TypeFamilies, UndecidableInstances #-} module Control.ContStuff.MonadsTf () where import qualified Control.Monad.Trans as T import Control.Applicative import Control.ContStuff.Classes import Control.Monad.Cont as Cont (MonadCont(..), ContT(..)) import Control.Monad.Error (MonadError(..)) import Control.Monad.State.Class as State (MonadState(..)) -- ================= -- -- Generic instances -- -- ================= -- instance MonadCont m => CallCC m where callCC = Cont.callCC instance (Applicative m, MonadError m) => HasExceptions m where type Exception m = ErrorType m raise = throwError try = flip catchError (pure . Left) . fmap Right instance T.MonadIO m => LiftBase m where type Base m = IO base = T.liftIO instance MonadState m => Stateful m where type StateOf m = StateType m get = State.get putLazy = State.put instance T.MonadTrans t => Transformer t where lift = T.lift -- ================== -- -- Specific instances -- -- ================== -- instance Applicative m => Abortable (ContT r m) where type Result (ContT r m) = r abort = ContT . const . pure