reader-soup-0.1.0.1: Vinyl-based reader-like monad composition

Safe HaskellNone
LanguageHaskell2010

Control.Monad.ReaderSoup

Contents

Synopsis

API for running a ReaderSoup

newtype ReaderSoup_ (record :: ((Symbol, *) -> *) -> [(Symbol, *)] -> *) ctxs a Source #

Represents a set of Reader-like monads as a one-layer Reader that can grow and host more Readers, in a way that's more generic than creating you own application stack of Reader and implementing a host of MonadXXX classes, because each of these MonadXXX classes can be implemented once and for all for the ReaderSoup type.

Constructors

ReaderSoup 

Fields

Instances
MonadBase IO (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

liftBase :: IO α -> ReaderSoup_ record ctxs α #

MonadBaseControl IO (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Associated Types

type StM (ReaderSoup_ record ctxs) a :: Type #

Methods

liftBaseWith :: (RunInBase (ReaderSoup_ record ctxs) IO -> IO a) -> ReaderSoup_ record ctxs a #

restoreM :: StM (ReaderSoup_ record ctxs) a -> ReaderSoup_ record ctxs a #

Monad (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

(>>=) :: ReaderSoup_ record ctxs a -> (a -> ReaderSoup_ record ctxs b) -> ReaderSoup_ record ctxs b #

(>>) :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b -> ReaderSoup_ record ctxs b #

return :: a -> ReaderSoup_ record ctxs a #

fail :: String -> ReaderSoup_ record ctxs a #

Functor (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

fmap :: (a -> b) -> ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b #

(<$) :: a -> ReaderSoup_ record ctxs b -> ReaderSoup_ record ctxs a #

MonadFail (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

fail :: String -> ReaderSoup_ record ctxs a #

Applicative (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

pure :: a -> ReaderSoup_ record ctxs a #

(<*>) :: ReaderSoup_ record ctxs (a -> b) -> ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b #

liftA2 :: (a -> b -> c) -> ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b -> ReaderSoup_ record ctxs c #

(*>) :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b -> ReaderSoup_ record ctxs b #

(<*) :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs b -> ReaderSoup_ record ctxs a #

Alternative (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

empty :: ReaderSoup_ record ctxs a #

(<|>) :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a #

some :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs [a] #

many :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs [a] #

MonadPlus (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

mzero :: ReaderSoup_ record ctxs a #

mplus :: ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a #

MonadIO (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

liftIO :: IO a -> ReaderSoup_ record ctxs a #

MonadThrow (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

throwM :: Exception e => e -> ReaderSoup_ record ctxs a #

MonadCatch (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

catch :: Exception e => ReaderSoup_ record ctxs a -> (e -> ReaderSoup_ record ctxs a) -> ReaderSoup_ record ctxs a #

MonadMask (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

mask :: ((forall a. ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a) -> ReaderSoup_ record ctxs b) -> ReaderSoup_ record ctxs b #

uninterruptibleMask :: ((forall a. ReaderSoup_ record ctxs a -> ReaderSoup_ record ctxs a) -> ReaderSoup_ record ctxs b) -> ReaderSoup_ record ctxs b #

generalBracket :: ReaderSoup_ record ctxs a -> (a -> ExitCase b -> ReaderSoup_ record ctxs c) -> (a -> ReaderSoup_ record ctxs b) -> ReaderSoup_ record ctxs (b, c) #

IsInSoup_ r ctxs "katip" => KatipContext (ReaderSoup_ r ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup.Katip

IsInSoup_ r ctxs "katip" => Katip (ReaderSoup_ r ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup.Katip

Methods

getLogEnv :: ReaderSoup_ r ctxs LogEnv #

localLogEnv :: (LogEnv -> LogEnv) -> ReaderSoup_ r ctxs a -> ReaderSoup_ r ctxs a #

IsInSoup_ r ctxs "resource" => MonadResource (ReaderSoup_ r ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup.Resource

Methods

liftResourceT :: ResourceT IO a -> ReaderSoup_ r ctxs a #

MonadUnliftIO (ReaderSoup_ record ctxs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Methods

askUnliftIO :: ReaderSoup_ record ctxs (UnliftIO (ReaderSoup_ record ctxs)) #

withRunInIO :: ((forall a. ReaderSoup_ record ctxs a -> IO a) -> IO b) -> ReaderSoup_ record ctxs b #

type StM (ReaderSoup_ record ctxs) a Source # 
Instance details

Defined in Control.Monad.ReaderSoup

type StM (ReaderSoup_ record ctxs) a = StM (ReaderT (record ElField ctxs) IO) a

type IsInSoup_ r ctxs l = (HasField r l ctxs ctxs (ContextFromName l) (ContextFromName l), RecElemFCtx r ElField) Source #

type IsInSoup ctxs l = IsInSoup_ ARec ctxs l Source #

class NatToInt (RLength (ContextsFromArgs args)) => ArgsForSoupConsumption args where Source #

Associated Types

type ContextsFromArgs args :: [(Symbol, *)] Source #

Instances
ArgsForSoupConsumption ([] :: [(Symbol, Type)]) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Associated Types

type ContextsFromArgs [] :: [(Symbol, Type)] Source #

(ArgsForSoupConsumption restArgs, m ~ CookedReaderSoup (ContextsFromArgs restArgs), CanRunSoupContext l t) => ArgsForSoupConsumption ((l ::: ContextRunner t m) ': restArgs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Associated Types

type ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs) :: [(Symbol, Type)] Source #

Methods

consumeSoup_ :: Rec ElField ((l ::: ContextRunner t m) ': restArgs) -> CookedReaderSoup (ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs)) a -> IO a Source #

newtype ContextRunner t m Source #

Knowing the prefered monad to run some context, gives you a way to override this monad's runner.

Constructors

ContextRunner 

Fields

Instances
(ArgsForSoupConsumption restArgs, m ~ CookedReaderSoup (ContextsFromArgs restArgs), CanRunSoupContext l t) => ArgsForSoupConsumption ((l ::: ContextRunner t m) ': restArgs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

Associated Types

type ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs) :: [(Symbol, Type)] Source #

Methods

consumeSoup_ :: Rec ElField ((l ::: ContextRunner t m) ': restArgs) -> CookedReaderSoup (ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs)) a -> IO a Source #

type ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs) Source # 
Instance details

Defined in Control.Monad.ReaderSoup

type ContextsFromArgs ((l ::: ContextRunner t m) ': restArgs) = (l ::: ContextFromName l) ': ContextsFromArgs restArgs

data Label (a :: Symbol) #

Proxy for label type

Instances
s ~ s' => IsLabel s (Label s') 
Instance details

Defined in Data.Vinyl.Derived

Methods

fromLabel :: Label s' #

Eq (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

(==) :: Label a -> Label a -> Bool #

(/=) :: Label a -> Label a -> Bool #

Show (Label a) 
Instance details

Defined in Data.Vinyl.Derived

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

(=:) :: KnownSymbol l => Label l -> v -> ElField (l ::: v) infix 8 #

Operator for creating an ElField. With the -XOverloadedLabels extension, this permits usage such as, #foo =: 23 to produce a value of type ElField ("foo" ::: Int).

type (:::) (a :: k) (b :: k1) = (,) a b #

Alias for Field spec

data Rec (a :: u -> Type) (b :: [u]) :: forall u. (u -> Type) -> [u] -> Type where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: forall u (a :: u -> Type) (b :: [u]). Rec a ([] :: [u]) 
(:&) :: forall u (a :: u -> Type) (b :: [u]) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 
Instances
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ([] :: [k]) (ss :: [k]) ([] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f :: Constraint #

Methods

rsubsetC :: (Functor g, RecSubsetFCtx Rec f) => (Rec f [] -> g (Rec f [])) -> Rec f ss -> g (Rec f ss) #

rcastC :: RecSubsetFCtx Rec f => Rec f ss -> Rec f [] #

rreplaceC :: RecSubsetFCtx Rec f => Rec f [] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f :: Constraint #

Methods

rsubsetC :: (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f :: Constraint #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) (S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f :: Constraint #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: Rec f a -> Rec f b -> Maybe (a :~: b) #

Eq (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f [] -> Rec f [] -> Bool #

(/=) :: Rec f [] -> Rec f [] -> Bool #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Ord (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f [] -> Rec f [] -> Ordering #

(<) :: Rec f [] -> Rec f [] -> Bool #

(<=) :: Rec f [] -> Rec f [] -> Bool #

(>) :: Rec f [] -> Rec f [] -> Bool #

(>=) :: Rec f [] -> Rec f [] -> Bool #

max :: Rec f [] -> Rec f [] -> Rec f [] #

min :: Rec f [] -> Rec f [] -> Rec f [] #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Generic (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f []) :: Type -> Type #

Methods

from :: Rec f [] -> Rep (Rec f []) x #

to :: Rep (Rec f []) x -> Rec f [] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Semigroup (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f [] -> Rec f [] -> Rec f [] #

sconcat :: NonEmpty (Rec f []) -> Rec f [] #

stimes :: Integral b => b -> Rec f [] -> Rec f [] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Monoid (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f [] #

mappend :: Rec f [] -> Rec f [] -> Rec f [] #

mconcat :: [Rec f []] -> Rec f [] #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Storable (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f [] -> Int #

alignment :: Rec f [] -> Int #

peekElemOff :: Ptr (Rec f []) -> Int -> IO (Rec f []) #

pokeElemOff :: Ptr (Rec f []) -> Int -> Rec f [] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f []) #

pokeByteOff :: Ptr b -> Int -> Rec f [] -> IO () #

peek :: Ptr (Rec f []) -> IO (Rec f []) #

poke :: Ptr (Rec f []) -> Rec f [] -> IO () #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ([] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

consumeSoup :: ArgsForSoupConsumption args => Rec ElField args -> ReaderSoup (ContextsFromArgs args) a -> IO a Source #

From the list of the arguments to initialize the contexts, runs the whole ReaderSoup_

API for working in a ReaderSoup and creating instances of SoupContext

type Reader r = ReaderT r Identity #

The parameterizable reader monad.

Computations are functions of a shared environment.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

newtype ReaderT r (m :: k -> Type) (a :: k) :: forall k. Type -> (k -> Type) -> k -> Type #

The reader monad transformer, which adds a read-only environment to the given monad.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

Constructors

ReaderT 

Fields

Instances
Monad m => MonadReader r (ReaderT r m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ReaderT r m r #

local :: (r -> r) -> ReaderT r m a -> ReaderT r m a #

reader :: (r -> a) -> ReaderT r m a #

MonadBase b m => MonadBase b (ReaderT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ReaderT r m α #

MonadBaseControl b m => MonadBaseControl b (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ReaderT r m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ReaderT r m) b -> b a) -> ReaderT r m a #

restoreM :: StM (ReaderT r m) a -> ReaderT r m a #

MFunctor (ReaderT r :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Morph

Methods

hoist :: Monad m => (forall a. m a -> n a) -> ReaderT r m b -> ReaderT r n b #

MMonad (ReaderT r :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Morph

Methods

embed :: Monad n => (forall a. m a -> ReaderT r n a) -> ReaderT r m b -> ReaderT r n b #

MonadTrans (ReaderT r :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

lift :: Monad m => m a -> ReaderT r m a #

MonadTransControl (ReaderT r :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (ReaderT r) a :: Type #

Methods

liftWith :: Monad m => (Run (ReaderT r) -> m a) -> ReaderT r m a #

restoreT :: Monad m => m (StT (ReaderT r) a) -> ReaderT r m a #

Monad m => Monad (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

(>>=) :: ReaderT r m a -> (a -> ReaderT r m b) -> ReaderT r m b #

(>>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

return :: a -> ReaderT r m a #

fail :: String -> ReaderT r m a #

Functor m => Functor (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

fmap :: (a -> b) -> ReaderT r m a -> ReaderT r m b #

(<$) :: a -> ReaderT r m b -> ReaderT r m a #

MonadFix m => MonadFix (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

mfix :: (a -> ReaderT r m a) -> ReaderT r m a #

MonadFail m => MonadFail (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

fail :: String -> ReaderT r m a #

Applicative m => Applicative (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

pure :: a -> ReaderT r m a #

(<*>) :: ReaderT r m (a -> b) -> ReaderT r m a -> ReaderT r m b #

liftA2 :: (a -> b -> c) -> ReaderT r m a -> ReaderT r m b -> ReaderT r m c #

(*>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

(<*) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m a #

Contravariant m => Contravariant (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

contramap :: (a -> b) -> ReaderT r m b -> ReaderT r m a #

(>$) :: b -> ReaderT r m b -> ReaderT r m a #

Representable m => Representable (ReaderT e m) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (ReaderT e m) :: Type #

Methods

tabulate :: (Rep (ReaderT e m) -> a) -> ReaderT e m a #

index :: ReaderT e m a -> Rep (ReaderT e m) -> a #

Alternative m => Alternative (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

empty :: ReaderT r m a #

(<|>) :: ReaderT r m a -> ReaderT r m a -> ReaderT r m a #

some :: ReaderT r m a -> ReaderT r m [a] #

many :: ReaderT r m a -> ReaderT r m [a] #

MonadPlus m => MonadPlus (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

mzero :: ReaderT r m a #

mplus :: ReaderT r m a -> ReaderT r m a -> ReaderT r m a #

MonadZip m => MonadZip (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

mzip :: ReaderT r m a -> ReaderT r m b -> ReaderT r m (a, b) #

mzipWith :: (a -> b -> c) -> ReaderT r m a -> ReaderT r m b -> ReaderT r m c #

munzip :: ReaderT r m (a, b) -> (ReaderT r m a, ReaderT r m b) #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

MonadCatch m => MonadCatch (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

(KatipContext m, Katip (ReaderT r m)) => KatipContext (ReaderT r m) 
Instance details

Defined in Katip.Monadic

Katip m => Katip (ReaderT s m) 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: ReaderT s m LogEnv #

localLogEnv :: (LogEnv -> LogEnv) -> ReaderT s m a -> ReaderT s m a #

PrimMonad m => PrimMonad (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ReaderT r m) :: Type #

Methods

primitive :: (State# (PrimState (ReaderT r m)) -> (#State# (PrimState (ReaderT r m)), a#)) -> ReaderT r m a #

MonadResource m => MonadResource (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftResourceT :: ResourceT IO a -> ReaderT r m a #

MonadUnliftIO m => MonadUnliftIO (ReaderT r m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

askUnliftIO :: ReaderT r m (UnliftIO (ReaderT r m)) #

withRunInIO :: ((forall a. ReaderT r m a -> IO a) -> IO b) -> ReaderT r m b #

Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t 
Instance details

Defined in Control.Lens.Zoom

Methods

zoom :: LensLike' (Zoomed (ReaderT e m) c) t s -> ReaderT e m c -> ReaderT e n c #

Monad m => Magnify (ReaderT b m) (ReaderT a m) b a 
Instance details

Defined in Control.Lens.Zoom

Methods

magnify :: (Functor (Magnified (ReaderT b m) c) -> Contravariant (Magnified (ReaderT b m) c) -> LensLike' (Magnified (ReaderT b m) c) a b) -> ReaderT b m c -> ReaderT a m c #

Wrapped (ReaderT r m a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (ReaderT r m a) :: Type #

Methods

_Wrapped' :: Iso' (ReaderT r m a) (Unwrapped (ReaderT r m a)) #

t ~ ReaderT s n b => Rewrapped (ReaderT r m a) t 
Instance details

Defined in Control.Lens.Wrapped

type StT (ReaderT r :: (Type -> Type) -> Type -> Type) a 
Instance details

Defined in Control.Monad.Trans.Control

type StT (ReaderT r :: (Type -> Type) -> Type -> Type) a = a
type Rep (ReaderT e m) 
Instance details

Defined in Data.Functor.Rep

type Rep (ReaderT e m) = (e, Rep m)
type Zoomed (ReaderT e m) 
Instance details

Defined in Control.Lens.Zoom

type Zoomed (ReaderT e m) = Zoomed m
type Magnified (ReaderT b m) 
Instance details

Defined in Control.Lens.Zoom

type Magnified (ReaderT b m) = Effect m
type PrimState (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ReaderT r m) = PrimState m
type StM (ReaderT r m) a 
Instance details

Defined in Control.Monad.Trans.Control

type StM (ReaderT r m) a = ComposeSt (ReaderT r :: (Type -> Type) -> Type -> Type) m a
type Unwrapped (ReaderT r m a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (ReaderT r m a) = r -> m a

runReader #

Arguments

:: Reader r a

A Reader to run.

-> r

An initial environment.

-> a 

Runs a Reader and extracts the final value from it. (The inverse of reader.)

mapReader :: (a -> b) -> Reader r a -> Reader r b #

Transform the value returned by a Reader.

withReader #

Arguments

:: (r' -> r)

The function to modify the environment.

-> Reader r a

Computation to run in the modified environment.

-> Reader r' a 

Execute a computation in a modified environment (a specialization of withReaderT).

mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b #

Transform the computation inside a ReaderT.

withReaderT #

Arguments

:: (r' -> r)

The function to modify the environment.

-> ReaderT r m a

Computation to run in the modified environment.

-> ReaderT r' m a 

Execute a computation in a modified environment (a more general version of local).

liftCatch :: Catch e m a -> Catch e (ReaderT r m) a #

Lift a catchE operation to the new monad.

liftCallCC :: CallCC m a b -> CallCC (ReaderT r m) a b #

Lift a callCC operation to the new monad.

asks #

Arguments

:: Monad m 
=> (r -> a)

The selector function to apply to the environment.

-> ReaderT r m a 

Retrieve a function of the current environment.

hoist :: (MFunctor t, Monad m) => (forall a. m a -> n a) -> t m b -> t n b #

Lift a monad morphism from m to n into a monad morphism from (t m) to (t n)

The first argument to hoist must be a monad morphism, even though the type system does not enforce this

class Monad m => MonadReader r (m :: Type -> Type) | m -> r where #

See examples in Control.Monad.Reader. Note, the partially applied function type (->) r is a simple reader monad. See the instance declaration below.

Minimal complete definition

(ask | reader), local

Methods

ask :: m r #

Retrieves the monad environment.

local #

Arguments

:: (r -> r)

The function to modify the environment.

-> m a

Reader to run in the modified environment.

-> m a 

Executes a computation in a modified environment.

reader #

Arguments

:: (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Instances
MonadReader r m => MonadReader r (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

ask :: ResourceT m r #

local :: (r -> r) -> ResourceT m a -> ResourceT m a #

reader :: (r -> a) -> ResourceT m a #

MonadReader r m => MonadReader r (KatipContextT m) 
Instance details

Defined in Katip.Monadic

Methods

ask :: KatipContextT m r #

local :: (r -> r) -> KatipContextT m a -> KatipContextT m a #

reader :: (r -> a) -> KatipContextT m a #

MonadReader r m => MonadReader r (NoLoggingT m) 
Instance details

Defined in Katip.Monadic

Methods

ask :: NoLoggingT m r #

local :: (r -> r) -> NoLoggingT m a -> NoLoggingT m a #

reader :: (r -> a) -> NoLoggingT m a #

MonadReader s (ReifiedGetter s) 
Instance details

Defined in Control.Lens.Reified

Methods

ask :: ReifiedGetter s s #

local :: (s -> s) -> ReifiedGetter s a -> ReifiedGetter s a #

reader :: (s -> a) -> ReifiedGetter s a #

MonadReader s (ReifiedFold s) 
Instance details

Defined in Control.Lens.Reified

Methods

ask :: ReifiedFold s s #

local :: (s -> s) -> ReifiedFold s a -> ReifiedFold s a #

reader :: (s -> a) -> ReifiedFold s a #

(Functor m, MonadReader e m) => MonadReader e (Free m) 
Instance details

Defined in Control.Monad.Free

Methods

ask :: Free m e #

local :: (e -> e) -> Free m a -> Free m a #

reader :: (e -> a) -> Free m a #

(Representable f, Rep f ~ a) => MonadReader a (Co f) 
Instance details

Defined in Data.Functor.Rep

Methods

ask :: Co f a #

local :: (a -> a) -> Co f a0 -> Co f a0 #

reader :: (a -> a0) -> Co f a0 #

MonadReader r m => MonadReader r (MaybeT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: MaybeT m r #

local :: (r -> r) -> MaybeT m a -> MaybeT m a #

reader :: (r -> a) -> MaybeT m a #

MonadReader r m => MonadReader r (ListT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ListT m r #

local :: (r -> r) -> ListT m a -> ListT m a #

reader :: (r -> a) -> ListT m a #

(Functor f, MonadReader r m) => MonadReader r (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

ask :: FreeT f m r #

local :: (r -> r) -> FreeT f m a -> FreeT f m a #

reader :: (r -> a) -> FreeT f m a #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: WriterT w m r #

local :: (r -> r) -> WriterT w m a -> WriterT w m a #

reader :: (r -> a) -> WriterT w m a #

(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: WriterT w m r #

local :: (r -> r) -> WriterT w m a -> WriterT w m a #

reader :: (r -> a) -> WriterT w m a #

MonadReader r m => MonadReader r (StateT s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: StateT s m r #

local :: (r -> r) -> StateT s m a -> StateT s m a #

reader :: (r -> a) -> StateT s m a #

MonadReader r m => MonadReader r (StateT s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: StateT s m r #

local :: (r -> r) -> StateT s m a -> StateT s m a #

reader :: (r -> a) -> StateT s m a #

MonadReader r m => MonadReader r (IdentityT m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: IdentityT m r #

local :: (r -> r) -> IdentityT m a -> IdentityT m a #

reader :: (r -> a) -> IdentityT m a #

MonadReader r m => MonadReader r (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ExceptT e m r #

local :: (r -> r) -> ExceptT e m a -> ExceptT e m a #

reader :: (r -> a) -> ExceptT e m a #

(Error e, MonadReader r m) => MonadReader r (ErrorT e m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ErrorT e m r #

local :: (r -> r) -> ErrorT e m a -> ErrorT e m a #

reader :: (r -> a) -> ErrorT e m a #

Monad m => MonadReader r (ReaderT r m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ReaderT r m r #

local :: (r -> r) -> ReaderT r m a -> ReaderT r m a #

reader :: (r -> a) -> ReaderT r m a #

MonadReader r ((->) r :: Type -> Type) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: r -> r #

local :: (r -> r) -> (r -> a) -> r -> a #

reader :: (r -> a) -> r -> a #

MonadReader r' m => MonadReader r' (ContT r m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: ContT r m r' #

local :: (r' -> r') -> ContT r m a -> ContT r m a #

reader :: (r' -> a) -> ContT r m a #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: RWST r w s m r #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a #

reader :: (r -> a) -> RWST r w s m a #

(Monad m, Monoid w) => MonadReader r (RWST r w s m) 
Instance details

Defined in Control.Monad.Reader.Class

Methods

ask :: RWST r w s m r #

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a #

reader :: (r -> a) -> RWST r w s m a #

type ReaderSoup = ReaderSoup_ ARec Source #

The type of ReaderSoup_ your application will eat

type family ContextFromName (l :: Symbol) :: * Source #

Associates the type-level label to the reader context

Instances
type ContextFromName "katip" Source # 
Instance details

Defined in Control.Monad.ReaderSoup.Katip

type ContextFromName "resource" Source # 
Instance details

Defined in Control.Monad.ReaderSoup.Resource

type ContextFromName "resource" = InternalState

class SoupContext c t | c -> t where Source #

A class for the contexts that have an associated monad transformer that can be turned into a ReaderT of this context, and the type of monad over which they can run.

Methods

toReaderT :: Monad m => t m a -> ReaderT c m a Source #

Turn this monad trans into an actual ReaderT

fromReaderT :: Monad m => ReaderT c m a -> t m a Source #

Reconstruct this monad trans from an actual ReaderT

type CanBeScoopedIn t ctxs l = CanBeScoopedIn_ ARec t ctxs l Source #

askSoup :: IsInSoup_ r ctxs l => Label l -> ReaderSoup_ r ctxs (ContextFromName l) Source #

filtering :: RecSubset ARec ctxs' ctxs (RImage ctxs' ctxs) => ReaderSoup ctxs' a -> ReaderSoup ctxs a Source #

Permits to select only a part of the whole contexts, to locally decide which part of the ReaderSoup will be exposed, and remove ambiguity.

picking :: CanBeScoopedIn_ r t ctxs l => Label l -> t IO a -> ReaderSoup_ r ctxs a Source #

Like dipping, but instead of Spoon_ runs some preferential Reader-like monad. That permits to reuse some already existing monad from an existing library (ResourceT, KatipContextT, etc.) if you cannot just use a MonadReader instance.

scooping :: CanBeScoopedIn_ r t ctxs l => Label l -> t (ReaderSoup_ r ctxs) a -> ReaderSoup_ r ctxs a Source #

Like picking, but gives you more context: instead of just running over IO, it makes the monad run over the whole soup (so instances of MonadXXX classes defined over the whole soup can still be used).

pouring :: forall l ctxs t a r. CanBeScoopedIn_ r t ctxs l => Label l -> ReaderSoup_ r ctxs a -> t (ReaderSoup_ r ctxs) a Source #

The opposite of scooping.

Low-level API

data ElField (field :: (Symbol, Type)) where #

A value with a phantom Symbol label. It is not a Haskell Functor, but it is used in many of the same places a Functor is used in vinyl.

Constructors

Field :: forall (field :: (Symbol, Type)) (s :: Symbol) t. KnownSymbol s => !t -> ElField ((,) s t) 
Instances
Eq t => Eq (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(==) :: ElField (s, t) -> ElField (s, t) -> Bool #

(/=) :: ElField (s, t) -> ElField (s, t) -> Bool #

(Floating t, KnownSymbol s) => Floating (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

pi :: ElField (s, t) #

exp :: ElField (s, t) -> ElField (s, t) #

log :: ElField (s, t) -> ElField (s, t) #

sqrt :: ElField (s, t) -> ElField (s, t) #

(**) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

logBase :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

sin :: ElField (s, t) -> ElField (s, t) #

cos :: ElField (s, t) -> ElField (s, t) #

tan :: ElField (s, t) -> ElField (s, t) #

asin :: ElField (s, t) -> ElField (s, t) #

acos :: ElField (s, t) -> ElField (s, t) #

atan :: ElField (s, t) -> ElField (s, t) #

sinh :: ElField (s, t) -> ElField (s, t) #

cosh :: ElField (s, t) -> ElField (s, t) #

tanh :: ElField (s, t) -> ElField (s, t) #

asinh :: ElField (s, t) -> ElField (s, t) #

acosh :: ElField (s, t) -> ElField (s, t) #

atanh :: ElField (s, t) -> ElField (s, t) #

log1p :: ElField (s, t) -> ElField (s, t) #

expm1 :: ElField (s, t) -> ElField (s, t) #

log1pexp :: ElField (s, t) -> ElField (s, t) #

log1mexp :: ElField (s, t) -> ElField (s, t) #

(Fractional t, KnownSymbol s) => Fractional (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(/) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

recip :: ElField (s, t) -> ElField (s, t) #

fromRational :: Rational -> ElField (s, t) #

(Num t, KnownSymbol s) => Num (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(+) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

(-) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

(*) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

negate :: ElField (s, t) -> ElField (s, t) #

abs :: ElField (s, t) -> ElField (s, t) #

signum :: ElField (s, t) -> ElField (s, t) #

fromInteger :: Integer -> ElField (s, t) #

Ord t => Ord (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

compare :: ElField (s, t) -> ElField (s, t) -> Ordering #

(<) :: ElField (s, t) -> ElField (s, t) -> Bool #

(<=) :: ElField (s, t) -> ElField (s, t) -> Bool #

(>) :: ElField (s, t) -> ElField (s, t) -> Bool #

(>=) :: ElField (s, t) -> ElField (s, t) -> Bool #

max :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

min :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

(Real t, KnownSymbol s) => Real (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

toRational :: ElField (s, t) -> Rational #

(RealFrac t, KnownSymbol s) => RealFrac (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

properFraction :: Integral b => ElField (s, t) -> (b, ElField (s, t)) #

truncate :: Integral b => ElField (s, t) -> b #

round :: Integral b => ElField (s, t) -> b #

ceiling :: Integral b => ElField (s, t) -> b #

floor :: Integral b => ElField (s, t) -> b #

(Show t, KnownSymbol s) => Show (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> ElField (s, t) -> ShowS #

show :: ElField (s, t) -> String #

showList :: [ElField (s, t)] -> ShowS #

KnownSymbol s => Generic (ElField ((,) s a)) 
Instance details

Defined in Data.Vinyl.Functor

Associated Types

type Rep (ElField (s, a)) :: Type -> Type #

Methods

from :: ElField (s, a) -> Rep (ElField (s, a)) x #

to :: Rep (ElField (s, a)) x -> ElField (s, a) #

Semigroup t => Semigroup (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(<>) :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

sconcat :: NonEmpty (ElField (s, t)) -> ElField (s, t) #

stimes :: Integral b => b -> ElField (s, t) -> ElField (s, t) #

(KnownSymbol s, Monoid t) => Monoid (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

mempty :: ElField (s, t) #

mappend :: ElField (s, t) -> ElField (s, t) -> ElField (s, t) #

mconcat :: [ElField (s, t)] -> ElField (s, t) #

(KnownSymbol s, Storable t) => Storable (ElField ((,) s t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

sizeOf :: ElField (s, t) -> Int #

alignment :: ElField (s, t) -> Int #

peekElemOff :: Ptr (ElField (s, t)) -> Int -> IO (ElField (s, t)) #

pokeElemOff :: Ptr (ElField (s, t)) -> Int -> ElField (s, t) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (ElField (s, t)) #

pokeByteOff :: Ptr b -> Int -> ElField (s, t) -> IO () #

peek :: Ptr (ElField (s, t)) -> IO (ElField (s, t)) #

poke :: Ptr (ElField (s, t)) -> ElField (s, t) -> IO () #

KnownSymbol s => IsoHKD ElField ((,) s a :: (Symbol, Type))

Work with values of type ElField '(s,a) as if they were of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD ElField (s, a) :: Type #

Methods

unHKD :: HKD ElField (s, a) -> ElField (s, a) #

toHKD :: ElField (s, a) -> HKD ElField (s, a) #

(i ~ RIndex t ts, NatToInt i, FieldOffset ElField ts t, Storable (Rec ElField ts), AllConstrained (FieldOffset ElField ts) ts) => RecElem (SRec2 ElField) (t :: (Symbol, Type)) (t :: (Symbol, Type)) (ts :: [(Symbol, Type)]) (ts :: [(Symbol, Type)]) i

Field accessors for SRec2 specialized to ElField as the functor.

Instance details

Defined in Data.Vinyl.SRec

Associated Types

type RecElemFCtx (SRec2 ElField) f :: Constraint #

Methods

rlensC :: (Functor g, RecElemFCtx (SRec2 ElField) f) => (f t -> g (f t)) -> SRec2 ElField f ts -> g (SRec2 ElField f ts) #

rgetC :: (RecElemFCtx (SRec2 ElField) f, t ~ t) => SRec2 ElField f ts -> f t #

rputC :: RecElemFCtx (SRec2 ElField) f => f t -> SRec2 ElField f ts -> SRec2 ElField f ts #

(is ~ RImage rs ss, RecSubset (Rec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) rs ss is, Storable (Rec ElField rs), Storable (Rec ElField ss), RPureConstrained (FieldOffset ElField ss) rs, RPureConstrained (FieldOffset ElField rs) rs, RFoldMap rs, RMap rs, RApply rs) => RecSubset (SRec2 ElField) (rs :: [(Symbol, Type)]) (ss :: [(Symbol, Type)]) is 
Instance details

Defined in Data.Vinyl.SRec

Associated Types

type RecSubsetFCtx (SRec2 ElField) f :: Constraint #

Methods

rsubsetC :: (Functor g, RecSubsetFCtx (SRec2 ElField) f) => (SRec2 ElField f rs -> g (SRec2 ElField f rs)) -> SRec2 ElField f ss -> g (SRec2 ElField f ss) #

rcastC :: RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f ss -> SRec2 ElField f rs #

rreplaceC :: RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f rs -> SRec2 ElField f ss -> SRec2 ElField f ss #

type Rep (ElField ((,) s a)) 
Instance details

Defined in Data.Vinyl.Functor

type Rep (ElField ((,) s a)) = C1 (MetaCons s PrefixI False) (Rec0 a)
type HKD ElField ((,) s a :: (Symbol, Type)) 
Instance details

Defined in Data.Vinyl.XRec

type HKD ElField ((,) s a :: (Symbol, Type)) = a
type RecElemFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) 
Instance details

Defined in Data.Vinyl.SRec

type RecElemFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) = f ~ ElField
type RecSubsetFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) 
Instance details

Defined in Data.Vinyl.SRec

type RecSubsetFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) = f ~ ElField

type Spoon = Spoon_ ARec Source #

cookReaderSoup :: NatToInt (RLength ctxs) => ReaderSoup ctxs a -> CookedReaderSoup ctxs a Source #

Turns a ReaderSoup_ into something than is ready to be eaten

pickTopping :: KnownSymbol l => CookedReaderSoup ((l ::: c) ': ctxs) a -> ReaderT c (CookedReaderSoup ctxs) a Source #

Extracts a ReaderT of the first context so it can be eaten

eatTopping :: KnownSymbol l => CookedReaderSoup ((l ::: c) ': ctxs) a -> c -> CookedReaderSoup ctxs a Source #

Consumes the first context in the record

finishBroth :: CookedReaderSoup '[] a -> IO a Source #

Once all contexts have been eaten, leaves only the base monad

rioToSpoon :: forall l ctxs a r. IsInSoup_ r ctxs l => ReaderT (ContextFromName l) IO a -> Spoon_ r ctxs l a Source #

If you have a code that cannot cope with any MonadReader but explicitly wants a ReaderT

spoonToReaderT :: forall l ctxs a r. (IsInSoup_ r ctxs l, KnownSymbol l) => Spoon_ r ctxs l a -> ReaderT (ContextFromName l) (ReaderSoup_ r ctxs) a Source #

Converting Spoon back to a ReaderT has to happen in the ReaderSoup because we need the global context

dipping :: Label l -> Spoon_ r ctxs l a -> ReaderSoup_ r ctxs a Source #

Brings forth one context of the whole soup, giving a MonadReader instance of just this context. This makes it possible that the same context type occurs several times in the broth, because the Label will disambiguate them.

withSpoon :: forall l ctxs t a r. CanBeScoopedIn_ r t ctxs l => t (ReaderSoup_ r ctxs) a -> Spoon_ r ctxs l a Source #

Converts an action in some ReaderT-like monad to Spoon_, this monad being determined by c. This is for code that cannot cope with any MonadReader and want some specific monad.

fromLabel :: IsLabel x a => a #