Copyright | (c) Well-Typed / Tim Watson |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | Tim Watson <watson.timothy@gmail.com> |
Stability | experimental |
Portability | non-portable (requires concurrency) |
Safe Haskell | None |
Language | Haskell2010 |
- Tracing/Debugging Facilities
Cloud Haskell provides a general purpose tracing mechanism, allowing a user supplied tracer process to receive messages when certain classes of system events occur. It's possible to use this facility to aid in debugging and/or perform other diagnostic tasks to a program at runtime.
- Enabling Tracing
Throughout the lifecycle of a local node, the distributed-process runtime
generates trace events, describing internal runtime activities such as
the spawning and death of processes, message sending, delivery and so on.
See the MxEvent
type's documentation for a list of all the published
event types, which correspond directly to the types of management events.
Users can additionally publish custom trace events in the form of
MxLog
log messages or pass custom (i.e., completely user defined)
event data using the traceMessage
function.
All published traces are forwarded to a tracer process, which can be
specified (and changed) at runtime using traceEnable
. Some pre-defined
tracer processes are provided for conveniently printing to stderr, a log file
or the GHC eventlog.
If a tracer process crashes, no attempt is made to restart it.
- Working with multiple tracer processes
The tracing facility only ever writes to a single tracer process. This invariant insulates the tracer controller and ensures a fast path for handling all trace events. This module provides facilities for layering trace handlers using Cloud Haskell's built-in delegation primitives.
The startTracer
function wraps the registered tracer
process with the
supplied handler and also forwards trace events to the original tracer.
The corresponding stopTracer
function terminates tracer processes in
reverse of the order in which they were started, and re-registers the
previous tracer process.
- Built in tracers
The built in tracers provide a simple logging facility that writes trace
events out to either a log file, stderr
or the GHC eventlog. These tracers
can be configured using environment variables, or specified manually using
the traceEnable
function.
When a new local node is started, the contents of several environment variables are checked to determine which default tracer process is selected. If none of these variables is set, a no-op tracer process is installed, which effectively ignores all trace messages. Note that in this case, trace events are still generated and passed through the system. Only one default tracer will be chosen - the first that contains a (valid) value. These environment variables, in the order they're examined, are:
DISTRIBUTED_PROCESS_TRACE_FILE
This is checked for a valid file path. If it exists and the file can be opened for writing, all trace output will be directed thence. If the supplied path is invalid, or the file is unavailable for writing, this tracer will not be selected.DISTRIBUTED_PROCESS_TRACE_CONSOLE
This is checked for any non-empty value. If set, then all trace output will be directed to the system logger process.DISTRIBUTED_PROCESS_TRACE_EVENTLOG
This is checked for any non-empty value. If set, all internal traces are written to the GHC eventlog.
By default, the built in tracers will ignore all trace events! In order to
enable tracing the incoming MxEvent
stream, the DISTRIBUTED_PROCESS_TRACE_FLAGS
environment variable accepts the following flags, which enable tracing specific
event types:
p
= trace the spawning of new processesd
= trace the death of processesn
= trace registration of names (i.e., named processes)u
= trace un-registration of names (i.e., named processes)s
= trace the sending of messages to other processesr
= trace the receipt of messages from other processesl
= trace node up/down events
Users of the simplelocalnet Cloud Haskell backend should also note that because the trace file option only supports trace output from a single node (so as to avoid interleaving), a file trace configured for the master node will prevent slaves from tracing to the file. They will need to fall back to the console or eventlog tracers instead, which can be accomplished by setting one of these environment variables as well, since the latter will only be selected on slaves (when the file tracer selection fails).
Support for writing to the eventlog requires specific intervention to work, without which, written traces are silently dropped/ignored and no output will be generated. The GHC eventlog documentation provides information about enabling, viewing and working with event traces at http://hackage.haskell.org/trac/ghc/wiki/EventLog.
Synopsis
- data TraceArg
- data TraceFlags = TraceFlags {
- traceSpawned :: !(Maybe TraceSubject)
- traceDied :: !(Maybe TraceSubject)
- traceRegistered :: !(Maybe TraceSubject)
- traceUnregistered :: !(Maybe TraceSubject)
- traceSend :: !(Maybe TraceSubject)
- traceRecv :: !(Maybe TraceSubject)
- traceNodes :: !Bool
- traceConnections :: !Bool
- data TraceSubject
- = TraceAll
- | TraceProcs !(Set ProcessId)
- | TraceNames !(Set String)
- enableTrace :: ProcessId -> Process ()
- enableTraceAsync :: ProcessId -> Process ()
- disableTrace :: Process ()
- withTracer :: (MxEvent -> Process ()) -> Process a -> Process (Either SomeException a)
- withFlags :: TraceFlags -> Process a -> Process (Either SomeException a)
- getTraceFlags :: Process TraceFlags
- setTraceFlags :: TraceFlags -> Process ()
- setTraceFlagsAsync :: TraceFlags -> Process ()
- defaultTraceFlags :: TraceFlags
- traceOn :: Maybe TraceSubject
- traceOnly :: Traceable a => [a] -> Maybe TraceSubject
- traceOff :: Maybe TraceSubject
- startTracer :: (MxEvent -> Process ()) -> Process ProcessId
- stopTracer :: Process ()
- traceLog :: String -> Process ()
- traceLogFmt :: String -> [TraceArg] -> Process ()
- traceMessage :: Serializable m => m -> Process ()
- remoteTable :: RemoteTable -> RemoteTable
- startTraceRelay :: NodeId -> Process ProcessId
- setTraceFlagsRemote :: TraceFlags -> NodeId -> Process ()
- systemLoggerTracer :: Process ()
- logfileTracer :: FilePath -> Process ()
- eventLogTracer :: Process ()
Exported Data Types
data TraceFlags Source #
Defines what will be traced. Flags that control tracing of
Process
events, take a TraceSubject
controlling which processes
should generate trace events in the target process.
TraceFlags | |
|
Instances
data TraceSubject Source #
Defines which processes will be traced by a given TraceFlag
,
either by name, or ProcessId
. Choosing TraceAll
is by far
the most efficient approach, as the tracer process therefore
avoids deciding whether or not a trace event is viable.
Instances
Generic TraceSubject Source # | |||||
Defined in Control.Distributed.Process.Management.Internal.Trace.Types
from :: TraceSubject -> Rep TraceSubject x # to :: Rep TraceSubject x -> TraceSubject # | |||||
Show TraceSubject Source # | |||||
Defined in Control.Distributed.Process.Management.Internal.Trace.Types showsPrec :: Int -> TraceSubject -> ShowS # show :: TraceSubject -> String # showList :: [TraceSubject] -> ShowS # | |||||
Binary TraceSubject Source # | |||||
type Rep TraceSubject Source # | |||||
Defined in Control.Distributed.Process.Management.Internal.Trace.Types type Rep TraceSubject = D1 ('MetaData "TraceSubject" "Control.Distributed.Process.Management.Internal.Trace.Types" "distributed-process-0.7.6-F5sZSqR3Cb09RBogyeswiz" 'False) (C1 ('MetaCons "TraceAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TraceProcs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set ProcessId))) :+: C1 ('MetaCons "TraceNames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set String))))) |
Configuring Tracing
enableTrace :: ProcessId -> Process () Source #
Enable tracing to the supplied process and wait for a TraceOk
response from the trace coordinator process.
enableTraceAsync :: ProcessId -> Process () Source #
Enable tracing to the supplied process.
disableTrace :: Process () Source #
Disable the currently configured trace and wait for a TraceOk
response from the trace coordinator process.
withTracer :: (MxEvent -> Process ()) -> Process a -> Process (Either SomeException a) Source #
Evaluate proc
with tracing enabled via handler
, and immediately
disable tracing thereafter, before giving the result (or exception
in case of failure).
withFlags :: TraceFlags -> Process a -> Process (Either SomeException a) Source #
Evaluate proc
with the supplied flags enabled. Any previously set
trace flags are restored immediately afterwards.
setTraceFlags :: TraceFlags -> Process () Source #
Set the given flags for the current tracer and wait for a TraceOk
response from the trace coordinator process.
setTraceFlagsAsync :: TraceFlags -> Process () Source #
Set the given flags for the current tracer.
traceOn :: Maybe TraceSubject Source #
Trace all targets.
traceOnly :: Traceable a => [a] -> Maybe TraceSubject Source #
Turn tracing for for a subset of trace targets.
traceOff :: Maybe TraceSubject Source #
Trace no targets.
Debugging
startTracer :: (MxEvent -> Process ()) -> Process ProcessId Source #
Starts a new tracer, using the supplied trace function.
Only one tracer can be registered at a time, however this function overlays
the registered tracer with the supplied handler, allowing the user to layer
multiple tracers on top of one another, with trace events forwarded down
through all the layers in turn. Once the top layer is stopped, the user
is responsible for re-registering the original (prior) tracer pid before
terminating. See withTracer
for a mechanism that handles that.
stopTracer :: Process () Source #
Stops a user supplied tracer started with startTracer
.
Note that only one tracer process can be active at any given time.
This process will stop the last process started with startTracer
.
If startTracer
is called multiple times, successive calls to this
function will stop the tracers in the reverse order which they were
started.
This function will never stop the system tracer (i.e., the tracer
initially started when the node is created), therefore once all user
supplied tracers (i.e., processes started via startTracer
) have exited,
subsequent calls to this function will have no effect.
If the last tracer to have been registered was not started
with startTracer
then the behaviour of this function is undefined.
Sending Custom Trace Data
traceLog :: String -> Process () Source #
Send a log message to the internal tracing facility. If tracing is enabled, this will create a custom trace log event.
traceLogFmt :: String -> [TraceArg] -> Process () Source #
Send a log message to the internal tracing facility, using the given
list of printable TraceArg
s interspersed with the preceding delimiter.
traceMessage :: Serializable m => m -> Process () Source #
Send an arbitrary Message
to the tracer process.
Working with remote nodes
remoteTable :: RemoteTable -> RemoteTable Source #
Remote Table.
startTraceRelay :: NodeId -> Process ProcessId Source #
Starts a trace relay process on the remote node, which forwards all trace events to the registered tracer on this (the calling process') node.
setTraceFlagsRemote :: TraceFlags -> NodeId -> Process () Source #
Set the given flags for a remote node (asynchronous).
Built in tracers
systemLoggerTracer :: Process () Source #
logfileTracer :: FilePath -> Process () Source #
eventLogTracer :: Process () Source #