File: LogStr.hs

package info (click to toggle)
haskell-fast-logger 3.2.4-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 168 kB
  • sloc: haskell: 898; makefile: 3
file content (174 lines) | stat: -rw-r--r-- 5,141 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Trustworthy #-}

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
#if MIN_VERSION_text(2,0,0)
import qualified Data.Text.Foreign as T
#endif
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL

import System.Log.FastLogger.Imports

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

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

fromBuilder :: Builder -> ByteString
#if MIN_VERSION_bytestring(0,10,0)
fromBuilder = BL.toStrict . 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 s1 b1 <> LogStr s2 b2 = LogStr (s1 + s2) (b1 <> b2)
instance Monoid LogStr where
    mempty = LogStr 0 (toBuilder BS.empty)
#else
instance Monoid LogStr where
    mempty = LogStr 0 (toBuilder BS.empty)
    {-# INLINE mappend #-}
    LogStr s1 b1 `mappend` LogStr s2 b2 = LogStr (s1 + s2) (b1 <> b2)
#endif

instance IsString LogStr where
    {-# INLINE fromString #-}
    fromString = toLogStr . 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 = id
instance ToLogStr S8.ByteString where
    {-# INLINE toLogStr #-}
    toLogStr bs = LogStr (BS.length bs) (toBuilder bs)
instance ToLogStr BL.ByteString where
    {-# INLINE toLogStr #-}
    toLogStr b = LogStr (fromIntegral (BL.length b)) (B.lazyByteString b)
instance ToLogStr Builder where
    {-# INLINE toLogStr #-}
    toLogStr x = let b = B.toLazyByteString x in LogStr (fromIntegral (BL.length b)) (B.lazyByteString b)
instance ToLogStr SBS.ShortByteString where
    {-# INLINE toLogStr #-}
    toLogStr b = LogStr (SBS.length b) (B.shortByteString b)
instance ToLogStr String where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . TL.pack
instance ToLogStr T.Text where
    {-# INLINE toLogStr #-}
#if MIN_VERSION_text(2,0,0)
    toLogStr t = LogStr (T.lengthWord8 t) (T.encodeUtf8Builder t)
#else
    toLogStr = toLogStr . T.encodeUtf8
#endif
instance ToLogStr TL.Text where
    {-# INLINE toLogStr #-}
#if MIN_VERSION_text(2,0,0)
    toLogStr t = LogStr (TL.foldlChunks (\n c -> T.lengthWord8 c + n) 0 t) (TL.encodeUtf8Builder t)
#else
    toLogStr = toLogStr . TL.encodeUtf8
#endif
-- | @since 2.4.14
instance ToLogStr Int where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.intDec
-- | @since 2.4.14
instance ToLogStr Int8 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.int8Dec
-- | @since 2.4.14
instance ToLogStr Int16 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.int16Dec
-- | @since 2.4.14
instance ToLogStr Int32 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.int32Dec
-- | @since 2.4.14
instance ToLogStr Int64 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.int64Dec

-- | @since 2.4.14
instance ToLogStr Word where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.wordDec
-- | @since 2.4.14
instance ToLogStr Word8 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.word8Dec
-- | @since 2.4.14
instance ToLogStr Word16 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.word16Dec
-- | @since 2.4.14
instance ToLogStr Word32 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.word32Dec
-- | @since 2.4.14
instance ToLogStr Word64 where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.word64Dec

-- | @since 2.4.14
instance ToLogStr Integer where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.integerDec
-- | @since 2.4.14
instance ToLogStr Float where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.floatDec
-- | @since 2.4.14
instance ToLogStr Double where
    {-# INLINE toLogStr #-}
    toLogStr = toLogStr . B.doubleDec

instance Show LogStr where
  show = show . T.decodeUtf8 . fromLogStr

instance Eq LogStr where
  a == b = fromLogStr a == fromLogStr b

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

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