{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Lumberjack
(
LogAction(..)
, HasLog(..)
, LoggingMonad(..)
, writeLogM
, safeLogAction
, logFilter
, Severity(..)
, LogType(..)
, LogMessage(..)
, msgWith
, WithLog
, withLogTag
, addLogActionTime
, cvtLogMessageToPlainText
, cvtLogMessageToANSITermText
, logFunctionCall, logFunctionCallM
, logProgress, logProgressM
, tshow
, defaultGetIOLogAction
)
where
import qualified Control.Monad.Catch as X
import Control.Monad.IO.Class
import Control.Monad.Reader
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Divisible
import Data.Monoid hiding ( (<>) )
import Data.Semigroup
import Data.Text ( Text, pack, empty )
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import qualified Data.Text.Prettyprint.Doc as PP
import qualified Data.Text.Prettyprint.Doc.Render.Terminal as PP_Term
import qualified Data.Text.Prettyprint.Doc.Render.Text as PP_Text
import Data.Time.Clock ( UTCTime(..), getCurrentTime, diffUTCTime )
import Data.Time.Format ( defaultTimeLocale, formatTime )
import Data.Void
import System.IO ( stderr )
import Prelude
newtype LogAction m msg = LogAction { writeLog :: msg -> m () }
instance Applicative m => Semigroup (LogAction m a) where
LogAction a1 <> LogAction a2 = LogAction $ \a -> a1 a *> a2 a
instance Applicative m => Monoid (LogAction m a) where
mappend = (<>)
mempty = LogAction $ \_ -> pure ()
instance Contravariant (LogAction m) where
contramap f (LogAction a) = LogAction $ a . f
instance (Applicative m) => Divisible (LogAction m) where
conquer = LogAction $ \_ -> pure ()
divide splitf lLog rLog = LogAction $ \i ->
let (l, r) = splitf i
ll = writeLog lLog l
rl = writeLog rLog r
in ll *> rl
instance (Applicative m) => Decidable (LogAction m) where
lose f = LogAction $ \a -> absurd (f a)
choose split l r = LogAction $ either (writeLog l) (writeLog r) . split
class Monad m => HasLog msg m where
getLogAction :: m (LogAction m msg)
class (Monad m, HasLog msg m) => LoggingMonad msg m where
adjustLogAction :: (forall k. LogAction k msg -> LogAction k msg) -> m a -> m a
writeLogM :: HasLog msg m => msg -> m ()
writeLogM m = getLogAction >>= flip writeLog m
safeLogAction :: X.MonadCatch m => LogAction m msg -> LogAction m msg
safeLogAction a = LogAction $ \m -> X.catch (writeLog a m) (\(_ex :: X.SomeException) -> return ())
logFilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg
logFilter f (LogAction l) = LogAction $ \m -> when (f m) (l m)
data Severity = Debug | Info | Warning | Error deriving (Ord, Eq, Show)
data LogType = Progress | FuncEntry | FuncExit | MiscLog | UserOp
deriving (Eq, Show)
data LogMessage = LogMessage { logType :: LogType
, logLevel :: Severity
, logTime :: UTCTime
, logTags :: [(Text, Text)]
, logText :: Text
}
instance Semigroup LogMessage where
a <> b = LogMessage { logType = if logType a == MiscLog then logType b else logType a
, logLevel = max (logLevel a) (logLevel b)
, logTime = max (logTime a) (logTime b)
, logTags = logTags a <> logTags b
, logText = case (T.null (logText a), T.null (logText b)) of
(False, False) -> logText a <> "; " <> logText b
(True, False) -> logText b
_ -> logText a
}
instance Monoid LogMessage where
mempty = LogMessage MiscLog Debug (UTCTime (toEnum 0) (toEnum 0)) [] empty
mappend = (<>)
msgWith :: LogMessage
msgWith = mempty
addLogActionTime :: MonadIO m => LogAction m LogMessage -> LogAction m LogMessage
addLogActionTime a = LogAction $ \m -> do t <- liftIO getCurrentTime
writeLog a $ m <> mempty { logTime = t }
type WithLog msg m = ( HasLog msg m)
withLogTag :: (LoggingMonad LogMessage m) => Text -> Text -> m a -> m a
withLogTag tname tval op =
let tagmsg = mempty { logTags = [(tname, tval)] }
in (adjustLogAction $ contramap (tagmsg <>)) op
data PrettyLogAnn = AnnLogType LogType
| AnnSeverity Severity
| AnnTime
| AnnTimeMinSec
| AnnTag
| AnnTagVal
instance PP.Pretty LogType where pretty = anyPrettyLogType
anyPrettyLogType :: LogType -> PP.Doc ann
anyPrettyLogType Progress = PP.pretty ("progress" :: Text)
anyPrettyLogType FuncEntry = PP.pretty ("entered" :: Text)
anyPrettyLogType FuncExit = PP.pretty ("completed" :: Text)
anyPrettyLogType UserOp = PP.pretty ("User-Op" :: Text)
anyPrettyLogType MiscLog = PP.pretty ("misc" :: Text)
prettyLogType :: LogType -> PP.Doc PrettyLogAnn
prettyLogType t = PP.annotate (AnnLogType t) $ anyPrettyLogType t
instance PP.Pretty Severity where pretty = anyPrettySev
anyPrettySev :: Severity -> PP.Doc ann
anyPrettySev Error = PP.pretty ("ERR " :: Text)
anyPrettySev Warning = PP.pretty ("Warn" :: Text)
anyPrettySev Info = PP.pretty ("I " :: Text)
anyPrettySev Debug = PP.pretty ("Dbg " :: Text)
prettySev :: Severity -> PP.Doc PrettyLogAnn
prettySev s = PP.annotate (AnnSeverity s) $ anyPrettySev s
instance PP.Pretty UTCTime where
pretty t = PP.hcat [ PP.pretty (formatTime defaultTimeLocale "%Z-%F:%H:" t)
, PP.pretty (formatTime defaultTimeLocale "%M:%S" t)
, PP.pretty (take 4 (formatTime defaultTimeLocale ".%q" t))
]
prettyTime :: UTCTime -> PP.Doc PrettyLogAnn
prettyTime t =
if t == UTCTime (toEnum 0) (toEnum 0)
then PP.annotate AnnTime $ PP.emptyDoc
else PP.hcat
[ PP.annotate AnnTime $ PP.pretty (formatTime defaultTimeLocale "%Z-%F_%H:" t)
, PP.annotate AnnTimeMinSec $ PP.pretty (formatTime defaultTimeLocale "%M:%S" t)
, PP.annotate AnnTime $ PP.pretty (take 4 (formatTime defaultTimeLocale ".%q" t))
]
anyPrettyTags :: [(Text, Text)] -> PP.Doc ann
anyPrettyTags =
let anyPrettyTag (tag, val) = PP.group $ PP.cat [ PP.pretty tag
, PP.equals
, PP.pretty val
]
in foldl (\acc tagval -> acc PP.<+> (anyPrettyTag tagval)) mempty
prettyTags :: [(Text, Text)] -> PP.Doc PrettyLogAnn
prettyTags =
let ppTag (tag, val) = PP.group $ PP.hcat [ PP.annotate AnnTag $ PP.pretty tag
, PP.equals
, PP.annotate AnnTagVal $ PP.pretty val
]
in foldl (\acc tagval -> acc PP.<+> (ppTag tagval)) mempty
prettyLogMessage :: LogMessage -> PP.Doc PrettyLogAnn
prettyLogMessage (LogMessage {..}) = PP.hsep [ prettyTime logTime
, prettySev logLevel
, PP.brackets (prettyLogType logType)
, prettyTags logTags
, PP.pretty logText
]
instance PP.Pretty LogMessage where
pretty (LogMessage {..}) = PP.hsep [ PP.pretty logTime
, PP.pretty logLevel
, PP.brackets (PP.pretty logType)
, anyPrettyTags logTags
, PP.pretty logText
]
termStyle :: PrettyLogAnn -> PP_Term.AnsiStyle
termStyle (AnnLogType Progress) = PP_Term.colorDull PP_Term.Green
termStyle (AnnLogType FuncEntry) = PP_Term.colorDull PP_Term.Magenta
termStyle (AnnLogType FuncExit) = PP_Term.colorDull PP_Term.Cyan
termStyle (AnnLogType UserOp) = PP_Term.bold <> PP_Term.color PP_Term.Green
termStyle (AnnLogType MiscLog) = mempty
termStyle (AnnSeverity Error) = PP_Term.bold <> PP_Term.color PP_Term.Red <> PP_Term.bgColor PP_Term.Yellow
termStyle (AnnSeverity Warning) = PP_Term.bold <> PP_Term.colorDull PP_Term.Red
termStyle (AnnSeverity Info) = mempty
termStyle (AnnSeverity Debug) = PP_Term.color PP_Term.Blue
termStyle AnnTime = mempty
termStyle AnnTimeMinSec = PP_Term.color PP_Term.White <> PP_Term.bold
termStyle AnnTag = PP_Term.color PP_Term.Black <> PP_Term.bold
termStyle AnnTagVal = PP_Term.color PP_Term.Black <> PP_Term.bold
cvtLogMessageToANSITermText :: LogMessage -> Text
cvtLogMessageToANSITermText = PP_Term.renderStrict .
PP.reAnnotateS termStyle .
PP.layoutSmart PP.defaultLayoutOptions .
prettyLogMessage
cvtLogMessageToPlainText :: LogMessage -> Text
cvtLogMessageToPlainText = PP_Text.renderStrict .
PP.layoutSmart PP.defaultLayoutOptions .
prettyLogMessage
logFunctionCall :: (MonadIO m) => LogAction m LogMessage -> Text -> m a -> m a
logFunctionCall = logFunctionCallWith . writeLog
logFunctionCallM :: (MonadIO m, WithLog LogMessage m) => Text -> m a -> m a
logFunctionCallM = logFunctionCallWith writeLogM
logFunctionCallWith :: (MonadIO m) => (LogMessage -> m ()) -> Text -> m a -> m a
logFunctionCallWith logger fName f =
do logger $ msgWith { logType = FuncEntry, logText = fName }
t <- liftIO getCurrentTime
r <- f
t' <- liftIO getCurrentTime
let dt = diffUTCTime t' t
logger $ msgWith { logType = FuncExit, logLevel = Info
, logText = fName <> ", executed for " <> pack (show dt) }
return r
logProgress :: (MonadIO m) => LogAction m LogMessage -> Text -> m ()
logProgress action txt = writeLog action $ msgWith { logLevel = Info, logType = Progress, logText = txt }
logProgressM :: (MonadIO m, WithLog LogMessage m) => Text -> m ()
logProgressM txt = writeLogM $ msgWith { logLevel = Info, logType = Progress, logText = txt }
tshow :: (Show a) => a -> Text
tshow = pack . show
defaultGetIOLogAction :: MonadIO m => LogAction m T.Text
defaultGetIOLogAction = LogAction $ liftIO . TIO.hPutStrLn stderr