Copyright | (c) 2023-2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Input
Description
This module provides the Input
effect, comes
from Polysemy.Input
in the polysemy
package.
Realizes input of values from the external world.
Synopsis
- data Input i (a :: Type -> Type) b where
- data InputLabel
- input :: forall i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Input i :> es) => f i
- input' :: forall {k} (key :: k) i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Input i) es) => f i
- input'' :: forall {k} (tag :: k) i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Input i) :> es) => f i
- input'_ :: forall i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Input i) es) => f i
- inputs :: forall i (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Input i :> es, Functor (Eff ff es), Free c ff) => (i -> a) -> Eff ff es a
- runInputEff :: forall i (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff es i -> Eff ff (Input i ': es) a -> Eff ff es a
- runInputConst :: forall i (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => i -> Eff ff (Input i ': es) a -> Eff ff es a
Documentation
data Input i (a :: Type -> Type) b where Source #
A general effect representing input of values from the external world.
Constructors
Input :: forall i (a :: Type -> Type). Input i a i | Retrieve a value input from the external world. |
Instances
FirstOrder (Input i) Source # | |
Defined in Data.Effect.Input | |
PolyHFunctor (Input i) Source # | |
Defined in Data.Effect.Input | |
HFunctor (Input i) Source # | |
Defined in Data.Effect.Input | |
type FormOf (Input i) Source # | |
Defined in Data.Effect.Input | |
type LabelOf (Input i) Source # | |
Defined in Data.Effect.Input | |
type OrderOf (Input i) Source # | |
Defined in Data.Effect.Input |
data InputLabel Source #
input :: forall i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Input i :> es) => f i Source #
Retrieve a value input from the external world.
input' :: forall {k} (key :: k) i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Input i) es) => f i Source #
Retrieve a value input from the external world.
input'' :: forall {k} (tag :: k) i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Input i) :> es) => f i Source #
Retrieve a value input from the external world.
input'_ :: forall i f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Input i) es) => f i Source #
Retrieve a value input from the external world.
inputs :: forall i (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Input i :> es, Functor (Eff ff es), Free c ff) => (i -> a) -> Eff ff es a Source #
Returns the value obtained by transforming the input value using the given function.