{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE CPP #-}
module Control.Eff.Writer.Strict ( Writer(..)
, withWriter
, tell
, censor
, runWriter
, runFirstWriter
, runLastWriter
, runListWriter
, runMonoidWriter
, execWriter
, execFirstWriter
, execLastWriter
, execListWriter
, execMonoidWriter
) where
import Control.Eff
import Control.Eff.Extend
import Control.Applicative ((<|>))
import Control.Monad.Base
import Control.Monad.Trans.Control
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import Data.Function (fix)
data Writer w v where
Tell :: !w -> Writer w ()
withWriter :: Monad m => a -> b -> (w -> b -> b) -> m (a, b)
withWriter x empty _append = return (x, empty)
instance Monad m => Handle (Writer w) r a (b -> (w -> b -> b) -> m (a, b)) where
handle step q (Tell w) e append = step (q ^$ ()) e append >>=
\(x, l) -> return (x, w `append` l)
instance ( MonadBase m m
, LiftedBase m r
) => MonadBaseControl m (Eff (Writer w ': r)) where
type StM (Eff (Writer w ': r)) a = StM (Eff r) (a, [w])
liftBaseWith f = raise $ liftBaseWith $ \runInBase ->
f (runInBase . runListWriter)
restoreM x = do !(a, ws :: [w]) <- raise (restoreM x)
mapM_ tell ws
return a
tell :: Member (Writer w) r => w -> Eff r ()
tell !w = send $ Tell w
censor :: forall w a r. Member (Writer w) r => (w -> w) -> Eff r a -> Eff r a
censor f = fix (respond_relay' h return)
where
h :: (Eff r b -> Eff r b) -> Arrs r v b -> Writer w v -> Eff r b
h step q (Tell w) = tell (f w) >>= \x -> step (q ^$ x)
runWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r (a, b)
runWriter accum !b m = fix (handle_relay withWriter) m b accum
runListWriter :: Eff (Writer w ': r) a -> Eff r (a,[w])
runListWriter = runWriter (:) []
runMonoidWriter :: (Monoid w) => Eff (Writer w ': r) a -> Eff r (a, w)
runMonoidWriter = runWriter (<>) mempty
runFirstWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w)
runFirstWriter = runWriter (\w b -> Just w <|> b) Nothing
runLastWriter :: Eff (Writer w ': r) a -> Eff r (a, Maybe w)
runLastWriter = runWriter (\w b -> b <|> Just w) Nothing
execWriter :: (w -> b -> b) -> b -> Eff (Writer w ': r) a -> Eff r b
execWriter accum b = fmap snd . runWriter accum b
{-# INLINE execWriter #-}
execListWriter :: Eff (Writer w ': r) a -> Eff r [w]
execListWriter = fmap snd . runListWriter
{-# INLINE execListWriter #-}
execMonoidWriter :: (Monoid w) => Eff (Writer w ': r) a -> Eff r w
execMonoidWriter = fmap snd . runMonoidWriter
{-# INLINE execMonoidWriter #-}
execFirstWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w)
execFirstWriter = fmap snd . runFirstWriter
{-# INLINE execFirstWriter #-}
execLastWriter :: Eff (Writer w ': r) a -> Eff r (Maybe w)
execLastWriter = fmap snd . runLastWriter
{-# INLINE execLastWriter #-}