libsystemd-journal-1.4.5.1: Haskell bindings to libsystemd-journal
Safe HaskellSafe-Inferred
LanguageGHC2021

Systemd.Journal

Synopsis

Writing to the journal

sendMessage :: Text -> IO () Source #

Send a message to the systemd journal.

sendMessage t == sendJournalFields (message t)

sendMessageWith :: Text -> JournalFields -> IO () Source #

Send a message and supply extra fields.

Note: The MESSAGE field will be replaced with the first parameter to this function. If you don't want this, use sendJournalFields

sendJournalFields :: JournalFields -> IO () Source #

Send an exact set of fields to the systemd journal.

type JournalFields = HashMap JournalField ByteString Source #

A structured object of all the fields in an entry in the journal. You generally don't construct this yourself, but you use the monoid instance and smart constructors below.

For example,

sendJournalFields (message "Oh god, it burns!" <> priority Emergency)

Standard systemd journal fields

message :: Text -> JournalFields Source #

The human readable message string for this entry. This is supposed to be the primary text shown to the user. It is usually not translated (but might be in some cases), and is not supposed to be parsed for meta data.

messageId :: UUID -> JournalFields Source #

A 128bit message identifier ID for recognizing certain message types, if this is desirable. Developers can generate a new ID for this purpose with journalctl --new-id.

priority :: Priority -> JournalFields Source #

A priority value compatible with syslog's priority concept.

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

Instances details
Bounded Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Enum 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 Source #

Read Priority 
Instance details

Defined in System.Posix.Syslog.Priority

Show 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

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-3TbFkohjWRv3G9jC0b0LZP" '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))))

codeFile :: FilePath -> JournalFields Source #

The source code file generating this message.

codeLine :: Int -> JournalFields Source #

The source code line number generating this message.

codeFunc :: Text -> JournalFields Source #

The source code function name generating this message.

errno :: Int -> JournalFields Source #

The low-level Unix error number causing this entry, if any. Contains the numeric value of errno(3).

syslogFacility :: Facility -> JournalFields Source #

Syslog compatibility field.

syslogIdentifier :: Text -> JournalFields Source #

Syslog compatibility field.

syslogPid :: CPid -> JournalFields Source #

Syslog compatibility field.

Custom journal fields

data JournalField Source #

Instances

Instances details
Data JournalField Source # 
Instance details

Defined in Systemd.Journal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JournalField -> c JournalField Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JournalField Source #

toConstr :: JournalField -> Constr Source #

dataTypeOf :: JournalField -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JournalField) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JournalField) Source #

gmapT :: (forall b. Data b => b -> b) -> JournalField -> JournalField Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JournalField -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JournalField -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> JournalField -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JournalField -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JournalField -> m JournalField Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JournalField -> m JournalField Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JournalField -> m JournalField Source #

IsString JournalField Source # 
Instance details

Defined in Systemd.Journal

Monoid JournalField Source # 
Instance details

Defined in Systemd.Journal

Semigroup JournalField Source # 
Instance details

Defined in Systemd.Journal

Read JournalField Source # 
Instance details

Defined in Systemd.Journal

Show JournalField Source # 
Instance details

Defined in Systemd.Journal

Eq JournalField Source # 
Instance details

Defined in Systemd.Journal

Ord JournalField Source # 
Instance details

Defined in Systemd.Journal

Hashable JournalField Source # 
Instance details

Defined in Systemd.Journal

mkJournalField :: Text -> JournalField Source #

Construct a JournalField by converting to uppercase, as required by the journal.

journalField :: JournalField -> Text Source #

Extract the name of a JournalField.

Reading the journal

openJournal Source #

Arguments

:: MonadSafe m 
=> [JournalFlag]

A list of flags taken under logical disjunction (or) to specify which journal files to open.

-> Start

Where to begin reading journal entries from.

-> Maybe Filter

An optional filter to apply the journal. Only entries satisfying the filter will be emitted.

-> Maybe Integer

The data field size threshold, or Nothing for no field size limit

-> Producer' JournalEntry m () 

Opens the journal for reading, optionally filtering the journal entries. Filters are defined as arbitrary binary expression trees, which are then rewritten to be in conjunctive normal form before filtering with systemd to comply with systemd's rule system.

data Start Source #

Where to begin reading the journal from.

Constructors

FromStart

Begin reading from the start of the journal.

FromEnd Direction

Begin reading from the end of the journal.

FromCursor JournalEntryCursor Direction

From a JournalEntryCursor.

data Direction Source #

In which direction to read the journal.

Constructors

Forwards

Read towards the end.

Backwards

Read towards the beginning.

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Systemd.Journal

data JournalEntry Source #

An entry that has been read from the systemd journal.

Instances

Instances details
Show JournalEntry Source # 
Instance details

Defined in Systemd.Journal

Eq JournalEntry Source # 
Instance details

Defined in Systemd.Journal

journalEntryCursor :: JournalEntry -> JournalEntryCursor Source #

A JournalCursor can be used as marker into the journal stream. This can be used to re-open the journal at a specific point in the future, and JournalCursors can be serialized to disk.

journalEntryRealtime :: JournalEntry -> Word64 Source #

The time (in microseconds since the epoch) when this journal entry was received by the systemd journal.

data JournalFlag Source #

Flags to specify which journal entries to read.

Constructors

LocalOnly

Only journal files generated on the local machine will be opened.

RuntimeOnly

Only volatile journal files will be opened, excluding those which are stored on persistent storage.

SystemOnly

Only journal files of system services and the kernel (in opposition to user session processes) will be opened.

data Filter Source #

A logical expression to filter journal entries when reading the journal.

Constructors

Match JournalField ByteString

A binary exact match on a given JournalField.

And Filter Filter

Logical conjunction of two filters. Will only show journal entries that satisfy both conditions.

Or Filter Filter

Logical disjunction of two filters. Will show journal entries that satisfy either condition.

Instances

Instances details
Data Filter Source # 
Instance details

Defined in Systemd.Journal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Filter -> c Filter Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Filter Source #

toConstr :: Filter -> Constr Source #

dataTypeOf :: Filter -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Filter) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Filter) Source #

gmapT :: (forall b. Data b => b -> b) -> Filter -> Filter Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Filter -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Filter -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Filter -> m Filter Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter Source #

Show Filter Source # 
Instance details

Defined in Systemd.Journal

Eq Filter Source # 
Instance details

Defined in Systemd.Journal