simple-log-0.3.3: Simple log for Haskell

Safe HaskellNone
LanguageHaskell98

System.Log.Simple.Base

Synopsis

Documentation

data Rule Source

Rule for politics

Constructors

Rule 

Fields

rulePath :: [Text] -> Bool
 
rulePolitics :: Politics -> Politics
 

type Rules = [Rule] Source

defaultPolitics :: Politics Source

Default politics

debugPolitics :: Politics Source

Debug politics

tracePolitics :: Politics Source

Trace politics

silentPolitics :: Politics Source

Silent politics

supressPolitics :: Politics Source

Supress all messages politics

rule :: ([Text] -> Bool) -> (Politics -> Politics) -> Rule Source

Make rule

absolute :: [Text] -> [Text] -> Bool Source

Absolute scope-path

relative :: [Text] -> [Text] -> Bool Source

Relative scope-path

child :: ([Text] -> Bool) -> [Text] -> Bool Source

Scope-path for child

root :: [Text] -> Bool Source

Root scope-path

path :: Text -> [Text] -> Bool Source

Scope-path by text

/ -- root
foo/bar -- relative
/foo/bar -- absolute
foo/bar/ -- child of relative
/foo/bar/ -- child of absolute

(%=) :: Text -> (Politics -> Politics) -> Rule Source

Rule by path

politics :: Level -> Level -> Politics -> Politics Source

Just set new politics

use :: Politics -> Politics -> Politics Source

Use predefined politics

low :: Level -> Politics -> Politics Source

Set new low level

high :: Level -> Politics -> Politics Source

Set new high level

data Message Source

Log message

Constructors

Message 

Fields

messageTime :: ZonedTime
 
messageLevel :: Level
 
messagePath :: [Text]
 
messageText :: Text
 

type Converter a = Message -> a Source

Converts message some representation

data Consumer a Source

Constructors

Consumer 

Fields

withConsumer :: ((a -> IO ()) -> IO ()) -> IO ()
 

data Entry Source

Log entry, scope or message

Constructors

Entry Message 
Scope Text Rules (IO ()) [Entry] 

data Command Source

Command to logger

Constructors

EnterScope Text Rules 
LeaveScope (IO ()) 
PostMessage Message 

entries :: [Command] -> [Entry] Source

Apply commands to construct list of entries

flatten :: [Entry] -> [Command] Source

Flatten entries to raw list of commands

rules :: Rules -> [Text] -> [Entry] -> [Entry] Source

Apply rules

logger :: Converter a -> Consumer a -> Consumer Message Source

Convert consumer creater to logger creater

type RulesLoad = IO (IO Rules) Source

Type to initialize rule updater

data Log Source

Log

Constructors

Log 

Fields

logPost :: Command -> IO ()
 
logStop :: IO ()
 
logRules :: IO Rules
 

Instances

noLog :: Log Source

Empty log

newLog :: RulesLoad -> [Logger] -> IO Log Source

Create log

Messages from distinct threads are splitted in several chans, where they are processed, and then messages combined back and sent to log-thread

writeLog :: MonadIO m => Log -> Level -> Text -> m () Source

Write message to log

stopLog :: MonadIO m => Log -> m () Source

Wait log messages and stop log

scopeLog_ :: MonadCatchIO m => Log -> Text -> m a -> m a Source

New log-scope

scopeLog :: MonadCatchIO m => Log -> Text -> m a -> m a Source

New log-scope with lifting exceptions as errors

scoperLog :: MonadCatchIO m => Show a => Log -> Text -> m a -> m a Source

New log-scope with tracing scope result