capability-0.2.0.0: Extensional capabilities and deriving combinators

Safe HaskellNone
LanguageHaskell2010

Capability.Reader

Contents

Description

Defines a capability type class for a reader effect. A reader provides an environment, say an initialization context or a configuration. The environment held in the reader effect can be changed (with local) within the scope of a sub-computation. Contrary to the Capability.State, such a change is local, and does not persist when the local call ends.

Synopsis

Interface

class Monad m => HasReader (tag :: k) (r :: *) (m :: * -> *) | tag m -> r where Source #

Reader capability

An instance should fulfill the following laws. At this point these laws are not definitive, see https://github.com/haskell/mtl/issues/5.

k <*> ask @t = ask @t <**> k
ask @t *> m = m = m <* ask @t
local @t f (ask @t) = fmap f (ask @t)
local @t f . local @t g = local @t (g . f)
local @t f (pure x) = pure x
local @t f (m >>= \x -> k x) = local @t f m >>= \x -> local @t f (k x)
reader @t f = f <$> ask @t

Methods

ask_ :: Proxy# tag -> m r Source #

For technical reasons, this method needs an extra proxy argument. You only need it if you are defining new instances of HasReader. Otherwise, you will want to use ask. See ask for more documentation.

local_ :: Proxy# tag -> (r -> r) -> m a -> m a Source #

For technical reasons, this method needs an extra proxy argument. You only need it if you are defining new instances of HasReader. Otherwise, you will want to use local. See local for more documentation.

reader_ :: Proxy# tag -> (r -> a) -> m a Source #

For technical reasons, this method needs an extra proxy argument. You only need it if you are defining new instances of HasReader. Otherwise, you will want to use reader. See reader for more documentation.

Instances
(HasReader tag r m, MonadTransControl t, Monad (t m)) => HasReader (tag :: k) r (Lift (t m)) Source #

Lift one layer in a monad transformer stack.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> Lift (t m) r Source #

local_ :: Proxy# tag -> (r -> r) -> Lift (t m) a -> Lift (t m) a Source #

reader_ :: Proxy# tag -> (r -> a) -> Lift (t m) a Source #

MonadReader r m => HasReader (tag :: k) r (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> MonadReader m r Source #

local_ :: Proxy# tag -> (r -> r) -> MonadReader m a -> MonadReader m a Source #

reader_ :: Proxy# tag -> (r -> a) -> MonadReader m a Source #

HasState tag r m => HasReader (tag :: k) r (ReadStatePure m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> ReadStatePure m r Source #

local_ :: Proxy# tag -> (r -> r) -> ReadStatePure m a -> ReadStatePure m a Source #

reader_ :: Proxy# tag -> (r -> a) -> ReadStatePure m a Source #

(HasState tag r m, MonadMask m) => HasReader (tag :: k) r (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> ReadState m r Source #

local_ :: Proxy# tag -> (r -> r) -> ReadState m a -> ReadState m a Source #

reader_ :: Proxy# tag -> (r -> a) -> ReadState m a Source #

(Coercible from to, HasReader tag from m, forall x y. Coercible x y => Coercible (m x) (m y)) => HasReader (tag :: k) to (Coerce to m) Source #

Convert the environment using safe coercion.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> Coerce to m to Source #

local_ :: Proxy# tag -> (to -> to) -> Coerce to m a -> Coerce to m a Source #

reader_ :: Proxy# tag -> (to -> a) -> Coerce to m a Source #

HasReader oldtag r m => HasReader (newtag :: k1) r (Rename oldtag m) Source #

Rename the tag.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# newtag -> Rename oldtag m r Source #

local_ :: Proxy# newtag -> (r -> r) -> Rename oldtag m a -> Rename oldtag m a Source #

reader_ :: Proxy# newtag -> (r -> a) -> Rename oldtag m a Source #

(forall x. Coercible (m x) (t2 (t1 m) x), Monad m, HasReader tag r (t2 (t1 m))) => HasReader (tag :: k) r ((t2 :.: t1) m) Source #

Compose two accessors.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> (t2 :.: t1) m r Source #

local_ :: Proxy# tag -> (r -> r) -> (t2 :.: t1) m a -> (t2 :.: t1) m a Source #

reader_ :: Proxy# tag -> (r -> a) -> (t2 :.: t1) m a Source #

(tag ~ pos, HasPosition' pos struct v, HasReader oldtag struct m) => HasReader (tag :: Nat) v (Pos pos oldtag m) Source #

Zoom in on the field at position pos of type v in the environment struct.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> Pos pos oldtag m v Source #

local_ :: Proxy# tag -> (v -> v) -> Pos pos oldtag m a -> Pos pos oldtag m a Source #

reader_ :: Proxy# tag -> (v -> a) -> Pos pos oldtag m a Source #

(tag ~ field, HasField' field record v, HasReader oldtag record m) => HasReader (tag :: Symbol) v (Field field oldtag m) Source #

Zoom in on the record field field of type v in the environment record.

Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> Field field oldtag m v Source #

local_ :: Proxy# tag -> (v -> v) -> Field field oldtag m a -> Field field oldtag m a Source #

reader_ :: Proxy# tag -> (v -> a) -> Field field oldtag m a Source #

ask :: forall tag r m. HasReader tag r m => m r Source #

ask @tag retrieves the environment of the reader capability tag.

asks :: forall tag r m a. HasReader tag r m => (r -> a) -> m a Source #

asks @tag retrieves the image by f of the environment of the reader capability tag.

asks @tag f = f <$> ask @tag

local :: forall tag r m a. HasReader tag r m => (r -> r) -> m a -> m a Source #

local @tag f m runs the monadic action m in a modified environment e' = f e, where e is the environment of the reader capability tag. Symbolically: return e = ask @tag.

reader :: forall tag r m a. HasReader tag r m => (r -> a) -> m a Source #

reader @tag act lifts a purely environment-dependent action act to a monadic action in an arbitrary monad m with capability HasReader.

It happens to coincide with asks: reader = asks.

magnify :: forall outertag innertag t outer inner m a. (forall x. Coercible (t m x) (m x), forall m'. HasReader outertag outer m' => HasReader innertag inner (t m'), HasReader outertag outer m) => (forall m'. HasReader innertag inner m' => m' a) -> m a Source #

Execute the given reader action on a sub-component of the current context as defined by the given transformer t.

See zoom.

This function is experimental and subject to change. See https://github.com/tweag/capability/issues/46.

Strategies

newtype MonadReader (m :: * -> *) (a :: *) Source #

Derive HasReader from m's MonadReader instance.

Constructors

MonadReader (m a) 
Instances
MonadReader r m => HasReader (tag :: k) r (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> MonadReader m r Source #

local_ :: Proxy# tag -> (r -> r) -> MonadReader m a -> MonadReader m a Source #

reader_ :: Proxy# tag -> (r -> a) -> MonadReader m a Source #

Monad m => Monad (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

(>>=) :: MonadReader m a -> (a -> MonadReader m b) -> MonadReader m b #

(>>) :: MonadReader m a -> MonadReader m b -> MonadReader m b #

return :: a -> MonadReader m a #

fail :: String -> MonadReader m a #

Functor m => Functor (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

fmap :: (a -> b) -> MonadReader m a -> MonadReader m b #

(<$) :: a -> MonadReader m b -> MonadReader m a #

Applicative m => Applicative (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

pure :: a -> MonadReader m a #

(<*>) :: MonadReader m (a -> b) -> MonadReader m a -> MonadReader m b #

liftA2 :: (a -> b -> c) -> MonadReader m a -> MonadReader m b -> MonadReader m c #

(*>) :: MonadReader m a -> MonadReader m b -> MonadReader m b #

(<*) :: MonadReader m a -> MonadReader m b -> MonadReader m a #

MonadIO m => MonadIO (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

liftIO :: IO a -> MonadReader m a #

PrimMonad m => PrimMonad (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Associated Types

type PrimState (MonadReader m) :: Type #

Methods

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

type PrimState (MonadReader m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

newtype ReadStatePure (m :: * -> *) (a :: *) Source #

Convert a pure state monad into a reader monad.

Pure meaning that the monad stack does not allow catching exceptions. Otherwise, an exception occurring in the action passed to local could cause the context to remain modified outside of the call to local. E.g.

local @tag (const r') (throw MyException)
`catch` \MyException -> ask @tag

returns r' instead of the previous value.

Note, that no MonadIO instance is provided, as this would allow catching exceptions.

See ReadState.

Constructors

ReadStatePure (m a) 
Instances
HasState tag r m => HasReader (tag :: k) r (ReadStatePure m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> ReadStatePure m r Source #

local_ :: Proxy# tag -> (r -> r) -> ReadStatePure m a -> ReadStatePure m a Source #

reader_ :: Proxy# tag -> (r -> a) -> ReadStatePure m a Source #

Monad m => Monad (ReadStatePure m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

(>>=) :: ReadStatePure m a -> (a -> ReadStatePure m b) -> ReadStatePure m b #

(>>) :: ReadStatePure m a -> ReadStatePure m b -> ReadStatePure m b #

return :: a -> ReadStatePure m a #

fail :: String -> ReadStatePure m a #

Functor m => Functor (ReadStatePure m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

fmap :: (a -> b) -> ReadStatePure m a -> ReadStatePure m b #

(<$) :: a -> ReadStatePure m b -> ReadStatePure m a #

Applicative m => Applicative (ReadStatePure m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

pure :: a -> ReadStatePure m a #

(<*>) :: ReadStatePure m (a -> b) -> ReadStatePure m a -> ReadStatePure m b #

liftA2 :: (a -> b -> c) -> ReadStatePure m a -> ReadStatePure m b -> ReadStatePure m c #

(*>) :: ReadStatePure m a -> ReadStatePure m b -> ReadStatePure m b #

(<*) :: ReadStatePure m a -> ReadStatePure m b -> ReadStatePure m a #

newtype ReadState (m :: * -> *) (a :: *) Source #

Convert a state monad into a reader monad.

Use this if the monad stack allows catching exceptions.

See ReadStatePure.

Constructors

ReadState (m a) 
Instances
(HasState tag r m, MonadMask m) => HasReader (tag :: k) r (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

ask_ :: Proxy# tag -> ReadState m r Source #

local_ :: Proxy# tag -> (r -> r) -> ReadState m a -> ReadState m a Source #

reader_ :: Proxy# tag -> (r -> a) -> ReadState m a Source #

Monad m => Monad (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

(>>=) :: ReadState m a -> (a -> ReadState m b) -> ReadState m b #

(>>) :: ReadState m a -> ReadState m b -> ReadState m b #

return :: a -> ReadState m a #

fail :: String -> ReadState m a #

Functor m => Functor (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

fmap :: (a -> b) -> ReadState m a -> ReadState m b #

(<$) :: a -> ReadState m b -> ReadState m a #

Applicative m => Applicative (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

pure :: a -> ReadState m a #

(<*>) :: ReadState m (a -> b) -> ReadState m a -> ReadState m b #

liftA2 :: (a -> b -> c) -> ReadState m a -> ReadState m b -> ReadState m c #

(*>) :: ReadState m a -> ReadState m b -> ReadState m b #

(<*) :: ReadState m a -> ReadState m b -> ReadState m a #

MonadIO m => MonadIO (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Methods

liftIO :: IO a -> ReadState m a #

PrimMonad m => PrimMonad (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Associated Types

type PrimState (ReadState m) :: Type #

Methods

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

type PrimState (ReadState m) Source # 
Instance details

Defined in Capability.Reader.Internal.Strategies

Modifiers