Copyright | (c) Tim Watson 2013 - 2017 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | Tim Watson <watson.timothy@gmail.com> |
Stability | experimental |
Portability | non-portable (requires concurrency) |
Safe Haskell | None |
Language | Haskell98 |
This module provides a general purpose logging facility, implemented as a
distributed-process Management Agent. To start the logging agent on a
running node, evaluate systemLog
with the relevant expressions to handle
logging textual messages, a cleanup operation (if required), initial log
level and a formatting expression.
We export a working example in the form of systemLogFile
, which logs
to a text file using buffered I/O. Its implementation is very simple, and
should serve as a demonstration of how to use the API:
systemLogFile :: FilePath -> LogLevel -> LogFormat -> Process ProcessId systemLogFile path lvl fmt = do h <- liftIO $ openFile path AppendMode liftIO $ hSetBuffering h LineBuffering systemLog (liftIO . hPutStrLn h) (liftIO (hClose h)) lvl fmt
- data LogLevel
- type LogFormat = String -> Process String
- data LogClient
- data LogChan
- type LogText = String
- class ToLog m where
- class Logger a where
- mxLogId :: MxAgentId
- systemLog :: (String -> Process ()) -> Process () -> LogLevel -> LogFormat -> Process ProcessId
- client :: Process (Maybe LogClient)
- logChannel :: LogChan
- addFormatter :: Addressable r => r -> Closure (Message -> Process (Maybe String)) -> Process ()
- systemLogFile :: FilePath -> LogLevel -> LogFormat -> Process ProcessId
- report :: Logger l => (l -> LogText -> Process ()) -> l -> String -> Process ()
- debug :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- info :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- notice :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- warning :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- error :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- critical :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- alert :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- emergency :: (Logger l, Serializable m, ToLog m) => l -> m -> Process ()
- sendLog :: (Logger l, Serializable m, ToLog m) => l -> m -> LogLevel -> Process ()
Types exposed by this module
logMessage :: a -> LogMessage -> Process () Source #
Mx Agent Configuration / Startup
:: (String -> Process ()) | This expression does the actual logging |
-> Process () | An expression used to clean up any residual state |
-> LogLevel | The initial |
-> LogFormat | An expression used to format logging messages/text |
-> Process ProcessId |
Start a system logger process as a management agent.
logChannel :: LogChan Source #
addFormatter :: Addressable r => r -> Closure (Message -> Process (Maybe String)) -> Process () Source #
systemLogFile
systemLogFile :: FilePath -> LogLevel -> LogFormat -> Process ProcessId Source #
Start a system logger that writes to a file.
This is a very basic file logging facility, that uses regular buffered
file I/O (i.e., System.IO.hPutStrLn
et al) under the covers. The handle
is closed appropriately if/when the logging process terminates.
See Control.Distributed.Process.Management.mxAgentWithFinalize
for futher
details about management agents that use finalizers.