Copyright | (c) 2023 Yamada Ryo |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Data.Effect.Provider.Implicit
Description
Documentation
data ImplicitProvider' c i e (f :: Type -> Type) (a :: Type) where Source #
Constructors
WithImplicit :: i -> (forall g. (c g, e g) => (forall x. f x -> g x) -> g a) -> ImplicitProvider' c i e f a |
Instances
() => HFunctor (ImplicitProvider' c i e) Source # | |
Defined in Data.Effect.Provider.Implicit Methods hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> ImplicitProvider' c i e f :-> ImplicitProvider' c i e g # |
data ImplicitProviderKey Source #
type ImplicitProvider c i e = (##>) ImplicitProviderKey (ImplicitProvider' c i e) Source #
withImplicit :: forall (i :: Type) (c :: (Type -> Type) -> Constraint) (e :: (Type -> Type) -> Constraint) (a :: Type) f. SendSigBy ImplicitProviderKey (ImplicitProvider' c i e) f => i -> (forall (g :: Type -> Type). (c g, e g) => (forall (x :: Type). f x -> g x) -> g a) -> f a Source #
withImplicit'' :: forall key (i :: Type) (c :: (Type -> Type) -> Constraint) (e :: (Type -> Type) -> Constraint) (a :: Type) f. SendSigBy key (ImplicitProvider' c i e) f => i -> (forall (g :: Type -> Type). (c g, e g) => (forall (x :: Type). f x -> g x) -> g a) -> f a Source #
withImplicit' :: forall tag (i :: Type) (c :: (Type -> Type) -> Constraint) (e :: (Type -> Type) -> Constraint) (a :: Type) f. SendSig (TagH (ImplicitProvider' c i e) tag) f => i -> (forall (g :: Type -> Type). (c g, e g) => (forall (x :: Type). f x -> g x) -> g a) -> f a Source #
withImplicit'_ :: forall (i :: Type) (c :: (Type -> Type) -> Constraint) (e :: (Type -> Type) -> Constraint) (a :: Type) f. SendSig (ImplicitProvider' c i e) f => i -> (forall (g :: Type -> Type). (c g, e g) => (forall (x :: Type). f x -> g x) -> g a) -> f a Source #
type MonadImplicitProvider i e = ImplicitProvider Monad i e Source #
type ApplicativeImplicitProvider i e = ImplicitProvider Applicative i e Source #
(.!) :: forall c e i f a. SendSigBy ImplicitProviderKey (ImplicitProvider' c i e) f => i -> (forall g. (c g, e g) => g a) -> f a Source #
(..!) :: forall c e i f a. SendSigBy ImplicitProviderKey (ImplicitProvider' c i e) f => i -> (forall g. (c g, e g) => (f ~> g) -> g a) -> f a Source #