Copyright | (c) Raphael 'kena' Poss 2014 |
---|---|
License | BSD3 |
Maintainer | kena@vodka-pomme.net |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Transformers for Functor
, Applicative
and Monad
types that add
tracing facilities for computation steps and applicative nesting.
- class TracerTrans t where
- runTracerT :: Applicative m => String -> t m a -> m a
- class Applicative m => Tracer m where
- class Pos p
- data PosShort
- data PosRel
- data PosStack
- data TracerT p m a
- type PureTracer p a = TracerT p Identity a
- runTracer :: Pos p => String -> PureTracer p a -> a
- lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
- type MaybeTracer p a = TracerT p Maybe a
- type IOTracer p a = TracerT p IO a
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.
runTracerT :: Applicative m => String -> t m a -> m a Source
Pos p => TracerTrans (TracerT p) | Provides |
class Applicative m => Tracer m where Source
A tracer structure internally tracks the progress of Applicative
computations performed “within it”.
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.
Mark a computation as a “call” (nesting), so that any relative progress counters are restored when the nested computation ends.
Position types
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.
pinitial, plabel, pstep, prewind, ppush, ppop, ptrace
A lightweight position type that only records the global number of steps.
A position type that extends PosShort
by also tracking
the relative number of steps
since the beginning of the current application group.
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.
Tracer transformer
Equips an underlying Functor
, Applicative
or Monad
type
with tracing facilities.
Pos p => MonadTrans (TracerT p) | Provides |
Pos p => TracerTrans (TracerT p) | Provides |
(Monad m, Pos p) => Monad (TracerT p m) | Provides do-notation with tracing. |
(Functor m, Pos p) => Functor (TracerT p m) | Provides |
(Applicative m, Pos p) => Applicative (TracerT p m) | |
(Pos p, Applicative m) => Tracer (TracerT p m) |
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