{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module OTel.API.Context.Internal
(
ContextT(..)
, mapContextT
, attachContextValue
, getAttachedContextValue
, getAttachedContext
) where
import Control.Applicative (Alternative)
import Control.Monad (MonadPlus)
import Control.Monad.Base (MonadBase)
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
import Control.Monad.Cont (MonadCont)
import Control.Monad.Except (MonadError)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.IO.Unlift (MonadUnliftIO)
import Control.Monad.Logger (MonadLogger)
import Control.Monad.RWS.Class (MonadRWS)
import Control.Monad.Reader (MonadReader(ask, local, reader))
import Control.Monad.State (MonadState)
import Control.Monad.Trans.Class (MonadTrans(lift))
import Control.Monad.Trans.Control (MonadBaseControl, MonadTransControl)
import Control.Monad.Trans.Reader (ReaderT(..))
import Control.Monad.Trans.Resource (MonadResource)
import Control.Monad.Writer.Class (MonadWriter)
import Data.Kind (Type)
import Data.Monoid (Ap(..))
import OTel.API.Context.Core
( Context, ContextBackend, attachContextValueUsing, getAttachedContextUsing
, getAttachedContextValueUsing
)
import Prelude
#if MIN_VERSION_mtl(2,3,0)
import Control.Monad.Accum (MonadAccum)
import Control.Monad.Select (MonadSelect)
#endif
type ContextT :: Type -> (Type -> Type) -> Type -> Type
newtype ContextT c m a = ContextT
{ forall c (m :: * -> *) a. ContextT c m a -> ContextBackend c -> m a
runContextT :: ContextBackend c -> m a
} deriving
( Functor (ContextT c m)
Functor (ContextT c m) =>
(forall a. a -> ContextT c m a)
-> (forall a b.
ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b)
-> (forall a b c.
(a -> b -> c)
-> ContextT c m a -> ContextT c m b -> ContextT c m c)
-> (forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b)
-> (forall a b. ContextT c m a -> ContextT c m b -> ContextT c m a)
-> Applicative (ContextT c m)
forall a. a -> ContextT c m a
forall a b. ContextT c m a -> ContextT c m b -> ContextT c m a
forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b
forall a b.
ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b
forall a b c.
(a -> b -> c) -> ContextT c m a -> ContextT c m b -> ContextT c m c
forall c (m :: * -> *). Applicative m => Functor (ContextT c m)
forall c (m :: * -> *) a. Applicative m => a -> ContextT c m a
forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m a -> ContextT c m b -> ContextT c m a
forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m a -> ContextT c m b -> ContextT c m b
forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b
forall c (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ContextT c m a -> ContextT c m b -> ContextT c 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
$cpure :: forall c (m :: * -> *) a. Applicative m => a -> ContextT c m a
pure :: forall a. a -> ContextT c m a
$c<*> :: forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b
<*> :: forall a b.
ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b
$cliftA2 :: forall c (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ContextT c m a -> ContextT c m b -> ContextT c m c
liftA2 :: forall a b c.
(a -> b -> c) -> ContextT c m a -> ContextT c m b -> ContextT c m c
$c*> :: forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m a -> ContextT c m b -> ContextT c m b
*> :: forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b
$c<* :: forall c (m :: * -> *) a b.
Applicative m =>
ContextT c m a -> ContextT c m b -> ContextT c m a
<* :: forall a b. ContextT c m a -> ContextT c m b -> ContextT c m a
Applicative, (forall a b. (a -> b) -> ContextT c m a -> ContextT c m b)
-> (forall a b. a -> ContextT c m b -> ContextT c m a)
-> Functor (ContextT c m)
forall a b. a -> ContextT c m b -> ContextT c m a
forall a b. (a -> b) -> ContextT c m a -> ContextT c m b
forall c (m :: * -> *) a b.
Functor m =>
a -> ContextT c m b -> ContextT c m a
forall c (m :: * -> *) a b.
Functor m =>
(a -> b) -> ContextT c m a -> ContextT c m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall c (m :: * -> *) a b.
Functor m =>
(a -> b) -> ContextT c m a -> ContextT c m b
fmap :: forall a b. (a -> b) -> ContextT c m a -> ContextT c m b
$c<$ :: forall c (m :: * -> *) a b.
Functor m =>
a -> ContextT c m b -> ContextT c m a
<$ :: forall a b. a -> ContextT c m b -> ContextT c m a
Functor, Applicative (ContextT c m)
Applicative (ContextT c m) =>
(forall a b.
ContextT c m a -> (a -> ContextT c m b) -> ContextT c m b)
-> (forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b)
-> (forall a. a -> ContextT c m a)
-> Monad (ContextT c m)
forall a. a -> ContextT c m a
forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b
forall a b.
ContextT c m a -> (a -> ContextT c m b) -> ContextT c m b
forall c (m :: * -> *). Monad m => Applicative (ContextT c m)
forall c (m :: * -> *) a. Monad m => a -> ContextT c m a
forall c (m :: * -> *) a b.
Monad m =>
ContextT c m a -> ContextT c m b -> ContextT c m b
forall c (m :: * -> *) a b.
Monad m =>
ContextT c m a -> (a -> ContextT c m b) -> ContextT c 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
$c>>= :: forall c (m :: * -> *) a b.
Monad m =>
ContextT c m a -> (a -> ContextT c m b) -> ContextT c m b
>>= :: forall a b.
ContextT c m a -> (a -> ContextT c m b) -> ContextT c m b
$c>> :: forall c (m :: * -> *) a b.
Monad m =>
ContextT c m a -> ContextT c m b -> ContextT c m b
>> :: forall a b. ContextT c m a -> ContextT c m b -> ContextT c m b
$creturn :: forall c (m :: * -> *) a. Monad m => a -> ContextT c m a
return :: forall a. a -> ContextT c m a
Monad, Monad (ContextT c m)
Monad (ContextT c m) =>
(forall a. String -> ContextT c m a) -> MonadFail (ContextT c m)
forall a. String -> ContextT c m a
forall c (m :: * -> *). MonadFail m => Monad (ContextT c m)
forall c (m :: * -> *) a. MonadFail m => String -> ContextT c m a
forall (m :: * -> *).
Monad m =>
(forall a. String -> m a) -> MonadFail m
$cfail :: forall c (m :: * -> *) a. MonadFail m => String -> ContextT c m a
fail :: forall a. String -> ContextT c m a
MonadFail, Monad (ContextT c m)
Monad (ContextT c m) =>
(forall a. IO a -> ContextT c m a) -> MonadIO (ContextT c m)
forall a. IO a -> ContextT c m a
forall c (m :: * -> *). MonadIO m => Monad (ContextT c m)
forall c (m :: * -> *) a. MonadIO m => IO a -> ContextT c m a
forall (m :: * -> *).
Monad m =>
(forall a. IO a -> m a) -> MonadIO m
$cliftIO :: forall c (m :: * -> *) a. MonadIO m => IO a -> ContextT c m a
liftIO :: forall a. IO a -> ContextT c m a
MonadIO
, Applicative (ContextT c m)
Applicative (ContextT c m) =>
(forall a. ContextT c m a)
-> (forall a. ContextT c m a -> ContextT c m a -> ContextT c m a)
-> (forall a. ContextT c m a -> ContextT c m [a])
-> (forall a. ContextT c m a -> ContextT c m [a])
-> Alternative (ContextT c m)
forall a. ContextT c m a
forall a. ContextT c m a -> ContextT c m [a]
forall a. ContextT c m a -> ContextT c m a -> ContextT c m a
forall c (m :: * -> *). Alternative m => Applicative (ContextT c m)
forall c (m :: * -> *) a. Alternative m => ContextT c m a
forall c (m :: * -> *) a.
Alternative m =>
ContextT c m a -> ContextT c m [a]
forall c (m :: * -> *) a.
Alternative m =>
ContextT c m a -> ContextT c m a -> ContextT c 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
$cempty :: forall c (m :: * -> *) a. Alternative m => ContextT c m a
empty :: forall a. ContextT c m a
$c<|> :: forall c (m :: * -> *) a.
Alternative m =>
ContextT c m a -> ContextT c m a -> ContextT c m a
<|> :: forall a. ContextT c m a -> ContextT c m a -> ContextT c m a
$csome :: forall c (m :: * -> *) a.
Alternative m =>
ContextT c m a -> ContextT c m [a]
some :: forall a. ContextT c m a -> ContextT c m [a]
$cmany :: forall c (m :: * -> *) a.
Alternative m =>
ContextT c m a -> ContextT c m [a]
many :: forall a. ContextT c m a -> ContextT c m [a]
Alternative, Monad (ContextT c m)
Alternative (ContextT c m)
(Alternative (ContextT c m), Monad (ContextT c m)) =>
(forall a. ContextT c m a)
-> (forall a. ContextT c m a -> ContextT c m a -> ContextT c m a)
-> MonadPlus (ContextT c m)
forall a. ContextT c m a
forall a. ContextT c m a -> ContextT c m a -> ContextT c m a
forall c (m :: * -> *). MonadPlus m => Monad (ContextT c m)
forall c (m :: * -> *). MonadPlus m => Alternative (ContextT c m)
forall c (m :: * -> *) a. MonadPlus m => ContextT c m a
forall c (m :: * -> *) a.
MonadPlus m =>
ContextT c m a -> ContextT c m a -> ContextT c m a
forall (m :: * -> *).
(Alternative m, Monad m) =>
(forall a. m a) -> (forall a. m a -> m a -> m a) -> MonadPlus m
$cmzero :: forall c (m :: * -> *) a. MonadPlus m => ContextT c m a
mzero :: forall a. ContextT c m a
$cmplus :: forall c (m :: * -> *) a.
MonadPlus m =>
ContextT c m a -> ContextT c m a -> ContextT c m a
mplus :: forall a. ContextT c m a -> ContextT c m a -> ContextT c m a
MonadPlus
, Monad (ContextT c m)
Monad (ContextT c m) =>
(forall a b.
((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a)
-> MonadCont (ContextT c m)
forall a b.
((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a
forall c (m :: * -> *). MonadCont m => Monad (ContextT c m)
forall c (m :: * -> *) a b.
MonadCont m =>
((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a
forall (m :: * -> *).
Monad m =>
(forall a b. ((a -> m b) -> m a) -> m a) -> MonadCont m
$ccallCC :: forall c (m :: * -> *) a b.
MonadCont m =>
((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a
callCC :: forall a b.
((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a
MonadCont, MonadError e, MonadState s, MonadWriter w
#if MIN_VERSION_mtl(2,3,0)
, MonadAccum w, MonadSelect r
#endif
, MonadThrow (ContextT c m)
MonadThrow (ContextT c m) =>
(forall e a.
(HasCallStack, Exception e) =>
ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a)
-> MonadCatch (ContextT c m)
forall e a.
(HasCallStack, Exception e) =>
ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a
forall c (m :: * -> *). MonadCatch m => MonadThrow (ContextT c m)
forall c (m :: * -> *) e a.
(MonadCatch m, HasCallStack, Exception e) =>
ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a
forall (m :: * -> *).
MonadThrow m =>
(forall e a.
(HasCallStack, Exception e) =>
m a -> (e -> m a) -> m a)
-> MonadCatch m
$ccatch :: forall c (m :: * -> *) e a.
(MonadCatch m, HasCallStack, Exception e) =>
ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a
catch :: forall e a.
(HasCallStack, Exception e) =>
ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a
MonadCatch, MonadCatch (ContextT c m)
MonadCatch (ContextT c m) =>
(forall b.
HasCallStack =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b)
-> (forall b.
HasCallStack =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b)
-> (forall a b c.
HasCallStack =>
ContextT c m a
-> (a -> ExitCase b -> ContextT c m c)
-> (a -> ContextT c m b)
-> ContextT c m (b, c))
-> MonadMask (ContextT c m)
forall b.
HasCallStack =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
forall a b c.
HasCallStack =>
ContextT c m a
-> (a -> ExitCase b -> ContextT c m c)
-> (a -> ContextT c m b)
-> ContextT c m (b, c)
forall c (m :: * -> *). MonadMask m => MonadCatch (ContextT c m)
forall c (m :: * -> *) b.
(MonadMask m, HasCallStack) =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
forall c (m :: * -> *) a b c.
(MonadMask m, HasCallStack) =>
ContextT c m a
-> (a -> ExitCase b -> ContextT c m c)
-> (a -> ContextT c m b)
-> ContextT c m (b, c)
forall (m :: * -> *).
MonadCatch m =>
(forall b. HasCallStack => ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b.
HasCallStack =>
((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
HasCallStack =>
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
$cmask :: forall c (m :: * -> *) b.
(MonadMask m, HasCallStack) =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
mask :: forall b.
HasCallStack =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
$cuninterruptibleMask :: forall c (m :: * -> *) b.
(MonadMask m, HasCallStack) =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
uninterruptibleMask :: forall b.
HasCallStack =>
((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b)
-> ContextT c m b
$cgeneralBracket :: forall c (m :: * -> *) a b c.
(MonadMask m, HasCallStack) =>
ContextT c m a
-> (a -> ExitCase b -> ContextT c m c)
-> (a -> ContextT c m b)
-> ContextT c m (b, c)
generalBracket :: forall a b c.
HasCallStack =>
ContextT c m a
-> (a -> ExitCase b -> ContextT c m c)
-> (a -> ContextT c m b)
-> ContextT c m (b, c)
MonadMask, Monad (ContextT c m)
Monad (ContextT c m) =>
(forall e a. (HasCallStack, Exception e) => e -> ContextT c m a)
-> MonadThrow (ContextT c m)
forall e a. (HasCallStack, Exception e) => e -> ContextT c m a
forall c (m :: * -> *). MonadThrow m => Monad (ContextT c m)
forall c (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> ContextT c m a
forall (m :: * -> *).
Monad m =>
(forall e a. (HasCallStack, Exception e) => e -> m a)
-> MonadThrow m
$cthrowM :: forall c (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> ContextT c m a
throwM :: forall e a. (HasCallStack, Exception e) => e -> ContextT c m a
MonadThrow
, MonadIO (ContextT c m)
MonadIO (ContextT c m) =>
(forall b.
((forall a. ContextT c m a -> IO a) -> IO b) -> ContextT c m b)
-> MonadUnliftIO (ContextT c m)
forall b.
((forall a. ContextT c m a -> IO a) -> IO b) -> ContextT c m b
forall c (m :: * -> *). MonadUnliftIO m => MonadIO (ContextT c m)
forall c (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. ContextT c m a -> IO a) -> IO b) -> ContextT c m b
forall (m :: * -> *).
MonadIO m =>
(forall b. ((forall a. m a -> IO a) -> IO b) -> m b)
-> MonadUnliftIO m
$cwithRunInIO :: forall c (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. ContextT c m a -> IO a) -> IO b) -> ContextT c m b
withRunInIO :: forall b.
((forall a. ContextT c m a -> IO a) -> IO b) -> ContextT c m b
MonadUnliftIO
, MonadBase b
, MonadBaseControl b
, Monad (ContextT c m)
Monad (ContextT c m) =>
(forall msg.
ToLogStr msg =>
Loc -> LogSource -> LogLevel -> msg -> ContextT c m ())
-> MonadLogger (ContextT c m)
forall msg.
ToLogStr msg =>
Loc -> LogSource -> LogLevel -> msg -> ContextT c m ()
forall c (m :: * -> *). MonadLogger m => Monad (ContextT c m)
forall c (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> LogSource -> LogLevel -> msg -> ContextT c m ()
forall (m :: * -> *).
Monad m =>
(forall msg.
ToLogStr msg =>
Loc -> LogSource -> LogLevel -> msg -> m ())
-> MonadLogger m
$cmonadLoggerLog :: forall c (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> LogSource -> LogLevel -> msg -> ContextT c m ()
monadLoggerLog :: forall msg.
ToLogStr msg =>
Loc -> LogSource -> LogLevel -> msg -> ContextT c m ()
MonadLogger
, MonadIO (ContextT c m)
MonadIO (ContextT c m) =>
(forall a. ResourceT IO a -> ContextT c m a)
-> MonadResource (ContextT c m)
forall a. ResourceT IO a -> ContextT c m a
forall c (m :: * -> *). MonadResource m => MonadIO (ContextT c m)
forall c (m :: * -> *) a.
MonadResource m =>
ResourceT IO a -> ContextT c m a
forall (m :: * -> *).
MonadIO m =>
(forall a. ResourceT IO a -> m a) -> MonadResource m
$cliftResourceT :: forall c (m :: * -> *) a.
MonadResource m =>
ResourceT IO a -> ContextT c m a
liftResourceT :: forall a. ResourceT IO a -> ContextT c m a
MonadResource
) via (ReaderT (ContextBackend c) m)
deriving
( MonadTrans (ContextT c)
MonadTrans (ContextT c) =>
(forall (m :: * -> *) a.
Monad m =>
(Run (ContextT c) -> m a) -> ContextT c m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT (ContextT c) a) -> ContextT c m a)
-> MonadTransControl (ContextT c)
forall c. MonadTrans (ContextT c)
forall c (m :: * -> *) a.
Monad m =>
m (StT (ContextT c) a) -> ContextT c m a
forall c (m :: * -> *) a.
Monad m =>
(Run (ContextT c) -> m a) -> ContextT c m a
forall (m :: * -> *) a.
Monad m =>
m (StT (ContextT c) a) -> ContextT c m a
forall (m :: * -> *) a.
Monad m =>
(Run (ContextT c) -> m a) -> ContextT c m a
forall (t :: (* -> *) -> * -> *).
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
$cliftWith :: forall c (m :: * -> *) a.
Monad m =>
(Run (ContextT c) -> m a) -> ContextT c m a
liftWith :: forall (m :: * -> *) a.
Monad m =>
(Run (ContextT c) -> m a) -> ContextT c m a
$crestoreT :: forall c (m :: * -> *) a.
Monad m =>
m (StT (ContextT c) a) -> ContextT c m a
restoreT :: forall (m :: * -> *) a.
Monad m =>
m (StT (ContextT c) a) -> ContextT c m a
MonadTransControl
) via (ReaderT (ContextBackend c))
deriving
( NonEmpty (ContextT c m a) -> ContextT c m a
ContextT c m a -> ContextT c m a -> ContextT c m a
(ContextT c m a -> ContextT c m a -> ContextT c m a)
-> (NonEmpty (ContextT c m a) -> ContextT c m a)
-> (forall b. Integral b => b -> ContextT c m a -> ContextT c m a)
-> Semigroup (ContextT c m a)
forall b. Integral b => b -> ContextT c m a -> ContextT c m a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall c (m :: * -> *) a.
(Applicative m, Semigroup a) =>
NonEmpty (ContextT c m a) -> ContextT c m a
forall c (m :: * -> *) a.
(Applicative m, Semigroup a) =>
ContextT c m a -> ContextT c m a -> ContextT c m a
forall c (m :: * -> *) a b.
(Applicative m, Semigroup a, Integral b) =>
b -> ContextT c m a -> ContextT c m a
$c<> :: forall c (m :: * -> *) a.
(Applicative m, Semigroup a) =>
ContextT c m a -> ContextT c m a -> ContextT c m a
<> :: ContextT c m a -> ContextT c m a -> ContextT c m a
$csconcat :: forall c (m :: * -> *) a.
(Applicative m, Semigroup a) =>
NonEmpty (ContextT c m a) -> ContextT c m a
sconcat :: NonEmpty (ContextT c m a) -> ContextT c m a
$cstimes :: forall c (m :: * -> *) a b.
(Applicative m, Semigroup a, Integral b) =>
b -> ContextT c m a -> ContextT c m a
stimes :: forall b. Integral b => b -> ContextT c m a -> ContextT c m a
Semigroup, Semigroup (ContextT c m a)
ContextT c m a
Semigroup (ContextT c m a) =>
ContextT c m a
-> (ContextT c m a -> ContextT c m a -> ContextT c m a)
-> ([ContextT c m a] -> ContextT c m a)
-> Monoid (ContextT c m a)
[ContextT c m a] -> ContextT c m a
ContextT c m a -> ContextT c m a -> ContextT c m a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
Semigroup (ContextT c m a)
forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
ContextT c m a
forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
[ContextT c m a] -> ContextT c m a
forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
ContextT c m a -> ContextT c m a -> ContextT c m a
$cmempty :: forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
ContextT c m a
mempty :: ContextT c m a
$cmappend :: forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
ContextT c m a -> ContextT c m a -> ContextT c m a
mappend :: ContextT c m a -> ContextT c m a -> ContextT c m a
$cmconcat :: forall c (m :: * -> *) a.
(Applicative m, Monoid a) =>
[ContextT c m a] -> ContextT c m a
mconcat :: [ContextT c m a] -> ContextT c m a
Monoid
) via (Ap (ReaderT (ContextBackend c) m) a)
deriving via (ReaderT (ContextBackend c)) instance MonadTrans (ContextT c)
instance (MonadReader r m) => MonadReader r (ContextT c m) where
ask :: ContextT c m r
ask = m r -> ContextT c m r
forall (m :: * -> *) a. Monad m => m a -> ContextT c m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m r
forall r (m :: * -> *). MonadReader r m => m r
ask
reader :: forall a. (r -> a) -> ContextT c m a
reader = m a -> ContextT c m a
forall (m :: * -> *) a. Monad m => m a -> ContextT c m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ContextT c m a)
-> ((r -> a) -> m a) -> (r -> a) -> ContextT c m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> a) -> m a
forall a. (r -> a) -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
reader
local :: forall a. (r -> r) -> ContextT c m a -> ContextT c m a
local = (m a -> m a) -> ContextT c m a -> ContextT c m a
forall (m :: * -> *) (n :: * -> *) c a b.
(m a -> n b) -> ContextT c m a -> ContextT c n b
mapContextT ((m a -> m a) -> ContextT c m a -> ContextT c m a)
-> ((r -> r) -> m a -> m a)
-> (r -> r)
-> ContextT c m a
-> ContextT c m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> r) -> m a -> m a
forall a. (r -> r) -> m a -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local
instance (MonadRWS r w s m) => MonadRWS r w s (ContextT c m)
mapContextT
:: forall m n c a b
. (m a -> n b)
-> ContextT c m a
-> ContextT c n b
mapContextT :: forall (m :: * -> *) (n :: * -> *) c a b.
(m a -> n b) -> ContextT c m a -> ContextT c n b
mapContextT m a -> n b
f ContextT c m a
action = (ContextBackend c -> n b) -> ContextT c n b
forall c (m :: * -> *) a.
(ContextBackend c -> m a) -> ContextT c m a
ContextT ((ContextBackend c -> n b) -> ContextT c n b)
-> (ContextBackend c -> n b) -> ContextT c n b
forall a b. (a -> b) -> a -> b
$ m a -> n b
f (m a -> n b)
-> (ContextBackend c -> m a) -> ContextBackend c -> n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContextT c m a -> ContextBackend c -> m a
forall c (m :: * -> *) a. ContextT c m a -> ContextBackend c -> m a
runContextT ContextT c m a
action
attachContextValue
:: forall m a b
. (MonadIO m, MonadMask m)
=> a
-> ContextT a m b
-> ContextT a m b
attachContextValue :: forall (m :: * -> *) a b.
(MonadIO m, MonadMask m) =>
a -> ContextT a m b -> ContextT a m b
attachContextValue a
value ContextT a m b
action =
(ContextBackend a -> m b) -> ContextT a m b
forall c (m :: * -> *) a.
(ContextBackend c -> m a) -> ContextT c m a
ContextT \ContextBackend a
ctxBackend -> do
ContextBackend a -> a -> m b -> m b
forall (m :: * -> *) a b.
(MonadIO m, MonadMask m) =>
ContextBackend a -> a -> m b -> m b
attachContextValueUsing ContextBackend a
ctxBackend a
value do
ContextT a m b -> ContextBackend a -> m b
forall c (m :: * -> *) a. ContextT c m a -> ContextBackend c -> m a
runContextT ContextT a m b
action ContextBackend a
ctxBackend
getAttachedContextValue
:: forall m a
. (MonadIO m, MonadMask m)
=> ContextT a m (Maybe a)
getAttachedContextValue :: forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ContextT a m (Maybe a)
getAttachedContextValue =
(ContextBackend a -> m (Maybe a)) -> ContextT a m (Maybe a)
forall c (m :: * -> *) a.
(ContextBackend c -> m a) -> ContextT c m a
ContextT \ContextBackend a
ctxBackend -> do
ContextBackend a -> m (Maybe a)
forall (m :: * -> *) a.
(MonadIO m, MonadThrow m) =>
ContextBackend a -> m (Maybe a)
getAttachedContextValueUsing ContextBackend a
ctxBackend
getAttachedContext
:: forall m a
. (MonadIO m, MonadThrow m)
=> ContextT a m Context
getAttachedContext :: forall (m :: * -> *) a.
(MonadIO m, MonadThrow m) =>
ContextT a m Context
getAttachedContext =
(ContextBackend a -> m Context) -> ContextT a m Context
forall c (m :: * -> *) a.
(ContextBackend c -> m a) -> ContextT c m a
ContextT \ContextBackend a
ctxBackend -> do
ContextBackend a -> m Context
forall (m :: * -> *) a.
(MonadIO m, MonadThrow m) =>
ContextBackend a -> m Context
getAttachedContextUsing ContextBackend a
ctxBackend