module System.Wlog.LoggerConfig
( LoggerMap
, RotationParameters (..)
, fromScratch
, isValidRotation
, LoggerTree (..)
, ltFiles
, ltSeverity
, ltSubloggers
, LoggerConfig (..)
, lcConsoleOutput
, lcFilePrefix
, lcMapper
, lcMemModeLimit
, lcRotation
, lcShowTime
, lcTermSeverity
, lcTree
, lcRoundVal
, zoomLogger
, consoleOutB
, mapperB
, memoryB
, prefixB
, productionB
, showTimeB
) where
import Universum
import Control.Lens (at, makeLenses, zoom, _Just)
import Control.Monad.State (put)
import Data.Aeson (withObject)
import qualified Data.HashMap.Strict as HM hiding (HashMap)
import Data.List (notElem)
import Data.Monoid (Any (..))
import Data.Text (Text)
import qualified Data.Text.Buildable as Buildable
import Data.Traversable (for)
import Data.Word (Word64)
import Data.Yaml (FromJSON (..), ToJSON (..), Value (Object),
object, (.!=), (.:), (.:?), (.=))
import Formatting (bprint, shown)
import GHC.Generics (Generic)
import System.Wlog.LoggerName (LoggerName)
import System.Wlog.Wrapper (Severity)
filterObject :: [Text] -> HashMap Text a -> HashMap Text a
filterObject excluded = HM.filterWithKey $ \k _ -> k `notElem` excluded
fromScratch :: Monoid m => State m a -> m
fromScratch = executingState mempty
type LoggerMap = HashMap Text LoggerTree
data LoggerTree = LoggerTree
{ _ltSubloggers :: !LoggerMap
, _ltFiles :: ![FilePath]
, _ltSeverity :: !(Maybe Severity)
} deriving (Generic, Show)
makeLenses ''LoggerTree
instance Monoid LoggerTree where
mempty = LoggerTree
{ _ltFiles = []
, _ltSeverity = Nothing
, _ltSubloggers = mempty
}
lt1 `mappend` lt2 = LoggerTree
{ _ltFiles = _ltFiles lt1 <> _ltFiles lt2
, _ltSeverity = _ltSeverity lt1 <|> _ltSeverity lt2
, _ltSubloggers = _ltSubloggers lt1 <> _ltSubloggers lt2
}
nonLoggers :: [Text]
nonLoggers = ["file", "files", "severity"]
instance ToJSON LoggerTree
instance FromJSON LoggerTree where
parseJSON = withObject "loggers tree" $ \o -> do
(singleFile :: Maybe FilePath) <- o .:? "file"
(manyFiles :: [FilePath]) <- o .:? "files" .!= []
let _ltFiles = maybe [] (:[]) singleFile ++ manyFiles
_ltSeverity <- o .:? "severity"
_ltSubloggers <- for (filterObject nonLoggers o) parseJSON
return LoggerTree{..}
zoomLogger :: Text -> State LoggerTree () -> State LoggerTree ()
zoomLogger loggerName initializer = zoom (ltSubloggers.at loggerName) $ do
put $ Just mempty
zoom _Just initializer
data RotationParameters = RotationParameters
{ rpLogLimit :: !Word64
, rpKeepFiles :: !Word
} deriving (Generic, Show)
instance Buildable.Buildable RotationParameters where
build = bprint shown
instance ToJSON RotationParameters
instance FromJSON RotationParameters where
parseJSON = withObject "rotation params" $ \o -> do
rpLogLimit <- o .: "logLimit"
rpKeepFiles <- o .: "keepFiles"
return RotationParameters{..}
isValidRotation :: RotationParameters -> Bool
isValidRotation RotationParameters{..} = rpLogLimit > 0 && rpKeepFiles > 0
data LoggerConfig = LoggerConfig
{
_lcRotation :: Maybe RotationParameters
, _lcTermSeverity :: Maybe Severity
, _lcShowTime :: Any
, _lcConsoleOutput :: Any
, _lcMapper :: Endo LoggerName
, _lcFilePrefix :: Maybe FilePath
, _lcMemModeLimit :: Maybe Word64
, _lcTree :: LoggerTree
, _lcRoundVal :: Maybe Int
}
makeLenses ''LoggerConfig
instance Monoid LoggerConfig where
mempty = LoggerConfig
{ _lcRotation = Nothing
, _lcTermSeverity = Nothing
, _lcShowTime = mempty
, _lcConsoleOutput = mempty
, _lcMapper = mempty
, _lcFilePrefix = mempty
, _lcMemModeLimit = Nothing
, _lcTree = mempty
, _lcRoundVal = Nothing
}
lc1 `mappend` lc2 = LoggerConfig
{ _lcRotation = _lcRotation lc1 <|> _lcRotation lc2
, _lcTermSeverity = _lcTermSeverity lc1 <|> _lcTermSeverity lc2
, _lcShowTime = _lcShowTime lc1 <> _lcShowTime lc2
, _lcConsoleOutput = _lcConsoleOutput lc1 <> _lcConsoleOutput lc2
, _lcMapper = _lcMapper lc1 <> _lcMapper lc2
, _lcFilePrefix = _lcFilePrefix lc1 <|> _lcFilePrefix lc2
, _lcMemModeLimit = _lcMemModeLimit lc1 <|> _lcMemModeLimit lc2
, _lcTree = _lcTree lc1 <> _lcTree lc2
, _lcRoundVal = _lcRoundVal lc1 `max` _lcRoundVal lc2
}
topLevelParams :: [Text]
topLevelParams =
["rotation", "showTime", "printOutput", "filePrefix", "memModeLimit", "roundTime"]
instance FromJSON LoggerConfig where
parseJSON = withObject "rotation params" $ \o -> do
_lcRotation <- o .:? "rotation"
_lcTermSeverity <- o .:? "termSeverity"
_lcShowTime <- Any <$> o .:? "showTime" .!= False
_lcConsoleOutput <- Any <$> o .:? "printOutput" .!= False
_lcFilePrefix <- o .:? "filePrefix"
_lcMemModeLimit <- o .:? "memModeLimit"
_lcTree <- parseJSON $ Object $ filterObject topLevelParams o
_lcRoundVal <- o .:? "roundTime"
let _lcMapper = mempty
return LoggerConfig{..}
instance ToJSON LoggerConfig where
toJSON LoggerConfig{..} = object
[ "rotation" .= _lcRotation
, "termSeverity" .= _lcTermSeverity
, "showTime" .= getAny _lcShowTime
, "printOutput" .= getAny _lcConsoleOutput
, "filePrefix" .= _lcFilePrefix
, "memModeLimit" .= _lcMemModeLimit
, ("logTree", toJSON _lcTree)
]
showTimeB :: Bool -> LoggerConfig
showTimeB isShowTime = mempty { _lcShowTime = Any isShowTime }
consoleOutB :: Bool -> LoggerConfig
consoleOutB printToConsole = mempty { _lcConsoleOutput = Any printToConsole }
productionB :: LoggerConfig
productionB = showTimeB True <> consoleOutB True
mapperB :: (LoggerName -> LoggerName) -> LoggerConfig
mapperB loggerNameMapper = mempty { _lcMapper = Endo loggerNameMapper }
prefixB :: FilePath -> LoggerConfig
prefixB filePrefix = mempty { _lcFilePrefix = Just filePrefix }
memoryB :: Word64 -> LoggerConfig
memoryB limit = mempty { _lcMemModeLimit = Just limit }