log-effect-syslog-0.2.0: Syslog functions for log-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Log.Syslog

Synopsis

Documentation

data SyslogMsg Source #

Message type that contains priority and message text.

Instances
LogMessage SyslogMsg Source # 
Instance details

Defined in Control.Eff.Log.Syslog

runSyslog Source #

Arguments

:: (MonadBase IO m, MonadBaseControl IO (Eff r), Lifted m r) 
=> String

Syslog ident

-> [Option]

Syslog options

-> Facility

Syslog facility

-> Eff (LogM m SyslogMsg ': r) a 
-> Eff r a 

Wrapper around runLogM and withSyslog

getLogMask :: MonadBase IO m => m [Priority] Source #

Get syslog log mask. Implemented as a wrapper around hsyslog's setlogmask

setLogMask :: MonadBase IO m => [Priority] -> m () Source #

Set syslog log mask Implemented as a wrapper around hsyslog's setlogmask

logSyslog :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => Priority -> l -> Eff r () Source #

Log some text to syslog

logDebug :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logInfo :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logNotice :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logWarning :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logError :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logCritical :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

logAlert :: (LogMessage l, MonadBase IO m, Member (LogM m SyslogMsg) r, Lifted m r) => l -> Eff r () Source #

data Priority #

Log messages are prioritized with one of the following levels:

>>> [minBound..maxBound] :: [Priority]
[Emergency,Alert,Critical,Error,Warning,Notice,Info,Debug]

The Ord instance for Priority considers the more urgent level lower than less urgent ones:

>>> Emergency < Debug
True
>>> minimum [minBound..maxBound] :: Priority
Emergency
>>> maximum [minBound..maxBound] :: Priority
Debug

Constructors

Emergency

the system is unusable

Alert

action must be taken immediately

Critical

critical conditions

Error

error conditions

Warning

warning conditions

Notice

normal but significant condition

Info

informational

Debug

debug-level messages

Instances
Bounded Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Enum Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Eq Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Ord Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Read Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Show Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Generic Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Associated Types

type Rep Priority :: Type -> Type #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

type Rep Priority 
Instance details

Defined in System.Posix.Syslog.Priority

type Rep Priority = D1 (MetaData "Priority" "System.Posix.Syslog.Priority" "hsyslog-5.0.2-4YPEwpeEGKZ6PP1UUUwS4g" False) (((C1 (MetaCons "Emergency" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Alert" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Critical" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Error" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Warning" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Notice" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Info" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Debug" PrefixI False) (U1 :: Type -> Type))))

data Option #

The function openlog allows one to configure a handful of process-wide options that modify the behavior of the syslog function. These options are pid, cons, odelay, and ndelay.

Constructors

LogPID

Log the pid with each message.

Console

Log on the console if errors occur while sending messages.

DelayedOpen

Delay all initialization until first syslog() call (default).

ImmediateOpen

Initialize the syslog system immediately.

DontWaitForChildren

The syslog system should not attempt to wait for child process it may have created. This option is required by applications who enable SIGCHLD themselves.

Instances
Bounded Option 
Instance details

Defined in System.Posix.Syslog.Options

Enum Option 
Instance details

Defined in System.Posix.Syslog.Options

Eq Option 
Instance details

Defined in System.Posix.Syslog.Options

Methods

(==) :: Option -> Option -> Bool #

(/=) :: Option -> Option -> Bool #

Read Option 
Instance details

Defined in System.Posix.Syslog.Options

Show Option 
Instance details

Defined in System.Posix.Syslog.Options

Generic Option 
Instance details

Defined in System.Posix.Syslog.Options

Associated Types

type Rep Option :: Type -> Type #

Methods

from :: Option -> Rep Option x #

to :: Rep Option x -> Option #

type Rep Option 
Instance details

Defined in System.Posix.Syslog.Options

type Rep Option = D1 (MetaData "Option" "System.Posix.Syslog.Options" "hsyslog-5.0.2-4YPEwpeEGKZ6PP1UUUwS4g" False) ((C1 (MetaCons "LogPID" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Console" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "DelayedOpen" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ImmediateOpen" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DontWaitForChildren" PrefixI False) (U1 :: Type -> Type))))

data Facility #

Syslog distinguishes various system facilities. Most applications should log in USER.

Constructors

Kernel

kernel messages

User

user-level messages (default unless set otherwise)

Mail

mail system

News

network news subsystem

UUCP

UUCP subsystem

Daemon

system daemons

Auth

security and authorization messages

Cron

clock daemon

LPR

line printer subsystem

Local0

reserved for local use

Local1

reserved for local use

Local2

reserved for local use

Local3

reserved for local use

Local4

reserved for local use

Local5

reserved for local use

Local6

reserved for local use

Local7

reserved for local use

Instances
Bounded Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Enum Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Eq Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Read Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Show Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Generic Facility 
Instance details

Defined in System.Posix.Syslog.Facility

Associated Types

type Rep Facility :: Type -> Type #

Methods

from :: Facility -> Rep Facility x #

to :: Rep Facility x -> Facility #

type Rep Facility 
Instance details

Defined in System.Posix.Syslog.Facility

type Rep Facility = D1 (MetaData "Facility" "System.Posix.Syslog.Facility" "hsyslog-5.0.2-4YPEwpeEGKZ6PP1UUUwS4g" False) ((((C1 (MetaCons "Kernel" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "User" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Mail" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "News" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "UUCP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Daemon" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Auth" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Cron" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "LPR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Local0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Local1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Local2" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Local3" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Local4" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Local5" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Local6" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Local7" PrefixI False) (U1 :: Type -> Type))))))