1
1
{-# LANGUAGE BangPatterns #-}
2
- {-# LANGUAGE CPP #-}
3
2
4
3
-- |
5
4
-- Module: Data.Aeson.Encoding.Builder
@@ -47,6 +46,7 @@ import Data.ByteString.Builder.Scientific (scientificBuilder)
47
46
import Data.Char (chr , ord )
48
47
import Data.Monoid ((<>) )
49
48
import Data.Scientific (Scientific , base10Exponent , coefficient )
49
+ import Data.Text.Encoding (encodeUtf8BuilderEscaped )
50
50
import Data.Time (UTCTime (.. ))
51
51
import Data.Time.Calendar (Day (.. ), toGregorian )
52
52
import Data.Time.LocalTime
@@ -55,20 +55,6 @@ import qualified Data.HashMap.Strict as HMS
55
55
import qualified Data.Text as T
56
56
import qualified Data.Vector as V
57
57
58
- #if MIN_VERSION_bytestring(0,10,4)
59
- import Data.Text.Encoding (encodeUtf8BuilderEscaped )
60
- #else
61
- import Data.Bits ((.&.) )
62
- import Data.Text.Internal (Text (.. ))
63
- import Data.Text.Internal.Unsafe.Shift (shiftR )
64
- import Foreign.Ptr (minusPtr , plusPtr )
65
- import Foreign.Storable (poke )
66
- import qualified Data.ByteString.Builder.Internal as B
67
- import qualified Data.ByteString.Builder.Prim.Internal as BP
68
- import qualified Data.Text.Array as A
69
- import qualified Data.Text.Internal.Encoding.Utf16 as U16
70
- #endif
71
-
72
58
-- | Encode a JSON value to a "Data.ByteString" 'B.Builder'.
73
59
--
74
60
-- Use this function if you are encoding over the wire, or need to
@@ -268,62 +254,3 @@ twoDigits a = T (digit hi) (digit lo)
268
254
269
255
digit :: Int -> Char
270
256
digit x = chr (x + 48 )
271
-
272
- #if !(MIN_VERSION_bytestring(0,10,4))
273
- -- | Encode text using UTF-8 encoding and escape the ASCII characters using
274
- -- a 'BP.BoundedPrim'.
275
- --
276
- -- Use this function is to implement efficient encoders for text-based formats
277
- -- like JSON or HTML.
278
- {-# INLINE encodeUtf8BuilderEscaped #-}
279
- -- TODO: Extend documentation with references to source code in @blaze-html@
280
- -- or @aeson@ that uses this function.
281
- encodeUtf8BuilderEscaped :: BP. BoundedPrim Word8 -> Text -> B. Builder
282
- encodeUtf8BuilderEscaped be =
283
- -- manual eta-expansion to ensure inlining works as expected
284
- \ txt -> B. builder (mkBuildstep txt)
285
- where
286
- bound = max 4 $ BP. sizeBound be
287
-
288
- mkBuildstep (Text arr off len) ! k =
289
- outerLoop off
290
- where
291
- iend = off + len
292
-
293
- outerLoop ! i0 br@ (B. BufferRange op0 ope)
294
- | i0 >= iend = k br
295
- | outRemaining > 0 = goPartial (i0 + min outRemaining inpRemaining)
296
- -- TODO: Use a loop with an integrated bound's check if outRemaining
297
- -- is smaller than 8, as this will save on divisions.
298
- | otherwise = return $ B. bufferFull bound op0 (outerLoop i0)
299
- where
300
- outRemaining = (ope `minusPtr` op0) `div` bound
301
- inpRemaining = iend - i0
302
-
303
- goPartial ! iendTmp = go i0 op0
304
- where
305
- go ! i ! op
306
- | i < iendTmp = case A. unsafeIndex arr i of
307
- w | w <= 0x7F ->
308
- BP. runB be (fromIntegral w) op >>= go (i + 1 )
309
- | w <= 0x7FF -> do
310
- poke8 0 $ (w `shiftR` 6 ) + 0xC0
311
- poke8 1 $ (w .&. 0x3f ) + 0x80
312
- go (i + 1 ) (op `plusPtr` 2 )
313
- | 0xD800 <= w && w <= 0xDBFF -> do
314
- let c = ord $ U16. chr2 w (A. unsafeIndex arr (i+ 1 ))
315
- poke8 0 $ (c `shiftR` 18 ) + 0xF0
316
- poke8 1 $ ((c `shiftR` 12 ) .&. 0x3F ) + 0x80
317
- poke8 2 $ ((c `shiftR` 6 ) .&. 0x3F ) + 0x80
318
- poke8 3 $ (c .&. 0x3F ) + 0x80
319
- go (i + 2 ) (op `plusPtr` 4 )
320
- | otherwise -> do
321
- poke8 0 $ (w `shiftR` 12 ) + 0xE0
322
- poke8 1 $ ((w `shiftR` 6 ) .&. 0x3F ) + 0x80
323
- poke8 2 $ (w .&. 0x3F ) + 0x80
324
- go (i + 1 ) (op `plusPtr` 3 )
325
- | otherwise =
326
- outerLoop i (B. BufferRange op ope)
327
- where
328
- poke8 j v = poke (op `plusPtr` j) (fromIntegral v :: Word8 )
329
- #endif
0 commit comments