data-effects-0.4.0.2: 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 HaskellSafe-Inferred
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 :: Effect where Source #

A general effect representing input of values from the external world.

Constructors

Input :: Input i f i

Retrieve a value input from the external world.

Instances

Instances details
FirstOrder (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 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 :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (Input i) es) => f i Source #

Retrieve a value input from the external world.

input'' :: forall tag (i :: Type) f es ff c. (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 key (i :: Type) f es ff c. (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 (i :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Input i) es) => f i Source #

Retrieve a value input from the external world.

inputs :: forall i es ff a c. (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 ff a c. 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 ff a c. (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.