{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
module Control.Monad.Trans.Writer.Strict (
Writer,
writer,
runWriter,
execWriter,
mapWriter,
WriterT(..),
execWriterT,
mapWriterT,
tell,
listen,
listens,
pass,
censor,
liftCallCC,
liftCatch,
) where
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Data.Functor.Classes
#if MIN_VERSION_base(4,12,0)
import Data.Functor.Contravariant
#endif
import Data.Functor.Identity
import Control.Applicative
import Control.Monad
#if MIN_VERSION_base(4,9,0)
import qualified Control.Monad.Fail as Fail
#endif
import Control.Monad.Fix
import Control.Monad.Signatures
#if MIN_VERSION_base(4,4,0)
import Control.Monad.Zip (MonadZip(mzipWith))
#endif
import Data.Foldable
import Data.Monoid
import Data.Traversable (Traversable(traverse))
import Prelude hiding (null, length)
type Writer w = WriterT w Identity
writer :: (Monad m) => (a, w) -> WriterT w m a
writer :: forall (m :: * -> *) a w. Monad m => (a, w) -> WriterT w m a
writer = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a)
-> ((a, w) -> m (a, w)) -> (a, w) -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, w) -> m (a, w)
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE writer #-}
runWriter :: Writer w a -> (a, w)
runWriter :: forall w a. Writer w a -> (a, w)
runWriter = Identity (a, w) -> (a, w)
forall a. Identity a -> a
runIdentity (Identity (a, w) -> (a, w))
-> (Writer w a -> Identity (a, w)) -> Writer w a -> (a, w)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Writer w a -> Identity (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT
{-# INLINE runWriter #-}
execWriter :: Writer w a -> w
execWriter :: forall w a. Writer w a -> w
execWriter Writer w a
m = (a, w) -> w
forall a b. (a, b) -> b
snd (Writer w a -> (a, w)
forall w a. Writer w a -> (a, w)
runWriter Writer w a
m)
{-# INLINE execWriter #-}
mapWriter :: ((a, w) -> (b, w')) -> Writer w a -> Writer w' b
mapWriter :: forall a w b w'. ((a, w) -> (b, w')) -> Writer w a -> Writer w' b
mapWriter (a, w) -> (b, w')
f = (Identity (a, w) -> Identity (b, w'))
-> WriterT w Identity a -> WriterT w' Identity b
forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT ((b, w') -> Identity (b, w')
forall a. a -> Identity a
Identity ((b, w') -> Identity (b, w'))
-> (Identity (a, w) -> (b, w'))
-> Identity (a, w)
-> Identity (b, w')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, w) -> (b, w')
f ((a, w) -> (b, w'))
-> (Identity (a, w) -> (a, w)) -> Identity (a, w) -> (b, w')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (a, w) -> (a, w)
forall a. Identity a -> a
runIdentity)
{-# INLINE mapWriter #-}
newtype WriterT w m a = WriterT { forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT :: m (a, w) }
instance (Eq w, Eq1 m) => Eq1 (WriterT w m) where
liftEq :: forall a b.
(a -> b -> Bool) -> WriterT w m a -> WriterT w m b -> Bool
liftEq a -> b -> Bool
eq (WriterT m (a, w)
m1) (WriterT m (b, w)
m2) = ((a, w) -> (b, w) -> Bool) -> m (a, w) -> m (b, w) -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq ((a -> b -> Bool) -> (w -> w -> Bool) -> (a, w) -> (b, w) -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> b -> Bool
eq w -> w -> Bool
forall a. Eq a => a -> a -> Bool
(==)) m (a, w)
m1 m (b, w)
m2
{-# INLINE liftEq #-}
instance (Ord w, Ord1 m) => Ord1 (WriterT w m) where
liftCompare :: forall a b.
(a -> b -> Ordering) -> WriterT w m a -> WriterT w m b -> Ordering
liftCompare a -> b -> Ordering
comp (WriterT m (a, w)
m1) (WriterT m (b, w)
m2) =
((a, w) -> (b, w) -> Ordering) -> m (a, w) -> m (b, w) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare ((a -> b -> Ordering)
-> (w -> w -> Ordering) -> (a, w) -> (b, w) -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> b -> Ordering
comp w -> w -> Ordering
forall a. Ord a => a -> a -> Ordering
compare) m (a, w)
m1 m (b, w)
m2
{-# INLINE liftCompare #-}
instance (Read w, Read1 m) => Read1 (WriterT w m) where
liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (WriterT w m a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = (String -> ReadS (WriterT w m a)) -> Int -> ReadS (WriterT w m a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (WriterT w m a)) -> Int -> ReadS (WriterT w m a))
-> (String -> ReadS (WriterT w m a))
-> Int
-> ReadS (WriterT w m a)
forall a b. (a -> b) -> a -> b
$
(Int -> ReadS (m (a, w)))
-> String
-> (m (a, w) -> WriterT w m a)
-> String
-> ReadS (WriterT w m a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith ((Int -> ReadS (a, w)) -> ReadS [(a, w)] -> Int -> ReadS (m (a, w))
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS (a, w)
rp' ReadS [(a, w)]
rl') String
"WriterT" m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT
where
rp' :: Int -> ReadS (a, w)
rp' = (Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS w)
-> ReadS [w]
-> Int
-> ReadS (a, w)
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
liftReadsPrec2 Int -> ReadS a
rp ReadS [a]
rl Int -> ReadS w
forall a. Read a => Int -> ReadS a
readsPrec ReadS [w]
forall a. Read a => ReadS [a]
readList
rl' :: ReadS [(a, w)]
rl' = (Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS w) -> ReadS [w] -> ReadS [(a, w)]
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [f a b]
liftReadList2 Int -> ReadS a
rp ReadS [a]
rl Int -> ReadS w
forall a. Read a => Int -> ReadS a
readsPrec ReadS [w]
forall a. Read a => ReadS [a]
readList
instance (Show w, Show1 m) => Show1 (WriterT w m) where
liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> WriterT w m a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (WriterT m (a, w)
m) =
(Int -> m (a, w) -> ShowS) -> String -> Int -> m (a, w) -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> (a, w) -> ShowS)
-> ([(a, w)] -> ShowS) -> Int -> m (a, w) -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> (a, w) -> ShowS
sp' [(a, w)] -> ShowS
sl') String
"WriterT" Int
d m (a, w)
m
where
sp' :: Int -> (a, w) -> ShowS
sp' = (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> w -> ShowS)
-> ([w] -> ShowS)
-> Int
-> (a, w)
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sp [a] -> ShowS
sl Int -> w -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [w] -> ShowS
forall a. Show a => [a] -> ShowS
showList
sl' :: [(a, w)] -> ShowS
sl' = (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> w -> ShowS)
-> ([w] -> ShowS)
-> [(a, w)]
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> [f a b]
-> ShowS
liftShowList2 Int -> a -> ShowS
sp [a] -> ShowS
sl Int -> w -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [w] -> ShowS
forall a. Show a => [a] -> ShowS
showList
instance (Eq w, Eq1 m, Eq a) => Eq (WriterT w m a) where == :: WriterT w m a -> WriterT w m a -> Bool
(==) = WriterT w m a -> WriterT w m a -> Bool
forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool
eq1
instance (Ord w, Ord1 m, Ord a) => Ord (WriterT w m a) where compare :: WriterT w m a -> WriterT w m a -> Ordering
compare = WriterT w m a -> WriterT w m a -> Ordering
forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering
compare1
instance (Read w, Read1 m, Read a) => Read (WriterT w m a) where
readsPrec :: Int -> ReadS (WriterT w m a)
readsPrec = Int -> ReadS (WriterT w m a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1
instance (Show w, Show1 m, Show a) => Show (WriterT w m a) where
showsPrec :: Int -> WriterT w m a -> ShowS
showsPrec = Int -> WriterT w m a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1
execWriterT :: (Monad m) => WriterT w m a -> m w
execWriterT :: forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT WriterT w m a
m = do
(a
_, w
w) <- WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m
w -> m w
forall (m :: * -> *) a. Monad m => a -> m a
return w
w
{-# INLINE execWriterT #-}
mapWriterT :: (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT :: forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT m (a, w) -> n (b, w')
f WriterT w m a
m = n (b, w') -> WriterT w' n b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (n (b, w') -> WriterT w' n b) -> n (b, w') -> WriterT w' n b
forall a b. (a -> b) -> a -> b
$ m (a, w) -> n (b, w')
f (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m)
{-# INLINE mapWriterT #-}
instance (Functor m) => Functor (WriterT w m) where
fmap :: forall a b. (a -> b) -> WriterT w m a -> WriterT w m b
fmap a -> b
f = (m (a, w) -> m (b, w)) -> WriterT w m a -> WriterT w m b
forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT ((m (a, w) -> m (b, w)) -> WriterT w m a -> WriterT w m b)
-> (m (a, w) -> m (b, w)) -> WriterT w m a -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((a, w) -> (b, w)) -> m (a, w) -> m (b, w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((a, w) -> (b, w)) -> m (a, w) -> m (b, w))
-> ((a, w) -> (b, w)) -> m (a, w) -> m (b, w)
forall a b. (a -> b) -> a -> b
$ \ (a
a, w
w) -> (a -> b
f a
a, w
w)
{-# INLINE fmap #-}
instance (Foldable f) => Foldable (WriterT w f) where
foldMap :: forall m a. Monoid m => (a -> m) -> WriterT w f a -> m
foldMap a -> m
f = ((a, w) -> m) -> f (a, w) -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (a -> m
f (a -> m) -> ((a, w) -> a) -> (a, w) -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, w) -> a
forall a b. (a, b) -> a
fst) (f (a, w) -> m)
-> (WriterT w f a -> f (a, w)) -> WriterT w f a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT w f a -> f (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT
{-# INLINE foldMap #-}
#if MIN_VERSION_base(4,8,0)
null :: forall a. WriterT w f a -> Bool
null (WriterT f (a, w)
t) = f (a, w) -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null f (a, w)
t
length :: forall a. WriterT w f a -> Int
length (WriterT f (a, w)
t) = f (a, w) -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length f (a, w)
t
#endif
instance (Traversable f) => Traversable (WriterT w f) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WriterT w f a -> f (WriterT w f b)
traverse a -> f b
f = (f (b, w) -> WriterT w f b) -> f (f (b, w)) -> f (WriterT w f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (b, w) -> WriterT w f b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (f (f (b, w)) -> f (WriterT w f b))
-> (WriterT w f a -> f (f (b, w)))
-> WriterT w f a
-> f (WriterT w f b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, w) -> f (b, w)) -> f (a, w) -> f (f (b, w))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (a, w) -> f (b, w)
forall {b}. (a, b) -> f (b, b)
f' (f (a, w) -> f (f (b, w)))
-> (WriterT w f a -> f (a, w)) -> WriterT w f a -> f (f (b, w))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterT w f a -> f (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT where
f' :: (a, b) -> f (b, b)
f' (a
a, b
b) = (b -> (b, b)) -> f b -> f (b, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ b
c -> (b
c, b
b)) (a -> f b
f a
a)
{-# INLINE traverse #-}
instance (Monoid w, Applicative m) => Applicative (WriterT w m) where
pure :: forall a. a -> WriterT w m a
pure a
a = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ (a, w) -> m (a, w)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
a, w
forall a. Monoid a => a
mempty)
{-# INLINE pure #-}
WriterT w m (a -> b)
f <*> :: forall a b. WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b
<*> WriterT w m a
v = m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ ((a -> b, w) -> (a, w) -> (b, w))
-> m (a -> b, w) -> m (a, w) -> m (b, w)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (a -> b, w) -> (a, w) -> (b, w)
forall {b} {t} {a}. Monoid b => (t -> a, b) -> (t, b) -> (a, b)
k (WriterT w m (a -> b) -> m (a -> b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m (a -> b)
f) (WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
v)
where k :: (t -> a, b) -> (t, b) -> (a, b)
k (t -> a
a, b
w) (t
b, b
w') = (t -> a
a t
b, b
w b -> b -> b
forall a. Monoid a => a -> a -> a
`mappend` b
w')
{-# INLINE (<*>) #-}
instance (Monoid w, Alternative m) => Alternative (WriterT w m) where
empty :: forall a. WriterT w m a
empty = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT m (a, w)
forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINE empty #-}
WriterT w m a
m <|> :: forall a. WriterT w m a -> WriterT w m a -> WriterT w m a
<|> WriterT w m a
n = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m m (a, w) -> m (a, w) -> m (a, w)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
n
{-# INLINE (<|>) #-}
instance (Monoid w, Monad m) => Monad (WriterT w m) where
#if !(MIN_VERSION_base(4,8,0))
return a = writer (a, mempty)
{-# INLINE return #-}
#endif
WriterT w m a
m >>= :: forall a b. WriterT w m a -> (a -> WriterT w m b) -> WriterT w m b
>>= a -> WriterT w m b
k = m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ do
(a
a, w
w) <- WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m
(b
b, w
w') <- WriterT w m b -> m (b, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (a -> WriterT w m b
k a
a)
(b, w) -> m (b, w)
forall (m :: * -> *) a. Monad m => a -> m a
return (b
b, w
w w -> w -> w
forall a. Monoid a => a -> a -> a
`mappend` w
w')
{-# INLINE (>>=) #-}
#if !(MIN_VERSION_base(4,13,0))
fail msg = WriterT $ fail msg
{-# INLINE fail #-}
#endif
#if MIN_VERSION_base(4,9,0)
instance (Monoid w, Fail.MonadFail m) => Fail.MonadFail (WriterT w m) where
fail :: forall a. String -> WriterT w m a
fail String
msg = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ String -> m (a, w)
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail String
msg
{-# INLINE fail #-}
#endif
instance (Monoid w, MonadPlus m) => MonadPlus (WriterT w m) where
mzero :: forall a. WriterT w m a
mzero = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT m (a, w)
forall (m :: * -> *) a. MonadPlus m => m a
mzero
{-# INLINE mzero #-}
WriterT w m a
m mplus :: forall a. WriterT w m a -> WriterT w m a -> WriterT w m a
`mplus` WriterT w m a
n = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m m (a, w) -> m (a, w) -> m (a, w)
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
n
{-# INLINE mplus #-}
instance (Monoid w, MonadFix m) => MonadFix (WriterT w m) where
mfix :: forall a. (a -> WriterT w m a) -> WriterT w m a
mfix a -> WriterT w m a
m = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ ((a, w) -> m (a, w)) -> m (a, w)
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix (((a, w) -> m (a, w)) -> m (a, w))
-> ((a, w) -> m (a, w)) -> m (a, w)
forall a b. (a -> b) -> a -> b
$ \ ~(a
a, w
_) -> WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (a -> WriterT w m a
m a
a)
{-# INLINE mfix #-}
instance (Monoid w) => MonadTrans (WriterT w) where
lift :: forall (m :: * -> *) a. Monad m => m a -> WriterT w m a
lift m a
m = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ do
a
a <- m a
m
(a, w) -> m (a, w)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, w
forall a. Monoid a => a
mempty)
{-# INLINE lift #-}
instance (Monoid w, MonadIO m) => MonadIO (WriterT w m) where
liftIO :: forall a. IO a -> WriterT w m a
liftIO = m a -> WriterT w m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> WriterT w m a) -> (IO a -> m a) -> IO a -> WriterT w m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
{-# INLINE liftIO #-}
#if MIN_VERSION_base(4,4,0)
instance (Monoid w, MonadZip m) => MonadZip (WriterT w m) where
mzipWith :: forall a b c.
(a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c
mzipWith a -> b -> c
f (WriterT m (a, w)
x) (WriterT m (b, w)
y) = m (c, w) -> WriterT w m c
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (c, w) -> WriterT w m c) -> m (c, w) -> WriterT w m c
forall a b. (a -> b) -> a -> b
$
((a, w) -> (b, w) -> (c, w)) -> m (a, w) -> m (b, w) -> m (c, w)
forall (m :: * -> *) a b c.
MonadZip m =>
(a -> b -> c) -> m a -> m b -> m c
mzipWith (\ (a
a, w
w) (b
b, w
w') -> (a -> b -> c
f a
a b
b, w
w w -> w -> w
forall a. Monoid a => a -> a -> a
`mappend` w
w')) m (a, w)
x m (b, w)
y
{-# INLINE mzipWith #-}
#endif
#if MIN_VERSION_base(4,12,0)
instance Contravariant m => Contravariant (WriterT w m) where
contramap :: forall a' a. (a' -> a) -> WriterT w m a -> WriterT w m a'
contramap a' -> a
f = (m (a, w) -> m (a', w)) -> WriterT w m a -> WriterT w m a'
forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT ((m (a, w) -> m (a', w)) -> WriterT w m a -> WriterT w m a')
-> (m (a, w) -> m (a', w)) -> WriterT w m a -> WriterT w m a'
forall a b. (a -> b) -> a -> b
$ ((a', w) -> (a, w)) -> m (a, w) -> m (a', w)
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap (((a', w) -> (a, w)) -> m (a, w) -> m (a', w))
-> ((a', w) -> (a, w)) -> m (a, w) -> m (a', w)
forall a b. (a -> b) -> a -> b
$ \ (a'
a, w
w) -> (a' -> a
f a'
a, w
w)
{-# INLINE contramap #-}
#endif
tell :: (Monad m) => w -> WriterT w m ()
tell :: forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell w
w = ((), w) -> WriterT w m ()
forall (m :: * -> *) a w. Monad m => (a, w) -> WriterT w m a
writer ((), w
w)
{-# INLINE tell #-}
listen :: (Monad m) => WriterT w m a -> WriterT w m (a, w)
listen :: forall (m :: * -> *) w a.
Monad m =>
WriterT w m a -> WriterT w m (a, w)
listen WriterT w m a
m = m ((a, w), w) -> WriterT w m (a, w)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m ((a, w), w) -> WriterT w m (a, w))
-> m ((a, w), w) -> WriterT w m (a, w)
forall a b. (a -> b) -> a -> b
$ do
(a
a, w
w) <- WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m
((a, w), w) -> m ((a, w), w)
forall (m :: * -> *) a. Monad m => a -> m a
return ((a
a, w
w), w
w)
{-# INLINE listen #-}
listens :: (Monad m) => (w -> b) -> WriterT w m a -> WriterT w m (a, b)
listens :: forall (m :: * -> *) w b a.
Monad m =>
(w -> b) -> WriterT w m a -> WriterT w m (a, b)
listens w -> b
f WriterT w m a
m = m ((a, b), w) -> WriterT w m (a, b)
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m ((a, b), w) -> WriterT w m (a, b))
-> m ((a, b), w) -> WriterT w m (a, b)
forall a b. (a -> b) -> a -> b
$ do
(a
a, w
w) <- WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m
((a, b), w) -> m ((a, b), w)
forall (m :: * -> *) a. Monad m => a -> m a
return ((a
a, w -> b
f w
w), w
w)
{-# INLINE listens #-}
pass :: (Monad m) => WriterT w m (a, w -> w) -> WriterT w m a
pass :: forall (m :: * -> *) w a.
Monad m =>
WriterT w m (a, w -> w) -> WriterT w m a
pass WriterT w m (a, w -> w)
m = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ do
((a
a, w -> w
f), w
w) <- WriterT w m (a, w -> w) -> m ((a, w -> w), w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m (a, w -> w)
m
(a, w) -> m (a, w)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, w -> w
f w
w)
{-# INLINE pass #-}
censor :: (Monad m) => (w -> w) -> WriterT w m a -> WriterT w m a
censor :: forall (m :: * -> *) w a.
Monad m =>
(w -> w) -> WriterT w m a -> WriterT w m a
censor w -> w
f WriterT w m a
m = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ do
(a
a, w
w) <- WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m
(a, w) -> m (a, w)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, w -> w
f w
w)
{-# INLINE censor #-}
liftCallCC :: (Monoid w) => CallCC m (a,w) (b,w) -> CallCC (WriterT w m) a b
liftCallCC :: forall w (m :: * -> *) a b.
Monoid w =>
CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b
liftCallCC CallCC m (a, w) (b, w)
callCC (a -> WriterT w m b) -> WriterT w m a
f = m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$
CallCC m (a, w) (b, w)
callCC CallCC m (a, w) (b, w) -> CallCC m (a, w) (b, w)
forall a b. (a -> b) -> a -> b
$ \ (a, w) -> m (b, w)
c ->
WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT ((a -> WriterT w m b) -> WriterT w m a
f (\ a
a -> m (b, w) -> WriterT w m b
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (b, w) -> WriterT w m b) -> m (b, w) -> WriterT w m b
forall a b. (a -> b) -> a -> b
$ (a, w) -> m (b, w)
c (a
a, w
forall a. Monoid a => a
mempty)))
{-# INLINE liftCallCC #-}
liftCatch :: Catch e m (a,w) -> Catch e (WriterT w m) a
liftCatch :: forall e (m :: * -> *) a w.
Catch e m (a, w) -> Catch e (WriterT w m) a
liftCatch Catch e m (a, w)
catchE WriterT w m a
m e -> WriterT w m a
h =
m (a, w) -> WriterT w m a
forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT (m (a, w) -> WriterT w m a) -> m (a, w) -> WriterT w m a
forall a b. (a -> b) -> a -> b
$ WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT w m a
m Catch e m (a, w)
`catchE` \ e
e -> WriterT w m a -> m (a, w)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT (e -> WriterT w m a
h e
e)
{-# INLINE liftCatch #-}