module Control.Distributed.Process.Management.Internal.Trace.Primitives
(
traceLog
, traceLogFmt
, traceMessage
, defaultTraceFlags
, enableTrace
, enableTraceAsync
, disableTrace
, disableTraceAsync
, getTraceFlags
, setTraceFlags
, setTraceFlagsAsync
, traceOnly
, traceOn
, traceOff
, withLocalTracer
, withRegisteredTracer
) where
import Control.Applicative ((<$>))
import Control.Distributed.Process.Internal.Primitives
( whereis
, newChan
, receiveChan
)
import Control.Distributed.Process.Management.Internal.Trace.Types
( TraceArg(..)
, TraceFlags(..)
, TraceOk(..)
, TraceSubject(..)
, defaultTraceFlags
)
import qualified Control.Distributed.Process.Management.Internal.Trace.Types as Tracer
( traceLog
, traceLogFmt
, traceMessage
, enableTrace
, enableTraceSync
, disableTrace
, disableTraceSync
, setTraceFlags
, setTraceFlagsSync
, getTraceFlags
, getCurrentTraceClient
)
import Control.Distributed.Process.Internal.Types
( Process
, ProcessId
, LocalProcess(..)
, LocalNode(localEventBus)
, SendPort
, MxEventBus(..)
)
import Control.Distributed.Process.Serializable
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader (ask)
import qualified Data.Set as Set (fromList)
class Traceable a where
uod :: [a] -> TraceSubject
instance Traceable ProcessId where
uod = TraceProcs . Set.fromList
instance Traceable String where
uod = TraceNames . Set.fromList
traceOnly :: Traceable a => [a] -> Maybe TraceSubject
traceOnly = Just . uod
traceOn :: Maybe TraceSubject
traceOn = Just TraceAll
traceOff :: Maybe TraceSubject
traceOff = Nothing
enableTraceAsync :: ProcessId -> Process ()
enableTraceAsync pid = withLocalTracer $ \t -> liftIO $ Tracer.enableTrace t pid
enableTrace :: ProcessId -> Process ()
enableTrace pid =
withLocalTracerSync $ \t sp -> Tracer.enableTraceSync t sp pid
disableTraceAsync :: Process ()
disableTraceAsync = withLocalTracer $ \t -> liftIO $ Tracer.disableTrace t
disableTrace :: Process ()
disableTrace =
withLocalTracerSync $ \t sp -> Tracer.disableTraceSync t sp
getTraceFlags :: Process TraceFlags
getTraceFlags = do
(sp, rp) <- newChan
withLocalTracer $ \t -> liftIO $ Tracer.getTraceFlags t sp
receiveChan rp
setTraceFlagsAsync :: TraceFlags -> Process ()
setTraceFlagsAsync f = withLocalTracer $ \t -> liftIO $ Tracer.setTraceFlags t f
setTraceFlags :: TraceFlags -> Process ()
setTraceFlags f =
withLocalTracerSync $ \t sp -> Tracer.setTraceFlagsSync t sp f
traceLog :: String -> Process ()
traceLog s = withLocalTracer $ \t -> liftIO $ Tracer.traceLog t s
traceLogFmt :: String -> [TraceArg] -> Process ()
traceLogFmt d ls = withLocalTracer $ \t -> liftIO $ Tracer.traceLogFmt t d ls
traceMessage :: Serializable m => m -> Process ()
traceMessage msg = withLocalTracer $ \t -> liftIO $ Tracer.traceMessage t msg
withLocalTracer :: (MxEventBus -> Process ()) -> Process ()
withLocalTracer act = do
node <- processNode <$> ask
act (localEventBus node)
withLocalTracerSync :: (MxEventBus -> SendPort TraceOk -> IO ()) -> Process ()
withLocalTracerSync act = do
(sp, rp) <- newChan
withLocalTracer $ \t -> liftIO $ (act t sp)
TraceOk <- receiveChan rp
return ()
withRegisteredTracer :: (ProcessId -> Process a) -> Process a
withRegisteredTracer act = do
(sp, rp) <- newChan
withLocalTracer $ \t -> liftIO $ Tracer.getCurrentTraceClient t sp
currentTracer <- receiveChan rp
case currentTracer of
Nothing -> do { (Just p') <- whereis "tracer.initial"; act p' }
(Just p) -> act p