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

Data.Effect.Log

Description

Interpreters for the co-log ecosystem.

The interface is similar to co-log-polysemy.

Documentation

data Log msg (a :: Type -> Type) b where Source #

Constructors

Log :: forall msg (a :: Type -> Type). msg -> Log msg a () 

Instances

Instances details
FirstOrder (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

PolyHFunctor (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

HFunctor (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

Methods

hfmap :: (forall x. f x -> g x) -> Log msg f a -> Log msg g a #

type FormOf (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

type FormOf (Log msg) = 'Polynomial
type LabelOf (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

type LabelOf (Log msg) = LogLabel
type OrderOf (Log msg) Source # 
Instance details

Defined in Data.Effect.Log

type OrderOf (Log msg) = 'FirstOrder

log :: forall msg f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Log msg :> es) => msg -> f () Source #

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

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

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

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

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

runLogAction :: forall msg a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => LogAction (Eff ff es) msg -> Eff ff (Log msg ': es) a -> Eff ff es a Source #

runLogActionEmbed :: forall msg (f :: Type -> Type) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => LogAction f msg -> Eff ff (Log msg ': es) a -> Eff ff es a Source #