{-# LANGUAGE CPP #-}
#if defined(__GLASGOW_HASKELL__)
{-# LANGUAGE DefaultSignatures #-}
#endif
{-# OPTIONS -fno-warn-deprecations #-}
module Bound.Class
( Bound(..)
, (=<<<)
) where
import Control.Monad.Trans.Class
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
import Control.Monad.Trans.Cont
import Control.Monad.Trans.Error
import Control.Monad.Trans.Identity
import Control.Monad.Trans.List
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.RWS
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State
import Control.Monad.Trans.Writer
infixl 1 >>>=
class Bound t where
(>>>=) :: Monad f => t f a -> (a -> f c) -> t f c
#if defined(__GLASGOW_HASKELL__)
default (>>>=) :: (MonadTrans t, Monad f, Monad (t f)) =>
t f a -> (a -> f c) -> t f c
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
#endif
instance Bound (ContT c) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Error e => Bound (ErrorT e) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Bound IdentityT where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Bound ListT where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Bound MaybeT where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Monoid w => Bound (RWST r w s) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Bound (ReaderT r) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Bound (StateT s) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
instance Monoid w => Bound (WriterT w) where
m >>>= f = m >>= lift . f
{-# INLINE (>>>=) #-}
infixr 1 =<<<
(=<<<) :: (Bound t, Monad f) => (a -> f c) -> t f a -> t f c
(=<<<) = flip (>>>=)
{-# INLINE (=<<<) #-}