distributed-process-extras-0.3.9: Cloud Haskell Extras
Copyright(c) Tim Watson 2013 - 2017
LicenseBSD3 (see the file LICENSE)
MaintainerTim Watson <watson.timothy@gmail.com>
Stabilityexperimental
Portabilitynon-portable (requires concurrency)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Distributed.Process.Extras.SystemLog

Description

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
Synopsis

Types exposed by this module

data LogLevel Source #

Instances

Instances details
Enum LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Generic LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Associated Types

type Rep LogLevel :: Type -> Type #

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

Read LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Show LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Binary LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

put :: LogLevel -> Put #

get :: Get LogLevel #

putList :: [LogLevel] -> Put #

NFData LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

rnf :: LogLevel -> () #

Eq LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Ord LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

type Rep LogLevel Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

type Rep LogLevel = D1 ('MetaData "LogLevel" "Control.Distributed.Process.Extras.SystemLog" "distributed-process-extras-0.3.9-3PIUq7kIBoQKuBft1CeSET" 'False) (((C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Notice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Critical" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Alert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Emergency" 'PrefixI 'False) (U1 :: Type -> Type))))

data LogChan Source #

Instances

Instances details
Routable LogChan Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Logger LogChan Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

logMessage :: LogChan -> LogMessage -> Process () Source #

class ToLog m where Source #

Minimal complete definition

Nothing

Methods

toLog :: Serializable m => m -> Process (LogLevel -> LogMessage) Source #

Instances

Instances details
ToLog Message Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

toLog :: Message -> Process (LogLevel -> LogMessage) Source #

ToLog LogText Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

toLog :: LogText -> Process (LogLevel -> LogMessage) Source #

class Logger a where Source #

Methods

logMessage :: a -> LogMessage -> Process () Source #

Instances

Instances details
Logger LogChan Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

logMessage :: LogChan -> LogMessage -> Process () Source #

Logger LogClient Source # 
Instance details

Defined in Control.Distributed.Process.Extras.SystemLog

Methods

logMessage :: LogClient -> LogMessage -> Process () Source #

Mx Agent Configuration / Startup

systemLog Source #

Arguments

:: (String -> Process ())

This expression does the actual logging

-> Process ()

An expression used to clean up any residual state

-> LogLevel

The initial LogLevel to use

-> LogFormat

An expression used to format logging messages/text

-> Process ProcessId 

Start a system logger process as a management agent.

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.

Logging Messages

report :: Logger l => (l -> LogText -> Process ()) -> l -> String -> Process () Source #

debug :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

info :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

notice :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

warning :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

error :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

critical :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

alert :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

emergency :: (Logger l, Serializable m, ToLog m) => l -> m -> Process () Source #

sendLog :: (Logger l, Serializable m, ToLog m) => l -> m -> LogLevel -> Process () Source #