module Blaze.ByteString.Builder.Char.Utf8
(
writeChar
, fromChar
, fromString
, fromShow
, fromText
, fromLazyText
) where
import Foreign
import Data.Char (ord)
import qualified Data.Text as TS
import qualified Data.Text.Encoding as TS
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TS
import Blaze.ByteString.Builder.Internal
writeChar :: Char -> Write
writeChar c = boundedWrite 4 (encodeCharUtf8 f1 f2 f3 f4 c)
where
f1 x1 = pokeN 1 $ \op -> do pokeByteOff op 0 x1
f2 x1 x2 = pokeN 2 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2
f3 x1 x2 x3 = pokeN 3 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2
pokeByteOff op 2 x3
f4 x1 x2 x3 x4 = pokeN 4 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2
pokeByteOff op 2 x3
pokeByteOff op 3 x4
encodeCharUtf8 :: (Word8 -> a)
-> (Word8 -> Word8 -> a)
-> (Word8 -> Word8 -> Word8 -> a)
-> (Word8 -> Word8 -> Word8 -> Word8 -> a)
-> Char
-> a
encodeCharUtf8 f1 f2 f3 f4 c = case ord c of
x | x <= 0x7F -> f1 $ fromIntegral x
| x <= 0x07FF ->
let x1 = fromIntegral $ (x `shiftR` 6) + 0xC0
x2 = fromIntegral $ (x .&. 0x3F) + 0x80
in f2 x1 x2
| x <= 0xFFFF ->
let x1 = fromIntegral $ (x `shiftR` 12) + 0xE0
x2 = fromIntegral $ ((x `shiftR` 6) .&. 0x3F) + 0x80
x3 = fromIntegral $ (x .&. 0x3F) + 0x80
in f3 x1 x2 x3
| otherwise ->
let x1 = fromIntegral $ (x `shiftR` 18) + 0xF0
x2 = fromIntegral $ ((x `shiftR` 12) .&. 0x3F) + 0x80
x3 = fromIntegral $ ((x `shiftR` 6) .&. 0x3F) + 0x80
x4 = fromIntegral $ (x .&. 0x3F) + 0x80
in f4 x1 x2 x3 x4
fromChar :: Char -> Builder
fromChar = fromWriteSingleton writeChar
fromString :: String -> Builder
fromString = fromWriteList writeChar
fromShow :: Show a => a -> Builder
fromShow = fromString . show
fromText :: TS.Text -> Builder
fromText = fromString . TS.unpack
fromLazyText :: TL.Text -> Builder
fromLazyText = fromString . TL.unpack