module Control.Monad.Constrained.Writer
(MonadWriter(..)
,WriterT
,pattern WriterT
,Writer
,runWriterT
,execWriterT
,execWriter
,runWriter
,listen
,pass
,evalWriterT
,evalWriter
)where
import GHC.Exts
import Control.Monad.Constrained
import Control.Monad.Constrained.Trans
import qualified Control.Monad.Trans.State.Lazy as State.Lazy
import qualified Control.Monad.Trans.State.Strict as State.Strict
import qualified Control.Monad.Trans.Identity as Identity
import qualified Control.Monad.Trans.Maybe as Maybe
import qualified Control.Monad.Trans.Reader as Reader
import qualified Control.Monad.Trans.Except as Except
import Control.Monad.Constrained.State
import Control.Monad.Constrained.Error
import Control.Monad.Constrained.Reader
import Data.Functor.Identity
import Data.Functor.Classes
class (Monoid w, Monad m) => MonadWriter w m | m -> w where
type WriterSuitable m a :: Constraint
writer :: WriterSuitable m a => (a,w) -> m a
tell :: WriterSuitable m () => w -> m ()
listenC :: WriterSuitable m b => (a -> w -> b) -> m a -> m b
passC :: WriterSuitable m a => (a -> w -> w) -> m a -> m a
instance MonadWriter w m =>
MonadWriter w (Except.ExceptT e m) where
type WriterSuitable (Except.ExceptT e m) a
= (WriterSuitable m a
,WriterSuitable m (Either e a)
,Suitable m (Either e a))
writer = lift . writer
tell = lift . tell
listenC f = (Except.mapExceptT . listenC . flip) (fmap . flip f)
passC = Except.mapExceptT . passC . either (const id)
listen
:: (MonadWriter w m, WriterSuitable m (a, w))
=> m a -> m (a, w)
listen = listenC (,)
pass
:: (MonadWriter w m, Suitable m a, WriterSuitable m (a, w -> w))
=> m (a, w -> w) -> m a
pass = fmap fst . passC snd
instance MonadWriter w m =>
MonadWriter w (State.Lazy.StateT s m) where
type WriterSuitable (State.Lazy.StateT s m) a
= (WriterSuitable m a
,WriterSuitable m (a, s)
,Suitable m (a, s))
writer = lift . writer
tell = lift . tell
listenC f m =
State.Lazy.StateT
(listenC
(\ ~(a,s') w ->
(f a w, s')) .
State.Lazy.runStateT m)
passC c m = State.Lazy.StateT (passC (c . fst) . State.Lazy.runStateT m)
instance MonadWriter w m =>
MonadWriter w (State.Strict.StateT s m) where
type WriterSuitable (State.Strict.StateT s m) a
= (WriterSuitable m a
,WriterSuitable m (a, s)
,Suitable m (a, s))
writer = lift . writer
tell = lift . tell
listenC f m =
State.Strict.StateT
(listenC
(\ (a,s') w ->
(f a w, s')) .
State.Strict.runStateT m)
passC c m = State.Strict.StateT (passC (c . fst) . State.Strict.runStateT m)
instance MonadWriter w m =>
MonadWriter w (Identity.IdentityT m) where
type WriterSuitable (Identity.IdentityT m) a = WriterSuitable m a
writer = lift . writer
tell = lift . tell
listenC f = Identity.mapIdentityT (listenC f)
passC f = Identity.mapIdentityT (passC f)
instance MonadWriter w m => MonadWriter w (Maybe.MaybeT m) where
type WriterSuitable (Maybe.MaybeT m) a
= (WriterSuitable m a
,WriterSuitable m (Maybe a)
,Suitable m (Maybe a))
writer = lift . writer
tell = lift . tell
listenC f = (Maybe.mapMaybeT . listenC . flip) (fmap . flip f)
passC = Maybe.mapMaybeT . passC . maybe id
instance MonadWriter w m => MonadWriter w (Reader.ReaderT r m) where
type WriterSuitable (Reader.ReaderT r m) a = WriterSuitable m a
writer = lift . writer
tell = lift . tell
listenC f = Reader.mapReaderT (listenC f)
passC f = Reader.mapReaderT (passC f)
newtype WriterT s m a =
WriterT_ { unWriterT :: State.Strict.StateT s m a }
instance Functor m => Functor (WriterT s m) where
type Suitable (WriterT s m) a = Suitable m (a,s)
fmap f (WriterT_ x) = WriterT_ (fmap f x)
x <$ WriterT_ xs = WriterT_ (x <$ xs)
instance Monad m =>
Applicative (WriterT s m) where
pure x = WriterT_ (pure x)
WriterT_ fs <*> WriterT_ xs = WriterT_ (fs <*> xs)
WriterT_ xs *> WriterT_ ys = WriterT_ (xs *> ys)
WriterT_ xs <* WriterT_ ys = WriterT_ (xs <* ys)
liftA = liftAM
instance Monad m => Monad (WriterT s m) where
WriterT_ xs >>= f = WriterT_ (xs >>= (unWriterT . f))
runWriterT
:: Monoid s
=> WriterT s m a -> m (a, s)
runWriterT =
(coerce :: (State.Strict.StateT s m a -> m (a, s)) -> WriterT s m a -> m (a, s))
(`State.Strict.runStateT` mempty)
pattern WriterT :: (Functor m, Monoid s, Suitable m (a, s)) =>
m (a, s) -> WriterT s m a
pattern WriterT x <- (runWriterT -> x)
where WriterT y
= WriterT_ (State.Strict.StateT (\ s -> (fmap.fmap) (mappend s) y))
type Writer s = WriterT s Identity
runWriter
:: Monoid s
=> Writer s a -> (a, s)
runWriter =
(coerce
:: (WriterT s Identity a -> Identity (a, s))
-> (WriterT s Identity a -> (a, s))
) runWriterT
instance (Monoid s, Monad m) =>
MonadWriter s (WriterT s m) where
type WriterSuitable (WriterT s m) a = Suitable m (a, s)
tell s = WriterT (pure ((), s))
writer (x,s) = WriterT (pure (x, s))
listenC f (WriterT_ xs) =
WriterT_
(State.Strict.StateT
(fmap
(\(x,s') ->
(f x s', s')) .
State.Strict.runStateT xs))
passC f (WriterT_ xs) =
WriterT_
(State.Strict.StateT
(fmap
(\(x,s') ->
(x, f x s')) . State.Strict.runStateT xs))
instance MonadTrans (WriterT w) where
type SuitableLift (WriterT w) m a = Suitable m (a, w)
lift xs = WriterT_ . State.Strict.StateT $ (\s -> fmap (flip (,) s) xs)
instance MonadState s m =>
MonadState s (WriterT w m) where
type StateSuitable (WriterT w m) a = (StateSuitable m a, Suitable m (a, w))
get = lift get
put = lift . put
state = lift . state
instance MonadError e m =>
MonadError e (WriterT w m) where
type SuitableError (WriterT w m) a = SuitableError m (a, w)
throwError e = WriterT_ . State.Strict.StateT $ const (throwError e)
catchError (WriterT_ xs) f =
WriterT_ (State.Strict.liftCatch catchError xs (unWriterT . f))
instance MonadReader r m =>
MonadReader r (WriterT w m) where
type ReaderSuitable (WriterT w m) a
= (ReaderSuitable m a
,Suitable m (a, w)
,ReaderSuitable m (a, w))
ask = WriterT_ ask
reader x = WriterT_ (reader x)
local f (WriterT_ xs) = WriterT_ (local f xs)
evalWriterT
:: (Monad m, Monoid s, Suitable m a)
=> WriterT s m a -> m a
evalWriterT = fmap fst . runWriterT
execWriterT
:: (Monad m, Monoid s, Suitable m s)
=> WriterT s m a -> m s
execWriterT = fmap snd . runWriterT
evalWriter
:: Monoid s
=> Writer s a -> a
evalWriter = fst . runWriter
execWriter
:: Monoid s
=> Writer s a -> s
execWriter = snd . runWriter
instance (Foldable m, Monoid w) =>
Foldable (WriterT w m) where
foldMap f =
foldMap
(\(x,_) ->
f x) .
runWriterT
instance (Eq1 m, Eq w, Monoid w) =>
Eq1 (WriterT w m) where
liftEq eq x y =
liftEq
(\(xx,xy) (yx,yy) ->
eq xx yx && xy == yy)
(runWriterT x)
(runWriterT y)
instance (Ord1 m, Ord w, Monoid w) =>
Ord1 (WriterT w m) where
liftCompare cmp x y =
liftCompare
(\(xx,xy) (yx,yy) ->
cmp xx yx `mappend` compare xy yy)
(runWriterT x)
(runWriterT y)
instance (Show w, Show1 m, Monoid w) =>
Show1 (WriterT w m) where
liftShowsPrec sp sl d m =
showsUnaryWith (liftShowsPrec sp' sl') "WriterT" d (runWriterT m)
where
sp' = liftShowsPrec2 sp sl showsPrec showList
sl' = liftShowList2 sp sl showsPrec showList
instance (Eq w, Eq1 m, Eq a, Monoid w) =>
Eq (WriterT w m a) where
(==) = eq1
instance (Ord w, Ord1 m, Ord a, Monoid w) =>
Ord (WriterT w m a) where
compare = compare1
instance (Show w, Show1 m, Show a, Monoid w) =>
Show (WriterT w m a) where
showsPrec = showsPrec1