Copyright | (c) Dennis Gosnell 2017 |
---|---|
License | BSD-style (see LICENSE file) |
Maintainer | cdep.illabout@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
This module contains the same functionality with Prelude's Debug.Trace module, with pretty printing the debug strings.
Warning: This module also shares the same unsafety of Debug.Trace module.
Synopsis
- pTrace :: String -> a -> a
- pTraceId :: String -> String
- pTraceShow :: Show a => a -> b -> b
- pTraceShowId :: Show a => a -> a
- pTraceIO :: String -> IO ()
- pTraceM :: Applicative f => String -> f ()
- pTraceShowM :: (Show a, Applicative f) => a -> f ()
- pTraceStack :: String -> a -> a
- pTraceEvent :: String -> a -> a
- pTraceEventIO :: String -> IO ()
- pTraceMarker :: String -> a -> a
- pTraceMarkerIO :: String -> IO ()
- pTraceWith :: (a -> String) -> a -> a
- pTraceShowWith :: Show b => (a -> b) -> a -> a
- pTraceForceColor :: String -> a -> a
- pTraceIdForceColor :: String -> String
- pTraceShowForceColor :: Show a => a -> b -> b
- pTraceShowIdForceColor :: Show a => a -> a
- pTraceMForceColor :: Applicative f => String -> f ()
- pTraceShowMForceColor :: (Show a, Applicative f) => a -> f ()
- pTraceStackForceColor :: String -> a -> a
- pTraceEventForceColor :: String -> a -> a
- pTraceEventIOForceColor :: String -> IO ()
- pTraceMarkerForceColor :: String -> a -> a
- pTraceMarkerIOForceColor :: String -> IO ()
- pTraceIOForceColor :: String -> IO ()
- pTraceNoColor :: String -> a -> a
- pTraceIdNoColor :: String -> String
- pTraceShowNoColor :: Show a => a -> b -> b
- pTraceShowIdNoColor :: Show a => a -> a
- pTraceMNoColor :: Applicative f => String -> f ()
- pTraceShowMNoColor :: (Show a, Applicative f) => a -> f ()
- pTraceStackNoColor :: String -> a -> a
- pTraceEventNoColor :: String -> a -> a
- pTraceEventIONoColor :: String -> IO ()
- pTraceMarkerNoColor :: String -> a -> a
- pTraceMarkerIONoColor :: String -> IO ()
- pTraceIONoColor :: String -> IO ()
- pTraceOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
- pTraceIdOpt :: CheckColorTty -> OutputOptions -> String -> String
- pTraceShowOpt :: Show a => CheckColorTty -> OutputOptions -> a -> b -> b
- pTraceShowIdOpt :: Show a => CheckColorTty -> OutputOptions -> a -> a
- pTraceOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
- pTraceOptM :: Applicative f => CheckColorTty -> OutputOptions -> String -> f ()
- pTraceShowOptM :: (Show a, Applicative f) => CheckColorTty -> OutputOptions -> a -> f ()
- pTraceStackOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
- pTraceEventOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
- pTraceEventOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
- pTraceMarkerOpt :: CheckColorTty -> OutputOptions -> String -> a -> a
- pTraceMarkerOptIO :: CheckColorTty -> OutputOptions -> String -> IO ()
Trace with color on dark background
pTrace :: String -> a -> a Source #
Warning: pTrace
remains in code
The pTrace
function pretty prints the trace message given as its first
argument, before returning the second argument as its result.
For example, this returns the value of f x
but first outputs the message.
pTrace ("calling f with x = " ++ show x) (f x)
The pTrace
function should only be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
that it is a pure function but it has the side effect of outputting the
trace message.
Since: 2.0.1.0
pTraceShow :: Show a => a -> b -> b Source #
Warning: pTraceShow
remains in code
Like pTrace
, but uses show
on the argument to convert it to a String
.
This makes it convenient for printing the values of interesting variables or
expressions inside a function. For example here we print the value of the
variables x
and z
:
f x y = pTraceShow (x, z) $ result where z = ... ...
Since: 2.0.1.0
pTraceShowId :: Show a => a -> a Source #
Warning: pTraceShowId
remains in code
Like pTraceShow
but returns the shown value instead of a third value.
Since: 2.0.1.0
pTraceM :: Applicative f => String -> f () Source #
Warning: pTraceM
remains in code
Like pTrace
but returning unit in an arbitrary Applicative
context. Allows
for convenient use in do-notation.
Note that the application of pTraceM
is not an action in the Applicative
context, as pTraceIO
is in the IO
type. While the fresh bindings in the
following example will force the traceM
expressions to be reduced every time
the do
-block is executed, traceM "not crashed"
would only be reduced once,
and the message would only be printed once. If your monad is in MonadIO
,
liftIO . pTraceIO
may be a better option.
... = do x <- ... pTraceM $ "x: " ++ show x y <- ... pTraceM $ "y: " ++ show y
Since: 2.0.1.0
pTraceShowM :: (Show a, Applicative f) => a -> f () Source #
Warning: pTraceShowM
remains in code
Like pTraceM
, but uses show
on the argument to convert it to a String
.
... = do x <- ... pTraceShowM $ x y <- ... pTraceShowM $ x + y
Since: 2.0.1.0
pTraceStack :: String -> a -> a Source #
Warning: pTraceStack
remains in code
like pTrace
, but additionally prints a call stack if one is
available.
In the current GHC implementation, the call stack is only
available if the program was compiled with -prof
; otherwise
pTraceStack
behaves exactly like pTrace
. Entries in the call
stack correspond to SCC
annotations, so it is a good idea to use
-fprof-auto
or -fprof-auto-calls
to add SCC annotations automatically.
Since: 2.0.1.0
pTraceEvent :: String -> a -> a Source #
Warning: pTraceEvent
remains in code
The pTraceEvent
function behaves like trace
with the difference that
the message is emitted to the eventlog, if eventlog profiling is available
and enabled at runtime.
It is suitable for use in pure code. In an IO context use pTraceEventIO
instead.
Note that when using GHC's SMP runtime, it is possible (but rare) to get
duplicate events emitted if two CPUs simultaneously evaluate the same thunk
that uses pTraceEvent
.
Since: 2.0.1.0
pTraceEventIO :: String -> IO () Source #
Warning: pTraceEventIO
remains in code
The pTraceEventIO
function emits a message to the eventlog, if eventlog
profiling is available and enabled at runtime.
Compared to pTraceEvent
, pTraceEventIO
sequences the event with respect to
other IO actions.
Since: 2.0.1.0
pTraceMarker :: String -> a -> a Source #
Warning: pTraceMarker
remains in code
The pTraceMarker
function emits a marker to the eventlog, if eventlog
profiling is available and enabled at runtime. The String
is the name of
the marker. The name is just used in the profiling tools to help you keep
clear which marker is which.
This function is suitable for use in pure code. In an IO context use
pTraceMarkerIO
instead.
Note that when using GHC's SMP runtime, it is possible (but rare) to get
duplicate events emitted if two CPUs simultaneously evaluate the same thunk
that uses pTraceMarker
.
Since: 2.0.1.0
pTraceMarkerIO :: String -> IO () Source #
Warning: pTraceMarkerIO
remains in code
The pTraceMarkerIO
function emits a marker to the eventlog, if eventlog
profiling is available and enabled at runtime.
Compared to pTraceMarker
, pTraceMarkerIO
sequences the event with respect
to other IO actions.
Since: 2.0.1.0
pTraceWith :: (a -> String) -> a -> a Source #
Warning: pTraceWith
remains in code
The pTraceWith
function pretty prints the result of
applying f to
a and returns back @a
@since ?
pTraceShowWith :: Show b => (a -> b) -> a -> a Source #
Warning: pTraceShowWith
remains in code
The pTraceShowWith
function similar to pTraceWith
except that
@f can return any type that implements Show
@since ?
Trace forcing color
pTraceForceColor :: String -> a -> a Source #
Warning: pTraceForceColor
remains in code
Similar to pTrace
, but forcing color.
pTraceIdForceColor :: String -> String Source #
Warning: pTraceIdForceColor
remains in code
Similar to pTraceId
, but forcing color.
pTraceShowForceColor :: Show a => a -> b -> b Source #
Warning: pTraceShowForceColor
remains in code
Similar to pTraceShow
, but forcing color.
pTraceShowIdForceColor :: Show a => a -> a Source #
Warning: pTraceShowIdForceColor
remains in code
Similar to pTraceShowId
, but forcing color.
pTraceMForceColor :: Applicative f => String -> f () Source #
Warning: pTraceMForceColor
remains in code
Similar to pTraceM
, but forcing color.
pTraceShowMForceColor :: (Show a, Applicative f) => a -> f () Source #
Warning: pTraceShowMForceColor
remains in code
Similar to pTraceShowM
, but forcing color.
pTraceStackForceColor :: String -> a -> a Source #
Warning: pTraceStackForceColor
remains in code
Similar to pTraceStack
, but forcing color.
pTraceEventForceColor :: String -> a -> a Source #
Warning: pTraceEventForceColor
remains in code
Similar to pTraceEvent
, but forcing color.
pTraceEventIOForceColor :: String -> IO () Source #
Warning: pTraceEventIOForceColor
remains in code
Similar to pTraceEventIO
, but forcing color.
pTraceMarkerForceColor :: String -> a -> a Source #
Warning: pTraceMarkerForceColor
remains in code
Similar to pTraceMarker
, but forcing color.
pTraceMarkerIOForceColor :: String -> IO () Source #
Warning: pTraceMarkerIOForceColor
remains in code
Similar to pTraceMarkerIO
, but forcing color.
pTraceIOForceColor :: String -> IO () Source #
Warning: pTraceIOForceColor
remains in code
Similar to pTraceIO
, but forcing color.
Trace without color
pTraceNoColor :: String -> a -> a Source #
Warning: pTraceNoColor
remains in code
Similar to pTrace
, but without color.
>>>
pTraceNoColor "wow" ()
wow ()
Since: 2.0.2.0
pTraceIdNoColor :: String -> String Source #
Warning: pTraceIdNoColor
remains in code
Similar to pTraceId
, but without color.
>>>
pTraceIdNoColor "(1, 2, 3)" `seq` ()
( 1 , 2 , 3 ) ()
Since: 2.0.2.0
pTraceShowNoColor :: Show a => a -> b -> b Source #
Warning: pTraceShowNoColor
remains in code
Similar to pTraceShow
, but without color.
>>>
import qualified Data.Map as M
>>>
pTraceShowNoColor (M.fromList [(1, True)]) ()
fromList [ ( 1 , True ) ] ()
Since: 2.0.2.0
pTraceShowIdNoColor :: Show a => a -> a Source #
Warning: pTraceShowIdNoColor
remains in code
Similar to pTraceShowId
, but without color.
>>>
import qualified Data.Map as M
>>>
pTraceShowIdNoColor (M.fromList [(1, True)]) `seq` ()
fromList [ ( 1 , True ) ] ()
Since: 2.0.2.0
pTraceMNoColor :: Applicative f => String -> f () Source #
Warning: pTraceMNoColor
remains in code
Similar to pTraceM
, but without color.
>>>
pTraceMNoColor "wow"
wow
Since: 2.0.2.0
pTraceShowMNoColor :: (Show a, Applicative f) => a -> f () Source #
Warning: pTraceShowMNoColor
remains in code
Similar to pTraceShowM
, but without color.
>>>
pTraceShowMNoColor [1,2,3]
[ 1 , 2 , 3 ]
Since: 2.0.2.0
pTraceStackNoColor :: String -> a -> a Source #
Warning: pTraceStackNoColor
remains in code
Similar to pTraceStack
, but without color.
>>>
pTraceStackNoColor "wow" () `seq` ()
wow ()
Since: 2.0.2.0
pTraceEventNoColor :: String -> a -> a Source #
pTraceEventIONoColor :: String -> IO () Source #
Warning: pTraceEventIONoColor
remains in code
Similar to pTraceEventIO
, but without color.
Since: 2.0.2.0
pTraceMarkerNoColor :: String -> a -> a Source #
Warning: pTraceMarkerNoColor
remains in code
Similar to pTraceMarker
, but without color.
Since: 2.0.2.0
pTraceMarkerIONoColor :: String -> IO () Source #
Warning: pTraceMarkerIONoColor
remains in code
Similar to pTraceMarkerIO
, but without color.
Since: 2.0.2.0
pTraceIONoColor :: String -> IO () Source #
Warning: pTraceIONoColor
remains in code
Similar to pTraceIO
, but without color.
>>>
pTraceIONoColor "(1, 2, 3)"
( 1 , 2 , 3 )
Since: 2.0.2.0
Trace With OutputOptions
pTraceOpt :: CheckColorTty -> OutputOptions -> String -> a -> a Source #
pTraceIdOpt :: CheckColorTty -> OutputOptions -> String -> String Source #
Warning: pTraceIdOpt
remains in code
Like pTraceId
but takes OutputOptions.
pTraceShowOpt :: Show a => CheckColorTty -> OutputOptions -> a -> b -> b Source #
Warning: pTraceShowOpt
remains in code
Like pTraceShow
but takes OutputOptions.
pTraceShowIdOpt :: Show a => CheckColorTty -> OutputOptions -> a -> a Source #
Warning: pTraceShowIdOpt
remains in code
Like pTraceShowId
but takes OutputOptions.
pTraceOptIO :: CheckColorTty -> OutputOptions -> String -> IO () Source #
Warning: pTraceOptIO
remains in code
Like pTraceIO
but takes OutputOptions.
pTraceOptM :: Applicative f => CheckColorTty -> OutputOptions -> String -> f () Source #
Warning: pTraceOptM
remains in code
Like pTraceM
but takes OutputOptions.
pTraceShowOptM :: (Show a, Applicative f) => CheckColorTty -> OutputOptions -> a -> f () Source #
Warning: pTraceShowOptM
remains in code
Like pTraceShowM
but takes OutputOptions.
pTraceStackOpt :: CheckColorTty -> OutputOptions -> String -> a -> a Source #
Warning: pTraceStackOpt
remains in code
Like pTraceStack
but takes OutputOptions.
pTraceEventOpt :: CheckColorTty -> OutputOptions -> String -> a -> a Source #
Warning: pTraceEventOpt
remains in code
Like pTraceEvent
but takes OutputOptions.
pTraceEventOptIO :: CheckColorTty -> OutputOptions -> String -> IO () Source #
Warning: pTraceEventOptIO
remains in code
Like pTraceEventIO
but takes OutputOptions.
pTraceMarkerOpt :: CheckColorTty -> OutputOptions -> String -> a -> a Source #
Warning: pTraceMarkerOpt
remains in code
Like pTraceMarker
but takes OutputOptions.
pTraceMarkerOptIO :: CheckColorTty -> OutputOptions -> String -> IO () Source #
Warning: pTraceMarkerOptIO
remains in code
Like pTraceMarkerIO
but takes OutputOptions.