{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Polysemy.ConstraintAbsorber.MonadWriter
( absorbWriter
) where
import qualified Control.Monad.Writer.Class as S
import Polysemy
import Polysemy.ConstraintAbsorber
import Polysemy.Writer
absorbWriter
:: forall w r a
. ( Monoid w
, Member (Writer w) r
)
=> (S.MonadWriter w (Sem r) => Sem r a)
-> Sem r a
absorbWriter =
let swapTuple (x,y) = (y,x)
semTell = tell
semListen :: Member (Writer w) r => Sem r b -> Sem r (b, w)
semListen = fmap swapTuple . listen @w
semPass :: Member (Writer w) r => Sem r (b, w -> w) -> Sem r b
semPass = pass @w . fmap swapTuple
in absorbWithSem @(S.MonadWriter _) @Action
(WriterDict semTell semListen semPass)
(Sub Dict)
{-# INLINEABLE absorbWriter #-}
data WriterDict w m = WriterDict
{ tell_ :: w -> m ()
, listen_ :: forall a. m a -> m (a, w)
, pass_ :: forall a. m (a, w -> w) -> m a
}
newtype Action m s' a = Action { action :: m a }
deriving (Functor, Applicative, Monad)
instance ( Monad m
, Monoid w
, Reifies s' (WriterDict w m)
) => S.MonadWriter w (Action m s') where
tell w = Action $ tell_ (reflect $ Proxy @s') w
{-# INLINEABLE tell #-}
listen x = Action $ listen_ (reflect $ Proxy @s') (action x)
{-# INLINEABLE listen #-}
pass x = Action $ pass_ (reflect $ Proxy @s') (action x)
{-# INLINEABLE pass #-}