Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Debugger.Logger
Description
Simple Logger API using co-log style loggers
Synopsis
- data Recorder msg
- logWith :: (HasCallStack, MonadIO m) => Recorder (WithSeverity msg) -> Severity -> msg -> m ()
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- newtype LogAction (m :: Type -> Type) msg = LogAction {
- unLogAction :: msg -> m ()
- toCologAction :: forall (m :: Type -> Type) msg. (MonadIO m, HasCallStack) => Recorder msg -> LogAction m msg
- fromCologAction :: HasCallStack => LogAction IO msg -> Recorder msg
- data Severity
- data WithSeverity msg = WithSeverity {
- getMsg :: msg
- getSeverity :: Severity
- cmap :: (a -> b) -> Recorder b -> Recorder a
- cmapIO :: (a -> IO b) -> Recorder b -> Recorder a
- cmapWithSev :: (a -> b) -> Recorder (WithSeverity b) -> Recorder (WithSeverity a)
- renderPrettyWithSeverity :: Pretty a => WithSeverity a -> Text
- renderWithSeverity :: (a -> Text) -> WithSeverity a -> Text
- renderPretty :: Pretty a => a -> Text
- renderSeverity :: Severity -> Text
- renderWithTimestamp :: Text -> IO Text
- class Contravariant (f :: Type -> Type) where
- contramap :: (a' -> a) -> f a -> f a'
The core Logger type
logWith :: (HasCallStack, MonadIO m) => Recorder (WithSeverity msg) -> Severity -> msg -> m () Source #
Log messages
Minimal complete definition
Methods
>>>
pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234
prettyList :: [a] -> Doc ann #
is only used to define the prettyList
instance
. In normal circumstances only the Pretty
a => Pretty
[a]
function is used.pretty
>>>
prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Void # | Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.
|
Defined in Prettyprinter.Internal | |
Pretty Int16 # | |
Defined in Prettyprinter.Internal | |
Pretty Int32 # | |
Defined in Prettyprinter.Internal | |
Pretty Int64 # | |
Defined in Prettyprinter.Internal | |
Pretty Int8 # | |
Defined in Prettyprinter.Internal | |
Pretty Word16 # | |
Defined in Prettyprinter.Internal | |
Pretty Word32 # | |
Defined in Prettyprinter.Internal | |
Pretty Word64 # | |
Defined in Prettyprinter.Internal | |
Pretty Word8 # | |
Defined in Prettyprinter.Internal | |
Pretty DebuggerLog Source # | |
Defined in GHC.Debugger | |
Pretty EvalLog Source # | |
Defined in GHC.Debugger.Evaluation | |
Pretty Log # | |
Defined in HIE.Bios.Ghc.Check | |
Pretty Log # | |
Defined in HIE.Bios.Ghc.Load | |
Pretty Log # | |
Defined in HIE.Bios.Types | |
Pretty Text # | Automatically converts all newlines to
Note that
Manually use |
Defined in Prettyprinter.Internal | |
Pretty Text # | (lazy |
Defined in Prettyprinter.Internal | |
Pretty Integer # |
|
Defined in Prettyprinter.Internal | |
Pretty Natural # | |
Defined in Prettyprinter.Internal | |
Pretty () # |
The argument is not used:
|
Defined in Prettyprinter.Internal | |
Pretty Bool # |
|
Defined in Prettyprinter.Internal | |
Pretty Char # | Instead of
|
Defined in Prettyprinter.Internal | |
Pretty Double # |
|
Defined in Prettyprinter.Internal | |
Pretty Float # |
|
Defined in Prettyprinter.Internal | |
Pretty Int # |
|
Defined in Prettyprinter.Internal | |
Pretty Word # | |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (NonEmpty a) # | |
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Identity a) # |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Maybe a) # | Ignore
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty [a] # |
|
Defined in Prettyprinter.Internal | |
(Pretty a1, Pretty a2) => Pretty (a1, a2) # |
|
Defined in Prettyprinter.Internal | |
Pretty a => Pretty (Const a b) # | |
Defined in Prettyprinter.Internal | |
(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) # |
|
Defined in Prettyprinter.Internal |
For simpler usage
newtype LogAction (m :: Type -> Type) msg #
Polymorphic and very general logging action type.
msg
type variables is an input for logger. It can beText
or custom logging messsage with different fields that you want to format in future.m
type variable is for monadic action inside which logging is happening. It can be eitherIO
or some custom pure monad.
Key design point here is that LogAction
is:
Constructors
LogAction | |
Fields
|
Instances
Contravariant (LogAction m) # | |
UnrepresentableClass => Functor (LogAction m) # | ⚠️CAUTION⚠️ This instance is for custom error display only.
In case it is used by mistake, the user will see the following:
# 207 "srcCologCore/Action.hs" Since: co-log-core-0.2.1.0 |
Applicative m => Monoid (LogAction m a) # | |
Applicative m => Semigroup (LogAction m a) # | This instance allows you to join multiple logging actions into single one. For example, if you have two actions like these: logToStdout :: You can create new logToBoth :: |
HasLog (LogAction m msg) msg m # | |
Defined in Colog.Core.Class Methods getLogAction :: LogAction m msg -> LogAction m msg # setLogAction :: LogAction m msg -> LogAction m msg -> LogAction m msg # overLogAction :: (LogAction m msg -> LogAction m msg) -> LogAction m msg -> LogAction m msg # logActionL :: Lens' (LogAction m msg) (LogAction m msg) # |
toCologAction :: forall (m :: Type -> Type) msg. (MonadIO m, HasCallStack) => Recorder msg -> LogAction m msg Source #
fromCologAction :: HasCallStack => LogAction IO msg -> Recorder msg Source #
Severity
Severity for the log messages.
Constructors
Debug | Information useful for debug purposes. E.g. output of the function that is important for the internal development, not for users. Like, the result of SQL query. |
Info | Normal operational information. E.g. describing general steps: starting application, finished downloading. |
Warning | General warnings, non-critical failures. E.g. couldn't download icon from some service to display. |
Error | General errors/severe errors. E.g. exceptional situations: couldn't syncronize accounts. |
Instances
Eq Severity # | |
Ord Severity # | |
Defined in Colog.Core.Severity | |
Bounded Severity # | |
Enum Severity # | |
Defined in Colog.Core.Severity | |
Ix Severity # | |
Defined in Colog.Core.Severity Methods range :: (Severity, Severity) -> [Severity] # index :: (Severity, Severity) -> Severity -> Int # unsafeIndex :: (Severity, Severity) -> Severity -> Int # inRange :: (Severity, Severity) -> Severity -> Bool # rangeSize :: (Severity, Severity) -> Int # unsafeRangeSize :: (Severity, Severity) -> Int # | |
Read Severity # | |
Show Severity # | |
data WithSeverity msg #
A message tagged with a Severity
.
It is common to want to log various types of messages tagged with a severity.
WithSeverity
provides a standard way to do so while allowing the messages to be processed independently of the severity.
It is easy to cmap
over a 'LogAction m (WithSeverity a)', or to filter based on the severity.
logSomething ::LogAction
m (WithSeverity
String
) -> m () logSomething logger = logger <& "hello" `WithSeverity`Info
cmap' :: (b -> a) ->LogAction
m (WithSeverity
a) ->LogAction
m (WithSeverity
b) cmap' f action =cmap
(fmap
f) action filterBySeverity' :: (Applicative
m) =>Severity
->LogAction
m (WithSeverity
a) ->LogAction
m (WithSeverity
a) filterBySeverity' threshold action =filterBySeverity
thresholdgetSeverity
action
Since: co-log-core-0.3.1.0
Constructors
WithSeverity | |
Fields
|
Instances
cmapWithSev :: (a -> b) -> Recorder (WithSeverity b) -> Recorder (WithSeverity a) Source #
Pretty printing of logs
renderPrettyWithSeverity :: Pretty a => WithSeverity a -> Text Source #
renderWithSeverity :: (a -> Text) -> WithSeverity a -> Text Source #
renderPretty :: Pretty a => a -> Text Source #
renderSeverity :: Severity -> Text Source #
class Contravariant (f :: Type -> Type) where #
The class of contravariant functors.
Whereas in Haskell, one can think of a Functor
as containing or producing
values, a contravariant functor is a functor that can be thought of as
consuming values.
As an example, consider the type of predicate functions a -> Bool
. One
such predicate might be negative x = x < 0
, which
classifies integers as to whether they are negative. However, given this
predicate, we can re-use it in other situations, providing we have a way to
map values to integers. For instance, we can use the negative
predicate
on a person's bank balance to work out if they are currently overdrawn:
newtype Predicate a = Predicate { getPredicate :: a -> Bool } instance Contravariant Predicate where contramap :: (a' -> a) -> (Predicate a -> Predicate a') contramap f (Predicate p) = Predicate (p . f) | `- First, map the input... `----- then apply the predicate. overdrawn :: Predicate Person overdrawn = contramap personBankBalance negative
Any instance should be subject to the following laws:
Note, that the second law follows from the free theorem of the type of
contramap
and the first law, so you need only check that the former
condition holds.