data-effects-0.4.2.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2023-2025 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

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

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

Instances details
FirstOrder (Input i) Source # 
Instance details

Defined in Data.Effect.Input

PolyHFunctor (Input i) Source # 
Instance details

Defined in Data.Effect.Input

HFunctor (Input i) Source # 
Instance details

Defined in Data.Effect.Input

Methods

hfmap :: (forall x. f x -> g x) -> Input i f a -> Input i g a #

type FormOf (Input i) Source # 
Instance details

Defined in Data.Effect.Input

type FormOf (Input i) = 'Polynomial
type LabelOf (Input i) Source # 
Instance details

Defined in Data.Effect.Input

type OrderOf (Input i) Source # 
Instance details

Defined in Data.Effect.Input

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.

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 Source #

Interprets the Input effect by executing the given input handler each time an input is required.

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 Source #

Interprets the Input effect by providing the given constant as input.