module Polysemy.Log.Format where
import qualified Data.Text as Text
import GHC.Exception (SrcLoc (..))
import System.Console.ANSI (Color (..), ColorIntensity (Dull), ConsoleLayer (Foreground), SGR (..), setSGRCode)
import Polysemy.Log.Data.LogEntry (LogEntry (LogEntry))
import qualified Polysemy.Log.Data.LogMessage as LogMessage
import Polysemy.Log.Data.LogMessage (LogMessage (LogMessage))
import Polysemy.Log.Data.Severity (Severity (..))
formatSeverity :: Severity -> Text
formatSeverity :: Severity -> Text
formatSeverity = \case
Severity
Trace -> Text
"[trace]"
Severity
Debug -> Color -> Text -> Text
color Color
Green Text
"[debug]"
Severity
Info -> Color -> Text -> Text
color Color
Blue Text
"[info] "
Severity
Warn -> Color -> Text -> Text
color Color
Yellow Text
"[warn] "
Severity
Error -> Color -> Text -> Text
color Color
Red Text
"[error]"
Severity
Crit -> Color -> Text -> Text
color Color
Magenta Text
"[crit] "
where
color :: Color -> Text -> Text
color Color
c Text
txt =
String -> Text
forall a. ToText a => a -> Text
toText ([SGR] -> String
setSGRCode [ConsoleLayer -> ColorIntensity -> Color -> SGR
SetColor ConsoleLayer
Foreground ColorIntensity
Dull Color
c]) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
String -> Text
forall a. ToText a => a -> Text
toText ([SGR] -> String
setSGRCode [SGR
Item [SGR]
Reset])
shortModule :: Text -> Text
shortModule :: Text -> Text
shortModule =
[Text] -> Text
spin ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
Text.splitOn Text
"."
where
spin :: [Text] -> Text
spin = \case
[] -> Text
""
[Item [Text]
m] -> Text
Item [Text]
m
Text
h : [Text]
t -> Int -> Text -> Text
Text.take Int
1 Text
h Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
spin [Text]
t
formatCaller :: CallStack -> Text
formatCaller :: CallStack -> Text
formatCaller =
Text
-> ((String, SrcLoc) -> Text) -> Maybe (String, SrcLoc) -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"<unknown loc>" (String, SrcLoc) -> Text
forall {a}. (a, SrcLoc) -> Text
format (Maybe (String, SrcLoc) -> Text)
-> (CallStack -> Maybe (String, SrcLoc)) -> CallStack -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(String, SrcLoc)] -> Maybe (String, SrcLoc)
forall a. [a] -> Maybe a
listToMaybe ([(String, SrcLoc)] -> Maybe (String, SrcLoc))
-> (CallStack -> [(String, SrcLoc)])
-> CallStack
-> Maybe (String, SrcLoc)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallStack -> [(String, SrcLoc)]
getCallStack
where
format :: (a, SrcLoc) -> Text
format (a
_, SrcLoc {Int
String
srcLocPackage :: SrcLoc -> String
srcLocModule :: SrcLoc -> String
srcLocFile :: SrcLoc -> String
srcLocStartLine :: SrcLoc -> Int
srcLocStartCol :: SrcLoc -> Int
srcLocEndLine :: SrcLoc -> Int
srcLocEndCol :: SrcLoc -> Int
srcLocEndCol :: Int
srcLocEndLine :: Int
srcLocStartCol :: Int
srcLocStartLine :: Int
srcLocFile :: String
srcLocModule :: String
srcLocPackage :: String
..}) =
Text -> Text
shortModule (String -> Text
forall a. ToText a => a -> Text
toText String
srcLocModule) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall b a. (Show a, IsString b) => a -> b
show Int
srcLocStartLine
formatLogEntry :: LogEntry LogMessage -> Text
formatLogEntry :: LogEntry LogMessage -> Text
formatLogEntry (LogEntry LogMessage {Text
Severity
$sel:message:LogMessage :: LogMessage -> Text
$sel:severity:LogMessage :: LogMessage -> Severity
message :: Text
severity :: Severity
..} UTCTime
_ CallStack
source) =
Severity -> Text
formatSeverity Severity
severity Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" [" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> CallStack -> Text
formatCaller CallStack
source Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"] " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
message