hsyslog-4: FFI interface to syslog(3) from POSIX.1-2001

Maintainersimons@cryp.to
Stabilityprovisional
PortabilityPosix
Safe HaskellNone
LanguageHaskell98

System.Posix.Syslog

Contents

Description

FFI bindings to syslog(3) from POSIX.1-2008.

Synopsis

Marshaled Data Types

data Priority Source #

Log messages have a priority attached.

Constructors

Emergency

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 Source # 
Enum Priority Source # 
Eq Priority Source # 
Read Priority Source # 
Show Priority Source # 
Generic Priority Source # 

Associated Types

type Rep Priority :: * -> * #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

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

data Facility Source #

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

Constructors

KERN

kernel messages

USER

user-level messages (default unless set otherwise)

MAIL

mail system

DAEMON

system daemons

AUTH

security/authorization messages

SYSLOG

messages generated internally by syslogd

LPR

line printer subsystem

NEWS

network news subsystem

UUCP

UUCP subsystem

CRON

clock daemon

AUTHPRIV

security/authorization messages (effectively equals AUTH on some systems)

FTP

ftp daemon (effectively equals DAEMON on some systems)

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 Source # 
Enum Facility Source # 
Eq Facility Source # 
Read Facility Source # 
Show Facility Source # 
Generic Facility Source # 

Associated Types

type Rep Facility :: * -> * #

Methods

from :: Facility -> Rep Facility x #

to :: Rep Facility x -> Facility #

type Rep Facility Source # 
type Rep Facility = D1 (MetaData "Facility" "System.Posix.Syslog" "hsyslog-4-Edwo6Gqh8hnCAflX2j2o6P" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "KERN" PrefixI False) U1) (C1 (MetaCons "USER" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MAIL" PrefixI False) U1) ((:+:) (C1 (MetaCons "DAEMON" PrefixI False) U1) (C1 (MetaCons "AUTH" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "SYSLOG" PrefixI False) U1) (C1 (MetaCons "LPR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NEWS" PrefixI False) U1) ((:+:) (C1 (MetaCons "UUCP" PrefixI False) U1) (C1 (MetaCons "CRON" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AUTHPRIV" PrefixI False) U1) (C1 (MetaCons "FTP" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LOCAL0" PrefixI False) U1) ((:+:) (C1 (MetaCons "LOCAL1" PrefixI False) U1) (C1 (MetaCons "LOCAL2" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "LOCAL3" PrefixI False) U1) (C1 (MetaCons "LOCAL4" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LOCAL5" PrefixI False) U1) ((:+:) (C1 (MetaCons "LOCAL6" PrefixI False) U1) (C1 (MetaCons "LOCAL7" PrefixI False) U1))))))

data Option Source #

withSyslog options for the syslog service.

Constructors

PID

log the pid with each message

CONS

log on the console if errors in sending

ODELAY

delay open until first syslog() (default)

NDELAY

don't delay open

NOWAIT

don't wait for console forks: DEPRECATED

PERROR

log to stderr as well (might be a no-op on some systems)

Instances

Bounded Option Source # 
Enum Option Source # 
Eq Option Source # 

Methods

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

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

Read Option Source # 
Show Option Source # 
Generic Option Source # 

Associated Types

type Rep Option :: * -> * #

Methods

from :: Option -> Rep Option x #

to :: Rep Option x -> Option #

type Rep Option Source # 
type Rep Option = D1 (MetaData "Option" "System.Posix.Syslog" "hsyslog-4-Edwo6Gqh8hnCAflX2j2o6P" False) ((:+:) ((:+:) (C1 (MetaCons "PID" PrefixI False) U1) ((:+:) (C1 (MetaCons "CONS" PrefixI False) U1) (C1 (MetaCons "ODELAY" PrefixI False) U1))) ((:+:) (C1 (MetaCons "NDELAY" PrefixI False) U1) ((:+:) (C1 (MetaCons "NOWAIT" PrefixI False) U1) (C1 (MetaCons "PERROR" PrefixI False) U1))))

data PriorityMask Source #

withSyslog options for the priority mask.

Constructors

NoMask

allow all messages thru

Mask [Priority]

allow only messages with the priorities listed

UpTo Priority

allow only messages down to and including the specified priority

Configuring syslog

data SyslogConfig Source #

Constructors

SyslogConfig 

Fields

defaultConfig :: SyslogConfig Source #

A practical default syslog config. You'll at least want to change the identifier.

The preferred Haskell API to syslog

withSyslog :: SyslogConfig -> (SyslogFn -> IO ()) -> IO () Source #

Bracket an IO computation between calls to _openlog, _setlogmask, and _closelog, providing a logging function which can be used as follows:

main = withSyslog defaultConfig $ \syslog -> do
         putStrLn "huhu"
         syslog USER Debug "huhu"

Note that these are process-wide settings, so multiple calls to this function will interfere with each other in unpredictable ways.

type SyslogFn Source #

Arguments

 = Facility

the facility to log to

-> Priority

the priority under which to log

-> ByteString

the message to log

-> IO () 

The type of function provided by withSyslog.

The unsafe Haskell API to syslog

syslogUnsafe :: SyslogFn Source #

Provides no guarantee that a call to _openlog has been made, inviting unpredictable results.

Low-level C functions

Low-level C macros

Utilities

Low-level utilities for syslog-related tools

makePri :: Facility -> Priority -> CInt Source #

Calculate the full priority value of a Facility and Priority