Skip to content

Commit

Permalink
trace to the event log *or* to a file handle
Browse files Browse the repository at this point in the history
  • Loading branch information
Tim Watson committed Jan 26, 2013
1 parent 5c3abff commit d2d38f2
Showing 1 changed file with 34 additions and 20 deletions.
Original file line number Original file line Diff line number Diff line change
@@ -1,10 +1,12 @@

-- | Simple (internal) system logging/tracing support.
module Control.Distributed.Process.Internal.Trace module Control.Distributed.Process.Internal.Trace
( Tracer ( Tracer
, trace -- :: String -> IO () , trace
, traceFormat -- :: (Show a) => (a -> a -> String) -> [a] -> IO () , traceFormat
, eventlog , startEventlogTracer
, console , startLogfileTracer
, defaultTracer
, stopTracer
) where ) where


import Control.Concurrent import Control.Concurrent
Expand All @@ -18,36 +20,48 @@ import Control.Concurrent.STM
, writeTQueue , writeTQueue
, atomically , atomically
) )
import Control.Distributed.Process.Internal.Types (forever')
import Control.Exception
import Data.List (foldl') import Data.List (foldl')
import Debug.Trace import Debug.Trace (traceEventIO)
( traceEventIO import System.IO
)


data Tracer = data Tracer =
ConsoleTracer ThreadId (TQueue String) LogFileTracer ThreadId (TQueue String)
| EventLogTracer (String -> IO ()) | EventLogTracer (String -> IO ())
| NoOpTracer


eventlog :: IO Tracer defaultTracer :: IO Tracer
eventlog = return $ EventLogTracer traceEventIO defaultTracer = return NoOpTracer


console :: IO Tracer startEventlogTracer :: IO Tracer
console = do startEventlogTracer = return $ EventLogTracer traceEventIO
q <- newTQueueIO
tid <- forkIO $ logger q startLogfileTracer :: FilePath -> IO Tracer
return $ ConsoleTracer tid q startLogfileTracer p = do
where logger q' = do q <- newTQueueIO
tid <- forkIO $ withFile p AppendMode (\h -> logger h q)
return $ LogFileTracer tid q
where logger :: Handle -> TQueue String -> IO ()
logger h q' = forever' $ do
msg <- atomically $ readTQueue q' msg <- atomically $ readTQueue q'
putStrLn msg hPutStr h msg
logger q' logger h q'

stopTracer :: Tracer -> IO ()
stopTracer (LogFileTracer tid _) = throwTo tid ThreadKilled
stopTracer _ = return ()


trace :: Tracer -> String -> IO () trace :: Tracer -> String -> IO ()
trace (ConsoleTracer _ q) msg = atomically $ writeTQueue q msg trace (LogFileTracer _ q) msg = atomically $ writeTQueue q msg
trace (EventLogTracer t) msg = t msg trace (EventLogTracer t) msg = t msg
trace NoOpTracer _ = return ()


traceFormat :: (Show a) traceFormat :: (Show a)
=> Tracer => Tracer
-> (String -> String -> String) -> (String -> String -> String)
-> [a] -> [a]
-> IO () -> IO ()
traceFormat NoOpTracer _ _ = return ()
traceFormat t f xs = traceFormat t f xs =
trace t $ foldl' (\e a -> ((show e) `f` (show a))) "" xs trace t $ foldl' (\e a -> ((show e) `f` (show a))) "" xs

0 comments on commit d2d38f2

Please sign in to comment.