{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe #-}

module System.Log.FastLogger.LogStr (
    Builder
  , LogStr(..)
  , logStrLength
  , fromLogStr
  , ToLogStr(..)
  , mempty
  , (<>)
  ) where

import qualified Data.ByteString as BS
import Data.ByteString.Builder (Builder)
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Char8 as S8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Short as SBS
#if MIN_VERSION_base(4,9,0)
import qualified Data.Semigroup as Semi (Semigroup(..))
#endif
import Data.String (IsString(..))
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL

import System.Log.FastLogger.Imports

----------------------------------------------------------------

toBuilder :: ByteString -> Builder
toBuilder :: ByteString -> Builder
toBuilder = ByteString -> Builder
B.byteString

fromBuilder :: Builder -> ByteString
#if MIN_VERSION_bytestring(0,10,0)
fromBuilder :: Builder -> ByteString
fromBuilder = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString
#else
fromBuilder = BS.concat . BL.toChunks . B.toLazyByteString
#endif

----------------------------------------------------------------

-- | Log message builder. Use ('<>') to append two LogStr in O(1).
data LogStr = LogStr !Int Builder

#if MIN_VERSION_base(4,9,0)
instance Semi.Semigroup LogStr where
    {-# INLINE (<>) #-}
    LogStr Int
s1 Builder
b1 <> :: LogStr -> LogStr -> LogStr
<> LogStr Int
s2 Builder
b2 = Int -> Builder -> LogStr
LogStr (Int
s1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) (Builder
b1 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
b2)
#endif

instance Monoid LogStr where
    mempty :: LogStr
mempty = Int -> Builder -> LogStr
LogStr Int
0 (ByteString -> Builder
toBuilder ByteString
BS.empty)
    {-# INLINE mappend #-}
    LogStr Int
s1 Builder
b1 mappend :: LogStr -> LogStr -> LogStr
`mappend` LogStr Int
s2 Builder
b2 = Int -> Builder -> LogStr
LogStr (Int
s1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s2) (Builder
b1 Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
b2)

instance IsString LogStr where
    {-# INLINE fromString #-}
    fromString :: String -> LogStr
fromString = Text -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Text -> LogStr) -> (String -> Text) -> String -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
TL.pack

-- | Types that can be converted to a 'LogStr'. Instances for
-- types from the @text@ library use a UTF-8 encoding. Instances
-- for numerical types use a decimal encoding.
class ToLogStr msg where
    toLogStr :: msg -> LogStr

instance ToLogStr LogStr where
    {-# INLINE toLogStr #-}
    toLogStr :: LogStr -> LogStr
toLogStr = LogStr -> LogStr
forall a. a -> a
id
instance ToLogStr S8.ByteString where
    {-# INLINE toLogStr #-}
    toLogStr :: ByteString -> LogStr
toLogStr ByteString
bs = Int -> Builder -> LogStr
LogStr (ByteString -> Int
BS.length ByteString
bs) (ByteString -> Builder
toBuilder ByteString
bs)
instance ToLogStr BL.ByteString where
    {-# INLINE toLogStr #-}
    toLogStr :: ByteString -> LogStr
toLogStr ByteString
b = Int -> Builder -> LogStr
LogStr (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BL.length ByteString
b)) (ByteString -> Builder
B.lazyByteString ByteString
b)
instance ToLogStr Builder where
    {-# INLINE toLogStr #-}
    toLogStr :: Builder -> LogStr
toLogStr Builder
x = let b :: ByteString
b = Builder -> ByteString
B.toLazyByteString Builder
x in Int -> Builder -> LogStr
LogStr (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int64
BL.length ByteString
b)) (ByteString -> Builder
B.lazyByteString ByteString
b)
instance ToLogStr SBS.ShortByteString where
    {-# INLINE toLogStr #-}
    toLogStr :: ShortByteString -> LogStr
toLogStr ShortByteString
b = Int -> Builder -> LogStr
LogStr (ShortByteString -> Int
SBS.length ShortByteString
b) (ShortByteString -> Builder
B.shortByteString ShortByteString
b)
instance ToLogStr String where
    {-# INLINE toLogStr #-}
    toLogStr :: String -> LogStr
toLogStr = Text -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Text -> LogStr) -> (String -> Text) -> String -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
TL.pack
instance ToLogStr T.Text where
    {-# INLINE toLogStr #-}
    toLogStr :: Text -> LogStr
toLogStr = ByteString -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (ByteString -> LogStr) -> (Text -> ByteString) -> Text -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
instance ToLogStr TL.Text where
    {-# INLINE toLogStr #-}
    toLogStr :: Text -> LogStr
toLogStr = ByteString -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (ByteString -> LogStr) -> (Text -> ByteString) -> Text -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
TL.encodeUtf8

-- | @since 2.4.14
instance ToLogStr Int where
    {-# INLINE toLogStr #-}
    toLogStr :: Int -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Int -> Builder) -> Int -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Builder
B.intDec
-- | @since 2.4.14
instance ToLogStr Int8 where
    {-# INLINE toLogStr #-}
    toLogStr :: Int8 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Int8 -> Builder) -> Int8 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Builder
B.int8Dec
-- | @since 2.4.14
instance ToLogStr Int16 where
    {-# INLINE toLogStr #-}
    toLogStr :: Int16 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Int16 -> Builder) -> Int16 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Builder
B.int16Dec
-- | @since 2.4.14
instance ToLogStr Int32 where
    {-# INLINE toLogStr #-}
    toLogStr :: Int32 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Int32 -> Builder) -> Int32 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Builder
B.int32Dec
-- | @since 2.4.14
instance ToLogStr Int64 where
    {-# INLINE toLogStr #-}
    toLogStr :: Int64 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Int64 -> Builder) -> Int64 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Builder
B.int64Dec

-- | @since 2.4.14
instance ToLogStr Word where
    {-# INLINE toLogStr #-}
    toLogStr :: Word -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Word -> Builder) -> Word -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Builder
B.wordDec
-- | @since 2.4.14
instance ToLogStr Word8 where
    {-# INLINE toLogStr #-}
    toLogStr :: Word8 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Word8 -> Builder) -> Word8 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Builder
B.word8Dec
-- | @since 2.4.14
instance ToLogStr Word16 where
    {-# INLINE toLogStr #-}
    toLogStr :: Word16 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Word16 -> Builder) -> Word16 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Builder
B.word16Dec
-- | @since 2.4.14
instance ToLogStr Word32 where
    {-# INLINE toLogStr #-}
    toLogStr :: Word32 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Word32 -> Builder) -> Word32 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Builder
B.word32Dec
-- | @since 2.4.14
instance ToLogStr Word64 where
    {-# INLINE toLogStr #-}
    toLogStr :: Word64 -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Word64 -> Builder) -> Word64 -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Builder
B.word64Dec

-- | @since 2.4.14
instance ToLogStr Integer where
    {-# INLINE toLogStr #-}
    toLogStr :: Integer -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Integer -> Builder) -> Integer -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Builder
B.integerDec
-- | @since 2.4.14
instance ToLogStr Float where
    {-# INLINE toLogStr #-}
    toLogStr :: Float -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Float -> Builder) -> Float -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Builder
B.floatDec
-- | @since 2.4.14
instance ToLogStr Double where
    {-# INLINE toLogStr #-}
    toLogStr :: Double -> LogStr
toLogStr = Builder -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (Builder -> LogStr) -> (Double -> Builder) -> Double -> LogStr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Builder
B.doubleDec

instance Show LogStr where
  show :: LogStr -> String
show = Text -> String
forall a. Show a => a -> String
show (Text -> String) -> (LogStr -> Text) -> LogStr -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> (LogStr -> ByteString) -> LogStr -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogStr -> ByteString
fromLogStr

instance Eq LogStr where
  LogStr
a == :: LogStr -> LogStr -> Bool
== LogStr
b = LogStr -> ByteString
fromLogStr LogStr
a ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== LogStr -> ByteString
fromLogStr LogStr
b

-- | Obtaining the length of 'LogStr'.
logStrLength :: LogStr -> Int
logStrLength :: LogStr -> Int
logStrLength (LogStr Int
n Builder
_) = Int
n

-- | Converting 'LogStr' to 'ByteString'.
fromLogStr :: LogStr -> ByteString
fromLogStr :: LogStr -> ByteString
fromLogStr (LogStr Int
_ Builder
builder) = Builder -> ByteString
fromBuilder Builder
builder