module Network.Wai.Middleware.FilterLogger.Internal where
import Control.Monad
import Data.Aeson
import Data.Aeson.Encode.Pretty
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS hiding (ByteString)
import qualified Data.ByteString.Lazy as BL (ByteString,
fromStrict,
toStrict)
import Data.Char
import Data.Default
import Data.Semigroup
import Data.Word
import Network.HTTP.Types.Status
import Network.Wai
import Network.Wai.Middleware.RequestLogger
import System.IO.Unsafe
import System.Log.FastLogger
import Text.Printf (printf)
class LogShowable a where
logShow :: a -> ByteString
instance LogShowable ByteString where
logShow = id
instance LogShowable BL.ByteString where
logShow = BL.toStrict
logShowJSON :: (ToJSON a) => a -> ByteString
logShowJSON = BL.toStrict . encodePretty
logFilterJSON :: (FromJSON a) => ByteString -> Maybe a
logFilterJSON = decodeStrict'
class LogFilterable a where
prep :: ByteString -> Maybe a
instance LogFilterable ByteString where
prep = return
instance LogFilterable BL.ByteString where
prep = return . BL.fromStrict
class (LogFilterable a, LogShowable a) => Loggable a where
instance Loggable ByteString where
instance Loggable BL.ByteString where
type LogFilter a = a -> Maybe a
logFilter :: (Loggable a) => ByteString -> LogFilter a -> Maybe a
logFilter bs lf = prep bs >>= lf
mkFilterLogger :: (Loggable a) => Bool -> LogFilter a -> Middleware
mkFilterLogger detailed lf = unsafePerformIO $
mkRequestLogger def { outputFormat = CustomOutputFormatWithDetails $ customOutputFormatter detailed lf }
customOutputFormatter :: (Loggable a) => Bool -> LogFilter a -> OutputFormatterWithDetails
customOutputFormatter detail lf date req status responseSize time reqBody builder =
maybe mempty (logString detail) $ logFilter (BS.concat reqBody) lf
where
toBS = BS.pack . map (fromIntegral . ord)
dfromRational :: Rational -> Double
dfromRational = fromRational
inMS = printf "%.2f" . dfromRational $ toRational time * 1000
header = date <> "\n" <>
toBS (show . fromIntegral $ statusCode status) <> " - " <> statusMessage status <> "\n"
buildRespSize (Just s) = "Response Size: " <> toBS (show s) <> "\n"
buildRespSize Nothing = ""
buildDuration = toBS inMS <> "ms" <> "\n"
buildDetails True = buildRespSize responseSize <> buildDuration
buildDetails False = ""
logString detailed msg = toLogStr (
header <>
buildDetails detail <>
logShow msg <>
"\n")