{-# LANGUAGE BlockArguments, DerivingVia #-}
module Control.Effect.Writer
(
Tell(..)
, Listen(..)
, Pass(..)
, Writer
, tell
, listen
, pass
, censor
, runTell
, runTellLazy
, runTellList
, runTellListLazy
, tellToIO
, runTellIORef
, runTellTVar
, runTellAction
, tellIntoEndoTell
, tellToTell
, tellIntoTell
, ignoreTell
, tellToIOSimple
, runTellIORefSimple
, runTellTVarSimple
, runTellActionSimple
, tellToTellSimple
, tellIntoTellSimple
, runListen
, runListenLazy
, listenToIO
, runListenTVar
, listenIntoEndoListen
, runWriter
, runWriterLazy
, writerToIO
, runWriterTVar
, writerToBracket
, writerToBracketTVar
, writerIntoEndoWriter
, fromEndoWriter
, WriterThreads
, WriterLazyThreads
, C.MonadMask
, TellC
, TellLazyC
, TellListC
, TellListLazyC
, TellIntoEndoTellC
, IgnoreTellC
, ListenC
, ListenLazyC
, ListenTVarC
, ListenIntoEndoListenC
, WriterC
, WriterLazyC
, WriterTVarC
, WriterToBracketC
, WriterIntoEndoWriterC
) where
import Data.Bifunctor
import Data.Semigroup
import Data.Tuple (swap)
import Data.IORef
import Control.Concurrent.STM
import Control.Monad
import Control.Effect
import Control.Effect.Reader
import Control.Effect.Bracket
import Control.Effect.Type.ListenPrim
import Control.Effect.Type.WriterPrim
import Control.Effect.Carrier
import Control.Effect.Internal.Writer
import qualified Control.Monad.Catch as C
import Control.Monad.Trans.Reader (ReaderT)
import qualified Control.Monad.Trans.Writer.CPS as W
import qualified Control.Monad.Trans.Writer.Lazy as LW
import Control.Effect.Internal.Utils
import Control.Effect.Carrier.Internal.Interpret
import Control.Effect.Carrier.Internal.Compose
import Control.Effect.Carrier.Internal.Intro
type Writer o = Bundle '[Tell o, Listen o, Pass o]
tell :: Eff (Tell o) m => o -> m ()
tell :: o -> m ()
tell = Tell o m () -> m ()
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (Tell o m () -> m ()) -> (o -> Tell o m ()) -> o -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> Tell o m ()
forall o (m :: * -> *). o -> Tell o m ()
Tell
{-# INLINE tell #-}
listen :: Eff (Listen o) m => m a -> m (o, a)
listen :: m a -> m (o, a)
listen = Listen o m (o, a) -> m (o, a)
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (Listen o m (o, a) -> m (o, a))
-> (m a -> Listen o m (o, a)) -> m a -> m (o, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> Listen o m (o, a)
forall (m :: * -> *) a o. m a -> Listen o m (o, a)
Listen
{-# INLINE listen #-}
pass :: Eff (Pass o) m => m (o -> o, a) -> m a
pass :: m (o -> o, a) -> m a
pass = Pass o m a -> m a
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (Pass o m a -> m a)
-> (m (o -> o, a) -> Pass o m a) -> m (o -> o, a) -> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# m (o -> o, a) -> Pass o m a
forall (m :: * -> *) o a. m (o -> o, a) -> Pass o m a
Pass
{-# INLINE pass #-}
censor :: Eff (Pass o) m => (o -> o) -> m a -> m a
censor :: (o -> o) -> m a -> m a
censor o -> o
f = m (o -> o, a) -> m a
forall o (m :: * -> *) a. Eff (Pass o) m => m (o -> o, a) -> m a
pass (m (o -> o, a) -> m a) -> (m a -> m (o -> o, a)) -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> (o -> o, a)) -> m a -> m (o -> o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) o -> o
f)
{-# INLINE censor #-}
data TellListH
newtype TellListC o m a = TellListC {
TellListC o m a
-> ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
unTellListC ::
ReinterpretC TellListH (Tell o) '[Tell (Dual [o])]
( TellC (Dual [o])
( m
)) a
} deriving ( a -> TellListC o m b -> TellListC o m a
(a -> b) -> TellListC o m a -> TellListC o m b
(forall a b. (a -> b) -> TellListC o m a -> TellListC o m b)
-> (forall a b. a -> TellListC o m b -> TellListC o m a)
-> Functor (TellListC o m)
forall a b. a -> TellListC o m b -> TellListC o m a
forall a b. (a -> b) -> TellListC o m a -> TellListC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> TellListC o m b -> TellListC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> TellListC o m a -> TellListC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TellListC o m b -> TellListC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> TellListC o m b -> TellListC o m a
fmap :: (a -> b) -> TellListC o m a -> TellListC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> TellListC o m a -> TellListC o m b
Functor, Functor (TellListC o m)
a -> TellListC o m a
Functor (TellListC o m)
-> (forall a. a -> TellListC o m a)
-> (forall a b.
TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b)
-> (forall a b c.
(a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c)
-> (forall a b.
TellListC o m a -> TellListC o m b -> TellListC o m b)
-> (forall a b.
TellListC o m a -> TellListC o m b -> TellListC o m a)
-> Applicative (TellListC o m)
TellListC o m a -> TellListC o m b -> TellListC o m b
TellListC o m a -> TellListC o m b -> TellListC o m a
TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b
(a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c
forall a. a -> TellListC o m a
forall a b. TellListC o m a -> TellListC o m b -> TellListC o m a
forall a b. TellListC o m a -> TellListC o m b -> TellListC o m b
forall a b.
TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b
forall a b c.
(a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c
forall o (m :: * -> *). Monad m => Functor (TellListC o m)
forall o (m :: * -> *) a. Monad m => a -> TellListC o m a
forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m a
forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m b
forall o (m :: * -> *) a b.
Monad m =>
TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b
forall o (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: TellListC o m a -> TellListC o m b -> TellListC o m a
$c<* :: forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m a
*> :: TellListC o m a -> TellListC o m b -> TellListC o m b
$c*> :: forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m b
liftA2 :: (a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Monad m =>
(a -> b -> c)
-> TellListC o m a -> TellListC o m b -> TellListC o m c
<*> :: TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b
$c<*> :: forall o (m :: * -> *) a b.
Monad m =>
TellListC o m (a -> b) -> TellListC o m a -> TellListC o m b
pure :: a -> TellListC o m a
$cpure :: forall o (m :: * -> *) a. Monad m => a -> TellListC o m a
$cp1Applicative :: forall o (m :: * -> *). Monad m => Functor (TellListC o m)
Applicative, Applicative (TellListC o m)
a -> TellListC o m a
Applicative (TellListC o m)
-> (forall a b.
TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b)
-> (forall a b.
TellListC o m a -> TellListC o m b -> TellListC o m b)
-> (forall a. a -> TellListC o m a)
-> Monad (TellListC o m)
TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b
TellListC o m a -> TellListC o m b -> TellListC o m b
forall a. a -> TellListC o m a
forall a b. TellListC o m a -> TellListC o m b -> TellListC o m b
forall a b.
TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b
forall o (m :: * -> *). Monad m => Applicative (TellListC o m)
forall o (m :: * -> *) a. Monad m => a -> TellListC o m a
forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m b
forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> TellListC o m a
$creturn :: forall o (m :: * -> *) a. Monad m => a -> TellListC o m a
>> :: TellListC o m a -> TellListC o m b -> TellListC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> TellListC o m b -> TellListC o m b
>>= :: TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
TellListC o m a -> (a -> TellListC o m b) -> TellListC o m b
$cp1Monad :: forall o (m :: * -> *). Monad m => Applicative (TellListC o m)
Monad
, Applicative (TellListC o m)
TellListC o m a
Applicative (TellListC o m)
-> (forall a. TellListC o m a)
-> (forall a.
TellListC o m a -> TellListC o m a -> TellListC o m a)
-> (forall a. TellListC o m a -> TellListC o m [a])
-> (forall a. TellListC o m a -> TellListC o m [a])
-> Alternative (TellListC o m)
TellListC o m a -> TellListC o m a -> TellListC o m a
TellListC o m a -> TellListC o m [a]
TellListC o m a -> TellListC o m [a]
forall a. TellListC o m a
forall a. TellListC o m a -> TellListC o m [a]
forall a. TellListC o m a -> TellListC o m a -> TellListC o m a
forall o (m :: * -> *). MonadPlus m => Applicative (TellListC o m)
forall o (m :: * -> *) a. MonadPlus m => TellListC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m [a]
forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m a -> TellListC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: TellListC o m a -> TellListC o m [a]
$cmany :: forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m [a]
some :: TellListC o m a -> TellListC o m [a]
$csome :: forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m [a]
<|> :: TellListC o m a -> TellListC o m a -> TellListC o m a
$c<|> :: forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m a -> TellListC o m a
empty :: TellListC o m a
$cempty :: forall o (m :: * -> *) a. MonadPlus m => TellListC o m a
$cp1Alternative :: forall o (m :: * -> *). MonadPlus m => Applicative (TellListC o m)
Alternative, Monad (TellListC o m)
Alternative (TellListC o m)
TellListC o m a
Alternative (TellListC o m)
-> Monad (TellListC o m)
-> (forall a. TellListC o m a)
-> (forall a.
TellListC o m a -> TellListC o m a -> TellListC o m a)
-> MonadPlus (TellListC o m)
TellListC o m a -> TellListC o m a -> TellListC o m a
forall a. TellListC o m a
forall a. TellListC o m a -> TellListC o m a -> TellListC o m a
forall o (m :: * -> *). MonadPlus m => Monad (TellListC o m)
forall o (m :: * -> *). MonadPlus m => Alternative (TellListC o m)
forall o (m :: * -> *) a. MonadPlus m => TellListC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m a -> TellListC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: TellListC o m a -> TellListC o m a -> TellListC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
TellListC o m a -> TellListC o m a -> TellListC o m a
mzero :: TellListC o m a
$cmzero :: forall o (m :: * -> *) a. MonadPlus m => TellListC o m a
$cp2MonadPlus :: forall o (m :: * -> *). MonadPlus m => Monad (TellListC o m)
$cp1MonadPlus :: forall o (m :: * -> *). MonadPlus m => Alternative (TellListC o m)
MonadPlus
, Monad (TellListC o m)
Monad (TellListC o m)
-> (forall a. (a -> TellListC o m a) -> TellListC o m a)
-> MonadFix (TellListC o m)
(a -> TellListC o m a) -> TellListC o m a
forall a. (a -> TellListC o m a) -> TellListC o m a
forall o (m :: * -> *). MonadFix m => Monad (TellListC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> TellListC o m a) -> TellListC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> TellListC o m a) -> TellListC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> TellListC o m a) -> TellListC o m a
$cp1MonadFix :: forall o (m :: * -> *). MonadFix m => Monad (TellListC o m)
MonadFix, Monad (TellListC o m)
Monad (TellListC o m)
-> (forall a. String -> TellListC o m a)
-> MonadFail (TellListC o m)
String -> TellListC o m a
forall a. String -> TellListC o m a
forall o (m :: * -> *). MonadFail m => Monad (TellListC o m)
forall o (m :: * -> *) a. MonadFail m => String -> TellListC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> TellListC o m a
$cfail :: forall o (m :: * -> *) a. MonadFail m => String -> TellListC o m a
$cp1MonadFail :: forall o (m :: * -> *). MonadFail m => Monad (TellListC o m)
MonadFail, Monad (TellListC o m)
Monad (TellListC o m)
-> (forall a. IO a -> TellListC o m a) -> MonadIO (TellListC o m)
IO a -> TellListC o m a
forall a. IO a -> TellListC o m a
forall o (m :: * -> *). MonadIO m => Monad (TellListC o m)
forall o (m :: * -> *) a. MonadIO m => IO a -> TellListC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> TellListC o m a
$cliftIO :: forall o (m :: * -> *) a. MonadIO m => IO a -> TellListC o m a
$cp1MonadIO :: forall o (m :: * -> *). MonadIO m => Monad (TellListC o m)
MonadIO
, Monad (TellListC o m)
e -> TellListC o m a
Monad (TellListC o m)
-> (forall e a. Exception e => e -> TellListC o m a)
-> MonadThrow (TellListC o m)
forall e a. Exception e => e -> TellListC o m a
forall o (m :: * -> *). MonadThrow m => Monad (TellListC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TellListC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> TellListC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TellListC o m a
$cp1MonadThrow :: forall o (m :: * -> *). MonadThrow m => Monad (TellListC o m)
MonadThrow, MonadThrow (TellListC o m)
MonadThrow (TellListC o m)
-> (forall e a.
Exception e =>
TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a)
-> MonadCatch (TellListC o m)
TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a
forall e a.
Exception e =>
TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a
forall o (m :: * -> *). MonadCatch m => MonadThrow (TellListC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TellListC o m a -> (e -> TellListC o m a) -> TellListC o m a
$cp1MonadCatch :: forall o (m :: * -> *). MonadCatch m => MonadThrow (TellListC o m)
MonadCatch, MonadCatch (TellListC o m)
MonadCatch (TellListC o m)
-> (forall b.
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b)
-> (forall b.
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b)
-> (forall a b c.
TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c))
-> MonadMask (TellListC o m)
TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c)
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
forall b.
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
forall a b c.
TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c)
forall o (m :: * -> *). MonadMask m => MonadCatch (TellListC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
TellListC o m a
-> (a -> ExitCase b -> TellListC o m c)
-> (a -> TellListC o m b)
-> TellListC o m (b, c)
uninterruptibleMask :: ((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
mask :: ((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListC o m a -> TellListC o m a) -> TellListC o m b)
-> TellListC o m b
$cp1MonadMask :: forall o (m :: * -> *). MonadMask m => MonadCatch (TellListC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> TellListC o m a
(forall (m :: * -> *) a. Monad m => m a -> TellListC o m a)
-> MonadTrans (TellListC o)
forall o (m :: * -> *) a. Monad m => m a -> TellListC o m a
forall (m :: * -> *) a. Monad m => m a -> TellListC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> TellListC o m a
$clift :: forall o (m :: * -> *) a. Monad m => m a -> TellListC o m a
MonadTrans, MonadTrans (TellListC o)
m (StT (TellListC o) a) -> TellListC o m a
MonadTrans (TellListC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (TellListC o) -> m a) -> TellListC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (TellListC o) a) -> TellListC o m a)
-> MonadTransControl (TellListC o)
(Run (TellListC o) -> m a) -> TellListC o m a
forall o. MonadTrans (TellListC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (TellListC o) a) -> TellListC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (TellListC o) -> m a) -> TellListC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (TellListC o) a) -> TellListC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (TellListC o) -> m a) -> TellListC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (TellListC o) a) -> TellListC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (TellListC o) a) -> TellListC o m a
liftWith :: (Run (TellListC o) -> m a) -> TellListC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (TellListC o) -> m a) -> TellListC o m a
$cp1MonadTransControl :: forall o. MonadTrans (TellListC o)
MonadTransControl)
via CompositionBaseT
'[ ReinterpretC TellListH (Tell o) '[Tell (Dual [o])]
, TellC (Dual [o])
]
deriving instance (Carrier m, Threads (W.WriterT (Dual [o])) (Prims m))
=> Carrier (TellListC o m)
instance Eff (Tell (Dual [o])) m
=> Handler TellListH (Tell o) m where
effHandler :: Tell o (Effly z) x -> Effly z x
effHandler (Tell o
o) = Dual [o] -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell ([o] -> Dual [o]
forall a. a -> Dual a
Dual [o
o])
{-# INLINEABLE effHandler #-}
runTellList :: forall o m a p
. ( Carrier m
, Threaders '[WriterThreads] m p
)
=> TellListC o m a
-> m ([o], a)
runTellList :: TellListC o m a -> m ([o], a)
runTellList =
(((Dual [o], a) -> ([o], a)) -> m (Dual [o], a) -> m ([o], a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Dual [o], a) -> ([o], a)) -> m (Dual [o], a) -> m ([o], a))
-> ((Dual [o] -> [o]) -> (Dual [o], a) -> ([o], a))
-> (Dual [o] -> [o])
-> m (Dual [o], a)
-> m ([o], a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dual [o] -> [o]) -> (Dual [o], a) -> ([o], a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first) ([o] -> [o]
forall a. [a] -> [a]
reverse ([o] -> [o]) -> (Dual [o] -> [o]) -> Dual [o] -> [o]
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# Dual [o] -> [o]
forall a. Dual a -> a
getDual)
(m (Dual [o], a) -> m ([o], a))
-> (TellC (Dual [o]) m a -> m (Dual [o], a))
-> TellC (Dual [o]) m a
-> m ([o], a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TellC (Dual [o]) m a -> m (Dual [o], a)
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Carrier m, Threaders '[WriterThreads] m p) =>
TellC o m a -> m (o, a)
runTell
(TellC (Dual [o]) m a -> m ([o], a))
-> (ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
-> TellC (Dual [o]) m a)
-> ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
-> m ([o], a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
-> TellC (Dual [o]) m a
forall h (e :: Effect) (new :: [Effect]) (m :: * -> *) a.
(Handler h e m, KnownList new, HeadEffs new m) =>
ReinterpretC h e new m a -> m a
reinterpretViaHandler
(ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
-> m ([o], a))
-> (TellListC o m a
-> ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a)
-> TellListC o m a
-> m ([o], a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# TellListC o m a
-> ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
forall o (m :: * -> *) a.
TellListC o m a
-> ReinterpretC
TellListH (Tell o) '[Tell (Dual [o])] (TellC (Dual [o]) m) a
unTellListC
{-# INLINE runTellList #-}
data TellListLazyH
newtype TellListLazyC o m a = TellListLazyC {
TellListLazyC o m a
-> ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
unTellListLazyC ::
ReinterpretC TellListLazyH (Tell o) '[Tell (Endo [o])]
( TellLazyC (Endo [o])
( m
)) a
} deriving ( a -> TellListLazyC o m b -> TellListLazyC o m a
(a -> b) -> TellListLazyC o m a -> TellListLazyC o m b
(forall a b.
(a -> b) -> TellListLazyC o m a -> TellListLazyC o m b)
-> (forall a b. a -> TellListLazyC o m b -> TellListLazyC o m a)
-> Functor (TellListLazyC o m)
forall a b. a -> TellListLazyC o m b -> TellListLazyC o m a
forall a b. (a -> b) -> TellListLazyC o m a -> TellListLazyC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> TellListLazyC o m b -> TellListLazyC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> TellListLazyC o m a -> TellListLazyC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TellListLazyC o m b -> TellListLazyC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> TellListLazyC o m b -> TellListLazyC o m a
fmap :: (a -> b) -> TellListLazyC o m a -> TellListLazyC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> TellListLazyC o m a -> TellListLazyC o m b
Functor, Functor (TellListLazyC o m)
a -> TellListLazyC o m a
Functor (TellListLazyC o m)
-> (forall a. a -> TellListLazyC o m a)
-> (forall a b.
TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b)
-> (forall a b c.
(a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c)
-> (forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b)
-> (forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a)
-> Applicative (TellListLazyC o m)
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a
TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b
(a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c
forall a. a -> TellListLazyC o m a
forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a
forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
forall a b.
TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b
forall a b c.
(a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c
forall o (m :: * -> *).
Applicative m =>
Functor (TellListLazyC o m)
forall o (m :: * -> *) a. Applicative m => a -> TellListLazyC o m a
forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a
forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m a
*> :: TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
liftA2 :: (a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> TellListLazyC o m a
-> TellListLazyC o m b
-> TellListLazyC o m c
<*> :: TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
TellListLazyC o m (a -> b)
-> TellListLazyC o m a -> TellListLazyC o m b
pure :: a -> TellListLazyC o m a
$cpure :: forall o (m :: * -> *) a. Applicative m => a -> TellListLazyC o m a
$cp1Applicative :: forall o (m :: * -> *).
Applicative m =>
Functor (TellListLazyC o m)
Applicative, Applicative (TellListLazyC o m)
a -> TellListLazyC o m a
Applicative (TellListLazyC o m)
-> (forall a b.
TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b)
-> (forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b)
-> (forall a. a -> TellListLazyC o m a)
-> Monad (TellListLazyC o m)
TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
forall a. a -> TellListLazyC o m a
forall a b.
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
forall a b.
TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b
forall o (m :: * -> *). Monad m => Applicative (TellListLazyC o m)
forall o (m :: * -> *) a. Monad m => a -> TellListLazyC o m a
forall o (m :: * -> *) a b.
Monad m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
forall o (m :: * -> *) a b.
Monad m =>
TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> TellListLazyC o m a
$creturn :: forall o (m :: * -> *) a. Monad m => a -> TellListLazyC o m a
>> :: TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
TellListLazyC o m a -> TellListLazyC o m b -> TellListLazyC o m b
>>= :: TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
TellListLazyC o m a
-> (a -> TellListLazyC o m b) -> TellListLazyC o m b
$cp1Monad :: forall o (m :: * -> *). Monad m => Applicative (TellListLazyC o m)
Monad
, Applicative (TellListLazyC o m)
TellListLazyC o m a
Applicative (TellListLazyC o m)
-> (forall a. TellListLazyC o m a)
-> (forall a.
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a)
-> (forall a. TellListLazyC o m a -> TellListLazyC o m [a])
-> (forall a. TellListLazyC o m a -> TellListLazyC o m [a])
-> Alternative (TellListLazyC o m)
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
TellListLazyC o m a -> TellListLazyC o m [a]
TellListLazyC o m a -> TellListLazyC o m [a]
forall a. TellListLazyC o m a
forall a. TellListLazyC o m a -> TellListLazyC o m [a]
forall a.
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (TellListLazyC o m)
forall o (m :: * -> *) a. Alternative m => TellListLazyC o m a
forall o (m :: * -> *) a.
Alternative m =>
TellListLazyC o m a -> TellListLazyC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: TellListLazyC o m a -> TellListLazyC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
TellListLazyC o m a -> TellListLazyC o m [a]
some :: TellListLazyC o m a -> TellListLazyC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
TellListLazyC o m a -> TellListLazyC o m [a]
<|> :: TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
empty :: TellListLazyC o m a
$cempty :: forall o (m :: * -> *) a. Alternative m => TellListLazyC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (TellListLazyC o m)
Alternative, Monad (TellListLazyC o m)
Alternative (TellListLazyC o m)
TellListLazyC o m a
Alternative (TellListLazyC o m)
-> Monad (TellListLazyC o m)
-> (forall a. TellListLazyC o m a)
-> (forall a.
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a)
-> MonadPlus (TellListLazyC o m)
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
forall a. TellListLazyC o m a
forall a.
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
forall o (m :: * -> *). MonadPlus m => Monad (TellListLazyC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (TellListLazyC o m)
forall o (m :: * -> *) a. MonadPlus m => TellListLazyC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
TellListLazyC o m a -> TellListLazyC o m a -> TellListLazyC o m a
mzero :: TellListLazyC o m a
$cmzero :: forall o (m :: * -> *) a. MonadPlus m => TellListLazyC o m a
$cp2MonadPlus :: forall o (m :: * -> *). MonadPlus m => Monad (TellListLazyC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (TellListLazyC o m)
MonadPlus
, Monad (TellListLazyC o m)
Monad (TellListLazyC o m)
-> (forall a. (a -> TellListLazyC o m a) -> TellListLazyC o m a)
-> MonadFix (TellListLazyC o m)
(a -> TellListLazyC o m a) -> TellListLazyC o m a
forall a. (a -> TellListLazyC o m a) -> TellListLazyC o m a
forall o (m :: * -> *). MonadFix m => Monad (TellListLazyC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> TellListLazyC o m a) -> TellListLazyC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> TellListLazyC o m a) -> TellListLazyC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> TellListLazyC o m a) -> TellListLazyC o m a
$cp1MonadFix :: forall o (m :: * -> *). MonadFix m => Monad (TellListLazyC o m)
MonadFix, Monad (TellListLazyC o m)
Monad (TellListLazyC o m)
-> (forall a. String -> TellListLazyC o m a)
-> MonadFail (TellListLazyC o m)
String -> TellListLazyC o m a
forall a. String -> TellListLazyC o m a
forall o (m :: * -> *). MonadFail m => Monad (TellListLazyC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> TellListLazyC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> TellListLazyC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> TellListLazyC o m a
$cp1MonadFail :: forall o (m :: * -> *). MonadFail m => Monad (TellListLazyC o m)
MonadFail, Monad (TellListLazyC o m)
Monad (TellListLazyC o m)
-> (forall a. IO a -> TellListLazyC o m a)
-> MonadIO (TellListLazyC o m)
IO a -> TellListLazyC o m a
forall a. IO a -> TellListLazyC o m a
forall o (m :: * -> *). MonadIO m => Monad (TellListLazyC o m)
forall o (m :: * -> *) a. MonadIO m => IO a -> TellListLazyC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> TellListLazyC o m a
$cliftIO :: forall o (m :: * -> *) a. MonadIO m => IO a -> TellListLazyC o m a
$cp1MonadIO :: forall o (m :: * -> *). MonadIO m => Monad (TellListLazyC o m)
MonadIO
, Monad (TellListLazyC o m)
e -> TellListLazyC o m a
Monad (TellListLazyC o m)
-> (forall e a. Exception e => e -> TellListLazyC o m a)
-> MonadThrow (TellListLazyC o m)
forall e a. Exception e => e -> TellListLazyC o m a
forall o (m :: * -> *). MonadThrow m => Monad (TellListLazyC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TellListLazyC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> TellListLazyC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> TellListLazyC o m a
$cp1MonadThrow :: forall o (m :: * -> *). MonadThrow m => Monad (TellListLazyC o m)
MonadThrow, MonadThrow (TellListLazyC o m)
MonadThrow (TellListLazyC o m)
-> (forall e a.
Exception e =>
TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a)
-> MonadCatch (TellListLazyC o m)
TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a
forall e a.
Exception e =>
TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (TellListLazyC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
TellListLazyC o m a
-> (e -> TellListLazyC o m a) -> TellListLazyC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (TellListLazyC o m)
MonadCatch, MonadCatch (TellListLazyC o m)
MonadCatch (TellListLazyC o m)
-> (forall b.
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b)
-> (forall b.
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b)
-> (forall a b c.
TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c))
-> MonadMask (TellListLazyC o m)
TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c)
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
forall b.
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
forall a b c.
TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c)
forall o (m :: * -> *).
MonadMask m =>
MonadCatch (TellListLazyC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
TellListLazyC o m a
-> (a -> ExitCase b -> TellListLazyC o m c)
-> (a -> TellListLazyC o m b)
-> TellListLazyC o m (b, c)
uninterruptibleMask :: ((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
mask :: ((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. TellListLazyC o m a -> TellListLazyC o m a)
-> TellListLazyC o m b)
-> TellListLazyC o m b
$cp1MonadMask :: forall o (m :: * -> *).
MonadMask m =>
MonadCatch (TellListLazyC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> TellListLazyC o m a
(forall (m :: * -> *) a. Monad m => m a -> TellListLazyC o m a)
-> MonadTrans (TellListLazyC o)
forall o (m :: * -> *) a. Monad m => m a -> TellListLazyC o m a
forall (m :: * -> *) a. Monad m => m a -> TellListLazyC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> TellListLazyC o m a
$clift :: forall o (m :: * -> *) a. Monad m => m a -> TellListLazyC o m a
MonadTrans, MonadTrans (TellListLazyC o)
m (StT (TellListLazyC o) a) -> TellListLazyC o m a
MonadTrans (TellListLazyC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (TellListLazyC o) -> m a) -> TellListLazyC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (TellListLazyC o) a) -> TellListLazyC o m a)
-> MonadTransControl (TellListLazyC o)
(Run (TellListLazyC o) -> m a) -> TellListLazyC o m a
forall o. MonadTrans (TellListLazyC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (TellListLazyC o) a) -> TellListLazyC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (TellListLazyC o) -> m a) -> TellListLazyC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (TellListLazyC o) a) -> TellListLazyC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (TellListLazyC o) -> m a) -> TellListLazyC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (TellListLazyC o) a) -> TellListLazyC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (TellListLazyC o) a) -> TellListLazyC o m a
liftWith :: (Run (TellListLazyC o) -> m a) -> TellListLazyC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (TellListLazyC o) -> m a) -> TellListLazyC o m a
$cp1MonadTransControl :: forall o. MonadTrans (TellListLazyC o)
MonadTransControl)
via CompositionBaseT
'[ ReinterpretC TellListLazyH (Tell o) '[Tell (Endo [o])]
, TellLazyC (Endo [o])
]
deriving instance (Carrier m, Threads (LW.WriterT (Endo [o])) (Prims m))
=> Carrier (TellListLazyC o m)
instance Eff (Tell (Endo [o])) m
=> Handler TellListLazyH (Tell o) m where
effHandler :: Tell o (Effly z) x -> Effly z x
effHandler (Tell o
o) = Endo [o] -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell (([o] -> [o]) -> Endo [o]
forall a. (a -> a) -> Endo a
Endo (o
oo -> [o] -> [o]
forall a. a -> [a] -> [a]
:))
{-# INLINEABLE effHandler #-}
runTellListLazy :: forall o m a p
. ( Carrier m
, Threaders '[WriterLazyThreads] m p
)
=> TellListLazyC o m a
-> m ([o], a)
runTellListLazy :: TellListLazyC o m a -> m ([o], a)
runTellListLazy =
m (Endo [o], a) -> m ([o], a)
forall o (f :: * -> *) a.
(Monoid o, Functor f) =>
f (Endo o, a) -> f (o, a)
fromEndoWriter
(m (Endo [o], a) -> m ([o], a))
-> (TellLazyC (Endo [o]) m a -> m (Endo [o], a))
-> TellLazyC (Endo [o]) m a
-> m ([o], a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TellLazyC (Endo [o]) m a -> m (Endo [o], a)
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Carrier m, Threaders '[WriterLazyThreads] m p) =>
TellLazyC o m a -> m (o, a)
runTellLazy
(TellLazyC (Endo [o]) m a -> m ([o], a))
-> (ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
-> TellLazyC (Endo [o]) m a)
-> ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
-> m ([o], a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
-> TellLazyC (Endo [o]) m a
forall h (e :: Effect) (new :: [Effect]) (m :: * -> *) a.
(Handler h e m, KnownList new, HeadEffs new m) =>
ReinterpretC h e new m a -> m a
reinterpretViaHandler
(ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
-> m ([o], a))
-> (TellListLazyC o m a
-> ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a)
-> TellListLazyC o m a
-> m ([o], a)
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# TellListLazyC o m a
-> ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
forall o (m :: * -> *) a.
TellListLazyC o m a
-> ReinterpretC
TellListLazyH
(Tell o)
'[Tell (Endo [o])]
(TellLazyC (Endo [o]) m)
a
unTellListLazyC
{-# INLINE runTellListLazy #-}
runTell :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterThreads] m p
)
=> TellC o m a
-> m (o, a)
runTell :: TellC o m a -> m (o, a)
runTell (TellC WriterT o m a
m) = do
(a
a, o
o) <- WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. Monoid w => WriterT w m a -> m (a, w)
W.runWriterT WriterT o m a
m
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE runTell #-}
runListen :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterThreads] m p
)
=> ListenC o m a
-> m (o, a)
runListen :: ListenC o m a -> m (o, a)
runListen (ListenC WriterT o m a
m) = do
(a
a, o
o) <- WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. Monoid w => WriterT w m a -> m (a, w)
W.runWriterT WriterT o m a
m
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE runListen #-}
runWriter :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterThreads] m p
)
=> WriterC o m a
-> m (o, a)
runWriter :: WriterC o m a -> m (o, a)
runWriter (WriterC WriterT o m a
m) = do
(a
a, o
o) <- WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. Monoid w => WriterT w m a -> m (a, w)
W.runWriterT WriterT o m a
m
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE runWriter #-}
runTellLazy :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterLazyThreads] m p
)
=> TellLazyC o m a
-> m (o, a)
runTellLazy :: TellLazyC o m a -> m (o, a)
runTellLazy (TellLazyC WriterT o m a
m) = (a, o) -> (o, a)
forall a b. (a, b) -> (b, a)
swap ((a, o) -> (o, a)) -> m (a, o) -> m (o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LW.runWriterT WriterT o m a
m
{-# INLINE runTellLazy #-}
runListenLazy :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterThreads] m p
)
=> ListenLazyC o m a
-> m (o, a)
runListenLazy :: ListenLazyC o m a -> m (o, a)
runListenLazy (ListenLazyC WriterT o m a
m) = (a, o) -> (o, a)
forall a b. (a, b) -> (b, a)
swap ((a, o) -> (o, a)) -> m (a, o) -> m (o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LW.runWriterT WriterT o m a
m
{-# INLINE runListenLazy #-}
runWriterLazy :: forall o m a p
. ( Monoid o
, Carrier m
, Threaders '[WriterLazyThreads] m p
)
=> WriterLazyC o m a
-> m (o, a)
runWriterLazy :: WriterLazyC o m a -> m (o, a)
runWriterLazy (WriterLazyC WriterT o m a
m) = (a, o) -> (o, a)
forall a b. (a, b) -> (b, a)
swap ((a, o) -> (o, a)) -> m (a, o) -> m (o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WriterT o m a -> m (a, o)
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
LW.runWriterT WriterT o m a
m
{-# INLINE runWriterLazy #-}
tellTVar :: ( Monoid o
, Effs '[Ask (o -> STM ()), Embed IO] m
)
=> o
-> m ()
tellTVar :: o -> m ()
tellTVar o
o = do
o -> STM ()
write <- m (o -> STM ())
forall i (m :: * -> *). Eff (Ask i) m => m i
ask
IO () -> m ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ o -> STM ()
write o
o
{-# INLINE tellTVar #-}
data WriterToEndoWriterH
instance (Monoid o, Eff (Tell (Endo o)) m)
=> Handler WriterToEndoWriterH (Tell o) m where
effHandler :: Tell o (Effly z) x -> Effly z x
effHandler (Tell o
o) = Endo o -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell ((o -> o) -> Endo o
forall a. (a -> a) -> Endo a
Endo (o
o o -> o -> o
forall a. Semigroup a => a -> a -> a
<>))
{-# INLINEABLE effHandler #-}
instance (Monoid o, Eff (Listen (Endo o)) m)
=> Handler WriterToEndoWriterH (Listen o) m where
effHandler :: Listen o (Effly z) x -> Effly z x
effHandler (Listen Effly z a
m) =
(((Endo o, a) -> (o, a)) -> Effly z (Endo o, a) -> Effly z (o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Endo o, a) -> (o, a)) -> Effly z (Endo o, a) -> Effly z (o, a))
-> ((Endo o -> o) -> (Endo o, a) -> (o, a))
-> (Endo o -> o)
-> Effly z (Endo o, a)
-> Effly z (o, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Endo o -> o) -> (Endo o, a) -> (o, a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first) (\(Endo o -> o
f) -> o -> o
f o
forall a. Monoid a => a
mempty) (Effly z (Endo o, a) -> Effly z (o, a))
-> Effly z (Endo o, a) -> Effly z (o, a)
forall a b. (a -> b) -> a -> b
$ Effly z a -> Effly z (Endo o, a)
forall o (m :: * -> *) a. Eff (Listen o) m => m a -> m (o, a)
listen Effly z a
m
{-# INLINEABLE effHandler #-}
instance (Monoid o, Eff (Pass (Endo o)) m)
=> Handler WriterToEndoWriterH (Pass o) m where
effHandler :: Pass o (Effly z) x -> Effly z x
effHandler (Pass Effly z (o -> o, x)
m) =
Effly z (Endo o -> Endo o, x) -> Effly z x
forall o (m :: * -> *) a. Eff (Pass o) m => m (o -> o, a) -> m a
pass (Effly z (Endo o -> Endo o, x) -> Effly z x)
-> Effly z (Endo o -> Endo o, x) -> Effly z x
forall a b. (a -> b) -> a -> b
$
(((o -> o, x) -> (Endo o -> Endo o, x))
-> Effly z (o -> o, x) -> Effly z (Endo o -> Endo o, x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((o -> o, x) -> (Endo o -> Endo o, x))
-> Effly z (o -> o, x) -> Effly z (Endo o -> Endo o, x))
-> (((o -> o) -> Endo o -> Endo o)
-> (o -> o, x) -> (Endo o -> Endo o, x))
-> ((o -> o) -> Endo o -> Endo o)
-> Effly z (o -> o, x)
-> Effly z (Endo o -> Endo o, x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((o -> o) -> Endo o -> Endo o)
-> (o -> o, x) -> (Endo o -> Endo o, x)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first)
(\o -> o
f (Endo o -> o
ss) -> let !s' :: o
s' = o -> o
f (o -> o
ss o
forall a. Monoid a => a
mempty) in (o -> o) -> Endo o
forall a. (a -> a) -> Endo a
Endo (o
s' o -> o -> o
forall a. Semigroup a => a -> a -> a
<>))
Effly z (o -> o, x)
m
{-# INLINEABLE effHandler #-}
fromEndoWriter :: (Monoid o, Functor f)
=> f (Endo o, a)
-> f (o, a)
fromEndoWriter :: f (Endo o, a) -> f (o, a)
fromEndoWriter = (((Endo o, a) -> (o, a)) -> f (Endo o, a) -> f (o, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Endo o, a) -> (o, a)) -> f (Endo o, a) -> f (o, a))
-> ((Endo o -> o) -> (Endo o, a) -> (o, a))
-> (Endo o -> o)
-> f (Endo o, a)
-> f (o, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Endo o -> o) -> (Endo o, a) -> (o, a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first) (\(Endo o -> o
f) -> o -> o
f o
forall a. Monoid a => a
mempty)
{-# INLINE fromEndoWriter #-}
type TellIntoEndoTellC o =
ReinterpretC WriterToEndoWriterH (Tell o) '[Tell (Endo o)]
tellIntoEndoTell :: ( Monoid o
, HeadEff (Tell (Endo o)) m
)
=> TellIntoEndoTellC o m a
-> m a
tellIntoEndoTell :: TellIntoEndoTellC o m a -> m a
tellIntoEndoTell = TellIntoEndoTellC o m a -> m a
forall h (e :: Effect) (new :: [Effect]) (m :: * -> *) a.
(Handler h e m, KnownList new, HeadEffs new m) =>
ReinterpretC h e new m a -> m a
reinterpretViaHandler
{-# INLINE tellIntoEndoTell #-}
newtype ListenIntoEndoListenC o m a = ListenIntoEndoListenC {
ListenIntoEndoListenC o m a
-> IntroC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
unListenIntoEndoListenC ::
IntroC '[Listen o, Tell o] '[Listen (Endo o), Tell (Endo o)]
( InterpretC WriterToEndoWriterH (Listen o)
( InterpretC WriterToEndoWriterH (Tell o)
( m
))) a
} deriving ( a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
(a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
(forall a b.
(a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b)
-> (forall a b.
a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a)
-> Functor (ListenIntoEndoListenC o m)
forall a b.
a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
forall a b.
(a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
fmap :: (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
Functor, Functor (ListenIntoEndoListenC o m)
a -> ListenIntoEndoListenC o m a
Functor (ListenIntoEndoListenC o m)
-> (forall a. a -> ListenIntoEndoListenC o m a)
-> (forall a b.
ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b)
-> (forall a b c.
(a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c)
-> (forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b)
-> (forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a)
-> Applicative (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
(a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c
forall a. a -> ListenIntoEndoListenC o m a
forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
forall a b.
ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
forall a b c.
(a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c
forall o (m :: * -> *).
Applicative m =>
Functor (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
Applicative m =>
a -> ListenIntoEndoListenC o m a
forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m a
*> :: ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
liftA2 :: (a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b
-> ListenIntoEndoListenC o m c
<*> :: ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
ListenIntoEndoListenC o m (a -> b)
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m b
pure :: a -> ListenIntoEndoListenC o m a
$cpure :: forall o (m :: * -> *) a.
Applicative m =>
a -> ListenIntoEndoListenC o m a
$cp1Applicative :: forall o (m :: * -> *).
Applicative m =>
Functor (ListenIntoEndoListenC o m)
Applicative, Applicative (ListenIntoEndoListenC o m)
a -> ListenIntoEndoListenC o m a
Applicative (ListenIntoEndoListenC o m)
-> (forall a b.
ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b)
-> (forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b)
-> (forall a. a -> ListenIntoEndoListenC o m a)
-> Monad (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
forall a. a -> ListenIntoEndoListenC o m a
forall a b.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
forall a b.
ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
forall o (m :: * -> *).
Monad m =>
Applicative (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
Monad m =>
a -> ListenIntoEndoListenC o m a
forall o (m :: * -> *) a b.
Monad m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
forall o (m :: * -> *) a b.
Monad m =>
ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> ListenIntoEndoListenC o m a
$creturn :: forall o (m :: * -> *) a.
Monad m =>
a -> ListenIntoEndoListenC o m a
>> :: ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m b -> ListenIntoEndoListenC o m b
>>= :: ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
ListenIntoEndoListenC o m a
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
$cp1Monad :: forall o (m :: * -> *).
Monad m =>
Applicative (ListenIntoEndoListenC o m)
Monad
, Applicative (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
Applicative (ListenIntoEndoListenC o m)
-> (forall a. ListenIntoEndoListenC o m a)
-> (forall a.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> (forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a])
-> (forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a])
-> Alternative (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
forall a. ListenIntoEndoListenC o m a
forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
forall a.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a
forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
some :: ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m [a]
<|> :: ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
empty :: ListenIntoEndoListenC o m a
$cempty :: forall o (m :: * -> *) a.
Alternative m =>
ListenIntoEndoListenC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (ListenIntoEndoListenC o m)
Alternative, Monad (ListenIntoEndoListenC o m)
Alternative (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
Alternative (ListenIntoEndoListenC o m)
-> Monad (ListenIntoEndoListenC o m)
-> (forall a. ListenIntoEndoListenC o m a)
-> (forall a.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> MonadPlus (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
forall a. ListenIntoEndoListenC o m a
forall a.
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadPlus m =>
Monad (ListenIntoEndoListenC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
MonadPlus m =>
ListenIntoEndoListenC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
ListenIntoEndoListenC o m a
-> ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a
mzero :: ListenIntoEndoListenC o m a
$cmzero :: forall o (m :: * -> *) a.
MonadPlus m =>
ListenIntoEndoListenC o m a
$cp2MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Monad (ListenIntoEndoListenC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (ListenIntoEndoListenC o m)
MonadPlus
, Monad (ListenIntoEndoListenC o m)
Monad (ListenIntoEndoListenC o m)
-> (forall a.
(a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a)
-> MonadFix (ListenIntoEndoListenC o m)
(a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a
forall a.
(a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadFix m =>
Monad (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> ListenIntoEndoListenC o m a) -> ListenIntoEndoListenC o m a
$cp1MonadFix :: forall o (m :: * -> *).
MonadFix m =>
Monad (ListenIntoEndoListenC o m)
MonadFix, Monad (ListenIntoEndoListenC o m)
Monad (ListenIntoEndoListenC o m)
-> (forall a. String -> ListenIntoEndoListenC o m a)
-> MonadFail (ListenIntoEndoListenC o m)
String -> ListenIntoEndoListenC o m a
forall a. String -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadFail m =>
Monad (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> ListenIntoEndoListenC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> ListenIntoEndoListenC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> ListenIntoEndoListenC o m a
$cp1MonadFail :: forall o (m :: * -> *).
MonadFail m =>
Monad (ListenIntoEndoListenC o m)
MonadFail, Monad (ListenIntoEndoListenC o m)
Monad (ListenIntoEndoListenC o m)
-> (forall a. IO a -> ListenIntoEndoListenC o m a)
-> MonadIO (ListenIntoEndoListenC o m)
IO a -> ListenIntoEndoListenC o m a
forall a. IO a -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadIO m =>
Monad (ListenIntoEndoListenC o m)
forall o (m :: * -> *) a.
MonadIO m =>
IO a -> ListenIntoEndoListenC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> ListenIntoEndoListenC o m a
$cliftIO :: forall o (m :: * -> *) a.
MonadIO m =>
IO a -> ListenIntoEndoListenC o m a
$cp1MonadIO :: forall o (m :: * -> *).
MonadIO m =>
Monad (ListenIntoEndoListenC o m)
MonadIO
, Monad (ListenIntoEndoListenC o m)
e -> ListenIntoEndoListenC o m a
Monad (ListenIntoEndoListenC o m)
-> (forall e a. Exception e => e -> ListenIntoEndoListenC o m a)
-> MonadThrow (ListenIntoEndoListenC o m)
forall e a. Exception e => e -> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadThrow m =>
Monad (ListenIntoEndoListenC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ListenIntoEndoListenC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> ListenIntoEndoListenC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ListenIntoEndoListenC o m a
$cp1MonadThrow :: forall o (m :: * -> *).
MonadThrow m =>
Monad (ListenIntoEndoListenC o m)
MonadThrow, MonadThrow (ListenIntoEndoListenC o m)
MonadThrow (ListenIntoEndoListenC o m)
-> (forall e a.
Exception e =>
ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a)
-> MonadCatch (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a
forall e a.
Exception e =>
ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (ListenIntoEndoListenC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ListenIntoEndoListenC o m a
-> (e -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (ListenIntoEndoListenC o m)
MonadCatch, MonadCatch (ListenIntoEndoListenC o m)
MonadCatch (ListenIntoEndoListenC o m)
-> (forall b.
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b)
-> (forall b.
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b)
-> (forall a b c.
ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c))
-> MonadMask (ListenIntoEndoListenC o m)
ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c)
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
forall b.
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
forall a b c.
ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c)
forall o (m :: * -> *).
MonadMask m =>
MonadCatch (ListenIntoEndoListenC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
ListenIntoEndoListenC o m a
-> (a -> ExitCase b -> ListenIntoEndoListenC o m c)
-> (a -> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m (b, c)
uninterruptibleMask :: ((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
mask :: ((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
ListenIntoEndoListenC o m a -> ListenIntoEndoListenC o m a)
-> ListenIntoEndoListenC o m b)
-> ListenIntoEndoListenC o m b
$cp1MonadMask :: forall o (m :: * -> *).
MonadMask m =>
MonadCatch (ListenIntoEndoListenC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> ListenIntoEndoListenC o m a
(forall (m :: * -> *) a.
Monad m =>
m a -> ListenIntoEndoListenC o m a)
-> MonadTrans (ListenIntoEndoListenC o)
forall o (m :: * -> *) a.
Monad m =>
m a -> ListenIntoEndoListenC o m a
forall (m :: * -> *) a.
Monad m =>
m a -> ListenIntoEndoListenC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> ListenIntoEndoListenC o m a
$clift :: forall o (m :: * -> *) a.
Monad m =>
m a -> ListenIntoEndoListenC o m a
MonadTrans, MonadTrans (ListenIntoEndoListenC o)
m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a
MonadTrans (ListenIntoEndoListenC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a)
-> MonadTransControl (ListenIntoEndoListenC o)
(Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a
forall o. MonadTrans (ListenIntoEndoListenC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (ListenIntoEndoListenC o) a) -> ListenIntoEndoListenC o m a
liftWith :: (Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (ListenIntoEndoListenC o) -> m a)
-> ListenIntoEndoListenC o m a
$cp1MonadTransControl :: forall o. MonadTrans (ListenIntoEndoListenC o)
MonadTransControl)
via CompositionBaseT
'[ IntroC '[Listen o, Tell o] '[Listen (Endo o), Tell (Endo o)]
, InterpretC WriterToEndoWriterH (Listen o)
, InterpretC WriterToEndoWriterH (Tell o)
]
deriving instance (Monoid o, HeadEffs '[Listen (Endo o), Tell (Endo o)] m)
=> Carrier (ListenIntoEndoListenC o m)
listenIntoEndoListen :: ( Monoid o
, HeadEffs '[Listen (Endo o), Tell (Endo o)] m
)
=> ListenIntoEndoListenC o m a
-> m a
listenIntoEndoListen :: ListenIntoEndoListenC o m a -> m a
listenIntoEndoListen =
InterpretC WriterToEndoWriterH (Tell o) m a -> m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC WriterToEndoWriterH (Tell o) m a -> m a)
-> (InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> InterpretC WriterToEndoWriterH (Tell o) m a)
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> InterpretC WriterToEndoWriterH (Tell o) m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> m a)
-> (IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a)
-> IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
forall (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a.
(KnownList top, KnownList new, IntroConsistent top new m) =>
IntroUnderManyC top new m a -> m a
introUnderMany
(IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> m a)
-> (ListenIntoEndoListenC o m a
-> IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a)
-> ListenIntoEndoListenC o m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# ListenIntoEndoListenC o m a
-> IntroUnderManyC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
forall o (m :: * -> *) a.
ListenIntoEndoListenC o m a
-> IntroC
'[Listen o, Tell o]
'[Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
unListenIntoEndoListenC
{-# INLINE listenIntoEndoListen #-}
newtype WriterIntoEndoWriterC o m a = WriterIntoEndoWriterC {
WriterIntoEndoWriterC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
unWriterIntoEndoWriterC ::
IntroC '[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
( InterpretC WriterToEndoWriterH (Pass o)
( InterpretC WriterToEndoWriterH (Listen o)
( InterpretC WriterToEndoWriterH (Tell o)
( m
)))) a
} deriving ( a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
(a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
(forall a b.
(a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b)
-> (forall a b.
a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a)
-> Functor (WriterIntoEndoWriterC o m)
forall a b.
a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
forall a b.
(a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
fmap :: (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
Functor, Functor (WriterIntoEndoWriterC o m)
a -> WriterIntoEndoWriterC o m a
Functor (WriterIntoEndoWriterC o m)
-> (forall a. a -> WriterIntoEndoWriterC o m a)
-> (forall a b.
WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b)
-> (forall a b c.
(a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c)
-> (forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b)
-> (forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a)
-> Applicative (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
(a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c
forall a. a -> WriterIntoEndoWriterC o m a
forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
forall a b.
WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
forall a b c.
(a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c
forall o (m :: * -> *).
Applicative m =>
Functor (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
Applicative m =>
a -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m a
*> :: WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
liftA2 :: (a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b
-> WriterIntoEndoWriterC o m c
<*> :: WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterIntoEndoWriterC o m (a -> b)
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m b
pure :: a -> WriterIntoEndoWriterC o m a
$cpure :: forall o (m :: * -> *) a.
Applicative m =>
a -> WriterIntoEndoWriterC o m a
$cp1Applicative :: forall o (m :: * -> *).
Applicative m =>
Functor (WriterIntoEndoWriterC o m)
Applicative, Applicative (WriterIntoEndoWriterC o m)
a -> WriterIntoEndoWriterC o m a
Applicative (WriterIntoEndoWriterC o m)
-> (forall a b.
WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b)
-> (forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b)
-> (forall a. a -> WriterIntoEndoWriterC o m a)
-> Monad (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
forall a. a -> WriterIntoEndoWriterC o m a
forall a b.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
forall a b.
WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
forall o (m :: * -> *).
Monad m =>
Applicative (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
Monad m =>
a -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a b.
Monad m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
forall o (m :: * -> *) a b.
Monad m =>
WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> WriterIntoEndoWriterC o m a
$creturn :: forall o (m :: * -> *) a.
Monad m =>
a -> WriterIntoEndoWriterC o m a
>> :: WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m b -> WriterIntoEndoWriterC o m b
>>= :: WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
WriterIntoEndoWriterC o m a
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
$cp1Monad :: forall o (m :: * -> *).
Monad m =>
Applicative (WriterIntoEndoWriterC o m)
Monad
, Applicative (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
Applicative (WriterIntoEndoWriterC o m)
-> (forall a. WriterIntoEndoWriterC o m a)
-> (forall a.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> (forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a])
-> (forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a])
-> Alternative (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
forall a. WriterIntoEndoWriterC o m a
forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
forall a.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
some :: WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m [a]
<|> :: WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
empty :: WriterIntoEndoWriterC o m a
$cempty :: forall o (m :: * -> *) a.
Alternative m =>
WriterIntoEndoWriterC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (WriterIntoEndoWriterC o m)
Alternative, Monad (WriterIntoEndoWriterC o m)
Alternative (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
Alternative (WriterIntoEndoWriterC o m)
-> Monad (WriterIntoEndoWriterC o m)
-> (forall a. WriterIntoEndoWriterC o m a)
-> (forall a.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> MonadPlus (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
forall a. WriterIntoEndoWriterC o m a
forall a.
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadPlus m =>
Monad (WriterIntoEndoWriterC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
MonadPlus m =>
WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
WriterIntoEndoWriterC o m a
-> WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a
mzero :: WriterIntoEndoWriterC o m a
$cmzero :: forall o (m :: * -> *) a.
MonadPlus m =>
WriterIntoEndoWriterC o m a
$cp2MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Monad (WriterIntoEndoWriterC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterIntoEndoWriterC o m)
MonadPlus
, Monad (WriterIntoEndoWriterC o m)
Monad (WriterIntoEndoWriterC o m)
-> (forall a.
(a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a)
-> MonadFix (WriterIntoEndoWriterC o m)
(a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a
forall a.
(a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadFix m =>
Monad (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterIntoEndoWriterC o m a) -> WriterIntoEndoWriterC o m a
$cp1MonadFix :: forall o (m :: * -> *).
MonadFix m =>
Monad (WriterIntoEndoWriterC o m)
MonadFix, Monad (WriterIntoEndoWriterC o m)
Monad (WriterIntoEndoWriterC o m)
-> (forall a. String -> WriterIntoEndoWriterC o m a)
-> MonadFail (WriterIntoEndoWriterC o m)
String -> WriterIntoEndoWriterC o m a
forall a. String -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadFail m =>
Monad (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> WriterIntoEndoWriterC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterIntoEndoWriterC o m a
$cp1MonadFail :: forall o (m :: * -> *).
MonadFail m =>
Monad (WriterIntoEndoWriterC o m)
MonadFail, Monad (WriterIntoEndoWriterC o m)
Monad (WriterIntoEndoWriterC o m)
-> (forall a. IO a -> WriterIntoEndoWriterC o m a)
-> MonadIO (WriterIntoEndoWriterC o m)
IO a -> WriterIntoEndoWriterC o m a
forall a. IO a -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadIO m =>
Monad (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) a.
MonadIO m =>
IO a -> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> WriterIntoEndoWriterC o m a
$cliftIO :: forall o (m :: * -> *) a.
MonadIO m =>
IO a -> WriterIntoEndoWriterC o m a
$cp1MonadIO :: forall o (m :: * -> *).
MonadIO m =>
Monad (WriterIntoEndoWriterC o m)
MonadIO
, Monad (WriterIntoEndoWriterC o m)
e -> WriterIntoEndoWriterC o m a
Monad (WriterIntoEndoWriterC o m)
-> (forall e a. Exception e => e -> WriterIntoEndoWriterC o m a)
-> MonadThrow (WriterIntoEndoWriterC o m)
forall e a. Exception e => e -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadThrow m =>
Monad (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> WriterIntoEndoWriterC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterIntoEndoWriterC o m a
$cp1MonadThrow :: forall o (m :: * -> *).
MonadThrow m =>
Monad (WriterIntoEndoWriterC o m)
MonadThrow, MonadThrow (WriterIntoEndoWriterC o m)
MonadThrow (WriterIntoEndoWriterC o m)
-> (forall e a.
Exception e =>
WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a)
-> MonadCatch (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a
forall e a.
Exception e =>
WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterIntoEndoWriterC o m a
-> (e -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterIntoEndoWriterC o m)
MonadCatch, MonadCatch (WriterIntoEndoWriterC o m)
MonadCatch (WriterIntoEndoWriterC o m)
-> (forall b.
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b)
-> (forall b.
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b)
-> (forall a b c.
WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c))
-> MonadMask (WriterIntoEndoWriterC o m)
WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c)
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
forall b.
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
forall a b c.
WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c)
forall o (m :: * -> *).
MonadMask m =>
MonadCatch (WriterIntoEndoWriterC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
WriterIntoEndoWriterC o m a
-> (a -> ExitCase b -> WriterIntoEndoWriterC o m c)
-> (a -> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m (b, c)
uninterruptibleMask :: ((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
mask :: ((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a.
WriterIntoEndoWriterC o m a -> WriterIntoEndoWriterC o m a)
-> WriterIntoEndoWriterC o m b)
-> WriterIntoEndoWriterC o m b
$cp1MonadMask :: forall o (m :: * -> *).
MonadMask m =>
MonadCatch (WriterIntoEndoWriterC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> WriterIntoEndoWriterC o m a
(forall (m :: * -> *) a.
Monad m =>
m a -> WriterIntoEndoWriterC o m a)
-> MonadTrans (WriterIntoEndoWriterC o)
forall o (m :: * -> *) a.
Monad m =>
m a -> WriterIntoEndoWriterC o m a
forall (m :: * -> *) a.
Monad m =>
m a -> WriterIntoEndoWriterC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> WriterIntoEndoWriterC o m a
$clift :: forall o (m :: * -> *) a.
Monad m =>
m a -> WriterIntoEndoWriterC o m a
MonadTrans, MonadTrans (WriterIntoEndoWriterC o)
m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a
MonadTrans (WriterIntoEndoWriterC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a)
-> MonadTransControl (WriterIntoEndoWriterC o)
(Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a
forall o. MonadTrans (WriterIntoEndoWriterC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterIntoEndoWriterC o) a) -> WriterIntoEndoWriterC o m a
liftWith :: (Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (WriterIntoEndoWriterC o) -> m a)
-> WriterIntoEndoWriterC o m a
$cp1MonadTransControl :: forall o. MonadTrans (WriterIntoEndoWriterC o)
MonadTransControl)
via CompositionBaseT
'[ IntroC '[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
, InterpretC WriterToEndoWriterH (Pass o)
, InterpretC WriterToEndoWriterH (Listen o)
, InterpretC WriterToEndoWriterH (Tell o)
]
deriving instance (Monoid o, HeadEffs '[Pass (Endo o), Listen (Endo o), Tell (Endo o)] m)
=> Carrier (WriterIntoEndoWriterC o m)
writerIntoEndoWriter :: ( Monoid o
, HeadEffs
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
m
)
=> WriterIntoEndoWriterC o m a
-> m a
writerIntoEndoWriter :: WriterIntoEndoWriterC o m a -> m a
writerIntoEndoWriter =
InterpretC WriterToEndoWriterH (Tell o) m a -> m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC WriterToEndoWriterH (Tell o) m a -> m a)
-> (InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> InterpretC WriterToEndoWriterH (Tell o) m a)
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> InterpretC WriterToEndoWriterH (Tell o) m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
-> m a)
-> (InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a)
-> InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
-> m a)
-> (IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
-> InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a)
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
-> InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m))
a
forall (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a.
(KnownList top, KnownList new, IntroConsistent top new m) =>
IntroUnderManyC top new m a -> m a
introUnderMany
(IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
-> m a)
-> (WriterIntoEndoWriterC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a)
-> WriterIntoEndoWriterC o m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# WriterIntoEndoWriterC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
forall o (m :: * -> *) a.
WriterIntoEndoWriterC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[Pass (Endo o), Listen (Endo o), Tell (Endo o)]
(InterpretC
WriterToEndoWriterH
(Pass o)
(InterpretC
WriterToEndoWriterH
(Listen o)
(InterpretC WriterToEndoWriterH (Tell o) m)))
a
unWriterIntoEndoWriterC
{-# INLINE writerIntoEndoWriter #-}
tellToTell :: forall o o' m a
. Eff (Tell o') m
=> (o -> o')
-> InterpretReifiedC (Tell o) m a
-> m a
tellToTell :: (o -> o') -> InterpretReifiedC (Tell o) m a -> m a
tellToTell o -> o'
f = EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a.
(RepresentationalEff e, Carrier m) =>
EffHandler e m -> InterpretReifiedC e m a -> m a
interpret (EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> o' -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell (o -> o'
f o
o)
{-# INLINE tellToTell #-}
tellToTellSimple :: forall o o' m a p
. ( Eff (Tell o') m
, Threaders '[ReaderThreads] m p
)
=> (o -> o')
-> InterpretSimpleC (Tell o) m a
-> m a
tellToTellSimple :: (o -> o') -> InterpretSimpleC (Tell o) m a -> m a
tellToTellSimple o -> o'
f = EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a (p :: [Effect]).
(RepresentationalEff e, Threaders '[ReaderThreads] m p,
Carrier m) =>
EffHandler e m -> InterpretSimpleC e m a -> m a
interpretSimple (EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> o' -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell (o -> o'
f o
o)
{-# INLINE tellToTellSimple #-}
tellIntoTell :: forall o o' m a
. HeadEff (Tell o') m
=> (o -> o')
-> ReinterpretReifiedC (Tell o) '[Tell o'] m a
-> m a
tellIntoTell :: (o -> o') -> ReinterpretReifiedC (Tell o) '[Tell o'] m a -> m a
tellIntoTell o -> o'
f = EffHandler (Tell o) m
-> ReinterpretReifiedC (Tell o) '[Tell o'] m a -> m a
forall (e :: Effect) (new :: [Effect]) (m :: * -> *) a.
(RepresentationalEff e, KnownList new, HeadEffs new m) =>
EffHandler e m -> ReinterpretReifiedC e new m a -> m a
reinterpret (EffHandler (Tell o) m
-> ReinterpretReifiedC (Tell o) '[Tell o'] m a -> m a)
-> EffHandler (Tell o) m
-> ReinterpretReifiedC (Tell o) '[Tell o'] m a
-> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> o' -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell (o -> o'
f o
o)
{-# INLINE tellIntoTell #-}
tellIntoTellSimple :: forall o o' m a p
. ( HeadEff (Tell o') m
, Threaders '[ReaderThreads] m p
)
=> (o -> o')
-> ReinterpretSimpleC (Tell o) '[Tell o'] m a
-> m a
tellIntoTellSimple :: (o -> o') -> ReinterpretSimpleC (Tell o) '[Tell o'] m a -> m a
tellIntoTellSimple o -> o'
f = EffHandler (Tell o) m
-> ReinterpretSimpleC (Tell o) '[Tell o'] m a -> m a
forall (e :: Effect) (new :: [Effect]) (m :: * -> *) a
(p :: [Effect]).
(RepresentationalEff e, KnownList new, HeadEffs new m,
Threaders '[ReaderThreads] m p) =>
EffHandler e m -> ReinterpretSimpleC e new m a -> m a
reinterpretSimple (EffHandler (Tell o) m
-> ReinterpretSimpleC (Tell o) '[Tell o'] m a -> m a)
-> EffHandler (Tell o) m
-> ReinterpretSimpleC (Tell o) '[Tell o'] m a
-> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> o' -> Effly z ()
forall o (m :: * -> *). Eff (Tell o) m => o -> m ()
tell (o -> o'
f o
o)
{-# INLINE tellIntoTellSimple #-}
listenTVar :: forall o m a
. ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m
)
=> m a
-> m (o, a)
listenTVar :: m a -> m (o, a)
listenTVar m a
main = do
o -> STM ()
writeGlobal <- m (o -> STM ())
forall i (m :: * -> *). Eff (Ask i) m => m i
ask
TVar o
localVar <- IO (TVar o) -> m (TVar o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar o) -> m (TVar o)) -> IO (TVar o) -> m (TVar o)
forall a b. (a -> b) -> a -> b
$ o -> IO (TVar o)
forall a. a -> IO (TVar a)
newTVarIO o
forall a. Monoid a => a
mempty
TVar Bool
switch <- IO (TVar Bool) -> m (TVar Bool)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar Bool) -> m (TVar Bool))
-> IO (TVar Bool) -> m (TVar Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> IO (TVar Bool)
forall a. a -> IO (TVar a)
newTVarIO Bool
True
let
writeLocal :: o -> STM ()
writeLocal :: o -> STM ()
writeLocal o
o = do
Bool
writeToLocal <- TVar Bool -> STM Bool
forall a. TVar a -> STM a
readTVar TVar Bool
switch
Bool -> STM () -> STM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
writeToLocal (STM () -> STM ()) -> STM () -> STM ()
forall a b. (a -> b) -> a -> b
$ do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
localVar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
localVar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
o -> STM ()
writeGlobal o
o
a
a <- (((o -> STM ()) -> o -> STM ()) -> m a -> m a
forall i (m :: * -> *) a. Eff (Local i) m => (i -> i) -> m a -> m a
local (\o -> STM ()
_ -> o -> STM ()
writeLocal) m a
main)
m a -> m () -> m a
forall (m :: * -> *) a b. Eff Bracket m => m a -> m b -> m a
`finally`
(IO () -> m ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar Bool -> Bool -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar Bool
switch Bool
False)
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ TVar o -> IO o
forall a. TVar a -> IO a
readTVarIO TVar o
localVar
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
passTVar :: forall o m a
. ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m
)
=> m (o -> o, a)
-> m a
passTVar :: m (o -> o, a) -> m a
passTVar m (o -> o, a)
main = do
o -> STM ()
writeGlobal <- m (o -> STM ())
forall i (m :: * -> *). Eff (Ask i) m => m i
ask
TVar o
localVar <- IO (TVar o) -> m (TVar o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar o) -> m (TVar o)) -> IO (TVar o) -> m (TVar o)
forall a b. (a -> b) -> a -> b
$ o -> IO (TVar o)
forall a. a -> IO (TVar a)
newTVarIO o
forall a. Monoid a => a
mempty
TVar Bool
switch <- IO (TVar Bool) -> m (TVar Bool)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar Bool) -> m (TVar Bool))
-> IO (TVar Bool) -> m (TVar Bool)
forall a b. (a -> b) -> a -> b
$ Bool -> IO (TVar Bool)
forall a. a -> IO (TVar a)
newTVarIO Bool
True
let
writeLocal :: o -> STM ()
writeLocal :: o -> STM ()
writeLocal o
o = do
Bool
writeToLocal <- TVar Bool -> STM Bool
forall a. TVar a -> STM a
readTVar TVar Bool
switch
if Bool
writeToLocal then do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
localVar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
localVar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
else
o -> STM ()
writeGlobal o
o
commit :: (o -> o) -> IO ()
commit :: (o -> o) -> IO ()
commit o -> o
f = STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Bool
notAlreadyCommited <- TVar Bool -> STM Bool
forall a. TVar a -> STM a
readTVar TVar Bool
switch
Bool -> STM () -> STM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
notAlreadyCommited (STM () -> STM ()) -> STM () -> STM ()
forall a b. (a -> b) -> a -> b
$ do
o
o <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
localVar
o -> STM ()
writeGlobal (o -> o
f o
o)
TVar Bool -> Bool -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar Bool
switch Bool
False
((o -> o
_, a
a), ()
_) <-
m ()
-> (() -> ExitCase (o -> o, a) -> m ())
-> (() -> m (o -> o, a))
-> m ((o -> o, a), ())
forall (m :: * -> *) a b c.
Eff Bracket m =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c)
generalBracket
(() -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
(\()
_ -> \case
ExitCaseSuccess (o -> o
f, a
_) -> IO () -> m ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed ((o -> o) -> IO ()
commit o -> o
f)
ExitCase (o -> o, a)
_ -> IO () -> m ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed ((o -> o) -> IO ()
commit o -> o
forall a. a -> a
id)
)
(\()
_ -> ((o -> STM ()) -> o -> STM ()) -> m (o -> o, a) -> m (o -> o, a)
forall i (m :: * -> *) a. Eff (Local i) m => (i -> i) -> m a -> m a
local (\o -> STM ()
_ -> o -> STM ()
writeLocal) m (o -> o, a)
main)
a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
data WriterToBracketH
newtype WriterToBracketC o m a = WriterToBracketC {
WriterToBracketC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
unWriterToBracketC ::
IntroC '[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
( InterpretC WriterToBracketH (Pass o)
( InterpretC WriterToBracketH (Listen o)
( InterpretC WriterTVarH (Tell o)
( ReaderC (o -> STM ())
( m
))))) a
} deriving ( a -> WriterToBracketC o m b -> WriterToBracketC o m a
(a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b
(forall a b.
(a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b)
-> (forall a b.
a -> WriterToBracketC o m b -> WriterToBracketC o m a)
-> Functor (WriterToBracketC o m)
forall a b. a -> WriterToBracketC o m b -> WriterToBracketC o m a
forall a b.
(a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> WriterToBracketC o m b -> WriterToBracketC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> WriterToBracketC o m b -> WriterToBracketC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> WriterToBracketC o m b -> WriterToBracketC o m a
fmap :: (a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> WriterToBracketC o m a -> WriterToBracketC o m b
Functor, Functor (WriterToBracketC o m)
a -> WriterToBracketC o m a
Functor (WriterToBracketC o m)
-> (forall a. a -> WriterToBracketC o m a)
-> (forall a b.
WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b)
-> (forall a b c.
(a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c)
-> (forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b)
-> (forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a)
-> Applicative (WriterToBracketC o m)
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a
WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b
(a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c
forall a. a -> WriterToBracketC o m a
forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a
forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
forall a b.
WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b
forall a b c.
(a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c
forall o (m :: * -> *).
Applicative m =>
Functor (WriterToBracketC o m)
forall o (m :: * -> *) a.
Applicative m =>
a -> WriterToBracketC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m a
*> :: WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
liftA2 :: (a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterToBracketC o m a
-> WriterToBracketC o m b
-> WriterToBracketC o m c
<*> :: WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterToBracketC o m (a -> b)
-> WriterToBracketC o m a -> WriterToBracketC o m b
pure :: a -> WriterToBracketC o m a
$cpure :: forall o (m :: * -> *) a.
Applicative m =>
a -> WriterToBracketC o m a
$cp1Applicative :: forall o (m :: * -> *).
Applicative m =>
Functor (WriterToBracketC o m)
Applicative, Applicative (WriterToBracketC o m)
a -> WriterToBracketC o m a
Applicative (WriterToBracketC o m)
-> (forall a b.
WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b)
-> (forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b)
-> (forall a. a -> WriterToBracketC o m a)
-> Monad (WriterToBracketC o m)
WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
forall a. a -> WriterToBracketC o m a
forall a b.
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
forall a b.
WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b
forall o (m :: * -> *).
Monad m =>
Applicative (WriterToBracketC o m)
forall o (m :: * -> *) a. Monad m => a -> WriterToBracketC o m a
forall o (m :: * -> *) a b.
Monad m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
forall o (m :: * -> *) a b.
Monad m =>
WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> WriterToBracketC o m a
$creturn :: forall o (m :: * -> *) a. Monad m => a -> WriterToBracketC o m a
>> :: WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
WriterToBracketC o m a
-> WriterToBracketC o m b -> WriterToBracketC o m b
>>= :: WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
WriterToBracketC o m a
-> (a -> WriterToBracketC o m b) -> WriterToBracketC o m b
$cp1Monad :: forall o (m :: * -> *).
Monad m =>
Applicative (WriterToBracketC o m)
Monad
, Applicative (WriterToBracketC o m)
WriterToBracketC o m a
Applicative (WriterToBracketC o m)
-> (forall a. WriterToBracketC o m a)
-> (forall a.
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a)
-> (forall a. WriterToBracketC o m a -> WriterToBracketC o m [a])
-> (forall a. WriterToBracketC o m a -> WriterToBracketC o m [a])
-> Alternative (WriterToBracketC o m)
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
WriterToBracketC o m a -> WriterToBracketC o m [a]
WriterToBracketC o m a -> WriterToBracketC o m [a]
forall a. WriterToBracketC o m a
forall a. WriterToBracketC o m a -> WriterToBracketC o m [a]
forall a.
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (WriterToBracketC o m)
forall o (m :: * -> *) a. Alternative m => WriterToBracketC o m a
forall o (m :: * -> *) a.
Alternative m =>
WriterToBracketC o m a -> WriterToBracketC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: WriterToBracketC o m a -> WriterToBracketC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
WriterToBracketC o m a -> WriterToBracketC o m [a]
some :: WriterToBracketC o m a -> WriterToBracketC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
WriterToBracketC o m a -> WriterToBracketC o m [a]
<|> :: WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
empty :: WriterToBracketC o m a
$cempty :: forall o (m :: * -> *) a. Alternative m => WriterToBracketC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (WriterToBracketC o m)
Alternative, Monad (WriterToBracketC o m)
Alternative (WriterToBracketC o m)
WriterToBracketC o m a
Alternative (WriterToBracketC o m)
-> Monad (WriterToBracketC o m)
-> (forall a. WriterToBracketC o m a)
-> (forall a.
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a)
-> MonadPlus (WriterToBracketC o m)
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
forall a. WriterToBracketC o m a
forall a.
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
forall o (m :: * -> *). MonadPlus m => Monad (WriterToBracketC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterToBracketC o m)
forall o (m :: * -> *) a. MonadPlus m => WriterToBracketC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
WriterToBracketC o m a
-> WriterToBracketC o m a -> WriterToBracketC o m a
mzero :: WriterToBracketC o m a
$cmzero :: forall o (m :: * -> *) a. MonadPlus m => WriterToBracketC o m a
$cp2MonadPlus :: forall o (m :: * -> *). MonadPlus m => Monad (WriterToBracketC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterToBracketC o m)
MonadPlus
, Monad (WriterToBracketC o m)
Monad (WriterToBracketC o m)
-> (forall a.
(a -> WriterToBracketC o m a) -> WriterToBracketC o m a)
-> MonadFix (WriterToBracketC o m)
(a -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall a. (a -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall o (m :: * -> *). MonadFix m => Monad (WriterToBracketC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> WriterToBracketC o m a) -> WriterToBracketC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterToBracketC o m a) -> WriterToBracketC o m a
$cp1MonadFix :: forall o (m :: * -> *). MonadFix m => Monad (WriterToBracketC o m)
MonadFix, Monad (WriterToBracketC o m)
Monad (WriterToBracketC o m)
-> (forall a. String -> WriterToBracketC o m a)
-> MonadFail (WriterToBracketC o m)
String -> WriterToBracketC o m a
forall a. String -> WriterToBracketC o m a
forall o (m :: * -> *). MonadFail m => Monad (WriterToBracketC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterToBracketC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> WriterToBracketC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterToBracketC o m a
$cp1MonadFail :: forall o (m :: * -> *). MonadFail m => Monad (WriterToBracketC o m)
MonadFail, Monad (WriterToBracketC o m)
Monad (WriterToBracketC o m)
-> (forall a. IO a -> WriterToBracketC o m a)
-> MonadIO (WriterToBracketC o m)
IO a -> WriterToBracketC o m a
forall a. IO a -> WriterToBracketC o m a
forall o (m :: * -> *). MonadIO m => Monad (WriterToBracketC o m)
forall o (m :: * -> *) a.
MonadIO m =>
IO a -> WriterToBracketC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> WriterToBracketC o m a
$cliftIO :: forall o (m :: * -> *) a.
MonadIO m =>
IO a -> WriterToBracketC o m a
$cp1MonadIO :: forall o (m :: * -> *). MonadIO m => Monad (WriterToBracketC o m)
MonadIO
, Monad (WriterToBracketC o m)
e -> WriterToBracketC o m a
Monad (WriterToBracketC o m)
-> (forall e a. Exception e => e -> WriterToBracketC o m a)
-> MonadThrow (WriterToBracketC o m)
forall e a. Exception e => e -> WriterToBracketC o m a
forall o (m :: * -> *).
MonadThrow m =>
Monad (WriterToBracketC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterToBracketC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> WriterToBracketC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterToBracketC o m a
$cp1MonadThrow :: forall o (m :: * -> *).
MonadThrow m =>
Monad (WriterToBracketC o m)
MonadThrow, MonadThrow (WriterToBracketC o m)
MonadThrow (WriterToBracketC o m)
-> (forall e a.
Exception e =>
WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a)
-> MonadCatch (WriterToBracketC o m)
WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall e a.
Exception e =>
WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterToBracketC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterToBracketC o m a
-> (e -> WriterToBracketC o m a) -> WriterToBracketC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterToBracketC o m)
MonadCatch, MonadCatch (WriterToBracketC o m)
MonadCatch (WriterToBracketC o m)
-> (forall b.
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b)
-> (forall b.
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b)
-> (forall a b c.
WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c))
-> MonadMask (WriterToBracketC o m)
WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c)
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
forall b.
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
forall a b c.
WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c)
forall o (m :: * -> *).
MonadMask m =>
MonadCatch (WriterToBracketC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
WriterToBracketC o m a
-> (a -> ExitCase b -> WriterToBracketC o m c)
-> (a -> WriterToBracketC o m b)
-> WriterToBracketC o m (b, c)
uninterruptibleMask :: ((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
mask :: ((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterToBracketC o m a -> WriterToBracketC o m a)
-> WriterToBracketC o m b)
-> WriterToBracketC o m b
$cp1MonadMask :: forall o (m :: * -> *).
MonadMask m =>
MonadCatch (WriterToBracketC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> WriterToBracketC o m a
(forall (m :: * -> *) a. Monad m => m a -> WriterToBracketC o m a)
-> MonadTrans (WriterToBracketC o)
forall o (m :: * -> *) a. Monad m => m a -> WriterToBracketC o m a
forall (m :: * -> *) a. Monad m => m a -> WriterToBracketC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> WriterToBracketC o m a
$clift :: forall o (m :: * -> *) a. Monad m => m a -> WriterToBracketC o m a
MonadTrans, MonadTrans (WriterToBracketC o)
m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a
MonadTrans (WriterToBracketC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a)
-> MonadTransControl (WriterToBracketC o)
(Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a
forall o. MonadTrans (WriterToBracketC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterToBracketC o) a) -> WriterToBracketC o m a
liftWith :: (Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (WriterToBracketC o) -> m a) -> WriterToBracketC o m a
$cp1MonadTransControl :: forall o. MonadTrans (WriterToBracketC o)
MonadTransControl)
via CompositionBaseT
'[ IntroC '[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
, InterpretC WriterToBracketH (Pass o)
, InterpretC WriterToBracketH (Listen o)
, InterpretC WriterTVarH (Tell o)
, ReaderC (o -> STM ())
]
deriving instance ( Effs '[Bracket, Embed IO] m
, Monoid o
, Threads (ReaderT (o -> STM ())) (Prims m)
)
=> Carrier (WriterToBracketC o m)
instance ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m
)
=> Handler WriterToBracketH (Listen o) m where
effHandler :: Listen o (Effly z) x -> Effly z x
effHandler (Listen Effly z a
m) = Effly z a -> Effly z (o, a)
forall o (m :: * -> *) a.
(Monoid o, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m) =>
m a -> m (o, a)
listenTVar Effly z a
m
{-# INLINEABLE effHandler #-}
instance ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m
)
=> Handler WriterToBracketH (Pass o) m where
effHandler :: Pass o (Effly z) x -> Effly z x
effHandler (Pass Effly z (o -> o, x)
m) = Effly z (o -> o, x) -> Effly z x
forall o (m :: * -> *) a.
(Monoid o, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m) =>
m (o -> o, a) -> m a
passTVar Effly z (o -> o, x)
m
{-# INLINEABLE effHandler #-}
writerToBracket :: forall o m a p
. ( Monoid o
, Effs [Embed IO, Bracket] m
, Threaders '[ReaderThreads] m p
)
=> WriterToBracketC o m a
-> m (o, a)
writerToBracket :: WriterToBracketC o m a -> m (o, a)
writerToBracket WriterToBracketC o m a
m = do
TVar o
tvar <- IO (TVar o) -> m (TVar o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar o) -> m (TVar o)) -> IO (TVar o) -> m (TVar o)
forall a b. (a -> b) -> a -> b
$ o -> IO (TVar o)
forall a. a -> IO (TVar a)
newTVarIO o
forall a. Monoid a => a
mempty
a
a <- TVar o -> WriterToBracketC o m a -> m a
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Effs '[Embed IO, Bracket] m,
Threaders '[ReaderThreads] m p) =>
TVar o -> WriterToBracketC o m a -> m a
writerToBracketTVar TVar o
tvar WriterToBracketC o m a
m
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ TVar o -> IO o
forall a. TVar a -> IO a
readTVarIO TVar o
tvar
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE writerToBracket #-}
writerToBracketTVar :: forall o m a p
. ( Monoid o
, Effs [Embed IO, Bracket] m
, Threaders '[ReaderThreads] m p
)
=> TVar o
-> WriterToBracketC o m a
-> m a
writerToBracketTVar :: TVar o -> WriterToBracketC o m a -> m a
writerToBracketTVar TVar o
tvar =
(o -> STM ()) -> ReaderC (o -> STM ()) m a -> m a
forall i (m :: * -> *) a (p :: [Effect]).
(Carrier m, Threaders '[ReaderThreads] m p) =>
i -> ReaderC i m a -> m a
runReader (\o
o -> do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
tvar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
tvar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
)
(ReaderC (o -> STM ()) m a -> m a)
-> (InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a)
-> InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a
-> m a)
-> (InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a
-> InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a)
-> InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a
-> InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m) a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a
-> m a)
-> (InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a)
-> InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a
-> m a)
-> (IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a)
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m)))
a
forall (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a.
(KnownList top, KnownList new, IntroConsistent top new m) =>
IntroUnderManyC top new m a -> m a
introUnderMany
(IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
-> m a)
-> (WriterToBracketC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a)
-> WriterToBracketC o m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# WriterToBracketC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
forall o (m :: * -> *) a.
WriterToBracketC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterToBracketH
(Pass o)
(InterpretC
WriterToBracketH
(Listen o)
(InterpretC WriterTVarH (Tell o) (ReaderC (o -> STM ()) m))))
a
unWriterToBracketC
{-# INLINE writerToBracketTVar #-}
data WriterTVarH
newtype ListenTVarC o m a = ListenTVarC {
ListenTVarC o m a
-> IntroC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
unListenTVarC ::
IntroC '[Listen o, Tell o]
'[ ListenPrim o
, Local (o -> STM ())
, Ask (o -> STM ())
]
( InterpretC WriterTVarH (Listen o)
( InterpretC WriterTVarH (Tell o)
( InterpretPrimC WriterTVarH (ListenPrim o)
( ReaderC (o -> STM ())
( m
))))) a
} deriving ( a -> ListenTVarC o m b -> ListenTVarC o m a
(a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
(forall a b. (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b)
-> (forall a b. a -> ListenTVarC o m b -> ListenTVarC o m a)
-> Functor (ListenTVarC o m)
forall a b. a -> ListenTVarC o m b -> ListenTVarC o m a
forall a b. (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> ListenTVarC o m b -> ListenTVarC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ListenTVarC o m b -> ListenTVarC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> ListenTVarC o m b -> ListenTVarC o m a
fmap :: (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
Functor, Functor (ListenTVarC o m)
a -> ListenTVarC o m a
Functor (ListenTVarC o m)
-> (forall a. a -> ListenTVarC o m a)
-> (forall a b.
ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b)
-> (forall a b c.
(a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c)
-> (forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b)
-> (forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a)
-> Applicative (ListenTVarC o m)
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a
ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
(a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c
forall a. a -> ListenTVarC o m a
forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a
forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
forall a b.
ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
forall a b c.
(a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c
forall o (m :: * -> *). Applicative m => Functor (ListenTVarC o m)
forall o (m :: * -> *) a. Applicative m => a -> ListenTVarC o m a
forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a
forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m a
*> :: ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
liftA2 :: (a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m c
<*> :: ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
ListenTVarC o m (a -> b) -> ListenTVarC o m a -> ListenTVarC o m b
pure :: a -> ListenTVarC o m a
$cpure :: forall o (m :: * -> *) a. Applicative m => a -> ListenTVarC o m a
$cp1Applicative :: forall o (m :: * -> *). Applicative m => Functor (ListenTVarC o m)
Applicative, Applicative (ListenTVarC o m)
a -> ListenTVarC o m a
Applicative (ListenTVarC o m)
-> (forall a b.
ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b)
-> (forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b)
-> (forall a. a -> ListenTVarC o m a)
-> Monad (ListenTVarC o m)
ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
forall a. a -> ListenTVarC o m a
forall a b.
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
forall a b.
ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b
forall o (m :: * -> *). Monad m => Applicative (ListenTVarC o m)
forall o (m :: * -> *) a. Monad m => a -> ListenTVarC o m a
forall o (m :: * -> *) a b.
Monad m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
forall o (m :: * -> *) a b.
Monad m =>
ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> ListenTVarC o m a
$creturn :: forall o (m :: * -> *) a. Monad m => a -> ListenTVarC o m a
>> :: ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
ListenTVarC o m a -> ListenTVarC o m b -> ListenTVarC o m b
>>= :: ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
ListenTVarC o m a -> (a -> ListenTVarC o m b) -> ListenTVarC o m b
$cp1Monad :: forall o (m :: * -> *). Monad m => Applicative (ListenTVarC o m)
Monad
, Applicative (ListenTVarC o m)
ListenTVarC o m a
Applicative (ListenTVarC o m)
-> (forall a. ListenTVarC o m a)
-> (forall a.
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a)
-> (forall a. ListenTVarC o m a -> ListenTVarC o m [a])
-> (forall a. ListenTVarC o m a -> ListenTVarC o m [a])
-> Alternative (ListenTVarC o m)
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
ListenTVarC o m a -> ListenTVarC o m [a]
ListenTVarC o m a -> ListenTVarC o m [a]
forall a. ListenTVarC o m a
forall a. ListenTVarC o m a -> ListenTVarC o m [a]
forall a.
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (ListenTVarC o m)
forall o (m :: * -> *) a. Alternative m => ListenTVarC o m a
forall o (m :: * -> *) a.
Alternative m =>
ListenTVarC o m a -> ListenTVarC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: ListenTVarC o m a -> ListenTVarC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
ListenTVarC o m a -> ListenTVarC o m [a]
some :: ListenTVarC o m a -> ListenTVarC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
ListenTVarC o m a -> ListenTVarC o m [a]
<|> :: ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
empty :: ListenTVarC o m a
$cempty :: forall o (m :: * -> *) a. Alternative m => ListenTVarC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (ListenTVarC o m)
Alternative, Monad (ListenTVarC o m)
Alternative (ListenTVarC o m)
ListenTVarC o m a
Alternative (ListenTVarC o m)
-> Monad (ListenTVarC o m)
-> (forall a. ListenTVarC o m a)
-> (forall a.
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a)
-> MonadPlus (ListenTVarC o m)
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
forall a. ListenTVarC o m a
forall a.
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
forall o (m :: * -> *). MonadPlus m => Monad (ListenTVarC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (ListenTVarC o m)
forall o (m :: * -> *) a. MonadPlus m => ListenTVarC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
ListenTVarC o m a -> ListenTVarC o m a -> ListenTVarC o m a
mzero :: ListenTVarC o m a
$cmzero :: forall o (m :: * -> *) a. MonadPlus m => ListenTVarC o m a
$cp2MonadPlus :: forall o (m :: * -> *). MonadPlus m => Monad (ListenTVarC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (ListenTVarC o m)
MonadPlus
, Monad (ListenTVarC o m)
Monad (ListenTVarC o m)
-> (forall a. (a -> ListenTVarC o m a) -> ListenTVarC o m a)
-> MonadFix (ListenTVarC o m)
(a -> ListenTVarC o m a) -> ListenTVarC o m a
forall a. (a -> ListenTVarC o m a) -> ListenTVarC o m a
forall o (m :: * -> *). MonadFix m => Monad (ListenTVarC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> ListenTVarC o m a) -> ListenTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> ListenTVarC o m a) -> ListenTVarC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> ListenTVarC o m a) -> ListenTVarC o m a
$cp1MonadFix :: forall o (m :: * -> *). MonadFix m => Monad (ListenTVarC o m)
MonadFix, Monad (ListenTVarC o m)
Monad (ListenTVarC o m)
-> (forall a. String -> ListenTVarC o m a)
-> MonadFail (ListenTVarC o m)
String -> ListenTVarC o m a
forall a. String -> ListenTVarC o m a
forall o (m :: * -> *). MonadFail m => Monad (ListenTVarC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> ListenTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> ListenTVarC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> ListenTVarC o m a
$cp1MonadFail :: forall o (m :: * -> *). MonadFail m => Monad (ListenTVarC o m)
MonadFail, Monad (ListenTVarC o m)
Monad (ListenTVarC o m)
-> (forall a. IO a -> ListenTVarC o m a)
-> MonadIO (ListenTVarC o m)
IO a -> ListenTVarC o m a
forall a. IO a -> ListenTVarC o m a
forall o (m :: * -> *). MonadIO m => Monad (ListenTVarC o m)
forall o (m :: * -> *) a. MonadIO m => IO a -> ListenTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> ListenTVarC o m a
$cliftIO :: forall o (m :: * -> *) a. MonadIO m => IO a -> ListenTVarC o m a
$cp1MonadIO :: forall o (m :: * -> *). MonadIO m => Monad (ListenTVarC o m)
MonadIO
, Monad (ListenTVarC o m)
e -> ListenTVarC o m a
Monad (ListenTVarC o m)
-> (forall e a. Exception e => e -> ListenTVarC o m a)
-> MonadThrow (ListenTVarC o m)
forall e a. Exception e => e -> ListenTVarC o m a
forall o (m :: * -> *). MonadThrow m => Monad (ListenTVarC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ListenTVarC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> ListenTVarC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ListenTVarC o m a
$cp1MonadThrow :: forall o (m :: * -> *). MonadThrow m => Monad (ListenTVarC o m)
MonadThrow, MonadThrow (ListenTVarC o m)
MonadThrow (ListenTVarC o m)
-> (forall e a.
Exception e =>
ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a)
-> MonadCatch (ListenTVarC o m)
ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a
forall e a.
Exception e =>
ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (ListenTVarC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ListenTVarC o m a -> (e -> ListenTVarC o m a) -> ListenTVarC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (ListenTVarC o m)
MonadCatch, MonadCatch (ListenTVarC o m)
MonadCatch (ListenTVarC o m)
-> (forall b.
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b)
-> (forall b.
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b)
-> (forall a b c.
ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c))
-> MonadMask (ListenTVarC o m)
ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c)
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
forall b.
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
forall a b c.
ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c)
forall o (m :: * -> *). MonadMask m => MonadCatch (ListenTVarC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
ListenTVarC o m a
-> (a -> ExitCase b -> ListenTVarC o m c)
-> (a -> ListenTVarC o m b)
-> ListenTVarC o m (b, c)
uninterruptibleMask :: ((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
mask :: ((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. ListenTVarC o m a -> ListenTVarC o m a)
-> ListenTVarC o m b)
-> ListenTVarC o m b
$cp1MonadMask :: forall o (m :: * -> *). MonadMask m => MonadCatch (ListenTVarC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> ListenTVarC o m a
(forall (m :: * -> *) a. Monad m => m a -> ListenTVarC o m a)
-> MonadTrans (ListenTVarC o)
forall o (m :: * -> *) a. Monad m => m a -> ListenTVarC o m a
forall (m :: * -> *) a. Monad m => m a -> ListenTVarC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> ListenTVarC o m a
$clift :: forall o (m :: * -> *) a. Monad m => m a -> ListenTVarC o m a
MonadTrans, MonadTrans (ListenTVarC o)
m (StT (ListenTVarC o) a) -> ListenTVarC o m a
MonadTrans (ListenTVarC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (ListenTVarC o) -> m a) -> ListenTVarC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (ListenTVarC o) a) -> ListenTVarC o m a)
-> MonadTransControl (ListenTVarC o)
(Run (ListenTVarC o) -> m a) -> ListenTVarC o m a
forall o. MonadTrans (ListenTVarC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (ListenTVarC o) a) -> ListenTVarC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (ListenTVarC o) -> m a) -> ListenTVarC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (ListenTVarC o) a) -> ListenTVarC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (ListenTVarC o) -> m a) -> ListenTVarC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (ListenTVarC o) a) -> ListenTVarC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (ListenTVarC o) a) -> ListenTVarC o m a
liftWith :: (Run (ListenTVarC o) -> m a) -> ListenTVarC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (ListenTVarC o) -> m a) -> ListenTVarC o m a
$cp1MonadTransControl :: forall o. MonadTrans (ListenTVarC o)
MonadTransControl)
via CompositionBaseT
'[ IntroC '[Listen o, Tell o]
'[ ListenPrim o
, Local (o -> STM ())
, Ask (o -> STM ())
]
, InterpretC WriterTVarH (Listen o)
, InterpretC WriterTVarH (Tell o)
, InterpretPrimC WriterTVarH (ListenPrim o)
, ReaderC (o -> STM ())
]
deriving instance ( Monoid o
, Eff (Embed IO) m
, MonadMask m
, Threads (ReaderT (o -> STM ())) (Prims m)
)
=> Carrier (ListenTVarC o m)
newtype WriterTVarC o m a = WriterTVarC {
WriterTVarC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
unWriterTVarC ::
IntroC '[Pass o, Listen o, Tell o]
'[ ListenPrim o
, WriterPrim o
, Local (o -> STM ())
, Ask (o -> STM ())
]
( InterpretC WriterTVarH (Pass o)
( InterpretC WriterTVarH (Listen o)
( InterpretC WriterTVarH (Tell o)
( InterpretC WriterTVarH (ListenPrim o)
( InterpretPrimC WriterTVarH (WriterPrim o)
( ReaderC (o -> STM ())
( m
))))))) a
} deriving ( a -> WriterTVarC o m b -> WriterTVarC o m a
(a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
(forall a b. (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b)
-> (forall a b. a -> WriterTVarC o m b -> WriterTVarC o m a)
-> Functor (WriterTVarC o m)
forall a b. a -> WriterTVarC o m b -> WriterTVarC o m a
forall a b. (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
forall o (m :: * -> *) a b.
Functor m =>
a -> WriterTVarC o m b -> WriterTVarC o m a
forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> WriterTVarC o m b -> WriterTVarC o m a
$c<$ :: forall o (m :: * -> *) a b.
Functor m =>
a -> WriterTVarC o m b -> WriterTVarC o m a
fmap :: (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
$cfmap :: forall o (m :: * -> *) a b.
Functor m =>
(a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
Functor, Functor (WriterTVarC o m)
a -> WriterTVarC o m a
Functor (WriterTVarC o m)
-> (forall a. a -> WriterTVarC o m a)
-> (forall a b.
WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b)
-> (forall a b c.
(a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c)
-> (forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b)
-> (forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a)
-> Applicative (WriterTVarC o m)
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a
WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
(a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c
forall a. a -> WriterTVarC o m a
forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a
forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
forall a b.
WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
forall a b c.
(a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c
forall o (m :: * -> *). Applicative m => Functor (WriterTVarC o m)
forall o (m :: * -> *) a. Applicative m => a -> WriterTVarC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a
forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a
$c<* :: forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m a
*> :: WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
$c*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
liftA2 :: (a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c
$cliftA2 :: forall o (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c)
-> WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m c
<*> :: WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
$c<*> :: forall o (m :: * -> *) a b.
Applicative m =>
WriterTVarC o m (a -> b) -> WriterTVarC o m a -> WriterTVarC o m b
pure :: a -> WriterTVarC o m a
$cpure :: forall o (m :: * -> *) a. Applicative m => a -> WriterTVarC o m a
$cp1Applicative :: forall o (m :: * -> *). Applicative m => Functor (WriterTVarC o m)
Applicative, Applicative (WriterTVarC o m)
a -> WriterTVarC o m a
Applicative (WriterTVarC o m)
-> (forall a b.
WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b)
-> (forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b)
-> (forall a. a -> WriterTVarC o m a)
-> Monad (WriterTVarC o m)
WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
forall a. a -> WriterTVarC o m a
forall a b.
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
forall a b.
WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b
forall o (m :: * -> *). Monad m => Applicative (WriterTVarC o m)
forall o (m :: * -> *) a. Monad m => a -> WriterTVarC o m a
forall o (m :: * -> *) a b.
Monad m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
forall o (m :: * -> *) a b.
Monad m =>
WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> WriterTVarC o m a
$creturn :: forall o (m :: * -> *) a. Monad m => a -> WriterTVarC o m a
>> :: WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
$c>> :: forall o (m :: * -> *) a b.
Monad m =>
WriterTVarC o m a -> WriterTVarC o m b -> WriterTVarC o m b
>>= :: WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b
$c>>= :: forall o (m :: * -> *) a b.
Monad m =>
WriterTVarC o m a -> (a -> WriterTVarC o m b) -> WriterTVarC o m b
$cp1Monad :: forall o (m :: * -> *). Monad m => Applicative (WriterTVarC o m)
Monad
, Applicative (WriterTVarC o m)
WriterTVarC o m a
Applicative (WriterTVarC o m)
-> (forall a. WriterTVarC o m a)
-> (forall a.
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a)
-> (forall a. WriterTVarC o m a -> WriterTVarC o m [a])
-> (forall a. WriterTVarC o m a -> WriterTVarC o m [a])
-> Alternative (WriterTVarC o m)
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
WriterTVarC o m a -> WriterTVarC o m [a]
WriterTVarC o m a -> WriterTVarC o m [a]
forall a. WriterTVarC o m a
forall a. WriterTVarC o m a -> WriterTVarC o m [a]
forall a.
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
forall o (m :: * -> *).
Alternative m =>
Applicative (WriterTVarC o m)
forall o (m :: * -> *) a. Alternative m => WriterTVarC o m a
forall o (m :: * -> *) a.
Alternative m =>
WriterTVarC o m a -> WriterTVarC o m [a]
forall o (m :: * -> *) a.
Alternative m =>
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
many :: WriterTVarC o m a -> WriterTVarC o m [a]
$cmany :: forall o (m :: * -> *) a.
Alternative m =>
WriterTVarC o m a -> WriterTVarC o m [a]
some :: WriterTVarC o m a -> WriterTVarC o m [a]
$csome :: forall o (m :: * -> *) a.
Alternative m =>
WriterTVarC o m a -> WriterTVarC o m [a]
<|> :: WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
$c<|> :: forall o (m :: * -> *) a.
Alternative m =>
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
empty :: WriterTVarC o m a
$cempty :: forall o (m :: * -> *) a. Alternative m => WriterTVarC o m a
$cp1Alternative :: forall o (m :: * -> *).
Alternative m =>
Applicative (WriterTVarC o m)
Alternative, Monad (WriterTVarC o m)
Alternative (WriterTVarC o m)
WriterTVarC o m a
Alternative (WriterTVarC o m)
-> Monad (WriterTVarC o m)
-> (forall a. WriterTVarC o m a)
-> (forall a.
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a)
-> MonadPlus (WriterTVarC o m)
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
forall a. WriterTVarC o m a
forall a.
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
forall o (m :: * -> *). MonadPlus m => Monad (WriterTVarC o m)
forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterTVarC o m)
forall o (m :: * -> *) a. MonadPlus m => WriterTVarC o m a
forall o (m :: * -> *) a.
MonadPlus m =>
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
mplus :: WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
$cmplus :: forall o (m :: * -> *) a.
MonadPlus m =>
WriterTVarC o m a -> WriterTVarC o m a -> WriterTVarC o m a
mzero :: WriterTVarC o m a
$cmzero :: forall o (m :: * -> *) a. MonadPlus m => WriterTVarC o m a
$cp2MonadPlus :: forall o (m :: * -> *). MonadPlus m => Monad (WriterTVarC o m)
$cp1MonadPlus :: forall o (m :: * -> *).
MonadPlus m =>
Alternative (WriterTVarC o m)
MonadPlus
, Monad (WriterTVarC o m)
Monad (WriterTVarC o m)
-> (forall a. (a -> WriterTVarC o m a) -> WriterTVarC o m a)
-> MonadFix (WriterTVarC o m)
(a -> WriterTVarC o m a) -> WriterTVarC o m a
forall a. (a -> WriterTVarC o m a) -> WriterTVarC o m a
forall o (m :: * -> *). MonadFix m => Monad (WriterTVarC o m)
forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterTVarC o m a) -> WriterTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. (a -> m a) -> m a) -> MonadFix m
mfix :: (a -> WriterTVarC o m a) -> WriterTVarC o m a
$cmfix :: forall o (m :: * -> *) a.
MonadFix m =>
(a -> WriterTVarC o m a) -> WriterTVarC o m a
$cp1MonadFix :: forall o (m :: * -> *). MonadFix m => Monad (WriterTVarC o m)
MonadFix, Monad (WriterTVarC o m)
Monad (WriterTVarC o m)
-> (forall a. String -> WriterTVarC o m a)
-> MonadFail (WriterTVarC o m)
String -> WriterTVarC o m a
forall a. String -> WriterTVarC o m a
forall o (m :: * -> *). MonadFail m => Monad (WriterTVarC o m)
forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: String -> WriterTVarC o m a
$cfail :: forall o (m :: * -> *) a.
MonadFail m =>
String -> WriterTVarC o m a
$cp1MonadFail :: forall o (m :: * -> *). MonadFail m => Monad (WriterTVarC o m)
MonadFail, Monad (WriterTVarC o m)
Monad (WriterTVarC o m)
-> (forall a. IO a -> WriterTVarC o m a)
-> MonadIO (WriterTVarC o m)
IO a -> WriterTVarC o m a
forall a. IO a -> WriterTVarC o m a
forall o (m :: * -> *). MonadIO m => Monad (WriterTVarC o m)
forall o (m :: * -> *) a. MonadIO m => IO a -> WriterTVarC o m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> WriterTVarC o m a
$cliftIO :: forall o (m :: * -> *) a. MonadIO m => IO a -> WriterTVarC o m a
$cp1MonadIO :: forall o (m :: * -> *). MonadIO m => Monad (WriterTVarC o m)
MonadIO
, Monad (WriterTVarC o m)
e -> WriterTVarC o m a
Monad (WriterTVarC o m)
-> (forall e a. Exception e => e -> WriterTVarC o m a)
-> MonadThrow (WriterTVarC o m)
forall e a. Exception e => e -> WriterTVarC o m a
forall o (m :: * -> *). MonadThrow m => Monad (WriterTVarC o m)
forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterTVarC o m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> WriterTVarC o m a
$cthrowM :: forall o (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> WriterTVarC o m a
$cp1MonadThrow :: forall o (m :: * -> *). MonadThrow m => Monad (WriterTVarC o m)
MonadThrow, MonadThrow (WriterTVarC o m)
MonadThrow (WriterTVarC o m)
-> (forall e a.
Exception e =>
WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a)
-> MonadCatch (WriterTVarC o m)
WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a
forall e a.
Exception e =>
WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a
forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterTVarC o m)
forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a
$ccatch :: forall o (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
WriterTVarC o m a -> (e -> WriterTVarC o m a) -> WriterTVarC o m a
$cp1MonadCatch :: forall o (m :: * -> *).
MonadCatch m =>
MonadThrow (WriterTVarC o m)
MonadCatch, MonadCatch (WriterTVarC o m)
MonadCatch (WriterTVarC o m)
-> (forall b.
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b)
-> (forall b.
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b)
-> (forall a b c.
WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c))
-> MonadMask (WriterTVarC o m)
WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c)
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
forall b.
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
forall a b c.
WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c)
forall o (m :: * -> *). MonadMask m => MonadCatch (WriterTVarC o m)
forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
forall o (m :: * -> *) a b c.
MonadMask m =>
WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c)
$cgeneralBracket :: forall o (m :: * -> *) a b c.
MonadMask m =>
WriterTVarC o m a
-> (a -> ExitCase b -> WriterTVarC o m c)
-> (a -> WriterTVarC o m b)
-> WriterTVarC o m (b, c)
uninterruptibleMask :: ((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
$cuninterruptibleMask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
mask :: ((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
$cmask :: forall o (m :: * -> *) b.
MonadMask m =>
((forall a. WriterTVarC o m a -> WriterTVarC o m a)
-> WriterTVarC o m b)
-> WriterTVarC o m b
$cp1MonadMask :: forall o (m :: * -> *). MonadMask m => MonadCatch (WriterTVarC o m)
MonadMask
, MonadBase b, MonadBaseControl b
)
deriving (m a -> WriterTVarC o m a
(forall (m :: * -> *) a. Monad m => m a -> WriterTVarC o m a)
-> MonadTrans (WriterTVarC o)
forall o (m :: * -> *) a. Monad m => m a -> WriterTVarC o m a
forall (m :: * -> *) a. Monad m => m a -> WriterTVarC o m a
forall (t :: Effect).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> WriterTVarC o m a
$clift :: forall o (m :: * -> *) a. Monad m => m a -> WriterTVarC o m a
MonadTrans, MonadTrans (WriterTVarC o)
m (StT (WriterTVarC o) a) -> WriterTVarC o m a
MonadTrans (WriterTVarC o)
-> (forall (m :: * -> *) a.
Monad m =>
(Run (WriterTVarC o) -> m a) -> WriterTVarC o m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (WriterTVarC o) a) -> WriterTVarC o m a)
-> MonadTransControl (WriterTVarC o)
(Run (WriterTVarC o) -> m a) -> WriterTVarC o m a
forall o. MonadTrans (WriterTVarC o)
forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterTVarC o) a) -> WriterTVarC o m a
forall o (m :: * -> *) a.
Monad m =>
(Run (WriterTVarC o) -> m a) -> WriterTVarC o m a
forall (m :: * -> *) a.
Monad m =>
m (StT (WriterTVarC o) a) -> WriterTVarC o m a
forall (m :: * -> *) a.
Monad m =>
(Run (WriterTVarC o) -> m a) -> WriterTVarC o m a
forall (t :: Effect).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT (WriterTVarC o) a) -> WriterTVarC o m a
$crestoreT :: forall o (m :: * -> *) a.
Monad m =>
m (StT (WriterTVarC o) a) -> WriterTVarC o m a
liftWith :: (Run (WriterTVarC o) -> m a) -> WriterTVarC o m a
$cliftWith :: forall o (m :: * -> *) a.
Monad m =>
(Run (WriterTVarC o) -> m a) -> WriterTVarC o m a
$cp1MonadTransControl :: forall o. MonadTrans (WriterTVarC o)
MonadTransControl)
via CompositionBaseT
'[ IntroC '[Pass o, Listen o, Tell o]
'[ ListenPrim o
, WriterPrim o
, Local (o -> STM ())
, Ask (o -> STM ())
]
, InterpretC WriterTVarH (Pass o)
, InterpretC WriterTVarH (Listen o)
, InterpretC WriterTVarH (Tell o)
, InterpretC WriterTVarH (ListenPrim o)
, InterpretPrimC WriterTVarH (WriterPrim o)
, ReaderC (o -> STM ())
]
deriving instance ( Monoid o
, Eff (Embed IO) m
, MonadMask m
, Threads (ReaderT (o -> STM ())) (Prims m)
)
=> Carrier (WriterTVarC o m)
instance ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO] m
)
=> Handler WriterTVarH (Tell o) m where
effHandler :: Tell o (Effly z) x -> Effly z x
effHandler (Tell o
o) = m () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (o -> m ()
forall o (m :: * -> *).
(Monoid o, Effs '[Ask (o -> STM ()), Embed IO] m) =>
o -> m ()
tellTVar o
o)
{-# INLINEABLE effHandler #-}
instance Eff (ListenPrim o) m
=> Handler WriterTVarH (Listen o) m where
effHandler :: Listen o (Effly z) x -> Effly z x
effHandler (Listen Effly z a
m) = ListenPrim o (Effly z) (o, a) -> Effly z (o, a)
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (ListenPrim o (Effly z) (o, a) -> Effly z (o, a))
-> ListenPrim o (Effly z) (o, a) -> Effly z (o, a)
forall a b. (a -> b) -> a -> b
$ Effly z a -> ListenPrim o (Effly z) (o, a)
forall (m :: * -> *) a o. m a -> ListenPrim o m (o, a)
ListenPrimListen Effly z a
m
{-# INLINEABLE effHandler #-}
instance Eff (WriterPrim o) m
=> Handler WriterTVarH (Pass o) m where
effHandler :: Pass o (Effly z) x -> Effly z x
effHandler (Pass Effly z (o -> o, x)
m) = WriterPrim o (Effly z) x -> Effly z x
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (WriterPrim o (Effly z) x -> Effly z x)
-> WriterPrim o (Effly z) x -> Effly z x
forall a b. (a -> b) -> a -> b
$ Effly z (o -> o, x) -> WriterPrim o (Effly z) x
forall (m :: * -> *) o a. m (o -> o, a) -> WriterPrim o m a
WriterPrimPass Effly z (o -> o, x)
m
{-# INLINEABLE effHandler #-}
instance Eff (WriterPrim o) m
=> Handler WriterTVarH (ListenPrim o) m where
effHandler :: ListenPrim o (Effly z) x -> Effly z x
effHandler = \case
ListenPrimTell o
o -> WriterPrim o (Effly z) () -> Effly z ()
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (WriterPrim o (Effly z) () -> Effly z ())
-> WriterPrim o (Effly z) () -> Effly z ()
forall a b. (a -> b) -> a -> b
$ o -> WriterPrim o (Effly z) ()
forall o (m :: * -> *). o -> WriterPrim o m ()
WriterPrimTell o
o
ListenPrimListen Effly z a
m -> WriterPrim o (Effly z) (o, a) -> Effly z (o, a)
forall (e :: Effect) (m :: * -> *) a.
(Member e (Derivs m), Carrier m) =>
e m a -> m a
send (WriterPrim o (Effly z) (o, a) -> Effly z (o, a))
-> WriterPrim o (Effly z) (o, a) -> Effly z (o, a)
forall a b. (a -> b) -> a -> b
$ Effly z a -> WriterPrim o (Effly z) (o, a)
forall (m :: * -> *) a o. m a -> WriterPrim o m (o, a)
WriterPrimListen Effly z a
m
{-# INLINEABLE effHandler #-}
instance ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO] m
, C.MonadMask m
)
=> PrimHandler WriterTVarH (ListenPrim o) m where
effPrimHandler :: ListenPrim o m x -> m x
effPrimHandler = \case
ListenPrimTell o
o -> o -> m ()
forall o (m :: * -> *).
(Monoid o, Effs '[Ask (o -> STM ()), Embed IO] m) =>
o -> m ()
tellTVar o
o
ListenPrimListen m a
m -> BracketToIOC m (o, a) -> m (o, a)
forall (m :: * -> *) a.
(Carrier m, MonadMask m) =>
BracketToIOC m a -> m a
bracketToIO (InterpretPrimC BracketToIOH Bracket m a -> BracketToIOC m (o, a)
forall o (m :: * -> *) a.
(Monoid o, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m) =>
m a -> m (o, a)
listenTVar (m a -> InterpretPrimC BracketToIOH Bracket m a
forall (t :: Effect) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m a
m))
{-# INLINEABLE effPrimHandler #-}
instance ( Monoid o
, Effs '[Reader (o -> STM ()), Embed IO] m
, C.MonadMask m
)
=> PrimHandler WriterTVarH (WriterPrim o) m where
effPrimHandler :: WriterPrim o m x -> m x
effPrimHandler = \case
WriterPrimTell o
o -> o -> m ()
forall o (m :: * -> *).
(Monoid o, Effs '[Ask (o -> STM ()), Embed IO] m) =>
o -> m ()
tellTVar o
o
WriterPrimListen m a
m -> BracketToIOC m (o, a) -> m (o, a)
forall (m :: * -> *) a.
(Carrier m, MonadMask m) =>
BracketToIOC m a -> m a
bracketToIO (InterpretPrimC BracketToIOH Bracket m a -> BracketToIOC m (o, a)
forall o (m :: * -> *) a.
(Monoid o, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m) =>
m a -> m (o, a)
listenTVar (m a -> InterpretPrimC BracketToIOH Bracket m a
forall (t :: Effect) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m a
m))
WriterPrimPass m (o -> o, x)
m -> BracketToIOC m x -> m x
forall (m :: * -> *) a.
(Carrier m, MonadMask m) =>
BracketToIOC m a -> m a
bracketToIO (InterpretPrimC BracketToIOH Bracket m (o -> o, x)
-> BracketToIOC m x
forall o (m :: * -> *) a.
(Monoid o, Effs '[Reader (o -> STM ()), Embed IO, Bracket] m) =>
m (o -> o, a) -> m a
passTVar (m (o -> o, x) -> InterpretPrimC BracketToIOH Bracket m (o -> o, x)
forall (t :: Effect) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (o -> o, x)
m))
{-# INLINEABLE effPrimHandler #-}
tellToIO :: forall o m a
. ( Monoid o
, Eff (Embed IO) m
)
=> InterpretReifiedC (Tell o) m a
-> m (o, a)
tellToIO :: InterpretReifiedC (Tell o) m a -> m (o, a)
tellToIO InterpretReifiedC (Tell o) m a
m = do
IORef o
ref <- IO (IORef o) -> m (IORef o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (IORef o) -> m (IORef o)) -> IO (IORef o) -> m (IORef o)
forall a b. (a -> b) -> a -> b
$ o -> IO (IORef o)
forall a. a -> IO (IORef a)
newIORef o
forall a. Monoid a => a
mempty
a
a <- IORef o -> InterpretReifiedC (Tell o) m a -> m a
forall o (m :: * -> *) a.
(Monoid o, Eff (Embed IO) m) =>
IORef o -> InterpretReifiedC (Tell o) m a -> m a
runTellIORef IORef o
ref InterpretReifiedC (Tell o) m a
m
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ IORef o -> IO o
forall a. IORef a -> IO a
readIORef IORef o
ref
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE tellToIO #-}
runTellIORef :: forall o m a
. ( Monoid o
, Eff (Embed IO) m
)
=> IORef o
-> InterpretReifiedC (Tell o) m a
-> m a
runTellIORef :: IORef o -> InterpretReifiedC (Tell o) m a -> m a
runTellIORef IORef o
ref = EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a.
(RepresentationalEff e, Carrier m) =>
EffHandler e m -> InterpretReifiedC e m a -> m a
interpret (EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> IO () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> Effly z ()) -> IO () -> Effly z ()
forall a b. (a -> b) -> a -> b
$ IORef o -> (o -> (o, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef o
ref (\o
s -> (o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o, ()))
{-# INLINE runTellIORef #-}
runTellTVar :: forall o m a
. ( Monoid o
, Eff (Embed IO) m
)
=> TVar o
-> InterpretReifiedC (Tell o) m a
-> m a
runTellTVar :: TVar o -> InterpretReifiedC (Tell o) m a -> m a
runTellTVar TVar o
tvar = EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a.
(RepresentationalEff e, Carrier m) =>
EffHandler e m -> InterpretReifiedC e m a -> m a
interpret (EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> IO () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> Effly z ()) -> IO () -> Effly z ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
tvar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
tvar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
{-# INLINE runTellTVar #-}
tellToIOSimple :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, Threaders '[ReaderThreads] m p
)
=> InterpretSimpleC (Tell o) m a
-> m (o, a)
tellToIOSimple :: InterpretSimpleC (Tell o) m a -> m (o, a)
tellToIOSimple InterpretSimpleC (Tell o) m a
m = do
IORef o
ref <- IO (IORef o) -> m (IORef o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (IORef o) -> m (IORef o)) -> IO (IORef o) -> m (IORef o)
forall a b. (a -> b) -> a -> b
$ o -> IO (IORef o)
forall a. a -> IO (IORef a)
newIORef o
forall a. Monoid a => a
mempty
a
a <- IORef o -> InterpretSimpleC (Tell o) m a -> m a
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Eff (Embed IO) m, Threaders '[ReaderThreads] m p) =>
IORef o -> InterpretSimpleC (Tell o) m a -> m a
runTellIORefSimple IORef o
ref InterpretSimpleC (Tell o) m a
m
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ IORef o -> IO o
forall a. IORef a -> IO a
readIORef IORef o
ref
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE tellToIOSimple #-}
runTellIORefSimple :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, Threaders '[ReaderThreads] m p
)
=> IORef o
-> InterpretSimpleC (Tell o) m a
-> m a
runTellIORefSimple :: IORef o -> InterpretSimpleC (Tell o) m a -> m a
runTellIORefSimple IORef o
ref = EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a (p :: [Effect]).
(RepresentationalEff e, Threaders '[ReaderThreads] m p,
Carrier m) =>
EffHandler e m -> InterpretSimpleC e m a -> m a
interpretSimple (EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> IO () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> Effly z ()) -> IO () -> Effly z ()
forall a b. (a -> b) -> a -> b
$ IORef o -> (o -> (o, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef o
ref (\o
s -> (o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o, ()))
{-# INLINE runTellIORefSimple #-}
runTellTVarSimple :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, Threaders '[ReaderThreads] m p
)
=> TVar o
-> InterpretSimpleC (Tell o) m a
-> m a
runTellTVarSimple :: TVar o -> InterpretSimpleC (Tell o) m a -> m a
runTellTVarSimple TVar o
tvar = EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a (p :: [Effect]).
(RepresentationalEff e, Threaders '[ReaderThreads] m p,
Carrier m) =>
EffHandler e m -> InterpretSimpleC e m a -> m a
interpretSimple (EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> IO () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO () -> Effly z ()) -> IO () -> Effly z ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
tvar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
tvar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
{-# INLINE runTellTVarSimple #-}
listenToIO :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, C.MonadMask m
, Threaders '[ReaderThreads] m p
)
=> ListenTVarC o m a
-> m (o, a)
listenToIO :: ListenTVarC o m a -> m (o, a)
listenToIO ListenTVarC o m a
m = do
TVar o
tvar <- IO (TVar o) -> m (TVar o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar o) -> m (TVar o)) -> IO (TVar o) -> m (TVar o)
forall a b. (a -> b) -> a -> b
$ o -> IO (TVar o)
forall a. a -> IO (TVar a)
newTVarIO o
forall a. Monoid a => a
mempty
a
a <- TVar o -> ListenTVarC o m a -> m a
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Eff (Embed IO) m, MonadMask m,
Threaders '[ReaderThreads] m p) =>
TVar o -> ListenTVarC o m a -> m a
runListenTVar TVar o
tvar ListenTVarC o m a
m
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ TVar o -> IO o
forall a. TVar a -> IO a
readTVarIO TVar o
tvar
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE listenToIO #-}
runListenTVar :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, C.MonadMask m
, Threaders '[ReaderThreads] m p
)
=> TVar o
-> ListenTVarC o m a
-> m a
runListenTVar :: TVar o -> ListenTVarC o m a -> m a
runListenTVar TVar o
tvar =
(o -> STM ()) -> ReaderC (o -> STM ()) m a -> m a
forall i (m :: * -> *) a (p :: [Effect]).
(Carrier m, Threaders '[ReaderThreads] m p) =>
i -> ReaderC i m a -> m a
runReader (\o
o -> do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
tvar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
tvar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
)
(ReaderC (o -> STM ()) m a -> m a)
-> (InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a)
-> InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a
forall h (e :: Effect) (m :: * -> *) a.
PrimHandler h e m =>
InterpretPrimC h e m a -> m a
interpretPrimViaHandler
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a
-> m a)
-> (InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a
-> InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a)
-> InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a
-> InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m) a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a
-> m a)
-> (InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a)
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a
-> m a)
-> (IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a)
-> IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m)))
a
forall (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a.
(KnownList top, KnownList new, IntroConsistent top new m) =>
IntroUnderManyC top new m a -> m a
introUnderMany
(IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
-> m a)
-> (ListenTVarC o m a
-> IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a)
-> ListenTVarC o m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# ListenTVarC o m a
-> IntroUnderManyC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
forall o (m :: * -> *) a.
ListenTVarC o m a
-> IntroC
'[Listen o, Tell o]
'[ListenPrim o, Local (o -> STM ()), Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretPrimC
WriterTVarH (ListenPrim o) (ReaderC (o -> STM ()) m))))
a
unListenTVarC
{-# INLINE runListenTVar #-}
writerToIO :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, C.MonadMask m
, Threaders '[ReaderThreads] m p
)
=> WriterTVarC o m a
-> m (o, a)
writerToIO :: WriterTVarC o m a -> m (o, a)
writerToIO WriterTVarC o m a
m = do
TVar o
tvar <- IO (TVar o) -> m (TVar o)
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO (TVar o) -> m (TVar o)) -> IO (TVar o) -> m (TVar o)
forall a b. (a -> b) -> a -> b
$ o -> IO (TVar o)
forall a. a -> IO (TVar a)
newTVarIO o
forall a. Monoid a => a
mempty
a
a <- TVar o -> WriterTVarC o m a -> m a
forall o (m :: * -> *) a (p :: [Effect]).
(Monoid o, Eff (Embed IO) m, MonadMask m,
Threaders '[ReaderThreads] m p) =>
TVar o -> WriterTVarC o m a -> m a
runWriterTVar TVar o
tvar WriterTVarC o m a
m
o
o <- IO o -> m o
forall (b :: * -> *) (m :: * -> *) a. Eff (Embed b) m => b a -> m a
embed (IO o -> m o) -> IO o -> m o
forall a b. (a -> b) -> a -> b
$ TVar o -> IO o
forall a. TVar a -> IO a
readTVarIO TVar o
tvar
(o, a) -> m (o, a)
forall (m :: * -> *) a. Monad m => a -> m a
return (o
o, a
a)
{-# INLINE writerToIO #-}
runWriterTVar :: forall o m a p
. ( Monoid o
, Eff (Embed IO) m
, C.MonadMask m
, Threaders '[ReaderThreads] m p
)
=> TVar o
-> WriterTVarC o m a
-> m a
runWriterTVar :: TVar o -> WriterTVarC o m a -> m a
runWriterTVar TVar o
tvar =
(o -> STM ()) -> ReaderC (o -> STM ()) m a -> m a
forall i (m :: * -> *) a (p :: [Effect]).
(Carrier m, Threaders '[ReaderThreads] m p) =>
i -> ReaderC i m a -> m a
runReader (\o
o -> do
o
s <- TVar o -> STM o
forall a. TVar a -> STM a
readTVar TVar o
tvar
TVar o -> o -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar o
tvar (o -> STM ()) -> o -> STM ()
forall a b. (a -> b) -> a -> b
$! o
s o -> o -> o
forall a. Semigroup a => a -> a -> a
<> o
o
)
(ReaderC (o -> STM ()) m a -> m a)
-> (InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a)
-> InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a
-> ReaderC (o -> STM ()) m a
forall h (e :: Effect) (m :: * -> *) a.
PrimHandler h e m =>
InterpretPrimC h e m a -> m a
interpretPrimViaHandler
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a
-> m a)
-> (InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a
-> InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a)
-> InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a
-> InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m) a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a
-> m a)
-> (InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a)
-> InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a
-> InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a
-> m a)
-> (InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a)
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a
-> InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a
-> m a)
-> (InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a)
-> InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a
-> InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))
a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a
-> m a)
-> (IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
-> InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a)
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
-> InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m)))))
a
forall (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a.
(KnownList top, KnownList new, IntroConsistent top new m) =>
IntroUnderManyC top new m a -> m a
introUnderMany
(IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
-> m a)
-> (WriterTVarC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a)
-> WriterTVarC o m a
-> m a
forall b a c. Coercible b a => (b -> c) -> (a -> b) -> a -> c
.# WriterTVarC o m a
-> IntroUnderManyC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
forall o (m :: * -> *) a.
WriterTVarC o m a
-> IntroC
'[Pass o, Listen o, Tell o]
'[ListenPrim o, WriterPrim o, Local (o -> STM ()),
Ask (o -> STM ())]
(InterpretC
WriterTVarH
(Pass o)
(InterpretC
WriterTVarH
(Listen o)
(InterpretC
WriterTVarH
(Tell o)
(InterpretC
WriterTVarH
(ListenPrim o)
(InterpretPrimC
WriterTVarH (WriterPrim o) (ReaderC (o -> STM ()) m))))))
a
unWriterTVarC
{-# INLINE runWriterTVar #-}
runTellAction :: forall o m a
. Carrier m
=> (o -> m ())
-> InterpretReifiedC (Tell o) m a
-> m a
runTellAction :: (o -> m ()) -> InterpretReifiedC (Tell o) m a -> m a
runTellAction o -> m ()
act = EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a.
(RepresentationalEff e, Carrier m) =>
EffHandler e m -> InterpretReifiedC e m a -> m a
interpret (EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretReifiedC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> m () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (o -> m ()
act o
o)
{-# INLINE runTellAction #-}
runTellActionSimple :: forall o m a p
. (Carrier m, Threaders '[ReaderThreads] m p)
=> (o -> m ())
-> InterpretSimpleC (Tell o) m a
-> m a
runTellActionSimple :: (o -> m ()) -> InterpretSimpleC (Tell o) m a -> m a
runTellActionSimple o -> m ()
act = EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall (e :: Effect) (m :: * -> *) a (p :: [Effect]).
(RepresentationalEff e, Threaders '[ReaderThreads] m p,
Carrier m) =>
EffHandler e m -> InterpretSimpleC e m a -> m a
interpretSimple (EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a)
-> EffHandler (Tell o) m -> InterpretSimpleC (Tell o) m a -> m a
forall a b. (a -> b) -> a -> b
$ \case
Tell o -> m () -> Effly z ()
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase (o -> m ()
act o
o)
{-# INLINE runTellActionSimple #-}
data IgnoreTellH
instance Carrier m
=> Handler IgnoreTellH (Tell o) m where
effHandler :: Tell o (Effly z) x -> Effly z x
effHandler (Tell o
_) = () -> Effly z ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# INLINEABLE effHandler #-}
type IgnoreTellC o = InterpretC IgnoreTellH (Tell o)
ignoreTell :: forall o m a
. Carrier m
=> IgnoreTellC o m a -> m a
ignoreTell :: IgnoreTellC o m a -> m a
ignoreTell = IgnoreTellC o m a -> m a
forall h (e :: Effect) (m :: * -> *) a.
Handler h e m =>
InterpretC h e m a -> m a
interpretViaHandler
{-# INLINE ignoreTell #-}