Skip to content
Snippets Groups Projects
Commit e661fd8e authored by bos's avatar bos
Browse files

Deduplicate

parent e33c89be
No related branches found
No related tags found
No related merge requests found
......@@ -58,13 +58,11 @@ module Data.Text.Internal.Builder
) where
import Control.Monad.ST (ST, runST)
import Data.Bits ((.&.))
import Data.Monoid (Monoid(..))
import Data.Text.Internal (Text(..))
import Data.Text.Internal.Lazy (smallChunkSize)
import Data.Text.Unsafe (inlineInterleaveST)
import Data.Text.Internal.Unsafe.Char (ord, unsafeWrite)
import Data.Text.Internal.Unsafe.Shift (shiftR)
import Data.Text.Internal.Unsafe.Char (unsafeWrite)
import Prelude hiding (map, putChar)
import qualified Data.String as String
......@@ -127,17 +125,7 @@ empty = Builder (\ k buf -> k buf)
-- * @'toLazyText' ('singleton' c) = 'L.singleton' c@
--
singleton :: Char -> Builder
singleton c = writeAtMost 2 $ \ marr o ->
if n < 0x10000
then A.unsafeWrite marr o (fromIntegral n) >> return 1
else do
A.unsafeWrite marr o lo
A.unsafeWrite marr (o+1) hi
return 2
where n = ord c
m = n - 0x10000
lo = fromIntegral $ (m `shiftR` 10) + 0xD800
hi = fromIntegral $ (m .&. 0x3FF) + 0xDC00
singleton c = writeAtMost 2 $ \ marr o -> unsafeWrite marr o c
{-# INLINE singleton #-}
------------------------------------------------------------------------
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment