Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class (Monad m, HasSource tag r m) => HasReader (tag :: k) (r :: *) (m :: * -> *) | tag m -> r where
- ask :: forall tag r m. HasReader tag r m => m r
- asks :: forall tag r m a. HasReader tag r m => (r -> a) -> m a
- local :: forall tag r m a. HasReader tag r m => (r -> r) -> m a -> m a
- reader :: forall tag r m a. HasReader tag r m => (r -> a) -> m a
- magnify :: forall innertag t (cs :: [Capability]) inner m a. (forall x. Coercible (t m x) (m x), HasReader innertag inner (t m), All cs m) => (forall m'. All (HasReader innertag inner ': cs) m' => m' a) -> m a
- type HasReader' (tag :: k) = HasReader tag (TypeOf k tag)
- type family TypeOf k (s :: k) :: *
- newtype MonadReader (m :: * -> *) (a :: *) = MonadReader (m a)
- newtype ReadStatePure (m :: * -> *) (a :: *) = ReadStatePure (m a)
- newtype ReadState (m :: * -> *) (a :: *) = ReadState (m a)
- module Capability.Accessors
Relational capability
class (Monad m, HasSource tag r 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
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. |
(HasState tag r m, MonadMask m) => HasReader (tag :: k) r (ReadState m) Source # | |
HasState tag r m => HasReader (tag :: k) r (ReadStatePure m) Source # | |
Defined in Capability.Reader.Internal.Strategies local_ :: Proxy# tag -> (r -> r) -> ReadStatePure m a -> ReadStatePure m a Source # reader_ :: Proxy# tag -> (r -> a) -> ReadStatePure m a Source # | |
MonadReader r m => HasReader (tag :: k) r (MonadReader m) Source # | |
Defined in Capability.Reader.Internal.Strategies local_ :: Proxy# tag -> (r -> r) -> MonadReader m a -> MonadReader m a Source # reader_ :: Proxy# tag -> (r -> a) -> MonadReader 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. |
HasReader oldtag r m => HasReader (newtag :: k1) r (Rename oldtag m) Source # | Rename the tag. |
(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. |
(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 |
(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 |
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 innertag t (cs :: [Capability]) inner m a. (forall x. Coercible (t m x) (m x), HasReader innertag inner (t m), All cs m) => (forall m'. All (HasReader innertag inner ': cs) 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
, retaining arbitrary capabilities
listed in cs
.
See the similar zoom
function for more details and
examples.
This function is experimental and subject to change. See https://github.com/tweag/capability/issues/46.
Functional capability
type HasReader' (tag :: k) = HasReader tag (TypeOf k tag) Source #
type family TypeOf k (s :: k) :: * Source #
Type family associating a tag to the corresponding type. It is intended to simplify constraint declarations, by removing the need to redundantly specify the type associated to a tag.
It is poly-kinded, which allows users to define their own kind of tags.
Standard haskell types can also be used as tags by specifying the *
kind
when defining the type family instance.
Defining TypeOf
instances for Symbol
s (typelevel string
literals) is discouraged. Since symbols all belong to the same global
namespace, such instances could conflict with others defined in external
libraries. More generally, as for typeclasses, TypeOf
instances should
always be defined in the same module as the tag type to prevent issues due to
orphan instances.
Example:
import Capability.Reader data Foo data Bar type instance TypeOf * Foo = Int type instance TypeOf * Bar = String -- Same as: foo :: HasReader Foo Int M => … foo :: HasReader' Foo m => … foo = …
Strategies
newtype MonadReader (m :: * -> *) (a :: *) Source #
Derive HasSource
from m
's MonadReader
instance.
MonadReader (m a) |
Instances
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
.
ReadStatePure (m a) |
Instances
newtype ReadState (m :: * -> *) (a :: *) Source #
Convert a state monad into a reader monad.
Use this if the monad stack allows catching exceptions.
See ReadStatePure
.
ReadState (m a) |
Instances
(HasState tag r m, MonadMask m) => HasSource (tag :: k) r (ReadState m) Source # | |
(HasState tag r m, MonadMask m) => HasReader (tag :: k) r (ReadState m) Source # | |
Monad m => Monad (ReadState m) Source # | |
Functor m => Functor (ReadState m) Source # | |
Applicative m => Applicative (ReadState m) Source # | |
Defined in Capability.Source.Internal.Strategies | |
MonadIO m => MonadIO (ReadState m) Source # | |
Defined in Capability.Source.Internal.Strategies | |
PrimMonad m => PrimMonad (ReadState m) Source # | |
type PrimState (ReadState m) Source # | |
Defined in Capability.Source.Internal.Strategies |
Modifiers
module Capability.Accessors