in-other-words-0.2.1.1: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Trace

Synopsis

Effects

data Trace :: Effect where Source #

An effect for debugging by printing/logging strings.

Constructors

Trace :: String -> Trace m () 

Actions

trace :: Eff Trace m => String -> m () Source #

Log the provided string

traceShow :: (Show a, Eff Trace m) => a -> m () Source #

show the provided item and log it.

Interpretations

runTraceList :: forall m a p. (Threaders '[WriterThreads] m p, Carrier m) => TraceListC m a -> m ([String], a) Source #

Run a Trace effect purely by accumulating all traced strings into a list.

runTraceListIO :: Eff (Embed IO) m => InterpretReifiedC Trace m a -> m ([String], a) Source #

Run a Trace effect by accumulating all traced strings into a list using atomic operations in IO.

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes runTraceListIO very difficult to use partially applied. In particular, it can't be composed using ..

If performance is secondary, consider using the slower runTraceListIOSimple, which doesn't have a higher-rank type.

runTracePrinting :: Eff (Embed IO) m => TracePrintingC m a -> m a Source #

Run a Trace effect by printing each traced string to stderr.

runTraceToHandle :: Eff (Embed IO) m => Handle -> InterpretReifiedC Trace m a -> m a Source #

Run Trace effect by providing each traced string to the provided Handle.

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes runTraceToHandle very difficult to use partially applied. In particular, it can't be composed using ..

If performance is secondary, consider using the slower runTraceToHandleSimple, which doesn't have a higher-rank type.

ignoreTrace :: Carrier m => IgnoreTraceC m a -> m a Source #

Run a Trace effect by ignoring it, doing no logging at all.

traceIntoTell :: HeadEff (Tell String) m => TraceIntoTellC m a -> m a Source #

Rewrite a Trace effect into a Tell String effect on top of the effect stack.

Simple variants of interprations

runTraceListIOSimple :: forall m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => InterpretSimpleC Trace m a -> m ([String], a) Source #

Run a Trace effect by accumulating all traced strings into a list using atomic operations in IO.

This is a less performant version of runTraceListIOSimple that doesn't have a higher-rank type, making it much easier to use partially applied.

runTraceToHandleSimple :: forall m a p. (Eff (Embed IO) m, Threaders '[ReaderThreads] m p) => Handle -> InterpretSimpleC Trace m a -> m a Source #

Run Trace effect by providing each traced string to the provided Handle.

This is a less performant version of runTraceToHandle that doesn't have a higher-rank type, making it much easier to use partially applied.

Threading constraints

class (forall o. Monoid o => Threads (WriterT o) p) => WriterThreads p Source #

WriterThreads accepts the following primitive effects:

Instances

Instances details
(forall o. Monoid o => Threads (WriterT o) p) => WriterThreads p Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Carriers

data TraceListC m a Source #

Instances

Instances details
MonadTrans TraceListC Source # 
Instance details

Defined in Control.Effect.Trace

Methods

lift :: Monad m => m a -> TraceListC m a #

MonadTransControl TraceListC Source # 
Instance details

Defined in Control.Effect.Trace

Associated Types

type StT TraceListC a #

Methods

liftWith :: Monad m => (Run TraceListC -> m a) -> TraceListC m a #

restoreT :: Monad m => m (StT TraceListC a) -> TraceListC m a #

MonadBase b m => MonadBase b (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

liftBase :: b α -> TraceListC m α #

MonadBaseControl b m => MonadBaseControl b (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Associated Types

type StM (TraceListC m) a #

Methods

liftBaseWith :: (RunInBase (TraceListC m) b -> b a) -> TraceListC m a #

restoreM :: StM (TraceListC m) a -> TraceListC m a #

Monad m => Monad (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

(>>=) :: TraceListC m a -> (a -> TraceListC m b) -> TraceListC m b #

(>>) :: TraceListC m a -> TraceListC m b -> TraceListC m b #

return :: a -> TraceListC m a #

Functor m => Functor (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

fmap :: (a -> b) -> TraceListC m a -> TraceListC m b #

(<$) :: a -> TraceListC m b -> TraceListC m a #

MonadFix m => MonadFix (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

mfix :: (a -> TraceListC m a) -> TraceListC m a #

MonadFail m => MonadFail (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

fail :: String -> TraceListC m a #

Monad m => Applicative (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

pure :: a -> TraceListC m a #

(<*>) :: TraceListC m (a -> b) -> TraceListC m a -> TraceListC m b #

liftA2 :: (a -> b -> c) -> TraceListC m a -> TraceListC m b -> TraceListC m c #

(*>) :: TraceListC m a -> TraceListC m b -> TraceListC m b #

(<*) :: TraceListC m a -> TraceListC m b -> TraceListC m a #

MonadIO m => MonadIO (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

liftIO :: IO a -> TraceListC m a #

MonadPlus m => Alternative (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

empty :: TraceListC m a #

(<|>) :: TraceListC m a -> TraceListC m a -> TraceListC m a #

some :: TraceListC m a -> TraceListC m [a] #

many :: TraceListC m a -> TraceListC m [a] #

MonadPlus m => MonadPlus (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

mzero :: TraceListC m a #

mplus :: TraceListC m a -> TraceListC m a -> TraceListC m a #

MonadThrow m => MonadThrow (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

throwM :: Exception e => e -> TraceListC m a #

MonadCatch m => MonadCatch (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

catch :: Exception e => TraceListC m a -> (e -> TraceListC m a) -> TraceListC m a #

MonadMask m => MonadMask (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

mask :: ((forall a. TraceListC m a -> TraceListC m a) -> TraceListC m b) -> TraceListC m b #

uninterruptibleMask :: ((forall a. TraceListC m a -> TraceListC m a) -> TraceListC m b) -> TraceListC m b #

generalBracket :: TraceListC m a -> (a -> ExitCase b -> TraceListC m c) -> (a -> TraceListC m b) -> TraceListC m (b, c) #

(Carrier m, Threads (WriterT (Dual [String])) (Prims m)) => Carrier (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Associated Types

type Derivs (TraceListC m) :: [Effect] Source #

type Prims (TraceListC m) :: [Effect] Source #

type StT TraceListC a Source # 
Instance details

Defined in Control.Effect.Trace

type Derivs (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

type Prims (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

type Prims (TraceListC m)
type StM (TraceListC m) a Source # 
Instance details

Defined in Control.Effect.Trace

type StM (TraceListC m) a

type TracePrintingC = InterpretC TracePrintingH Trace Source #

type IgnoreTraceC = InterpretC IgnoreTraceH Trace Source #