{-# LANGUAGE AllowAmbiguousTypes #-}
module Data.Effect.Output where
data Output o :: Effect where
Output :: o -> Output o f ()
makeEffectF ''Output
runOutputEff
:: forall o es ff a c
. (Free c ff)
=> (o -> Eff ff es ())
-> Eff ff (Output o ': es) a
-> Eff ff es a
runOutputEff :: forall o (es :: [Effect]) (ff :: Effect) a
(c :: (* -> *) -> Constraint).
Free c ff =>
(o -> Eff ff es ()) -> Eff ff (Output o : es) a -> Eff ff es a
runOutputEff o -> Eff ff es ()
f = (Output o ~~> Eff ff es) -> Eff ff (Output o : es) a -> Eff ff es a
forall (e :: Effect) (es :: [Effect]) (ff :: Effect) a
(c :: (* -> *) -> Constraint).
(KnownOrder e, Free c ff) =>
(e ~~> Eff ff es) -> Eff ff (e : es) a -> Eff ff es a
interpret \(Output o
o) -> o -> Eff ff es ()
f o
o
{-# INLINE runOutputEff #-}
ignoreOutput
:: forall o es ff a c
. (Applicative (Eff ff es), Free c ff)
=> Eff ff (Output o ': es) a
-> Eff ff es a
ignoreOutput :: forall o (es :: [Effect]) (ff :: Effect) a
(c :: (* -> *) -> Constraint).
(Applicative (Eff ff es), Free c ff) =>
Eff ff (Output o : es) a -> Eff ff es a
ignoreOutput = (o -> Eff ff es ()) -> Eff ff (Output o : es) a -> Eff ff es a
forall o (es :: [Effect]) (ff :: Effect) a
(c :: (* -> *) -> Constraint).
Free c ff =>
(o -> Eff ff es ()) -> Eff ff (Output o : es) a -> Eff ff es a
runOutputEff ((o -> Eff ff es ()) -> Eff ff (Output o : es) a -> Eff ff es a)
-> (o -> Eff ff es ()) -> Eff ff (Output o : es) a -> Eff ff es a
forall a b. (a -> b) -> a -> b
$ Eff ff es () -> o -> Eff ff es ()
forall a b. a -> b -> a
const (Eff ff es () -> o -> Eff ff es ())
-> Eff ff es () -> o -> Eff ff es ()
forall a b. (a -> b) -> a -> b
$ () -> Eff ff es ()
forall a. a -> Eff ff es a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# INLINE ignoreOutput #-}