doctest-parallel-0.3.1: Test interactive Haskell examples
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.DocTest.Internal.Logging

Synopsis

Documentation

type DebugLogger = String -> IO () Source #

Convenience type alias - not used in this module, but sprinkled across the project.

noLogger :: DebugLogger Source #

Discards any log message

data LogLevel Source #

Constructors

Debug

Intended for debug runs

Verbose

Intended for debug runs, but without flooding the user with internal messages

Info

Default log level - print messages user is likely wanting to see

Warning

Only print warnings

Error

Only print errors

Instances

Instances details
Bounded LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

Enum LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

Generic LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

Associated Types

type Rep LogLevel :: Type -> Type #

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

Show LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

NFData LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

Methods

rnf :: LogLevel -> () #

Eq LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

Ord LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

type Rep LogLevel Source # 
Instance details

Defined in Test.DocTest.Internal.Logging

type Rep LogLevel = D1 ('MetaData "LogLevel" "Test.DocTest.Internal.Logging" "doctest-parallel-0.3.1-inplace" 'False) ((C1 ('MetaCons "Debug" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Verbose" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Info" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type))))

parseLogLevel :: String -> Maybe LogLevel Source #

Case insensitive

>>> parseLogLevel "Info"
Just Info
>>> parseLogLevel "info"
Just Info
>>> parseLogLevel "errox"
Nothing

showJustifiedLogLevel :: LogLevel -> String Source #

Pretty print a LogLevel in a justified manner, i.e., all outputs take the same amount of characters to display.

>>> showJustifiedLogLevel Debug
"Debug  "
>>> showJustifiedLogLevel Verbose
"Verbose"
>>> showJustifiedLogLevel Info
"Info   "
>>> showJustifiedLogLevel Warning
"Warning"
>>> showJustifiedLogLevel Error
"Error  "

justifyLeft :: Int -> a -> [a] -> [a] Source #

Justify a list with a custom fill symbol

>>> justifyLeft 10 'x' "foo"
"fooxxxxxxx"
>>> justifyLeft 3 'x' "foo"
"foo"
>>> justifyLeft 2 'x' "foo"
"foo"

formatLog :: ThreadId -> LogLevel -> String -> String Source #

Prettily format a log message

threadId <- myThreadId
formatLog Debug threadId "some debug message"

"[DEBUG ] [ThreadId 1277462] some debug message"

formatLogHere :: LogLevel -> String -> IO String Source #

Like formatLog, but instantiates the thread argument with the current ThreadId

formatLogHere Debug "some debug message"

"[DEBUG ] [ThreadId 1440849] some debug message"

shouldLog :: (?verbosity :: LogLevel) => LogLevel -> Bool Source #

Should a message be printed? For a given verbosity level and message log level.

log :: (?verbosity :: LogLevel) => LogLevel -> String -> IO () Source #

Basic logging function. Uses formatLogHere. Is not thread-safe.