{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UnicodeSyntax #-}
module System.Logger.Types
(
LogLevel(..)
, logLevelText
, readLogLevel
, pLogLevel
, pLogLevel_
, LogPolicy(..)
, logPolicyText
, readLogPolicy
, pLogPolicy
, pLogPolicy_
, LogLabel
, LogScope
, LoggerException(..)
, LogMessage(..)
, logMsg
, logMsgLevel
, logMsgScope
, logMsgTime
, LoggerBackend
, LogFunction
, LogFunctionIO
, LoggerCtx(..)
, LoggerCtxT
, runLoggerCtxT
, MonadLog(..)
, withLabel
, clearScope
, popLabel
) where
import Configuration.Utils hiding (Lens, Lens', Error)
import Control.DeepSeq
import Control.Exception
import Control.Lens hiding ((.=))
import Control.Monad.Base
import Control.Monad.Catch (MonadThrow, MonadCatch, MonadMask)
import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.Trans.Control
import Control.Monad.State
import Control.Monad.Writer
import Control.Monad.Unicode
import qualified Data.CaseInsensitive as CI
import Data.Monoid.Unicode
import Data.String
import qualified Data.Text as T
import Data.Text.Lens
import Data.Typeable
import Data.Void
import GHC.Generics
import qualified Options.Applicative as O
import Prelude.Unicode
import System.Clock
data LogLevel
= Quiet
| Error
| Warn
| Info
| Debug
deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable, Generic)
instance NFData LogLevel
readLogLevel
∷ (MonadError e m, Eq a, Show a, CI.FoldCase a, IsString a, IsString e, Monoid e)
⇒ a
→ m LogLevel
readLogLevel x = case CI.mk x of
"quiet" → return Quiet
"error" → return Error
"warn" → return Warn
"info" → return Info
"debug" → return Debug
e → throwError $ "unexpected log level value: "
⊕ fromString (show e)
⊕ ", expected \"quiet\", \"error\", \"warn\", \"info\", or \"debug\""
logLevelText
∷ IsString a
⇒ LogLevel
→ a
logLevelText Quiet = "quiet"
logLevelText Error = "error"
logLevelText Warn = "warn"
logLevelText Info = "info"
logLevelText Debug = "debug"
instance ToJSON LogLevel where
toJSON = String ∘ logLevelText
instance FromJSON LogLevel where
parseJSON = withText "LogLevel" $ either fail return ∘ readLogLevel
pLogLevel ∷ O.Parser LogLevel
pLogLevel = pLogLevel_ ""
pLogLevel_
∷ T.Text
→ O.Parser LogLevel
pLogLevel_ prefix = option (eitherReader readLogLevel)
× long (T.unpack prefix ⊕ "log-level")
⊕ metavar "quiet|error|warn|info|debug"
⊕ help "threshold for log messages"
data LogPolicy
= LogPolicyDiscard
| LogPolicyRaise
| LogPolicyBlock
deriving (Show, Read, Eq, Ord, Bounded, Enum, Typeable, Generic)
instance NFData LogPolicy
logPolicyText ∷ IsString s ⇒ LogPolicy → s
logPolicyText LogPolicyDiscard = "discard"
logPolicyText LogPolicyRaise = "raise"
logPolicyText LogPolicyBlock = "block"
readLogPolicy
∷ (MonadError e m, Eq a, Show a, CI.FoldCase a, IsText a, IsString e, Monoid e)
⇒ a
→ m LogPolicy
readLogPolicy x = case CI.mk tx of
"discard" → return LogPolicyDiscard
"raise" → return LogPolicyRaise
"block" → return LogPolicyBlock
e → throwError
$ "invalid log policy value " ⊕ fromString (show e) ⊕ ";"
⊕ " the log policy value must be one of \"discard\", \"raise\", or \"block\""
where
tx = packed # x
instance ToJSON LogPolicy where
toJSON = toJSON ∘ (logPolicyText ∷ LogPolicy → T.Text)
instance FromJSON LogPolicy where
parseJSON = withText "LogPolicy" $ either fail return ∘ readLogPolicy
pLogPolicy ∷ O.Parser LogPolicy
pLogPolicy = pLogPolicy_ ""
pLogPolicy_
∷ T.Text
→ O.Parser LogPolicy
pLogPolicy_ prefix = option (eitherReader readLogPolicy)
× long (T.unpack prefix ⊕ "log-policy")
⊕ metavar "block|raise|discard"
⊕ help "how to deal with a congested logging pipeline"
type LogLabel = (T.Text, T.Text)
type LogScope = [LogLabel]
data LoggerException a where
QueueFullException ∷ LogMessage a → LoggerException a
BackendTerminatedException ∷ SomeException → LoggerException Void
BackendTooManyExceptions ∷ [SomeException] → LoggerException Void
deriving (Typeable)
deriving instance Show a ⇒ Show (LoggerException a)
instance (Typeable a, Show a) ⇒ Exception (LoggerException a)
data LogMessage a = LogMessage
{ _logMsg ∷ !a
, _logMsgLevel ∷ !LogLevel
, _logMsgScope ∷ !LogScope
, _logMsgTime ∷ !TimeSpec
}
deriving (Show, Read, Eq, Ord, Typeable, Generic)
logMsg ∷ Lens (LogMessage a) (LogMessage b) a b
logMsg = lens _logMsg $ \a b → a { _logMsg = b }
logMsgLevel ∷ Lens' (LogMessage a) LogLevel
logMsgLevel = lens _logMsgLevel $ \a b → a { _logMsgLevel = b }
logMsgScope ∷ Lens' (LogMessage a) LogScope
logMsgScope = lens _logMsgScope $ \a b → a { _logMsgScope = b }
logMsgTime ∷ Lens' (LogMessage a) TimeSpec
logMsgTime = lens _logMsgTime $ \a b → a { _logMsgTime = b }
instance NFData TimeSpec
instance NFData a ⇒ NFData (LogMessage a)
type LoggerBackend a = Either (LogMessage T.Text) (LogMessage a) → IO ()
type LogFunctionIO a = LogLevel → a → IO ()
type LogFunction a m = LogLevel → a → m ()
class Monad m ⇒ MonadLog a m | m → a where
logg ∷ LogFunction a m
withLevel ∷ LogLevel → m α → m α
withPolicy ∷ LogPolicy → m α → m α
localScope ∷ (LogScope → LogScope) → m α → m α
withLabel ∷ MonadLog a m ⇒ LogLabel → m α → m α
withLabel = localScope ∘ (:)
popLabel ∷ MonadLog a m ⇒ m α → m α
popLabel = localScope $ \case { [] → []; (_:t) → t }
clearScope ∷ MonadLog a m ⇒ m α → m α
clearScope = localScope $ const []
instance (Monoid σ, MonadLog a m) ⇒ MonadLog a (WriterT σ m) where
logg l = lift ∘ logg l
withLevel level inner = liftWith (\run → withLevel level (run inner)) ≫= restoreT ∘ return
withPolicy policy inner = liftWith (\run → withPolicy policy (run inner)) ≫= restoreT ∘ return
localScope f inner = liftWith (\run → localScope f (run inner)) ≫= restoreT ∘ return
{-# INLINE logg #-}
{-# INLINE withLevel #-}
{-# INLINE withPolicy #-}
{-# INLINE localScope #-}
instance (MonadLog a m) ⇒ MonadLog a (ExceptT ε m) where
logg l = lift ∘ logg l
withLevel level inner = liftWith (\run → withLevel level (run inner)) ≫= restoreT ∘ return
withPolicy policy inner = liftWith (\run → withPolicy policy (run inner)) ≫= restoreT ∘ return
localScope f inner = liftWith (\run → localScope f (run inner)) ≫= restoreT ∘ return
{-# INLINE logg #-}
{-# INLINE withLevel #-}
{-# INLINE withPolicy #-}
{-# INLINE localScope #-}
instance (MonadLog a m) ⇒ MonadLog a (StateT σ m) where
logg l = lift ∘ logg l
withLevel level inner = liftWith (\run → withLevel level (run inner)) ≫= restoreT ∘ return
withPolicy policy inner = liftWith (\run → withPolicy policy (run inner)) ≫= restoreT ∘ return
localScope f inner = liftWith (\run → localScope f (run inner)) ≫= restoreT ∘ return
{-# INLINE logg #-}
{-# INLINE withLevel #-}
{-# INLINE withPolicy #-}
{-# INLINE localScope #-}
class LoggerCtx ctx msg | ctx → msg where
loggerFunIO
∷ (Show msg, Typeable msg, NFData msg)
⇒ ctx
→ LogFunctionIO msg
setLoggerLevel ∷ Setter' ctx LogLevel
setLoggerScope ∷ Setter' ctx LogScope
setLoggerPolicy ∷ Setter' ctx LogPolicy
withLoggerLevel ∷ LogLevel → ctx → (ctx → α) → α
withLoggerLevel level ctx f = f $ ctx & setLoggerLevel .~ level
{-# INLINE withLoggerLevel #-}
withLoggerLabel ∷ LogLabel → ctx → (ctx → α) → α
withLoggerLabel label ctx f = f $ ctx & setLoggerScope %~ (:) label
{-# INLINE withLoggerLabel #-}
withLoggerPolicy ∷ LogPolicy → ctx → (ctx → α) → α
withLoggerPolicy policy ctx f = f $ ctx & setLoggerPolicy .~ policy
{-# INLINE withLoggerPolicy #-}
newtype LoggerCtxT ctx m α = LoggerCtxT { unLoggerCtxT ∷ ReaderT ctx m α }
deriving (Functor, Applicative, Monad, MonadIO, MonadTrans, MonadReader ctx, MonadError a, MonadState a, MonadWriter a, MonadBase a, MonadThrow, MonadCatch, MonadMask)
instance MonadTransControl (LoggerCtxT ctx) where
type StT (LoggerCtxT ctx) a = StT (ReaderT ctx) a
liftWith = defaultLiftWith LoggerCtxT unLoggerCtxT
restoreT = defaultRestoreT LoggerCtxT
{-# INLINE liftWith #-}
{-# INLINE restoreT #-}
instance MonadBaseControl b m ⇒ MonadBaseControl b (LoggerCtxT ctx m) where
type StM (LoggerCtxT ctx m) a = ComposeSt (LoggerCtxT ctx) m a
liftBaseWith = defaultLiftBaseWith
restoreM = defaultRestoreM
{-# INLINE liftBaseWith #-}
{-# INLINE restoreM #-}
runLoggerCtxT
∷ LoggerCtxT ctx m α
→ ctx
→ m α
runLoggerCtxT = runReaderT ∘ unLoggerCtxT
{-# INLINE runLoggerCtxT #-}
instance (Show a, Typeable a, NFData a, MonadIO m, LoggerCtx ctx a) ⇒ MonadLog a (LoggerCtxT ctx m) where
logg l m = ask ≫= \ctx → liftIO (loggerFunIO ctx l m)
withLevel level = local $ setLoggerLevel .~ level
withPolicy policy = local $ setLoggerPolicy .~ policy
localScope f = local $ setLoggerScope %~ f
{-# INLINE logg #-}
{-# INLINE withLevel #-}
{-# INLINE withPolicy #-}
{-# INLINE localScope #-}