tracer-0.1: Tracing utilities for Functor/Applicative/Monad types

Copyright(c) Raphael 'kena' Poss 2014
LicenseBSD3
Maintainerkena@vodka-pomme.net
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Debug.Tracer

Contents

Description

Transformers for Functor, Applicative and Monad types that add tracing facilities for computation steps and applicative nesting.

Synopsis

General interfaces

class TracerTrans t where Source

Tracer transformers are Applicative transformers. All resulting tracers can be evaluated to trace the evaluation of the applicative effects that they encapsulate.

Methods

runTracerT :: Applicative m => String -> t m a -> m a Source

Evaluate the tracer, which forces the application and reports the progress according to the uses of trace, label and enter in the composition.

Instances

Pos p => TracerTrans (TracerT p)

Provides runTracerT.

class Applicative m => Tracer m where Source

A tracer structure internally tracks the progress of Applicative computations performed “within it”.

Methods

trace :: String -> m () Source

Emit the current progress followed by a message. The progress is emitted using the standard trace function.

label :: String -> m () Source

Label the current computation step, so that subsequent uses of trace will report the relative progress since this step.

enter :: m a -> m a Source

Mark a computation as a “call” (nesting), so that any relative progress counters are restored when the nested computation ends.

Instances

(Pos p, Applicative m) => Tracer (TracerT p m)

Provides label, trace and enter.

Position types

class Pos p Source

The class of position holders for TracerT instances. There are multiple types in this class in order with different levels of complexity, so that user programs can control the amount of overhead involved during tracing.

Minimal complete definition

pinitial, plabel, pstep, prewind, ppush, ppop, ptrace

data PosShort Source

A lightweight position type that only records the global number of steps.

Instances

data PosRel Source

A position type that extends PosShort by also tracking the relative number of steps since the beginning of the current application group.

Instances

data PosStack Source

A position type that extends PosRel by also tracking the name of labels and the stacking of application levels.

It involves more run-time overhead due to string manipulations.

Instances

Tracer transformer

data TracerT p m a Source

Equips an underlying Functor, Applicative or Monad type with tracing facilities.

Instances

Pos p => MonadTrans (TracerT p)

Provides lift, to trace actions from the underlying monad.

Pos p => TracerTrans (TracerT p)

Provides runTracerT.

(Monad m, Pos p) => Monad (TracerT p m)

Provides do-notation with tracing.

(Functor m, Pos p) => Functor (TracerT p m)

Provides fmap with tracing.

(Applicative m, Pos p) => Applicative (TracerT p m)

Provides sequencing with tracing (<*>, *> and <*).

(Pos p, Applicative m) => Tracer (TracerT p m)

Provides label, trace and enter.

Utilities

type PureTracer p a = TracerT p Identity a Source

Simple tracer for pure computations.

For this tracer, runTracerT has the following type:

runTracerT :: (Pos p) => String -> PureTracer p a -> Identity a

runTracer :: Pos p => String -> PureTracer p a -> a Source

Evaluates a traced pure computation encapsulated in a PureTracer, emit its trace and return the computation's result.

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a

Lift a computation from the argument monad to the constructed monad.

type MaybeTracer p a = TracerT p Maybe a Source

Simple tracer for Maybe computations.

For this tracer, runTracerT has the following type:

runTracerT :: (Pos p) => String -> MaybeTracer p a -> Maybe a

type IOTracer p a = TracerT p IO a Source

Simple tracer for IO computations.

For this tracer, runTracerT has the following type:

runTracerT :: (Pos p) => String -> IOTracer p a -> IO a