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

Maintainersimons@cryp.to
Stabilityprovisional
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

System.Posix.Syslog

Contents

Description

A Haskell interface to syslog(3) as specified in POSIX.1-2008. The entire public API lives in this module. There is a set of exposed modules available underneath this one, which contain various implementation details that may be useful to other developers who want to implement syslog-related functionality. Users of syslog, however, do not need those modules; System.Posix.Syslog has all you'll need.

Check out the example program that demonstrates how to use this library.

Synopsis

Writing Log Messages

syslog Source #

Arguments

:: Maybe Facility

Categorize this message as belonging into the given system facility. If left unspecified, the process-wide default will be used, which tends to be User by default.

-> Priority

Log with the specified priority.

-> CStringLen

The actual log message. The string does not need to be terminated by a \0 byte. If the string does contain a \0 byte, then the message ends there regardless of what the length argument says.

-> IO () 

Log the given text message via syslog(3). Please note that log messages are committed to the log verbatim --- printf()-style text formatting features offered by the underlying system function are not available. If your log message reads "%s", then that string is exactly what will be written to the log. Also, log messages cannot contain \0 bytes. If they do, all content following that byte will be cut off because the C function assumes that the string ends there.

The Haskell String type can be easily logged with withCStringLen:

 withCStringLen "Hello, world." $ syslog (Just User) Info

ByteStrings can be logged in the same way with the unsafeUseAsCStringLen function from Data.ByteString.Unsafe, which extracts a CStringLen from the ByteString in constant time (no copying!).

data Priority Source #

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 Source # 
Enum Priority Source # 
Eq Priority Source # 
Ord 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.Priority" "hsyslog-5.0.1-24pighp6aYiFDQiBZ9eKP9" 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

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 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.Facility" "hsyslog-5.0.1-24pighp6aYiFDQiBZ9eKP9" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Kernel" PrefixI False) U1) (C1 (MetaCons "User" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Mail" PrefixI False) U1) (C1 (MetaCons "News" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "UUCP" PrefixI False) U1) (C1 (MetaCons "Daemon" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Auth" PrefixI False) U1) (C1 (MetaCons "Cron" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LPR" 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))))))

Configuring the system's logging engine

openlog Source #

Arguments

:: CString

An identifier to prepend to all log messages, typically the name of the programm. Note that the memory that contains this name must remain valid until the pointer provided here is released by calling closelog.

-> [Option]

A set of options that configure the behavior of the system's syslog engine.

-> Facility

The facility to use by default when none has been specified with a syslog call.

-> IO () 

This function configures the process-wide hidden state of the system's syslog engine. It's probably a bad idea to call this function anywhere except at the very top of your program's main function. And even then you should probably prefer withSyslog instead, which guarantees that syslog is properly initialized within its scope.

closelog :: IO () Source #

Release all syslog-related resources.

withSyslog :: String -> [Option] -> Facility -> IO a -> IO a Source #

Run the given IO a computation within an initialized syslogging scope. The definition is:

  withSyslog ident opts facil f =
    withCString ident $ ptr ->
      bracket_ (openlog ptr opts facil) closelog f

setlogmask :: [Priority] -> IO [Priority] Source #

Configure a process-wide filter that determines which logging priorities are ignored and which ones are forwarded to the syslog implementation. For example, use setlogmask [Emergency .. Info] to filter out all debug-level messages from the message stream. Calling setlogmask [minBound..maxBound] enables everything. The special case setlogmask [] does nothing, i.e. the current filter configuration is not modified. This can be used to retrieve the current configuration.

data Option Source #

The function openlog allows one to configure a handful of process-wide options that modify the bahavior of the syslog funcion. 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

Initalize 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 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.Options" "hsyslog-5.0.1-24pighp6aYiFDQiBZ9eKP9" False) ((:+:) ((:+:) (C1 (MetaCons "LogPID" PrefixI False) U1) (C1 (MetaCons "Console" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DelayedOpen" PrefixI False) U1) ((:+:) (C1 (MetaCons "ImmediateOpen" PrefixI False) U1) (C1 (MetaCons "DontWaitForChildren" PrefixI False) U1))))