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.Output

Description

This module provides the Output effect, comes from Polysemy.Output in the polysemy package.

Realizes output of values to the external world.

Synopsis

Documentation

data Output o (a :: Type -> Type) b where Source #

A general effect representing output of values to the external world.

Constructors

Output :: forall o (a :: Type -> Type). o -> Output o a ()

Output a value to the external world.

Instances

Instances details
FirstOrder (Output o) Source # 
Instance details

Defined in Data.Effect.Output

PolyHFunctor (Output o) Source # 
Instance details

Defined in Data.Effect.Output

HFunctor (Output o) Source # 
Instance details

Defined in Data.Effect.Output

Methods

hfmap :: (forall x. f x -> g x) -> Output o f a -> Output o g a #

type FormOf (Output o) Source # 
Instance details

Defined in Data.Effect.Output

type LabelOf (Output o) Source # 
Instance details

Defined in Data.Effect.Output

type OrderOf (Output o) Source # 
Instance details

Defined in Data.Effect.Output

output :: forall o f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Output o :> es) => o -> f () Source #

Output a value to the external world.

output' :: forall {k} (key :: k) o f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Output o) es) => o -> f () Source #

Output a value to the external world.

output'' :: forall {k} (tag :: k) o f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Output o) :> es) => o -> f () Source #

Output a value to the external world.

output'_ :: forall o f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Output o) es) => o -> f () Source #

Output a value to the external world.

runOutputEff :: forall o (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). Free c ff => (o -> Eff ff es ()) -> Eff ff (Output o ': es) a -> Eff ff es a Source #

Interprets the Output effect using the given output handler.

ignoreOutput :: forall o (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Applicative (Eff ff es), Free c ff) => Eff ff (Output o ': es) a -> Eff ff es a Source #

Interprets the Output effect by ignoring the outputs.