{-# LANGUAGE TemplateHaskell #-} {- | Logger type definitions -} module LuminescentDreams.Logger.Types where import Control.Lens import qualified Data.Text.Buildable as TFB import qualified Data.Text as T {- | An ordinary hierarchy of logging priorities. -} data LogLevel = LogDebug | LogInfo | LogWarning | LogError | LogEmergency deriving (Eq, Ord, Show) tzFormat :: String tzFormat = "%Y-%m-%dT%H:%M:%S%Q%z" {- | The primary data structure to contain a logger of any kind. -} data Logger = Logger { _logCmd :: (T.Text -> IO ()) -- ^ Any IO action that accepts the log message , _logLvl :: LogLevel , _logApp :: T.Text , _logTags :: [T.Text] -- ^ The minimum level at which a log message should be accepted } {- | Generate standard text representations of a log level. This is useful to the Standard logger but may not be interesting to any others. -} instance TFB.Buildable LogLevel where build LogDebug = TFB.build ("DEBUG" :: String) build LogInfo = TFB.build ("INFO" :: String) build LogWarning = TFB.build ("WARNING" :: String) build LogError = TFB.build ("ERROR" :: String) build LogEmergency = TFB.build ("EMERGENCY" :: String) makeLenses ''Logger