contra-tracer-0.1.0.0: Arrow and contravariant tracers
Copyright(c) Alexander Vieth 2019
LicenseApache-2.0
Maintaineraovieth@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Tracer.Arrow

Description

 
Synopsis

Documentation

data Tracer m a b where Source #

Formal representation of a tracer arrow as a Kleisli arrow over some monad, but tagged so that we know whether it has any effects which will emit a trace.

Constructors

Emitting :: Kleisli m a x -> Kleisli m x b -> Tracer m a b

An emitting part, followed by a non-emitting part. The non-emitting part is there so that later emitting parts can be tacked-on later.

Squelching :: Kleisli m a b -> Tracer m a b

No emitting. There may be side-effects, but they are assumed to be benign and will be discarded by runTracer.

Instances

Instances details
Monad m => Arrow (Tracer m) Source # 
Instance details

Defined in Control.Tracer.Arrow

Methods

arr :: (b -> c) -> Tracer m b c #

first :: Tracer m b c -> Tracer m (b, d) (c, d) #

second :: Tracer m b c -> Tracer m (d, b) (d, c) #

(***) :: Tracer m b c -> Tracer m b' c' -> Tracer m (b, b') (c, c') #

(&&&) :: Tracer m b c -> Tracer m b c' -> Tracer m b (c, c') #

Monad m => ArrowChoice (Tracer m) Source # 
Instance details

Defined in Control.Tracer.Arrow

Methods

left :: Tracer m b c -> Tracer m (Either b d) (Either c d) #

right :: Tracer m b c -> Tracer m (Either d b) (Either d c) #

(+++) :: Tracer m b c -> Tracer m b' c' -> Tracer m (Either b b') (Either c c') #

(|||) :: Tracer m b d -> Tracer m c d -> Tracer m (Either b c) d #

Monad m => Category (Tracer m :: Type -> Type -> Type) Source # 
Instance details

Defined in Control.Tracer.Arrow

Methods

id :: forall (a :: k). Tracer m a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Tracer m b c -> Tracer m a b -> Tracer m a c #

runTracer :: Monad m => Tracer m a () -> Kleisli m a () Source #

The resulting Kleisli arrow includes all of the effects required to do the emitting part.

compute :: Applicative m => (a -> b) -> Tracer m a b Source #

Pure computation in a tracer: no side effects or emits.

emit :: Applicative m => (a -> m ()) -> Tracer m a () Source #

Do an emitting effect. Contrast with effect which does not make the tracer an emitting tracer.

effect :: (a -> m b) -> Tracer m a b Source #

Do a non-emitting effect. This effect will only be run if some part of the tracer downstream emits (see emit).

squelch :: Applicative m => Tracer m a () Source #

Ignore the input and do not emit. The name is intended to lead to clear and suggestive arrow expressions.

nat :: (forall x. m x -> n x) -> Tracer m a b -> Tracer n a b Source #

Use a natural transformation to change the underlying monad.